From 9aba4e88c26d98aafaf231163e949b9a53aa9561 Mon Sep 17 00:00:00 2001 From: Elena Pourmal Date: Thu, 26 Apr 2001 22:50:22 -0500 Subject: [svn-r3861] Purpose: Code maintenance Description: read/write APIs have been changed. Solution: Made necessary changes to the tests. Platforms tested: Windows 98, Linux, Solaris 2.7, O2K, T3E --- fortran/test/fflush1.f90 | 5 ++++- fortran/test/fflush2.f90 | 5 ++++- fortran/test/tH5A.f90 | 33 ++++++++++++++++++++++----------- fortran/test/tH5D.f90 | 14 ++++++++++---- fortran/test/tH5F.f90 | 22 ++++++++++++++-------- fortran/test/tH5G.f90 | 6 ++++-- fortran/test/tH5I.f90 | 6 ++++-- fortran/test/tH5R.f90 | 27 +++++++++++++++++---------- fortran/test/tH5S.f90 | 17 +++++++++++++---- fortran/test/tH5Sselect.f90 | 33 ++++++++++++++++++++++++--------- fortran/test/tH5T.f90 | 18 ++++++++++-------- 11 files changed, 126 insertions(+), 60 deletions(-) diff --git a/fortran/test/fflush1.f90 b/fortran/test/fflush1.f90 index 89083eb..d71a7c0 100644 --- a/fortran/test/fflush1.f90 +++ b/fortran/test/fflush1.f90 @@ -67,6 +67,9 @@ !data buffers ! INTEGER, DIMENSION(NX,NY) :: data_in, data_out + INTEGER, DIMENSION(7) :: data_dims + data_dims(1) = NX + data_dims(2) = NY ! !Initialize FORTRAN predifined datatypes @@ -111,7 +114,7 @@ ! ! Write data_in to the dataset ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, error) + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! diff --git a/fortran/test/fflush2.f90 b/fortran/test/fflush2.f90 index a494d63..d7e5053 100644 --- a/fortran/test/fflush2.f90 +++ b/fortran/test/fflush2.f90 @@ -67,6 +67,9 @@ !data buffers ! INTEGER, DIMENSION(NX,NY) :: data_out + INTEGER, DIMENSION(7) :: data_dims + data_dims(1) = NX + data_dims(2) = NY ! !Initialize FORTRAN predifined datatypes @@ -95,7 +98,7 @@ ! !Read the dataset. ! - CALL h5dread_f(dset_id, dtype_id, data_out, error) + CALL h5dread_f(dset_id, dtype_id, data_out, data_dims, error) CALL check("h5dread_f",error,total_error) ! diff --git a/fortran/test/tH5A.f90 b/fortran/test/tH5A.f90 index a144317..d35a00f 100644 --- a/fortran/test/tH5A.f90 +++ b/fortran/test/tH5A.f90 @@ -70,6 +70,7 @@ DOUBLE PRECISION, DIMENSION(1) :: attr_double_data = 3.459 REAL, DIMENSION(1) :: attr_real_data = 4.0 INTEGER, DIMENSION(1) :: attr_integer_data = 5 + INTEGER, DIMENSION(7) :: data_dims CHARACTER :: aread_character_data ! variable to put read back Character attr data @@ -131,7 +132,9 @@ ! ! Write data_in to the dataset ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, error) + data_dims(1) = NX + data_dims(2) = NY + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! @@ -214,28 +217,32 @@ ! ! Write the String attribute data. ! - CALL h5awrite_f(attr_id, atype_id, attr_data, error) + data_dims(1) = 2 + CALL h5awrite_f(attr_id, atype_id, attr_data, data_dims, error) CALL check("h5awrite_f",error,total_error) ! ! Write the Character attribute data. ! - CALL h5awrite_f(attr2_id, atype2_id, attr_character_data, error) + CALL h5awrite_f(attr2_id, atype2_id, attr_character_data, data_dims, error) CALL check("h5awrite_f",error,total_error) ! ! Write the DOUBLE attribute data. ! - CALL h5awrite_f(attr3_id, atype3_id, attr_double_data, error) + data_dims(1) = 1 + CALL h5awrite_f(attr3_id, atype3_id, attr_double_data, data_dims, error) CALL check("h5awrite_f",error,total_error) ! ! Write the Real attribute data. ! - CALL h5awrite_f(attr4_id, atype4_id, attr_real_data, error) + data_dims(1) = 1 + CALL h5awrite_f(attr4_id, atype4_id, attr_real_data, data_dims, error) CALL check("h5awrite_f",error,total_error) ! ! Write the Integer attribute data. ! - CALL h5awrite_f(attr5_id, atype5_id, attr_integer_data, error) + data_dims(1) = 1 + CALL h5awrite_f(attr5_id, atype5_id, attr_integer_data, data_dims, error) CALL check("h5awrite_f",error,total_error) ! @@ -388,7 +395,8 @@ ! !read the string attribute data back to memory ! - CALL h5aread_f(attr_id, atype_id, aread_data, error) + data_dims(1) = 2 + CALL h5aread_f(attr_id, atype_id, aread_data, data_dims, error) CALL check("h5aread_f",error,total_error) if ( (aread_data(1) .ne. attr_data(1)) .or. (aread_data(2) .ne. attr_data(2)) ) then @@ -399,7 +407,7 @@ ! !read the CHARACTER attribute data back to memory ! - CALL h5aread_f(attr2_id, H5T_NATIVE_CHARACTER, aread_character_data, error) + CALL h5aread_f(attr2_id, H5T_NATIVE_CHARACTER, aread_character_data, data_dims, error) CALL check("h5aread_f",error,total_error) if (aread_character_data .ne. 'A' ) then write(*,*) "Read back character attrbute is wrong ",aread_character_data @@ -408,7 +416,8 @@ ! !read the double attribute data back to memory ! - CALL h5aread_f(attr3_id, H5T_NATIVE_DOUBLE, aread_double_data, error) + data_dims(1) = 1 + CALL h5aread_f(attr3_id, H5T_NATIVE_DOUBLE, aread_double_data, data_dims, error) CALL check("h5aread_f",error,total_error) if (aread_double_data(1) .ne. 3.459 ) then write(*,*) "Read back double attrbute is wrong", aread_double_data(1) @@ -417,7 +426,8 @@ ! !read the real attribute data back to memory ! - CALL h5aread_f(attr4_id, H5T_NATIVE_REAL, aread_real_data, error) + data_dims(1) = 1 + CALL h5aread_f(attr4_id, H5T_NATIVE_REAL, aread_real_data, data_dims, error) CALL check("h5aread_f",error,total_error) if (aread_real_data(1) .ne. 4.0 ) then write(*,*) "Read back real attrbute is wrong ", aread_real_data @@ -426,7 +436,8 @@ ! !read the Integer attribute data back to memory ! - CALL h5aread_f(attr5_id, H5T_NATIVE_INTEGER, aread_integer_data, error) + data_dims(1) = 1 + CALL h5aread_f(attr5_id, H5T_NATIVE_INTEGER, aread_integer_data, data_dims, error) CALL check("h5aread_f",error,total_error) if (aread_integer_data(1) .ne. 5 ) then write(*,*) "Read back integer attrbute is wrong ", aread_integer_data diff --git a/fortran/test/tH5D.f90 b/fortran/test/tH5D.f90 index 04ed534..781cbc1 100644 --- a/fortran/test/tH5D.f90 +++ b/fortran/test/tH5D.f90 @@ -35,6 +35,7 @@ INTEGER :: error ! Error flag INTEGER :: i, j !general purpose integers + INTEGER, DIMENSION(7) :: data_dims ! ! Initialize the dset_data array. @@ -75,7 +76,9 @@ ! ! Write the dataset. ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, error) + data_dims(1) = 4 + data_dims(2) = 6 + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, data_dims, error) CALL check("h5dwrite_f", error, total_error) @@ -124,7 +127,7 @@ ! ! Read the dataset. ! - CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, error) + CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, data_dims, error) CALL check("h5dread_f", error, total_error) ! @@ -242,6 +245,7 @@ ! INTEGER(HSIZE_T), DIMENSION(2) :: dimsr, maxdimsr INTEGER :: rankr + INTEGER, DIMENSION(7) :: data_dims ! !data initialization @@ -309,7 +313,9 @@ ! !Write the data of size 10X3 to the extended dataset. ! - CALL H5Dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, error) + data_dims(1) = 10 + data_dims(2) = 3 + CALL H5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! @@ -391,7 +397,7 @@ ! !Read data ! - CALL H5Dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, error, & + CALL H5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, & memspace, dataspace) CALL check("h5dread_f",error,total_error) diff --git a/fortran/test/tH5F.f90 b/fortran/test/tH5F.f90 index 9c8a9f9..31da85d 100644 --- a/fortran/test/tH5F.f90 +++ b/fortran/test/tH5F.f90 @@ -81,6 +81,7 @@ ! INTEGER, DIMENSION(NX,NY) :: data_in, data_out + INTEGER, DIMENSION(7) :: data_dims ! !Initialize FORTRAN predifined datatypes ! @@ -90,8 +91,8 @@ ! !Initialize data_in buffer ! - do i = 1, NX - do j = 1, NY + do j = 1, NY + do i = 1, NX data_in(i,j) = (i-1) + (j-1) end do end do @@ -139,7 +140,9 @@ ! ! Write data_in to the dataset ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, error) + data_dims(1) = NX + data_dims(2) = NY + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data_in, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! @@ -199,7 +202,7 @@ ! !Read the dataset. ! - CALL h5dread_f(dset_id, dtype_id, data_out, error) + CALL h5dread_f(dset_id, dtype_id, data_out, data_dims, error) CALL check("h5dread_f",error,total_error) ! @@ -304,12 +307,13 @@ !array to store data ! INTEGER, DIMENSION(4,6) :: dset_data, data_out + INTEGER, DIMENSION(7) :: data_dims ! !initialize the dset_data array which will be written to the "/dset" ! - do i = 1, NX - do j = 1, NY + do j = 1, NY + do i = 1, NX dset_data(i,j) = (i-1)*6 + j; end do end do @@ -343,7 +347,9 @@ ! !Write the dataset. ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, error) + data_dims(1) = NX + data_dims(2) = NY + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! @@ -373,7 +379,7 @@ ! !Read the dataset. ! - CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, error) + CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, data_dims, error) CALL check("h5dread_f",error,total_error) ! diff --git a/fortran/test/tH5G.f90 b/fortran/test/tH5G.f90 index 2ec6435..5486bb8 100644 --- a/fortran/test/tH5G.f90 +++ b/fortran/test/tH5G.f90 @@ -41,6 +41,7 @@ CHARACTER*100 :: commentout !comment to the file INTEGER :: nmembers INTEGER :: obj_type + INTEGER, DIMENSION(7) :: data_dims ! ! Create the file. ! @@ -74,7 +75,8 @@ ! ! Write data_in to dataset1 ! - CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, dset1_data, error) + data_dims(1) = 1 + CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, dset1_data, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! @@ -87,7 +89,7 @@ ! ! Write data_in to dataset2 ! - CALL h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, dset2_data, error) + CALL h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, dset2_data, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! diff --git a/fortran/test/tH5I.f90 b/fortran/test/tH5I.f90 index 075c26f..958453b 100644 --- a/fortran/test/tH5I.f90 +++ b/fortran/test/tH5I.f90 @@ -34,6 +34,7 @@ INTEGER :: type !object identifier INTEGER :: error ! Error flag + INTEGER, DIMENSION(7) :: data_dims ! @@ -64,7 +65,8 @@ ! ! Write data_in to the dataset ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, error) + data_dims(1) = 1 + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, dset_data, data_dims, error) CALL check("h5dwrite_f",error,total_error) ! @@ -89,7 +91,7 @@ ! ! Write the Integer attribute data. ! - CALL h5awrite_f(attr_id, atype_id, attr_data, error) + CALL h5awrite_f(attr_id, atype_id, attr_data, data_dims, error) CALL check("h5awrite_f",error,total_error) ! diff --git a/fortran/test/tH5R.f90 b/fortran/test/tH5R.f90 index 3975357..345345b 100644 --- a/fortran/test/tH5R.f90 +++ b/fortran/test/tH5R.f90 @@ -38,8 +38,9 @@ INTEGER :: rankr = 1 TYPE(hobj_ref_t_f), DIMENSION(4) :: ref TYPE(hobj_ref_t_f), DIMENSION(4) :: ref_out - INTEGER :: ref_dim + INTEGER, DIMENSION(7) :: ref_dim INTEGER, DIMENSION(5) :: data = (/1, 2, 3, 4, 5/) + INTEGER, DIMENSION(7) :: data_dims ! ! Initialize FORTRAN predefined datatypes @@ -124,7 +125,7 @@ CALL check("h5rcreate_f",error,total_error) CALL h5rcreate_f(file_id, "MyType", ref(4), error) CALL check("h5rcreate_f",error,total_error) - ref_dim = size(ref) + ref_dim(1) = size(ref) CALL h5dwrite_f(dsetr_id, H5T_STD_REF_OBJ, ref, ref_dim, error) CALL check("h5dwrite_f",error,total_error) @@ -138,7 +139,7 @@ ! CALL h5dopen_f(file_id, dsetnamer,dsetr_id,error) CALL check("h5dopen_f",error,total_error) - ref_dim = size(ref_out) + ref_dim(1) = size(ref_out) CALL h5dread_f(dsetr_id, H5T_STD_REF_OBJ, ref_out, ref_dim, error) CALL check("h5dread_f",error,total_error) @@ -151,7 +152,8 @@ CALL h5rdereference_f(dsetr_id, ref(3), dset1_id, error) CALL check("h5rdereference_f",error,total_error) - CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, data, error) + data_dims(1) = 5 + CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, data, data_dims, error) CALL check("h5dwrite_f",error,total_error) end if @@ -206,7 +208,8 @@ INTEGER :: error TYPE(hdset_reg_ref_t_f) , DIMENSION(2) :: ref ! Buffers to store references TYPE(hdset_reg_ref_t_f) , DIMENSION(2) :: ref_out ! - INTEGER :: ref_dim + INTEGER, DIMENSION(7) :: ref_dim + INTEGER, DIMENSION(7) :: data_dims INTEGER(HSIZE_T), DIMENSION(2) :: dims = (/2,9/) ! Datasets dimensions INTEGER(HSIZE_T), DIMENSION(1) :: dimsr = (/2/) ! INTEGER(HSSIZE_T), DIMENSION(2) :: start @@ -253,7 +256,9 @@ CALL h5dcreate_f(file_id, dsetnamev, H5T_NATIVE_INTEGER, space_id, & dsetv_id, error) CALL check("h5dcreate_f", error, total_error) - CALL h5dwrite_f(dsetv_id, H5T_NATIVE_INTEGER, data, error) + data_dims(1) = 2 + data_dims(2) = 9 + CALL h5dwrite_f(dsetv_id, H5T_NATIVE_INTEGER, data, data_dims, error) CALL check("h5dwrite_f", error, total_error) CALL h5dclose_f(dsetv_id, error) @@ -289,7 +294,7 @@ ! ! Write dataset with the references. ! - ref_dim = size(ref) + ref_dim(1) = size(ref) CALL h5dwrite_f(dsetr_id, H5T_STD_REF_DSETREG, ref, ref_dim, error) CALL check("h5dwrite_f", error, total_error) ! @@ -313,7 +318,7 @@ ! ! Read references to the dataset regions. ! - ref_dim = size(ref_out) + ref_dim(1) = size(ref_out) CALL h5dread_f(dsetr_id, H5T_STD_REF_DSETREG, ref_out, ref_dim, error) CALL check("h5dread_f", error, total_error) ! @@ -326,7 +331,9 @@ ! ! Read selected data from the dataset. ! - CALL h5dread_f(dsetv_id, H5T_NATIVE_INTEGER, data_out, error, & + data_dims(1) = 2 + data_dims(2) = 9 + CALL h5dread_f(dsetv_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, & mem_space_id = space_id, file_space_id = space_id) CALL check("h5dread_f", error, total_error) CALL h5sclose_f(space_id, error) @@ -345,7 +352,7 @@ ! ! Read selected data from the dataset. ! - CALL h5dread_f(dsetv_id, H5T_NATIVE_INTEGER, data_out, error, & + CALL h5dread_f(dsetv_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, & mem_space_id = space_id, file_space_id = space_id) CALL check("h5dread_f", error, total_error) ! diff --git a/fortran/test/tH5S.f90 b/fortran/test/tH5S.f90 index 7d64ada..c20c445 100644 --- a/fortran/test/tH5S.f90 +++ b/fortran/test/tH5S.f90 @@ -47,6 +47,7 @@ LOGICAL :: flag !flag to test datyspace is simple or not INTEGER :: i, j !general purpose integers + INTEGER, DIMENSION(7) :: data_dims ! ! Initialize the dset_data array. @@ -168,16 +169,22 @@ ! ! Write the datasets. ! - CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, data1_in, error) + data_dims(1) = 4 + data_dims(2) = 6 + CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, data1_in, data_dims, error) CALL check("h5dwrite_f", error, total_error) - CALL h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, data2_in, error) + data_dims(1) = 6 + data_dims(2) = 6 + CALL h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, data2_in, data_dims, error) CALL check("h5dwrite_f", error, total_error) ! ! Read the first dataset. ! - CALL h5dread_f(dset1_id, H5T_NATIVE_INTEGER, data1_out, error) + data_dims(1) = 4 + data_dims(2) = 6 + CALL h5dread_f(dset1_id, H5T_NATIVE_INTEGER, data1_out, data_dims, error) CALL check("h5dread_f", error, total_error) ! @@ -196,7 +203,9 @@ ! ! Read the second dataset. ! - CALL h5dread_f(dset2_id, H5T_NATIVE_INTEGER, data2_out, error) + data_dims(1) = 6 + data_dims(2) = 6 + CALL h5dread_f(dset2_id, H5T_NATIVE_INTEGER, data2_out, data_dims, error) CALL check("h5dread_f", error, total_error) ! diff --git a/fortran/test/tH5Sselect.f90 b/fortran/test/tH5Sselect.f90 index c7cd398..64d4916 100644 --- a/fortran/test/tH5Sselect.f90 +++ b/fortran/test/tH5Sselect.f90 @@ -104,6 +104,7 @@ !flag to check operation success ! INTEGER :: error, error_n + INTEGER, DIMENSION(7) :: data_dims ! @@ -154,7 +155,9 @@ ! ! Write the dataset ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data, error) + data_dims(1) = 5 + data_dims(2) = 6 + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data, data_dims, error) CALL check("h5dwrite_f", error, total_error) ! @@ -232,7 +235,10 @@ !Read data from hyperslab in the file into the hyperslab in !memory and display. ! - CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, error, & + data_dims(1) = 7 + data_dims(2) = 7 + data_dims(3) = 3 + CALL h5dread_f(dset_id, H5T_NATIVE_INTEGER, data_out, data_dims, error, & memspace, dataspace) CALL check("h5dread_f", error, total_error) @@ -373,6 +379,7 @@ ! INTEGER :: error LOGICAL :: status + INTEGER, DIMENSION(7) :: data_dims ! @@ -433,10 +440,12 @@ ! ! Write the datasets ! - CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, buf1, error) + data_dims(1) = 3 + data_dims(2) = 4 + CALL h5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, buf1, data_dims, error) CALL check("h5dwrite_f", error, total_error) - CALL h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, buf2, error) + CALL h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, buf2, data_dims, error) CALL check("h5dwrite_f", error, total_error) ! @@ -521,7 +530,8 @@ ! !Write value into the selected points in dataset1 ! - CALL H5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, val, error, & + data_dims(1) = 2 + CALL H5dwrite_f(dset1_id, H5T_NATIVE_INTEGER, val, data_dims, error, & mem_space_id=memspace, file_space_id=dataspace1) CALL check("h5dwrite_f", error, total_error) @@ -534,7 +544,7 @@ ! !Write value into the selected points in dataset2 ! - CALL H5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, val, error, & + CALL H5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, val, data_dims, error, & mem_space_id=memspace, file_space_id=dataspace2) CALL check("h5dwrite_f", error, total_error) @@ -596,7 +606,9 @@ ! !Read dataset1. ! - CALL h5dread_f(dset1_id, H5T_NATIVE_INTEGER, bufnew, error) + data_dims(1) = 3 + data_dims(2) = 4 + CALL h5dread_f(dset1_id, H5T_NATIVE_INTEGER, bufnew, data_dims, error) CALL check("h5dread_f", error, total_error) ! @@ -610,7 +622,7 @@ ! !Read dataset2. ! - CALL h5dread_f(dset2_id, H5T_NATIVE_INTEGER, bufnew, error) + CALL h5dread_f(dset2_id, H5T_NATIVE_INTEGER, bufnew, data_dims, error) CALL check("h5dread_f", error, total_error) ! @@ -772,6 +784,7 @@ !flag to check operation success ! INTEGER :: error, error_n + INTEGER, DIMENSION(7) :: data_dims ! !initialize the coord array to give the selected points' position @@ -824,7 +837,9 @@ ! ! Write the dataset ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data, error) + data_dims(1) = 5 + data_dims(2) = 6 + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data, data_dims, error) CALL check("h5dwrite_f", error, total_error) ! diff --git a/fortran/test/tH5T.f90 b/fortran/test/tH5T.f90 index 961f7e7..1182429 100644 --- a/fortran/test/tH5T.f90 +++ b/fortran/test/tH5T.f90 @@ -68,6 +68,8 @@ INTEGER(HSIZE_T), DIMENSION(3) :: array_dims=(/2,3,4/) INTEGER :: elements = 24 ! number of elements in the array_dims array. INTEGER(SIZE_T) :: sizechar + INTEGER, DIMENSION(7) :: data_dims + data_dims(1) = dimsize ! ! Initialize data buffer. ! @@ -193,13 +195,13 @@ ! ! Write data by fields in the datatype. Fields order is not important. ! - CALL h5dwrite_f(dset_id, dt4_id, real_member, error, xfer_prp = plist_id) + CALL h5dwrite_f(dset_id, dt4_id, real_member, data_dims, error, xfer_prp = plist_id) CALL check("h5dwrite_f", error, total_error) - CALL h5dwrite_f(dset_id, dt1_id, char_member, error, xfer_prp = plist_id) + CALL h5dwrite_f(dset_id, dt1_id, char_member, data_dims, error, xfer_prp = plist_id) CALL check("h5dwrite_f", error, total_error) - CALL h5dwrite_f(dset_id, dt3_id, double_member, error, xfer_prp = plist_id) + CALL h5dwrite_f(dset_id, dt3_id, double_member, data_dims, error, xfer_prp = plist_id) CALL check("h5dwrite_f", error, total_error) - CALL h5dwrite_f(dset_id, dt2_id, int_member, error, xfer_prp = plist_id) + CALL h5dwrite_f(dset_id, dt2_id, int_member, data_dims, error, xfer_prp = plist_id) CALL check("h5dwrite_f", error, total_error) ! @@ -372,7 +374,7 @@ ! ! Read part of the dataset ! - CALL h5dread_f(dset_id, dt1_id, char_member_out, error) + CALL h5dread_f(dset_id, dt1_id, char_member_out, data_dims, error) CALL check("h5dread_f", error, total_error) do i = 1, dimsize if (char_member_out(i) .ne. char_member(i)) then @@ -389,7 +391,7 @@ ! ! Read part of the dataset ! - CALL h5dread_f(dset_id, dt5_id, int_member_out, error) + CALL h5dread_f(dset_id, dt5_id, int_member_out, data_dims, error) CALL check("h5dread_f", error, total_error) do i = 1, dimsize if (int_member_out(i) .ne. int_member(i)) then @@ -407,7 +409,7 @@ ! ! Read part of the dataset ! - CALL h5dread_f(dset_id, dt3_id, double_member_out, error) + CALL h5dread_f(dset_id, dt3_id, double_member_out, data_dims, error) CALL check("h5dread_f", error, total_error) do i = 1, dimsize if (double_member_out(i) .ne. double_member(i)) then @@ -425,7 +427,7 @@ ! ! Read part of the dataset ! - CALL h5dread_f(dset_id, dt4_id, real_member_out, error) + CALL h5dread_f(dset_id, dt4_id, real_member_out, data_dims, error) CALL check("h5dread_f", error, total_error) do i = 1, dimsize if (real_member_out(i) .ne. real_member(i)) then -- cgit v0.12