summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5O.F90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5O.F90')
-rw-r--r--fortran/test/tH5O.F90138
1 files changed, 69 insertions, 69 deletions
diff --git a/fortran/test/tH5O.F90 b/fortran/test/tH5O.F90
index fa3787e..e8a226e 100644
--- a/fortran/test/tH5O.F90
+++ b/fortran/test/tH5O.F90
@@ -77,22 +77,22 @@ SUBROUTINE test_h5o_link(total_error)
INTEGER, PARAMETER :: TRUE = 1
- LOGICAL :: committed ! Whether the named datatype is committed
+ LOGICAL :: committed ! Whether the named datatype is committed
INTEGER :: i, j
- INTEGER :: error ! Value returned from API calls
+ INTEGER :: error ! Value returned from API calls
CHARACTER(LEN=14) :: NAME_DATATYPE_SIMPLE="H5T_NATIVE_INT"
CHARACTER(LEN=16) :: NAME_DATATYPE_SIMPLE2="H5T_NATIVE_INT-2"
INTEGER(HID_T) :: tid, tid2
LOGICAL :: flag
-
+
! Data for tested h5ocopy_f
CHARACTER(LEN=3) , PARAMETER :: dataset = "DS1"
INTEGER , PARAMETER :: dim0 = 4
INTEGER(HSIZE_T), DIMENSION(1:1) :: dims2 = (/dim0/) ! size read/write buffer
- INTEGER , DIMENSION(1:dim0) :: wdata2 ! Write buffer
+ INTEGER , DIMENSION(1:dim0) :: wdata2 ! Write buffer
LOGICAL :: link_exists
CHARACTER(LEN=8) :: chr_exact
CHARACTER(LEN=10) :: chr_lg
@@ -107,45 +107,45 @@ SUBROUTINE test_h5o_link(total_error)
INTEGER(HSSIZE_T) :: comment_size
INTEGER(SIZE_T) :: comment_size2
- ! Initialize the raw data
+ ! Initialize the raw data
DO i = 1, TEST6_DIM1
DO j = 1, TEST6_DIM2
wdata(i,j) = i*j
ENDDO
ENDDO
- ! Create the dataspace
+ ! Create the dataspace
CALL h5screate_simple_f(2, dims, space_id, error)
CALL check("h5screate_simple_f",error,total_error)
- ! Create LCPL with intermediate group creation flag set
+ ! Create LCPL with intermediate group creation flag set
CALL H5Pcreate_f(H5P_LINK_CREATE_F, lcpl_id, error)
CALL check("h5Pcreate_f",error,total_error)
CALL H5Pset_create_inter_group_f(lcpl_id, TRUE, error)
CALL check("H5Pset_create_inter_group_f",error,total_error)
- ! Loop over using new group format
+ ! Loop over using new group format
! for(new_format = FALSE; new_format <= TRUE; new_format++) {
- ! Make a FAPL that uses the "use the latest version of the format" bounds
+ ! Make a FAPL that uses the "use the latest version of the format" bounds
CALL H5Pcreate_f(H5P_FILE_ACCESS_F,fapl_id,error)
CALL check("h5Pcreate_f",error,total_error)
- ! Set the "use the latest version of the format" bounds for creating objects in the file
+ ! Set the "use the latest version of the format" bounds for creating objects in the file
CALL H5Pset_libver_bounds_f(fapl_id, H5F_LIBVER_LATEST_F, H5F_LIBVER_LATEST_F, error)
CALL check("H5Pset_libver_bounds_f",error, total_error)
- ! Create a new HDF5 file
+ ! Create a new HDF5 file
CALL H5Fcreate_f(TEST_FILENAME, H5F_ACC_TRUNC_F, file_id, error, H5P_DEFAULT_F, fapl_id)
CALL check("H5Fcreate_f", error, total_error)
- ! Close the FAPL
+ ! Close the FAPL
CALL h5pclose_f(fapl_id, error)
CALL check("h5pclose_f",error,total_error)
- ! Create and commit a datatype with no name
+ ! Create and commit a datatype with no name
CALL H5Tcopy_f( H5T_NATIVE_INTEGER, type_id, error)
CALL check("H5Tcopy_F",error,total_error)
@@ -160,22 +160,22 @@ SUBROUTINE test_h5o_link(total_error)
CALL H5Dcreate_anon_f(file_id, type_id, space_id, dset_id, error ) ! using no optional parameters
CALL check("H5Dcreate_anon_f",error,total_error)
!
- ! Verify that we can write to and read from the dataset
+ ! Verify that we can write to and read from the dataset
!
- ! Write the data to the dataset
+ ! Write the data to the dataset
!EP CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, wdata, dims, error, &
!EP mem_space_id=H5S_ALL_F, file_space_id=H5S_ALL_F, xfer_prp = H5P_DEFAULT_F)
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, wdata, dims, error)
CALL check("h5dwrite_f", error, total_error)
- ! Read the data back
+ ! Read the data back
!EP CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, rdata, dims, error, &
!EP mem_space_id=H5S_ALL_F, file_space_id=H5S_ALL_F, xfer_prp = H5P_DEFAULT_F)
CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, rdata, dims, error)
CALL check("h5dread_f", error, total_error)
- ! Verify the data
+ ! Verify the data
DO i = 1, TEST6_DIM1
DO j = 1, TEST6_DIM2
CALL verify("H5Dread_f",wdata(i,j),rdata(i,j),total_error)
@@ -188,21 +188,21 @@ SUBROUTINE test_h5o_link(total_error)
CALL H5Gcreate_anon_f(file_id, group_id, error)
CALL check("H5Gcreate_anon", error, total_error)
- ! Link nameless datatype into nameless group
+ ! Link nameless datatype into nameless group
CALL H5Olink_f(type_id, group_id, "datatype", error, H5P_DEFAULT_F)
CALL check("H5Olink_f", error, total_error)
- ! Link nameless dataset into nameless group with intermediate group
+ ! Link nameless dataset into nameless group with intermediate group
CALL H5Olink_f(dset_id, group_id, "inter_group/dataset", error, lcpl_id, H5P_DEFAULT_F)
CALL check("H5Olink_f", error, total_error)
- ! Close IDs for dataset and datatype
+ ! Close IDs for dataset and datatype
CALL h5dclose_f(dset_id, error)
CALL check("h5dclose_f", error, total_error)
CALL h5tclose_f(type_id, error)
CALL check("h5tclose_f", error, total_error)
- ! Re-open datatype using new link
+ ! Re-open datatype using new link
CALL H5Topen_f(group_id, "datatype", type_id, error)
CALL check("h5topen_f", error, total_error)
@@ -213,30 +213,30 @@ SUBROUTINE test_h5o_link(total_error)
CALL h5gclose_f(group_id, error)
CALL check("h5gclose_f",error,total_error)
- ! Open dataset through root group and verify its data
+ ! Open dataset through root group and verify its data
CALL H5Dopen_f(file_id, "/group/inter_group/dataset", dset_id, error)
CALL check("test_lcpl.h5dopen_f", error, total_error)
- ! Read data from dataset
+ ! Read data from dataset
!EP CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, rdata, dims, error, &
!EP H5S_ALL_F, H5S_ALL_F, xfer_prp = H5P_DEFAULT_F)
CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, rdata, dims, error)
CALL check("h5dread_f", error, total_error)
- ! Verify the data
+ ! Verify the data
DO i = 1, TEST6_DIM1
DO j = 1, TEST6_DIM2
CALL verify("H5Dread",wdata(i,j),rdata(i,j),total_error)
ENDDO
ENDDO
- ! Close open IDs
+ ! Close open IDs
CALL h5dclose_f(dset_id, error)
CALL check("h5dclose_f",error,total_error)
CALL h5tclose_f(type_id, error)
CALL check("h5tclose_f",error,total_error)
- ! Close remaining IDs
+ ! Close remaining IDs
CALL h5sclose_f(space_id, error)
CALL check("h5sclose_f",error,total_error)
CALL h5pclose_f(lcpl_id,error)
@@ -270,7 +270,7 @@ SUBROUTINE test_h5o_link(total_error)
comment_lg = ' '
- CALL h5oget_comment_by_name_f(file_id, "/G1/G2/G3", comment_lg, error)
+ CALL h5oget_comment_by_name_f(file_id, "/G1/G2/G3", comment_lg, error)
CALL check("h5oget_comment_by_name_f", error, total_error)
IF(comment_lg(1:13).NE.grp_comment)THEN
@@ -287,7 +287,7 @@ SUBROUTINE test_h5o_link(total_error)
comment_lg = ' '
- CALL h5oget_comment_by_name_f(file_id, "/G1/G2/G3"//' ', comment_lg, error)
+ CALL h5oget_comment_by_name_f(file_id, "/G1/G2/G3"//' ', comment_lg, error)
CALL check("h5oget_comment_by_name_f", error, total_error)
IF(comment_lg(1:13).NE.grp_comment)THEN
@@ -309,7 +309,7 @@ SUBROUTINE test_h5o_link(total_error)
! Try reading into a buffer that is the correct size
- CALL h5oget_comment_f(dset_id, comment, error)
+ CALL h5oget_comment_f(dset_id, comment, error)
CALL check("h5oget_comment_f", error, total_error)
IF(comment(1:15).NE.dset_comment(1:15))THEN
@@ -318,18 +318,18 @@ SUBROUTINE test_h5o_link(total_error)
! Try reading into a buffer that is to small
- CALL h5oget_comment_f(dset_id, comment_sm, error)
+ CALL h5oget_comment_f(dset_id, comment_sm, error)
CALL check("h5oget_comment_f", error, total_error)
IF(comment_sm(1:10).NE.dset_comment(1:10))THEN
CALL check("h5oget_comment_f", -1, total_error)
- ENDIF
+ ENDIF
! Try reading into a buffer that is larger then needed
comment_lg = ' '
- CALL h5oget_comment_f(dset_id, comment_lg, error)
+ CALL h5oget_comment_f(dset_id, comment_lg, error)
CALL check("h5oget_comment_f", error, total_error)
IF(comment_lg(1:15).NE.dset_comment)THEN
@@ -341,7 +341,7 @@ SUBROUTINE test_h5o_link(total_error)
!
! Check optional parameter
!
- CALL h5oget_comment_f(dset_id, comment_lg, error, comment_size)
+ CALL h5oget_comment_f(dset_id, comment_lg, error, comment_size)
CALL check("h5oget_comment_f", error, total_error)
IF( comment_size.NE.15)THEN
@@ -352,7 +352,7 @@ SUBROUTINE test_h5o_link(total_error)
! Try reading into a buffer that is the correct size
- CALL h5oget_comment_by_name_f(dset_id, ".", comment, error)
+ CALL h5oget_comment_by_name_f(dset_id, ".", comment, error)
CALL check("h5oget_comment_by_name_f", error, total_error)
IF(comment(1:15).NE.dset_comment(1:15))THEN
@@ -361,7 +361,7 @@ SUBROUTINE test_h5o_link(total_error)
! Try with trailing blanks in the name
- CALL h5oget_comment_by_name_f(dset_id, ". ", comment, error)
+ CALL h5oget_comment_by_name_f(dset_id, ". ", comment, error)
CALL check("h5oget_comment_by_name_f", error, total_error)
IF(comment(1:15).NE.dset_comment(1:15))THEN
@@ -371,7 +371,7 @@ SUBROUTINE test_h5o_link(total_error)
!
! Check optional parameter
!
- CALL h5oget_comment_by_name_f(dset_id, ". ", comment_lg, error, comment_size2)
+ CALL h5oget_comment_by_name_f(dset_id, ". ", comment_lg, error, comment_size2)
CALL check("h5oget_comment_by_name_f", error, total_error)
IF( comment_size2.NE.15)THEN
@@ -481,7 +481,7 @@ SUBROUTINE test_h5o_link(total_error)
CALL h5gclose_f(group_id, error)
CALL check("h5gclose_f", error, total_error)
- ! Test opening an object by index, note
+ ! Test opening an object by index, note
CALL h5oopen_by_idx_f(file_id, "/G1/G2/G3", H5_INDEX_NAME_F, H5_ITER_INC_F, 0_hsize_t, group_id, error)
CALL check("h5oopen_by_idx_f", error, total_error)
@@ -508,13 +508,13 @@ SUBROUTINE test_h5o_link(total_error)
CALL h5pcreate_f(H5P_OBJECT_COPY_F, ocpypl_id, error)
CALL check("h5Pcreate_f",error,total_error)
- CALL h5pset_copy_object_f(ocpypl_id, H5O_COPY_SHALLOW_HIERARCHY_F, error)
+ CALL h5pset_copy_object_f(ocpypl_id, H5O_COPY_SHALLOW_HIERARCHY_F, error)
CALL check("H5Pset_copy_object_f",error,total_error)
- CALL h5ocopy_f(file_id, "/G1/G2", file_id, "/G1/G_cp2", error, ocpypl_id=ocpypl_id)
+ CALL h5ocopy_f(file_id, "/G1/G2", file_id, "/G1/G_cp2", error, ocpypl_id=ocpypl_id)
CALL check("h5ocopy_f",error,total_error)
- ! Makes sure the "DS1" dataset was not copied since we set a
+ ! Makes sure the "DS1" dataset was not copied since we set a
! flag to copy only immediate members of a group.
! Therefore, this should fail.
CALL h5dopen_f(file_id, "/G1/G_cp2/DS1", dset_id, error)
@@ -578,31 +578,31 @@ SUBROUTINE test_h5o_plist(total_error)
IMPLICIT NONE
INTEGER, INTENT(INOUT) :: total_error
- INTEGER(hid_t) :: fid ! HDF5 File ID
- INTEGER(hid_t) :: grp, dset, dtype, dspace ! Object identifiers
- INTEGER(hid_t) :: fapl ! File access property list
- INTEGER(hid_t) :: gcpl, dcpl, tcpl ! Object creation properties
- INTEGER :: def_max_compact, def_min_dense ! Default phase change parameters
- INTEGER :: max_compact, min_dense ! Actual phase change parameters
- INTEGER :: error ! Value returned from API calls
+ INTEGER(hid_t) :: fid ! HDF5 File ID
+ INTEGER(hid_t) :: grp, dset, dtype, dspace ! Object identifiers
+ INTEGER(hid_t) :: fapl ! File access property list
+ INTEGER(hid_t) :: gcpl, dcpl, tcpl ! Object creation properties
+ INTEGER :: def_max_compact, def_min_dense ! Default phase change parameters
+ INTEGER :: max_compact, min_dense ! Actual phase change parameters
+ INTEGER :: error ! Value returned from API calls
CHARACTER(LEN=7), PARAMETER :: TEST_FILENAME = 'test.h5'
! PRINT*,'Testing object creation properties'
- ! Make a FAPL that uses the "use the latest version of the format" flag
+ ! Make a FAPL that uses the "use the latest version of the format" flag
CALL H5Pcreate_f(H5P_FILE_ACCESS_F, fapl, error)
CALL check("H5Pcreate_f", error, total_error)
- ! Set the "use the latest version of the format" bounds for creating objects in the file
+ ! Set the "use the latest version of the format" bounds for creating objects in the file
CALL H5Pset_libver_bounds_f(fapl, H5F_LIBVER_LATEST_F, H5F_LIBVER_LATEST_F, error)
CALL check("H5Pcreate_f", error, total_error)
- ! Create a new HDF5 file
+ ! Create a new HDF5 file
CALL H5Fcreate_f(TEST_FILENAME, H5F_ACC_TRUNC_F, fid, error, access_prp=fapl)
CALL check("H5Fcreate_f", error, total_error)
- ! Create group, dataset & named datatype creation property lists
+ ! Create group, dataset & named datatype creation property lists
CALL H5Pcreate_f(H5P_GROUP_CREATE_F, gcpl, error)
CALL check("H5Pcreate_f", error, total_error)
CALL H5Pcreate_f(H5P_DATASET_CREATE_F, dcpl, error)
@@ -610,11 +610,11 @@ SUBROUTINE test_h5o_plist(total_error)
CALL H5Pcreate_f(H5P_DATATYPE_CREATE_F, tcpl, error)
CALL check("H5Pcreate_f", error, total_error)
- ! Retrieve default attribute phase change values
+ ! Retrieve default attribute phase change values
CALL H5Pget_attr_phase_change_f(gcpl, def_max_compact, def_min_dense, error)
CALL check("H5Pget_attr_phase_change_f", error, total_error)
- ! Set non-default attribute phase change values on each creation property list
+ ! Set non-default attribute phase change values on each creation property list
CALL H5Pset_attr_phase_change_f(gcpl, def_max_compact+1, def_min_dense-1, error)
CALL check("H5Pget_attr_phase_change_f", error, total_error)
CALL H5Pset_attr_phase_change_f(dcpl, def_max_compact+1, def_min_dense-1, error)
@@ -622,7 +622,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL H5Pset_attr_phase_change_f(tcpl, def_max_compact+1, def_min_dense-1, error)
CALL check("H5Pget_attr_phase_change_f", error, total_error)
- ! Retrieve attribute phase change values on each creation property list and verify
+ ! Retrieve attribute phase change values on each creation property list and verify
CALL H5Pget_attr_phase_change_f(gcpl, max_compact, min_dense, error)
CALL check("H5Pget_attr_phase_change_f", error, total_error)
CALL verify("H5Pget_attr_phase_change_f", max_compact, (def_max_compact + 1), total_error)
@@ -640,16 +640,16 @@ SUBROUTINE test_h5o_plist(total_error)
! Create a group, dataset, and committed datatype within the file,
! using the respective type of creation property lists.
- !
+ !
- ! Create the group anonymously and link it in
+ ! Create the group anonymously and link it in
CALL H5Gcreate_anon_f(fid, grp, error, gcpl_id=gcpl)
CALL check("H5Gcreate_anon_f", error, total_error)
CALL H5Olink_f(grp, fid, "group", error)
CALL check("H5Olink_f", error, total_error)
- ! Commit the type inside the group anonymously and link it in
+ ! Commit the type inside the group anonymously and link it in
CALL h5tcopy_f(H5T_NATIVE_INTEGER, dtype, error)
CALL check("h5tcopy_f", error, total_error)
@@ -659,11 +659,11 @@ SUBROUTINE test_h5o_plist(total_error)
CALL H5Olink_f(dtype, fid, "datatype", error)
CALL check("H5Olink_f", error, total_error)
- ! Create the dataspace for the dataset.
+ ! Create the dataspace for the dataset.
CALL h5screate_f(H5S_SCALAR_F, dspace, error)
CALL check("h5screate_f",error,total_error)
- ! Create the dataset anonymously and link it in
+ ! Create the dataset anonymously and link it in
CALL H5Dcreate_anon_f(fid, H5T_NATIVE_INTEGER, dspace, dset, error, dcpl )
CALL check("H5Dcreate_anon_f",error,total_error)
@@ -673,7 +673,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL h5sclose_f(dspace, error)
CALL check("h5sclose_f",error,total_error)
- ! Close current creation property lists
+ ! Close current creation property lists
CALL h5pclose_f(gcpl,error)
CALL check("h5pclose_f", error, total_error)
CALL h5pclose_f(dcpl,error)
@@ -681,7 +681,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL h5pclose_f(tcpl,error)
CALL check("h5pclose_f", error, total_error)
- ! Retrieve each object's creation property list
+ ! Retrieve each object's creation property list
CALL H5Gget_create_plist_f(grp, gcpl, error)
CALL check("H5Gget_create_plist", error, total_error)
@@ -691,7 +691,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL H5Dget_create_plist_f(dset, dcpl, error)
CALL check("H5Dget_create_plist_f", error, total_error)
- ! Retrieve attribute phase change values on each creation property list and verify
+ ! Retrieve attribute phase change values on each creation property list and verify
CALL H5Pget_attr_phase_change_f(gcpl, max_compact, min_dense, error)
CALL check("H5Pget_attr_phase_change_f", error, total_error)
CALL verify("H5Pget_attr_phase_change_f", max_compact, (def_max_compact + 1), total_error)
@@ -707,7 +707,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL verify("H5Pget_attr_phase_change_f", max_compact, (def_max_compact + 1), total_error)
CALL verify("H5Pget_attr_phase_change_f", min_dense, (def_min_dense - 1), total_error)
- ! Close current objects
+ ! Close current objects
CALL h5pclose_f(gcpl,error)
CALL check("h5pclose_f", error, total_error)
CALL h5pclose_f(dcpl,error)
@@ -724,11 +724,11 @@ SUBROUTINE test_h5o_plist(total_error)
CALL check("h5dclose_f",error,total_error)
CALL h5fclose_f(fid, error)
CALL check("h5fclose_f",error,total_error)
- ! Re-open the file and check that the object creation properties persist
+ ! Re-open the file and check that the object creation properties persist
CALL h5fopen_f(TEST_FILENAME, H5F_ACC_RDONLY_F, fid, error, access_prp=fapl)
CALL check("H5fopen_f",error,total_error)
- ! Re-open objects
+ ! Re-open objects
CALL H5Gopen_f(fid, "group", grp, error)
CALL check("h5gopen_f", error, total_error)
@@ -738,7 +738,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL H5Dopen_f(fid, "dataset", dset, error)
CALL check("h5dopen_f", error, total_error)
- ! Retrieve each object's creation property list
+ ! Retrieve each object's creation property list
CALL H5Gget_create_plist_f(grp, gcpl, error)
CALL check("H5Gget_create_plist", error, total_error)
@@ -748,7 +748,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL H5Dget_create_plist_f(dset, dcpl, error)
CALL check("H5Dget_create_plist_f", error, total_error)
- ! Retrieve attribute phase change values on each creation property list and verify
+ ! Retrieve attribute phase change values on each creation property list and verify
CALL H5Pget_attr_phase_change_f(gcpl, max_compact, min_dense, error)
CALL check("H5Pget_attr_phase_change_f", error, total_error)
CALL verify("H5Pget_attr_phase_change_f", max_compact, (def_max_compact + 1), total_error)
@@ -764,7 +764,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL verify("H5Pget_attr_phase_change_f", max_compact, (def_max_compact + 1), total_error)
CALL verify("H5Pget_attr_phase_change_f", min_dense, (def_min_dense - 1), total_error)
- ! Close current objects
+ ! Close current objects
CALL h5pclose_f(gcpl,error)
CALL check("h5pclose_f", error, total_error)
CALL h5pclose_f(dcpl,error)
@@ -782,7 +782,7 @@ SUBROUTINE test_h5o_plist(total_error)
CALL h5fclose_f(fid, error)
CALL check("h5fclose_f",error,total_error)
- ! Close the FAPL
+ ! Close the FAPL
CALL H5Pclose_f(fapl, error)
CALL check("H5Pclose_f", error, total_error)