summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5Sselect.F90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5Sselect.F90')
-rw-r--r--fortran/test/tH5Sselect.F90438
1 files changed, 219 insertions, 219 deletions
diff --git a/fortran/test/tH5Sselect.F90 b/fortran/test/tH5Sselect.F90
index 8415bce..5f7ece7 100644
--- a/fortran/test/tH5Sselect.F90
+++ b/fortran/test/tH5Sselect.F90
@@ -26,12 +26,12 @@
! h5sselect_none_f, h5sselect_valid_f, h5sselect_hyperslab_f,
! h5sget_select_bounds_f, h5sget_select_elem_pointlist_f,
! h5sget_select_elem_npoints_f, h5sget_select_hyper_blocklist_f,
-! h5sget_select_hyper_nblocks_f, h5sget_select_npoints_f
+! h5sget_select_hyper_nblocks_f, h5sget_select_npoints_f
!
! CONTAINS SUBROUTINES
! test_select_hyperslab, test_select_element, test_basic_select,
! test_select_point, test_select_combine, test_select_bounds
-!
+!
!
!*****
MODULE TH5SSELECT
@@ -1033,12 +1033,12 @@ CONTAINS
!***************************************************************
SUBROUTINE test_select_point(cleanup, total_error)
-
+
IMPLICIT NONE
LOGICAL, INTENT(IN) :: cleanup
INTEGER, INTENT(INOUT) :: total_error
INTEGER(HID_T) :: xfer_plist
-
+
INTEGER, PARAMETER :: SPACE1_DIM1=3
INTEGER, PARAMETER :: SPACE1_DIM2=15
INTEGER, PARAMETER :: SPACE1_DIM3=13
@@ -1046,36 +1046,36 @@ SUBROUTINE test_select_point(cleanup, total_error)
INTEGER, PARAMETER :: SPACE2_DIM2=26
INTEGER, PARAMETER :: SPACE3_DIM1=15
INTEGER, PARAMETER :: SPACE3_DIM2=26
-
+
INTEGER, PARAMETER :: SPACE1_RANK=3
INTEGER, PARAMETER :: SPACE2_RANK=2
INTEGER, PARAMETER :: SPACE3_RANK=2
-
- ! Element selection information
+
+ ! Element selection information
INTEGER, PARAMETER :: POINT1_NPOINTS=10
- INTEGER(hid_t) ::fid1 ! HDF5 File IDs
- INTEGER(hid_t) ::dataset ! Dataset ID
- INTEGER(hid_t) ::sid1,sid2 ! Dataspace ID
+ INTEGER(hid_t) ::fid1 ! HDF5 File IDs
+ INTEGER(hid_t) ::dataset ! Dataset ID
+ INTEGER(hid_t) ::sid1,sid2 ! Dataspace ID
INTEGER(hsize_t), DIMENSION(1:3) :: dims1 = (/SPACE1_DIM1, SPACE1_DIM2, SPACE1_DIM3/)
INTEGER(hsize_t), DIMENSION(1:2) :: dims2 = (/SPACE2_DIM1, SPACE2_DIM2/)
INTEGER(hsize_t), DIMENSION(1:2) :: dims3 = (/SPACE3_DIM1, SPACE3_DIM2/)
-
- INTEGER(hsize_t), DIMENSION(1:SPACE1_RANK,1:POINT1_NPOINTS) :: coord1 ! Coordinates for point selection
- INTEGER(hsize_t), DIMENSION(1:SPACE1_RANK,1:POINT1_NPOINTS) :: temp_coord1 ! Coordinates for point selection
- INTEGER(hsize_t), DIMENSION(1:SPACE2_RANK,1:POINT1_NPOINTS) :: coord2 ! Coordinates for point selection
- INTEGER(hsize_t), DIMENSION(1:SPACE2_RANK,1:POINT1_NPOINTS) :: temp_coord2 ! Coordinates for point selection
- INTEGER(hsize_t), DIMENSION(1:SPACE3_RANK,1:POINT1_NPOINTS) :: coord3 ! Coordinates for point selection
- INTEGER(hsize_t), DIMENSION(1:SPACE3_RANK,1:POINT1_NPOINTS) :: temp_coord3 ! Coordinates for point selection
+
+ INTEGER(hsize_t), DIMENSION(1:SPACE1_RANK,1:POINT1_NPOINTS) :: coord1 ! Coordinates for point selection
+ INTEGER(hsize_t), DIMENSION(1:SPACE1_RANK,1:POINT1_NPOINTS) :: temp_coord1 ! Coordinates for point selection
+ INTEGER(hsize_t), DIMENSION(1:SPACE2_RANK,1:POINT1_NPOINTS) :: coord2 ! Coordinates for point selection
+ INTEGER(hsize_t), DIMENSION(1:SPACE2_RANK,1:POINT1_NPOINTS) :: temp_coord2 ! Coordinates for point selection
+ INTEGER(hsize_t), DIMENSION(1:SPACE3_RANK,1:POINT1_NPOINTS) :: coord3 ! Coordinates for point selection
+ INTEGER(hsize_t), DIMENSION(1:SPACE3_RANK,1:POINT1_NPOINTS) :: temp_coord3 ! Coordinates for point selection
INTEGER(hssize_t) :: npoints
-!!$ uint8_t *wbuf, buffer to write to disk
-!!$ *rbuf, buffer read from disk
-!!$ *tbuf; temporary buffer pointer
- INTEGER :: i,j; ! Counters
-! struct pnt_iter pi; Custom Pointer iterator struct
- INTEGER :: error ! Generic return value
+!!$ uint8_t *wbuf, buffer to write to disk
+!!$ *rbuf, buffer read from disk
+!!$ *tbuf; temporary buffer pointer
+ INTEGER :: i,j; ! Counters
+! struct pnt_iter pi; Custom Pointer iterator struct
+ INTEGER :: error ! Generic return value
CHARACTER(LEN=9) :: filename = 'h5s_hyper'
- CHARACTER(LEN=80) :: fix_filename
+ CHARACTER(LEN=80) :: fix_filename
CHARACTER(LEN=1), DIMENSION(1:SPACE2_DIM1,1:SPACE2_DIM2) :: wbuf
CALL h5_fixname_f(filename, fix_filename, H5P_DEFAULT_F, error)
@@ -1086,11 +1086,11 @@ SUBROUTINE test_select_point(cleanup, total_error)
xfer_plist = H5P_DEFAULT_F
! MESSAGE(5, ("Testing Element Selection Functions\n"));
- ! Allocate write & read buffers
+ ! Allocate write & read buffers
!!$ wbuf = HDmalloc(sizeof(uint8_t) * SPACE2_DIM1 * SPACE2_DIM2);
!!$ rbuf = HDcalloc(sizeof(uint8_t), (size_t)(SPACE3_DIM1 * SPACE3_DIM2));
!!$
- ! Initialize WRITE buffer
+ ! Initialize WRITE buffer
DO i = 1, SPACE2_DIM1
DO j = 1, SPACE2_DIM2
@@ -1101,20 +1101,20 @@ SUBROUTINE test_select_point(cleanup, total_error)
!!$ for(i=0, tbuf=wbuf; i<SPACE2_DIM1; i++)
!!$ for(j=0; j<SPACE2_DIM2; j++)
!!$ *tbuf++=(uint8_t)((i*SPACE2_DIM2)+j);
-
- ! Create file
+
+ ! Create file
CALL h5fcreate_f(fix_filename, H5F_ACC_TRUNC_F, fid1, error)
CALL check("h5fcreate_f", error, total_error)
-
- ! Create dataspace for dataset
+
+ ! Create dataspace for dataset
CALL h5screate_simple_f(SPACE1_RANK, dims1, sid1, error)
CALL check("h5screate_simple_f", error, total_error)
- ! Create dataspace for write buffer
+ ! Create dataspace for write buffer
CALL h5screate_simple_f(SPACE2_RANK, dims2, sid2, error)
CALL check("h5screate_simple_f", error, total_error)
- ! Select sequence of ten points for disk dataset
+ ! Select sequence of ten points for disk dataset
coord1(1,1)=1; coord1(2,1)=11; coord1(3,1)= 6;
coord1(1,2)=2; coord1(2,2)= 3; coord1(3,2)= 8;
coord1(1,3)=3; coord1(2,3)= 5; coord1(3,3)=10;
@@ -1129,7 +1129,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL h5sselect_elements_f(sid1, H5S_SELECT_SET_F, SPACE1_RANK, INT(POINT1_NPOINTS,size_t), coord1, error)
CALL check("h5sselect_elements_f", error, total_error)
- ! Verify correct elements selected
+ ! Verify correct elements selected
CALL h5sget_select_elem_pointlist_f(sid1, INT(0,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord1,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
@@ -1144,7 +1144,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL check("h5sget_select_npoints_f", error, total_error)
CALL verify("h5sget_select_npoints_f", INT(npoints), 10, total_error)
- ! Append another sequence of ten points to disk dataset
+ ! Append another sequence of ten points to disk dataset
coord1(1,1)=1; coord1(2,1)=3; coord1(3,1)= 1;
coord1(1,2)=2; coord1(2,2)=11; coord1(3,2)= 9;
@@ -1160,8 +1160,8 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL h5sselect_elements_f(sid1, H5S_SELECT_APPEND_F, SPACE1_RANK, INT(POINT1_NPOINTS,size_t), coord1, error)
CALL check("h5sselect_elements_f", error, total_error)
- ! Verify correct elements selected
-
+ ! Verify correct elements selected
+
CALL h5sget_select_elem_pointlist_f(sid1, INT(POINT1_NPOINTS,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord1,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
@@ -1175,7 +1175,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL check("h5sget_select_npoints_f", error, total_error)
CALL verify("h5sget_select_npoints_f", INT(npoints), 20, total_error)
- ! Select sequence of ten points for memory dataset
+ ! Select sequence of ten points for memory dataset
coord2(1,1)=13; coord2(2,1)= 4;
coord2(1,2)=16; coord2(2,2)=14;
coord2(1,3)= 8; coord2(2,3)=26;
@@ -1191,8 +1191,8 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL check("h5sselect_elements_f", error, total_error)
- ! Verify correct elements selected
-
+ ! Verify correct elements selected
+
CALL h5sget_select_elem_pointlist_f(sid2, INT(0,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord2,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
@@ -1202,9 +1202,9 @@ SUBROUTINE test_select_point(cleanup, total_error)
ENDDO
!!$
-!!$ Save points for later iteration
-!!$ (these are in the second half of the buffer, because we are prepending
-!!$ the next list of points to the beginning of the point selection list)
+!!$ Save points for later iteration
+!!$ (these are in the second half of the buffer, because we are prepending
+!!$ the next list of points to the beginning of the point selection list)
!!$ HDmemcpy(((char *)pi.coord)+sizeof(coord2),coord2,sizeof(coord2));
!!$
@@ -1212,7 +1212,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL check("h5sget_select_npoints_f", error, total_error)
CALL verify("h5sget_select_npoints_f", INT(npoints), 10, total_error)
- ! Append another sequence of ten points to memory dataset
+ ! Append another sequence of ten points to memory dataset
coord2(1,1)=25; coord2(2,1)= 1;
coord2(1,2)= 3; coord2(2,2)=26;
coord2(1,3)=14; coord2(2,3)=18;
@@ -1228,7 +1228,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL check("h5sselect_elements_f", error, total_error)
- ! Verify correct elements selected
+ ! Verify correct elements selected
CALL h5sget_select_elem_pointlist_f(sid2, INT(0,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord2,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
@@ -1241,26 +1241,26 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL check("h5sget_select_npoints_f", error, total_error)
CALL verify("h5sget_select_npoints_f", INT(npoints), 20, total_error)
-!!$ Save points for later iteration
+!!$ Save points for later iteration
!!$ HDmemcpy(pi.coord,coord2,sizeof(coord2));
- ! Create a dataset
+ ! Create a dataset
CALL h5dcreate_f(fid1, "Dataset1", H5T_NATIVE_CHARACTER, sid1, dataset, error)
CALL check("h5dcreate_f", error, total_error)
- ! Write selection to disk
+ ! Write selection to disk
CALL h5dwrite_f(dataset, H5T_NATIVE_CHARACTER, wbuf, dims2, error, sid2, sid1, xfer_plist)
CALL check("h5dwrite_f", error, total_error)
- ! Close memory dataspace
+ ! Close memory dataspace
CALL h5sclose_f(sid2, error)
CALL check("h5sclose_f", error, total_error)
- ! Create dataspace for reading buffer
+ ! Create dataspace for reading buffer
CALL h5screate_simple_f(SPACE3_RANK, dims3, sid2, error)
CALL check("h5screate_simple_f", error, total_error)
- ! Select sequence of points for read dataset
+ ! Select sequence of points for read dataset
coord3(1,1)= 1; coord3(2,1)= 3;
coord3(1,2)= 5; coord3(2,2)= 9;
coord3(1,3)=14; coord3(2,3)=14;
@@ -1275,7 +1275,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL h5sselect_elements_f(sid2, H5S_SELECT_SET_F, SPACE3_RANK, INT(POINT1_NPOINTS,size_t), coord3, error)
CALL check("h5sselect_elements_f", error, total_error)
- ! Verify correct elements selected
+ ! Verify correct elements selected
CALL h5sget_select_elem_pointlist_f(sid2, INT(0,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord3,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
DO i= 1, POINT1_NPOINTS
@@ -1287,7 +1287,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL check("h5sget_select_npoints_f", error, total_error)
CALL verify("h5sget_select_npoints_f", INT(npoints), 10, total_error)
- ! Append another sequence of ten points to disk dataset
+ ! Append another sequence of ten points to disk dataset
coord3(1,1)=15; coord3(2,1)=26;
coord3(1,2)= 1; coord3(2,2)= 1;
coord3(1,3)=12; coord3(2,3)=12;
@@ -1302,7 +1302,7 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL h5sselect_elements_f(sid2, H5S_SELECT_APPEND_F, SPACE3_RANK, INT(POINT1_NPOINTS,size_t), coord3, error)
CALL check("h5sselect_elements_f", error, total_error)
- ! Verify correct elements selected
+ ! Verify correct elements selected
CALL h5sget_select_elem_pointlist_f(sid2, INT(POINT1_NPOINTS,hsize_t), INT(POINT1_NPOINTS,hsize_t),temp_coord3,error)
CALL check("h5sget_select_elem_pointlist_f", error, total_error)
DO i= 1, POINT1_NPOINTS
@@ -1315,11 +1315,11 @@ SUBROUTINE test_select_point(cleanup, total_error)
CALL verify("h5sget_select_npoints_f", INT(npoints), 20, total_error)
! F2003 feature
-!!$ Read selection from disk
+!!$ Read selection from disk
!!$ ret=H5Dread(dataset,H5T_NATIVE_UCHAR,sid2,sid1,xfer_plist,rbuf);
!!$ CHECK(ret, FAIL, "H5Dread");
!!$
-!!$ Check that the values match with a dataset iterator
+!!$ Check that the values match with a dataset iterator
!!$ pi.buf=wbuf;
!!$ pi.offset=0;
!!$ ret = H5Diterate(rbuf,H5T_NATIVE_UCHAR,sid2,test_select_point_iter1,&pi);
@@ -1327,19 +1327,19 @@ SUBROUTINE test_select_point(cleanup, total_error)
!!$
! F2003 feature
- ! Close memory dataspace
+ ! Close memory dataspace
CALL h5sclose_f(sid2, error)
CALL check("h5sclose_f", error, total_error)
- ! Close disk dataspace
+ ! Close disk dataspace
CALL h5sclose_f(sid1, error)
CALL check("h5sclose_f", error, total_error)
- ! Close Dataset
+ ! Close Dataset
CALL h5dclose_f(dataset, error)
CALL check("h5dclose_f", error, total_error)
- ! Close file
+ ! Close file
CALL h5fclose_f(fid1, error)
CALL check("h5fclose_f", error, total_error)
@@ -1358,34 +1358,34 @@ END SUBROUTINE test_select_point
!***************************************************************
SUBROUTINE test_select_combine(total_error)
-
+
IMPLICIT NONE
INTEGER, INTENT(INOUT) :: total_error
INTEGER, PARAMETER :: SPACE7_RANK = 2
INTEGER, PARAMETER :: SPACE7_DIM1 = 10
INTEGER, PARAMETER :: SPACE7_DIM2 = 10
-
- INTEGER(hid_t) :: base_id ! Base dataspace for test
- INTEGER(hid_t) :: all_id ! Dataspace for "all" selection
- INTEGER(hid_t) :: none_id ! Dataspace for "none" selection
- INTEGER(hid_t) :: space1 ! Temporary dataspace #1
- INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: start ! Hyperslab start
- INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: stride ! Hyperslab stride
- INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: icount ! Hyperslab count
- INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: iblock ! Hyperslab BLOCK
- INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: dims = (/SPACE7_DIM1,SPACE7_DIM2/) ! Dimensions of dataspace
- INTEGER :: sel_type ! Selection type
- INTEGER(hssize_t) :: nblocks ! Number of hyperslab blocks
- INTEGER(hsize_t), DIMENSION(1:128,1:2,1:SPACE7_RANK) :: blocks ! List of blocks
+
+ INTEGER(hid_t) :: base_id ! Base dataspace for test
+ INTEGER(hid_t) :: all_id ! Dataspace for "all" selection
+ INTEGER(hid_t) :: none_id ! Dataspace for "none" selection
+ INTEGER(hid_t) :: space1 ! Temporary dataspace #1
+ INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: start ! Hyperslab start
+ INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: stride ! Hyperslab stride
+ INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: icount ! Hyperslab count
+ INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: iblock ! Hyperslab BLOCK
+ INTEGER(hsize_t), DIMENSION(1:SPACE7_RANK) :: dims = (/SPACE7_DIM1,SPACE7_DIM2/) ! Dimensions of dataspace
+ INTEGER :: sel_type ! Selection type
+ INTEGER(hssize_t) :: nblocks ! Number of hyperslab blocks
+ INTEGER(hsize_t), DIMENSION(1:128,1:2,1:SPACE7_RANK) :: blocks ! List of blocks
INTEGER :: error, area
- ! Create dataspace for dataset on disk
+ ! Create dataspace for dataset on disk
CALL h5screate_simple_f(SPACE7_RANK, dims, base_id, error)
CALL check("h5screate_simple_f", error, total_error)
- ! Copy base dataspace and set selection to "all"
- CALL h5scopy_f(base_id, all_id, error)
+ ! Copy base dataspace and set selection to "all"
+ CALL h5scopy_f(base_id, all_id, error)
CALL check("h5scopy_f", error, total_error)
CALL H5Sselect_all_f(all_id, error)
@@ -1395,8 +1395,8 @@ SUBROUTINE test_select_combine(total_error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT(H5S_SEL_ALL_F), total_error)
- ! Copy base dataspace and set selection to "none"
- CALL h5scopy_f(base_id, none_id, error)
+ ! Copy base dataspace and set selection to "none"
+ CALL h5scopy_f(base_id, none_id, error)
CALL check("h5scopy_f", error, total_error)
CALL H5Sselect_none_f(none_id, error)
@@ -1405,100 +1405,100 @@ SUBROUTINE test_select_combine(total_error)
CALL H5Sget_select_type_f(none_id, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT(H5S_SEL_NONE_F), total_error)
-
- ! Copy "all" selection & space
- CALL H5Scopy_f(all_id, space1, error)
+
+ ! Copy "all" selection & space
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'OR' "all" selection with another hyperslab
+ ! 'OR' "all" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/)
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_OR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that it's still "all" selection
+ ! Verify that it's still "all" selection
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT(H5S_SEL_ALL_F), total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "all" selection & space
- CALL H5Scopy_f(all_id, space1, error)
+ ! Copy "all" selection & space
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'AND' "all" selection with another hyperslab
+ ! 'AND' "all" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/)
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_AND_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is the same at the original block
+ ! Verify that the new selection is the same at the original block
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
- ! Verify that there is only one block
+ ! Verify that there is only one block
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
CALL verify("h5sget_select_hyper_nblocks_f", INT(nblocks), 1, total_error)
-
- ! Retrieve the block defined
+
+ ! Retrieve the block defined
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- ! Verify that the correct block is defined
+ ! Verify that the correct block is defined
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(3,1,1)), 5, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(4,1,1)), 4, total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "all" selection & space
- CALL H5Scopy_f(all_id, space1, error)
+ ! Copy "all" selection & space
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'XOR' "all" selection with another hyperslab
+ ! 'XOR' "all" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/)
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_XOR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is an inversion of the original block
+ ! Verify that the new selection is an inversion of the original block
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
- ! Verify that there are two blocks
+ ! Verify that there are two blocks
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
CALL verify("h5sget_select_hyper_nblocks_f", INT(nblocks), 2, total_error)
- ! Retrieve the block defined
+ ! Retrieve the block defined
- blocks = -1 ! Reset block list
+ blocks = -1 ! Reset block list
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- ! Verify that the correct block is defined
+ ! Verify that the correct block is defined
- ! No guarantee is implied as the order in which blocks are listed.
+ ! No guarantee is implied as the order in which blocks are listed.
! So this will ONLY work for square domains iblock(1:2) = (/5,5/)
!!$ CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
!!$ CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 5, total_error)
@@ -1514,42 +1514,42 @@ SUBROUTINE test_select_combine(total_error)
area = area + (ABS(INT(blocks(5,1,1)-blocks(7,1,1)))+1)*(ABS(INT(blocks(6,1,1)-blocks(8,1,1)))+1)
CALL verify("h5sget_select_hyper_blocklist_f", area, 80, total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "all" selection & space
- CALL H5Scopy_f(all_id, space1, error)
+ ! Copy "all" selection & space
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'NOTB' "all" selection with another hyperslab
+ ! 'NOTB' "all" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTB_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is an inversion of the original block
+ ! Verify that the new selection is an inversion of the original block
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
- ! Verify that there are two blocks
+ ! Verify that there are two blocks
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
CALL verify("h5sget_select_hyper_nblocks_f", INT(nblocks), 2, total_error)
- ! Retrieve the block defined
- blocks = -1 ! Reset block list
+ ! Retrieve the block defined
+ blocks = -1 ! Reset block list
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- ! Verify that the correct block is defined
+ ! Verify that the correct block is defined
- ! No guarantee is implied as the order in which blocks are listed.
+ ! No guarantee is implied as the order in which blocks are listed.
! So this will ONLY work for square domains iblock(1:2) = (/5,5/)
!!$ CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
@@ -1567,200 +1567,200 @@ SUBROUTINE test_select_combine(total_error)
CALL verify("h5sget_select_hyper_blocklist_f", area, 80, total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "all" selection & space
- CALL H5Scopy_f(all_id, space1, error)
+ ! Copy "all" selection & space
+ CALL H5Scopy_f(all_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'NOTA' "all" selection with another hyperslab
+ ! 'NOTA' "all" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTA_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is the "none" selection
+ ! Verify that the new selection is the "none" selection
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_NONE_F), total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "none" selection & space
- CALL H5Scopy_f(none_id, space1, error)
+ ! Copy "none" selection & space
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'OR' "none" selection with another hyperslab
+ ! 'OR' "none" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_OR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is the same as the original hyperslab
+ ! Verify that the new selection is the same as the original hyperslab
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
-
- ! Verify that there is only one block
+
+ ! Verify that there is only one block
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
CALL verify("h5sget_select_hyper_nblocks_f", INT(nblocks), 1, total_error)
- ! Retrieve the block defined
- blocks = -1 ! Reset block list
+ ! Retrieve the block defined
+ blocks = -1 ! Reset block list
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- ! Verify that the correct block is defined
+ ! Verify that the correct block is defined
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(3,1,1)), 5, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(4,1,1)), 4, total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "none" selection & space
- CALL H5Scopy_f(none_id, space1, error)
+ ! Copy "none" selection & space
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'AND' "none" selection with another hyperslab
+ ! 'AND' "none" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_AND_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is the "none" selection
+ ! Verify that the new selection is the "none" selection
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_NONE_F), total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "none" selection & space
- CALL H5Scopy_f(none_id, space1, error)
+ ! Copy "none" selection & space
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'XOR' "none" selection with another hyperslab
+ ! 'XOR' "none" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_XOR_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is the same as the original hyperslab
+ ! Verify that the new selection is the same as the original hyperslab
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
-
- ! Verify that there is only one block
+
+ ! Verify that there is only one block
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
CALL verify("h5sget_select_hyper_nblocks_f", INT(nblocks), 1, total_error)
- ! Retrieve the block defined
- blocks = -1 ! Reset block list
+ ! Retrieve the block defined
+ blocks = -1 ! Reset block list
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- ! Verify that the correct block is defined
+ ! Verify that the correct block is defined
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(3,1,1)), 5, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(4,1,1)), 4, total_error)
-
- ! Close temporary dataspace
+
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "none" selection & space
- CALL H5Scopy_f(none_id, space1, error)
+ ! Copy "none" selection & space
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'NOTB' "none" selection with another hyperslab
+ ! 'NOTB' "none" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTB_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is the "none" selection
+ ! Verify that the new selection is the "none" selection
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_NONE_F), total_error)
- ! Close temporary dataspace
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Copy "none" selection & space
- CALL H5Scopy_f(none_id, space1, error)
+ ! Copy "none" selection & space
+ CALL H5Scopy_f(none_id, space1, error)
CALL check("h5scopy_f", error, total_error)
- ! 'NOTA' "none" selection with another hyperslab
+ ! 'NOTA' "none" selection with another hyperslab
start(1:2) = 0
stride(1:2) = 1
icount(1:2) = 1
- iblock(1:2) = (/5,4/) !5
+ iblock(1:2) = (/5,4/) !5
CALL h5sselect_hyperslab_f(space1, H5S_SELECT_NOTA_F, start, &
- icount, error, stride, iblock)
+ icount, error, stride, iblock)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Verify that the new selection is the same as the original hyperslab
+ ! Verify that the new selection is the same as the original hyperslab
CALL H5Sget_select_type_f(space1, sel_type, error)
CALL check("H5Sget_select_type_f", error, total_error)
CALL verify("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_HYPERSLABS_F), total_error)
-
- ! Verify that there is ONLY one BLOCK
+
+ ! Verify that there is ONLY one BLOCK
CALL h5sget_select_hyper_nblocks_f(space1, nblocks, error)
CALL check("h5sget_select_hyper_nblocks_f", error, total_error)
CALL verify("h5sget_select_hyper_nblocks_f", INT(nblocks), 1, total_error)
- ! Retrieve the block defined
+ ! Retrieve the block defined
- blocks = -1 ! Reset block list
+ blocks = -1 ! Reset block list
CALL h5sget_select_hyper_blocklist_f(space1, INT(0, hsize_t), INT(nblocks,hsize_t), blocks, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- ! Verify that the correct block is defined
+ ! Verify that the correct block is defined
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(1,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(2,1,1)), 1, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(3,1,1)), 5, total_error)
CALL verify("h5sget_select_hyper_blocklist_f", INT(blocks(4,1,1)), 4, total_error)
-
- ! Close temporary dataspace
+
+ ! Close temporary dataspace
CALL h5sclose_f(space1, error)
CALL check("h5sclose_f", error, total_error)
- ! Close dataspaces
-
+ ! Close dataspaces
+
CALL h5sclose_f(base_id, error)
CALL check("h5sclose_f", error, total_error)
CALL h5sclose_f(all_id, error)
@@ -1778,7 +1778,7 @@ END SUBROUTINE test_select_combine
!***************************************************************
SUBROUTINE test_select_bounds(total_error)
-
+
IMPLICIT NONE
INTEGER, INTENT(INOUT) :: total_error
@@ -1786,25 +1786,25 @@ SUBROUTINE test_select_bounds(total_error)
INTEGER, PARAMETER :: SPACE11_DIM1=100
INTEGER, PARAMETER :: SPACE11_DIM2=50
INTEGER, PARAMETER :: SPACE11_NPOINTS=4
-
- INTEGER(hid_t) :: sid ! Dataspace ID
+
+ INTEGER(hid_t) :: sid ! Dataspace ID
INTEGER(hsize_t), DIMENSION(1:SPACE11_RANK) :: dims = (/SPACE11_DIM1, SPACE11_DIM2/) !Dataspace dimensions
INTEGER(hsize_t), DIMENSION(SPACE11_RANK, SPACE11_NPOINTS) :: coord ! Coordinates for point selection
- INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: start ! The start of the hyperslab
- INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: stride ! The stride between block starts for the hyperslab
- INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: count ! The number of blocks for the hyperslab
- INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: BLOCK ! The size of each block for the hyperslab
- INTEGER(hssize_t), DIMENSION(SPACE11_RANK) :: offset ! Offset amount for selection
- INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: low_bounds ! The low bounds for the selection
- INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: high_bounds ! The high bounds for the selection
-
+ INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: start ! The start of the hyperslab
+ INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: stride ! The stride between block starts for the hyperslab
+ INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: count ! The number of blocks for the hyperslab
+ INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: BLOCK ! The size of each block for the hyperslab
+ INTEGER(hssize_t), DIMENSION(SPACE11_RANK) :: offset ! Offset amount for selection
+ INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: low_bounds ! The low bounds for the selection
+ INTEGER(hsize_t), DIMENSION(SPACE11_RANK) :: high_bounds ! The high bounds for the selection
+
INTEGER :: error
- ! Create dataspace
+ ! Create dataspace
CALL h5screate_simple_f(SPACE11_RANK, dims, sid, error)
CALL check("h5screate_simple_f", error, total_error)
- ! Get bounds for 'all' selection
+ ! Get bounds for 'all' selection
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1813,12 +1813,12 @@ SUBROUTINE test_select_bounds(total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(1), INT(SPACE11_DIM1, hsize_t), total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), INT(SPACE11_DIM2, hsize_t), total_error)
- ! Set offset for selection
+ ! Set offset for selection
offset(1:2) = 1
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Get bounds for 'all' selection with offset (which should be ignored)
+ ! Get bounds for 'all' selection with offset (which should be ignored)
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1827,21 +1827,21 @@ SUBROUTINE test_select_bounds(total_error)
CALL VERIFY("h5sget_select_bounds_f", high_bounds(1), INT(SPACE11_DIM1, hsize_t), total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), INT(SPACE11_DIM2, hsize_t), total_error)
- ! Reset offset for selection
+ ! Reset offset for selection
offset(1:2) = 0
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Set 'none' selection
+ ! Set 'none' selection
CALL H5Sselect_none_f(sid, error)
CALL check("H5Sselect_none_f", error, total_error)
- ! Get bounds for 'none' selection, should fail
+ ! Get bounds for 'none' selection, should fail
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL verify("h5sget_select_bounds_f", error, -1, total_error)
- ! Set point selection
-
+ ! Set point selection
+
coord(1,1)= 3; coord(2,1)= 3;
coord(1,2)= 3; coord(2,2)= 46;
coord(1,3)= 96; coord(2,3)= 3;
@@ -1850,7 +1850,7 @@ SUBROUTINE test_select_bounds(total_error)
CALL h5sselect_elements_f(sid, H5S_SELECT_SET_F, SPACE11_RANK, INT(SPACE11_NPOINTS,size_t), coord, error)
CALL check("h5sselect_elements_f", error, total_error)
- ! Get bounds for point selection
+ ! Get bounds for point selection
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1859,22 +1859,22 @@ SUBROUTINE test_select_bounds(total_error)
CALL VERIFY("h5sget_select_bounds_f", high_bounds(1), INT(SPACE11_DIM1-4,hsize_t), total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), INT(SPACE11_DIM2-4,hsize_t), total_error)
- ! Set bad offset for selection
+ ! Set bad offset for selection
offset(1:2) = (/5,-5/)
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Get bounds for hyperslab selection with negative offset
+ ! Get bounds for hyperslab selection with negative offset
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL verify("h5sget_select_bounds_f", error, -1, total_error)
-
- ! Set valid offset for selection
+
+ ! Set valid offset for selection
offset(1:2) = (/2,-2/)
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Get bounds for point selection with offset
+ ! Get bounds for point selection with offset
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1883,22 +1883,22 @@ SUBROUTINE test_select_bounds(total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(1), INT(SPACE11_DIM1-2,hsize_t), total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), INT(SPACE11_DIM2-6,hsize_t), total_error)
- ! Reset offset for selection
+ ! Reset offset for selection
offset(1:2) = 0
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Set "regular" hyperslab selection
+ ! Set "regular" hyperslab selection
start(1:2) = 2
stride(1:2) = 10
count(1:2) = 4
block(1:2) = 5
-
+
CALL h5sselect_hyperslab_f(sid, H5S_SELECT_SET_F, start, &
- count, error, stride, block)
+ count, error, stride, block)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Get bounds for hyperslab selection
+ ! Get bounds for hyperslab selection
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1907,21 +1907,21 @@ SUBROUTINE test_select_bounds(total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(1), 37_hsize_t, total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), 37_hsize_t, total_error)
- ! Set bad offset for selection
+ ! Set bad offset for selection
offset(1:2) = (/5,-5/)
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Get bounds for hyperslab selection with negative offset
+ ! Get bounds for hyperslab selection with negative offset
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL verify("h5sget_select_bounds_f", error, -1, total_error)
- ! Set valid offset for selection
+ ! Set valid offset for selection
offset(1:2) = (/5,-2/)
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Get bounds for hyperslab selection with offset
+ ! Get bounds for hyperslab selection with offset
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1930,22 +1930,22 @@ SUBROUTINE test_select_bounds(total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(1), 42_hsize_t, total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), 35_hsize_t, total_error)
- ! Reset offset for selection
+ ! Reset offset for selection
offset(1:2) = 0
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
-
- ! Make "irregular" hyperslab selection
+
+ ! Make "irregular" hyperslab selection
start(1:2) = 20
stride(1:2) = 20
count(1:2) = 2
block(1:2) = 10
CALL h5sselect_hyperslab_f(sid, H5S_SELECT_OR_F, start, &
- count, error, stride, block)
+ count, error, stride, block)
CALL check("h5sselect_hyperslab_f", error, total_error)
- ! Get bounds for hyperslab selection
+ ! Get bounds for hyperslab selection
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1954,21 +1954,21 @@ SUBROUTINE test_select_bounds(total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(1), 50_hsize_t, total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), 50_hsize_t, total_error)
- ! Set bad offset for selection
+ ! Set bad offset for selection
offset(1:2) = (/5,-5/)
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Get bounds for hyperslab selection with negative offset
+ ! Get bounds for hyperslab selection with negative offset
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL verify("h5sget_select_bounds_f", error, -1, total_error)
- ! Set valid offset for selection
+ ! Set valid offset for selection
offset(1:2) = (/5,-2/)
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Get bounds for hyperslab selection with offset
+ ! Get bounds for hyperslab selection with offset
CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error)
CALL check("h5sget_select_bounds_f", error, total_error)
@@ -1977,12 +1977,12 @@ SUBROUTINE test_select_bounds(total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(1), 55_hsize_t, total_error)
CALL verify("h5sget_select_bounds_f", high_bounds(2), 48_hsize_t, total_error)
- ! Reset offset for selection
+ ! Reset offset for selection
offset(1:2) = 0
CALL H5Soffset_simple_f(sid, offset, error)
CALL check("H5Soffset_simple_f", error, total_error)
- ! Close the dataspace
+ ! Close the dataspace
CALL h5sclose_f(sid, error)
CALL check("h5sclose_f", error, total_error)