Skip to content

Commit

Permalink
Remove H5Tdecode wrapper
Browse files Browse the repository at this point in the history
  • Loading branch information
mattjala committed Jan 15, 2025
1 parent 9e87628 commit 10c1cf4
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 54 deletions.
42 changes: 0 additions & 42 deletions fortran/src/H5Tf.c
Original file line number Diff line number Diff line change
Expand Up @@ -1890,48 +1890,6 @@ h5tcommitted_c(hid_t_f *dtype_id)
return ret_value;
}

/****if* H5Tf/h5tdecode_c
* NAME
* h5tdecode_c
* PURPOSE
* Call H5Tdecode
* INPUTS
*
* buf - Buffer for the data space object to be decoded.
* buf_size - Size of the buffer
* OUTPUTS
*
* obj_id - Object_id (non-negative)
*
* RETURNS
* 0 on success, -1 on failure
* SOURCE
*/

int_f
h5tdecode_c(_fcd buf, size_t_f buf_size, hid_t_f *obj_id)
/******/
{
int ret_value = -1;
unsigned char *c_buf = NULL; /* Buffer to hold C string */
hid_t c_obj_id;

/*
* Call H5Tdecode function.
*/

c_buf = (unsigned char *)buf;

c_obj_id = H5Tdecode2(c_buf, buf_size);
if (c_obj_id < 0)
return ret_value;

*obj_id = (hid_t_f)c_obj_id;
ret_value = 0;

return ret_value;
}

/****if* H5Tf/h5tencode_c
* NAME
* h5tencode_c
Expand Down
27 changes: 16 additions & 11 deletions fortran/src/H5Tff.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1876,19 +1876,22 @@ SUBROUTINE h5tdecode_with_size_f(buf, buf_size, obj_id, hdferr)
INTEGER(HID_T), INTENT(OUT) :: obj_id
INTEGER, INTENT(OUT) :: hdferr
INTERFACE
INTEGER FUNCTION h5tdecode_c(buf, buf_size, obj_id) BIND(C,NAME='h5tdecode_c')
INTEGER(HID_T) FUNCTION H5Tdecode2(buf, buf_size) BIND(C,NAME='H5Tdecode2')
IMPORT :: C_CHAR
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: buf
INTEGER(SIZE_T), INTENT(IN) :: buf_size
INTEGER(HID_T), INTENT(OUT) :: obj_id
END FUNCTION h5tdecode_c
END FUNCTION H5Tdecode2
END INTERFACE

hdferr = h5tdecode_c(buf, buf_size, obj_id)
END SUBROUTINE h5tdecode_with_size_f
obj_id = H5Tdecode2(buf, buf_size)

IF(obj_id.LT.0)THEN
hdferr = -1
ENDIF

END SUBROUTINE h5tdecode_with_size_f
!>
!! \ingroup FH5T
!!
Expand All @@ -1907,21 +1910,23 @@ SUBROUTINE h5tdecode_auto_size_f(buf, obj_id, hdferr)
INTEGER, INTENT(OUT) :: hdferr
INTEGER(SIZE_T) :: buf_size
INTERFACE
INTEGER FUNCTION h5tdecode_c(buf, buf_size, obj_id) BIND(C,NAME='h5tdecode_c')
INTEGER(HID_T) FUNCTION H5Tdecode2(buf, buf_size) BIND(C,NAME='H5Tdecode2')
IMPORT :: C_CHAR
IMPORT :: HID_T, SIZE_T
IMPLICIT NONE
CHARACTER(KIND=C_CHAR), DIMENSION(*), INTENT(IN) :: buf
INTEGER(SIZE_T), INTENT(IN) :: buf_size
INTEGER(HID_T), INTENT(OUT) :: obj_id
END FUNCTION h5tdecode_c
END FUNCTION H5Tdecode2
END INTERFACE

buf_size = LEN(buf)
hdferr = h5tdecode_c(buf, buf_size, obj_id)
END SUBROUTINE h5tdecode_auto_size_f
obj_id = H5Tdecode2(buf, buf_size)

!>
IF(obj_id.LT.0)THEN
hdferr = -1
ENDIF

END SUBROUTINE h5tdecode_auto_size_f!>
!! \ingroup FH5T
!!
!! \brief Encode a data type object description into a binary buffer.
Expand Down
1 change: 0 additions & 1 deletion fortran/src/H5f90proto.h
Original file line number Diff line number Diff line change
Expand Up @@ -327,7 +327,6 @@ H5_FCDLL int_f h5tvlen_create_c(hid_t_f *type_id, hid_t_f *vltype_id);
H5_FCDLL int_f h5tis_variable_str_c(hid_t_f *type_id, int_f *flag);
H5_FCDLL int_f h5tget_member_class_c(hid_t_f *type_id, int_f *member_no, int_f *cls);
H5_FCDLL int_f h5tcommit_anon_c(hid_t_f *loc_id, hid_t_f *dtype_id, hid_t_f *tcpl_id, hid_t_f *tapl_id);
H5_FCDLL int_f h5tdecode_c(_fcd buf, size_t_f buf_size, hid_t_f *obj_id);
H5_FCDLL int_f h5tencode_c(_fcd buf, hid_t_f *obj_id, size_t_f *nalloc);
H5_FCDLL int_f h5tget_create_plist_c(hid_t_f *dtype_id, hid_t_f *dtpl_id);
H5_FCDLL int_f h5tcompiler_conv_c(hid_t_f *src_id, hid_t_f *dst_id, int_f *c_flag);
Expand Down

0 comments on commit 10c1cf4

Please sign in to comment.