summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Aff.F90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Aff.F90')
-rw-r--r--fortran/src/H5Aff.F90142
1 files changed, 72 insertions, 70 deletions
diff --git a/fortran/src/H5Aff.F90 b/fortran/src/H5Aff.F90
index 2f1e6d0..b30044d 100644
--- a/fortran/src/H5Aff.F90
+++ b/fortran/src/H5Aff.F90
@@ -96,12 +96,12 @@ MODULE H5A
! Interface for the function used to pass the C pointer of the buffer
! to the C H5Awrite routine
INTERFACE
- INTEGER FUNCTION h5awrite_f_c(attr_id, mem_type_id, buf) BIND(C, NAME='h5awrite_f_c')
+ INTEGER FUNCTION h5awrite_f_c(attr_id, memtype_id, buf) BIND(C, NAME='h5awrite_f_c')
IMPORT :: c_ptr
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: attr_id
- INTEGER(HID_T), INTENT(IN) :: mem_type_id
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
TYPE(C_PTR), VALUE :: buf
END FUNCTION h5awrite_f_c
END INTERFACE
@@ -109,12 +109,12 @@ MODULE H5A
! Interface for the function used to pass the C pointer of the buffer
! to the C H5Aread routine
INTERFACE
- INTEGER FUNCTION h5aread_f_c(attr_id, mem_type_id, buf) BIND(C, NAME='h5aread_f_c')
+ INTEGER FUNCTION h5aread_f_c(attr_id, memtype_id, buf) BIND(C, NAME='h5aread_f_c')
IMPORT :: c_ptr
IMPORT :: HID_T
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: attr_id
- INTEGER(HID_T), INTENT(IN) :: mem_type_id
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
TYPE(C_PTR), VALUE :: buf
END FUNCTION h5aread_f_c
END INTERFACE
@@ -207,7 +207,7 @@ CONTAINS
!! \param type_id Attribute datatype identifier
!! \param space_id Attribute dataspace identifier
!! \param attr_id Attribute identifier
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param acpl_id Attribute creation property list identifier
!! \param aapl_id Attribute access property list identifier
@@ -229,8 +229,8 @@ CONTAINS
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T) , INTENT(IN), OPTIONAL :: acpl_id
INTEGER(HID_T) , INTENT(IN), OPTIONAL :: aapl_id
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
INTEGER(HID_T) :: acpl_id_default
@@ -238,7 +238,6 @@ CONTAINS
TYPE(C_PTR) :: file_default = C_NULL_PTR
TYPE(C_PTR) :: func_default = C_NULL_PTR
INTEGER(KIND=C_INT) :: line_default = 0
-
CHARACTER(LEN=LEN_TRIM(name)+1,KIND=C_CHAR) :: c_name
INTERFACE
@@ -583,7 +582,7 @@ CONTAINS
!! \brief Closes the specified attribute.
!!
!! \param attr_id Attribute identifier
-!! \param hdferr \fortran_error
+!! \param hdferr \fortran_error
!!
!! See C API: @ref H5Aclose()
!!
@@ -609,7 +608,7 @@ CONTAINS
!! \brief Asynchronously closes the specified attribute.
!!
!! \param attr_id Attribute identifier
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param file \fortran_file
!! \param func \fortran_func
@@ -622,8 +621,8 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: attr_id
INTEGER(HID_T), INTENT(IN) :: es_id
INTEGER, INTENT(OUT) :: hdferr
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
TYPE(C_PTR) :: file_default = C_NULL_PTR
@@ -779,6 +778,7 @@ CONTAINS
!! \param obj_name Name of object, relative to location, whose attribute is to be renamed
!! \param old_attr_name Prior attribute name
!! \param new_attr_name New attribute name
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param lapl_id Link access property list identifier
!! \param file \fortran_file
@@ -797,8 +797,8 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: es_id
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T), INTENT(IN), OPTIONAL :: lapl_id
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
INTEGER(HID_T) :: lapl_id_default
@@ -891,7 +891,7 @@ CONTAINS
!! \param obj_id Identifier for object to which attribute is attached
!! \param attr_name Name of attribute to open
!! \param attr_id Attribute identifier
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param aapl_id Attribute access property list
!! \param file \fortran_file
@@ -908,8 +908,8 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: es_id
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T), INTENT(IN), OPTIONAL :: aapl_id
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN) , OPTIONAL :: line
INTEGER(HID_T) :: aapl_id_default
@@ -1155,7 +1155,7 @@ CONTAINS
!! \li H5_ITER_N_F - Number of iteration orders
!! \param n Attribute’s position in index.
!! \param attr_id Attribute identifier.
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param aapl_id Attribute access property list.
!! \param lapl_id Link access property list.
@@ -1178,8 +1178,8 @@ CONTAINS
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T), INTENT(IN), OPTIONAL :: aapl_id
INTEGER(HID_T), INTENT(IN), OPTIONAL :: lapl_id
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN) , OPTIONAL :: line
INTEGER(HID_T) :: aapl_id_default
@@ -1507,7 +1507,7 @@ CONTAINS
!! \param type_id Attribute datatype identifier
!! \param space_id Attribute dataspace identifier
!! \param attr An attribute identifier
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param acpl_id Attribute creation property list identifier (Currently not used.)
!! \param aapl_id Attribute access property list identifier (Currently not used.)
@@ -1534,8 +1534,8 @@ CONTAINS
INTEGER(HID_T), INTENT(IN), OPTIONAL :: acpl_id
INTEGER(HID_T), INTENT(IN), OPTIONAL :: aapl_id
INTEGER(HID_T), INTENT(IN), OPTIONAL :: lapl_id
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
INTEGER(HID_T) :: acpl_id_default
@@ -1644,8 +1644,10 @@ CONTAINS
!!
!! \param obj_id Object identifier
!! \param attr_name Attribute name
-!! \param attr_exists Pointer to attribute exists status, must be of type LOGICAL(C_BOOL) and initialize to .FALSE.
-!! \param es_id \es_id
+!! \param attr_exists Pointer to attribute exists status. It should be declared INTEGER(C_INT) and initialized
+!! to zero (false) for portability. It will return one when true. LOGICAL(C_BOOL) is also
+!! acceptable but may encounter atypical anomalies. It should be initialized to false when used.
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param file \fortran_file
!! \param func \fortran_func
@@ -1657,11 +1659,11 @@ CONTAINS
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: obj_id
CHARACTER(LEN=*), INTENT(IN) :: attr_name
- TYPE(C_PTR) , INTENT(INOUT) :: attr_exists
+ TYPE(C_PTR) , INTENT(IN) :: attr_exists
INTEGER(HID_T) , INTENT(IN) :: es_id
INTEGER , INTENT(OUT) :: hdferr
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
CHARACTER(LEN=LEN_TRIM(attr_name)+1,KIND=C_CHAR) :: c_attr_name
@@ -1760,7 +1762,7 @@ CONTAINS
!! \param obj_name Object name either relative to loc_id, absolute from the file’s root group, or '. '(a dot)
!! \param attr_name Attribute name
!! \param attr_exists Pointer to attribute exists status, must be of type LOGICAL(C_BOOL) and initialize to .FALSE.
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param lapl_id Link access property list identifier
!! \param file \fortran_file
@@ -1774,12 +1776,12 @@ CONTAINS
INTEGER (HID_T), INTENT(IN) :: loc_id
CHARACTER(LEN=*), INTENT(IN) :: obj_name
CHARACTER(LEN=*), INTENT(IN) :: attr_name
- TYPE(C_PTR) , INTENT(INOUT) :: attr_exists
+ TYPE(C_PTR) , INTENT(IN) :: attr_exists
INTEGER (HID_T), INTENT(IN) :: es_id
INTEGER , INTENT(OUT) :: hdferr
INTEGER (HID_T), INTENT(IN) , OPTIONAL :: lapl_id
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN) , OPTIONAL :: line
INTEGER(HID_T) :: lapl_id_default
@@ -1890,7 +1892,7 @@ CONTAINS
!! \param obj_name Object name either relative to loc_id, absolute from the file’s root group, or '.' (a dot)
!! \param attr_name Attribute name
!! \param attr_id Attribute identifier
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param aapl_id Attribute access property list (Currently unused; should be passed in as H5P_DEFAULT.)
!! \param lapl_id Link access property list identifier
@@ -1912,8 +1914,8 @@ CONTAINS
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T), INTENT(IN), OPTIONAL :: aapl_id
INTEGER(HID_T), INTENT(IN), OPTIONAL :: lapl_id
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
INTEGER(HID_T) :: aapl_id_default
@@ -2010,7 +2012,7 @@ CONTAINS
!! \param loc_id Location or object identifier; may be dataset or group
!! \param old_attr_name Prior attribute name
!! \param new_attr_name New attribute name
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param file \fortran_file
!! \param func \fortran_func
@@ -2026,8 +2028,8 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: new_attr_name
INTEGER(HID_T), INTENT(IN) :: es_id
INTEGER, INTENT(OUT) :: hdferr
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
TYPE(C_PTR) :: file_default = C_NULL_PTR
@@ -2073,7 +2075,7 @@ CONTAINS
!! \param attr_id Identifier of an attribute to read.
!! \param memtype_id Identifier of the attribute datatype (in memory).
!! \param buf Buffer for data to be read.
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param file \fortran_file
!! \param func \fortran_func
@@ -2082,15 +2084,15 @@ CONTAINS
!! See C API: @ref H5Aread_async()
!!
- SUBROUTINE h5aread_async_f(attr_id, mem_type_id, buf, es_id, hdferr, file, func, line)
+ SUBROUTINE h5aread_async_f(attr_id, memtype_id, buf, es_id, hdferr, file, func, line)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id
- INTEGER(HID_T), INTENT(IN) :: mem_type_id
- TYPE(C_PTR) , INTENT(OUT) :: buf
- INTEGER(HID_T), INTENT(IN) :: es_id
- INTEGER , INTENT(OUT) :: hdferr
- TYPE(C_PTR), OPTIONAL :: file
- TYPE(C_PTR), OPTIONAL :: func
+ INTEGER(HID_T), INTENT(IN) :: attr_id
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
+ TYPE(C_PTR) , INTENT(IN) :: buf
+ INTEGER(HID_T), INTENT(IN) :: es_id
+ INTEGER , INTENT(OUT) :: hdferr
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: file
+ TYPE(C_PTR), OPTIONAL, INTENT(IN) :: func
INTEGER , INTENT(IN), OPTIONAL :: line
TYPE(C_PTR) :: file_default = C_NULL_PTR
@@ -2098,7 +2100,7 @@ CONTAINS
INTEGER(KIND=C_INT) :: line_default = 0
INTERFACE
- INTEGER FUNCTION H5Aread_async(file, func, line, attr_id, mem_type_id, buf, es_id) &
+ INTEGER FUNCTION H5Aread_async(file, func, line, attr_id, memtype_id, buf, es_id) &
BIND(C,NAME='H5Aread_async')
IMPORT :: C_CHAR, C_INT, C_PTR
IMPORT :: HID_T
@@ -2107,7 +2109,7 @@ CONTAINS
TYPE(C_PTR), VALUE :: func
INTEGER(C_INT), VALUE :: line
INTEGER(HID_T), VALUE :: attr_id
- INTEGER(HID_T), VALUE :: mem_type_id
+ INTEGER(HID_T), VALUE :: memtype_id
TYPE(C_PTR) , VALUE :: buf
INTEGER(HID_T), VALUE :: es_id
END FUNCTION H5Aread_async
@@ -2117,7 +2119,7 @@ CONTAINS
IF (PRESENT(func)) func_default = func
IF (PRESENT(line)) line_default = INT(line, C_INT)
- hdferr = H5Aread_async(file_default, func_default, line_default, attr_id, mem_type_id, buf, es_id)
+ hdferr = H5Aread_async(file_default, func_default, line_default, attr_id, memtype_id, buf, es_id)
END SUBROUTINE h5aread_async_f
@@ -2129,7 +2131,7 @@ CONTAINS
!! \param attr_id Identifier of an attribute to read.
!! \param memtype_id Identifier of the attribute datatype (in memory).
!! \param buf Data to be written.
-!! \param es_id \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param file \fortran_file
!! \param func \fortran_func
@@ -2138,13 +2140,13 @@ CONTAINS
!! See C API: @ref H5Awrite_async()
!!
- SUBROUTINE h5awrite_async_f(attr_id, mem_type_id, buf, es_id, hdferr, file, func, line)
+ SUBROUTINE h5awrite_async_f(attr_id, memtype_id, buf, es_id, hdferr, file, func, line)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: attr_id
- INTEGER(HID_T), INTENT(IN) :: mem_type_id
- TYPE(C_PTR) , INTENT(IN) :: buf
- INTEGER(HID_T), INTENT(IN) :: es_id
- INTEGER , INTENT(OUT) :: hdferr
+ INTEGER(HID_T), INTENT(IN) :: attr_id
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
+ TYPE(C_PTR) , INTENT(IN) :: buf
+ INTEGER(HID_T), INTENT(IN) :: es_id
+ INTEGER , INTENT(OUT) :: hdferr
TYPE(C_PTR), OPTIONAL :: file
TYPE(C_PTR), OPTIONAL :: func
INTEGER , INTENT(IN), OPTIONAL :: line
@@ -2154,7 +2156,7 @@ CONTAINS
INTEGER(KIND=C_INT) :: line_default = 0
INTERFACE
- INTEGER FUNCTION H5Awrite_async(file, func, line, attr_id, mem_type_id, buf, es_id) &
+ INTEGER FUNCTION H5Awrite_async(file, func, line, attr_id, memtype_id, buf, es_id) &
BIND(C,NAME='H5Awrite_async')
IMPORT :: C_CHAR, C_INT, C_PTR
IMPORT :: HID_T
@@ -2163,7 +2165,7 @@ CONTAINS
TYPE(C_PTR), VALUE :: func
INTEGER(C_INT), VALUE :: line
INTEGER(HID_T), VALUE :: attr_id
- INTEGER(HID_T), VALUE :: mem_type_id
+ INTEGER(HID_T), VALUE :: memtype_id
TYPE(C_PTR) , VALUE :: buf
INTEGER(HID_T), VALUE :: es_id
END FUNCTION H5Awrite_async
@@ -2173,7 +2175,7 @@ CONTAINS
IF (PRESENT(func)) func_default = func
IF (PRESENT(line)) line_default = INT(line, C_INT)
- hdferr = H5Awrite_async(file_default, func_default, line_default, attr_id, mem_type_id, buf, es_id)
+ hdferr = H5Awrite_async(file_default, func_default, line_default, attr_id, memtype_id, buf, es_id)
END SUBROUTINE h5awrite_async_f
@@ -2239,10 +2241,10 @@ CONTAINS
!! See C API: @ref H5Aread()
!!
SUBROUTINE h5aread_f(attr_id, memtype_id, buf, hdferr)
- INTEGER(HID_T), INTENT(IN) :: attr_id
- INTEGER(HID_T), INTENT(IN) :: memtype_id
- TYPE(C_PTR) , INTENT(INOUT) :: buf
- INTEGER , INTENT(OUT) :: hdferr
+ INTEGER(HID_T), INTENT(IN) :: attr_id
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
+ TYPE(C_PTR) , INTENT(IN) :: buf
+ INTEGER , INTENT(OUT) :: hdferr
END SUBROUTINE h5aread_f
!>
@@ -2299,14 +2301,14 @@ CONTAINS
END SUBROUTINE h5awrite_char_scalar_fix
- SUBROUTINE h5awrite_ptr(attr_id, mem_type_id, buf, hdferr)
+ SUBROUTINE h5awrite_ptr(attr_id, memtype_id, buf, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: attr_id
- INTEGER(HID_T), INTENT(IN) :: mem_type_id
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
TYPE(C_PTR), INTENT(IN), TARGET :: buf
INTEGER, INTENT(OUT) :: hdferr
- hdferr = H5Awrite_f_c(attr_id, mem_type_id, buf)
+ hdferr = H5Awrite_f_c(attr_id, memtype_id, buf)
END SUBROUTINE h5awrite_ptr
@@ -2337,14 +2339,14 @@ CONTAINS
END SUBROUTINE h5aread_char_scalar_fix
- SUBROUTINE h5aread_ptr(attr_id, mem_type_id, buf, hdferr)
+ SUBROUTINE h5aread_ptr(attr_id, memtype_id, buf, hdferr)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: attr_id
- INTEGER(HID_T), INTENT(IN) :: mem_type_id
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
TYPE(C_PTR), INTENT(INOUT) :: buf
INTEGER, INTENT(OUT) :: hdferr
- hdferr = H5Aread_f_c(attr_id, mem_type_id, buf)
+ hdferr = H5Aread_f_c(attr_id, memtype_id, buf)
END SUBROUTINE h5aread_ptr