Skip to content

Commit

Permalink
updates to H5R APIs
Browse files Browse the repository at this point in the history
  • Loading branch information
brtnfld committed Apr 18, 2024
1 parent f480022 commit 9b7d459
Show file tree
Hide file tree
Showing 8 changed files with 320 additions and 12 deletions.
2 changes: 1 addition & 1 deletion configure.ac
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
## ----------------------------------------------------------------------
## Initialize configure.
##
AC_PREREQ([2.71])
AC_PREREQ([2.69])

## AC_INIT takes the name of the package, the version number, and an
## email address to report bugs. AC_CONFIG_SRCDIR takes a unique file
Expand Down
79 changes: 73 additions & 6 deletions fortran/src/H5Rff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ MODULE H5R
END TYPE hdset_reg_ref_t_f03

TYPE, BIND(C) :: H5R_ref_t
INTEGER(C_INT8_T), DIMENSION(1:H5R_REF_BUF_SIZE_F) :: __data
INTEGER(C_INT8_T), DIMENSION(1:H5R_REF_BUF_SIZE_F) :: data
INTEGER(C_INT64_T) :: align
END TYPE

Expand Down Expand Up @@ -655,7 +655,7 @@ END SUBROUTINE h5rget_obj_type_f
!! \param oapl_id Object access property list identifier
!! \param hdferr \fortran_error
!!
!! See C API: @ref H5Ropen_object()
!! See C API: @ref H5Ropen_object()
!!
SUBROUTINE h5ropen_object_f(ref_ptr, rapl_id, oapl_id, hdferr)

Expand All @@ -664,22 +664,89 @@ SUBROUTINE h5ropen_object_f(ref_ptr, rapl_id, oapl_id, hdferr)
TYPE(C_PTR) :: ref_ptr
INTEGER(HID_T), INTENT(IN) :: rapl_id
INTEGER(HID_T), INTENT(IN) :: oapl_id
INTEGER, INTENT(OUT) :: hdferr
INTEGER, INTENT(OUT) :: hdferr

INTERFACE
INTEGER(C_INT) FUNCTION H5Ropen_object_f(ref_ptr, rapl_id, oapl_id) &
INTEGER(C_INT) FUNCTION H5Ropen_object(ref_ptr, rapl_id, oapl_id) &
BIND(C, NAME='H5Ropen_object')
IMPORT :: C_PTR, C_INT
IMPORT :: HID_T
IMPLICIT NONE
TYPE(C_PTR) , VALUE :: ref_ptr
INTEGER(HID_T), VALUE :: rapl_id
INTEGER(HID_T), VALUE :: oapl_id
END FUNCTION H5Ropen_object_f
END FUNCTION H5Ropen_object
END INTERFACE

hdferr = INT(H5Ropen_object_f(ref_ptr, rapl_id, oapl_id))
hdferr = INT(H5Ropen_object(ref_ptr, rapl_id, oapl_id))

END SUBROUTINE h5ropen_object_f

!>
!! \ingroup FH5R
!!
!! \brief Copies an existing reference.
!!
!! \param src_ref_ptr Pointer to reference to copy, of TYPE(H5R_ref_t)
!! \param dst_ref_ptr Pointer to output reference, of TYPE(H5R_ref_t)
!! \param hdferr \fortran_error
!!
!! See C API: @ref H5Rcopy()
!!
SUBROUTINE h5rcopy_f(src_ref_ptr, dst_ref_ptr, hdferr)

IMPLICIT NONE

TYPE(C_PTR) :: src_ref_ptr
TYPE(C_PTR) :: dst_ref_ptr
INTEGER, INTENT(OUT) :: hdferr

INTERFACE
INTEGER(C_INT) FUNCTION H5Rcopy(src_ref_ptr, dst_ref_ptr) &
BIND(C, NAME='H5Rcopy')
IMPORT :: C_PTR, C_INT
IMPLICIT NONE
TYPE(C_PTR), VALUE :: src_ref_ptr
TYPE(C_PTR), VALUE :: dst_ref_ptr
END FUNCTION H5Rcopy
END INTERFACE

hdferr = INT(H5Rcopy(src_ref_ptr, dst_ref_ptr))

END SUBROUTINE h5rcopy_f

!>
!! \ingroup FH5R
!!
!! \brief Retrieves the type of a reference.
!!
!! \param ref_ptr Pointer to reference to copy, of TYPE(H5R_ref_t)
!! \param hdferr \fortran_error
!!
!! See C API: @ref H5Rget_type()
!!
SUBROUTINE h5rget_type_f(ref_ptr, ref_type, hdferr)

IMPLICIT NONE

TYPE(C_PTR) :: ref_ptr
INTEGER, INTENT(OUT) :: ref_type
INTEGER, INTENT(OUT) :: hdferr

INTERFACE
INTEGER(C_INT) FUNCTION H5Rget_type(ref_ptr) &
BIND(C, NAME='H5Rget_type')
IMPORT :: C_PTR, C_INT
IMPLICIT NONE
TYPE(C_PTR) :: ref_ptr
END FUNCTION H5Rget_type
END INTERFACE

ref_type = INT(H5Rget_type(ref_ptr))

hdferr = 0
IF(ref_type .EQ. H5R_BADTYPE_F) hdferr = -1

END SUBROUTINE h5rget_type_f

END MODULE H5R
7 changes: 7 additions & 0 deletions fortran/src/H5_f.c
Original file line number Diff line number Diff line change
Expand Up @@ -766,6 +766,13 @@ h5init_flags_c(int_f *h5d_flags, size_t_f *h5d_size_flags, int_f *h5e_flags, hid
*/
h5r_flags[0] = (int_f)H5R_OBJECT;
h5r_flags[1] = (int_f)H5R_DATASET_REGION;
h5r_flags[2] = (int_f)H5R_BADTYPE;
h5r_flags[3] = (int_f)H5R_OBJECT1;
h5r_flags[4] = (int_f)H5R_DATASET_REGION1;
h5r_flags[5] = (int_f)H5R_OBJECT2;
h5r_flags[6] = (int_f)H5R_DATASET_REGION2;
h5r_flags[7] = (int_f)H5R_ATTR;
h5r_flags[8] = (int_f)H5R_MAXTYPE;

/*
* H5S flags
Expand Down
13 changes: 10 additions & 3 deletions fortran/src/H5_ff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ MODULE H5LIB
!
! H5R flags declaration
!
INTEGER, PARAMETER :: H5R_FLAGS_LEN = 2
INTEGER, PARAMETER :: H5R_FLAGS_LEN = 9
INTEGER, DIMENSION(1:H5R_FLAGS_LEN) :: H5R_flags
!
! H5S flags declaration
Expand Down Expand Up @@ -627,8 +627,15 @@ END FUNCTION h5init1_flags_c
!
! H5R flags
!
H5R_OBJECT_F = H5R_flags(1)
H5R_DATASET_REGION_F = H5R_flags(2)
H5R_OBJECT_F = H5R_flags(1)
H5R_DATASET_REGION_F = H5R_flags(2)
H5R_BADTYPE_F = H5R_flags(3)
H5R_OBJECT1_F = H5R_flags(4)
H5R_DATASET_REGION1_F = H5R_flags(5)
H5R_OBJECT2_F = H5R_flags(6)
H5R_DATASET_REGION2_F = H5R_flags(7)
H5R_ATTR_F = H5R_flags(8)
H5R_MAXTYPE_F = H5R_flags(9)
!
! H5S flags
!
Expand Down
18 changes: 16 additions & 2 deletions fortran/src/H5f90global.F90
Original file line number Diff line number Diff line change
Expand Up @@ -762,11 +762,25 @@ MODULE H5GLOBAL
!DEC$if defined(BUILD_HDF5_DLL)
!DEC$ATTRIBUTES DLLEXPORT :: H5R_OBJECT_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_DATASET_REGION_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_BADTYPE_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_OBJECT1_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_DATASET_REGION1_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_OBJECT2_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_DATASET_REGION2_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_ATTR_F
!DEC$ATTRIBUTES DLLEXPORT :: H5R_MAXTYPE_F
!DEC$endif
!> \addtogroup FH5R
!> @{
INTEGER :: H5R_OBJECT_F !< H5R_OBJECT
INTEGER :: H5R_DATASET_REGION_F !< H5R_DATASET_REGION
INTEGER :: H5R_OBJECT_F !< H5R_OBJECT
INTEGER :: H5R_DATASET_REGION_F !< H5R_DATASET_REGION
INTEGER :: H5R_BADTYPE_F !< H5R_BADTYPE
INTEGER :: H5R_OBJECT1_F !< H5R_OBJECT1
INTEGER :: H5R_DATASET_REGION1_F !< H5R_DATASET_REGION1
INTEGER :: H5R_OBJECT2_F !< H5R_OBJECT2
INTEGER :: H5R_DATASET_REGION2_F !< H5R_DATASET_REGION2
INTEGER :: H5R_ATTR_F !< H5R_ATTR
INTEGER :: H5R_MAXTYPE_F !< H5R_MAXTYPE
!> @}
!
! H5S flags declaration
Expand Down
3 changes: 3 additions & 0 deletions fortran/src/hdf5_fortrandll.def.in
Original file line number Diff line number Diff line change
Expand Up @@ -471,6 +471,9 @@ H5R_mp_H5RCREATE_PTR_F
H5R_mp_H5RDEREFERENCE_PTR_F
H5R_mp_H5RGET_NAME_PTR_F
H5R_mp_H5RGET_OBJ_TYPE_F
H5R_mp_H5ROPEN_OBJECT_F
H5R_mp_H5RCOPY_F
H5R_mp_H5RGET_TYPE_F
; H5S
H5S_mp_H5SCREATE_SIMPLE_F
H5S_mp_H5SCLOSE_F
Expand Down
5 changes: 5 additions & 0 deletions fortran/test/fortranlib_test.F90
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,10 @@ PROGRAM fortranlibtest
! 'Testing REFERENCE Interface '
! '========================================='

ret_total_error = 0
CALL genreftest(cleanup, ret_total_error)
CALL write_test_status(ret_total_error, ' General References test', total_error)

ret_total_error = 0
CALL refobjtest(cleanup, ret_total_error)
CALL write_test_status(ret_total_error, ' Reference to object test', total_error)
Expand All @@ -149,6 +153,7 @@ PROGRAM fortranlibtest
CALL refregtest(cleanup, ret_total_error)
CALL write_test_status(ret_total_error, ' Reference to dataset region test', total_error)


!
! '========================================='
! 'Testing selection functionalities '
Expand Down
Loading

0 comments on commit 9b7d459

Please sign in to comment.