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.f90814
1 files changed, 412 insertions, 402 deletions
diff --git a/fortran/src/H5Lff.f90 b/fortran/src/H5Lff.f90
index 8d30c20..8043d74 100644
--- a/fortran/src/H5Lff.f90
+++ b/fortran/src/H5Lff.f90
@@ -1,3 +1,14 @@
+!****h* ROBODoc/H5L
+!
+! NAME
+! MODULE H5L
+!
+! PURPOSE
+! This file contains Fortran interfaces for H5L functions. It includes
+! all the functions that are independent on whether the Fortran 2003 functions
+! are enabled or disabled.
+!
+! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! Copyright by the Board of Trustees of the University of Illinois. *
@@ -13,43 +24,48 @@
! access to either file, you may request a copy from help@hdfgroup.org. *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
+! NOTES
+! *** IMPORTANT ***
+! If you add a new H5L 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.
!
-! This file contains Fortran90 interfaces for H5L functions.
-!
+!*****
+
MODULE H5L
USE H5GLOBAL
CONTAINS
-!----------------------------------------------------------------------
-! Name: h5lcopy_f
!
-! Purpose: Copies a link from one location to another.
+!****s* H5L/h5lcopy_f
+!
+! NAME
+! h5lcopy_f
!
-! Inputs:
-! src_loc_id - Location identifier of the source link
-! src_name - Name of the link to be copied
-! dest_loc_id - Location identifier specifying the destination of the copy
-! 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
+! PURPOSE
+! Copies a link from one location to another.
!
-! Outputs:
-! hdferr - error code:
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lcpl_id - Link creation property list identifier
-! lapl_id - Link access property list identifier
+! INPUTS
+! src_loc_id - Location identifier of the source link
+! src_name - Name of the link to be copied
+! dest_loc_id - Location identifier specifying the destination of the copy
+! 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
!
-! Programmer: M.S. Breitenfeld
-! February 27, 2008
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! lcpl_id - Link creation property list identifier
+! lapl_id - Link access property list identifier
!
-! Modifications:
+! AUTHOR
+! M. Scot Breitenfeld
+! February 27, 2008
!
-! Comment:
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5lcopy_f(src_loc_id, src_name, dest_loc_id, dest_name, hdferr, &
lcpl_id, lapl_id)
IMPLICIT NONE
@@ -62,16 +78,13 @@ CONTAINS
! 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.
-!
INTERFACE
INTEGER FUNCTION h5lcopy_c(src_loc_id, src_name, src_namelen, dest_loc_id, dest_name, dest_namelen, &
lcpl_id_default, lapl_id_default)
@@ -106,29 +119,29 @@ CONTAINS
END SUBROUTINE h5lcopy_f
-!----------------------------------------------------------------------
-! Name: h5ldelete_f
!
-! Purpose: Removes a link from a group.
+!****s* H5L/h5ldelete_f
!
-! Inputs:
-! loc_id - Identifier of the file or group containing the object
-! name - Name of the link to delete
+! NAME
+! h5ldelete_f
!
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lapl_id - Link access property list identifier
+! PURPOSE
+! Removes a link from a group.
!
-! Programmer: M.S. Breitenfeld
-! January, 2008
+! INPUTS
+! loc_id - Identifier of the file or group containing the object
+! name - Name of the link to delete
!
-! Modifications:
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! lapl_id - Link access property list identifier
!
-! Comment:
-!----------------------------------------------------------------------
+! AUTHOR
+! M. Scot Breitenfeld
+! January, 2008
+!
+! SOURCE
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
@@ -136,12 +149,10 @@ CONTAINS
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.
-!
INTERFACE
INTEGER FUNCTION h5ldelete_c(loc_id, name, namelen, lapl_id_default)
USE H5GLOBAL
@@ -165,48 +176,46 @@ CONTAINS
END SUBROUTINE h5ldelete_f
-!----------------------------------------------------------------------
-! Name: H5Lcreate_soft_f
!
-! Purpose: Creates a soft link to an object.
+!****s* H5L/H5Lcreate_soft_f
!
-! Inputs:
-! 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.
+! NAME
+! H5Lcreate_soft_f
!
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lcpl_id - Link creation property list identifier.
-! lapl_id - Link access property list identifier.
+! PURPOSE
+! Creates a soft link to an object.
!
-! Programmer: M.S. Breitenfeld
-! February 20, 2008
+! INPUTS
+! 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.
!
-! Modifications:
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! lcpl_id - Link creation property list identifier.
+! lapl_id - Link access property list identifier.
!
-! Comment:
-!----------------------------------------------------------------------
+! AUTHOR
+! M. Scot Breitenfeld
+! February 20, 2008
+!
+! SOURCE
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.
+ 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:
- ! 0 on success and -1 on failure
+ CHARACTER(LEN=*), INTENT(IN) :: link_name ! The name of the new link.
+ 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) :: target_path_len
INTEGER(SIZE_T) :: link_name_len
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5lcreate_soft_c(target_path, target_path_len, &
link_loc_id, &
@@ -242,33 +251,33 @@ CONTAINS
END SUBROUTINE h5lcreate_soft_f
-!----------------------------------------------------------------------
-! Name: H5Lcreate_hard_f
!
-! Purpose: Creates a hard link to an object.
+!****s* H5L/H5Lcreate_hard_f
!
-! Inputs:
+! NAME
+! H5Lcreate_hard_f
!
-! obj_loc_id - The file or group identifier for the target object.
-! 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.
+! PURPOSE
+! Creates a hard link to an object.
!
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lcpl_id - Link creation property list identifier.
-! lapl_id - Link access property list identifier.
+! INPUTS
!
-! Programmer: M.S. Breitenfeld
-! February 27, 2008
+! obj_loc_id - The file or group identifier for the target object.
+! 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.
!
-! Modifications:
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! lcpl_id - Link creation property list identifier.
+! lapl_id - Link access property list identifier.
!
-! Comment:
-!----------------------------------------------------------------------
+! AUTHOR
+! M. Scot Breitenfeld
+! February 27, 2008
+!
+! SOURCE
SUBROUTINE h5lcreate_hard_f(obj_loc_id, obj_name, link_loc_id, link_name, hdferr, lcpl_id, lapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: obj_loc_id ! The file or group identifier for the target object.
@@ -281,15 +290,13 @@ CONTAINS
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) :: 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)
@@ -322,37 +329,36 @@ CONTAINS
END SUBROUTINE h5lcreate_hard_f
-!----------------------------------------------------------------------
-! Name: H5Lcreate_external_f
!
-! Purpose: Creates a soft link to an object in a different file.
+!****s* H5L/H5Lcreate_external_f
!
-! Inputs:
+! NAME
+! H5Lcreate_external_f
!
-! 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.
+! PURPOSE
+! Creates a soft link to an object in a different file.
!
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lcpl_id - Link creation property list identifier.
-! lapl_id - Link access property list identifier.
+! INPUTS
!
-! Programmer: M.S. Breitenfeld
-! February 27, 2008
+! 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.
!
-! Modifications:
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! lcpl_id - Link creation property list identifier.
+! lapl_id - Link access property list identifier.
!
-! Comment:
-!----------------------------------------------------------------------
+! AUTHOR
+! M. Scot Breitenfeld
+! February 27, 2008
+! SOURCE
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
+ 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.
@@ -364,7 +370,7 @@ CONTAINS
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
@@ -372,8 +378,6 @@ CONTAINS
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)
@@ -408,42 +412,40 @@ CONTAINS
END SUBROUTINE h5lcreate_external_f
-!----------------------------------------------------------------------
-! Name: h5ldelete_by_idx_f
-!
-! Purpose: Removes the nth link in a group.
-! 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:
-!
-! H5_INDEX_UNKNOWN_F = -1 - Unknown index type
-! 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
-! H5_ITER_INC_F - Increasing order
-! H5_ITER_DEC_F - Decreasing order
-! H5_ITER_NATIVE_F - No particular order, whatever is fastest
-! H5_ITER_N_F - Number of iteration orders
-!
-! n - Link for which to retrieve information
-! Outputs:
-! hdferr: - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lapl_id - Link access property list
!
-! Programmer: M.S. Breitenfeld
-! February 29, 2008
-!
-! Modifications: N/A
-!
-!----------------------------------------------------------------------
+!****s* H5L/h5ldelete_by_idx_f
+!
+! NAME
+! h5ldelete_by_idx_f
+!
+! PURPOSE
+! Removes the nth link in a group.
+! 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:
+! H5_INDEX_UNKNOWN_F = -1 - Unknown index type
+! 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
+! H5_ITER_INC_F - Increasing order
+! H5_ITER_DEC_F - Decreasing order
+! H5_ITER_NATIVE_F - No particular order, whatever is fastest
+! H5_ITER_N_F - Number of iteration orders
+!
+! n - Link for which to retrieve information
+! OUTPUTS
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! lapl_id - Link access property list
+!
+! AUTHOR
+! M. Scot Breitenfeld
+! February 29, 2008
+! SOURCE
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
@@ -464,12 +466,10 @@ CONTAINS
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
INTEGER FUNCTION h5ldelete_by_idx_c(loc_id, group_name, group_namelen, index_field, order, n, lapl_id_default)
USE H5GLOBAL
@@ -495,29 +495,30 @@ CONTAINS
END SUBROUTINE h5ldelete_by_idx_f
-!----------------------------------------------------------------------
-! Name: H5Lexists_f
!
-! Purpose: Check if a link with a particular name exists in a group.
+!****s* H5L/H5Lexists_f
+!
+! NAME
+! H5Lexists_f
!
-! Inputs:
-! loc_id - Identifier of the file or group to query.
-! name - Link name to check
+! PURPOSE
+! Check if a link with a particular name exists in a group.
!
-! Outputs:
-! link_exists - link exists status (.TRUE.,.FALSE.)
-! hdferr - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lapl_id - Link access property list identifier.
+! INPUTS
+! loc_id - Identifier of the file or group to query.
+! name - Link name to check
!
-! Programmer: M. S. Breitenfeld
-! February 29, 2008
+! OUTPUTS
+! link_exists - link exists status (.TRUE.,.FALSE.)
+! hdferr - Returns 0 if successful and -1 if fails
+! OPTIONAL PARAMETERS
+! lapl_id - Link access property list identifier.
!
-! Modifications: N/A
+! AUTHOR
+! M. Scot Breitenfeld
+! February 29, 2008
!
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5lexists_f(loc_id, name, link_exists, hdferr, lapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier of the file or group to query.
@@ -527,12 +528,11 @@ CONTAINS
! 0 on success and -1 on failure
INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id
! Link access property list identifier.
+!*****
INTEGER :: link_exists_c
INTEGER(HID_T) :: lapl_id_default
INTEGER(SIZE_T) :: namelen
-!
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+
INTERFACE
INTEGER FUNCTION h5lexists_c(loc_id, name, namelen, lapl_id_default, link_exists_c)
USE H5GLOBAL
@@ -561,46 +561,50 @@ CONTAINS
END SUBROUTINE h5lexists_f
-!----------------------------------------------------------------------
-! Name: h5lget_info_f
-!
-! Purpose: Returns information about a link.
-!
-! Inputs:
-! link_loc_id - File or group identifier.
-! 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.
-! 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:
-! H5L_TYPE_HARD_F - Hard link
-! H5L_TYPE_SOFT_F - Soft link
-! 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
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lapl_id - Link access property list
-!
-! Programmer: M. S. Breitenfeld
-! February 29, 2008
-!
-! Modifications:
+!
+!****s* H5L/h5lget_info_f
+!
+! NAME
+! h5lget_info_f
+!
+! PURPOSE
+! Returns information about a link.
+!
+! INPUTS
+! link_loc_id - File or group identifier.
+! 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.
+! corder - specifies the link’s creation order position.
+! corder_valid - indicates whether the value in corder is valid.
+! link_type - specifies the link class:
+! H5L_TYPE_HARD_F - Hard link
+! H5L_TYPE_SOFT_F - Soft link
+! 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 - Returns 0 if successful and -1 if fails
+!
+! OPTIONAL PARAMETERS
+! lapl_id - Link access property list
+!
+! AUTHOR
+! M. Scot Breitenfeld
+! February 29, 2008
+!
+! HISTORY
! 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
! to
! H5L_TYPE_HARD_F, H5L_TYPE_SOFT_F,H5L_TYPE_EXTERNAL_F,H5L_TYPE_ERROR_F
! MSB January 8, 2010.
!
-!----------------------------------------------------------------------
-
+! SOURCE
SUBROUTINE h5lget_info_f(link_loc_id, link_name, &
cset, corder, f_corder_valid, link_type, address, val_size, &
hdferr, lapl_id)
@@ -609,7 +613,7 @@ 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
+! 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) :: corder ! Specifies the link’s creation order position.
LOGICAL, INTENT(OUT) :: f_corder_valid ! Indicates whether the value in corder is valid.
@@ -618,19 +622,17 @@ CONTAINS
! H5L_TYPE_SOFT_F - Soft link
! 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(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, 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(SIZE_T) :: link_namelen
INTEGER(HID_T) :: lapl_id_default
INTEGER :: corder_valid
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5lget_info_c(link_loc_id, link_name, link_namelen, &
cset, corder, corder_valid, link_type, address, val_size, &
@@ -668,46 +670,51 @@ CONTAINS
END SUBROUTINE h5lget_info_f
-!----------------------------------------------------------------------
-! 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
-! index_field - Index or field which determines the order
-! order - Order within field or index
-! n - Link for which to retrieve information
-!
-! 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
-! 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
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lapl_id - Link access property list
-!
-! Programmer: M.S. Breitenfeld
-! February 29, 2008
-!
-! Modifications:
+!
+!****s* H5L/h5lget_info_by_idx_f
+!
+! 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
+! index_field - Index or field which determines the order
+! order - Order within field or index
+! n - Link for which to retrieve information
+!
+! 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
+! 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 - Returns 0 if successful and -1 if fails
+!
+! OPTIONAL PARAMETERS
+! lapl_id - Link access property list
+!
+! AUTHOR
+! M. Scot Breitenfeld
+! February 29, 2008
+!
+! HISTORY
! 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
! to
! H5L_TYPE_HARD_F, H5L_TYPE_SOFT_F,H5L_TYPE_EXTERNAL_F,H5L_TYPE_ERROR_F
-! MSB January 8, 2010.
+! MSB January 8, 2010.
!
-!----------------------------------------------------------------------
+! SOURCE
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,15 +732,16 @@ 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
- 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
+ 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
+!*****
INTEGER :: corder_valid
INTEGER(SIZE_T) :: group_namelen
INTEGER(HID_T) :: lapl_id_default
@@ -755,7 +763,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
@@ -777,29 +785,30 @@ CONTAINS
END SUBROUTINE h5lget_info_by_idx_f
-!----------------------------------------------------------------------
-! Name: h5lis_registered_f
!
-! Purpose: Determines whether a class of user-defined links is registered.
+!****s* H5L/h5lis_registered_f
!
-! Inputs:
-! link_cls_id - User-defined link class identifier
+! NAME
+! h5lis_registered_f
!
-! Outputs:
-! registered - .TRUE. - if the link class has been registered
-! .FALSE. - if it is unregistered
-! hdferr - Error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! None
+! PURPOSE
+! Determines whether a class of user-defined links is registered.
!
-! Programmer: M.S. Breitenfeld
-! February 29, 2008
+! INPUTS
+! link_cls_id - User-defined link class identifier
!
-! Modifications: N/A
+! OUTPUTS
+! registered - .TRUE. - if the link class has been registered
+! .FALSE. - if it is unregistered
+! hdferr - Error code
+! Success: 0
+! Failure: -1
!
-!----------------------------------------------------------------------
+! AUTHOR
+! M. Scot Breitenfeld
+! February 29, 2008
+!
+! SOURCE
SUBROUTINE h5lis_registered_f(link_cls_id, registered, hdferr)
IMPLICIT NONE
INTEGER, INTENT(IN) :: link_cls_id ! User-defined link class identifier
@@ -807,9 +816,7 @@ CONTAINS
! .FALSE. - if it is unregistered
INTEGER, INTENT(OUT) :: hdferr ! Error code:
! 0 on success and -1 on failure
-!
-! MS FORTRAN needs explicit interface for C functions called here.
-!
+!*****
INTERFACE
INTEGER FUNCTION h5lis_registered_c(link_cls_id)
USE H5GLOBAL
@@ -830,31 +837,34 @@ CONTAINS
END SUBROUTINE h5lis_registered_f
-!----------------------------------------------------------------------
-! Name: h5lmove_f
!
-! Purpose: Renames a link within an HDF5 file.
+!****s* H5L/h5lmove_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.
+! 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
-! Success: 0
-! 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.
+! OUTPUTS
+! hdferr - Error code:
+! 0 on success and -1 on failure
!
-! Programmer: M.S. Breitenfeld
-! March 3, 2008
+! 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.
!
-! Modifications: N/A
+! AUTHOR
+! M. Scot Breitenfeld
+! March 3, 2008
!
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5lmove_f(src_loc_id, src_name, dest_loc_id, dest_name, hdferr, lcpl_id, lapl_id)
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN) :: src_loc_id ! Original file or group identifier.
@@ -867,16 +877,13 @@ CONTAINS
! to be associated WITH the NEW link.
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
-!
-! 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)
@@ -886,6 +893,7 @@ CONTAINS
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: src_name, dest_name
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
@@ -911,34 +919,35 @@ CONTAINS
END SUBROUTINE h5lmove_f
-!----------------------------------------------------------------------
-! Name: h5lget_name_by_idx_f
!
-! Purpose: Retrieves name of the nth link in a group, according to the order within a specified field or index.
+!****s* H5L/h5lget_name_by_idx_f
+!
+! NAME
+! h5lget_name_by_idx_f
!
-! 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
+! PURPOSE
+! Retrieves name of the nth link in a group, according to the order within a specified field or index.
!
-! Outputs:
-! name - Buffer in which link value is returned
-! hdferr - error code
-! Success: 0
-! Failure: -1
+! 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
!
-! Optional parameters:
-! lapl_id - List access property list identifier.
-! size - Maximum number of characters of link value to be returned.
+! OUTPUTS
+! name - Buffer in which link value is returned
+! hdferr - Returns 0 if successful and -1 if fails
!
-! Programmer: M. S. Breitenfeld
-! March 10, 2008
+! OPTIONAL PARAMETERS
+! lapl_id - List access property list identifier.
+! size - Maximum number of characters of link value to be returned.
!
-! Modifications: N/A
+! AUTHOR
+! M. Scot Breitenfeld
+! March 10, 2008
!
-!----------------------------------------------------------------------
+! SOURCE
SUBROUTINE h5lget_name_by_idx_f(loc_id, group_name, index_field, order, n, &
name, hdferr, size, lapl_id)
IMPLICIT NONE
@@ -958,16 +967,13 @@ 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
-
-! MS FORTRAN needs explicit interface for C functions called here.
-!
INTERFACE
INTEGER FUNCTION h5lget_name_by_idx_c(loc_id, group_name, group_namelen, index_field, order, n, &
size_default, name, lapl_id_default)
@@ -977,6 +983,7 @@ CONTAINS
!DEC$ENDIF
!DEC$ATTRIBUTES reference :: group_name, name
INTEGER(HID_T), INTENT(IN) :: loc_id
+
CHARACTER(LEN=*), INTENT(IN) :: group_name
INTEGER(SIZE_T) :: group_namelen
INTEGER, INTENT(IN) :: index_field
@@ -1004,24 +1011,27 @@ CONTAINS
END SUBROUTINE h5lget_name_by_idx_f
-! HAS PROBLEM WITH void pointer in C
-
-!!$!----------------------------------------------------------------------
-!!$! Name: h5lget_val_by_idx_f
+! HAS PROBLEM WITH void pointer in C
!!$!
-!!$! Purpose: Returns the link value of a link, according to the order of
+!!$!****s* H5L/
+!!$!
+!!$! NAME
+!!$! h5lget_val_by_idx_f
+!!$!
+!!$! PURPOSE
+!!$! Returns the link value of a link, according to the order of
!!$! 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
!!$! order - Order within field or index
!!$! n - Link for which to retrieve information
-!!$! size - Maximum number of characters of link value to be returned.
+!!$! size - Maximum number of characters of link value to be returned.
!!$!
-!!$! Outputs: NOTE: In C these are defined as a structure: H5L_info_t
+!!$! 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
@@ -1029,15 +1039,17 @@ CONTAINS
!!$! hdferr - error code
!!$! Success: 0
!!$! Failure: -1
-!!$! Optional parameters:
+!!$! OPTIONAL PARAMETERS
!!$! lapl_id - List access property list identifier.
!!$!
-!!$! Programmer: M. S. Breitenfeld
+!!$! AUTHOR
+!!$! M. Scot Breitenfeld
!!$! March 3, 2008
!!$!
-!!$! Modifications: N/A
+!!$! HISTORY N/A
!!$!
-!!$!----------------------------------------------------------------------
+!!$!
+!!$! SOURCE
!!$ 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
@@ -1065,8 +1077,6 @@ CONTAINS
!!$ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
!!$ INTEGER(HID_T) :: lapl_id_default
!!$
-!!$! MS FORTRAN needs explicit interface for C functions called here.
-!!$!
!!$ INTERFACE
!!$ INTEGER FUNCTION h5lget_val_by_idx_c(loc_id, group_name, group_namelen, index_field, order, n, &
!!$ corder_valid, corder, cset, data_size, lapl_id_default)
@@ -1101,33 +1111,32 @@ CONTAINS
!!$
!!$ END SUBROUTINE h5lget_val_by_idx_f
-
-
-!----------------------------------------------------------------------
-! Name: h5lget_val_f
-!
-! Purpose: Returns the value of a symbolic link.
-!
-! 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:
-! linkval_buff - The buffer to hold the returned link value.
-! hdferr - error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! lapl_id - List access property list identifier.
-!
-! Programmer: M. S. Breitenfeld
-! March 3, 2008
-!
-! Modifications: N/A
-!
-!----------------------------------------------------------------------
-
+!!$!
+!!$!****s* H5L/h5lget_val_f
+!!$!
+!!$! NAME
+!!$! h5lget_val_f
+!!$!
+!!$! PURPOSE
+!!$! Returns the value of a symbolic link.
+!!$!
+!!$! 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
+!!$! linkval_buff - The buffer to hold the returned link value.
+!!$! hdferr - error code
+!!$! Success: 0
+!!$! Failure: -1
+!!$! OPTIONAL PARAMETERS
+!!$! lapl_id - List access property list identifier.
+!!$!
+!!$! AUTHOR
+!!$! M. Scot Breitenfeld
+!!$! March 3, 2008
+!!$! SOURCE
!!$ SUBROUTINE h5lget_val_f(link_loc_id, link_name, size, linkval_buff, &
!!$ hdferr, lapl_id)
!!$ IMPLICIT NONE
@@ -1179,37 +1188,41 @@ CONTAINS
!!$
!!$ END SUBROUTINE h5lget_val_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
-!
-! Outputs:
-! hdferr - Error code
-! Success: 0
-! Failure: -1
-! Optional parameters:
-! None
-!
-! Programmer: M.S. Breitenfeld
-! February 29, 2008
-!
-! Modifications: N/A
-!
-!----------------------------------------------------------------------
+!!$!
+!!$!****s* H5L/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
+!!$!
+!!$! OUTPUTS
+!!$! hdferr - Error code
+!!$! Success: 0
+!!$! Failure: -1
+!!$! OPTIONAL PARAMETERS
+!!$! None
+!!$!
+!!$! AUTHOR
+!!$! M. Scot Breitenfeld
+!!$! February 29, 2008
+!!$!
+!!$! HISTORY N/A
+!!$!
+!!$!
+!!$! SOURCE
!!$ SUBROUTINE H5Lregistered_f(version, class_id, comment, create_func, &
!!$ move_func, copy_func, trav_func, del_func, query_func, hdferr)
!!$ IMPLICIT NONE
@@ -1232,9 +1245,6 @@ CONTAINS
!!$ INTEGER :: del_func_len
!!$ INTEGER :: query_func_len
!!$
-!!$!
-!!$! MS FORTRAN needs explicit interface for C functions called here.
-!!$!
!!$ INTERFACE
!!$ INTEGER FUNCTION H5Lregistered_c(version, class_id, comment, &
!!$ create_func, create_func_len, &