summaryrefslogtreecommitdiffstats
path: root/fortran/examples/grpit.f90
diff options
context:
space:
mode:
authorBill Wendling <wendling@ncsa.uiuc.edu>2000-09-19 20:06:49 (GMT)
committerBill Wendling <wendling@ncsa.uiuc.edu>2000-09-19 20:06:49 (GMT)
commit8055378bcecfc77af85b2bb07e7904edc9492789 (patch)
tree01c100c34cd727b9dc15ae21c89b6e0dfa361303 /fortran/examples/grpit.f90
parent8272da0b67a9ef3a7299fd10cc5f3ccbf80cbeae (diff)
downloadhdf5-8055378bcecfc77af85b2bb07e7904edc9492789.zip
hdf5-8055378bcecfc77af85b2bb07e7904edc9492789.tar.gz
hdf5-8055378bcecfc77af85b2bb07e7904edc9492789.tar.bz2
[svn-r2576] Purpose:
Adding the Fortran interface to the HDF5 library Description: Fortran is now a subdirectory of the HDF5 library tree. Platforms tested: Solaris and IRIX (O2K)
Diffstat (limited to 'fortran/examples/grpit.f90')
-rw-r--r--fortran/examples/grpit.f90189
1 files changed, 189 insertions, 0 deletions
diff --git a/fortran/examples/grpit.f90 b/fortran/examples/grpit.f90
new file mode 100644
index 0000000..66fb09e
--- /dev/null
+++ b/fortran/examples/grpit.f90
@@ -0,0 +1,189 @@
+!
+! In this example we iterate through the members of the groups.
+!
+
+
+ PROGRAM GRPITEXAMPLE
+
+ USE HDF5 ! This module contains all necessary modules
+
+ IMPLICIT NONE
+
+ CHARACTER(LEN=11), PARAMETER :: filename = "iteratef.h5" ! File name
+ CHARACTER(LEN=7), PARAMETER :: groupname1 = "MyGroup" ! Group name
+ CHARACTER(LEN=15), PARAMETER :: groupname2 = "Group_A" ! Group name
+ CHARACTER(LEN=13), PARAMETER :: dsetname1 = "dset1" ! Dataset name
+ CHARACTER(LEN=5), PARAMETER :: dsetname2 = "dset2" !
+
+ CHARACTER(LEN=20) :: name_buffer ! Buffer to hold object's name
+ INTEGER :: type ! Type of the object
+ INTEGER :: nmembers ! Number of group members
+
+ INTEGER(HID_T) :: file_id ! File identifier
+ INTEGER(HID_T) :: dataset1_id ! Dataset1 identifier
+ INTEGER(HID_T) :: dataset2_id ! Dataset2 identifier
+ INTEGER(HID_T) :: dataspace1_id ! Data space identifier
+ INTEGER(HID_T) :: dataspace2_id ! Data space identifier
+ INTEGER(HID_T) :: group1_id, group2_id ! Group identifiers
+
+ INTEGER :: i, j
+
+ INTEGER :: error ! Error flag
+
+ INTEGER, DIMENSION(3,3) :: dset1_data ! Arrays to hold data
+ INTEGER, DIMENSION(2,10) :: dset2_data !
+
+ INTEGER(HSIZE_T), DIMENSION(2) :: dims1 = (/3,3/) ! Dataset dimensions
+ INTEGER(HSIZE_T), DIMENSION(2) :: dims2 = (/2,10/)!
+ INTEGER :: rank = 2 ! Datasets rank
+
+ !
+ ! Initialize dset1_data array.
+ !
+ do i = 1, 3
+ do j = 1, 3
+ dset1_data(i,j) = j;
+ end do
+ end do
+
+
+ !
+ ! Initialize dset2_data array.
+ !
+ do i = 1, 2
+ do j = 1, 10
+ dset2_data(i,j) = j;
+ end do
+ end do
+
+ !
+ ! Initialize FORTRAN predefined datatypes.
+ !
+ CALL h5init_types_f(error)
+
+ !
+ ! Create a new file using default properties.
+ !
+ CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, error)
+
+ !
+ ! Create group "MyGroup" in the root group using absolute name.
+ !
+ CALL h5gcreate_f(file_id, groupname1, group1_id, error)
+
+ !
+ ! Create group "Group_A" in group "MyGroup" using relative name.
+ !
+ CALL h5gcreate_f(group1_id, groupname2, group2_id, error)
+
+ !
+ ! Create the data space for the first dataset.
+ !
+ CALL h5screate_simple_f(rank, dims1, dataspace1_id, error)
+
+ !
+ ! Create a dataset in group "MyGroup" with default properties.
+ !
+ CALL h5dcreate_f(group1_id, dsetname1, H5T_NATIVE_INTEGER, dataspace1_id, &
+ dataset1_id, error)
+
+ !
+ ! Write the first dataset.
+ !
+ CALL h5dwrite_f(dataset1_id, H5T_NATIVE_INTEGER, dset1_data, error)
+
+ !
+ ! Create the data space for the second dataset.
+ !
+ CALL h5screate_simple_f(rank, dims2, dataspace2_id, error)
+
+ !
+ ! Create the second dataset in group "Group_A" with default properties
+ !
+ CALL h5dcreate_f(group2_id, dsetname2, H5T_NATIVE_INTEGER, dataspace2_id, &
+ dataset2_id, error)
+
+ !
+ ! Write the second dataset
+ !
+ CALL h5dwrite_f(dataset2_id, H5T_NATIVE_INTEGER, dset2_data, error)
+
+ !
+ ! Get number of members in the root group.
+ !
+ CALL h5gn_members_f(file_id, "/", nmembers, error)
+ write(*,*) "Number of root group member is " , nmembers
+
+ !
+ ! Print each group member's name and type.
+ !
+ do i = 0, nmembers - 1
+ CALL h5gget_obj_info_idx_f(file_id, "/", i, name_buffer, type, &
+ error)
+ write(*,*) name_buffer, type
+ end do
+
+ !
+ ! Get number of members in MyGroup.
+ !
+ CALL h5gn_members_f(file_id, "MyGroup", nmembers, error)
+ write(*,*) "Number of group MyGroup member is ", nmembers
+
+ !
+ ! Print each group member's name and type in "MyGroup" group.
+ !
+ do i = 0, nmembers - 1
+ CALL h5gget_obj_info_idx_f(file_id, groupname1, i, name_buffer, type, &
+ error)
+ write(*,*) name_buffer, type
+ end do
+
+
+ !
+ ! Get number of members in MyGroup/Group_A.
+ !
+ CALL h5gn_members_f(file_id, "MyGroup/Group_A", nmembers, error)
+ write(*,*) "Number of group MyGroup/Group_A member is ", nmembers
+
+ !
+ ! Print each group member's name and type in "MyGroup/Group_A" group.
+ !
+ do i = 0, nmembers - 1
+ CALL h5gget_obj_info_idx_f(file_id,"MyGroup/Group_A" , i, name_buffer, type, &
+ error)
+ write(*,*) name_buffer, type
+ end do
+
+ !
+ ! Close the dataspace for the first dataset.
+ !
+ CALL h5sclose_f(dataspace1_id, error)
+
+ !
+ ! Close the first dataset.
+ !
+ CALL h5dclose_f(dataset1_id, error)
+
+ !
+ ! Close the dataspace for the second dataset.
+ !
+ CALL h5sclose_f(dataspace2_id, error)
+
+ !
+ ! Close the second dataset.
+ !
+ CALL h5dclose_f(dataset2_id, error)
+
+ !
+ ! Close the groups.
+ !
+ CALL h5gclose_f(group1_id, error)
+
+ CALL h5gclose_f(group2_id, error)
+
+ !
+ ! Close the file.
+ !
+ CALL h5fclose_f(file_id, error)
+
+ END PROGRAM GRPITEXAMPLE