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/tH5T_F03.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/tH5T_F03.f90')
-rw-r--r-- | fortran/test/tH5T_F03.f90 | 37 |
1 files changed, 24 insertions, 13 deletions
diff --git a/fortran/test/tH5T_F03.f90 b/fortran/test/tH5T_F03.f90 index f21f84a..bd6a701 100644 --- a/fortran/test/tH5T_F03.f90 +++ b/fortran/test/tH5T_F03.f90 @@ -90,7 +90,7 @@ SUBROUTINE test_array_compound_atomic(total_error) INTEGER :: error ! Generic RETURN value INTEGER :: namelen - LOGICAL :: flag + LOGICAL :: flag, differ TYPE(C_PTR) :: f_ptr ! Needed to pass the pointer, for g95 compiler to work @@ -258,7 +258,8 @@ SUBROUTINE test_array_compound_atomic(total_error) PRINT*, 'ERROR: Wrong integer data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF - IF( .NOT.( wdata(i,j)%f .REALEQ. rdata(i,j)%f) ) THEN + CALL compare_floats(wdata(i,j)%f, rdata(i,j)%f, differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong real data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF @@ -348,6 +349,7 @@ END SUBROUTINE test_array_compound_atomic INTEGER(SIZE_T) :: attrlen ! Length of the attribute string TYPE(c_ptr) :: f_ptr + LOGICAL :: differ ! Initialize array data to write DO i = 1, SPACE1_DIM1 @@ -620,8 +622,8 @@ END SUBROUTINE test_array_compound_atomic total_error = total_error + 1 ENDIF DO k = 1, ARRAY2_DIM1 - - IF(wdata(i,j)%f(k).NE.rdata(i,j)%f(k))THEN + CALL compare_floats(wdata(i,j)%f(k), rdata(i,j)%f(k), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong real array data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF @@ -720,6 +722,7 @@ END SUBROUTINE test_array_compound_atomic INTEGER :: error TYPE(c_ptr) :: f_ptr + LOGICAL :: differ ! Initialize the data ! ------------------- @@ -831,12 +834,13 @@ END SUBROUTINE test_array_compound_atomic PRINT*, 'ERROR: Wrong integer data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF - - IF( .NOT.(cf(i)%b(j) .REALEQ. cfr(i)%b(j) ) ) THEN + CALL compare_floats(cf(i)%b(j), cfr(i)%b(j), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong real data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF - IF( .NOT.(cf(i)%c(j) .REALEQ. cfr(i)%c(j) ) ) THEN + CALL compare_floats(cf(i)%c(j), cfr(i)%c(j), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong double data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF @@ -899,7 +903,8 @@ END SUBROUTINE test_array_compound_atomic DO i = 1, LENGTH DO j = 1, ALEN - IF( .NOT.(fld(i)%b(j) .REALEQ. fldr(i)%b(j) ) ) THEN + CALL compare_floats(fld(i)%b(j), fldr(i)%b(j), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong real data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF @@ -930,11 +935,13 @@ END SUBROUTINE test_array_compound_atomic PRINT*, 'ERROR: Wrong integer data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF - IF( .NOT.(cf(i)%b(j) .REALEQ. cfr(i)%b(j) ) ) THEN + CALL compare_floats(cf(i)%b(j), cfr(i)%b(j), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong real data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF - IF( .NOT.(cf(i)%c(j) .REALEQ. cfr(i)%c(j) ) ) THEN + CALL compare_floats(cf(i)%c(j), cfr(i)%c(j), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong double data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF @@ -988,11 +995,13 @@ END SUBROUTINE test_array_compound_atomic PRINT*, 'ERROR: Wrong integer data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF - IF( .NOT.(cf(i)%b(j) .REALEQ. cfr(i)%b(j) ) ) THEN + CALL compare_floats(cf(i)%b(j),cfr(i)%b(j), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong real data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF - IF( .NOT.(cf(i)%c(j) .REALEQ. cfr(i)%c(j) ) ) THEN + CALL compare_floats(cf(i)%c(j), cfr(i)%c(j), differ) + IF(differ)THEN PRINT*, 'ERROR: Wrong double data is read back by H5Dread_f ' total_error = total_error + 1 ENDIF @@ -2997,6 +3006,7 @@ SUBROUTINE test_nbit(total_error ) LOGICAL :: status INTEGER(hsize_t) :: i, j TYPE(C_PTR) :: f_ptr + LOGICAL :: differ ! check to see if filter is available CALL H5Zfilter_avail_f(H5Z_FILTER_NBIT_F, status, error) @@ -3069,7 +3079,8 @@ SUBROUTINE test_nbit(total_error ) i_loop: DO i = 1, dims(1) j_loop: DO j = 1, dims(2) IF(.NOT.(orig_data(i,j).EQ.orig_data(i,j))) CYCLE ! skip IF value is NaN - IF( .NOT.(new_data(i,j) .REALEQ. orig_data(i,j) ) ) THEN + CALL compare_floats(new_data(i,j), orig_data(i,j), differ) + IF(differ)THEN total_error = total_error + 1 WRITE(*,'(" Read different values than written.")') WRITE(*,'(" At index ", 2(1X,I0))') i, j |