summaryrefslogtreecommitdiffstats
path: root/fortran/test/tf_F03.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/test/tf_F03.f90')
-rw-r--r--fortran/test/tf_F03.f9048
1 files changed, 25 insertions, 23 deletions
diff --git a/fortran/test/tf_F03.f90 b/fortran/test/tf_F03.f90
index 365879a..4513783 100644
--- a/fortran/test/tf_F03.f90
+++ b/fortran/test/tf_F03.f90
@@ -1,11 +1,11 @@
-!****h* root/fortran/test/tf_F08.f90
+!****h* root/fortran/test/tf_F03.f90
!
! NAME
-! tf_F08.f90
+! tf_F03.f90
!
! FUNCTION
-! Contains Functions that are part of the F2008 standard and needed by
-! the hdf5 fortran tests.
+! Contains functions that are part of the F2003 standard, and are not F2008 compliant.
+! Needed by the hdf5 fortran tests.
!
! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
@@ -26,12 +26,27 @@
! CONTAINS SUBROUTINES
! H5_SIZEOF
!
+! NOTES
+! The Sun/Oracle compiler has the following restrictions on the SIZEOF intrinsic function:
+!
+! "The SIZEOF intrinsic cannot be applied to arrays of an assumed size, characters of a
+! length that is passed, or subroutine calls or names. SIZEOF returns default INTEGER*4 data.
+! If compiling for a 64-bit environment, the compiler will issue a warning if the result overflows
+! the INTEGER*4 data range. To use SIZEOF in a 64-bit environment with arrays larger
+! than the INTEGER*4 limit (2 Gbytes), the SIZEOF function and
+! the variables receiving the result must be declared INTEGER*8."
+!
+! Thus, we can not overload the H5_SIZEOF function to handle arrays (as used in tH5P_F03.f90), or
+! characters that do not have a set length (as used in tH5P_F03.f90), sigh...
+!
!*****
MODULE TH5_MISC_PROVISIONAL
+
+ USE ISO_C_BINDING
IMPLICIT NONE
- INTEGER, PARAMETER :: sp = KIND(0.0)
- INTEGER, PARAMETER :: dp = KIND(0.D0)
+ INTEGER, PARAMETER :: sp = SELECTED_REAL_KIND(5) ! This should map to REAL*4 on most modern processors
+ INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(10) ! This should map to REAL*8 on most modern processors
! generic compound datatype
TYPE, BIND(C) :: comp_datatype
@@ -40,12 +55,11 @@ MODULE TH5_MISC_PROVISIONAL
DOUBLE PRECISION :: y
CHARACTER(LEN=1) :: z
END TYPE comp_datatype
-
+
PUBLIC :: H5_SIZEOF
INTERFACE H5_SIZEOF
MODULE PROCEDURE H5_SIZEOF_CMPD
- MODULE PROCEDURE H5_SIZEOF_CHR
- MODULE PROCEDURE H5_SIZEOF_I, H5_SIZEOF_IV
+ MODULE PROCEDURE H5_SIZEOF_I, H5_SIZEOF_CHR
MODULE PROCEDURE H5_SIZEOF_SP,H5_SIZEOF_DP
END INTERFACE
@@ -54,7 +68,7 @@ CONTAINS
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5_sizeof_cmpd
-!DEC$endif
+ !DEC$endif
INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_CMPD(a)
IMPLICIT NONE
TYPE(comp_datatype), INTENT(in) :: a
@@ -69,7 +83,7 @@ CONTAINS
!DEC$endif
INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_CHR(a)
IMPLICIT NONE
- CHARACTER(LEN=*), INTENT(in):: a
+ CHARACTER(LEN=1), INTENT(in):: a
H5_SIZEOF_CHR = SIZEOF(a)
@@ -89,18 +103,6 @@ CONTAINS
!This definition is needed for Windows DLLs
!DEC$if defined(BUILD_HDF5_DLL)
-!DEC$attributes dllexport :: h5_sizeof_iv
-!DEC$endif
- INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_IV(a)
- IMPLICIT NONE
- INTEGER, DIMENSION(:), INTENT(in):: a
-
- H5_SIZEOF_IV = SIZEOF(a)
-
- END FUNCTION H5_SIZEOF_IV
-
-!This definition is needed for Windows DLLs
-!DEC$if defined(BUILD_HDF5_DLL)
!DEC$attributes dllexport :: h5_sizeof_sp
!DEC$endif
INTEGER(C_SIZE_T) FUNCTION H5_SIZEOF_SP(a)