diff options
Diffstat (limited to 'fortran/examples/compound.f90')
-rw-r--r-- | fortran/examples/compound.f90 | 44 |
1 files changed, 22 insertions, 22 deletions
diff --git a/fortran/examples/compound.f90 b/fortran/examples/compound.f90 index a315fb0..2005f41 100644 --- a/fortran/examples/compound.f90 +++ b/fortran/examples/compound.f90 @@ -1,4 +1,4 @@ -! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * +! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * ! Copyright by The HDF Group. * ! Copyright by the Board of Trustees of the University of Illinois. * ! All rights reserved. * @@ -11,7 +11,7 @@ ! is linked from the top-level documents page. It can also be found at * ! http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have * ! access to either file, you may request a copy from help@hdfgroup.org. * -! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * +! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * ! ! ! This program creates a dataset that is one dimensional array of @@ -26,23 +26,23 @@ PROGRAM COMPOUNDEXAMPLE - USE HDF5 ! This module contains all necessary modules - + USE HDF5 ! This module contains all necessary modules + IMPLICIT NONE CHARACTER(LEN=11), PARAMETER :: filename = "compound.h5" ! File name CHARACTER(LEN=8), PARAMETER :: dsetname = "Compound" ! Dataset name INTEGER, PARAMETER :: dimsize = 6 ! Size of the dataset - INTEGER(HID_T) :: file_id ! File identifier - INTEGER(HID_T) :: dset_id ! Dataset identifier + INTEGER(HID_T) :: file_id ! File identifier + INTEGER(HID_T) :: dset_id ! Dataset identifier INTEGER(HID_T) :: dspace_id ! Dataspace identifier INTEGER(HID_T) :: dtype_id ! Compound datatype identifier INTEGER(HID_T) :: dt1_id ! Memory datatype identifier (for character field) INTEGER(HID_T) :: dt2_id ! Memory datatype identifier (for integer field) INTEGER(HID_T) :: dt3_id ! Memory datatype identifier (for double precision field) INTEGER(HID_T) :: dt4_id ! Memory datatype identifier (for real field) - INTEGER(HID_T) :: dt5_id ! Memory datatype identifier + INTEGER(HID_T) :: dt5_id ! Memory datatype identifier INTEGER(HID_T) :: plist_id ! Dataset trasfer property INTEGER(SIZE_T) :: typesize @@ -52,7 +52,7 @@ INTEGER :: error ! Error flag INTEGER(SIZE_T) :: type_size ! Size of the datatype - INTEGER(SIZE_T) :: type_sizec ! Size of the character datatype + INTEGER(SIZE_T) :: type_sizec ! Size of the character datatype INTEGER(SIZE_T) :: type_sizei ! Size of the integer datatype INTEGER(SIZE_T) :: type_sized ! Size of the double precision datatype INTEGER(SIZE_T) :: type_sizer ! Size of the real datatype @@ -63,7 +63,7 @@ DOUBLE PRECISION, DIMENSION(dimsize) :: double_member REAL, DIMENSION(dimsize) :: real_member INTEGER :: i - INTEGER(HSIZE_T), DIMENSION(1) :: data_dims + INTEGER(HSIZE_T), DIMENSION(1) :: data_dims data_dims(1) = dimsize ! ! Initialize data buffer. @@ -71,8 +71,8 @@ do i = 1, dimsize char_member(i)(1:1) = char(65+i) char_member(i)(2:2) = char(65+i) - char_member_out(i)(1:1) = char(65) - char_member_out(i)(2:2) = char(65) + char_member_out(i)(1:1) = char(65) + char_member_out(i)(2:2) = char(65) int_member(i) = i double_member(i) = 2.* i real_member(i) = 3. * i @@ -91,10 +91,10 @@ ! ! Create a new file using default properties. - ! + ! CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, file_id, error) - ! + ! ! Create the dataspace. ! CALL h5screate_simple_f(rank, dims, dspace_id, error) @@ -141,8 +141,8 @@ CALL h5dcreate_f(file_id, dsetname, dtype_id, dspace_id, & dset_id, error) ! - ! Create memory types. We have to create a compound datatype - ! for each member we want to write. + ! Create memory types. We have to create a compound datatype + ! for each member we want to write. ! CALL h5tcreate_f(H5T_COMPOUND_F, type_sizec, dt1_id, error) offset = 0 @@ -167,9 +167,9 @@ CALL h5dwrite_f(dset_id, dt3_id, double_member, data_dims, error, xfer_prp = plist_id) CALL h5dwrite_f(dset_id, dt2_id, int_member, data_dims, error, xfer_prp = plist_id) - ! + ! ! End access to the dataset and release resources used by it. - ! + ! CALL h5dclose_f(dset_id, error) ! @@ -186,11 +186,11 @@ CALL h5tclose_f(dt4_id, error) CALL h5tclose_f(dt5_id, error) - ! + ! ! Close the file. ! CALL h5fclose_f(file_id, error) - + ! ! Open the file. ! @@ -227,6 +227,6 @@ ! CALL h5close_f(error) - END PROGRAM COMPOUNDEXAMPLE - - + END PROGRAM COMPOUNDEXAMPLE + + |