summaryrefslogtreecommitdiffstats
path: root/fortran/test/tf.f90
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2015-03-27 22:16:49 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2015-03-27 22:16:49 (GMT)
commitff1c86df14d33cda54b36d72cf2e40a8db2cf8d2 (patch)
treece8d0c2189ac27332bcafe0dcb91eaadd8f68441 /fortran/test/tf.f90
parentd494d7b3b95cf893e6dd20688057bb13ba10422f (diff)
downloadhdf5-ff1c86df14d33cda54b36d72cf2e40a8db2cf8d2.zip
hdf5-ff1c86df14d33cda54b36d72cf2e40a8db2cf8d2.tar.gz
hdf5-ff1c86df14d33cda54b36d72cf2e40a8db2cf8d2.tar.bz2
[svn-r26631] reverted change r26629
Diffstat (limited to 'fortran/test/tf.f90')
-rw-r--r--fortran/test/tf.f9011
1 files changed, 6 insertions, 5 deletions
diff --git a/fortran/test/tf.f90 b/fortran/test/tf.f90
index 242d757..6d5911f 100644
--- a/fortran/test/tf.f90
+++ b/fortran/test/tf.f90
@@ -134,19 +134,20 @@ CONTAINS
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_TEST_DLL)
-!DEC$attributes dllexport :: verify_INTEGER_HID_T
+!DEC$attributes dllexport :: verify_Fortran_INTEGER_4
!DEC$endif
- SUBROUTINE verify_INTEGER_HID_T(string,value,correct_value,total_error)
- USE HDF5
+ SUBROUTINE verify_Fortran_INTEGER_4(string,value,correct_value,total_error)
+ USE HDF5
+ INTEGER, PARAMETER :: int_kind_8 = SELECTED_INT_KIND(Fortran_INTEGER_4) ! should map to INTEGER*4 on most modern processors
CHARACTER(LEN=*) :: string
- INTEGER(HID_T) :: value, correct_value
+ INTEGER(int_kind_8) :: value, correct_value
INTEGER :: total_error
IF (value .NE. correct_value) THEN
total_error=total_error+1
WRITE(*,*) "ERROR: INCORRECT VALIDATION ", string
ENDIF
RETURN
- END SUBROUTINE verify_INTEGER_HID_T
+ END SUBROUTINE verify_Fortran_INTEGER_4
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_TEST_DLL)