summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorScot Breitenfeld <brtnfld@hdfgroup.org>2011-10-14 21:55:33 (GMT)
committerScot Breitenfeld <brtnfld@hdfgroup.org>2011-10-14 21:55:33 (GMT)
commitf4fb04d6b3db29fa6df965c3eba24c9baecd1d9c (patch)
tree5ae23ed214748ce1cea37dad7b1b2f60452d6513
parentc43f28230df5f8cedb4f22a04cabeca898de7ac4 (diff)
downloadhdf5-f4fb04d6b3db29fa6df965c3eba24c9baecd1d9c.zip
hdf5-f4fb04d6b3db29fa6df965c3eba24c9baecd1d9c.tar.gz
hdf5-f4fb04d6b3db29fa6df965c3eba24c9baecd1d9c.tar.bz2
[svn-r21585] Description: Fixed robodoc headers (functions and derived types), updated the definition of derived types from the original F2003 merge.
Tested: jam (intel, gnu, pgi)
-rw-r--r--fortran/src/H5Lff_F03.f90203
-rw-r--r--fortran/src/H5Of.c89
-rw-r--r--fortran/src/H5Off_F03.f90140
-rw-r--r--fortran/src/H5_ff.f9078
-rw-r--r--fortran/src/H5f90proto.h53
-rw-r--r--fortran/test/tH5L_F03.f9013
6 files changed, 325 insertions, 251 deletions
diff --git a/fortran/src/H5Lff_F03.f90 b/fortran/src/H5Lff_F03.f90
index e1da7c1..56062b2 100644
--- a/fortran/src/H5Lff_F03.f90
+++ b/fortran/src/H5Lff_F03.f90
@@ -9,9 +9,9 @@
! PURPOSE
!
! This file contains Fortran 90 and Fortran 2003 interfaces for H5L functions.
-! It contains the same functions as H5Lff_DEPRECIATE.f90 but includes the
+! It contains the same functions as H5Lff_F90.f90 but includes the
! Fortran 2003 functions and the interface listings. This file will be compiled
-! instead of H5Lff_DEPRECIATE.f90 if Fortran 2003 functions are enabled.
+! instead of H5Lff_F90.f90 if Fortran 2003 functions are enabled.
!
! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
@@ -40,6 +40,38 @@
MODULE H5L_PROVISIONAL
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
@@ -52,54 +84,50 @@ CONTAINS
! Iterates through links in a group.
!
! Inputs:
-! group_id - Identifier specifying subject group
-! index_type - Type of index which determines the order
-! order - Order within index
-! idx - 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
+! 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 - Position at which an interrupted iteration may be restarted
-! hdferr - Error code:
-! Success: 0
-! Failure: -1
+! 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
!
-! Signature:
+! Fortran2003 Interface:
SUBROUTINE h5literate_f(group_id, index_type, order, idx, op, op_data, return_value, hdferr)
- USE ISO_C_BINDING
+ USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: group_id ! Identifier specifying subject group
- INTEGER, INTENT(IN) :: 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
- INTEGER, INTENT(IN) :: order ! Order within index:
- ! H5_ITER_INC_F - Increasing order
- ! H5_ITER_DEC_F - Decreasing order
- ! H5_ITER_NATIVE_F - Fastest available order
- INTEGER(HSIZE_T), INTENT(INOUT) :: idx ! IN : Iteration position at which to start
- ! OUT: Position at which an interrupted iteration may be restarted
-
- TYPE(C_FUNPTR):: op ! Callback function passing data regarding the link to the calling application
- TYPE(C_PTR) :: op_data ! User-defined pointer to data required by the application for its processing of the link
-
- INTEGER, INTENT(OUT) :: 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.
-
- INTEGER, INTENT(OUT) :: hdferr ! Error code:
- ! 0 on success and -1 on failure
+ 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)
- USE ISO_C_BINDING
+ USE, INTRINSIC :: ISO_C_BINDING
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5LITERATE_C'::h5literate_c
@@ -132,87 +160,80 @@ CONTAINS
! 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
-! order - Order within index
-! idx - 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
+! 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 - Position at which an interrupted iteration may be restarted
-! hdferr - Error code:
-! Success: 0
-! Failure: -1
+! 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
+! lapl_id - Link access property list
!
! AUTHOR
! M. Scot Breitenfeld
! Augest 18, 2008
!
-! Signature:
+! Fortran2003 Interface:
SUBROUTINE h5literate_by_name_f(loc_id, group_name, index_type, order, idx, op, op_data, return_value, hdferr, lapl_id)
- USE ISO_C_BINDING
+ USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: loc_id ! Identifier specifying subject group
- CHARACTER(LEN=*) :: group_name ! Name of subject group
- INTEGER, INTENT(IN) :: 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
- INTEGER, INTENT(IN) :: order ! Order within index:
- ! H5_ITER_INC_F - Increasing order
- ! H5_ITER_DEC_F - Decreasing order
- ! H5_ITER_NATIVE_F - Fastest available order
- INTEGER(HSIZE_T), INTENT(INOUT) :: idx ! IN : Iteration position at which to start
- ! OUT: Position at which an interrupted iteration may be restarted
-
- TYPE(C_FUNPTR):: op ! Callback function passing data regarding the link to the calling application
- TYPE(C_PTR) :: op_data ! User-defined pointer to data required by the application for its processing of the link
-
- INTEGER, INTENT(OUT) :: 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.
-
- 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) , 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)
- USE ISO_C_BINDING
+ INTEGER FUNCTION h5literate_by_name_c(loc_id, name, namelen, index_type, order, idx, op, op_data, lapl_id_default)
+ USE, INTRINSIC :: ISO_C_BINDING
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5LITERATE_BY_NAME_C'::h5literate_by_name_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: loc_id
- CHARACTER(LEN=*) :: name
- INTEGER(SIZE_T) :: namelen
- INTEGER, INTENT(IN) :: index_type
- INTEGER, INTENT(IN) :: order
+ INTEGER(HID_T) , INTENT(IN) :: loc_id
+ CHARACTER(LEN=*), 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) :: lapl_id_default
+ INTEGER(HID_T) , INTENT(IN) :: lapl_id_default
END FUNCTION
-! h5literate_by_name_c
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)
+ 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
diff --git a/fortran/src/H5Of.c b/fortran/src/H5Of.c
index a23f2a7..ffbf661 100644
--- a/fortran/src/H5Of.c
+++ b/fortran/src/H5Of.c
@@ -240,12 +240,13 @@ nh5oopen_by_addr_c (hid_t_f *loc_id, haddr_t_f *addr, hid_t_f *obj_id)
*/
int_f
nh5oget_info_by_name_c (hid_t_f *loc_id, _fcd name, size_t_f *namelen, hid_t_f *lapl_id,
- H5O_info_t *object_info)
+ H5O_info_t_f *object_info)
/******/
{
char *c_name = NULL; /* Buffer to hold C string */
int_f ret_value = 0; /* Return value */
H5O_info_t Oinfo;
+ struct tm *ts;
/*
* Convert FORTRAN name to C name
@@ -261,27 +262,73 @@ nh5oget_info_by_name_c (hid_t_f *loc_id, _fcd name, size_t_f *namelen, hid_t_f *
HGOTO_DONE(FAIL);
object_info->fileno = Oinfo.fileno;
- object_info->addr = Oinfo.addr;
- object_info->type = Oinfo.type;
- object_info->rc = Oinfo.rc;
- object_info->atime = Oinfo.atime;
- object_info->mtime = Oinfo.mtime;
- object_info->ctime = Oinfo.ctime;
- object_info->btime = Oinfo.btime;
- object_info->num_attrs = Oinfo.num_attrs;
-
-
-/* printf("fileno %d %d\n",object_info->fileno, Oinfo.fileno); */
-/* printf("string %d %d\n",object_info.rc, Oinfo.rc); */
-
-/* printf("atime %lld %lld\n",(long long int)object_info.atime, (long long int)Oinfo.atime); */
-/* printf("atime %lld %lld\n",(long long int)object_info.mtime, (long long int)Oinfo.mtime); */
-/* printf("atime %lld %lld\n",(long long int)object_info.ctime, (long long int)Oinfo.ctime); */
-/* printf("atime %lld %lld\n",(long long int)object_info.btime, (long long int)Oinfo.btime); */
-/* printf("string %f %f\n",object_info.addr, Oinfo.addr); */
-/* printf("num_attrs %d %d\n",object_info.num_attrs, Oinfo.num_attrs); */
-/* printf("num_attrs %f %f\n",object_info.hdr.version, Oinfo.hdr.version); */
+ object_info->addr = (haddr_t_f)Oinfo.addr;
+
+
+ object_info->type = (int_f)Oinfo.type;
+ object_info->rc = (int_f)Oinfo.rc;
+
+ ts = gmtime(&Oinfo.atime);
+
+ object_info->atime[0] = (int_f)ts->tm_year+1900; /* year starts at 1900 */
+ object_info->atime[1] = (int_f)ts->tm_mon+1; /* month starts at 0 in C */
+ object_info->atime[2] = (int_f)ts->tm_mday;
+/* object_info->atime[3] = (int_f)ts->tm_gmtoff; /\* convert from seconds to minutes *\/ */
+ object_info->atime[4] = (int_f)ts->tm_hour;
+ object_info->atime[5] = (int_f)ts->tm_min;
+ object_info->atime[6] = (int_f)ts->tm_sec;
+ object_info->atime[7] = -32767; /* millisecond is not available, assign it -HUGE(0) */
+
+ ts = gmtime(&Oinfo.btime);
+
+ object_info->btime[0] = (int_f)ts->tm_year+1900; /* year starts at 1900 */
+ object_info->btime[1] = (int_f)ts->tm_mon+1; /* month starts at 0 in C */
+ object_info->btime[2] = (int_f)ts->tm_mday;
+/* object_info->btime[3] = (int_f)ts->tm_gmtoff/60; /\* convert from seconds to minutes *\/ */
+ object_info->btime[4] = (int_f)ts->tm_hour;
+ object_info->btime[5] = (int_f)ts->tm_min;
+ object_info->btime[6] = (int_f)ts->tm_sec;
+ object_info->btime[7] = -32767; /* millisecond is not available, assign it -HUGE(0) */
+
+ ts = gmtime(&Oinfo.ctime);
+
+ object_info->ctime[0] = (int_f)ts->tm_year+1900; /* year starts at 1900 */
+ object_info->ctime[1] = (int_f)ts->tm_mon+1; /* month starts at 0 in C */
+ object_info->ctime[2] = (int_f)ts->tm_mday;
+/* object_info->ctime[3] = (int_f)ts->tm_gmtoff/60; /\* convert from seconds to minutes *\/ */
+ object_info->ctime[4] = (int_f)ts->tm_hour;
+ object_info->ctime[5] = (int_f)ts->tm_min;
+ object_info->ctime[6] = (int_f)ts->tm_sec;
+ object_info->ctime[7] = -32767; /* millisecond is not available, assign it -HUGE(0) */
+
+ ts = gmtime(&Oinfo.mtime);
+
+ object_info->mtime[0] = (int_f)ts->tm_year+1900; /* year starts at 1900 */
+ object_info->mtime[1] = (int_f)ts->tm_mon+1; /* month starts at 0 in C */
+ object_info->mtime[2] = (int_f)ts->tm_mday;
+/* object_info->mtime[3] = (int_f)ts->tm_gmtoff/60; /\* convert from seconds to minutes *\/ */
+ object_info->mtime[4] = (int_f)ts->tm_hour;
+ object_info->mtime[5] = (int_f)ts->tm_min;
+ object_info->mtime[6] = (int_f)ts->tm_sec;
+ object_info->mtime[7] = -32767; /* millisecond is not available, assign it -HUGE(0) */
+
+ object_info->num_attrs = (hsize_t_f)Oinfo.num_attrs;
+
+ object_info->hdr.version = (int_f)Oinfo.hdr.version;
+ object_info->hdr.nmesgs = (int_f)Oinfo.hdr.nmesgs;
+ object_info->hdr.nchunks = (int_f)Oinfo.hdr.nchunks;
+ object_info->hdr.flags = (int_f)Oinfo.hdr.flags;
+
+ object_info->hdr.space.total = (hsize_t_f)Oinfo.hdr.space.total;
+ object_info->hdr.space.meta = (hsize_t_f)Oinfo.hdr.space.meta;
+ object_info->hdr.space.mesg = (hsize_t_f)Oinfo.hdr.space.mesg;
+ object_info->hdr.space.free = (hsize_t_f)Oinfo.hdr.space.free;
+
+ object_info->hdr.mesg.present = Oinfo.hdr.mesg.present;
+ object_info->hdr.mesg.shared = Oinfo.hdr.mesg.shared;
+ object_info->meta_size.obj.index_size = (hsize_t_f)Oinfo.meta_size.obj.index_size;
+ object_info->meta_size.obj.heap_size = (hsize_t_f)Oinfo.meta_size.obj.heap_size;
done:
return ret_value;
diff --git a/fortran/src/H5Off_F03.f90 b/fortran/src/H5Off_F03.f90
index 4233c14..be253ce 100644
--- a/fortran/src/H5Off_F03.f90
+++ b/fortran/src/H5Off_F03.f90
@@ -5,9 +5,9 @@
!
! PURPOSE
! This file contains Fortran 90 and Fortran 2003 interfaces for H5O functions.
-! It contains the same functions as H5Off_DEPRECIATE.f90 but includes the
+! It contains the same functions as H5Off_F90.f90 but includes the
! Fortran 2003 functions and the interface listings. This file will be compiled
-! instead of H5Off_DEPRECIATE.f90 if Fortran 2003 functions are enabled.
+! instead of H5Off_F90.f90 if Fortran 2003 functions are enabled.
!
! COPYRIGHT
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
@@ -36,40 +36,38 @@
MODULE H5O_PROVISIONAL
USE H5GLOBAL
- USE ISO_C_BINDING
+ USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
-
+!****t* H5T (F03)/h5o_info_t
+!
+! Fortran2003 Derived Type:
+!
enum, bind(c)
enumerator :: H5O_TYPE_UNKNOWN_F = -1
enumerator :: H5O_TYPE_GROUP_F, H5O_TYPE_DATASET_F, H5O_TYPE_NAMED_DATATYPE_F, H5O_TYPE_NTYPES_F
end enum
-
TYPE, BIND(C) :: space_t
INTEGER(hsize_t) :: total ! Total space for storing object header in file
INTEGER(hsize_t) :: meta ! Space within header for object header metadata information
INTEGER(hsize_t) :: mesg ! Space within header for actual message information
INTEGER(hsize_t) :: free ! Free space within object header
END TYPE space_t
-
+
TYPE, BIND(C) :: mesg_t
INTEGER(c_int64_t) :: present ! Flags to indicate presence of message type in header
INTEGER(c_int64_t) :: shared ! Flags to indicate message type is shared in header
END TYPE mesg_t
TYPE, BIND(C) :: hdr_t
- INTEGER(c_int) :: version ! Version number of header format in file
- ! unsigned version
- INTEGER(c_int) :: nmesgs ! Number of object header messages
- ! unsigned nmesgs
- INTEGER(c_int) :: nchunks ! Number of object header chunks
- ! unsigned nchunks
- INTEGER(c_int) :: flags ! Object header status flags
- ! unsigned flags
- TYPE(space_t) :: space
- TYPE(mesg_t) :: mesg
+ INTEGER :: version ! Version number of header format in file
+ INTEGER :: nmesgs ! Number of object header messages
+ INTEGER :: nchunks ! Number of object header chunks
+ INTEGER :: flags ! Object header status flags
+ TYPE(space_t) :: space
+ TYPE(mesg_t) :: mesg
END TYPE hdr_t
! Extra metadata storage for obj & attributes
@@ -83,28 +81,29 @@ MODULE H5O_PROVISIONAL
TYPE(H5_ih_info_t) :: attr ! v2 B-tree & heap for attributes
ENDTYPE meta_size_t
+ TYPE, BIND(C) :: h5o_info_t
+ INTEGER(c_long) :: fileno ! File number that object is located in
+ INTEGER(haddr_t) :: addr ! Object address in file
+ INTEGER :: type ! Basic object type (group, dataset, etc.)
+ INTEGER :: rc ! Reference count of object
+
+ INTEGER, DIMENSION(8) :: atime ! Access time ! -- NOTE --
+ INTEGER, DIMENSION(8) :: mtime ! Modification time ! Returns an integer array
+ INTEGER, DIMENSION(8) :: ctime ! Change time ! as specified in the Fortran
+ INTEGER, DIMENSION(8) :: btime ! Birth time ! intrinsic DATE_AND_TIME(VALUES)
- TYPE, BIND(C) :: H5O_info_t
- INTEGER(c_long) :: fileno ! File number that object is located in
- ! unsigned long
- INTEGER(HADDR_T) :: addr ! Object address in file
- INTEGER(c_int) :: TYPE ! Basic object type (group, dataset, etc.)
- ! H5O_type_t type which is type enum
- INTEGER(c_int) :: rc ! Reference count of object
- ! unsigned rc
- INTEGER(c_int) :: atime ! Access time
- INTEGER(c_int) :: mtime ! Modification time
- INTEGER(c_int) :: ctime ! Change time
- INTEGER(c_int) :: btime ! Birth time
- INTEGER(hsize_t) :: num_attrs ! # of attributes attached to object
+ INTEGER(hsize_t) :: num_attrs ! # of attributes attached to object
TYPE(hdr_t) :: hdr
+
TYPE(meta_size_t) :: meta_size
- END TYPE H5O_info_t
+ END TYPE h5o_info_t
+
+!*****
CONTAINS
-!****s* H5O (F03)/h5ovisit_f
+!****s* H5O (F03)/h5ovisit_f_F03
!
! NAME
! h5ovisit_f
@@ -113,58 +112,47 @@ CONTAINS
! Recursively visits all objects starting from a specified object.
!
! Inputs:
-! group_id - Identifier of the group at which the recursive iteration begins
-! index_type - Type of index; valid values include:
-! H5_INDEX_NAME_F
-! H5_INDEX_CRT_ORDER_F
-! order - Order in which index is traversed; valid values include:
-! H5_ITER_DEC_F
-! H5_ITER_INC_F
-! H5_ITER_NATIVE_F
-! op - Callback function passing data regarding the group to the calling application
-! op_data - User-defined pointer to data required by the application for its processing of the group
+! object_id - Identifier of the object at which the recursive iteration begins.
+! index_type - Type of index; valid values include:
+! H5_INDEX_NAME_F
+! H5_INDEX_CRT_ORDER_F
+! order - Order in which index is traversed; valid values include:
+! H5_ITER_DEC_F
+! H5_ITER_INC_F
+! H5_ITER_NATIVE_F
+! op - Callback function passing data regarding the group to the calling application
+! op_data - User-defined pointer to data required by the application for its processing of the group
!
! Outputs:
-! idx - returns the return value of the first operator that returns a positive value, or
-! zero if all members were processed with no operator returning non-zero.
-! hdferr - error code:
-! 0 on success and -1 on failure
+! return_value - returns the return value of the first operator that returns a positive value, or
+! zero if all members were processed with no operator returning non-zero.
+! hdferr - Returns 0 if successful and -1 if fails
! AUTHOR
! M. Scot Breitenfeld
! November 19, 2008
!
-! Signature:
- SUBROUTINE h5ovisit_f(group_id, index_type, order, op, op_data, return_value, hdferr)
- USE ISO_C_BINDING
+! Fortran2003 Interface:
+ SUBROUTINE h5ovisit_f(object_id, index_type, order, op, op_data, return_value, hdferr)
+ USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
- INTEGER(HID_T), INTENT(IN) :: group_id
+ INTEGER(HID_T), INTENT(IN) :: object_id
INTEGER, INTENT(IN) :: index_type
INTEGER, INTENT(IN) :: order
-!!$ INTEGER(HSIZE_T), INTENT(INOUT) :: idx ! IN : Iteration position at which to start
-!!$ ! OUT: Position at which an interrupted iteration may be restarted
-
- TYPE(C_FUNPTR):: op ! Callback function passing data regarding the link to the calling application
- TYPE(C_PTR) :: op_data ! User-defined pointer to data required by the application for its processing of the link
-
- INTEGER, INTENT(OUT) :: 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.
-
- INTEGER, INTENT(OUT) :: hdferr ! Error code:
- ! 0 on success and -1 on failure
+ TYPE(C_FUNPTR):: op
+ TYPE(C_PTR) :: op_data
+ INTEGER, INTENT(OUT) :: return_value
+ INTEGER, INTENT(OUT) :: hdferr
!*****
+
INTERFACE
- INTEGER FUNCTION h5ovisit_c(group_id, index_type, order, op, op_data)
- USE ISO_C_BINDING
+ INTEGER FUNCTION h5ovisit_c(object_id, index_type, order, op, op_data)
+ USE, INTRINSIC :: ISO_C_BINDING
USE H5GLOBAL
!DEC$IF DEFINED(HDF5F90_WINDOWS)
!DEC$ATTRIBUTES C,reference,decorate,alias:'H5OVISIT_C'::h5ovisit_c
!DEC$ENDIF
- INTEGER(HID_T), INTENT(IN) :: group_id
+ INTEGER(HID_T), INTENT(IN) :: object_id
INTEGER, INTENT(IN) :: index_type
INTEGER, INTENT(IN) :: order
TYPE(C_FUNPTR), VALUE :: op
@@ -172,7 +160,7 @@ CONTAINS
END FUNCTION h5ovisit_c
END INTERFACE
- return_value = h5ovisit_c(group_id, index_type, order, op, op_data)
+ return_value = h5ovisit_c(object_id, index_type, order, op, op_data)
IF(return_value.GE.0)THEN
hdferr = 0
@@ -182,10 +170,8 @@ CONTAINS
END SUBROUTINE h5ovisit_f
-
-
!
-!!$!****s* H5O/h5oget_info_by_name_f
+!!$!****s* H5O (F03)/h5oget_info_by_name_f_F03
!
! NAME
! h5oget_info_by_name_f
@@ -208,20 +194,15 @@ CONTAINS
! M. Scot Breitenfeld
! December 1, 2008
!
-! Signature:
+! Fortran2003 Interface:
SUBROUTINE h5oget_info_by_name_f(loc_id, name, &
object_info, hdferr, lapl_id)
- ! f_corder_valid, corder, cset, data_size, hdferr, lapl_id)
- USE ISO_C_BINDING
+ USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: loc_id
CHARACTER(LEN=*), INTENT(IN) :: name
TYPE(C_PTR) :: object_info
-!!$ LOGICAL , INTENT(OUT) :: f_corder_valid
-!!$ INTEGER , INTENT(OUT) :: corder
-!!$ INTEGER , INTENT(OUT) :: cset
-!!$ INTEGER(HSIZE_T), INTENT(OUT) :: data_size
INTEGER , INTENT(OUT) :: hdferr
INTEGER(HID_T) , INTENT(IN) , OPTIONAL :: lapl_id
!*****
@@ -255,9 +236,6 @@ CONTAINS
object_info)
-!!$ f_corder_valid =.FALSE.
-!!$ IF (corder_valid .EQ. 1) f_corder_valid =.TRUE.
-
END SUBROUTINE H5Oget_info_by_name_f
END MODULE H5O_PROVISIONAL
diff --git a/fortran/src/H5_ff.f90 b/fortran/src/H5_ff.f90
index 21449d3..57c1afd 100644
--- a/fortran/src/H5_ff.f90
+++ b/fortran/src/H5_ff.f90
@@ -41,6 +41,7 @@ MODULE H5LIB
! pre-Fortran 2003 - empty module
! Forttran 2003 - contains functions
USE H5GLOBAL
+
CONTAINS
!****s* H5LIB/h5open_f
!
@@ -50,10 +51,9 @@ CONTAINS
! PURPOSE
! Initializes HDF5 Fortran interface.
!
-! OUTPUTS
-! error - error code
-! Success: 0
-! Failure: -1
+! Outputs:
+! error - Returns 0 if successful and -1 if fails
+!
! AUTHOR
! Elena Pourmal
! August 12, 1999
@@ -66,7 +66,7 @@ CONTAINS
! Removed call to h5open_c since this may cause a problem for an
! application that uses HDF5 library outside HDF5 Fortran APIs.
! October 13, 2011
-! SOURCE
+! Fortran90 Interface:
SUBROUTINE h5open_f(error)
USE H5GLOBAL
IMPLICIT NONE
@@ -165,15 +165,12 @@ CONTAINS
! PURPOSE
! Closes HDF5 Fortran interface.
!
-! OUTPUTS
-! error - error code
-! Success: 0
-! Failure: -1
+! Outputs:
+! error - Returns 0 if successful and -1 if fails
!
! AUTHOR
! Elena Pourmal
! August 12, 1999
-
!
! HISTORY
! Explicit Fortran interfaces were added for
@@ -183,7 +180,7 @@ CONTAINS
! Removed call to h5close_c since this may cause a problem for an
! application that uses HDF5 library outside HDF5 Fortran APIs.
! October 13, 2011
-! SOURCE
+! Fortran90 Interface:
SUBROUTINE h5close_f(error)
USE H5GLOBAL
IMPLICIT NONE
@@ -209,7 +206,7 @@ CONTAINS
error_1 = h5close_types_c(predef_types, PREDEF_TYPES_LEN, &
floating_types, FLOATING_TYPES_LEN, &
integer_types, INTEGER_TYPES_LEN )
- error = error_1
+ error = error_1
END SUBROUTINE h5close_f
@@ -221,19 +218,17 @@ CONTAINS
! PURPOSE
! Returns the HDF5 LIbrary release number
!
-! OUTPUTS
-! majnum - major version of the library
-! minum - minor version of the library
-! relnum - release version of the library
-! error - error code
-! Success: 0
-! Failure: -1
+! Outputs:
+! majnum - major version of the library
+! minum - minor version of the library
+! relnum - release version of the library
+! error - Returns 0 if successful and -1 if fails
!
! AUTHOR
! Elena Pourmal
! September 24, 2002
!
-! SOURCE
+! Fortran90 Interface:
SUBROUTINE h5get_libversion_f(majnum, minnum, relnum, error)
USE H5GLOBAL
IMPLICIT NONE
@@ -260,24 +255,23 @@ CONTAINS
! PURPOSE
! Verifies that library versions are consistent.
!
-! INPUTS
-! majnum - major version of the library
-! minum - minor version of the library
-! relnum - release version of the library
-! OUTPUTS
-! error - error code
-! Success: 0
-! Failure: application aborts
+! Inputs:
+! majnum - major version of the library
+! minum - minor version of the library
+! relnum - release version of the library
+!
+! Outputs:
+! error - Returns 0 if successful and -1 if fails
!
! AUTHOR
! Elena Pourmal
! September 24, 2002
!
-! SOURCE
+! Fortran90 Interface:
SUBROUTINE h5check_version_f(majnum, minnum, relnum, error)
USE H5GLOBAL
IMPLICIT NONE
- INTEGER, INTENT(IN) :: majnum, minnum, relnum
+ INTEGER, INTENT(IN) :: majnum, minnum, relnum
INTEGER, INTENT(OUT) :: error
!*****
INTERFACE
@@ -300,16 +294,14 @@ CONTAINS
! PURPOSE
! Garbage collects on all free-lists of all types.
!
-! OUTPUTS
-! error - error code
-! Success: 0
-! Failure: -1
+! Outputs:
+! error - Returns 0 if successful and -1 if fails
!
! AUTHOR
! Elena Pourmal
! September 24, 2002
!
-! SOURCE
+! Fortran90 Interface:
SUBROUTINE h5garbage_collect_f(error)
USE H5GLOBAL
IMPLICIT NONE
@@ -334,16 +326,14 @@ CONTAINS
! PURPOSE
! Instructs library not to install atexit cleanup routine.
!
-! OUTPUTS
-! error - error code
-! Success: 0
-! Failure: -1
+! Outputs:
+! error - Returns 0 if successful and -1 if fails
!
! AUTHOR
! Elena Pourmal
! September 24, 2002
!
-! SOURCE
+! Fortran90 Interface:
SUBROUTINE h5dont_atexit_f(error)
USE H5GLOBAL
IMPLICIT NONE
@@ -369,19 +359,19 @@ CONTAINS
! PURPOSE
! Converts the KIND to the correct HDF type
!
-! INPUTS
+! Inputs:
! kind - Fortran KIND parameter
! flag - whether KIND is of type INTEGER or REAL:
! H5_INTEGER_KIND - integer
! H5_REAL_KIND - real
-! OUTPUTS
+! Outputs:
! h5_type - returns the type
!
! AUTHOR
! M. Scot Breitenfeld
-! Augest 25, 2008
+! August 25, 2008
!
-! SOURCE
+! Fortran90 Interface:
INTEGER(HID_T) FUNCTION h5kind_to_type(kind, flag) RESULT(h5_type)
USE H5GLOBAL
IMPLICIT NONE
diff --git a/fortran/src/H5f90proto.h b/fortran/src/H5f90proto.h
index c9319d5..89957a4 100644
--- a/fortran/src/H5f90proto.h
+++ b/fortran/src/H5f90proto.h
@@ -27,6 +27,57 @@ H5_FCDLL void HD5packFstring(char *src, char *dest, size_t len);
#endif /*H5_VMS*/
/*
+ * Storage info struct used by H5O_info_t and H5F_info_t
+ * interoperable with Fortran.
+ */
+typedef struct H5_ih_info_t_f {
+ hsize_t index_size; /* btree and/or list */
+ hsize_t heap_size;
+} H5_ih_info_t_f;
+
+/* Information struct for object header metadata (for H5Oget_info/H5Oget_info_by_name/H5Oget_info_by_idx)
+ * interoperable with Fortran.
+ */
+typedef struct H5O_hdr_info_t_f {
+ int_f version; /* Version number of header format in file */
+ int_f nmesgs; /* Number of object header messages */
+ int_f nchunks; /* Number of object header chunks */
+ int_f flags; /* Object header status flags */
+ struct {
+ hsize_t total; /* Total space for storing object header in file */
+ hsize_t meta; /* Space within header for object header metadata information */
+ hsize_t mesg; /* Space within header for actual message information */
+ hsize_t free; /* Free space within object header */
+ } space;
+ struct {
+ uint64_t present; /* Flags to indicate presence of message type in header */
+ uint64_t shared; /* Flags to indicate message type is shared in header */
+ } mesg;
+} H5O_hdr_info_t_f;
+
+/* Information struct for object (for H5Oget_info/H5Oget_info_by_name/H5Oget_info_by_idx)
+ * interoperable with Fortran.
+ */
+typedef struct H5O_info_t_f {
+ unsigned long fileno; /* File number that object is located in */
+ haddr_t_f addr; /* Object address in file */
+ int_f type; /* Basic object type (group, dataset, etc.) */
+ int_f rc; /* Reference count of object */
+ int_f atime[8]; /* Access time */
+ int_f mtime[8]; /* Modification time */
+ int_f ctime[8]; /* Change time */
+ int_f btime[8]; /* Birth time */
+ hsize_t num_attrs; /* # of attributes attached to object */
+ H5O_hdr_info_t_f hdr; /* Object header information */
+ /* Extra metadata storage for obj & attributes */
+ struct {
+ H5_ih_info_t_f obj; /* v1/v2 B-tree & local/fractal heap for groups, B-tree for chunked datasets */
+ H5_ih_info_t_f attr; /* v2 B-tree & heap for attributes */
+ } meta_size;
+} H5O_info_t_f;
+
+
+/*
* Functions from H5Ff.c
*/
#define nh5fcreate_c H5_FC_FUNC_(h5fcreate_c, H5FCREATE_C)
@@ -766,7 +817,7 @@ H5_FCDLL int_f nh5olink_c (hid_t_f *object_id, hid_t_f *new_loc_id, _fcd name, s
hid_t_f *lcpl_id, hid_t_f *lapl_id);
H5_FCDLL int_f nh5ovisit_c (hid_t_f *group_id, int_f *index_type, int_f *order, H5O_iterate_t op, void *op_data);
H5_FCDLL int_f nh5oget_info_by_name_c (hid_t_f *loc_id, _fcd name, size_t_f *namelen,hid_t_f *lapl_id,
- H5O_info_t *object_info);
+ H5O_info_t_f *object_info);
/*
* Functions from H5Pf.c
*/
diff --git a/fortran/test/tH5L_F03.f90 b/fortran/test/tH5L_F03.f90
index 616734d..f71f450 100644
--- a/fortran/test/tH5L_F03.f90
+++ b/fortran/test/tH5L_F03.f90
@@ -51,19 +51,6 @@ MODULE liter_cb_mod
INTEGER(c_int) :: command ! The TYPE of RETURN value
END TYPE iter_info
- 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
-
CONTAINS
!***************************************************************