H5L

[ Top ] [ Modules ]

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.

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.

h5lcopy_f

[ Top ] [ H5L ] [ Subroutines ]

NAME

  h5lcopy_f

PURPOSE

  Copies a link from one location to another.

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

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

AUTHOR

  M. Scot Breitenfeld
  February 27, 2008

SOURCE

  SUBROUTINE h5lcopy_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  ! Location identifier of the source link
    CHARACTER(LEN=*), INTENT(IN) :: src_name   ! Name of the link to be copied
    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:
                                          ! 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

H5Lcreate_external_f

[ Top ] [ H5L ] [ Subroutines ]

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
  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        - Returns 0 if successful and -1 if fails

OPTIONAL PARAMETERS

  lcpl_id       - Link creation property list identifier.
  lapl_id       - Link access property list identifier.

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
                                              ! 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:
                                          ! 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.

H5Lcreate_hard_f

[ Top ] [ H5L ] [ Subroutines ]

NAME

  H5Lcreate_hard_f

PURPOSE

  Creates a hard link to an object.

INPUTS

  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.

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.

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.
    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:
                                          ! 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.

H5Lcreate_soft_f

[ Top ] [ H5L ] [ Subroutines ]

NAME

  H5Lcreate_soft_f

PURPOSE

  Creates a soft link to an object.

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.

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.

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.
    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
    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.

h5ldelete_by_idx_f

[ Top ] [ H5L ] [ Subroutines ]

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
    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
                                               !    H5_INDEX_NAME_F      - Index on names
                                               !    H5_INDEX_CRT_ORDER_F - Index on creation order
                                               !    H5_INDEX_N_F              - Number of indices defined
    INTEGER, INTENT(IN) :: order               ! Order in which to iterate over 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
    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

h5ldelete_f

[ Top ] [ H5L ] [ Subroutines ]

NAME

  h5ldelete_f

PURPOSE

  Removes a link from a group.

INPUTS

  loc_id        - Identifier of the file or group containing the object
  name          - Name of the link to delete

OUTPUTS

  hdferr        - Returns 0 if successful and -1 if fails

OPTIONAL PARAMETERS

  lapl_id       - Link access property list identifier

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
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Name of the link to delete
    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

H5Lexists_f

[ Top ] [ H5L ] [ Subroutines ]

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        - Returns 0 if successful and -1 if fails

OPTIONAL PARAMETERS

  lapl_id       - Link access property list identifier.

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.
    CHARACTER(LEN=*), INTENT(IN) :: name  ! Link name to check.
    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
                                          ! Link access property list identifier.

h5lget_info_by_idx_f

[ Top ] [ H5L ] [ Subroutines ]

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.  

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  
    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
                                        !    H5_INDEX_NAME_F      - Index on names
                                        !    H5_INDEX_CRT_ORDER_F - Index on creation order
                                        !    H5_INDEX_N_F             - Number of indices defined
    INTEGER, INTENT(IN) :: order        ! Order in which to iterate over 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
    INTEGER(HSIZE_T), INTENT(IN) :: n   ! Attributeâs position in index
    INTEGER, INTENT(OUT) :: 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
    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, INTENT(OUT) :: hdferr       ! Error code:
                                         ! 0 on success and -1 on failure
    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id  ! Link access property list

h5lget_info_f

[ Top ] [ H5L ] [ Subroutines ]

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)
    IMPLICIT NONE

    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) :: 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:
                                      !  H5L_TYPE_HARD_F      - Hard link
                                      !  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, INTENT(OUT) :: hdferr       ! Error code:
                                         ! 0 on success and -1 on failure
    INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id  ! Link access property list

h5lget_name_by_idx_f

[ Top ] [ H5L ] [ Subroutines ]

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.

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

  name          - Buffer in which link value is returned
  hdferr        - Returns 0 if successful and -1 if fails

OPTIONAL PARAMETERS

  lapl_id       - List access property list identifier.
  size          - Maximum number of characters of link value to be returned.

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
    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
                                        !    H5_INDEX_NAME_F      - Index on names
                                        !    H5_INDEX_CRT_ORDER_F - Index on creation order
                                        !    H5_INDEX_N_F             - Number of indices defined
    INTEGER, INTENT(IN) :: order        ! Order in which to iterate over 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
    INTEGER(HSIZE_T), INTENT(IN) :: n   ! Attributeâs position in index
    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

h5lis_registered_f

[ Top ] [ H5L ] [ Subroutines ]

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
  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
    LOGICAL, INTENT(OUT) :: registered  ! .TRUE. - if the link class has been registered and
                                        ! .FALSE. - if it is unregistered
    INTEGER, INTENT(OUT) :: hdferr      ! Error code:
                                        ! 0 on success and -1 on failure

h5lmove_f

[ Top ] [ H5L ] [ Subroutines ]

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:
                   0 on success and -1 on failure

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.

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.
    CHARACTER(LEN=*), INTENT(IN) :: src_name  ! Original link name.
    INTEGER(HID_T), INTENT(IN) :: dest_loc_id ! Destination file or group identifier.
    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
                                                    ! 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.