Skip to content

Commit

Permalink
H5Eget_auto2_f implement
Browse files Browse the repository at this point in the history
  • Loading branch information
brtnfld committed Apr 12, 2024
1 parent 8642ed4 commit 10ef487
Show file tree
Hide file tree
Showing 3 changed files with 50 additions and 0 deletions.
40 changes: 40 additions & 0 deletions fortran/src/H5Eff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -273,6 +273,46 @@ END SUBROUTINE h5eset_auto_f
!>
!! \ingroup FH5E
!!
!! \brief Returns the settings for the automatic error stack traversal function and its data.
!!
!! \param estack_id Error stack identifier.
!! \param func The function currently set to be called upon an error condition.
!! \param client_data Data currently set to be passed to the error function.
!! \param hdferr \fortran_error
!!
!! See C API: @ref H5Eget_auto2()
!!
SUBROUTINE h5eget_auto_f(estack_id, hdferr, func, client_data)
USE, INTRINSIC :: ISO_C_BINDING, ONLY : C_PTR, C_FUNPTR
INTEGER(HID_T), INTENT(IN) :: estack_id
INTEGER , INTENT(OUT) :: hdferr
TYPE(C_FUNPTR), OPTIONAL :: func
TYPE(C_PTR) , OPTIONAL :: client_data
TYPE(C_FUNPTR) :: func_default
TYPE(C_PTR) :: client_data_default
INTERFACE
INTEGER FUNCTION H5Eget_auto2(estack_id, func, client_data) &
BIND(C, NAME='H5Eget_auto2')
IMPORT :: c_ptr, c_funptr
IMPORT :: HID_T
INTEGER(HID_T), VALUE :: estack_id
TYPE(C_FUNPTR), VALUE :: func
TYPE(C_PTR) , VALUE :: client_data
END FUNCTION H5Eget_auto2
END INTERFACE

func_default = C_NULL_FUNPTR
client_data_default = C_NULL_PTR

IF(PRESENT(func)) func_default = func
IF(PRESENT(client_data)) client_data_default = client_data

hdferr = INT(H5Eget_auto2(estack_id, func_default, client_data_default))
END SUBROUTINE h5eget_auto_f

!>
!! \ingroup FH5E
!!
!! \brief Pushes a new error record onto an error stack.
!!
!! \param err_stack Error stack identifier. If the identifier is H5E_DEFAULT_F, the error
Expand Down
1 change: 1 addition & 0 deletions fortran/src/hdf5_fortrandll.def.in
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,7 @@ H5E_mp_H5EPRINT2_F
H5E_mp_H5EGET_MAJOR_F
H5E_mp_H5EGET_MINOR_F
H5E_mp_H5ESET_AUTO_F
H5E_mp_H5EGET_AUTO_F
H5E_mp_H5EREGISTER_CLASS_F
H5E_mp_H5EUNREGISTER_CLASS_F
H5E_mp_H5ECREATE_MSG_F
Expand Down
9 changes: 9 additions & 0 deletions fortran/test/tH5E_F03.F90
Original file line number Diff line number Diff line change
Expand Up @@ -190,7 +190,9 @@ SUBROUTINE test_error(total_error)
INTEGER, TARGET :: my_hdf5_error_handler_data
INTEGER, TARGET :: iunit
TYPE(C_PTR) :: f_ptr
TYPE(C_PTR) :: f_ptr_ret
TYPE(C_FUNPTR) :: func
TYPE(C_FUNPTR) :: func_ret
CHARACTER(LEN=180) :: chr180
INTEGER :: idx
INTEGER(HID_T) :: fapl
Expand All @@ -215,6 +217,13 @@ SUBROUTINE test_error(total_error)
CALL H5Eset_auto_f(1, error, H5E_DEFAULT_F, func, f_ptr)
CALL check("H5Eset_auto_f", error, total_error)

CALL H5Eget_auto_f(H5E_DEFAULT_F, error, func_ret)
CALL check("H5Eget_auto_f", error, total_error)

! IF( func_ret .EQ. C_NULL_FUNPTR)THEN
! CALL check("H5Eget_auto_f", -1, total_error)
! ENDIF

! If a fapl is not created, then the test will fail when using
! check-passthrough-vol because the callback function is called twice, gh #4137.
CALL h5pcreate_f(H5P_DATASET_ACCESS_F, fapl, error)
Expand Down

0 comments on commit 10ef487

Please sign in to comment.