[svn-r22163] Added tests for optional parameters in h5ocopy_f.

Cleaned up comments by removing "C" notation comments

Tested: jam (gnu, intel)
        koala (intel)
This commit is contained in:
Scot Breitenfeld 2012-03-28 00:43:22 -05:00
parent e4291accaa
commit 0ce5cbc925

View File

@ -72,6 +72,7 @@ SUBROUTINE test_h5o_link(total_error)
INTEGER(HID_T) :: type_id
INTEGER(HID_T) :: fapl_id
INTEGER(HID_T) :: lcpl_id
INTEGER(HID_T) :: ocpypl_id
INTEGER(HID_T) :: mem_space_id, file_space_id, xfer_prp
CHARACTER(LEN=11), PARAMETER :: TEST_FILENAME = 'TestFile.h5'
INTEGER, PARAMETER :: TEST6_DIM1 = 2, TEST6_DIM2 = 5
@ -82,57 +83,65 @@ SUBROUTINE test_h5o_link(total_error)
INTEGER, PARAMETER :: TRUE = 1, FALSE = 0
LOGICAL :: committed ! /* Whether the named datatype is committed */
LOGICAL :: committed ! /* Whether the named datatype is committed
INTEGER :: i, n, 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
! /* Initialize the raw data */
INTEGER(HSIZE_T), DIMENSION(1:1) :: dims2 = (/dim0/) ! size read/write buffer
INTEGER , DIMENSION(1:dim0) :: wdata2, & ! Write buffer
rdata2 ! Read buffer
! 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)
!!$ ret = H5Pset_libver_bounds(fapl_id, (new_format ? H5F_LIBVER_LATEST : H5F_LIBVER_EARLIEST), H5F_LIBVER_LATEST);
! /* 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)
@ -143,27 +152,27 @@ SUBROUTINE test_h5o_link(total_error)
CALL check("H5Tcommitted_f",error,total_error)
CALL verifyLogical("H5Tcommitted_f", committed, .TRUE., total_error)
! /* Create a dataset with no name using the committed datatype*/
! Create a dataset with no name using the committed datatype
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)
@ -171,31 +180,31 @@ SUBROUTINE test_h5o_link(total_error)
ENDDO
ENDDO
! /* Create a group with no name*/
! Create a group with no name
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)
! /* Link nameless group to root group and close the group ID*/
! Link nameless group to root group and close the group ID
CALL H5Olink_f(group_id, file_id, "/group", error)
CALL check("H5Olink_f", error, total_error)
@ -203,24 +212,24 @@ 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)
@ -228,22 +237,94 @@ SUBROUTINE test_h5o_link(total_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)
CALL check("h5pclose_f", error, total_error)
! *********************
! CHECK H5OCOPY_F
! *********************
DO i = 1, dim0
wdata2(i) = i-1
ENDDO
!
! Create dataspace. Setting size to be the current size.
!
CALL h5screate_simple_f(1, dims2, space_id, error)
CALL check("h5screate_simple_f", error, total_error)
!
! Create intermediate groups
!
CALL h5gcreate_f(file_id,"/G1",group_id,error)
CALL check("h5gcreate_f", error, total_error)
CALL h5gcreate_f(file_id,"/G1/G2",group_id,error)
CALL check("h5gcreate_f", error, total_error)
CALL h5gcreate_f(file_id,"/G1/G2/G3",group_id,error)
CALL check("h5gcreate_f", error, total_error)
!
! Create the dataset
!
CALL h5dcreate_f(group_id, dataset, H5T_STD_I32LE, space_id, dset_id, error)
CALL check("h5dcreate_f", error, total_error)
!
! Write the data to the dataset.
!
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, wdata2, dims2, error)
CALL check("h5dwrite_f", error, total_error)
!
! Close and release resources.
!
CALL h5dclose_f(dset_id , error)
CALL check(" h5dclose_f", error, total_error)
CALL h5sclose_f(space_id, error)
CALL check("h5sclose_f", error, total_error)
CALL h5gclose_f(group_id, error)
CALL check("h5gclose_f", error, total_error)
!
! create property to pass copy options
!
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)
!
! Check optional parameter lcpl_id, this would fail if lcpl_id was not specified
!
CALL h5ocopy_f(file_id, "/G1/G2/G3/DS1", file_id, "/G1/G_cp1/DS2", error, lcpl_id=lcpl_id)
CALL check("h5ocopy_f -- W/ OPTION: lcpl_id", error ,total_error)
CALL h5pclose_f(lcpl_id, error)
CALL check("h5pclose_f",error,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 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 check("h5ocopy_f",error,total_error)
! 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)
IF(error.EQ.0)THEN
CALL check("h5ocopy_f -- W/ OPTION: ocpypl_id", -1, total_error)
ENDIF
CALL h5pclose_f(ocpypl_id, error)
CALL check("h5pclose_f",error,total_error)
! create datatype
CALL h5tcopy_f(H5T_NATIVE_INTEGER, tid, error)
CALL check("h5tcopy_f", error, total_error)
! create named datatype
! create named datatype
CALL h5tcommit_f(file_id, NAME_DATATYPE_SIMPLE, tid, error)
CALL check("h5tcommit_f", error, total_error)
@ -282,11 +363,11 @@ SUBROUTINE test_h5o_link(total_error)
END SUBROUTINE test_h5o_link
!/****************************************************************
!***************************************************************
!**
!** test_h5o_plist(): Test object creation properties
!**
!****************************************************************/
!***************************************************************
SUBROUTINE test_h5o_plist(total_error)
@ -295,31 +376,31 @@ SUBROUTINE test_h5o_plist(total_error)
IMPLICIT NONE
INTEGER, INTENT(OUT) :: 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)
@ -327,11 +408,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)
@ -339,7 +420,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)
@ -356,18 +437,18 @@ SUBROUTINE test_h5o_plist(total_error)
CALL VERIFY("H5Pget_attr_phase_change_f", min_dense, (def_min_dense - 1), total_error)
!/* Create a group, dataset, and committed datatype within the file,
! * using the respective type of creation property lists.
! */
! 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)
@ -377,11 +458,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)
@ -392,7 +473,7 @@ SUBROUTINE test_h5o_plist(total_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)
@ -400,7 +481,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)
@ -412,7 +493,7 @@ SUBROUTINE test_h5o_plist(total_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)
@ -429,7 +510,7 @@ SUBROUTINE test_h5o_plist(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)
@ -447,11 +528,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)
@ -461,7 +542,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)
@ -472,7 +553,7 @@ SUBROUTINE test_h5o_plist(total_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)
@ -489,7 +570,7 @@ SUBROUTINE test_h5o_plist(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)
@ -508,7 +589,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)