summaryrefslogtreecommitdiffstats
path: root/fortran/test/tf.f90
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2008-05-21 15:02:24 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2008-05-21 15:02:24 (GMT)
commitfcf8a9a2cbdca2dd8e8a7af51961ad9b0729c380 (patch)
tree1c6911ba828f6e4c729f7ea65be0d96dc3d9d49c /fortran/test/tf.f90
parent0c40ae2d42f935dcc2d8eed01a4c0e877417ef90 (diff)
downloadhdf5-fcf8a9a2cbdca2dd8e8a7af51961ad9b0729c380.zip
hdf5-fcf8a9a2cbdca2dd8e8a7af51961ad9b0729c380.tar.gz
hdf5-fcf8a9a2cbdca2dd8e8a7af51961ad9b0729c380.tar.bz2
[svn-r15054] Purpose:
Made reporting of the test status global by handling the output via a module. Cleaned-up output to the terminal. Description: Put writing the test status as a call to a subroutine instead of on a per account basis. Added the dependency of compiling in the correct order in the Makefiles for use of the Module.
Diffstat (limited to 'fortran/test/tf.f90')
-rw-r--r--fortran/test/tf.f9047
1 files changed, 46 insertions, 1 deletions
diff --git a/fortran/test/tf.f90 b/fortran/test/tf.f90
index 1cbac24..b69152e 100644
--- a/fortran/test/tf.f90
+++ b/fortran/test/tf.f90
@@ -18,11 +18,56 @@
! This file contains subroutines which are used in
! all the hdf5 fortran tests
!
+MODULE error_handler
+
+! Controls the output style for reporting test results
+
+ CHARACTER(LEN=8) :: error_string
+ CHARACTER(LEN=8), PARAMETER :: success = ' PASSED '
+ CHARACTER(LEN=8), PARAMETER :: failure = '*FAILED*'
+ CHARACTER(LEN=8), PARAMETER :: skip = '--SKIP--'
+ CHARACTER(LEN=4), PARAMETER :: e_format ='(8a)'
+
+CONTAINS
+
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: check
+!DEC$attributes dllexport :: write_test_status
!DEC$endif
+ SUBROUTINE write_test_status( test_result, test_title, total_error)
+
+! Writes the results of the tests
+
+ IMPLICIT NONE
+
+ INTEGER, INTENT(IN) :: test_result ! negative, --skip --
+ ! 0 , passed
+ ! positive, failed
+
+ CHARACTER(LEN=*), INTENT(IN) :: test_title ! Short description of test
+ INTEGER, INTENT(INOUT) :: total_error ! Accumulated error
+ error_string = failure
+ IF (test_result == 0) THEN
+ error_string = success
+ ELSE IF (test_result == -1) THEN
+ error_string = skip
+ ENDIF
+
+ WRITE(*, fmt = '(A,T72)', advance = 'no') test_title
+ WRITE(*, fmt = e_format) error_string
+
+ IF(test_result.GT.0) total_error = total_error + test_result
+
+ END SUBROUTINE write_test_status
+
+END MODULE error_handler
+
+
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: check
+!DEC$endif
SUBROUTINE check(string,error,total_error)
CHARACTER(LEN=*) :: string
INTEGER :: error, total_error