diff options
Diffstat (limited to 'fortran/test/tH5P.f90')
-rw-r--r-- | fortran/test/tH5P.f90 | 31 |
1 files changed, 23 insertions, 8 deletions
diff --git a/fortran/test/tH5P.f90 b/fortran/test/tH5P.f90 index 4c78334..6db6b1a 100644 --- a/fortran/test/tH5P.f90 +++ b/fortran/test/tH5P.f90 @@ -26,6 +26,9 @@ ! external_test, multi_file_test ! !***** +MODULE TH5P + +CONTAINS SUBROUTINE external_test(cleanup, total_error) @@ -34,6 +37,7 @@ SUBROUTINE external_test(cleanup, total_error) ! h5pget_external_f USE HDF5 ! This module contains all necessary modules + USE TH5_MISC IMPLICIT NONE LOGICAL, INTENT(IN) :: cleanup @@ -150,6 +154,7 @@ END SUBROUTINE external_test SUBROUTINE multi_file_test(cleanup, total_error) USE HDF5 ! This module contains all necessary modules + USE TH5_MISC IMPLICIT NONE LOGICAL, INTENT(IN) :: cleanup @@ -419,6 +424,7 @@ END SUBROUTINE multi_file_test SUBROUTINE test_chunk_cache(cleanup, total_error) USE HDF5 ! This module contains all necessary modules + USE TH5_MISC IMPLICIT NONE LOGICAL, INTENT(IN) :: cleanup @@ -427,7 +433,6 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CHARACTER(LEN=14), PARAMETER :: filename="chunk_cache" CHARACTER(LEN=80) :: fix_filename INTEGER(hid_t) :: fid = -1 ! File ID - INTEGER(hid_t) :: file INTEGER(hid_t) :: fapl_local = -1 ! Local fapl INTEGER(hid_t) :: fapl_def = -1 ! Default fapl INTEGER(hid_t) :: dcpl = -1 ! Dataset creation property list ID @@ -445,6 +450,7 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) INTEGER(size_t) rdcc_nelmts INTEGER(size_t) rdcc_nbytes REAL :: rdcc_w0 + LOGICAL :: differ CALL h5_fixname_f(filename, fix_filename, H5P_DEFAULT_F, error) @@ -468,7 +474,8 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("H5Pget_chunk_cache_f", error, total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nslots_1), INT(nslots_4), total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nbytes_1), INT(nbytes_4), total_error) - IF(w0_1.NE.w0_4)THEN + CALL compare_floats(w0_1, w0_4, differ) + IF(differ)THEN CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error) ENDIF @@ -526,7 +533,8 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("H5Pget_chunk_cache_f", error, total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nslots_2), INT(nslots_4), total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nbytes_2), INT(nbytes_4), total_error) - IF(w0_2.NE.w0_4)THEN + CALL compare_floats(w0_2, w0_4, differ) + IF(differ)THEN CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error) ENDIF CALL H5Pclose_f(dapl2,error) @@ -558,7 +566,8 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("H5Pget_chunk_cache_f", error, total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nslots_3), INT(nslots_4), total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nbytes_2), INT(nbytes_4), total_error) - IF(w0_3.NE.w0_4)THEN + CALL compare_floats(w0_3, w0_4, differ) + IF(differ)THEN CALL VERIFYlogical("H5Pget_chunk_cache_f4", .TRUE., .FALSE., total_error) ENDIF CALL H5Pclose_f(dapl2,error) @@ -578,7 +587,8 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("H5Pget_chunk_cache_f", error, total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nslots_2), INT(nslots_4), total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nbytes_2), INT(nbytes_4), total_error) - IF(w0_2.NE.w0_4)THEN + CALL compare_floats(w0_2, w0_4, differ) + IF(differ)THEN CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error) ENDIF CALL H5Pclose_f(dapl2,error) @@ -598,7 +608,8 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("H5Pget_chunk_cache_f", error, total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nslots_2), INT(nslots_4), total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nbytes_2), INT(nbytes_4), total_error) - IF(w0_2.NE.w0_4)THEN + CALL compare_floats(w0_2, w0_4, differ) + IF(differ)THEN CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error) ENDIF ! Don't close dapl2, we will use it in the next section @@ -635,7 +646,8 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("H5Pget_chunk_cache_f", error, total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nslots_2), INT(nslots_4), total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nbytes_2), INT(nbytes_4), total_error) - IF(w0_2.NE.w0_4)THEN + CALL compare_floats(w0_2, w0_4, differ) + IF(differ)THEN CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error) ENDIF @@ -660,7 +672,8 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("H5Pget_chunk_cache_f", error, total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nslots_3), INT(nslots_4), total_error) CALL VERIFY("H5Pget_chunk_cache_f", INT(nbytes_2), INT(nbytes_4), total_error) - IF(w0_3.NE.w0_4)THEN + CALL compare_floats(w0_3, w0_4, differ) + IF(differ)THEN CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error) ENDIF @@ -687,3 +700,5 @@ SUBROUTINE test_chunk_cache(cleanup, total_error) CALL check("h5_cleanup_f", error, total_error) END SUBROUTINE test_chunk_cache + +END MODULE TH5P |