added H5Pset_vol

This commit is contained in:
M. Scot Breitenfeld 2019-05-22 14:09:17 -05:00
parent 4673a34825
commit 2c79243111
3 changed files with 184 additions and 0 deletions

View File

@ -8114,5 +8114,90 @@ END SUBROUTINE h5pget_virtual_dsetname_f
END SUBROUTINE h5pset_dset_no_attrs_hint_f
!****s* H5P/H5Pset_vol_f
!
! NAME
! H5Pset_vol_f
!
! PURPOSE
! Set the file VOL connector (VOL_ID) for a file access
! property list (PLIST_ID)
! INPUTS
! plist_id - access property list identifier.
! new_vol_id - VOL connector id.
! new_vol_info - VOL connector info.
!
! OUTPUTS
! hdferr - error code:
! 0 on success and -1 on failure
!
! AUTHOR
! M.S. Breitenfeld
! May 2019
!
! Fortran Interface:
SUBROUTINE h5pset_vol_f(plist_id, new_vol_id, new_vol_info, hdferr)
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: plist_id
INTEGER(HID_T) , INTENT(IN) :: new_vol_id
TYPE(C_PTR) , INTENT(IN) :: new_vol_info
INTEGER , INTENT(OUT) :: hdferr
!*****
INTERFACE
INTEGER FUNCTION h5pset_vol(plist_id, new_vol_id, new_vol_info) BIND(C, NAME='H5Pset_vol')
IMPORT :: HID_T, C_PTR
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN), VALUE :: plist_id
INTEGER(HID_T), INTENT(IN), VALUE :: new_vol_id
TYPE(C_PTR) , INTENT(IN), VALUE :: new_vol_info
END FUNCTION h5pset_vol
END INTERFACE
hdferr = INT(h5pset_vol(plist_id, new_vol_id, new_vol_info))
END SUBROUTINE h5pset_vol_f
!****s* H5P/H5Pget_vol_id_f
!
! NAME
! H5Pget_vol_id_f
!
! PURPOSE
! Get the file VOL connector (VOL_ID) for a file access
! property list (PLIST_ID)
! INPUTS
! plist_id - access property list identifier.
!
! OUTPUTS
! vol_id - VOL connector id.
! hdferr - error code:
! 0 on success and -1 on failure
!
! AUTHOR
! M.S. Breitenfeld
! May 2019
!
! Fortran Interface:
SUBROUTINE h5pget_vol_id_f(plist_id, vol_id, hdferr)
IMPLICIT NONE
INTEGER(HID_T) , INTENT(IN) :: plist_id
INTEGER(HID_T) , INTENT(OUT) :: vol_id
INTEGER , INTENT(OUT) :: hdferr
!*****
INTERFACE
INTEGER FUNCTION h5pget_vol_id(plist_id, vol_id) BIND(C, NAME='H5Pget_vol_id')
IMPORT :: HID_T, C_PTR
IMPLICIT NONE
INTEGER(HID_T), INTENT(IN), VALUE :: plist_id
INTEGER(HID_T), INTENT(OUT) :: vol_id
END FUNCTION h5pget_vol_id
END INTERFACE
hdferr = INT(h5pget_vol_id(plist_id, vol_id))
END SUBROUTINE h5pget_vol_id_f
END MODULE H5P

View File

@ -335,6 +335,8 @@ H5P_mp_H5PGET_VIRTUAL_FILENAME_F
H5P_mp_H5PGET_VIRTUAL_DSETNAME_F
H5P_mp_H5PGET_DSET_NO_ATTRS_HINT_F
H5P_mp_H5PSET_DSET_NO_ATTRS_HINT_F
H5P_mp_H5PSET_VOL_F
H5P_mp_H5PGET_VOL_ID_F
; Parallel
@H5_NOPAREXP@H5P_mp_H5PSET_FAPL_MPIO_F
@H5_NOPAREXP@H5P_mp_H5PGET_FAPL_MPIO_F

View File

@ -138,6 +138,99 @@ CONTAINS
END SUBROUTINE test_registration_by_value
!-------------------------------------------------------------------------
! Function: test_registration_by_name()
!
! Purpose: Tests if we can load, register, and close a VOL
! connector by name.
!
!-------------------------------------------------------------------------
!
SUBROUTINE test_registration_by_fapl(total_error)
IMPLICIT NONE
INTEGER, INTENT(INOUT) :: total_error
INTEGER :: error = 0
LOGICAL :: is_registered = .FALSE.
INTEGER(hid_t) :: vol_id = 0, vol_id_out = 1
CHARACTER(LEN=64) :: name
INTEGER(SIZE_T) :: name_len
INTEGER(hid_t) :: file_id
INTEGER :: cmp = -1
INTEGER(hid_t) :: fapl_id
TYPE(C_PTR) :: f_ptr
INTEGER(hid_t), TARGET :: under_fapl
CALL H5VLis_connector_registered_f( "FAKE_VOL_CONNECTOR_NAME", is_registered, error)
CALL check("H5VLis_connector_registered_f",error,total_error)
CALL VERIFY("H5VLis_connector_registered_f", is_registered, .FALSE., total_error)
! The null VOL connector should not be registered at the start of the test
CALL H5VLis_connector_registered_f( "FAKE_VOL_CONNECTOR_NAME", is_registered, error)
CALL check("H5VLis_connector_registered_f",error,total_error)
CALL VERIFY("H5VLis_connector_registered_f", is_registered, .FALSE., total_error)
CALL H5VLregister_connector_by_name_f(NATIVE_VOL_CONNECTOR_NAME, vol_id, error)
CALL check("H5VLregister_connector_by_name_f",error,total_error)
! The connector should be registered now
CALL H5VLis_connector_registered_f(NATIVE_VOL_CONNECTOR_NAME, is_registered, error)
CALL check("H5VLis_connector_registered_f",error,total_error)
CALL VERIFY("H5VLis_connector_registered_f", is_registered, .TRUE., total_error)
! Register the connector
CALL H5Pcreate_f(H5P_FILE_ACCESS_F, fapl_id, error)
CALL check("H5Pcreate_f",error,total_error)
f_ptr = C_NULL_PTR
CALL H5Pset_vol_f(fapl_id, vol_id, f_ptr, error)
CALL check("H5Pset_vol_f",error,total_error)
CALL H5Pget_vol_id_f(fapl_id, vol_id_out, error)
CALL check("H5Pget_vol_id_f",error,total_error)
CALL VERIFY("H5Pget_vol_id_f", vol_id_out, vol_id, total_error)
#if 0
CALL H5Pcreate_f(H5P_FILE_ACCESS_F, under_fapl, error)
CALL check("H5Pcreate_f",error,total_error)
f_ptr = C_LOC(under_fapl)
CALL H5Pset_vol_f(fapl_id, vol_id, f_ptr, error)
CALL check("H5Pset_vol_f",error,total_error)
CALL H5Pget_vol_id_f(fapl_id, vol_id_out, error)
CALL check("H5Pget_vol_id_f",error,total_error)
CALL VERIFY("H5Pget_vol_id_f", vol_id_out, vol_id, total_error)
#endif
CALL H5VLget_connector_id_f(NATIVE_VOL_CONNECTOR_NAME, vol_id_out, error)
CALL check("H5VLget_connector_id_f",error,total_error)
CALL VERIFY("H5VLget_connector_id_f", vol_id_out, vol_id, total_error)
CALL H5Fcreate_f("voltest.h5",H5F_ACC_TRUNC_F, file_id, error, H5P_DEFAULT_F, fapl_id)
CALL check("H5F_create_f",error,total_error)
CALL H5VLclose_f(vol_id_out, error)
CALL check("H5VLclose_f",error, total_error)
CALL H5VLclose_f(vol_id, error)
CALL check("H5VLclose_f",error, total_error)
! Unregister the connector
CALL H5VLunregister_connector_f(vol_id, error)
CALL check("H5VLunregister_connector_f", error, total_error)
CALL H5Fclose_f(file_id, error)
CALL check("H5Fclose_f",error,total_error)
CALL H5Pclose_f(fapl_id, error)
CALL check("H5Pclose_f",error,total_error)
END SUBROUTINE test_registration_by_fapl
END MODULE VOL_TMOD
@ -172,6 +265,10 @@ PROGRAM vol_connector
CALL test_registration_by_value(ret_total_error)
CALL write_test_status(ret_total_error, ' Testing VOL registration by value', total_error)
ret_total_error = 0
CALL test_registration_by_fapl(ret_total_error)
CALL write_test_status(ret_total_error, ' Testing VOL registration by fapl', total_error)
WRITE(*, fmt = '(/18X,A)') '============================================'
WRITE(*, fmt = '(19X, A)', advance='NO') ' FORTRAN VOL tests completed with '
WRITE(*, fmt = '(I4)', advance='NO') total_error