summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Lff.f90
diff options
context:
space:
mode:
Diffstat (limited to 'fortran/src/H5Lff.f90')
-rw-r--r--fortran/src/H5Lff.f90424
1 files changed, 212 insertions, 212 deletions
diff --git a/fortran/src/H5Lff.f90 b/fortran/src/H5Lff.f90
index e38dade..8d30c20 100644
--- a/fortran/src/H5Lff.f90
+++ b/fortran/src/H5Lff.f90
@@ -1,4 +1,4 @@
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
! All rights reserved. *
@@ -11,7 +11,7 @@
! is linked from the top-level documents page. It can also be found at *
! http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
! access to either file, you may request a copy from help@hdfgroup.org. *
-! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
+! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
!
! This file contains Fortran90 interfaces for H5L functions.
@@ -23,7 +23,7 @@ MODULE H5L
CONTAINS
!----------------------------------------------------------------------
-! Name: h5lcopy_f
+! Name: h5lcopy_f
!
! Purpose: Copies a link from one location to another.
!
@@ -34,11 +34,11 @@ CONTAINS
! dest_name - Name to be assigned to the NEW copy
! loc_id - Identifier of the file or group containing the object
! name - Name of the link to delete
-!
-! Outputs:
+!
+! Outputs:
! hdferr - error code:
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lcpl_id - Link creation property list identifier
! lapl_id - Link access property list identifier
@@ -48,7 +48,7 @@ CONTAINS
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5lcopy_f(src_loc_id, src_name, dest_loc_id, dest_name, hdferr, &
lcpl_id, lapl_id)
@@ -58,17 +58,17 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: dest_loc_id ! Location identifier specifying the destination of the copy
CHARACTER(LEN=*), INTENT(IN) :: dest_name ! Name to be assigned to the NEW copy
- INTEGER, INTENT(OUT) :: hdferr ! Error code:
+ INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lcpl_id ! Link creation property list identifier
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
-
+
INTEGER(HID_T) :: lcpl_id_default
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: src_namelen
INTEGER(SIZE_T) :: dest_namelen
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -84,10 +84,10 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: src_name
INTEGER(HID_T), INTENT(IN) :: dest_loc_id
CHARACTER(LEN=*), INTENT(IN) :: dest_name
-
+
INTEGER(HID_T) :: lcpl_id_default
INTEGER(HID_T) :: lapl_id_default
-
+
INTEGER(SIZE_T) :: src_namelen
INTEGER(SIZE_T) :: dest_namelen
END FUNCTION h5lcopy_c
@@ -107,18 +107,18 @@ CONTAINS
END SUBROUTINE h5lcopy_f
!----------------------------------------------------------------------
-! Name: h5ldelete_f
+! Name: h5ldelete_f
!
! Purpose: Removes a link from a group.
!
-! Inputs:
+! Inputs:
! loc_id - Identifier of the file or group containing the object
! name - Name of the link to delete
-!
-! Outputs:
-! hdferr: - error code
+!
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lapl_id - Link access property list identifier
!
@@ -127,18 +127,18 @@ CONTAINS
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5ldelete_f(loc_id, name, hdferr, lapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier of the file or group containing the object
CHARACTER(LEN=*), INTENT(IN) :: name ! Name of the link to delete
- INTEGER, INTENT(OUT) :: hdferr ! Error code:
+ INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: namelen
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
@@ -163,10 +163,10 @@ CONTAINS
hdferr = h5ldelete_c(loc_id, name, namelen, lapl_id_default)
- END SUBROUTINE h5ldelete_f
+ END SUBROUTINE h5ldelete_f
!----------------------------------------------------------------------
-! Name: H5Lcreate_soft_f
+! Name: H5Lcreate_soft_f
!
! Purpose: Creates a soft link to an object.
!
@@ -174,11 +174,11 @@ CONTAINS
! target_path - Path to the target object, which is not required to exist.
! link_loc_id - The file or group identifier for the new link.
! link_name - The name of the new link.
-!
-! Outputs:
-! hdferr: - error code
+!
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lcpl_id - Link creation property list identifier.
! lapl_id - Link access property list identifier.
@@ -188,20 +188,20 @@ CONTAINS
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5lcreate_soft_f(target_path, link_loc_id, link_name, hdferr, lcpl_id, lapl_id)
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(IN) :: target_path ! Path to the target object, which is not required to exist.
INTEGER(HID_T), INTENT(IN) :: link_loc_id ! The file or group identifier for the new link.
CHARACTER(LEN=*), INTENT(IN) :: link_name ! The name of the new link.
- INTEGER, INTENT(OUT) :: hdferr ! Error code:
+ INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lcpl_id ! Link creation property list identifier.
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier.
- INTEGER(HID_T) :: lcpl_id_default
- INTEGER(HID_T) :: lapl_id_default
+ INTEGER(HID_T) :: lcpl_id_default
+ INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: target_path_len
INTEGER(SIZE_T) :: link_name_len
@@ -243,7 +243,7 @@ CONTAINS
END SUBROUTINE h5lcreate_soft_f
!----------------------------------------------------------------------
-! Name: H5Lcreate_hard_f
+! Name: H5Lcreate_hard_f
!
! Purpose: Creates a hard link to an object.
!
@@ -253,11 +253,11 @@ CONTAINS
! obj_name - Name of the target object, which must already exist.
! link_loc_id - The file or group identifier for the new link.
! link_name - The name of the new link.
-!
-! Outputs:
-! hdferr: - error code
+!
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lcpl_id - Link creation property list identifier.
! lapl_id - Link access property list identifier.
@@ -267,7 +267,7 @@ CONTAINS
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5lcreate_hard_f(obj_loc_id, obj_name, link_loc_id, link_name, hdferr, lcpl_id, lapl_id)
IMPLICIT NONE
@@ -276,23 +276,23 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: link_loc_id ! The file or group identifier for the new link.
CHARACTER(LEN=*), INTENT(IN) :: link_name ! The name of the new link.
- INTEGER, INTENT(OUT) :: hdferr ! Error code:
+ INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lcpl_id ! Link creation property list identifier.
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier.
- INTEGER(HID_T) :: lcpl_id_default
+ INTEGER(HID_T) :: lcpl_id_default
INTEGER(HID_T) :: lapl_id_default
-
- INTEGER(SIZE_T) :: obj_namelen
+
+ INTEGER(SIZE_T) :: obj_namelen
INTEGER(SIZE_T) :: link_namelen
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
INTEGER FUNCTION h5lcreate_hard_c(obj_loc_id, obj_name, obj_namelen, &
- link_loc_id, link_name, link_namelen, lcpl_id_default, lapl_id_default)
+ link_loc_id, link_name, link_namelen, lcpl_id_default, lapl_id_default)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
@@ -303,13 +303,13 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: obj_name
INTEGER(HID_T), INTENT(IN) :: link_loc_id
CHARACTER(LEN=*), INTENT(IN) :: link_name
- INTEGER(SIZE_T) :: obj_namelen
+ INTEGER(SIZE_T) :: obj_namelen
INTEGER(SIZE_T) :: link_namelen
INTEGER(HID_T) :: lcpl_id_default
INTEGER(HID_T) :: lapl_id_default
END FUNCTION h5lcreate_hard_c
END INTERFACE
- obj_namelen = LEN(obj_name)
+ obj_namelen = LEN(obj_name)
link_namelen = LEN(link_name)
lcpl_id_default = H5P_DEFAULT_F
@@ -323,22 +323,22 @@ CONTAINS
END SUBROUTINE h5lcreate_hard_f
!----------------------------------------------------------------------
-! Name: H5Lcreate_external_f
+! Name: H5Lcreate_external_f
!
! Purpose: Creates a soft link to an object in a different file.
!
! Inputs:
!
-! file_name - Name of the file containing the target object. Neither the file nor the target object is
+! file_name - Name of the file containing the target object. Neither the file nor the target object is
! required to exist. May be the file the link is being created in.
! obj_name - Path within the target file to the target object.
! link_loc_id - The file or group identifier for the new link.
! link_name - The name of the new link.
-!
-! Outputs:
-! hdferr: - error code
+!
+! Outputs:
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lcpl_id - Link creation property list identifier.
! lapl_id - Link access property list identifier.
@@ -348,35 +348,35 @@ CONTAINS
!
! Modifications:
!
-! Comment:
+! Comment:
!----------------------------------------------------------------------
SUBROUTINE h5lcreate_external_f(file_name, obj_name, link_loc_id, link_name, hdferr, lcpl_id, lapl_id)
IMPLICIT NONE
- CHARACTER(LEN=*), INTENT(IN) :: file_name ! Name of the file containing the target object. Neither
- ! the file nor the target object is required to exist.
+ CHARACTER(LEN=*), INTENT(IN) :: file_name ! Name of the file containing the target object. Neither
+ ! the file nor the target object is required to exist.
! May be the file the link is being created in.
CHARACTER(LEN=*), INTENT(IN) :: obj_name ! Name of the target object, which must already exist.
INTEGER(HID_T), INTENT(IN) :: link_loc_id ! The file or group identifier for the new link.
CHARACTER(LEN=*), INTENT(IN) :: link_name ! The name of the new link.
- INTEGER, INTENT(OUT) :: hdferr ! Error code:
+ INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lcpl_id ! Link creation property list identifier.
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier.
- INTEGER(HID_T) :: lcpl_id_default
+ INTEGER(HID_T) :: lcpl_id_default
INTEGER(HID_T) :: lapl_id_default
-
+
INTEGER(SIZE_T) :: file_namelen
- INTEGER(SIZE_T) :: obj_namelen
+ INTEGER(SIZE_T) :: obj_namelen
INTEGER(SIZE_T) :: link_namelen
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
INTEGER FUNCTION h5lcreate_external_c(file_name, file_namelen, obj_name, obj_namelen, &
- link_loc_id, link_name, link_namelen, lcpl_id_default, lapl_id_default)
+ link_loc_id, link_name, link_namelen, lcpl_id_default, lapl_id_default)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
@@ -387,15 +387,15 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: obj_name
INTEGER(HID_T), INTENT(IN) :: link_loc_id
CHARACTER(LEN=*), INTENT(IN) :: link_name
- INTEGER(SIZE_T) :: file_namelen
- INTEGER(SIZE_T) :: obj_namelen
+ INTEGER(SIZE_T) :: file_namelen
+ INTEGER(SIZE_T) :: obj_namelen
INTEGER(SIZE_T) :: link_namelen
INTEGER(HID_T) :: lcpl_id_default
INTEGER(HID_T) :: lapl_id_default
END FUNCTION h5lcreate_external_c
END INTERFACE
- file_namelen = LEN(file_name)
- obj_namelen = LEN(obj_name)
+ file_namelen = LEN(file_name)
+ obj_namelen = LEN(obj_name)
link_namelen = LEN(link_name)
lcpl_id_default = H5P_DEFAULT_F
@@ -409,10 +409,10 @@ CONTAINS
END SUBROUTINE h5lcreate_external_f
!----------------------------------------------------------------------
-! Name: h5ldelete_by_idx_f
+! Name: h5ldelete_by_idx_f
!
! Purpose: Removes the nth link in a group.
-! Inputs:
+! Inputs:
! loc_id - File or group identifier specifying location of subject group
! group_name - Name of subject group
! index_field - Type of index; Possible values are:
@@ -421,7 +421,7 @@ CONTAINS
! H5_INDEX_NAME_F - Index on names
! H5_INDEX_CRT_ORDER_F - Index on creation order
! H5_INDEX_N_F - Number of indices defined
-!
+!
! order - Order within field or index; Possible values are:
!
! H5_ITER_UNKNOWN_F - Unknown order
@@ -432,22 +432,22 @@ CONTAINS
!
! n - Link for which to retrieve information
! Outputs:
-! hdferr: - error code
+! hdferr: - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lapl_id - Link access property list
!
! Programmer: M.S. Breitenfeld
! February 29, 2008
!
-! Modifications: N/A
+! Modifications: N/A
!
!----------------------------------------------------------------------
SUBROUTINE h5ldelete_by_idx_f(loc_id, group_name, index_field, order, n, hdferr, lapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifer for object to which attribute is attached
- CHARACTER(LEN=*), INTENT(IN) :: group_name ! Name of object, relative to location,
+ CHARACTER(LEN=*), INTENT(IN) :: group_name ! Name of object, relative to location,
! from which attribute is to be removed
INTEGER, INTENT(IN) :: index_field ! Type of index; Possible values are:
! H5_INDEX_UNKNOWN_F - Unknown index type
@@ -460,14 +460,14 @@ CONTAINS
! H5_ITER_DEC_F - Decreasing order
! H5_ITER_NATIVE_F - No particular order, whatever is fastest
! H5_ITER_N_F - Number of iteration orders
- INTEGER(HSIZE_T), INTENT(IN) :: n ! Offset within index
+ INTEGER(HSIZE_T), INTENT(IN) :: n ! Offset within index
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: group_namelen
-
+
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
@@ -481,7 +481,7 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: group_name
INTEGER, INTENT(IN) :: index_field
INTEGER, INTENT(IN) :: order
- INTEGER(HSIZE_T), INTENT(IN) :: n
+ INTEGER(HSIZE_T), INTENT(IN) :: n
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: group_namelen
END FUNCTION h5ldelete_by_idx_c
@@ -489,31 +489,31 @@ CONTAINS
lapl_id_default = H5P_DEFAULT_F
IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
-
+
group_namelen = LEN(group_name)
hdferr = h5ldelete_by_idx_c(loc_id, group_name, group_namelen, index_field, order, n, lapl_id_default)
-
+
END SUBROUTINE h5ldelete_by_idx_f
!----------------------------------------------------------------------
-! Name: H5Lexists_f
+! Name: H5Lexists_f
!
! Purpose: Check if a link with a particular name exists in a group.
-!
+!
! Inputs:
! loc_id - Identifier of the file or group to query.
! name - Link name to check
!
! Outputs:
! link_exists - link exists status (.TRUE.,.FALSE.)
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list identifier.
+! lapl_id - Link access property list identifier.
!
! Programmer: M. S. Breitenfeld
-! February 29, 2008
+! February 29, 2008
!
! Modifications: N/A
!
@@ -525,7 +525,7 @@ CONTAINS
LOGICAL, INTENT(OUT) :: link_exists ! .TRUE. if exists, .FALSE. otherwise
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id
! Link access property list identifier.
INTEGER :: link_exists_c
INTEGER(HID_T) :: lapl_id_default
@@ -545,7 +545,7 @@ CONTAINS
INTEGER(SIZE_T), INTENT(IN) :: namelen
INTEGER, INTENT(OUT) :: link_exists_c
INTEGER(HID_T) :: lapl_id_default
-
+
END FUNCTION h5lexists_c
END INTERFACE
@@ -557,7 +557,7 @@ CONTAINS
hdferr = h5lexists_c(loc_id, name, namelen, lapl_id_default, link_exists_c)
link_exists = .FALSE.
- IF(link_exists_c.GT.0) link_exists = .TRUE.
+ IF(link_exists_c.GT.0) link_exists = .TRUE.
END SUBROUTINE h5lexists_f
@@ -566,13 +566,13 @@ CONTAINS
!
! Purpose: Returns information about a link.
!
-! Inputs:
+! Inputs:
! link_loc_id - File or group identifier.
-! link_name - Name of the link for which information is being sought
+! link_name - Name of the link for which information is being sought
!
! Outputs: NOTE: In C these are contained in the structure H5L_info_t
!
-! cset - indicates the character set used for link’s name.
+! cset - indicates the character set used for link’s name.
! corder - specifies the link’s creation order position.
!f_corder_valid - indicates whether the value in corder is valid.
! link_type - specifies the link class:
@@ -581,20 +581,20 @@ CONTAINS
! H5L_TYPE_EXTERNAL_F - External link
! H5L_TYPE_ERROR_F - Error
! address - If the link is a hard link, address specifies the file address that the link points to
-! val_size - If the link is a symbolic link, val_size will be the length of the link value, e.g.,
-! the length of the name of the pointed-to object with a null terminator.
-! hdferr - error code
+! val_size - If the link is a symbolic link, val_size will be the length of the link value, e.g.,
+! the length of the name of the pointed-to object with a null terminator.
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list
+! lapl_id - Link access property list
!
! Programmer: M. S. Breitenfeld
-! February 29, 2008
+! February 29, 2008
!
-! Modifications:
+! Modifications:
! Changed the link_type names to match those in C (bug 1720) from,
-! H5L_LINK_HARD_F, H5L_LINK_SOFT_F,H5L_LINK_EXTERNAL_F,H5L_LINK_ERROR_F
+! H5L_LINK_HARD_F, H5L_LINK_SOFT_F,H5L_LINK_EXTERNAL_F,H5L_LINK_ERROR_F
! to
! H5L_TYPE_HARD_F, H5L_TYPE_SOFT_F,H5L_TYPE_EXTERNAL_F,H5L_TYPE_ERROR_F
! MSB January 8, 2010.
@@ -608,9 +608,9 @@ CONTAINS
INTEGER(HID_T), INTENT(IN) :: link_loc_id ! File or group identifier.
CHARACTER(LEN=*), INTENT(IN) :: link_name ! Name of the link for which information is being sought
-
+
! Outputs: NOTE: In C these are contained in the structure H5L_info_t
- INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the link’s name.
+ INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the link’s name.
INTEGER, INTENT(OUT) :: corder ! Specifies the link’s creation order position.
LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the value in corder is valid.
INTEGER, INTENT(OUT) :: link_type ! Specifies the link class:
@@ -619,8 +619,8 @@ CONTAINS
! H5L_TYPE_EXTERNAL_F - External link
! H5L_TYPE_ERROR _F - Error
INTEGER(HADDR_T), INTENT(OUT) :: address ! If the link is a hard link, address specifies the file address that the link points to
- INTEGER(SIZE_T), INTENT(OUT) :: val_size ! If the link is a symbolic link, val_size will be the length of the link value, e.g.,
- ! the length of the name of the pointed-to object with a null terminator.
+ INTEGER(SIZE_T), INTENT(OUT) :: val_size ! If the link is a symbolic link, val_size will be the length of the link value, e.g.,
+ ! the length of the name of the pointed-to object with a null terminator.
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
@@ -642,7 +642,7 @@ CONTAINS
!DEC$ATTRIBUTES reference :: link_name
INTEGER(HID_T), INTENT(IN) :: link_loc_id
CHARACTER(LEN=*), INTENT(IN) :: link_name
- INTEGER, INTENT(OUT) :: cset
+ INTEGER, INTENT(OUT) :: cset
INTEGER, INTENT(OUT) :: corder
INTEGER, INTENT(OUT) :: link_type
INTEGER(HADDR_T), INTENT(OUT) :: address
@@ -662,7 +662,7 @@ CONTAINS
cset, corder, corder_valid, link_type, &
address, val_size, &
lapl_id_default)
-
+
f_corder_valid =.FALSE.
IF(corder_valid .EQ. 1) f_corder_valid =.TRUE.
@@ -672,7 +672,7 @@ CONTAINS
! Name: h5lget_info_by_idx_f
!
! Purpose: Retrieves metadata for a link in a group, according to the order within a field or index.
-!
+!
! Inputs:
! loc_id - File or group identifier specifying location of subject group
! group_name - Name of subject group
@@ -682,23 +682,23 @@ CONTAINS
!
! Outputs: NOTE: In C these are defined as a structure: H5L_info_t
! corder_valid - indicates whether the creation order data is valid for this attribute
-! corder - is a positive integer containing the creation order of the attribute
-! cset - indicates the character set used for the attribute’s name
+! corder - is a positive integer containing the creation order of the attribute
+! cset - indicates the character set used for the attribute’s name
! address - If the link is a hard link, address specifies the file address that the link points to
-! val_size - If the link is a symbolic link, val_size will be the length of the link value, e.g.,
-! the length of the name of the pointed-to object with a null terminator.
-! hdferr - error code
+! val_size - If the link is a symbolic link, val_size will be the length of the link value, e.g.,
+! the length of the name of the pointed-to object with a null terminator.
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! lapl_id - Link access property list
+! lapl_id - Link access property list
!
! Programmer: M.S. Breitenfeld
-! February 29, 2008
+! February 29, 2008
!
-! Modifications:
+! Modifications:
! Changed the link_type names to match those in C (bug 1720) from,
-! H5L_LINK_HARD_F, H5L_LINK_SOFT_F,H5L_LINK_EXTERNAL_F,H5L_LINK_ERROR_F
+! H5L_LINK_HARD_F, H5L_LINK_SOFT_F,H5L_LINK_EXTERNAL_F,H5L_LINK_ERROR_F
! to
! H5L_TYPE_HARD_F, H5L_TYPE_SOFT_F,H5L_TYPE_EXTERNAL_F,H5L_TYPE_ERROR_F
! MSB January 8, 2010.
@@ -707,7 +707,7 @@ CONTAINS
SUBROUTINE h5lget_info_by_idx_f(loc_id, group_name, index_field, order, n, &
link_type, f_corder_valid, corder, cset, address, val_size, hdferr, lapl_id)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier specifying location of subject group
+ INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier specifying location of subject group
CHARACTER(LEN=*), INTENT(IN) :: group_name ! Name of subject group
INTEGER, INTENT(IN) :: index_field ! Index or field which determines the order
! H5_INDEX_UNKNOWN_F - Unknown index type
@@ -725,12 +725,12 @@ CONTAINS
! H5L_TYPE_SOFT_F - Soft link
! H5L_TYPE_EXTERNAL_F - External link
! H5L_TYPE_ERROR _F - Error
- LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
+ LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the attribute’s name
INTEGER(HADDR_T), INTENT(OUT) :: address ! If the link is a hard link, address specifies the file address that the link points to
- INTEGER(SIZE_T), INTENT(OUT) :: val_size ! If the link is a symbolic link, val_size will be the length of the link value, e.g.,
- ! the length of the name of the pointed-to object with a null terminator.
+ INTEGER(SIZE_T), INTENT(OUT) :: val_size ! If the link is a symbolic link, val_size will be the length of the link value, e.g.,
+ ! the length of the name of the pointed-to object with a null terminator.
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
@@ -755,7 +755,7 @@ CONTAINS
INTEGER, INTENT(IN) :: order
INTEGER(HSIZE_T), INTENT(IN) :: n
INTEGER, INTENT(OUT) :: link_type
- INTEGER :: corder_valid
+ INTEGER :: corder_valid
INTEGER, INTENT(OUT) :: corder
INTEGER, INTENT(OUT) :: cset
INTEGER(HADDR_T), INTENT(OUT) :: address
@@ -778,24 +778,24 @@ CONTAINS
END SUBROUTINE h5lget_info_by_idx_f
!----------------------------------------------------------------------
-! Name: h5lis_registered_f
+! Name: h5lis_registered_f
!
! Purpose: Determines whether a class of user-defined links is registered.
-!
+!
! Inputs:
! link_cls_id - User-defined link class identifier
!
! Outputs:
! registered - .TRUE. - if the link class has been registered
! .FALSE. - if it is unregistered
-! hdferr - Error code
+! hdferr - Error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! None
+! None
!
! Programmer: M.S. Breitenfeld
-! February 29, 2008
+! February 29, 2008
!
! Modifications: N/A
!
@@ -827,30 +827,30 @@ CONTAINS
ELSE IF(hdferr.EQ.0)THEN
registered = .FALSE.
ENDIF
-
+
END SUBROUTINE h5lis_registered_f
!----------------------------------------------------------------------
! Name: h5lmove_f
!
! Purpose: Renames a link within an HDF5 file.
-!
+!
! Inputs:
! src_loc_id - Original file or group identifier.
! src_name - Original link name.
! dest_loc_id - Destination file or group identifier.
! dest_name - NEW link name.
!
-! Outputs:
-! hdferr - Error code
+! Outputs:
+! hdferr - Error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lcpl_id - Link creation property list identifier to be associated WITH the NEW link.
! lapl_id - Link access property list identifier to be associated WITH the NEW link.
!
! Programmer: M.S. Breitenfeld
-! March 3, 2008
+! March 3, 2008
!
! Modifications: N/A
!
@@ -863,37 +863,37 @@ CONTAINS
CHARACTER(LEN=*), INTENT(IN) :: dest_name ! NEW link name.
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lcpl_id ! Link creation property list identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lcpl_id ! Link creation property list identifier
! to be associated WITH the NEW link.
- INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
+ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list identifier
! to be associated WITH the NEW link.
INTEGER(SIZE_T) :: src_namelen
INTEGER(SIZE_T) :: dest_namelen
- INTEGER(HID_T) :: lcpl_id_default
- INTEGER(HID_T) :: lapl_id_default
-
+ INTEGER(HID_T) :: lcpl_id_default
+ INTEGER(HID_T) :: lapl_id_default
+
!
! MS FORTRAN needs explicit interface for C functions called here.
!
INTERFACE
INTEGER FUNCTION h5lmove_c(src_loc_id, src_name, src_namelen, dest_loc_id, &
- dest_name, dest_namelen, lcpl_id_default, lapl_id_default)
+ dest_name, dest_namelen, lcpl_id_default, lapl_id_default)
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5LMOVE_C'::h5lmove_c
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: src_name, dest_name
- INTEGER(HID_T), INTENT(IN) :: src_loc_id
+ INTEGER(HID_T), INTENT(IN) :: src_loc_id
CHARACTER(LEN=*), INTENT(IN) :: src_name
INTEGER(SIZE_T) :: src_namelen
INTEGER(HID_T), INTENT(IN) :: dest_loc_id
CHARACTER(LEN=*), INTENT(IN) :: dest_name
INTEGER(SIZE_T) :: dest_namelen
-
- INTEGER(HID_T) :: lcpl_id_default
- INTEGER(HID_T) :: lapl_id_default
+
+ INTEGER(HID_T) :: lcpl_id_default
+ INTEGER(HID_T) :: lapl_id_default
END FUNCTION h5lmove_c
END INTERFACE
@@ -916,16 +916,16 @@ CONTAINS
!
! Purpose: Retrieves name of the nth link in a group, according to the order within a specified field or index.
!
-! Inputs:
+! Inputs:
! loc_id - File or group identifier specifying location of subject group
! group_name - Name of subject group
! index_field - Index or field which determines the order
! order - Order within field or index
! n - Link for which to retrieve information
!
-! Outputs:
+! Outputs:
! name - Buffer in which link value is returned
-! hdferr - error code
+! hdferr - error code
! Success: 0
! Failure: -1
!
@@ -934,7 +934,7 @@ CONTAINS
! size - Maximum number of characters of link value to be returned.
!
! Programmer: M. S. Breitenfeld
-! March 10, 2008
+! March 10, 2008
!
! Modifications: N/A
!
@@ -942,7 +942,7 @@ CONTAINS
SUBROUTINE h5lget_name_by_idx_f(loc_id, group_name, index_field, order, n, &
name, hdferr, size, lapl_id)
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier specifying location of subject group
+ INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier specifying location of subject group
CHARACTER(LEN=*), INTENT(IN) :: group_name ! Name of subject group
INTEGER, INTENT(IN) :: index_field ! Index or field which determines the order
! H5_INDEX_UNKNOWN_F - Unknown index type
@@ -958,12 +958,12 @@ CONTAINS
CHARACTER(LEN=*), INTENT(OUT) :: name ! Buffer in which link value is returned
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
-
+
INTEGER(SIZE_T) :: group_namelen
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T), OPTIONAL, INTENT(OUT) :: size ! Indicates the size, in the number of characters, of the link
- INTEGER(SIZE_T) :: size_default
+ INTEGER(SIZE_T) :: size_default
! MS FORTRAN needs explicit interface for C functions called here.
@@ -976,7 +976,7 @@ CONTAINS
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5LGET_NAME_BY_IDX_C'::h5lget_name_by_idx_c
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: group_name, name
- INTEGER(HID_T), INTENT(IN) :: loc_id
+ INTEGER(HID_T), INTENT(IN) :: loc_id
CHARACTER(LEN=*), INTENT(IN) :: group_name
INTEGER(SIZE_T) :: group_namelen
INTEGER, INTENT(IN) :: index_field
@@ -1013,7 +1013,7 @@ CONTAINS
!!$! an index. For symbolic links, this is the path to which the
!!$! link points, including the null terminator. For user-defined
!!$! links, it is the link buffer.
-!!$! Inputs:
+!!$! Inputs:
!!$! loc_id - File or group identifier specifying location of subject group
!!$! group_name - Name of subject group
!!$! index_field - Index or field which determines the order
@@ -1023,17 +1023,17 @@ CONTAINS
!!$!
!!$! Outputs: NOTE: In C these are defined as a structure: H5L_info_t
!!$! corder_valid - indicates whether the creation order data is valid for this attribute
-!!$! corder - is a positive integer containing the creation order of the attribute
-!!$! cset - indicates the character set used for the attribute’s name
-!!$! data_size - indicates the size, in the number of characters, of the attribute
-!!$! hdferr - error code
+!!$! corder - is a positive integer containing the creation order of the attribute
+!!$! cset - indicates the character set used for the attribute’s name
+!!$! data_size - indicates the size, in the number of characters, of the attribute
+!!$! hdferr - error code
!!$! Success: 0
-!!$! Failure: -1
+!!$! Failure: -1
!!$! Optional parameters:
!!$! lapl_id - List access property list identifier.
!!$!
!!$! Programmer: M. S. Breitenfeld
-!!$! March 3, 2008
+!!$! March 3, 2008
!!$!
!!$! Modifications: N/A
!!$!
@@ -1041,7 +1041,7 @@ CONTAINS
!!$ SUBROUTINE h5lget_val_by_idx_f(loc_id, group_name, index_field, order, n, &
!!$ f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
!!$ IMPLICIT NONE
-!!$ INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier specifying location of subject group
+!!$ INTEGER(HID_T), INTENT(IN) :: loc_id ! File or group identifier specifying location of subject group
!!$ CHARACTER(LEN=*), INTENT(IN) :: group_name ! Name of subject group
!!$ INTEGER, INTENT(IN) :: index_field ! Index or field which determines the order
!!$ ! H5_INDEX_UNKNOWN_F - Unknown index type
@@ -1054,7 +1054,7 @@ CONTAINS
!!$ ! H5_ITER_DEC_F - Decreasing order
!!$ ! H5_ITER_NATIVE_F - No particular order, whatever is fastest
!!$ INTEGER(HSIZE_T), INTENT(IN) :: n ! Attribute’s position in index
-!!$ LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
+!!$ LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the creation order data is valid for this attribute
!!$ INTEGER, INTENT(OUT) :: corder ! Is a positive integer containing the creation order of the attribute
!!$ INTEGER, INTENT(OUT) :: cset ! Indicates the character set used for the attribute’s name
!!$ INTEGER(HSIZE_T), INTENT(OUT) :: data_size ! Indicates the size, in the number of characters, of the attribute
@@ -1074,7 +1074,7 @@ CONTAINS
!!$ !DEC$IF DEFINED(HDF5F90_WINDOWS)
!!$ !DEC$ATTRIBUTES C,reference,decorate,alias:'H5LGET_VAL_BY_IDX_C'::h5lget_val_by_idx_c
!!$ !DEC$ENDIF
-!!$ INTEGER(HID_T), INTENT(IN) :: loc_id
+!!$ INTEGER(HID_T), INTENT(IN) :: loc_id
!!$ CHARACTER(LEN=*), INTENT(IN) :: group_name
!!$ INTEGER(SIZE_T) :: group_namelen
!!$ INTEGER, INTENT(IN) :: index_field
@@ -1098,7 +1098,7 @@ CONTAINS
!!$
!!$ f_corder_valid =.FALSE.
!!$ IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
-!!$
+!!$
!!$ END SUBROUTINE h5lget_val_by_idx_f
@@ -1108,21 +1108,21 @@ CONTAINS
!
! Purpose: Returns the value of a symbolic link.
!
-! Inputs:
+! Inputs:
! link_loc_id - File or group identifier.
! link_name - Link whose value is to be returned.
! size - Maximum number of characters of link value to be returned.
!
-! Outputs:
+! Outputs:
! linkval_buff - The buffer to hold the returned link value.
-! hdferr - error code
+! hdferr - error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
! lapl_id - List access property list identifier.
!
! Programmer: M. S. Breitenfeld
-! March 3, 2008
+! March 3, 2008
!
! Modifications: N/A
!
@@ -1134,18 +1134,18 @@ CONTAINS
!!$ INTEGER(HID_T), INTENT(IN) :: link_loc_id ! File or group identifier.
!!$ CHARACTER(LEN=*), INTENT(IN) :: link_name ! Link whose value is to be returned.
!!$ INTEGER(SIZE_T), INTENT(IN) :: size ! Maximum number of characters of link value to be returned.
-!!$
+!!$
!!$ CHARACTER(LEN=size), INTENT(OUT) :: linkval_buff ! The buffer to hold the returned link value.
!!$ INTEGER, INTENT(OUT) :: hdferr ! Error code:
!!$ ! 0 on success and -1 on failure
!!$ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
-!!$
+!!$
!!$ INTEGER :: link_namelen
!!$ INTEGER(HID_T) :: lapl_id_default
!!$ INTEGER :: corder_valid
!!$
-!!$ INTEGER :: link_namelen
-!!$ INTEGER(HID_T) :: lapl_id_default
+!!$ INTEGER :: link_namelen
+!!$ INTEGER(HID_T) :: lapl_id_default
!!$
!!$! MS FORTRAN needs explicit interface for C functions called here.
!!$!
@@ -1158,9 +1158,9 @@ CONTAINS
!!$ !DEC$ENDIF
!!$ INTEGER(HID_T), INTENT(IN) :: link_loc_id ! File or group identifier.
!!$ CHARACTER(LEN=*), INTENT(IN) :: link_name ! Link whose value is to be returned.
-!!$ INTEGER :: link_namelen
+!!$ INTEGER :: link_namelen
!!$ INTEGER(SIZE_T), INTENT(IN) :: size ! Maximum number of characters of link value to be returned.
-!!$
+!!$
!!$ CHARACTER(LEN=size), INTENT(OUT) :: linkval_buff ! The buffer to hold the returned link value.
!!$
!!$ INTEGER :: link_namelen
@@ -1182,30 +1182,30 @@ CONTAINS
!----------------------------------------------------------------------
-! Name: H5Lregistered_f
+! Name: H5Lregistered_f
!
! Purpose: Registers user-defined link class or changes behavior of existing class.
-!
+!
! Inputs: NOTE: In C the following represents struct H5L_class_t:
-! version - Version number of this struct
-! class_id - Link class identifier
-! comment - Comment for debugging
-! create_func - Callback during link creation
-! move_func - Callback after moving link
-! copy_func - Callback after copying link
-! trav_func - The main traversal function
-! del_func - Callback for link deletion
-! query_func - Callback for queries
+! version - Version number of this struct
+! class_id - Link class identifier
+! comment - Comment for debugging
+! create_func - Callback during link creation
+! move_func - Callback after moving link
+! copy_func - Callback after copying link
+! trav_func - The main traversal function
+! del_func - Callback for link deletion
+! query_func - Callback for queries
!
! Outputs:
-! hdferr - Error code
+! hdferr - Error code
! Success: 0
-! Failure: -1
+! Failure: -1
! Optional parameters:
-! None
+! None
!
! Programmer: M.S. Breitenfeld
-! February 29, 2008
+! February 29, 2008
!
! Modifications: N/A
!
@@ -1213,25 +1213,25 @@ CONTAINS
!!$ SUBROUTINE H5Lregistered_f(version, class_id, comment, create_func, &
!!$ move_func, copy_func, trav_func, del_func, query_func, hdferr)
!!$ IMPLICIT NONE
-!!$ INTEGER, INTENT(IN) :: version ! Version number of this struct
-!!$ INTEGER, INTENT(IN) :: class_id ! Link class identifier
-!!$ CHARACTER(LEN=*), INTENT(IN) :: comment ! Comment for debugging
-!!$ CHARACTER(LEN=*), INTENT(IN) :: create_func ! Callback during link creation
-!!$ CHARACTER(LEN=*), INTENT(IN) :: move_func ! Callback after moving link
-!!$ CHARACTER(LEN=*), INTENT(IN) :: copy_func ! Callback after copying link
-!!$ CHARACTER(LEN=*), INTENT(IN) :: trav_func ! The main traversal function
-!!$ CHARACTER(LEN=*), INTENT(IN) :: del_func ! Callback for link deletion
+!!$ INTEGER, INTENT(IN) :: version ! Version number of this struct
+!!$ INTEGER, INTENT(IN) :: class_id ! Link class identifier
+!!$ CHARACTER(LEN=*), INTENT(IN) :: comment ! Comment for debugging
+!!$ CHARACTER(LEN=*), INTENT(IN) :: create_func ! Callback during link creation
+!!$ CHARACTER(LEN=*), INTENT(IN) :: move_func ! Callback after moving link
+!!$ CHARACTER(LEN=*), INTENT(IN) :: copy_func ! Callback after copying link
+!!$ CHARACTER(LEN=*), INTENT(IN) :: trav_func ! The main traversal function
+!!$ CHARACTER(LEN=*), INTENT(IN) :: del_func ! Callback for link deletion
!!$ CHARACTER(LEN=*), INTENT(IN) :: query_func ! Callback for queries
!!$ INTEGER, INTENT(OUT) :: hdferr ! Error code:
!!$ ! 0 on success and -1 on failure
-!!$ INTEGER :: comment_len
+!!$ INTEGER :: comment_len
!!$ INTEGER :: create_func_len
-!!$ INTEGER :: move_func_len
-!!$ INTEGER :: copy_func_len
-!!$ INTEGER :: trav_func_len
+!!$ INTEGER :: move_func_len
+!!$ INTEGER :: copy_func_len
+!!$ INTEGER :: trav_func_len
!!$ INTEGER :: del_func_len
!!$ INTEGER :: query_func_len
-!!$
+!!$
!!$!
!!$! MS FORTRAN needs explicit interface for C functions called here.
!!$!
@@ -1247,33 +1247,33 @@ CONTAINS
!!$ !DEC$IF DEFINED(HDF5F90_WINDOWS)
!!$ !DEC$ATTRIBUTES C,reference,decorate,alias:'H5LREGISTERED_C'::H5Lregistered_c
!!$ !DEC$ENDIF
-!!$ INTEGER, INTENT(IN) :: version ! Version number of this struct
-!!$ INTEGER, INTENT(IN) :: class_id ! Link class identifier
-!!$ CHARACTER(LEN=*), INTENT(IN) :: comment ! Comment for debugging
-!!$ CHARACTER(LEN=*), INTENT(IN) :: create_func ! Callback during link creation
-!!$ CHARACTER(LEN=*), INTENT(IN) :: move_func ! Callback after moving link
-!!$ CHARACTER(LEN=*), INTENT(IN) :: copy_func ! Callback after copying link
-!!$ CHARACTER(LEN=*), INTENT(IN) :: trav_func ! The main traversal function
-!!$ CHARACTER(LEN=*), INTENT(IN) :: del_func ! Callback for link deletion
+!!$ INTEGER, INTENT(IN) :: version ! Version number of this struct
+!!$ INTEGER, INTENT(IN) :: class_id ! Link class identifier
+!!$ CHARACTER(LEN=*), INTENT(IN) :: comment ! Comment for debugging
+!!$ CHARACTER(LEN=*), INTENT(IN) :: create_func ! Callback during link creation
+!!$ CHARACTER(LEN=*), INTENT(IN) :: move_func ! Callback after moving link
+!!$ CHARACTER(LEN=*), INTENT(IN) :: copy_func ! Callback after copying link
+!!$ CHARACTER(LEN=*), INTENT(IN) :: trav_func ! The main traversal function
+!!$ CHARACTER(LEN=*), INTENT(IN) :: del_func ! Callback for link deletion
!!$ CHARACTER(LEN=*), INTENT(IN) :: query_func ! Callback for queries
!!$ INTEGER, INTENT(OUT) :: hdferr ! Error code:
!!$ ! 0 on success and -1 on failure
-!!$ INTEGER :: comment_len
+!!$ INTEGER :: comment_len
!!$ INTEGER :: create_func_len
-!!$ INTEGER :: move_func_len
-!!$ INTEGER :: copy_func_len
-!!$ INTEGER :: trav_func_len
+!!$ INTEGER :: move_func_len
+!!$ INTEGER :: copy_func_len
+!!$ INTEGER :: trav_func_len
!!$ INTEGER :: del_func_len
!!$ INTEGER :: query_func_len
-!!$
+!!$
!!$ END FUNCTION H5Lregistered_c
!!$ END INTERFACE
!!$
!!$ comment_len = LEN(comment)
!!$ create_func_len = LEN(create_func)
!!$ move_func_len = LEN(move_func)
-!!$ copy_func_len = LEN(copy_func)
-!!$ trav_func_len = LEN(trav_func)
+!!$ copy_func_len = LEN(copy_func)
+!!$ trav_func_len = LEN(trav_func)
!!$ del_func_len = LEN(del_func)
!!$ query_func_len = LEN(query_func)
!!$
@@ -1284,7 +1284,7 @@ CONTAINS
!!$ trav_func, trav_func_len, &
!!$ del_func, del_func_len, &
!!$ query_func, query_func_len)
-!!$
+!!$
!!$ END SUBROUTINE H5Lregistered_f
END MODULE H5L