summaryrefslogtreecommitdiffstats
path: root/fortran/test/tf.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tf.f90')
-rw-r--r--fortran/test/tf.f9043
1 files changed, 43 insertions, 0 deletions
diff --git a/fortran/test/tf.f90 b/fortran/test/tf.f90
index d48ede1..b4956ea 100644
--- a/fortran/test/tf.f90
+++ b/fortran/test/tf.f90
@@ -272,3 +272,46 @@ SUBROUTINE h5_exit_f(status)
END SUBROUTINE h5_exit_f
+!----------------------------------------------------------------------
+! Name: h5_env_nocleanup_f
+!
+! Purpose: Uses the HDF5_NOCLEANUP environment variable in Fortran
+! tests to determine if the output files should be removed
+!
+! Inputs:
+!
+! Outputs: HDF5_NOCLEANUP: .true. - don't remove test files
+! .false. - remove test files
+!
+! Programmer: M.S. Breitenfeld
+! September 30, 2008
+!
+!----------------------------------------------------------------------
+SUBROUTINE h5_env_nocleanup_f(HDF5_NOCLEANUP)
+!
+!This definition is needed for Windows DLLs
+!DEC$if defined(BUILD_HDF5_DLL)
+!DEC$attributes dllexport :: h5_env_nocleanup_f
+!DEC$endif
+ IMPLICIT NONE
+ LOGICAL, INTENT(OUT) :: HDF5_NOCLEANUP ! Return code
+ INTEGER :: status
+
+ INTERFACE
+ SUBROUTINE h5_env_nocleanup_c(status)
+ !DEC$ IF DEFINED(HDF5F90_WINDOWS)
+ !DEC$ ATTRIBUTES C,reference,decorate,alias:'H5_ENV_NOCLEANUP_C':: h5_env_nocleanup_c
+ !DEC$ ENDIF
+ INTEGER :: status
+ END SUBROUTINE h5_env_nocleanup_c
+ END INTERFACE
+
+ CALL h5_env_nocleanup_c(status)
+
+ HDF5_NOCLEANUP = .FALSE.
+ IF(status.EQ.1)THEN
+ HDF5_NOCLEANUP = .TRUE.
+ ENDIF
+
+END SUBROUTINE h5_env_nocleanup_f
+