Skip to content

Commit

Permalink
Added new Fortran API wrappers (#3511)
Browse files Browse the repository at this point in the history
* Added new wrappers for
h5get_free_list_sizes_f
H5Sselect_intersect_block_f
H5Sselect_shape_same_f
h5pget_no_selection_io_cause_f
h5pget_mpio_no_collective_cause_f
H5Lvisit_by_name_f
H5Lvisit_f
H5Fget_info_f
h5dwrite_chunk_f
h5dread_chunk_f

* added h5pget_file_space_page_size_f, h5pset_file_space_page_size_f, h5pget_file_space_strategy_f, h5pset_file_space_strategy_f, h5info tests

* added fortran tests

* Update tH5F.F90
  • Loading branch information
brtnfld authored Sep 7, 2023
1 parent 8253ab9 commit 08e115b
Show file tree
Hide file tree
Showing 32 changed files with 2,882 additions and 1,403 deletions.
140 changes: 140 additions & 0 deletions fortran/src/H5Dff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2282,6 +2282,8 @@ END SUBROUTINE h5dfill_char
!! \param buf Buffer with data to be written to the file.
!! \param hdferr \fortran_error
!! \param xfer_prp Identifier of a transfer property list for this I/O operation.
!!
!! See C API: @ref H5Dread_multi()
!!
SUBROUTINE h5dread_multi_f(count, dset_id, mem_type_id, mem_space_id, file_space_id, buf, hdferr, xfer_prp)
IMPLICIT NONE
Expand Down Expand Up @@ -2320,6 +2322,7 @@ END FUNCTION H5Dread_multi
hdferr = H5Dread_multi(count, dset_id, mem_type_id, mem_space_id, file_space_id, xfer_prp_default, buf)

END SUBROUTINE h5dread_multi_f

!>
!! \ingroup FH5D
!!
Expand All @@ -2333,6 +2336,8 @@ END SUBROUTINE h5dread_multi_f
!! \param buf Buffer with data to be written to the file.
!! \param hdferr \fortran_error
!! \param xfer_prp Identifier of a transfer property list for this I/O operation.
!!
!! See C API: @ref H5Dwrite_multi()
!!
SUBROUTINE h5dwrite_multi_f(count, dset_id, mem_type_id, mem_space_id, file_space_id, buf, hdferr, xfer_prp)
IMPLICIT NONE
Expand Down Expand Up @@ -2372,6 +2377,141 @@ END FUNCTION H5Dwrite_multi

END SUBROUTINE h5dwrite_multi_f

!>
!! \ingroup FH5D
!!
!! \brief Reads a raw data chunk directly from a dataset in a file into a buffer.
!!
!! \param dset_id Identifier of the dataset to read from
!! \param offset Logical position of the chunk's first element in the dataspace, \Bold{0-based indices}
!! \param filters Mask for identifying the filters in use
!! \param buf Buffer containing data to be read from the chunk
!! \param hdferr \fortran_error
!! \param dxpl_id Dataset transfer property list identifier
!!
!! See C API: @ref H5Dread_chunk()
!!
SUBROUTINE h5dread_chunk_f(dset_id, offset, filters, buf, hdferr, dxpl_id)
IMPLICIT NONE

INTEGER(HID_T) , INTENT(IN) :: dset_id
INTEGER(HSIZE_T) , INTENT(IN), DIMENSION(:) :: offset
INTEGER(C_INT32_T), INTENT(INOUT) :: filters
TYPE(C_PTR) :: buf
INTEGER , INTENT(OUT) :: hdferr
INTEGER(HID_T) , INTENT(IN), OPTIONAL :: dxpl_id

INTEGER(HID_T) :: dxpl_id_default
INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: offset_c
INTEGER(HSIZE_T) :: i, rank

INTERFACE
INTEGER(C_INT) FUNCTION H5Dread_chunk(dset_id, dxpl_id, offset, filters, buf) &
BIND(C, NAME='H5Dread_chunk')
IMPORT :: SIZE_T, HSIZE_T, HID_T
IMPORT :: C_PTR, C_INT32_T, C_INT
IMPLICIT NONE
INTEGER(HID_T) , VALUE :: dset_id
INTEGER(HID_T) , VALUE :: dxpl_id
INTEGER(HSIZE_T) , DIMENSION(*) :: offset
INTEGER(C_INT32_T) :: filters
TYPE(C_PTR) , VALUE :: buf
END FUNCTION H5Dread_chunk
END INTERFACE

dxpl_id_default = H5P_DEFAULT_F
IF (PRESENT(dxpl_id)) dxpl_id_default = dxpl_id

rank = SIZE(offset, KIND=HSIZE_T)

ALLOCATE(offset_c(rank), STAT=hdferr)
IF (hdferr .NE. 0 ) THEN
hdferr = -1
RETURN
ENDIF

!
! Reverse dimensions due to C-FORTRAN storage order
!
DO i = 1, rank
offset_c(i) = offset(rank - i + 1)
ENDDO

hdferr = INT(H5Dread_chunk(dset_id, dxpl_id_default, offset_c, filters, buf))

DEALLOCATE(offset_c)

END SUBROUTINE h5dread_chunk_f

!>
!! \ingroup FH5D
!!
!! \brief Writes a raw data chunk from a buffer directly to a dataset in a file.
!!
!! \param dset_id Identifier of the dataset to write to
!! \param filters Mask for identifying the filters in use
!! \param offset Logical position of the chunk's first element in the dataspace, \Bold{0-based indices}
!! \param data_size Size of the actual data to be written in bytes
!! \param buf Buffer containing data to be written to the chunk
!! \param hdferr \fortran_error
!! \param dxpl_id Dataset transfer property list identifier
!!
!! See C API: @ref H5Dwrite_chunk()
!!
SUBROUTINE h5dwrite_chunk_f(dset_id, filters, offset, data_size, buf, hdferr, dxpl_id)
IMPLICIT NONE

INTEGER(HID_T) , INTENT(IN) :: dset_id
INTEGER(C_INT32_T), INTENT(IN) :: filters
INTEGER(HSIZE_T) , INTENT(IN), DIMENSION(:) :: offset
INTEGER(SIZE_T) , INTENT(IN) :: data_size
TYPE(C_PTR) :: buf
INTEGER , INTENT(OUT) :: hdferr
INTEGER(HID_T) , INTENT(IN), OPTIONAL :: dxpl_id

INTEGER(HID_T) :: dxpl_id_default
INTEGER(HSIZE_T), DIMENSION(:), ALLOCATABLE :: offset_c
INTEGER(HSIZE_T) :: i, rank

INTERFACE
INTEGER(C_INT) FUNCTION H5Dwrite_chunk(dset_id, dxpl_id, filters, offset, data_size, buf) &
BIND(C, NAME='H5Dwrite_chunk')
IMPORT :: SIZE_T, HSIZE_T, HID_T
IMPORT :: C_PTR, C_INT32_T, C_INT
IMPLICIT NONE
INTEGER(HID_T) , VALUE :: dset_id
INTEGER(HID_T) , VALUE :: dxpl_id
INTEGER(C_INT32_T), VALUE :: filters
INTEGER(HSIZE_T), DIMENSION(*) :: offset
INTEGER(SIZE_T) , VALUE :: data_size
TYPE(C_PTR) , VALUE :: buf
END FUNCTION H5Dwrite_chunk
END INTERFACE

dxpl_id_default = H5P_DEFAULT_F
IF (PRESENT(dxpl_id)) dxpl_id_default = dxpl_id

rank = SIZE(offset, KIND=HSIZE_T)

ALLOCATE(offset_c(rank), STAT=hdferr)
IF (hdferr .NE. 0 ) THEN
hdferr = -1
RETURN
ENDIF

!
! Reverse dimensions due to C-FORTRAN storage order
!
DO i = 1, rank
offset_c(i) = offset(rank - i + 1)
ENDDO

hdferr = INT(H5Dwrite_chunk(dset_id, dxpl_id_default, filters, offset_c, data_size, buf))

DEALLOCATE(offset_c)

END SUBROUTINE h5dwrite_chunk_f

END MODULE H5D


65 changes: 64 additions & 1 deletion fortran/src/H5Fff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,6 @@ MODULE H5F
! Number of objects opened in H5open_f
INTEGER(SIZE_T) :: H5OPEN_NUM_OBJ


#ifndef H5_DOXYGEN
INTERFACE
INTEGER(C_INT) FUNCTION h5fis_accessible(name, &
Expand All @@ -58,6 +57,40 @@ END FUNCTION h5fis_accessible
END INTERFACE
#endif

!> @brief H5F_info_t_super derived type.
TYPE, BIND(C) :: H5F_info_super_t
INTEGER(C_INT) :: version !< Superblock version number
INTEGER(HSIZE_T) :: super_size !< Superblock size
INTEGER(HSIZE_T) :: super_ext_size !< Superblock extension size
END TYPE H5F_info_super_t

!> @brief H5F_info_t_free derived type.
TYPE, BIND(C) :: H5F_info_free_t
INTEGER(C_INT) :: version !< Version # of file free space management
INTEGER(HSIZE_T) :: meta_size !< Free space manager metadata size
INTEGER(HSIZE_T) :: tot_space !< Amount of free space in the file
END TYPE H5F_info_free_t

!> @brief H5_ih_info_t derived type.
TYPE, BIND(C) :: H5_ih_info_t
INTEGER(HSIZE_T) :: heap_size !< Heap size
INTEGER(HSIZE_T) :: index_size !< btree and/or list
END TYPE H5_ih_info_t

!> @brief H5F_info_t_sohm derived type.
TYPE, BIND(C) :: H5F_info_sohm_t
INTEGER(C_INT) :: version !< Version # of shared object header info
INTEGER(HSIZE_T) :: hdr_size !< Shared object header message header size
TYPE(H5_ih_info_t) :: msgs_info !< Shared object header message index & heap size
END TYPE H5F_info_sohm_t

!> @brief h5f_info_t derived type.
TYPE, BIND(C) :: h5f_info_t
TYPE(H5F_info_super_t) :: super
TYPE(H5F_info_free_t) :: free
TYPE(H5F_info_sohm_t) :: sohm
END TYPE h5f_info_t

CONTAINS
!>
!! \ingroup FH5F
Expand Down Expand Up @@ -1093,5 +1126,35 @@ END FUNCTION h5fset_dset_no_attrs_hint_c

END SUBROUTINE h5fset_dset_no_attrs_hint_f

!>
!! \ingroup FH5F
!!
!! \brief Retrieves global file information
!!
!! \param obj_id Object identifier. The identifier may be that of a file, group, dataset, named datatype, or attribute.
!! \param file_info Buffer for global file information
!! \param hdferr \fortran_error
!!
!! See C API: @ref H5Fget_info2()
!!
SUBROUTINE H5Fget_info_f(obj_id, file_info, hdferr)
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: obj_id
TYPE(H5F_INFO_T), INTENT(OUT) :: file_info
INTEGER , INTENT(OUT) :: hdferr

INTERFACE
INTEGER(C_INT) FUNCTION H5Fget_info(obj_id, file_info) BIND(C, NAME='H5Fget_info2')
IMPORT :: HID_T, C_INT, H5F_INFO_T
IMPLICIT NONE
INTEGER(HID_T) , VALUE :: obj_id
TYPE(H5F_INFO_T), VALUE :: file_info
END FUNCTION H5Fget_info
END INTERFACE

hdferr = INT(H5Fget_info(obj_id, file_info))

END SUBROUTINE H5Fget_info_f

END MODULE H5F

106 changes: 103 additions & 3 deletions fortran/src/H5Lff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -748,10 +748,10 @@ END FUNCTION H5Lexists
link_exists_c = H5Lexists(loc_id, c_name, lapl_id_default)

link_exists = .FALSE.
IF(link_exists_c.GT.0) link_exists = .TRUE.
IF(link_exists_c.GT.0_C_INT) link_exists = .TRUE.

hdferr = 0
IF(link_exists_c.LT.0) hdferr = -1
IF(link_exists_c.LT.0_C_INT) hdferr = -1

END SUBROUTINE h5lexists_f

Expand Down Expand Up @@ -1462,7 +1462,7 @@ END SUBROUTINE h5literate_async_f
!!
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, ONLY : C_PTR, C_FUNPTR

IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: loc_id
CHARACTER(LEN=*), INTENT(IN) :: group_name
Expand Down Expand Up @@ -1509,4 +1509,104 @@ INTEGER FUNCTION h5literate_by_name_c(loc_id, name, namelen, index_type, order,&

END SUBROUTINE h5literate_by_name_f

!>
!! \ingroup FH5L
!!
!! \brief Recursively visits all links starting from a specified group.
!!
!! \param grp_id Group identifier
!! \param idx_type Index type
!! \param order Iteration order
!! \param op Callback function
!! \param op_data User-defined callback function context
!! \param hdferr \fortran_error
!!
!! See C API: @ref H5Lvisit2()
!!
SUBROUTINE H5Lvisit_f(grp_id, idx_type, order, op, op_data, hdferr)

IMPLICIT NONE

INTEGER(hid_t), INTENT(IN) :: grp_id
INTEGER , INTENT(IN) :: idx_type
INTEGER , INTENT(IN) :: order
TYPE(C_FUNPTR) :: op
TYPE(C_PTR) :: op_data
INTEGER , INTENT(OUT) :: hdferr

INTERFACE
INTEGER(C_INT) FUNCTION H5Lvisit(grp_id, idx_type, order, op, op_data) BIND(C, NAME='H5Lvisit2')
IMPORT :: c_char, c_int, c_ptr, c_funptr
IMPORT :: HID_T, SIZE_T, HSIZE_T
IMPLICIT NONE
INTEGER(hid_t), VALUE :: grp_id
INTEGER , VALUE :: idx_type
INTEGER , VALUE :: order
TYPE(C_FUNPTR), VALUE :: op
TYPE(C_PTR) , VALUE :: op_data
END FUNCTION H5Lvisit
END INTERFACE

hdferr = INT(H5Lvisit(grp_id, INT(idx_type, C_INT), INT(order, C_INT), op, op_data))

END SUBROUTINE H5Lvisit_f

!>
!! \ingroup FH5L
!!
!! \brief Recursively visits all links starting from a specified group.
!!
!! \param loc_id Location identifier
!! \param group_name Group name
!! \param idx_type Index type
!! \param order Iteration order
!! \param op Callback function
!! \param op_data User-defined callback function context
!! \param hdferr \fortran_error
!! \param lapl_id Link access property list
!!
!!
!! See C API: @ref H5Lvisit_by_name2()
!!
SUBROUTINE H5Lvisit_by_name_f(loc_id, group_name, idx_type, order, op, op_data, hdferr, lapl_id)

IMPLICIT NONE

INTEGER(hid_t), INTENT(IN) :: loc_id
CHARACTER(LEN=*), INTENT(IN) :: group_name
INTEGER , INTENT(IN) :: idx_type
INTEGER , INTENT(IN) :: order
TYPE(C_FUNPTR) :: op
TYPE(C_PTR) :: op_data
INTEGER , INTENT(OUT) :: hdferr
INTEGER(HID_T), INTENT(IN), OPTIONAL :: lapl_id

INTEGER(HID_T) :: lapl_id_default
CHARACTER(LEN=LEN_TRIM(group_name)+1,KIND=C_CHAR) :: c_name

INTERFACE
INTEGER(C_INT) FUNCTION H5Lvisit_by_name(loc_id, group_name, idx_type, order, op, op_data, lapl_id_default) &
BIND(C, NAME='H5Lvisit_by_name2')
IMPORT :: C_CHAR, C_INT, C_PTR, C_FUNPTR
IMPORT :: HID_T, SIZE_T, HSIZE_T
IMPLICIT NONE
INTEGER(hid_t), VALUE :: loc_id
CHARACTER(KIND=C_CHAR), DIMENSION(*) :: group_name
INTEGER , VALUE :: idx_type
INTEGER , VALUE :: order
TYPE(C_FUNPTR), VALUE :: op
TYPE(C_PTR) , VALUE :: op_data
INTEGER(HID_T), VALUE :: lapl_id_default
END FUNCTION H5Lvisit_by_name
END INTERFACE

c_name = TRIM(group_name)//C_NULL_CHAR

lapl_id_default = H5P_DEFAULT_F
IF(PRESENT(lapl_id)) lapl_id_default = lapl_id

hdferr = INT(H5Lvisit_by_name(loc_id, c_name, INT(idx_type, C_INT), INT(order, C_INT), op, op_data, lapl_id_default))

END SUBROUTINE H5Lvisit_by_name_f

END MODULE H5L
Loading

0 comments on commit 08e115b

Please sign in to comment.