diff options
Diffstat (limited to 'fortran/test/tH5Sselect.f90')
-rw-r--r-- | fortran/test/tH5Sselect.f90 | 219 |
1 files changed, 113 insertions, 106 deletions
diff --git a/fortran/test/tH5Sselect.f90 b/fortran/test/tH5Sselect.f90 index aeb80e9..7d07308 100644 --- a/fortran/test/tH5Sselect.f90 +++ b/fortran/test/tH5Sselect.f90 @@ -38,14 +38,13 @@ !***** MODULE TH5SSELECT - USE HDF5 ! This module contains all necessary modules - USE TH5_MISC - USE TH5_MISC_GEN - CONTAINS SUBROUTINE test_select_hyperslab(cleanup, total_error) + USE HDF5 ! This module contains all necessary modules + USE TH5_MISC + IMPLICIT NONE LOGICAL, INTENT(IN) :: cleanup INTEGER, INTENT(INOUT) :: total_error @@ -700,6 +699,8 @@ CONTAINS SUBROUTINE test_basic_select(cleanup, total_error) + USE HDF5 ! This module contains all necessary modules + USE TH5_MISC IMPLICIT NONE LOGICAL, INTENT(IN) :: cleanup @@ -1035,6 +1036,8 @@ CONTAINS !*************************************************************** SUBROUTINE test_select_point(cleanup, total_error) + USE HDF5 ! This module contains all necessary modules + USE TH5_MISC IMPLICIT NONE LOGICAL, INTENT(IN) :: cleanup @@ -1137,9 +1140,9 @@ SUBROUTINE test_select_point(cleanup, total_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) + 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) @@ -1168,9 +1171,9 @@ SUBROUTINE test_select_point(cleanup, total_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) + 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) @@ -1199,8 +1202,8 @@ SUBROUTINE test_select_point(cleanup, total_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) + 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 !!$ @@ -1235,8 +1238,8 @@ SUBROUTINE test_select_point(cleanup, total_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) + 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) @@ -1281,8 +1284,8 @@ SUBROUTINE test_select_point(cleanup, total_error) 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) + 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) @@ -1308,8 +1311,8 @@ SUBROUTINE test_select_point(cleanup, total_error) 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) + 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) @@ -1360,6 +1363,8 @@ END SUBROUTINE test_select_point !*************************************************************** SUBROUTINE test_select_combine(total_error) + USE HDF5 ! This module contains all necessary modules + USE TH5_MISC IMPLICIT NONE INTEGER, INTENT(INOUT) :: total_error @@ -1395,7 +1400,7 @@ SUBROUTINE test_select_combine(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) + 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) @@ -1406,7 +1411,7 @@ 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) + 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) @@ -1424,7 +1429,7 @@ SUBROUTINE test_select_combine(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) + CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT(H5S_SEL_ALL_F), total_error) ! Close temporary dataspace CALL h5sclose_f(space1, error) @@ -1446,12 +1451,12 @@ SUBROUTINE test_select_combine(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) + 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) + 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) @@ -1459,10 +1464,10 @@ SUBROUTINE test_select_combine(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) + 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) @@ -1485,12 +1490,12 @@ SUBROUTINE test_select_combine(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) + 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) + CALL VERIFY("h5sget_select_hyper_nblocks_f", INT(nblocks), 2, total_error) ! Retrieve the block defined @@ -1502,19 +1507,19 @@ SUBROUTINE test_select_combine(total_error) ! 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) +!!$ 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) + CALL VERIFY("h5sget_select_hyper_blocklist_f", area, 80, total_error) ! Close temporary dataspace CALL h5sclose_f(space1, error) @@ -1537,12 +1542,12 @@ SUBROUTINE test_select_combine(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) + 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) + CALL VERIFY("h5sget_select_hyper_nblocks_f", INT(nblocks), 2, total_error) ! Retrieve the block defined blocks = -1 ! Reset block list @@ -1554,19 +1559,19 @@ SUBROUTINE test_select_combine(total_error) ! 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) +!!$ 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) + CALL VERIFY("h5sget_select_hyper_blocklist_f", area, 80, total_error) ! Close temporary dataspace @@ -1589,7 +1594,7 @@ SUBROUTINE test_select_combine(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) + CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_NONE_F), total_error) ! Close temporary dataspace CALL h5sclose_f(space1, error) @@ -1612,13 +1617,13 @@ SUBROUTINE test_select_combine(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) + 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) + CALL VERIFY("h5sget_select_hyper_nblocks_f", INT(nblocks), 1, total_error) ! Retrieve the block defined blocks = -1 ! Reset block list @@ -1626,10 +1631,10 @@ SUBROUTINE test_select_combine(total_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) + 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) @@ -1652,7 +1657,7 @@ SUBROUTINE test_select_combine(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) + CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_NONE_F), total_error) ! Close temporary dataspace CALL h5sclose_f(space1, error) @@ -1675,23 +1680,23 @@ SUBROUTINE test_select_combine(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) + 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) + 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) + 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) @@ -1714,7 +1719,7 @@ SUBROUTINE test_select_combine(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) + CALL VERIFY("H5Sget_select_type_f", INT(sel_type), INT( H5S_SEL_NONE_F), total_error) ! Close temporary dataspace CALL h5sclose_f(space1, error) @@ -1736,12 +1741,12 @@ SUBROUTINE test_select_combine(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) + 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) + CALL VERIFY("h5sget_select_hyper_nblocks_f", INT(nblocks), 1, total_error) ! Retrieve the block defined @@ -1752,10 +1757,10 @@ SUBROUTINE test_select_combine(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) + 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) @@ -1780,6 +1785,8 @@ END SUBROUTINE test_select_combine !*************************************************************** SUBROUTINE test_select_bounds(total_error) + USE HDF5 ! This module contains all necessary modules + USE TH5_MISC IMPLICIT NONE INTEGER, INTENT(INOUT) :: total_error @@ -1810,10 +1817,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 1_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 1_hsize_t, 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) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(1)), 1, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(2)), 1, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(1)), SPACE11_DIM1, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(2)), SPACE11_DIM2, total_error) ! Set offset for selection offset(1:2) = 1 @@ -1824,10 +1831,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 1_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 1_hsize_t, 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) + CALL verify("h5sget_select_bounds_f", INT(low_bounds(1)), 1, total_error) + CALL verify("h5sget_select_bounds_f", INT(low_bounds(2)), 1, total_error) + CALL verify("h5sget_select_bounds_f", INT(high_bounds(1)), SPACE11_DIM1, total_error) + CALL verify("h5sget_select_bounds_f", INT(high_bounds(2)), SPACE11_DIM2, total_error) ! Reset offset for selection offset(1:2) = 0 @@ -1840,7 +1847,7 @@ SUBROUTINE test_select_bounds(total_error) ! 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) + CALL VERIFY("h5sget_select_bounds_f", error, -1, total_error) ! Set point selection @@ -1856,10 +1863,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 3_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 3_hsize_t, 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) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(1)), 3, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(2)), 3, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(1)), INT(SPACE11_DIM1-4), total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(2)), INT(SPACE11_DIM2-4), total_error) ! Set bad offset for selection @@ -1869,7 +1876,7 @@ SUBROUTINE test_select_bounds(total_error) ! 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) + CALL VERIFY("h5sget_select_bounds_f", error, -1, total_error) ! Set valid offset for selection offset(1:2) = (/2,-2/) @@ -1880,10 +1887,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 5_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 1_hsize_t, 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) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(1)), 5, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(2)), 1, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(1)), INT(SPACE11_DIM1-2), total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(2)), INT(SPACE11_DIM2-6), total_error) ! Reset offset for selection offset(1:2) = 0 @@ -1904,10 +1911,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 3_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 3_hsize_t, 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) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(1)), 3, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(2)), 3, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(1)), 37, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(2)), 37, total_error) ! Set bad offset for selection offset(1:2) = (/5,-5/) @@ -1916,7 +1923,7 @@ SUBROUTINE test_select_bounds(total_error) ! 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) + CALL VERIFY("h5sget_select_bounds_f", error, -1, total_error) ! Set valid offset for selection offset(1:2) = (/5,-2/) @@ -1927,10 +1934,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 8_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 1_hsize_t, 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) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(1)), 8, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(2)), 1, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(1)), 42, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(2)), 35, total_error) ! Reset offset for selection offset(1:2) = 0 @@ -1951,10 +1958,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 3_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 3_hsize_t, 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) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(1)), 3, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(2)), 3, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(1)), 50, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(2)), 50, total_error) ! Set bad offset for selection offset(1:2) = (/5,-5/) @@ -1963,7 +1970,7 @@ SUBROUTINE test_select_bounds(total_error) ! 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) + CALL VERIFY("h5sget_select_bounds_f", error, -1, total_error) ! Set valid offset for selection offset(1:2) = (/5,-2/) @@ -1974,10 +1981,10 @@ SUBROUTINE test_select_bounds(total_error) CALL h5sget_select_bounds_f(sid, low_bounds, high_bounds, error) CALL check("h5sget_select_bounds_f", error, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(1), 8_hsize_t, total_error) - CALL verify("h5sget_select_bounds_f", low_bounds(2), 1_hsize_t, 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) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(1)), 8, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(low_bounds(2)), 1, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(1)), 55, total_error) + CALL VERIFY("h5sget_select_bounds_f", INT(high_bounds(2)), 48, total_error) ! Reset offset for selection offset(1:2) = 0 |