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.F9065
1 files changed, 33 insertions, 32 deletions
diff --git a/fortran/src/H5Aff.F90 b/fortran/src/H5Aff.F90
index 23bfaea..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
@@ -582,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()
!!
@@ -608,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
@@ -778,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
@@ -890,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
@@ -1154,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.
@@ -1506,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.)
@@ -1646,7 +1647,7 @@ CONTAINS
!! \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 \es_id
+!! \param es_id \fortran_es_id
!! \param hdferr \fortran_error
!! \param file \fortran_file
!! \param func \fortran_func
@@ -1761,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
@@ -1891,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
@@ -2011,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
@@ -2074,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
@@ -2083,10 +2084,10 @@ 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
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
TYPE(C_PTR) , INTENT(IN) :: buf
INTEGER(HID_T), INTENT(IN) :: es_id
INTEGER , INTENT(OUT) :: hdferr
@@ -2099,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
@@ -2108,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
@@ -2118,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
@@ -2130,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
@@ -2139,10 +2140,10 @@ 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
+ INTEGER(HID_T), INTENT(IN) :: memtype_id
TYPE(C_PTR) , INTENT(IN) :: buf
INTEGER(HID_T), INTENT(IN) :: es_id
INTEGER , INTENT(OUT) :: hdferr
@@ -2155,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
@@ -2164,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
@@ -2174,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
@@ -2300,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
@@ -2338,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