summaryrefslogtreecommitdiffstats
path: root/fortran
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-23 21:52:19 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2008-09-23 21:52:19 (GMT)
commit844a56e79b49d93fe241ef06fb929eb3762c7cfe (patch)
treed0e406479d02807d9dd295e4bd40f9465ebae1a7 /fortran
parent9b4a0aea49bc59063e066ae73c006525d71fb81a (diff)
downloadhdf5-844a56e79b49d93fe241ef06fb929eb3762c7cfe.zip
hdf5-844a56e79b49d93fe241ef06fb929eb3762c7cfe.tar.gz
hdf5-844a56e79b49d93fe241ef06fb929eb3762c7cfe.tar.bz2
[svn-r15688] Description:
Added additional tests for h5sget_select_hyper_blocklist_f and 5sget_select_elem_pointlist_f
Diffstat (limited to 'fortran')
-rw-r--r--fortran/test/fortranlib_test.f908
-rw-r--r--fortran/test/tH5Sselect.f90749
2 files changed, 756 insertions, 1 deletions
diff --git a/fortran/test/fortranlib_test.f90 b/fortran/test/fortranlib_test.f90
index 73946de..a540f99 100644
--- a/fortran/test/fortranlib_test.f90
+++ b/fortran/test/fortranlib_test.f90
@@ -127,6 +127,14 @@ PROGRAM fortranlibtest
CALL test_select_element(cleanup, ret_total_error)
CALL write_test_status(ret_total_error, ' Element selection test', total_error)
+ ret_total_error = 0
+ CALL test_select_point(cleanup, ret_total_error)
+ CALL write_test_status(ret_total_error, ' Element selection functions test ', total_error)
+
+ ret_total_error = 0
+ CALL test_select_combine(cleanup, total_error)
+ CALL write_test_status(ret_total_error, ' Selection combinations test ', total_error)
+
! write(*,*)
! write(*,*) '========================================='
! write(*,*) 'Testing DATATYPE interface '
diff --git a/fortran/test/tH5Sselect.f90 b/fortran/test/tH5Sselect.f90
index a004ba7..57a846b 100644
--- a/fortran/test/tH5Sselect.f90
+++ b/fortran/test/tH5Sselect.f90
@@ -794,6 +794,8 @@
INTEGER :: error
INTEGER(HSIZE_T), DIMENSION(3) :: data_dims
+ INTEGER :: i
+
!
!initialize the coord array to give the selected points' position
!
@@ -916,7 +918,7 @@
CALL h5sget_select_hyper_blocklist_f(dataspace, startblock, &
num_blocks, blocklist, error)
CALL check("h5sget_select_hyper_blocklist_f", error, total_error)
- !write(*,*) (blocklist(i), i =1, num_blocks*RANK*2)
+! write(*,*) (blocklist(i), i =1, num_blocks*RANK*2)
!result of blocklist selected is:
!1, 1, 2, 2, 4, 1, 5, 2, 1, 4, 2, 5, 4, 4, 5, 5
@@ -1010,4 +1012,749 @@
RETURN
END SUBROUTINE test_basic_select
+!/****************************************************************
+!**
+!** test_select_point(): Test basic H5S (dataspace) selection code.
+!** Tests element selections between dataspaces of various sizes
+!** and dimensionalities.
+!**
+!****************************************************************/
+
+SUBROUTINE test_select_point(cleanup, total_error)
+ USE HDF5 ! This module contains all necessary modules
+
+ IMPLICIT NONE
+ LOGICAL, INTENT(IN) :: cleanup
+ INTEGER, INTENT(OUT) :: total_error
+ INTEGER(HID_T) :: xfer_plist
+
+ INTEGER, PARAMETER :: SPACE1_DIM1=3
+ INTEGER, PARAMETER :: SPACE1_DIM2=15
+ INTEGER, PARAMETER :: SPACE1_DIM3=13
+ INTEGER, PARAMETER :: SPACE2_DIM1=30
+ 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 */
+ 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(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(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 */
+ CHARACTER(LEN=12) :: filename = 'h5s_hyper.h5'
+ CHARACTER(LEN=1), DIMENSION(1:SPACE2_DIM1,1:SPACE2_DIM2) :: wbuf, rbuf
+
+ xfer_plist = H5P_DEFAULT_F
+! MESSAGE(5, ("Testing Element Selection Functions\n"));
+
+ !/* 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 */
+
+ DO i = 1, SPACE2_DIM1
+ DO j = 1, SPACE2_DIM2
+ wbuf(i,j) = 'a'
+ ENDDO
+ ENDDO
+
+!!$ 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 */
+ CALL h5fcreate_f(filename, H5F_ACC_TRUNC_F, fid1, error)
+ CALL check("h5fcreate_f", error, total_error)
+
+ !/* 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 */
+ 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 */
+ 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;
+ coord1(1,4)=1; coord1(2,4)= 7; coord1(3,4)=12;
+ coord1(1,5)=2; coord1(2,5)= 9; coord1(3,5)=14;
+ coord1(1,6)=3; coord1(2,6)=13; coord1(3,6)= 1;
+ coord1(1,7)=1; coord1(2,7)=15; coord1(3,7)= 3;
+ coord1(1,8)=2; coord1(2,8)= 1; coord1(3,8)= 5;
+ coord1(1,9)=3; coord1(2,9)= 2; coord1(3,9)= 7;
+ coord1(1,10)=1; coord1(2,10)= 4; coord1(3,10)= 9
+
+
+ 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 */
+
+ 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)
+
+ DO i= 1, POINT1_NPOINTS
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord1(1,i)), INT(coord1(1,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord1(2,i)), INT(coord1(2,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord1(3,i)), INT(coord1(3,i)), total_error)
+ ENDDO
+
+ CALL H5Sget_select_npoints_f(sid1, npoints, 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 */
+
+ coord1(1,1)=1; coord1(2,1)=3; coord1(3,1)= 1;
+ coord1(1,2)=2; coord1(2,2)=11; coord1(3,2)= 9;
+ coord1(1,3)=3; coord1(2,3)= 9; coord1(3,3)=11;
+ coord1(1,4)=1; coord1(2,4)= 8; coord1(3,4)=13;
+ coord1(1,5)=2; coord1(2,5)= 4; coord1(3,5)=12;
+ coord1(1,6)=3; coord1(2,6)= 2; coord1(3,6)= 2;
+ coord1(1,7)=1; coord1(2,7)=14; coord1(3,7)= 8;
+ coord1(1,8)=2; coord1(2,8)=15; coord1(3,8)= 7;
+ coord1(1,9)=3; coord1(2,9)= 3; coord1(3,9)= 6;
+ coord1(1,10)=1; coord1(2,10)= 7; coord1(3,10)= 14
+
+
+ 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 */
+
+ 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)
+
+ DO i= 1, POINT1_NPOINTS
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord1(1,i)), INT(coord1(1,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord1(2,i)), INT(coord1(2,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord1(3,i)), INT(coord1(3,i)), total_error)
+ ENDDO
+
+ CALL H5Sget_select_npoints_f(sid1, npoints, 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 */
+ coord2(1,1)=13; coord2(2,1)= 4;
+ coord2(1,2)=16; coord2(2,2)=14;
+ coord2(1,3)= 8; coord2(2,3)=26;
+ coord2(1,4)= 1; coord2(2,4)= 7;
+ coord2(1,5)=14; coord2(2,5)= 1;
+ coord2(1,6)=25; coord2(2,6)=12;
+ coord2(1,7)=13; coord2(2,7)=22;
+ coord2(1,8)=30; coord2(2,8)= 5;
+ coord2(1,9)= 9; coord2(2,9)= 9;
+ coord2(1,10)=20; coord2(2,10)=18
+
+ CALL h5sselect_elements_f(sid2, H5S_SELECT_SET_F, SPACE2_RANK, INT(POINT1_NPOINTS,size_t), coord2, error)
+ CALL check("h5sselect_elements_f", error, total_error)
+
+
+ !/* 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)
+
+ DO i= 1, POINT1_NPOINTS
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord2(1,i)), INT(coord2(1,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord2(2,i)), INT(coord2(2,i)), 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) */
+!!$ HDmemcpy(((char *)pi.coord)+sizeof(coord2),coord2,sizeof(coord2));
+!!$
+
+ CALL H5Sget_select_npoints_f(sid2, npoints, 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 */
+ coord2(1,1)=25; coord2(2,1)= 1;
+ coord2(1,2)= 3; coord2(2,2)=26;
+ coord2(1,3)=14; coord2(2,3)=18;
+ coord2(1,4)= 9; coord2(2,4)= 4;
+ coord2(1,5)=30; coord2(2,5)= 5;
+ coord2(1,6)=12; coord2(2,6)=15;
+ coord2(1,7)= 6; coord2(2,7)=23;
+ coord2(1,8)=13; coord2(2,8)= 3;
+ coord2(1,9)=22; coord2(2,9)=13;
+ coord2(1,10)= 10; coord2(2,10)=19
+
+ CALL h5sselect_elements_f(sid2, H5S_SELECT_PREPEND_F, SPACE2_RANK, INT(POINT1_NPOINTS,size_t), coord2, error)
+ CALL check("h5sselect_elements_f", error, total_error)
+
+
+ !/* 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)
+
+ DO i= 1, POINT1_NPOINTS
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord2(1,i)), INT(coord2(1,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord2(2,i)), INT(coord2(2,i)), total_error)
+ ENDDO
+
+ CALL H5Sget_select_npoints_f(sid2, npoints, 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 */
+!!$ HDmemcpy(pi.coord,coord2,sizeof(coord2));
+
+ ! /* 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 */
+ CALL h5dwrite_f(dataset, H5T_NATIVE_CHARACTER, wbuf, dims2, error, sid2, sid1, xfer_plist)
+ CALL check("h5dwrite_f", error, total_error)
+
+!!$ ret=H5Dwrite(dataset,H5T_NATIVE_UCHAR,sid2,sid1,xfer_plist,wbuf);
+!!$ CHECK(ret, FAIL, "H5Dwrite");
+!!$
+
+
+
+ ! /* Close memory dataspace */
+ CALL h5sclose_f(sid2, error)
+ CALL check("h5sclose_f", error, total_error)
+
+ ! /* 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 */
+ coord3(1,1)= 1; coord3(2,1)= 3;
+ coord3(1,2)= 5; coord3(2,2)= 9;
+ coord3(1,3)=14; coord3(2,3)=14;
+ coord3(1,4)=15; coord3(2,4)=21;
+ coord3(1,5)= 8; coord3(2,5)=10;
+ coord3(1,6)= 3; coord3(2,6)= 1;
+ coord3(1,7)= 10; coord3(2,7)=20;
+ coord3(1,8)= 2; coord3(2,8)=23;
+ coord3(1,9)=13; coord3(2,9)=22;
+ coord3(1,10)=12; coord3(2,10)=7;
+
+ 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 */
+ 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
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord3(1,i)), INT(coord3(1,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord3(2,i)), INT(coord3(2,i)), total_error)
+ ENDDO
+
+ CALL H5Sget_select_npoints_f(sid2, npoints, 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 */
+ coord3(1,1)=15; coord3(2,1)=26;
+ coord3(1,2)= 1; coord3(2,2)= 1;
+ coord3(1,3)=12; coord3(2,3)=12;
+ coord3(1,4)= 6; coord3(2,4)=15;
+ coord3(1,5)= 4; coord3(2,5)= 6;
+ coord3(1,6)= 3; coord3(2,6)= 3;
+ coord3(1,7)= 8; coord3(2,7)=14;
+ coord3(1,8)=10; coord3(2,8)=17;
+ coord3(1,9)=13; coord3(2,9)=23;
+ coord3(1,10)=14; coord3(2,10)=10
+
+ 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 */
+ 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
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord3(1,i)), INT(coord3(1,i)), total_error)
+ CALL VERIFY("h5sget_select_elem_pointlist_f", INT(temp_coord3(2,i)), INT(coord3(2,i)), total_error)
+ ENDDO
+
+ CALL H5Sget_select_npoints_f(sid2, npoints, error)
+ CALL check("h5sget_select_npoints_f", error, total_error)
+ CALL verify("h5sget_select_npoints_f", INT(npoints), 20, total_error)
+
+! F2003 feature
+!!$ /* 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 */
+!!$ pi.buf=wbuf;
+!!$ pi.offset=0;
+!!$ ret = H5Diterate(rbuf,H5T_NATIVE_UCHAR,sid2,test_select_point_iter1,&pi);
+!!$ CHECK(ret, FAIL, "H5Diterate");
+!!$
+! F2003 feature
+
+ !/* Close memory dataspace */
+ CALL h5sclose_f(sid2, error)
+ CALL check("h5sclose_f", error, total_error)
+
+ !/* Close disk dataspace */
+ CALL h5sclose_f(sid1, error)
+ CALL check("h5sclose_f", error, total_error)
+
+ !/* Close Dataset */
+ CALL h5dclose_f(dataset, error)
+ CALL check("h5dclose_f", error, total_error)
+
+ !/* Close file */
+ CALL h5fclose_f(fid1, error)
+ CALL check("h5fclose_f", error, total_error)
+
+END SUBROUTINE test_select_point
+
+
+!/****************************************************************
+!**
+!** test_select_combine(): Test basic H5S (dataspace) selection code.
+!** Tests combining "all" and "none" selections with hyperslab
+!** operations.
+!**
+!****************************************************************/
+
+SUBROUTINE test_select_combine(cleanup, total_error)
+ USE HDF5 ! This module contains all necessary modules
+
+ IMPLICIT NONE
+ LOGICAL, INTENT(IN) :: cleanup
+ INTEGER, INTENT(OUT) :: 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 :: error, area
+
+ !/* 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)
+ CALL check("h5scopy_f", error, total_error)
+
+ CALL H5Sselect_all_f(all_id, error)
+ CALL check("H5Sselect_all_f", error, total_error)
+
+ CALL H5Sget_select_type_f(all_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_ALL_F), total_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)
+ CALL check("H5Sselect_none_f", error, 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)
+ CALL check("h5scopy_f", error, total_error)
+
+ !/* '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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ !/* 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ !/* 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 */
+ 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 */
+ 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 */
+
+ 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ ! /* 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 */
+ 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 */
+ 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 */
+
+ ! 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)
+!!$ 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)), 10, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(5,1,1)), 6, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(6,1,1)), 1, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(7,1,1)), 10, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(8,1,1)), 10, total_error)
+
+ ! Otherwise make sure the "area" of the block is correct
+ area = (ABS(INT(blocks(1,1,1)-blocks(3,1,1)))+1)*(ABS(INT(blocks(2,1,1)-blocks(4,1,1)))+1)
+ 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ ! /* 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 */
+ 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 */
+ 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 */
+
+ ! 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)
+!!$ 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)),10, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(5,1,1)), 6, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(6,1,1)), 1, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(7,1,1)),10, total_error)
+!!$ CALL VERIFY("h5sget_select_hyper_blocklist_f", INT(blocks(8,1,1)),10, total_error)
+
+ ! Otherwise make sure the "area" of the block is correct
+ area = (ABS(INT(blocks(1,1,1)-blocks(3,1,1)))+1)*(ABS(INT(blocks(2,1,1)-blocks(4,1,1)))+1)
+ 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ !/* 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ ! /* 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 */
+ 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 */
+ 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 */
+ 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ ! /* 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ ! /* 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 */
+ 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 */
+ 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 */
+ 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ ! /* 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_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 */
+ 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)
+ CALL check("h5sselect_hyperslab_f", error, total_error)
+
+ ! /* 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 */
+ 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 */
+ 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 */
+
+ 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 */
+ CALL h5sclose_f(space1, error)
+ CALL check("h5sclose_f", error, total_error)
+
+ ! /* Close dataspaces */
+
+ CALL h5sclose_f(base_id, error)
+ CALL check("h5sclose_f", error, total_error)
+ CALL h5sclose_f(all_id, error)
+ CALL check("h5sclose_f", error, total_error)
+ CALL h5sclose_f(none_id, error)
+ CALL check("h5sclose_f", error, total_error)
+
+END SUBROUTINE test_select_combine