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.F90331
1 files changed, 109 insertions, 222 deletions
diff --git a/fortran/src/H5_ff.F90 b/fortran/src/H5_ff.F90
index 4c93de9..5968e73 100644
--- a/fortran/src/H5_ff.F90
+++ b/fortran/src/H5_ff.F90
@@ -1,10 +1,13 @@
-!****h* ROBODoc/H5LIB
-!
-! NAME
-! MODULE H5LIB
-!
-! PURPOSE
-! This module provides fortran specific helper functions for the HDF library
+!> @defgroup FH5 Fortran Library (H5) Interface
+!!
+!! @see H5, C-API
+!!
+!! @see @ref H5_UG, User Guide
+!!
+
+!> @ingroup FH5
+!!
+!! @brief This module provides fortran specific helper functions for the HDF library.
!
! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
@@ -32,7 +35,6 @@
! Windows dll file 'hdf5_fortrandll.def.in' in the fortran/src directory.
! This is needed for Windows based operating systems.
!
-!*****
#include <H5config_f.inc>
@@ -145,36 +147,18 @@ MODULE H5LIB
PUBLIC :: h5garbage_collect_f, h5check_version_f
CONTAINS
-!****s* H5LIB/h5open_f
-!
-! NAME
-! h5open_f
-!
-! PURPOSE
-! Initializes HDF5 Fortran interface.
-!
-! Outputs:
-! error - Returns 0 if successful and -1 if fails
-!
-! 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
-!
-! Removed call to h5open_c since this may cause a problem for an
-! application that uses HDF5 library outside HDF5 Fortran APIs.
-! October 13, 2011
-! Fortran90 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Initializes HDF5 Fortran interface.
+!!
+!! \param error \fortran_error
+!!
SUBROUTINE h5open_f(error)
USE H5F, ONLY : h5fget_obj_count_f, H5OPEN_NUM_OBJ
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
INTEGER(SIZE_T) :: H5OPEN_NUM_OBJ_LOC = 0
-!*****
INTERFACE
INTEGER FUNCTION h5init_types_c(p_types, f_types, i_types) &
@@ -646,35 +630,17 @@ CONTAINS
END SUBROUTINE h5open_f
-!****s* H5LIB/h5close_f
-!
-! NAME
-! h5close_f
-!
-! PURPOSE
-! Closes HDF5 Fortran interface.
-!
-! Outputs:
-! error - Returns 0 if successful and -1 if fails
-!
-! 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
-!
-! Removed call to h5close_c since this may cause a problem for an
-! application that uses HDF5 library outside HDF5 Fortran APIs.
-! October 13, 2011
-! Fortran90 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Closes HDF5 Fortran interface.
+!!
+!! \param error \fortran_error
+!!
SUBROUTINE h5close_f(error)
USE H5F, ONLY : h5fget_obj_count_f, H5OPEN_NUM_OBJ
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
-!*****
INTERFACE
INTEGER FUNCTION h5close_types_c(p_types, P_TYPES_LEN, &
f_types, F_TYPES_LEN, &
@@ -702,29 +668,19 @@ CONTAINS
END SUBROUTINE h5close_f
-!****s* H5LIB/h5get_libversion_f
-!
-! NAME
-! h5get_libversion_f
-!
-! PURPOSE
-! Returns the HDF5 LIbrary release number
-!
-! Outputs:
-! majnum - major version of the library
-! minnum - minor version of the library
-! relnum - release version of the library
-! error - Returns 0 if successful and -1 if fails
-!
-! AUTHOR
-! Elena Pourmal
-! September 24, 2002
-!
-! Fortran90 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Returns the HDF5 LIbrary release number
+!!
+!! \param majnum Major version of the library.
+!! \param minnum Minor version of the library.
+!! \param relnum Release version of the library.
+!! \param error \fortran_error
+!!
SUBROUTINE h5get_libversion_f(majnum, minnum, relnum, error)
IMPLICIT NONE
INTEGER, INTENT(OUT) :: majnum, minnum, relnum, error
-!*****
INTERFACE
INTEGER FUNCTION h5get_libversion_c(majnum, minnum, relnum) &
BIND(C,NAME='h5get_libversion_c')
@@ -737,32 +693,20 @@ CONTAINS
END SUBROUTINE h5get_libversion_f
-!****s* H5LIB/h5check_version_f
-!
-! NAME
-! h5check_version_f
-!
-! PURPOSE
-! Verifies that library versions are consistent.
-!
-! Inputs:
-! majnum - major version of the library
-! minnum - minor version of the library
-! relnum - release version of the library
-!
-! Outputs:
-! error - Returns 0 if successful and -1 if fails
-!
-! AUTHOR
-! Elena Pourmal
-! September 24, 2002
-!
-! Fortran90 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Verifies that library versions are consistent.
+!!
+!! \param majnum Major version of the library.
+!! \param minnum Minor version of the library.
+!! \param relnum Release version of the library.
+!! \param error \fortran_error
+!!
SUBROUTINE h5check_version_f(majnum, minnum, relnum, error)
IMPLICIT NONE
INTEGER, INTENT(IN) :: majnum, minnum, relnum
INTEGER, INTENT(OUT) :: error
-!*****
INTERFACE
INTEGER FUNCTION h5check_version_c(majnum, minnum, relnum) &
BIND(C,NAME='h5check_version_c')
@@ -774,58 +718,38 @@ CONTAINS
error = h5check_version_c(majnum, minnum, relnum)
END SUBROUTINE h5check_version_f
-!****s* H5LIB/h5garbage_collect_f
-!
-! NAME
-! h5garbage_collect_f
-!
-! PURPOSE
-! Garbage collects on all free-lists of all types.
-!
-! Outputs:
-! error - Returns 0 if successful and -1 if fails
-!
-! AUTHOR
-! Elena Pourmal
-! September 24, 2002
-!
-! Fortran90 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Garbage collects on all free-lists of all types.
+!!
+!! \param error \fortran_error
+!!
SUBROUTINE h5garbage_collect_f(error)
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
-!*****
INTERFACE
- INTEGER FUNCTION h5garbage_collect_c() &
- BIND(C,NAME='h5garbage_collect_c')
+ INTEGER FUNCTION h5garbage_collect_c() BIND(C,NAME='h5garbage_collect_c')
+ IMPLICIT NONE
END FUNCTION h5garbage_collect_c
END INTERFACE
error = h5garbage_collect_c()
END SUBROUTINE h5garbage_collect_f
-!****s* H5LIB/h5dont_atexit_f
-!
-! NAME
-! h5dont_atexit_f
-!
-! PURPOSE
-! Instructs library not to install atexit cleanup routine.
-!
-! Outputs:
-! error - Returns 0 if successful and -1 if fails
-!
-! AUTHOR
-! Elena Pourmal
-! September 24, 2002
-!
-! Fortran90 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Instructs library not to install atexit cleanup routine.
+!!
+!! \param error \fortran_error
+!!
SUBROUTINE h5dont_atexit_f(error)
IMPLICIT NONE
INTEGER, INTENT(OUT) :: error
-!*****
INTERFACE
- INTEGER FUNCTION h5dont_atexit_c() &
- BIND(C,NAME='h5dont_atexit_c')
+ INTEGER FUNCTION h5dont_atexit_c() BIND(C,NAME='h5dont_atexit_c')
+ IMPLICIT NONE
END FUNCTION h5dont_atexit_c
END INTERFACE
@@ -833,34 +757,23 @@ CONTAINS
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
-! August 25, 2008
-!
-! Fortran90 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Converts the KIND to the correct HDF type
+!!
+!! \param ikind Fortran KIND parameter.
+!! \param flag Whether KIND is of type INTEGER or REAL:
+!! \li H5_INTEGER_KIND - integer
+!! \li H5_REAL_KIND - real
+!! \result h5_type Returns the type.
+!!
INTEGER(HID_T) FUNCTION h5kind_to_type(ikind, flag) RESULT(h5_type)
USE ISO_C_BINDING
IMPLICIT NONE
INTEGER, INTENT(IN) :: ikind
INTEGER, INTENT(IN) :: flag
INTEGER :: i
-!*****
!#if H5_HAVE_Fortran_INTEGER_SIZEOF_16!=0
! ! (1) The array index assumes INTEGER*16 the last integer in the series, and
@@ -896,34 +809,20 @@ CONTAINS
END FUNCTION h5kind_to_type
-!****f* H5LIB_PROVISIONAL/h5offsetof
-!
-! NAME
-! h5offsetof
-!
-! PURPOSE
-! Computes the offset in memory
-!
-! Inputs:
-! start - starting pointer address
-! end - ending pointer address
-!
-! Outputs:
-! offset - offset of a member within the derived type
-!
-! AUTHOR
-! M. Scot Breitenfeld
-! August 25, 2008
-!
-! ACKNOWLEDGEMENTS
-! Joe Krahn
-!
-! Fortran2003 Interface:
+!>
+!! \ingroup FH5
+!!
+!! \brief Computes the offset in memory
+!!
+!! \param start Starting pointer address.
+!! \param end Ending pointer address.
+!!
+!! \result offset Offset of a member within the derived type.
+!!
FUNCTION h5offsetof(start,end) RESULT(offset)
IMPLICIT NONE
INTEGER(SIZE_T) :: offset
TYPE(C_PTR), VALUE, INTENT(IN) :: start, end
-!*****
INTEGER(C_INTPTR_T) :: int_address_start, int_address_end
int_address_start = TRANSFER(start, int_address_start)
int_address_end = TRANSFER(end , int_address_end )
@@ -932,38 +831,26 @@ CONTAINS
END FUNCTION h5offsetof
-!****f* H5LIB_PROVISIONAL/h5gmtime
-!
-! NAME
-! h5gmtime
-!
-! PURPOSE
-! Convert time_t structure (C) to Fortran DATE AND TIME storage format.
-!
-! Inputs:
-! stdtime_t - Object of type time_t that contains a time value
-!
-! Outputs:
-! datetime - A date/time array using Fortran conventions:
-! datetime(1) = year
-! datetime(2) = month
-! datetime(3) = day
-! datetime(4) = 0 ! time is expressed as UTC (or GMT timezone) */
-! datetime(5) = hour
-! datetime(6) = minute
-! datetime(7) = second
-! datetime(8) = millisecond -- not available, assigned - HUGE(0)
-!
-! AUTHOR
-! M. Scot Breitenfeld
-! January, 2019
-!
-! Fortran Interface:
- FUNCTION h5gmtime(stdtime_t)
+!>
+!! \ingroup FH5
+!!
+!! \brief Convert time_t structure (C) to Fortran DATE AND TIME storage format.
+!!
+!! \param stdtime_t Object of type time_t that contains a time value.
+!! \result datetime A date/time array using Fortran conventions:
+!! \li datetime(1) = year
+!! \li datetime(2) = month
+!! \li datetime(3) = day
+!! \li datetime(4) = 0 ! time is expressed as UTC (or GMT timezone)
+!! \li datetime(5) = hour
+!! \li datetime(6) = minute
+!! \li datetime(7) = second
+!! \li datetime(8) = millisecond -- not available, assigned - HUGE(0)
+!!
+ FUNCTION h5gmtime(stdtime_t) RESULT(datetime)
IMPLICIT NONE
INTEGER(KIND=TIME_T), INTENT(IN) :: stdtime_t
- INTEGER, DIMENSION(1:8) :: h5gmtime
-!*****
+ INTEGER, DIMENSION(1:8) :: datetime
TYPE(C_PTR) :: cptr
INTEGER(C_INT), DIMENSION(:), POINTER :: c_time
@@ -979,14 +866,14 @@ CONTAINS
cptr = gmtime(stdtime_t)
CALL C_F_POINTER(cptr, c_time, [9])
- h5gmtime(1) = INT(c_time(6)+1900) ! year starts at 1900
- h5gmtime(2) = INT(c_time(5)+1) ! month starts at 0 in C
- h5gmtime(3) = INT(c_time(4)) ! day
- h5gmtime(4) = 0 ! time is expressed as UTC (or GMT timezone)
- h5gmtime(5) = INT(c_time(3)) ! hour
- h5gmtime(6) = INT(c_time(2)) ! minute
- h5gmtime(7) = INT(c_time(1)) ! second
- h5gmtime(8) = -32767 ! millisecond is not available, assign it -HUGE(0)
+ datetime(1) = INT(c_time(6)+1900) ! year starts at 1900
+ datetime(2) = INT(c_time(5)+1) ! month starts at 0 in C
+ datetime(3) = INT(c_time(4)) ! day
+ datetime(4) = 0 ! time is expressed as UTC (or GMT timezone)
+ datetime(5) = INT(c_time(3)) ! hour
+ datetime(6) = INT(c_time(2)) ! minute
+ datetime(7) = INT(c_time(1)) ! second
+ datetime(8) = -32767 ! millisecond is not available, assign it -HUGE(0)
END FUNCTION h5gmtime