summaryrefslogtreecommitdiffstats
path: root/fortran/src/H5Lff.f90
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2015-04-14 20:46:59 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2015-04-14 20:46:59 (GMT)
commit74e0d6d697072ade42a04200da5cb9cddd0ef128 (patch)
tree62b999b879815cd2b5da0269db34be95ec775919 /fortran/src/H5Lff.f90
parentf8b34b0ff80c6948b0059fa46961d3f61bd5296b (diff)
downloadhdf5-74e0d6d697072ade42a04200da5cb9cddd0ef128.zip
hdf5-74e0d6d697072ade42a04200da5cb9cddd0ef128.tar.gz
hdf5-74e0d6d697072ade42a04200da5cb9cddd0ef128.tar.bz2
[svn-r26807] Combined *_F03* files and removed *_F90* files.
Diffstat (limited to 'fortran/src/H5Lff.f90')
-rw-r--r--fortran/src/H5Lff.f90196
1 files changed, 196 insertions, 0 deletions
diff --git a/fortran/src/H5Lff.f90 b/fortran/src/H5Lff.f90
index 4660e52..24f7a02 100644
--- a/fortran/src/H5Lff.f90
+++ b/fortran/src/H5Lff.f90
@@ -35,6 +35,37 @@
MODULE H5L
USE H5GLOBAL
+ USE ISO_C_BINDING
+
+ IMPLICIT NONE
+
+!****t* H5L (F03)/h5l_info_t
+!
+! Fortran2003 Derived Type:
+!
+ TYPE, bind(c) :: union_t
+ INTEGER(haddr_t) :: address
+ INTEGER(size_t) :: val_size
+ END TYPE union_t
+
+ TYPE, bind(c) :: h5l_info_t
+ INTEGER(c_int) :: type ! H5L_type_t type
+! LOGICAL(c_bool) :: corder_valid ! hbool_t corder_valid
+ INTEGER(c_int64_t) :: corder ! int64_t corder;
+ INTEGER(c_int) :: cset ! H5T_cset_t cset;
+ TYPE(union_t) :: u
+ END TYPE h5l_info_t
+
+!*****
+
+!type specifies the link class. Valid values include the following:
+! H5L_TYPE_HARD Hard link
+! H5L_TYPE_SOFT Soft link
+! H5L_TYPE_EXTERNAL External link
+! H5L_TYPE_ERROR Error
+!cset specifies the character set in which the link name is encoded. Valid values include the following:
+! H5T_CSET_ASCII US ASCII
+! H5T_CSET_UTF8 UTF-8 Unicode encoding
CONTAINS
@@ -1297,4 +1328,169 @@ CONTAINS
!!$
!!$ END SUBROUTINE H5Lregistered_f
+!****s* H5L (F03)/h5literate_f
+!
+! NAME
+! h5literate_f
+!
+! PURPOSE
+! Iterates through links in a group.
+!
+! Inputs:
+! group_id - Identifier specifying subject group
+! index_type - Type of index which determines the order:
+! H5_INDEX_NAME_F - Alpha-numeric index on name
+! H5_INDEX_CRT_ORDER_F - Index on creation order
+! order - Order within index:
+! H5_ITER_INC_F - Increasing order
+! H5_ITER_DEC_F - Decreasing order
+! H5_ITER_NATIVE_F - Fastest available order
+! idx - IN: Iteration position at which to start
+! op - Callback function passing data regarding the link to the calling application
+! op_data - User-defined pointer to data required by the application for its processing of the link
+!
+! Outputs:
+! idx - OUT: Position at which an interrupted iteration may be restarted
+! return_value - Success: The return value of the first operator that
+! returns non-zero, or zero if all members were
+! processed with no operator returning non-zero.
+!
+! Failure: Negative if something goes wrong within the
+! library, or the negative value returned by one
+! of the operators.
+!
+! hdferr - Returns 0 if successful and -1 if fails
+!
+! AUTHOR
+! M. Scot Breitenfeld
+! July 8, 2008
+!
+! Fortran2003 Interface:
+ SUBROUTINE h5literate_f(group_id, index_type, order, idx, op, op_data, return_value, hdferr)
+ USE, INTRINSIC :: ISO_C_BINDING
+ IMPLICIT NONE
+ INTEGER(HID_T) , INTENT(IN) :: group_id
+ INTEGER , INTENT(IN) :: index_type
+ INTEGER , INTENT(IN) :: order
+ INTEGER(HSIZE_T), INTENT(INOUT) :: idx
+ TYPE(C_FUNPTR) , INTENT(IN) :: op
+ TYPE(C_PTR) , INTENT(IN) :: op_data
+ INTEGER , INTENT(OUT) :: return_value
+ INTEGER , INTENT(OUT) :: hdferr
+!*****
+ INTERFACE
+ INTEGER FUNCTION h5literate_c(group_id, index_type, order, idx, op, op_data) &
+ BIND(C, NAME='h5literate_c')
+ USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_ptr, c_funptr
+ USE H5GLOBAL
+ INTEGER(HID_T), INTENT(IN) :: group_id
+ INTEGER, INTENT(IN) :: index_type
+ INTEGER, INTENT(IN) :: order
+ INTEGER(HSIZE_T), INTENT(INOUT) :: idx
+ TYPE(C_FUNPTR), VALUE :: op
+ TYPE(C_PTR), VALUE :: op_data
+ END FUNCTION h5literate_c
+ END INTERFACE
+
+ return_value = h5literate_c(group_id, index_type, order, idx, op, op_data)
+
+ IF(return_value.GE.0)THEN
+ hdferr = 0
+ ELSE
+ hdferr = -1
+ END IF
+
+ END SUBROUTINE h5literate_f
+
+!****s* H5L (F03)/h5literate_by_name_f
+!
+! NAME
+! h5literate_by_name_f
+!
+! PURPOSE
+! Iterates through links in a group.
+!
+! Inputs:
+! loc_id - File or group identifier specifying location of subject group
+! group_name - Name of subject group
+! index_type - Type of index which determines the order:
+! H5_INDEX_NAME_F - Alpha-numeric index on name
+! H5_INDEX_CRT_ORDER_F - Index on creation order
+! order - Order within index:
+! H5_ITER_INC_F - Increasing order
+! H5_ITER_DEC_F - Decreasing order
+! H5_ITER_NATIVE_F - Fastest available order
+! idx - IN: Iteration position at which to start
+! op - Callback function passing data regarding the link to the calling application
+! op_data - User-defined pointer to data required by the application for its processing of the link
+!
+! Outputs:
+! idx - OUT: Position at which an interrupted iteration may be restarted
+! return_value - Success: The return value of the first operator that
+! returns non-zero, or zero if all members were
+! processed with no operator returning non-zero.
+!
+! Failure: Negative if something goes wrong within the
+! library, or the negative value returned by one
+! of the operators.
+!
+! hdferr - Returns 0 if successful and -1 if fails
+!
+! Optional parameters:
+! lapl_id - Link access property list
+!
+! AUTHOR
+! M. Scot Breitenfeld
+! Augest 18, 2008
+!
+! Fortran2003 Interface:
+ SUBROUTINE h5literate_by_name_f(loc_id, group_name, index_type, order, &
+ idx, op, op_data, return_value, hdferr, lapl_id)
+ USE, INTRINSIC :: ISO_C_BINDING
+ IMPLICIT NONE
+ INTEGER(HID_T) , INTENT(IN) :: loc_id
+ CHARACTER(LEN=*), INTENT(IN) :: group_name
+ INTEGER , INTENT(IN) :: index_type
+ INTEGER , INTENT(IN) :: order
+ INTEGER(HSIZE_T), INTENT(INOUT) :: idx
+ TYPE(C_FUNPTR) , INTENT(IN) :: op
+ TYPE(C_PTR) , INTENT(IN) :: op_data
+ INTEGER , INTENT(OUT) :: return_value
+ INTEGER , INTENT(OUT) :: hdferr
+ INTEGER(HID_T) , INTENT(IN), OPTIONAL :: lapl_id
+!*****
+ INTEGER(HID_T) :: lapl_id_default
+ INTEGER(SIZE_T) :: namelen
+
+ INTERFACE
+ INTEGER FUNCTION h5literate_by_name_c(loc_id, name, namelen, index_type, order,&
+ idx, op, op_data, lapl_id_default) BIND(C, NAME='h5literate_by_name_c')
+ USE, INTRINSIC :: ISO_C_BINDING, ONLY : c_char, c_ptr, c_funptr
+ USE H5GLOBAL
+ INTEGER(HID_T) , INTENT(IN) :: loc_id
+ CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: name
+ INTEGER(SIZE_T) , INTENT(IN) :: namelen
+ INTEGER , INTENT(IN) :: index_type
+ INTEGER , INTENT(IN) :: order
+ INTEGER(HSIZE_T), INTENT(INOUT) :: idx
+ TYPE(C_FUNPTR), VALUE :: op
+ TYPE(C_PTR), VALUE :: op_data
+ INTEGER(HID_T) , INTENT(IN) :: lapl_id_default
+ END FUNCTION
+ END INTERFACE
+
+ namelen = LEN(group_name)
+ lapl_id_default = H5P_DEFAULT_F
+ IF(PRESENT(lapl_id)) lapl_id_default = lapl_id
+
+ return_value = h5literate_by_name_c(loc_id, group_name, namelen, index_type, order, idx, op, op_data, lapl_id_default)
+
+ IF(return_value.GE.0)THEN
+ hdferr = 0
+ ELSE
+ hdferr = -1
+ END IF
+
+ END SUBROUTINE h5literate_by_name_f
+
END MODULE H5L