summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5_ff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5_ff.f90')
-rw-r--r--fortran/src/H5_ff.f90332
1 files changed, 203 insertions, 129 deletions
diff --git a/fortran/src/H5_ff.f90 b/fortran/src/H5_ff.f90
index 7dffd0a..fdb8748 100644
--- a/fortran/src/H5_ff.f90
+++ b/fortran/src/H5_ff.f90
@@ -1,3 +1,17 @@
+!****h* ROBODoc/H5LIB
+!
+! NAME
+! MODULE H5LIB
+!
+! PURPOSE
+! This module provides fortran specific helper functions for the HDF library
+!
+! USES
+! H5LIB_PROVISIONAL - This module provides helper functions for Fortran 2003
+! only features. If Fortran 2003 functions are enabled then
+! H5_ff_F03.f90 is compiled, else H5_ff_F90.f90,
+! which is just a place holder blank module, is compiled.
+! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
@@ -13,45 +27,55 @@
! access to either file, you may request a copy from help@hdfgroup.org. *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
+! NOTES
+! *** IMPORTANT ***
+! If you add a new function you must add the function name to the
+! Windows dll file 'hdf5_fortrandll.def' in the fortran/src directory.
+! This is needed for Windows based operating systems.
+!
+!*****
+
MODULE H5LIB
+ USE H5LIB_PROVISIONAL ! helper functions for Fortran 2003 features:
+ ! pre-Fortran 2003 - empty module
+ ! Forttran 2003 - contains functions
+ USE H5GLOBAL
CONTAINS
-!----------------------------------------------------------------------
-! Name: h5open_f
+!****s* H5LIB/h5open_f
!
-! Purpose: Initializes the HDF5 library and Fortran90 interface.
+! NAME
+! h5open_f
!
-! Inputs:
-! Outputs:
-! error: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Initializes the HDF5 library and Fortran90 interface.
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! OUTPUTS
+! error - error code
+! Success: 0
+! Failure: -1
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). February 28, 2001
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). February 28, 2001
!
-! Comment:
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5open_f(error)
USE H5GLOBAL
-
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
+!*****
INTEGER :: error_0, error_1, error_2, error_3
-! INTEGER, EXTERNAL :: h5init_types_c
-! INTEGER, EXTERNAL :: h5init_flags_c
-! INTEGER, EXTERNAL :: h5init1_flags_c
-! INTEGER, EXTERNAL :: h5open_c
-!
-! MS FORTRAN needs explicit interfaces for C functions called here.
-!
+! INTEGER, EXTERNAL :: h5init_types_c
+! INTEGER, EXTERNAL :: h5init_flags_c
+! INTEGER, EXTERNAL :: h5init1_flags_c
+! INTEGER, EXTERNAL :: h5open_c
+
INTERFACE
INTEGER FUNCTION h5open_c()
!DEC$IF DEFINED(HDF5F90_WINDOWS)
@@ -72,6 +96,8 @@ CONTAINS
END INTERFACE
INTERFACE
INTEGER FUNCTION h5init_flags_c(i_H5D_flags, &
+ i_H5E_flags, &
+ i_H5E_hid_flags, &
i_H5F_flags, &
i_H5FD_flags, &
i_H5FD_hid_flags, &
@@ -87,9 +113,11 @@ CONTAINS
i_H5Z_flags, &
i_H5generic_flags)
USE H5GLOBAL
+ INTEGER i_H5D_flags(H5D_FLAGS_LEN)
+ INTEGER i_H5E_flags(H5E_FLAGS_LEN)
+ INTEGER(HID_T) i_H5E_hid_flags(H5E_HID_FLAGS_LEN)
INTEGER i_H5F_flags(H5F_FLAGS_LEN)
INTEGER i_H5G_flags(H5G_FLAGS_LEN)
- INTEGER i_H5D_flags(H5D_FLAGS_LEN)
INTEGER i_H5FD_flags(H5FD_FLAGS_LEN)
INTEGER(HID_T) i_H5FD_hid_flags(H5FD_HID_FLAGS_LEN)
INTEGER i_H5I_flags(H5I_FLAGS_LEN)
@@ -102,9 +130,9 @@ CONTAINS
INTEGER i_H5T_flags(H5T_FLAGS_LEN)
INTEGER i_H5Z_flags(H5Z_FLAGS_LEN)
INTEGER i_H5generic_flags(H5generic_FLAGS_LEN)
- !DEC$IF DEFINED(HDF5F90_WINDOWS)
- !DEC$ATTRIBUTES C,reference,decorate,alias:'H5INIT_FLAGS_C'::h5init_flags_c
- !DEC$ENDIF
+ !DEC$IF DEFINED(HDF5F90_WINDOWS)
+ !DEC$ATTRIBUTES C,reference,decorate,alias:'H5INIT_FLAGS_C'::h5init_flags_c
+ !DEC$ENDIF
END FUNCTION h5init_flags_c
END INTERFACE
INTERFACE
@@ -119,6 +147,8 @@ CONTAINS
error_0 = h5open_c()
error_1 = h5init_types_c(predef_types, floating_types, integer_types)
error_2 = h5init_flags_c(H5D_flags, &
+ H5E_flags, &
+ H5E_hid_flags, &
H5F_flags, &
H5FD_flags, &
H5FD_hid_flags, &
@@ -137,35 +167,36 @@ CONTAINS
error = error_0 + error_1 + error_2 + error_3
END SUBROUTINE h5open_f
-!----------------------------------------------------------------------
-! Name: h5close_f
+!****s* H5LIB/h5close_f
!
-! Purpose: Closes the HDF5 library and Fortran90 interface.
+! NAME
+! h5close_f
!
-! Inputs:
-! Outputs:
-! error: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Closes the HDF5 library and Fortran90 interface.
!
-! Programmer: Elena Pourmal
-! August 12, 1999
+! OUTPUTS
+! error - error code
+! Success: 0
+! Failure: -1
!
-! Modifications: Explicit Fortran interfaces were added for
-! called C functions (it is needed for Windows
-! port). February 28, 2001
-!
-! Comment:
-!----------------------------------------------------------------------
+! AUTHOR
+! Elena Pourmal
+! August 12, 1999
+!
+! HISTORY
+! Explicit Fortran interfaces were added for
+! called C functions (it is needed for Windows
+! port). February 28, 2001
+!
+! SOURCE
SUBROUTINE h5close_f(error)
USE H5GLOBAL
-
IMPLICIT NONE
- INTEGER :: error_1, error_2
INTEGER, INTENT(OUT) :: error
+!*****
+ INTEGER :: error_1, error_2
! INTEGER, EXTERNAL :: h5close_types_c, h5close_c
INTERFACE
INTEGER FUNCTION h5close_c()
@@ -198,33 +229,32 @@ CONTAINS
END SUBROUTINE h5close_f
-!----------------------------------------------------------------------
-! Name: h5get_libversion_f
-!
-! Purpose: Returns the HDF5 LIbrary release number
-!
-! Inputs:
-! Outputs:
-! majnum: - major version of the library
-! minum: - minor version of the library
-! relnum: - release version of the library
-! error: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
-!
-! Programmer: Elena Pourmal
-! September 24, 2002
-!
-! Comment:
-!----------------------------------------------------------------------
-
+!****s* H5LIB/h5get_libversion_f
+!
+! NAME
+! h5get_libversion_f
+!
+! PURPOSE
+! Returns the HDF5 LIbrary release number
+!
+! OUTPUTS
+! majnum - major version of the library
+! minum - minor version of the library
+! relnum - release version of the library
+! error - error code
+! Success: 0
+! Failure: -1
+!
+! AUTHOR
+! Elena Pourmal
+! September 24, 2002
+!
+! SOURCE
SUBROUTINE h5get_libversion_f(majnum, minnum, relnum, error)
USE H5GLOBAL
-
IMPLICIT NONE
INTEGER, INTENT(OUT) :: majnum, minnum, relnum, error
+!*****
INTERFACE
INTEGER FUNCTION h5get_libversion_c(majnum, minnum, relnum)
!DEC$IF DEFINED(HDF5F90_WINDOWS)
@@ -238,34 +268,34 @@ CONTAINS
END SUBROUTINE h5get_libversion_f
-!----------------------------------------------------------------------
-! Name: h5check_version_f
-!
-! Purpose: Verifies that library versions are consistent.
-!
-! Inputs:
-! majnum: - major version of the library
-! minum: - minor version of the library
-! relnum: - release version of the library
-! Outputs:
-! error: - error code
-! Success: 0
-! Failure: application aborts
-! Optional parameters:
-! NONE
-!
-! Programmer: Elena Pourmal
-! September 24, 2002
-!
-! Comment:
-!----------------------------------------------------------------------
-
+!****s* H5LIB/h5check_version_f
+!
+! NAME
+! h5check_version_f
+!
+! PURPOSE
+! Verifies that library versions are consistent.
+!
+! INPUTS
+! majnum - major version of the library
+! minum - minor version of the library
+! relnum - release version of the library
+! OUTPUTS
+! error - error code
+! Success: 0
+! Failure: application aborts
+!
+! AUTHOR
+! Elena Pourmal
+! September 24, 2002
+!
+! SOURCE
SUBROUTINE h5check_version_f(majnum, minnum, relnum, error)
USE H5GLOBAL
-
IMPLICIT NONE
INTEGER, INTENT(IN) :: majnum, minnum, relnum
INTEGER, INTENT(OUT) :: error
+!*****
INTERFACE
INTEGER FUNCTION h5check_version_c(majnum, minnum, relnum)
!DEC$IF DEFINED(HDF5F90_WINDOWS)
@@ -278,32 +308,29 @@ CONTAINS
error = h5check_version_c(majnum, minnum, relnum)
END SUBROUTINE h5check_version_f
-
-!----------------------------------------------------------------------
-! Name: h5garbage_collect_f
+!****s* H5LIB/h5garbage_collect_f
!
-! Purpose: Garbage collects on all free-lists of all types.
+! NAME
+! h5garbage_collect_f
!
-! Inputs:
-! Outputs:
-! error: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Garbage collects on all free-lists of all types.
!
-! Programmer: Elena Pourmal
-! September 24, 2002
+! OUTPUTS
+! error - error code
+! Success: 0
+! Failure: -1
!
+! AUTHOR
+! Elena Pourmal
+! September 24, 2002
!
-! Comment:
-!----------------------------------------------------------------------
-
+! SOURCE
SUBROUTINE h5garbage_collect_f(error)
USE H5GLOBAL
-
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
+!*****
INTERFACE
INTEGER FUNCTION h5garbage_collect_c()
!DEC$IF DEFINED(HDF5F90_WINDOWS)
@@ -315,32 +342,29 @@ CONTAINS
error = h5garbage_collect_c()
END SUBROUTINE h5garbage_collect_f
-
-!----------------------------------------------------------------------
-! Name: h5dont_atexit_f
+!****s* H5LIB/h5dont_atexit_f
!
-! Purpose: Instructs library not to install atexit cleanup routine.
+! NAME
+! h5dont_atexit_f
!
-! Inputs:
-! Outputs:
-! error: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! NONE
+! PURPOSE
+! Instructs library not to install atexit cleanup routine.
!
-! Programmer: Elena Pourmal
-! September 24, 2002
+! OUTPUTS
+! error - error code
+! Success: 0
+! Failure: -1
!
+! AUTHOR
+! Elena Pourmal
+! September 24, 2002
!
-! Comment:
-!----------------------------------------------------------------------
-
+! SOURCE
SUBROUTINE h5dont_atexit_f(error)
USE H5GLOBAL
-
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
+!*****
INTERFACE
INTEGER FUNCTION h5dont_atexit_c()
!DEC$IF DEFINED(HDF5F90_WINDOWS)
@@ -352,4 +376,54 @@ CONTAINS
error = h5dont_atexit_c()
END SUBROUTINE h5dont_atexit_f
+
+!****f* H5LIB/h5kind_to_type
+!
+! NAME
+! h5kind_to_type
+!
+! PURPOSE
+! Converts the KIND to the correct HDF type
+!
+! INPUTS
+! kind - Fortran KIND parameter
+! flag - whether KIND is of type INTEGER or REAL:
+! H5_INTEGER_KIND - integer
+! H5_REAL_KIND - real
+! OUTPUTS
+! h5_type - returns the type
+!
+! AUTHOR
+! M. Scot Breitenfeld
+! Augest 25, 2008
+!
+! SOURCE
+ INTEGER(HID_T) FUNCTION h5kind_to_type(kind, flag) RESULT(h5_type)
+ USE H5GLOBAL
+ IMPLICIT NONE
+ INTEGER, INTENT(IN) :: kind
+ INTEGER, INTENT(IN) :: flag
+!*****
+ IF(flag.EQ.H5_INTEGER_KIND)THEN
+ IF(kind.EQ.Fortran_INTEGER_1)THEN
+ h5_type = H5T_NATIVE_INTEGER_1
+ ELSE IF(kind.EQ.Fortran_INTEGER_2)THEN
+ h5_type = H5T_NATIVE_INTEGER_2
+ ELSE IF(kind.EQ.Fortran_INTEGER_4)THEN
+ h5_type = H5T_NATIVE_INTEGER_4
+ ELSE IF(kind.EQ.Fortran_INTEGER_8)THEN
+ h5_type = H5T_NATIVE_INTEGER_8
+ ENDIF
+ ELSE IF(flag.EQ.H5_REAL_KIND)THEN
+ IF(kind.EQ.Fortran_REAL_4)THEN
+ h5_type = H5T_NATIVE_REAL_4
+ ELSE IF(kind.EQ.Fortran_REAL_8)THEN
+ h5_type = H5T_NATIVE_REAL_8
+ ELSE IF(kind.EQ.Fortran_REAL_16)THEN
+ h5_type = H5T_NATIVE_REAL_16
+ ENDIF
+ ENDIF
+
+ END FUNCTION h5kind_to_type
+
END MODULE H5LIB