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.F90286
1 files changed, 0 insertions, 286 deletions
diff --git a/fortran/src/H5Lff.F90 b/fortran/src/H5Lff.F90
index d5bb1d1..9775a7d 100644
--- a/fortran/src/H5Lff.F90
+++ b/fortran/src/H5Lff.F90
@@ -1020,292 +1020,6 @@ CONTAINS
END SUBROUTINE h5lget_name_by_idx_f
-! HAS PROBLEM WITH void pointer in C
-!!$!
-!!$!****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
-!!$! 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.
-!!$!
-!!$! 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
-!!$! Success: 0
-!!$! Failure: -1
-!!$! OPTIONAL PARAMETERS
-!!$! lapl_id - List access property list identifier.
-!!$!
-!!$! AUTHOR
-!!$! M. Scot Breitenfeld
-!!$! March 3, 2008
-!!$!
-!!$! 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
-!!$ 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
-!!$ 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
-!!$ INTEGER, INTENT(OUT) :: hdferr ! Error code:
-!!$ ! 0 on success and -1 on failure
-!!$ INTEGER :: corder_valid
-!!$ INTEGER(SIZE_T) :: group_namelen
-!!$ INTEGER(HID_T), OPTIONAL, INTENT(IN) :: lapl_id ! Link access property list
-!!$ INTEGER(HID_T) :: lapl_id_default
-!!$
-!!$ 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)
-!!$ USE H5GLOBAL
-!!$ !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
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: group_name
-!!$ INTEGER(SIZE_T) :: group_namelen
-!!$ INTEGER, INTENT(IN) :: index_field
-!!$ INTEGER, INTENT(IN) :: order
-!!$ INTEGER(HSIZE_T), INTENT(IN) :: n
-!!$ INTEGER :: corder_valid
-!!$ INTEGER, INTENT(OUT) :: corder
-!!$ INTEGER, INTENT(OUT) :: cset
-!!$ INTEGER(HSIZE_T), INTENT(OUT) :: data_size
-!!$ INTEGER(HID_T) :: lapl_id_default
-!!$ END FUNCTION h5lget_val_by_idx_c
-!!$ END INTERFACE
-!!$
-!!$ group_namelen = LEN(group_name)
-!!$
-!!$ lapl_id_default = H5P_DEFAULT_F
-!!$ IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
-!!$
-!!$ hdferr = h5lget_info_by_idx_c(loc_id, group_name, group_namelen, index_field, order, n, &
-!!$ corder_valid, corder, cset, data_size, lapl_id_default)
-!!$
-!!$ f_corder_valid =.FALSE.
-!!$ IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
-!!$
-!!$ END SUBROUTINE h5lget_val_by_idx_f
-
-!!$!
-!!$!****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
-!!$ 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
-!!$
-!!$! MS FORTRAN needs explicit interface for C functions called here.
-!!$!
-!!$ INTERFACE
-!!$ INTEGER FUNCTION h5lget_val_c(link_loc_id, link_name, link_namelen, size, linkval_buff, &
-!!$ lapl_id_default)
-!!$ USE H5GLOBAL
-!!$ !DEC$IF DEFINED(HDF5F90_WINDOWS)
-!!$ !DEC$ATTRIBUTES C,reference,decorate,alias:'H5LGET_VAL_C'::h5lget_val_c
-!!$ !DEC$ENDIF
-!!$ INTEGER(HID_T), INTENT(IN) :: link_loc_id ! File or group identifier.
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: link_name ! Link whose value is to be returned.
-!!$ 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
-!!$ INTEGER(HID_T) :: lapl_id_default
-!!$
-!!$ END FUNCTION h5lget_val_c
-!!$ END INTERFACE
-!!$
-!!$ link_namelen = LEN(link_name)
-!!$
-!!$ lapl_id_default = H5P_DEFAULT_F
-!!$ IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
-!!$
-!!$ hdferr = h5lget_val_c(link_loc_id, link_name, link_namelen, size, linkval_buff, &
-!!$ lapl_id_default)
-!!$
-!!$ END SUBROUTINE h5lget_val_f
-
-!!$!
-!!$!****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
-!!$ 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 :: create_func_len
-!!$ INTEGER :: move_func_len
-!!$ INTEGER :: copy_func_len
-!!$ INTEGER :: trav_func_len
-!!$ INTEGER :: del_func_len
-!!$ INTEGER :: query_func_len
-!!$
-!!$ INTERFACE
-!!$ INTEGER FUNCTION H5Lregistered_c(version, class_id, comment, &
-!!$ create_func, create_func_len, &
-!!$ move_func, move_func_len, &
-!!$ copy_func, copy_func_len, &
-!!$ trav_func, trav_func_len, &
-!!$ del_func, del_func_len, &
-!!$ query_func,query_func_len)
-!!$ USE H5GLOBAL
-!!$ !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(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: comment ! Comment for debugging
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: create_func ! Callback during link creation
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: move_func ! Callback after moving link
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: copy_func ! Callback after copying link
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: trav_func ! The main traversal function
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: del_func ! Callback for link deletion
-!!$ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: query_func ! Callback for queries
-!!$ INTEGER, INTENT(OUT) :: hdferr ! Error code:
-!!$ ! 0 on success and -1 on failure
-!!$ INTEGER :: comment_len
-!!$ INTEGER :: create_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)
-!!$ del_func_len = LEN(del_func)
-!!$ query_func_len = LEN(query_func)
-!!$
-!!$ hdferr = H5Lregistered_c(version, class_id, comment, &
-!!$ create_func, create_func_len, &
-!!$ move_func, move_func_len, &
-!!$ copy_func, copy_func_len, &
-!!$ trav_func, trav_func_len, &
-!!$ del_func, del_func_len, &
-!!$ query_func, query_func_len)
-!!$
-!!$ END SUBROUTINE H5Lregistered_f
-
!****s* H5L (F03)/h5literate_f
!
! NAME