diff options
author | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2014-06-16 15:15:25 (GMT) |
---|---|---|
committer | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2014-06-16 15:15:25 (GMT) |
commit | 744bc7d236c18d65e9ac84e856f67e8ed145ef91 (patch) | |
tree | 7de2903b9bd1db3d387598ab47469e009db160e9 /fortran/test/tH5P_F03.f90 | |
parent | 588a733b189d7410ccf4dc7da56ef81f2b11604f (diff) | |
download | hdf5-744bc7d236c18d65e9ac84e856f67e8ed145ef91.zip hdf5-744bc7d236c18d65e9ac84e856f67e8ed145ef91.tar.gz hdf5-744bc7d236c18d65e9ac84e856f67e8ed145ef91.tar.bz2 |
[svn-r25286] Fix for:
HDFFV-8653
replace non-standard sizeof in the fortran tests with c_sizeof
Tested: jam (gnu, intel) with make and cmake.
Diffstat (limited to 'fortran/test/tH5P_F03.f90')
-rw-r--r-- | fortran/test/tH5P_F03.f90 | 23 |
1 files changed, 7 insertions, 16 deletions
diff --git a/fortran/test/tH5P_F03.f90 b/fortran/test/tH5P_F03.f90 index 6039a52..0f2f3de 100644 --- a/fortran/test/tH5P_F03.f90 +++ b/fortran/test/tH5P_F03.f90 @@ -106,20 +106,12 @@ SUBROUTINE test_create(total_error) INTEGER(hsize_t), DIMENSION(1:5), PARAMETER :: ch_size= (/1, 1, 1, 4, 1/) CHARACTER(LEN=14) :: filename ='test_create.h5' - ! /* compound datatype operations */ - TYPE, BIND(C) :: comp_datatype - REAL :: a - INTEGER :: x - DOUBLE PRECISION :: y - CHARACTER(LEN=1) :: z - END TYPE comp_datatype - TYPE(comp_datatype), TARGET :: rd_c, fill_ctype INTEGER :: error INTEGER(SIZE_T) :: h5off TYPE(C_PTR) :: f_ptr LOGICAL :: differ1, differ2 - + !/* ! * Create a file. ! */ @@ -136,8 +128,7 @@ SUBROUTINE test_create(total_error) CALL check("h5pset_chunk_f",error, total_error) ! /* Create a compound datatype */ - - CALL h5tcreate_f(H5T_COMPOUND_F, INT(SIZEOF(fill_ctype),size_t), comp_type_id, error) + CALL h5tcreate_f(H5T_COMPOUND_F, H5_SIZEOF(fill_ctype), comp_type_id, error) CALL check("h5tcreate_f", error, total_error) h5off = H5OFFSETOF(C_LOC(fill_ctype), C_LOC(fill_ctype%a)) CALL h5tinsert_f(comp_type_id, "a", h5off , H5T_NATIVE_REAL, error) @@ -412,7 +403,7 @@ SUBROUTINE test_h5p_file_image(total_error) ! Set file image f_ptr = C_LOC(buffer(1)) - size = SIZEOF(buffer) + size = H5_SIZEOF(buffer) CALL h5pset_file_image_f(fapl_1, f_ptr, size, error) CALL check("h5pset_file_image_f", error, total_error) @@ -505,13 +496,13 @@ SUBROUTINE external_test_offset(cleanup,total_error) ! Create the dataset CALL h5pcreate_f(H5P_DATASET_CREATE_F, dcpl, error) CALL check("h5pcreate_f", error, total_error) - CALL h5pset_external_f(dcpl, "extern_1a.raw", INT(0,off_t), INT(SIZEOF(part), hsize_t), error) + CALL h5pset_external_f(dcpl, "extern_1a.raw", INT(0,off_t), INT(H5_SIZEOF(part), hsize_t), error) CALL check("h5pset_external_f",error,total_error) - CALL h5pset_external_f(dcpl, "extern_2a.raw", INT(10,off_t), INT(SIZEOF(part), hsize_t), error) + CALL h5pset_external_f(dcpl, "extern_2a.raw", INT(10,off_t), INT(H5_SIZEOF(part), hsize_t), error) CALL check("h5pset_external_f",error,total_error) - CALL h5pset_external_f(dcpl, "extern_3a.raw", INT(20,off_t), INT(SIZEOF(part), hsize_t), error) + CALL h5pset_external_f(dcpl, "extern_3a.raw", INT(20,off_t), INT(H5_SIZEOF(part), hsize_t), error) CALL check("h5pset_external_f",error,total_error) - CALL h5pset_external_f(dcpl, "extern_4a.raw", INT(30,off_t), INT(SIZEOF(part), hsize_t), error) + CALL h5pset_external_f(dcpl, "extern_4a.raw", INT(30,off_t), INT(H5_SIZEOF(part), hsize_t), error) CALL check("h5pset_external_f",error,total_error) cur_size(1) = 100 |