summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5P.f90
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2014-04-08 00:18:20 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2014-04-08 00:18:20 (GMT)
commitff9a10cfdacfd30fc1720b7c82bc28d204b76ce2 (patch)
tree2e7c07b41caace92775d8162012d94e79b4df029 /fortran/test/tH5P.f90
parent67a61ed22f31b9af0ace476b0cc58d7236bb9ac3 (diff)
downloadhdf5-ff9a10cfdacfd30fc1720b7c82bc28d204b76ce2.zip
hdf5-ff9a10cfdacfd30fc1720b7c82bc28d204b76ce2.tar.gz
hdf5-ff9a10cfdacfd30fc1720b7c82bc28d204b76ce2.tar.bz2
[svn-r24984] Added overload operatorZ to compare REALs for tests.
Tested on jam (gfortran, (-r8))
Diffstat (limited to 'fortran/test/tH5P.f90')
-rw-r--r--fortran/test/tH5P.f9024
1 files changed, 8 insertions, 16 deletions
diff --git a/fortran/test/tH5P.f90 b/fortran/test/tH5P.f90
index 454f507..0ed12d2 100644
--- a/fortran/test/tH5P.f90
+++ b/fortran/test/tH5P.f90
@@ -450,8 +450,6 @@ 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
@@ -474,8 +472,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)
- CALL compare_floats(w0_1, w0_4, differ)
- IF(differ)THEN
+
+ IF( .NOT.( w0_1 .REALEQ. w0_4) )THEN
CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error)
ENDIF
@@ -533,8 +531,7 @@ 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)
- CALL compare_floats(w0_2, w0_4, differ)
- IF(differ)THEN
+ IF( .NOT.( w0_2 .REALEQ. w0_4) )THEN
CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error)
ENDIF
CALL H5Pclose_f(dapl2,error)
@@ -566,8 +563,7 @@ 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)
- CALL compare_floats(w0_3, w0_4, differ)
- IF(differ)THEN
+ IF( .NOT.( w0_3 .REALEQ. w0_4) )THEN
CALL VERIFYlogical("H5Pget_chunk_cache_f4", .TRUE., .FALSE., total_error)
ENDIF
CALL H5Pclose_f(dapl2,error)
@@ -587,8 +583,7 @@ 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)
- CALL compare_floats(w0_2, w0_4, differ)
- IF(differ)THEN
+ IF( .NOT.( w0_2 .REALEQ. w0_4) ) THEN
CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error)
ENDIF
CALL H5Pclose_f(dapl2,error)
@@ -608,8 +603,7 @@ 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)
- CALL compare_floats(w0_2, w0_4, differ)
- IF(differ)THEN
+ IF( .NOT.( w0_2 .REALEQ. w0_4) ) THEN
CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error)
ENDIF
! Don't close dapl2, we will use it in the next section
@@ -646,8 +640,7 @@ 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)
- CALL compare_floats(w0_2, w0_4, differ)
- IF(differ)THEN
+ IF( .NOT.( w0_2 .REALEQ. w0_4) ) THEN
CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error)
ENDIF
@@ -672,8 +665,7 @@ 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)
- CALL compare_floats(w0_3, w0_4, differ)
- IF(differ)THEN
+ IF( .NOT.( w0_3 .REALEQ. w0_4) ) THEN
CALL VERIFYlogical("H5Pget_chunk_cache_f", .TRUE., .FALSE., total_error)
ENDIF