summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5A.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tH5A.f90')
-rw-r--r--fortran/test/tH5A.f9029
1 files changed, 18 insertions, 11 deletions
diff --git a/fortran/test/tH5A.f90 b/fortran/test/tH5A.f90
index 5ba2d62..b43707c 100644
--- a/fortran/test/tH5A.f90
+++ b/fortran/test/tH5A.f90
@@ -117,7 +117,7 @@ CONTAINS
!
!general purpose integer
!
- INTEGER :: i, j, wp
+ INTEGER :: i, j
INTEGER :: error ! Error flag
!
@@ -129,6 +129,8 @@ CONTAINS
!data buffers
!
INTEGER, DIMENSION(NX,NY) :: data_in
+ LOGICAL :: differ
+
!
!Initialize data_in buffer
@@ -517,22 +519,27 @@ CONTAINS
data_dims(1) = 1
CALL h5aread_f(attr3_id, H5T_NATIVE_DOUBLE, aread_double_data, data_dims, error)
CALL check("h5aread_f",error,total_error)
-
- IF( .NOT.(aread_double_data(1) .REALEQ. 3.459_Fortran_DOUBLE) )THEN
- WRITE(*,*) "Read back double attrbute is wrong", aread_double_data(1)
- total_error = total_error + 1
- ENDIF
+ differ = .FALSE.
+ if(abs(aread_double_data(1)- 3.459D0) .ge. 1.D-08) then
+ differ = .TRUE.
+ endif
+ ! This is a temporary fix
+ !CALL compare_floats(aread_double_data(1), 3.459D0, differ)
+ IF (differ) THEN
+ WRITE(*,*) "Read back double attrbute is wrong", aread_double_data(1)
+ total_error = total_error + 1
+ END IF
!
!read the real attribute data back to memory
!
data_dims(1) = 1
CALL h5aread_f(attr4_id, H5T_NATIVE_REAL, aread_real_data, data_dims, error)
CALL check("h5aread_f",error,total_error)
-
- IF( .NOT.(aread_real_data(1) .REALEQ. REAL(4.0)) )THEN
- WRITE(*,*) "Read back real attrbute is wrong", aread_real_data(1)
- total_error = total_error + 1
- ENDIF
+ CALL compare_floats(aread_real_data(1), 4.0, differ)
+ IF (differ) THEN
+ WRITE(*,*) "Read back real attrbute is wrong ", aread_real_data
+ total_error = total_error + 1
+ END IF
!
!read the Integer attribute data back to memory
!