diff options
author | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2014-04-08 01:00:24 (GMT) |
---|---|---|
committer | Scot Breitenfeld <brtnfld@hdfgroup.org> | 2014-04-08 01:00:24 (GMT) |
commit | d1f2b1a682213d98db080e91c09d3f95b4f2b3b0 (patch) | |
tree | 3f38c808358221ffbe9232ba1c23ebe439bfdb30 /fortran/test/tH5P.f90 | |
parent | ff9a10cfdacfd30fc1720b7c82bc28d204b76ce2 (diff) | |
download | hdf5-d1f2b1a682213d98db080e91c09d3f95b4f2b3b0.zip hdf5-d1f2b1a682213d98db080e91c09d3f95b4f2b3b0.tar.gz hdf5-d1f2b1a682213d98db080e91c09d3f95b4f2b3b0.tar.bz2 |
[svn-r24985] reverted the r24984 update.
Diffstat (limited to 'fortran/test/tH5P.f90')
-rw-r--r-- | fortran/test/tH5P.f90 | 24 |
1 files changed, 16 insertions, 8 deletions
diff --git a/fortran/test/tH5P.f90 b/fortran/test/tH5P.f90 index 0ed12d2..454f507 100644 --- a/fortran/test/tH5P.f90 +++ b/fortran/test/tH5P.f90 @@ -450,6 +450,8 @@ 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) IF (error .NE. 0) THEN @@ -472,8 +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( .NOT.( w0_1 .REALEQ. 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 @@ -531,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( .NOT.( w0_2 .REALEQ. 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) @@ -563,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( .NOT.( w0_3 .REALEQ. 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) @@ -583,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( .NOT.( w0_2 .REALEQ. 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) @@ -603,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( .NOT.( w0_2 .REALEQ. 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 @@ -640,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( .NOT.( w0_2 .REALEQ. 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 @@ -665,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( .NOT.( w0_3 .REALEQ. 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 |