From fef182fd966c8c113a5bab02f19afca4c91f0ba5 Mon Sep 17 00:00:00 2001 From: Elena Pourmal Date: Thu, 26 Apr 2001 22:52:24 -0500 Subject: [svn-r3862] Purpose: Codemaintenance Description: read/write APIs have been changed. Solution: Made necessary changes to the source code. Platforms tested: Linux, Solaris 2.7, O2K, T3E --- fortran/examples/attrexample.f90 | 4 +++- fortran/examples/compound.f90 | 12 +++++++----- fortran/examples/grpdsetexample.f90 | 9 +++++++-- fortran/examples/grpit.f90 | 10 ++++++++-- fortran/examples/hyperslab.f90 | 14 ++++++++++---- fortran/examples/mountexample.f90 | 7 +++++-- fortran/examples/refobjexample.f90 | 10 ++++++---- fortran/examples/refregexample.f90 | 15 +++++++++------ fortran/examples/rwdsetexample.f90 | 7 +++++-- fortran/examples/selectele.f90 | 19 +++++++++++++------ 10 files changed, 73 insertions(+), 34 deletions(-) diff --git a/fortran/examples/attrexample.f90 b/fortran/examples/attrexample.f90 index 82167aa..99ff789 100644 --- a/fortran/examples/attrexample.f90 +++ b/fortran/examples/attrexample.f90 @@ -28,6 +28,7 @@ CHARACTER*80, DIMENSION(2) :: attr_data ! Attribute data INTEGER :: error ! Error flag + INTEGER, DIMENSION(7) :: data_dims ! @@ -71,7 +72,8 @@ ! ! Write the 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) ! ! Close the attribute. diff --git a/fortran/examples/compound.f90 b/fortran/examples/compound.f90 index a2bd6b0..0bb6672 100644 --- a/fortran/examples/compound.f90 +++ b/fortran/examples/compound.f90 @@ -48,6 +48,8 @@ DOUBLE PRECISION, DIMENSION(dimsize) :: double_member REAL, DIMENSION(dimsize) :: real_member INTEGER :: i + INTEGER, DIMENSION(7) :: data_dims + data_dims(1) = dimsize ! ! Initialize data buffer. ! @@ -145,10 +147,10 @@ ! ! 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, dt1_id, char_member, error, xfer_prp = plist_id) - CALL h5dwrite_f(dset_id, dt3_id, double_member, error, xfer_prp = plist_id) - CALL h5dwrite_f(dset_id, dt2_id, int_member, error, xfer_prp = plist_id) + CALL h5dwrite_f(dset_id, dt4_id, real_member, data_dims, error, xfer_prp = plist_id) + CALL h5dwrite_f(dset_id, dt1_id, char_member, data_dims, error, xfer_prp = plist_id) + 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. @@ -195,7 +197,7 @@ ! ! Read part of the datatset and display it. ! - CALL h5dread_f(dset_id, dt1_id, char_member_out, error) + CALL h5dread_f(dset_id, dt1_id, char_member_out, data_dims, error) write(*,*) (char_member_out(i), i=1, dimsize) ! diff --git a/fortran/examples/grpdsetexample.f90 b/fortran/examples/grpdsetexample.f90 index 1c2fe65..2822cf7 100644 --- a/fortran/examples/grpdsetexample.f90 +++ b/fortran/examples/grpdsetexample.f90 @@ -29,6 +29,7 @@ INTEGER(HSIZE_T), DIMENSION(2) :: dims1 = (/3,3/) ! Datasets dimensions INTEGER(HSIZE_T), DIMENSION(2) :: dims2 = (/2,10/)! + INTEGER, DIMENSION(7) :: data_dims INTEGER :: rank = 2 ! Datasets rank @@ -75,7 +76,9 @@ ! ! Write the first dataset. ! - CALL h5dwrite_f(dataset_id, H5T_NATIVE_INTEGER, dset1_data, error) + data_dims(1) = 3 + data_dims(2) = 3 + CALL h5dwrite_f(dataset_id, H5T_NATIVE_INTEGER, dset1_data, data_dims, error) ! ! Close the dataspace for the first dataset. @@ -106,7 +109,9 @@ ! ! Write the second dataset. ! - CALL h5dwrite_f(dataset_id, H5T_NATIVE_INTEGER, dset2_data, error) + data_dims(1) = 2 + data_dims(1) = 10 + CALL h5dwrite_f(dataset_id, H5T_NATIVE_INTEGER, dset2_data, data_dims, error) ! ! Close the dataspace for the second dataset. diff --git a/fortran/examples/grpit.f90 b/fortran/examples/grpit.f90 index 3aff2ad..3616eca 100644 --- a/fortran/examples/grpit.f90 +++ b/fortran/examples/grpit.f90 @@ -33,9 +33,11 @@ INTEGER, DIMENSION(3,3) :: dset1_data ! Arrays to hold data INTEGER, DIMENSION(2,10) :: dset2_data ! + INTEGER(HSIZE_T), DIMENSION(2) :: dims1 = (/3,3/) ! Dataset dimensions INTEGER(HSIZE_T), DIMENSION(2) :: dims2 = (/2,10/)! INTEGER :: rank = 2 ! Datasets rank + INTEGER, DIMENSION(7) :: data_dims ! ! Initialize dset1_data array. @@ -90,7 +92,9 @@ ! ! Write the first dataset. ! - CALL h5dwrite_f(dataset1_id, H5T_NATIVE_INTEGER, dset1_data, error) + data_dims(1) = 3 + data_dims(2) = 3 + CALL h5dwrite_f(dataset1_id, H5T_NATIVE_INTEGER, dset1_data, data_dims, error) ! ! Create the data space for the second dataset. @@ -106,7 +110,9 @@ ! ! Write the second dataset ! - CALL h5dwrite_f(dataset2_id, H5T_NATIVE_INTEGER, dset2_data, error) + data_dims(1) = 2 + data_dims(2) = 10 + CALL h5dwrite_f(dataset2_id, H5T_NATIVE_INTEGER, dset2_data, data_dims, error) ! ! Get number of members in the root group. diff --git a/fortran/examples/hyperslab.f90 b/fortran/examples/hyperslab.f90 index ec24d98..f8e6bfe 100644 --- a/fortran/examples/hyperslab.f90 +++ b/fortran/examples/hyperslab.f90 @@ -38,6 +38,7 @@ INTEGER :: i, j, k INTEGER :: error, error_n ! Error flags + INTEGER, DIMENSION(7) :: data_dims ! @@ -84,7 +85,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) ! ! Close the dataspace for the dataset. @@ -109,9 +112,9 @@ ! ! Initialize data_out array. ! - do i = 1, 7 + do k = 1, 3 do j = 1, 7 - do k = 1,3 + do i = 1, 7 data_out(i,j,k) = 0; end do end do @@ -154,7 +157,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) ! diff --git a/fortran/examples/mountexample.f90 b/fortran/examples/mountexample.f90 index f4341b2..ad5ad5a 100644 --- a/fortran/examples/mountexample.f90 +++ b/fortran/examples/mountexample.f90 @@ -68,6 +68,7 @@ ! Data buffers ! INTEGER, DIMENSION(NX,NY) :: data_in, data_out + INTEGER, DIMENSION(7) :: data_dims ! ! Initialize FORTRAN interface. @@ -118,7 +119,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) ! ! Close file, dataset and dataspace identifiers. @@ -152,7 +155,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) ! ! Print out the data. diff --git a/fortran/examples/refobjexample.f90 b/fortran/examples/refobjexample.f90 index fdbb26d..6eda815 100644 --- a/fortran/examples/refobjexample.f90 +++ b/fortran/examples/refobjexample.f90 @@ -35,7 +35,8 @@ TYPE(hobj_ref_t_f), DIMENSION(4) :: ref TYPE(hobj_ref_t_f), DIMENSION(4) :: ref_out INTEGER, DIMENSION(5) :: data = (/1, 2, 3, 4, 5/) - INTEGER :: class, ref_size + INTEGER :: class + INTEGER, DIMENSION(7) :: data_dims, ref_size ! ! Initialize FORTRAN interface. ! @@ -91,7 +92,7 @@ CALL h5rcreate_f(file_id, "/GROUP1/GROUP2", ref(2), error) CALL h5rcreate_f(file_id, dsetnamei, ref(3), error) CALL h5rcreate_f(file_id, "MyType", ref(4), error) - ref_size = size(ref) + ref_size(1) = size(ref) CALL h5dwrite_f(dsetr_id, H5T_STD_REF_OBJ, ref, ref_size, error) ! ! Close the dataset @@ -101,7 +102,7 @@ ! Reopen the dataset with object references and read references to the buffer ! CALL h5dopen_f(file_id, dsetnamer,dsetr_id,error) - ref_size = size(ref_out) + ref_size(1) = size(ref_out) CALL h5dread_f(dsetr_id, H5T_STD_REF_OBJ, ref_out, ref_size, error) ! ! Dereference the third reference. We know that it is a dataset. On practice @@ -112,7 +113,8 @@ ! ! Write data to the dataset. ! - CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data, error) + data_dims(1) = size(data) + CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, data, data_dims, error) if (error .eq. 0) write(*,*) "Data has been successfully written to the dataset " ! ! Dereference the fourth reference. We know that it is a datatype. On practice diff --git a/fortran/examples/refregexample.f90 b/fortran/examples/refregexample.f90 index 05fcf3f..de584fc 100644 --- a/fortran/examples/refregexample.f90 +++ b/fortran/examples/refregexample.f90 @@ -36,7 +36,8 @@ INTEGER(HSSIZE_T) , DIMENSION(2,3) :: coord INTEGER(SIZE_T) ::num_points = 3 ! Number of selected points INTEGER :: i, j - INTEGER :: ref_size + INTEGER, DIMENSION(7) :: ref_size + INTEGER, DIMENSION(7) :: data_dims coord = reshape((/1,1,2,7,1,9/), (/2,3/)) ! Coordinates of selected points data = reshape ((/1,1,1,2,2,2,3,3,3,4,4,4,5,5,5,6,6,6/), (/2,9/)) ! @@ -66,7 +67,9 @@ ! CALL h5dcreate_f(file_id, dsetnamev, H5T_NATIVE_INTEGER, space_id, & dsetv_id, 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 h5dclose_f(dsetv_id, error) ! ! Dataset with references @@ -93,7 +96,7 @@ ! ! Write dataset with the references. ! - ref_size = size(ref) + ref_size(1) = size(ref) CALL h5dwrite_f(dsetr_id, H5T_STD_REF_DSETREG, ref, ref_size, error) ! ! Close all objects. @@ -110,7 +113,7 @@ ! ! Read references to the dataset regions. ! - ref_size = size(ref_out) + ref_size(1) = size(ref_out) CALL h5dread_f(dsetr_id, H5T_STD_REF_DSETREG, ref_out, ref_size, error) ! ! Dereference the first reference. @@ -120,7 +123,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) write(*,*) "Hypeslab selection" write(*,*) @@ -139,7 +142,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) write(*,*) "Point selection" write(*,*) diff --git a/fortran/examples/rwdsetexample.f90 b/fortran/examples/rwdsetexample.f90 index 3bc0ecb..b3cc424 100644 --- a/fortran/examples/rwdsetexample.f90 +++ b/fortran/examples/rwdsetexample.f90 @@ -22,6 +22,7 @@ INTEGER :: i, j INTEGER, DIMENSION(4,6) :: dset_data, data_out ! Data buffers + INTEGER, DIMENSION(7) :: data_dims ! ! Initialize the dset_data array. @@ -50,12 +51,14 @@ ! ! 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) ! ! 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) ! ! Close the dataset. diff --git a/fortran/examples/selectele.f90 b/fortran/examples/selectele.f90 index e0f25c8..60e3241 100644 --- a/fortran/examples/selectele.f90 +++ b/fortran/examples/selectele.f90 @@ -50,6 +50,7 @@ INTEGER :: error ! Error flag LOGICAL :: status + INTEGER, DIMENSION(7) :: data_dims ! @@ -103,9 +104,11 @@ ! ! 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 h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, buf2, error) + CALL h5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, buf2, data_dims, error) ! ! Close the dataspace for the datasets. @@ -176,7 +179,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) ! @@ -187,7 +191,8 @@ ! ! Write value into the selected points in dataset2. ! - CALL H5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, val, error, & + data_dims(1) = 2 + CALL H5dwrite_f(dset2_id, H5T_NATIVE_INTEGER, val, data_dims, error, & mem_space_id=memspace, file_space_id=dataspace2) ! @@ -237,7 +242,9 @@ ! ! Read dataset from the first file. ! - 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) ! ! Display the data read from dataset "Copy1" @@ -250,7 +257,7 @@ ! ! Read dataset from the second file. ! - CALL h5dread_f(dset2_id, H5T_NATIVE_INTEGER, bufnew, error) + CALL h5dread_f(dset2_id, H5T_NATIVE_INTEGER, bufnew, data_dims, error) ! ! Display the data read from dataset "Copy2" -- cgit v0.12