2010-01-30 12:29:13 +08:00
|
|
|
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
|
2007-02-08 01:55:01 +08:00
|
|
|
! Copyright by The HDF Group. *
|
2003-04-16 06:28:05 +08:00
|
|
|
! Copyright by the Board of Trustees of the University of Illinois. *
|
|
|
|
! All rights reserved. *
|
|
|
|
! *
|
|
|
|
! This file is part of HDF5. The full HDF5 copyright notice, including *
|
|
|
|
! terms governing use, modification, and redistribution, is contained in *
|
2017-04-18 03:32:16 +08:00
|
|
|
! the COPYING file, which can be found at the root of the source code *
|
|
|
|
! distribution tree, or in https://support.hdfgroup.org/ftp/HDF5/releases. *
|
|
|
|
! If you do not have access to either file, you may request a copy from *
|
|
|
|
! help@hdfgroup.org. *
|
2010-01-30 12:29:13 +08:00
|
|
|
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
|
2003-04-16 06:28:05 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
!In the following example we create one file with a group in it,
|
2000-09-20 04:06:49 +08:00
|
|
|
!and another file with a dataset. Mounting is used to
|
2010-01-30 12:29:13 +08:00
|
|
|
!access the dataset from the second file as a member of a group
|
|
|
|
!in the first file.
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
|
|
|
|
PROGRAM MOUNTEXAMPLE
|
|
|
|
|
2010-01-30 12:29:13 +08:00
|
|
|
USE HDF5 ! This module contains all necessary modules
|
|
|
|
|
2000-09-20 04:06:49 +08:00
|
|
|
IMPLICIT NONE
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Filenames are "mount1.h5" and "mount2.h5"
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
CHARACTER(LEN=9), PARAMETER :: filename1 = "mount1.h5"
|
|
|
|
CHARACTER(LEN=9), PARAMETER :: filename2 = "mount2.h5"
|
|
|
|
|
|
|
|
!
|
|
|
|
!data space rank and dimensions
|
|
|
|
!
|
|
|
|
INTEGER, PARAMETER :: RANK = 2
|
|
|
|
INTEGER, PARAMETER :: NX = 4
|
|
|
|
INTEGER, PARAMETER :: NY = 5
|
|
|
|
|
|
|
|
!
|
|
|
|
! File identifiers
|
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
INTEGER(HID_T) :: file1_id, file2_id
|
|
|
|
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
! Group identifier
|
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
INTEGER(HID_T) :: gid
|
2000-09-20 04:06:49 +08:00
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Dataset identifier
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
INTEGER(HID_T) :: dset_id
|
2010-01-30 12:29:13 +08:00
|
|
|
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Data space identifier
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
INTEGER(HID_T) :: dataspace
|
2010-01-30 12:29:13 +08:00
|
|
|
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Data type identifier
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
INTEGER(HID_T) :: dtype_id
|
|
|
|
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! The dimensions for the dataset.
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
INTEGER(HSIZE_T), DIMENSION(2) :: dims = (/NX,NY/)
|
|
|
|
|
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
! Flag to check operation success
|
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
INTEGER :: error
|
|
|
|
|
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
! General purpose integer
|
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
INTEGER :: i, j
|
|
|
|
|
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
! Data buffers
|
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
INTEGER, DIMENSION(NX,NY) :: data_in, data_out
|
2004-04-23 01:18:46 +08:00
|
|
|
INTEGER(HSIZE_T), DIMENSION(2) :: data_dims
|
2000-09-20 04:06:49 +08:00
|
|
|
|
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
! Initialize FORTRAN interface.
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
CALL h5open_f(error)
|
2000-09-20 04:06:49 +08:00
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Initialize data_in buffer
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
do i = 1, NX
|
|
|
|
do j = 1, NY
|
|
|
|
data_in(i,j) = (i-1) + (j-1)
|
|
|
|
end do
|
|
|
|
end do
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Create first file "mount1.h5" using default properties.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5fcreate_f(filename1, H5F_ACC_TRUNC_F, file1_id, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Create group "/G" inside file "mount1.h5".
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5gcreate_f(file1_id, "/G", gid, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Close file and group identifiers.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5gclose_f(gid, error)
|
|
|
|
CALL h5fclose_f(file1_id, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Create second file "mount2.h5" using default properties.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5fcreate_f(filename2, H5F_ACC_TRUNC_F, file2_id, error)
|
|
|
|
|
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
! Create data space for the dataset.
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
CALL h5screate_simple_f(RANK, dims, dataspace, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Create dataset "/D" inside file "mount2.h5".
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5dcreate_f(file2_id, "/D", H5T_NATIVE_INTEGER, dataspace, &
|
|
|
|
dset_id, error)
|
2010-01-30 12:29:13 +08:00
|
|
|
|
2000-09-20 04:06:49 +08:00
|
|
|
!
|
|
|
|
! Write data_in to the dataset
|
|
|
|
!
|
2001-04-27 11:52:24 +08:00
|
|
|
data_dims(1) = NX
|
|
|
|
data_dims(2) = NY
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, data_dims, error)
|
2000-09-20 04:06:49 +08:00
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Close file, dataset and dataspace identifiers.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5sclose_f(dataspace, error)
|
|
|
|
CALL h5dclose_f(dset_id, error)
|
|
|
|
CALL h5fclose_f(file2_id, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Reopen both files.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5fopen_f (filename1, H5F_ACC_RDWR_F, file1_id, error)
|
|
|
|
CALL h5fopen_f (filename2, H5F_ACC_RDWR_F, file2_id, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Mount the second file under the first file's "/G" group.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5fmount_f (file1_id, "/G", file2_id, error)
|
|
|
|
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Access dataset D in the first file under /G/D name.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5dopen_f(file1_id, "/G/D", dset_id, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Get dataset's data type.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5dget_type_f(dset_id, dtype_id, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Read the dataset.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2001-04-27 11:52:24 +08:00
|
|
|
CALL h5dread_f(dset_id, dtype_id, data_out, data_dims, error)
|
2000-09-20 04:06:49 +08:00
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Print out the data.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
do i = 1, NX
|
|
|
|
print *, (data_out(i,j), j = 1, NY)
|
|
|
|
end do
|
|
|
|
|
|
|
|
|
|
|
|
!
|
|
|
|
!Close dset_id and dtype_id.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5dclose_f(dset_id, error)
|
|
|
|
CALL h5tclose_f(dtype_id, error)
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Unmount the second file.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5funmount_f(file1_id, "/G", error);
|
|
|
|
|
|
|
|
!
|
2000-11-04 03:49:59 +08:00
|
|
|
! Close both files.
|
2010-01-30 12:29:13 +08:00
|
|
|
!
|
2000-09-20 04:06:49 +08:00
|
|
|
CALL h5fclose_f(file1_id, error)
|
|
|
|
CALL h5fclose_f(file2_id, error)
|
2000-11-04 03:49:59 +08:00
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
! Close FORTRAN interface.
|
2000-11-04 03:49:59 +08:00
|
|
|
!
|
2010-01-30 12:29:13 +08:00
|
|
|
CALL h5close_f(error)
|
2000-09-20 04:06:49 +08:00
|
|
|
|
|
|
|
END PROGRAM MOUNTEXAMPLE
|
|
|
|
|