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.f9019
1 files changed, 7 insertions, 12 deletions
diff --git a/fortran/test/tH5A.f90 b/fortran/test/tH5A.f90
index e3b3b2a..5b814fa 100644
--- a/fortran/test/tH5A.f90
+++ b/fortran/test/tH5A.f90
@@ -29,6 +29,10 @@
!*****
MODULE TH5A
+ USE HDF5 ! This module contains all necessary modules
+ USE TH5_MISC
+ USE TH5_MISC_GEN
+
CONTAINS
SUBROUTINE attribute_test(cleanup, total_error)
@@ -36,9 +40,6 @@ CONTAINS
! h5acreate_f, h5awrite_f, h5aclose_f,h5aread_f, h5aopen_name_f,
! h5aget_name_f,h5aget_space_f, h5aget_type_f,
!
-
- USE HDF5 ! This module contains all necessary modules
- USE TH5_MISC
IMPLICIT NONE
LOGICAL, INTENT(IN) :: cleanup
INTEGER, INTENT(INOUT) :: total_error
@@ -309,7 +310,7 @@ CONTAINS
!
CALL h5aget_storage_size_f(attr_id, attr_storage, error)
CALL check("h5aget_storage_size_f",error,total_error)
-! CALL VERIFY("h5aget_storage_size_f",attr_storage,*SizeOf(attr_storage),total_error)
+! CALL verify("h5aget_storage_size_f",attr_storage,*SizeOf(attr_storage),total_error)
CALL h5aget_storage_size_f(attr2_id, attr_storage, error)
CALL check("h5aget_storage_size_f",error,total_error)
! CALL verify("h5aget_storage_size_f",attr_storage,1,total_error)
@@ -517,21 +518,15 @@ 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)
+ CALL VERIFY("Read back double attrbute is wrong", aread_double_data(1),3.459_Fortran_DOUBLE,total_error)
- IF( .NOT.dreal_eq( REAL(aread_double_data(1),dp), 3.459_dp) )THEN
- WRITE(*,*) "Read back double attrbute is wrong", aread_double_data(1)
- total_error = total_error + 1
- ENDIF
!
!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.dreal_eq( REAL(aread_real_data(1),dp), 4.0_dp) )THEN
- WRITE(*,*) "Read back real attrbute is wrong", aread_real_data(1)
- total_error = total_error + 1
- ENDIF
+ CALL VERIFY("Read back real attrbute is wrong", aread_real_data(1),4.0,total_error)
!
!read the Integer attribute data back to memory
!