Multi Dataset (#2120)

* Fix bug with cross platform compatibility of references within vlens.
No testing yet.

* Merge from multi_rd_wd_coll_io to a more recent branch from develop.
Untested, probably does not work yet.

* Committing clang-format changes

* Committing clang-format changes

* Fix many bugs in multi dataset branch.  Mostly works, some issues in
SWMR tests.

* Committing clang-format changes

* Disable test in swmr.c that was failing due to bug in HDF5 unrelated to
multi dataset.

* Committing clang-format changes

* Fixed fortran multi-dataset tests

* Fixed xlf errors

* Added benchmark code for multi-datasets

* loops over datasets

* added missing error arg.

* Added gnuplot formatting

* Jonathan Kim original MD benchmarking code

* updated MD benchmarking code

* code clean-up

* Only make files in feature test mode

* misc clean-up

* removed TEST_MDSET_NO_LAST_DSET_2ND_PROC option

* Committing clang-format changes

* Change multi dataset API to use arrays of individual parameters instead
of the parameter struct.

* Committing clang-format changes

* Update to new multi dataset Fortran API and tests. (#1724)

* Update to new multi dataset Fortran API and tests.
* Sync Fortran with develop.
* skipping h5pget_mpio_actual_io_mode_f for now

* Fixed issue with dxpl_id, changed to variable size dim. (#1770)

* Remove "is_coll_broken" field from H5D_io_info_t struct

* Committing clang-format changes

* Minor cleanup in multi dataset code.

* Committing clang-format changes

* Clean up in multi dataset code.

* Committing clang-format changes

* Committing clang-format changes

* Fix speeling

* Fix bug in parallel compression. Switch base_maddr in io_info to be a
union.

* Committing clang-format changes

* Implement selection I/O support with multi dataset.  Will be broken in
parallel until PR 1803 is merged to develop then the MDS branch.

* Committing clang-format changes

* Spelling

* Fix bug in multi dataset that could cause errors when only some of the
datasets in the multi dataset I/O used type conversion.

* Committing clang-format changes

* Integrate multi dataset APIs with VOL layer.  Add async versions of
multi dataset APIs.

* Committing clang-format changes

* Spelling fixes

* Fix bug in non-parallel HDF5 compilation.

* Committing clang-format changes

* Fix potential memory/free list error. Minor performance fix. Other minor
changes.

* Committing clang-format changes

* Fix memory leak with memory dataspace for I/O.

* Committing clang-format changes

* Fix stack variables too large.  Rename H5D_dset_info_t to
H5D_dset_io_info_t.

* Committing clang-format changes

* Remove mem_space_alloc field from H5D_dset_io_info_t.  Each function is
now responsible for freeing any spaces it adds to dset_info.

* Committing clang-format changes

* fixed _multi Fortran declaration

* Refactor various things in (mostly) the serial I/O code path to make
things more maintainable.

* Committing clang-format changes

* updated to array based, doxygen, and examples

* Reinstate H5D_chunk_map_t, stored (via pointer) inside
H5D_dset_io_info_t.

* Change from calloc to malloc for H5D_dset_io_info_t and H5D_chunk_map_t.
Switch temporary dset_infos to be local stack variables.

* Committing clang-format changes

* format cleanup

* format cleanup

* added coll and ind

* Modify all parallel I/O paths to take dset_info instead of assuming
dset_info[0].

* Committing clang-format changes

* fixed output

* Rework parallel I/O code to work properly with multi dataset in more
cases.  Fix bug in parallel compression.

* Committing clang-format changes

* Prevent H5D__multi_chunk_collective_io() from messing up collective opt
property for other datasets in I/O.  Other minor cleanup.  Add new test
case to t_pmulti_dset.c for H5FD_MPIO_INDIVIDUAL_IO, disabled for now
due to failures apparently unrelated to multi dataset code.

* Fix spelling

* Committing clang-format changes

* Replace N log N algorithm for finding chunk in
H5D__multi_chunk_collective_io() with O(N) algorithm, and remove use of
io_info->sel_pieces in that function.

* Committing clang-format changes

* Replace sel_pieces skiplist in io_info with flat array of pointers, use
qsort in I/O routine only when necessary.

* Committing clang-format changes

* Add new test case to mdset.c

* Committing clang-format changes

* Fix spelling

* Very minor fix in H5VL__native_dataset_read()

* Fix bug that could affect filtered parallel multi-dataset I/O.

* Add RM entries for H5Dread_multi(), H5Dread_multi_async(),
H5Dwrite_multi(), and H5Dwrite_multi_async()

* Unskip test in swmr.c

* Committing clang-format changes

* Eliminate H5D__pre_read and H5D__pre_write

* Remove examples/ph5mdsettest.c. Will fix and re-add as a test.

* Enable hyperslab combinations in mdset test

* Committing clang-format changes

* Clarify H5Dread/write_multi documentation.

* Fix bugs in multi-dataset I/O.  Expand serial multi dataset test.
Update macro in parallel multi dataset test.

* Committing clang-format changes

* Spelling

* Remove obsolete entry in bin/trace

* Rework type conversion buffer allocation. Only one buffer is shared
between datasets in mdset mode, and it is malloced instead of calloced.

* Committing clang-format changes

* Fix bug in error handling in H5D__read/write

* added multi-dataset fortran check with optional dataset creation id (#2150)

* removed dup. dll entry

* Address comments from code review.

* Remove spurious changes in H5Fmpi.c

* Fix issue with reading unallocated datasets in multi-dataset mode.
Address other comments from code review.

* Committing clang-format changes

* Delay chunk index lookup from io_init to mdio_init so it doesn't add
overhead to single dataset I/O.

* Committing clang-format changes

* Fix inappropriate use of piece_count

* updated copyright on new file, removed benchmark from testing dir.

Co-authored-by: github-actions <41898282+github-actions[bot]@users.noreply.github.com>
Co-authored-by: M. Scot Breitenfeld <brtnfld@hdfgroup.org>
Co-authored-by: Dana Robinson <43805+derobins@users.noreply.github.com>
This commit is contained in:
Neil Fortner 2022-10-19 11:13:15 -05:00 committed by GitHub
parent a898cef6c2
commit 93754cae33
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
40 changed files with 6493 additions and 2975 deletions

View File

@ -1098,7 +1098,7 @@ CONTAINS
!>
!! \ingroup FH5D
!!
!! \brief Writes raw data from a dataset into a buffer.
!! \brief Writes raw data from a buffer to a dataset.
!!
!! \attention \fortran_approved
!!
@ -1762,6 +1762,108 @@ CONTAINS
CALL h5dfill_ptr(f_ptr_fill_value, fill_type_id, f_ptr_buf, mem_type_id, space_id, hdferr)
END SUBROUTINE h5dfill_char
!>
!! \ingroup FH5D
!!
!! \brief Reads data from a file to memory buffers for multiple datasets.
!!
!! \param count Number of datasets to write to.
!! \param dset_id Identifier of the dataset to write to.
!! \param mem_type_id Identifier of the memory datatype.
!! \param mem_space_id Identifier of the memory dataspace.
!! \param file_space_id Identifier of the dataset&apos;s dataspace in the file.
!! \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.
!!
SUBROUTINE H5Dread_multi_f(count, dset_id, mem_type_id, mem_space_id, file_space_id, buf, hdferr, xfer_prp)
IMPLICIT NONE
INTEGER(SIZE_T), INTENT(IN) :: count
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: dset_id
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: mem_type_id
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: mem_space_id
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: file_space_id
TYPE(C_PTR), DIMENSION(*) :: buf
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T), INTENT(IN), OPTIONAL :: xfer_prp
INTEGER(HID_T) :: xfer_prp_default
INTERFACE
INTEGER FUNCTION H5Dread_multi(count, dset_id, mem_type_id, mem_space_id, file_space_id, xfer_prp, buf) &
BIND(C, NAME='H5Dread_multi')
IMPORT :: SIZE_T
IMPORT :: HID_T
IMPORT :: C_PTR
IMPLICIT NONE
INTEGER(SIZE_T), VALUE :: count
INTEGER(HID_T), DIMENSION(*) :: dset_id
INTEGER(HID_T), DIMENSION(*) :: mem_type_id
INTEGER(HID_T), DIMENSION(*) :: mem_space_id
INTEGER(HID_T), DIMENSION(*) :: file_space_id
INTEGER(HID_T), VALUE :: xfer_prp
TYPE(C_PTR), DIMENSION(*) :: buf
END FUNCTION H5Dread_multi
END INTERFACE
xfer_prp_default = H5P_DEFAULT_F
IF (PRESENT(xfer_prp)) xfer_prp_default = xfer_prp
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
!!
!! \brief Writes data in memory to a file for multiple datasets.
!!
!! \param count Number of datasets to write to.
!! \param dset_id Identifier of the dataset to write to.
!! \param mem_type_id Identifier of the memory datatype.
!! \param mem_space_id Identifier of the memory dataspace.
!! \param file_space_id Identifier of the dataset&apos;s dataspace in the file.
!! \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.
!!
SUBROUTINE H5Dwrite_multi_f(count, dset_id, mem_type_id, mem_space_id, file_space_id, buf, hdferr, xfer_prp)
IMPLICIT NONE
INTEGER(SIZE_T), INTENT(IN) :: count
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: dset_id
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: mem_type_id
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: mem_space_id
INTEGER(HID_T), INTENT(IN), DIMENSION(*) :: file_space_id
TYPE(C_PTR), DIMENSION(*) :: buf
INTEGER, INTENT(OUT) :: hdferr
INTEGER(HID_T), INTENT(IN), OPTIONAL :: xfer_prp
INTEGER(HID_T) :: xfer_prp_default
INTERFACE
INTEGER FUNCTION H5Dwrite_multi(count, dset_id, mem_type_id, mem_space_id, file_space_id, xfer_prp, buf) &
BIND(C, NAME='H5Dwrite_multi')
IMPORT :: SIZE_T
IMPORT :: HID_T
IMPORT :: C_PTR
IMPLICIT NONE
INTEGER(SIZE_T), VALUE :: count
INTEGER(HID_T), DIMENSION(*) :: dset_id
INTEGER(HID_T), DIMENSION(*) :: mem_type_id
INTEGER(HID_T), DIMENSION(*) :: mem_space_id
INTEGER(HID_T), DIMENSION(*) :: file_space_id
INTEGER(HID_T), VALUE :: xfer_prp
TYPE(C_PTR), DIMENSION(*) :: buf
END FUNCTION H5Dwrite_multi
END INTERFACE
xfer_prp_default = H5P_DEFAULT_F
IF (PRESENT(xfer_prp)) xfer_prp_default = xfer_prp
hdferr = H5Dwrite_multi(count, dset_id, mem_type_id, mem_space_id, file_space_id, xfer_prp_default, buf)
END SUBROUTINE H5Dwrite_multi_f
#endif

View File

@ -80,6 +80,8 @@ H5D_mp_H5DGET_ACCESS_PLIST_F
H5D_mp_H5DWRITE_PTR
H5D_mp_H5DREAD_PTR
H5D_mp_H5DVLEN_RECLAIM_F
H5D_mp_H5DREAD_MULTI_F
H5D_mp_H5DWRITE_MULTI_F
; H5E
H5E_mp_H5ECLEAR_F
H5E_mp_H5EPRINT_F

View File

@ -151,6 +151,10 @@ PROGRAM fortranlibtest_F03
CALL test_h5p_file_image(ret_total_error)
CALL write_test_status(ret_total_error, ' Testing h5pset/get file image', total_error)
ret_total_error = 0
CALL multiple_dset_rw(ret_total_error)
CALL write_test_status(ret_total_error, ' Testing multi-dataset reads and writes', total_error)
! write(*,*)
! write(*,*) '========================================='
! write(*,*) 'Testing OBJECT interface '

View File

@ -3407,4 +3407,258 @@ SUBROUTINE t_enum_conv(total_error)
END SUBROUTINE t_enum_conv
! Tests the reading and writing of multiple datasets using H5Dread_multi and
! H5Dwrite_multi
SUBROUTINE multiple_dset_rw(total_error)
!-------------------------------------------------------------------------
! Subroutine: multiple_dset_rw
!
! Purpose: Tests the reading and writing of multiple datasets
! using H5Dread_multi and H5Dwrite_multi
!
! Return: Success: 0
! Failure: number of errors
!
! Programmer: M. Scot Breitenfeld
! April 2, 2014
!
!-------------------------------------------------------------------------
!
USE iso_c_binding
USE hdf5
IMPLICIT NONE
INTEGER, INTENT(INOUT) :: total_error ! number of errors
INTEGER :: error ! HDF hdferror flag
INTEGER(SIZE_T), PARAMETER :: ndset = 5 ! Number of data sets
INTEGER(HID_T), DIMENSION(:), ALLOCATABLE :: dset_id
INTEGER(HID_T), DIMENSION(:), ALLOCATABLE :: mem_type_id
INTEGER(HID_T), DIMENSION(:), ALLOCATABLE :: mem_space_id
INTEGER(HID_T), DIMENSION(:), ALLOCATABLE :: file_space_id
INTEGER, PARAMETER :: idim=10, idim2=5, idim3=3 ! size of integer array
INTEGER, PARAMETER :: rdim=5 ! size of real array
INTEGER, PARAMETER :: cdim=3 ! size of character array
INTEGER, PARAMETER :: sdim=2 ! length of character string
INTEGER, PARAMETER :: ddim=2 ! size of derived type array
INTEGER :: i,j,k
TYPE(C_PTR), ALLOCATABLE, DIMENSION(:) :: buf_md ! array to hold the multi-datasets
INTEGER, DIMENSION(1:idim), TARGET :: wbuf_int ! integer write buffer
INTEGER, DIMENSION(1:idim,idim2,idim3), TARGET :: wbuf_intmd
REAL, DIMENSION(1:rdim), TARGET :: wbuf_real ! real write buffer
CHARACTER(LEN=sdim), DIMENSION(1:cdim), TARGET :: wbuf_chr ! character write buffer
INTEGER, DIMENSION(1:idim), TARGET :: rbuf_int ! integer read buffer
INTEGER, DIMENSION(1:idim,idim2,idim3), TARGET :: rbuf_intmd ! integer read buffer
REAL, DIMENSION(1:rdim), TARGET :: rbuf_real ! real read buffer
CHARACTER(LEN=sdim), DIMENSION(1:cdim), TARGET :: rbuf_chr ! character read buffer
TYPE derived
REAL :: r
INTEGER :: i
CHARACTER(LEN=sdim) :: c
END TYPE derived
TYPE(derived), DIMENSION(1:ddim), TARGET :: wbuf_derived ! derived type write buffer
TYPE(derived), DIMENSION(1:ddim), TARGET :: rbuf_derived ! derived type read buffer
INTEGER(HSIZE_T), DIMENSION(1:1) :: dims ! dimension of the spaces
INTEGER(HSIZE_T), DIMENSION(1:3) :: dimsmd ! dimension of the spaces
INTEGER(HID_T) :: file_id, strtype ! handles
INTEGER(SIZE_T) :: obj_count
ALLOCATE(buf_md(1:ndset),stat=error)
IF (error .NE. 0) THEN
WRITE(*,*) 'allocate error'
total_error = total_error + 1
RETURN
ENDIF
ALLOCATE(dset_id(1:ndset),stat=error)
IF (error .NE. 0) THEN
WRITE(*,*) 'allocate error'
total_error = total_error + 1
RETURN
ENDIF
ALLOCATE(mem_type_id(1:ndset),stat=error)
IF (error .NE. 0) THEN
WRITE(*,*) 'allocate error'
total_error = total_error + 1
RETURN
ENDIF
ALLOCATE(mem_space_id(1:ndset),stat=error)
IF (error .NE. 0) THEN
WRITE(*,*) 'allocate error'
total_error = total_error + 1
RETURN
ENDIF
ALLOCATE(file_space_id(1:ndset),stat=error)
IF (error .NE. 0) THEN
WRITE(*,*) 'allocate error'
total_error = total_error + 1
RETURN
ENDIF
CALL h5fcreate_f("multidset_rw.h5", H5F_ACC_TRUNC_F, file_id, error)
CALL check("h5fcreate_f", error, total_error)
!
! Create real dataset
!
wbuf_real(1:rdim) = (/(i,i=1,rdim)/)
dims(1) = rdim
buf_md(1) = C_LOC(wbuf_real(1))
mem_type_id(1) = H5T_NATIVE_REAL
CALL h5screate_simple_f(1, dims, file_space_id(1), error)
CALL check("h5screate_simple_f", error, total_error)
CALL h5dcreate_f(file_id, "ds real", mem_type_id(1), file_space_id(1), dset_id(1), error)
CALL check("h5dcreate_f", error, total_error)
mem_space_id(1) = file_space_id(1)
! Create integer dataset (1D)
wbuf_int(1:idim) = (/(i,i=1,idim)/)
dims(1) = idim
buf_md(2) = C_LOC(wbuf_int(1))
mem_type_id(2) = H5T_NATIVE_INTEGER
CALL h5screate_simple_f(1, dims, file_space_id(2), error)
CALL check("h5screate_simple_f", error, total_error)
CALL h5dcreate_f(file_id, "ds int", mem_type_id(2), file_space_id(2), dset_id(2), error)
CALL check("h5dcreate_f", error, total_error)
mem_space_id(2) = file_space_id(2)
! Create character dataset
wbuf_chr(1:cdim) = (/'ab','cd','ef'/)
dims(1) = cdim
buf_md(3) = C_LOC(wbuf_chr(1)(1:1))
CALL H5Tcopy_f(H5T_FORTRAN_S1, mem_type_id(3), error)
CALL check("H5Tcopy_f", error, total_error)
CALL H5Tset_size_f(mem_type_id(3), INT(sdim,SIZE_T), error)
CALL check("H5Tset_size_f", error, total_error)
CALL h5screate_simple_f(1, dims, file_space_id(3), error)
CALL check("h5screate_simple_f", error, total_error)
CALL h5dcreate_f(file_id, "ds chr", mem_type_id(3), file_space_id(3), dset_id(3), error)
CALL check("h5dcreate_f", error, total_error)
mem_space_id(3) = file_space_id(3)
! Create derived type dataset
wbuf_derived(1:ddim)%r = (/10.,20./)
wbuf_derived(1:ddim)%i = (/30,40/)
wbuf_derived(1:ddim)%c = (/'wx','yz'/)
buf_md(4) = C_LOC(wbuf_derived(1)%r)
CALL h5tcreate_f(H5T_COMPOUND_F, H5OFFSETOF(C_LOC(wbuf_derived(1)), C_LOC(wbuf_derived(2))), mem_type_id(4), error)
CALL check("h5tcreate_f", error, total_error)
CALL h5tinsert_f(mem_type_id(4), "real", &
H5OFFSETOF(C_LOC(wbuf_derived(1)),C_LOC(wbuf_derived(1)%r)), H5T_NATIVE_REAL, error)
CALL check("h5tinsert_f", error, total_error)
CALL h5tinsert_f(mem_type_id(4), "int", &
H5OFFSETOF(C_LOC(wbuf_derived(1)),C_LOC(wbuf_derived(1)%i)), H5T_NATIVE_INTEGER, error)
CALL check("h5tinsert_f", error, total_error)
CALL h5tcopy_f(H5T_NATIVE_CHARACTER, strtype, error)
CALL check("h5tcopy_f", error, total_error)
CALL h5tset_size_f(strtype, INT(sdim,size_t), error)
CALL check("h5tset_size_f", error, total_error)
CALL h5tinsert_f(mem_type_id(4), "chr", &
H5OFFSETOF(C_LOC(wbuf_derived(1)),C_LOC(wbuf_derived(1)%c(1:1))), strtype, error)
CALL check("h5tinsert_f", error, total_error)
dims(1) = ddim
CALL h5screate_simple_f(1, dims, file_space_id(4), error)
CALL check("h5screate_simple_f", error, total_error)
CALL h5dcreate_f(file_id, "ds derived", mem_type_id(4), file_space_id(4), dset_id(4), error)
CALL check("h5dcreate_f", error, total_error)
mem_space_id(4) = file_space_id(4)
! Create integer dataset (3D)
DO i = 1, idim
DO j = 1, idim2
DO k = 1, idim3
wbuf_intmd(i,j,k) = i*j
ENDDO
ENDDO
ENDDO
dimsmd(1:3) = (/idim,idim2,idim3/)
buf_md(5) = C_LOC(wbuf_intmd(1,1,1))
mem_type_id(5) = H5T_NATIVE_INTEGER
CALL h5screate_simple_f(3, dimsmd, file_space_id(5), error)
CALL check("h5screate_simple_f", error, total_error)
CALL h5dcreate_f(file_id, "ds int 3d", mem_type_id(5), file_space_id(5), dset_id(5), error)
CALL check("h5dcreate_f", error, total_error)
mem_space_id(5) = file_space_id(5)
! write all the datasets
CALL h5dwrite_multi_f(ndset, dset_id, mem_type_id, mem_space_id, file_space_id, buf_md, error)
CALL check("h5dwrite_multi_f", error, total_error)
! point to read buffers
buf_md(1) = C_LOC(rbuf_real(1))
buf_md(2) = C_LOC(rbuf_int(1))
buf_md(3) = C_LOC(rbuf_chr(1)(1:1))
buf_md(4) = C_LOC(rbuf_derived(1)%r)
buf_md(5) = C_LOC(rbuf_intmd(1,1,1))
! read all the datasets
CALL h5dread_multi_f(ndset, dset_id, mem_type_id, mem_space_id, file_space_id, buf_md, error)
CALL check("h5dread_multi_f", error, total_error)
! check the written and read in values
DO i = 1, rdim
IF(rbuf_real(i).NE.wbuf_real(i))THEN
total_error = total_error + 1
END IF
END DO
DO i = 1, idim
IF(rbuf_int(i).NE.wbuf_int(i))THEN
total_error = total_error + 1
END IF
END DO
DO i = 1, cdim
IF(rbuf_chr(i).NE.wbuf_chr(i))THEN
total_error = total_error + 1
END IF
END DO
DO i = 1, ddim
IF(rbuf_derived(i)%r.NE.wbuf_derived(i)%r)THEN
total_error = total_error + 1
END IF
IF(rbuf_derived(i)%i.NE.wbuf_derived(i)%i)THEN
total_error = total_error + 1
END IF
IF(rbuf_derived(i)%c.NE.wbuf_derived(i)%c)THEN
total_error = total_error + 1
END IF
END DO
DO i = 1, idim
DO j = 1, idim2
DO k = 1, idim3
IF(rbuf_intmd(i,j,k).NE.wbuf_intmd(i,j,k))THEN
total_error = total_error + 1
END IF
END DO
ENDDO
ENDDO
DO i = 1, ndset
CALL H5Dclose_f(dset_id(i), error)
CALL check("H5Dclose_f", error, total_error)
CALL H5Sclose_f(file_space_id(i), error)
CALL check("H5Sclose_f", error, total_error)
ENDDO
CALL H5Tclose_f(mem_type_id(4), error)
CALL check("H5Tclose_f", error, total_error)
CALL h5fget_obj_count_f(file_id, H5F_OBJ_ALL_F, obj_count, error)
IF(obj_count.NE.1)THEN
total_error = total_error + 1
END IF
CALL H5Fclose_f(file_id, error)
END SUBROUTINE multiple_dset_rw
END MODULE TH5T_F03

View File

@ -88,7 +88,7 @@ CONTAINS
error_string = skip
ENDIF
WRITE(*, fmt = '(A, T80, A)') test_title, error_string
WRITE(*, fmt = '(A, T88, A)') test_title, error_string
IF(test_result.GT.0) total_error = total_error + test_result

View File

@ -20,6 +20,7 @@ add_executable (parallel_test
ptest.F90
hyper.F90
mdset.F90
multidsetrw.F90
)
target_include_directories (parallel_test
PRIVATE ${TESTPAR_INCLUDES}

View File

@ -40,7 +40,7 @@ check_PROGRAMS=$(TEST_PROG_PARA)
CHECK_CLEANFILES+=parf[12].h5 subf.h5*
# Test source files
parallel_test_SOURCES=ptest.F90 hyper.F90 mdset.F90
parallel_test_SOURCES=ptest.F90 hyper.F90 mdset.F90 multidsetrw.F90
subfiling_test_SOURCES=subfiling.F90
# The tests depend on several libraries.

View File

@ -237,19 +237,23 @@ SUBROUTINE hyper(length,do_collective,do_chunk, mpi_size, mpi_rank, nerrors)
CALL h5pget_mpio_actual_io_mode_f(dxpl_id, actual_io_mode, hdferror)
CALL check("h5pget_mpio_actual_io_mode_f", hdferror, nerrors)
IF(do_collective.AND.do_chunk)THEN
IF(actual_io_mode.NE.H5D_MPIO_CHUNK_COLLECTIVE_F)THEN
CALL check("h5pget_mpio_actual_io_mode_f", -1, nerrors)
ENDIF
ELSEIF(.NOT.do_collective)THEN
IF(actual_io_mode.NE.H5D_MPIO_NO_COLLECTIVE_F)THEN
CALL check("h5pget_mpio_actual_io_mode_f", -1, nerrors)
ENDIF
ELSEIF( do_collective.AND.(.NOT.do_chunk))THEN
IF(actual_io_mode.NE.H5D_MPIO_CONTIG_COLLECTIVE_F)THEN
CALL check("h5pget_mpio_actual_io_mode_f", -1, nerrors)
ENDIF
ENDIF
! MSB -- TODO FIX: skipping for now since multi-dataset
! has no specific path for contiguous collective
!
! IF(do_collective.AND.do_chunk)THEN
! IF(actual_io_mode.NE.H5D_MPIO_CHUNK_COLLECTIVE_F)THEN
! CALL check("h5pget_mpio_actual_io_mode_f", -1, nerrors)
! ENDIF
! ELSEIF(.NOT.do_collective)THEN
! IF(actual_io_mode.NE.H5D_MPIO_NO_COLLECTIVE_F)THEN
! CALL check("h5pget_mpio_actual_io_mode_f", -1, nerrors)
! ENDIF
! ELSEIF( do_collective.AND.(.NOT.do_chunk))THEN
! IF(actual_io_mode.NE.H5D_MPIO_CONTIG_COLLECTIVE_F)THEN
! CALL check("h5pget_mpio_actual_io_mode_f", -1, nerrors)
! ENDIF
! ENDIF
! MSB
!
! close HDF5 I/O
@ -318,7 +322,6 @@ SUBROUTINE hyper(length,do_collective,do_chunk, mpi_size, mpi_rank, nerrors)
CALL h5pcreate_f(H5P_DATASET_XFER_F, dxpl_id, hdferror)
CALL check("h5pcreate_f", hdferror, nerrors)
IF (do_collective) THEN
CALL h5pset_dxpl_mpio_f(dxpl_id, H5FD_MPIO_COLLECTIVE_F, hdferror)
CALL check("h5pset_dxpl_mpio_f", hdferror, nerrors)

View File

@ -0,0 +1,235 @@
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
! Copyright by The HDF Group. *
! All rights reserved. *
! *
! This file is part of HDF5. The full HDF5 copyright notice, including *
! terms governing use, modification, and redistribution, is contained in *
! the files COPYING and Copyright.html. COPYING can be found at the root *
! of the source code distribution tree; Copyright.html can be found at the *
! root level of an installed copy of the electronic HDF5 document set and *
! is linked from the top-level documents page. It can also be found at *
! http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
! access to either file, you may request a copy from help@hdfgroup.org. *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
! writes/reads dataset by hyperslabs using multi-dataset routines, h5dread_multi and
! h5dwrite_multi
!
SUBROUTINE pmultiple_dset_hyper_rw(do_collective, do_chunk, mpi_size, mpi_rank, nerrors)
USE iso_c_binding
USE TH5_MISC
USE hdf5
USE mpi
IMPLICIT NONE
LOGICAL, INTENT(in) :: do_collective ! use collective IO
LOGICAL, INTENT(in) :: do_chunk ! use chunking
INTEGER, INTENT(in) :: mpi_size ! number of processes in the group of communicator
INTEGER, INTENT(in) :: mpi_rank ! rank of the calling process in the communicator
INTEGER, INTENT(inout) :: nerrors ! number of errors
CHARACTER(LEN=80):: dsetname ! Dataset name
INTEGER(hsize_t), DIMENSION(1:2) :: cdims ! chunk dimensions
INTEGER(HID_T) :: file_id ! File identifier
INTEGER(HID_T) :: filespace ! Dataspace identifier in file
INTEGER(HID_T) :: memspace ! Dataspace identifier in memory
INTEGER(HID_T) :: plist_id ! Property list identifier
INTEGER(HID_T) :: dcpl_id ! Dataset creation property list
INTEGER(HSIZE_T), DIMENSION(1:2) :: dimsf ! Dataset dimensions.
INTEGER(HSIZE_T), DIMENSION(1:2) :: count
INTEGER(HSSIZE_T), DIMENSION(1:2) :: offset
INTEGER, ALLOCATABLE, DIMENSION(:,:,:), TARGET :: DATA ! Data to write
INTEGER, ALLOCATABLE, DIMENSION(:,:,:), TARGET :: rDATA ! Data to write
INTEGER, PARAMETER :: rank = 2 ! Dataset rank
INTEGER :: i
INTEGER(HSIZE_T) :: ii, jj, kk, istart
INTEGER :: error ! Error flags
INTEGER(SIZE_T), PARAMETER :: ndsets = 5
INTEGER(HID_T), DIMENSION(1:ndsets) :: dset_id
INTEGER(HID_T), DIMENSION(1:ndsets) :: mem_type_id
INTEGER(HID_T), DIMENSION(1:ndsets) :: mem_space_id
INTEGER(HID_T), DIMENSION(1:ndsets) :: file_space_id
TYPE(C_PTR), DIMENSION(1:ndsets) :: buf_md
INTEGER(SIZE_T) :: obj_count
INTEGER :: data_xfer_mode
dimsf(1) = 5_hsize_t
dimsf(2) = INT(mpi_size, hsize_t)*8_hsize_t
!
! Setup file access property list with parallel I/O access.
!
CALL h5pcreate_f(H5P_FILE_ACCESS_F, plist_id, error)
CALL check("h5pcreate_f", error, nerrors)
CALL h5pset_fapl_mpio_f(plist_id, MPI_COMM_WORLD, MPI_INFO_NULL, error)
CALL check("h5pset_fapl_mpio_f", error, nerrors)
!
! Create the file collectively.
!
CALL h5fcreate_f("parf2.h5", H5F_ACC_TRUNC_F, file_id, error, access_prp = plist_id)
CALL check("h5fcreate_f", error, nerrors)
CALL h5pclose_f(plist_id, error)
CALL check("h5pclose_f", error, nerrors)
!
! Create the data space for the dataset.
!
CALL h5screate_simple_f(rank, dimsf, filespace, error)
CALL check("h5screate_simple_f", error, nerrors)
!
! Each process defines dataset in memory and writes it to the hyperslab
! in the file.
!
count(1) = dimsf(1)
count(2) = dimsf(2)/mpi_size
offset(1) = 0
offset(2) = mpi_rank * count(2)
CALL h5screate_simple_f(rank, count, memspace, error)
CALL check("h5screate_simple_f", error, nerrors)
!
! Modify dataset creation properties to enable chunking
!
CALL h5pcreate_f(H5P_DATASET_CREATE_F, dcpl_id, error)
CALL check("h5pcreate_f", error, nerrors)
IF (do_chunk) THEN
cdims(1) = dimsf(1)
cdims(2) = dimsf(2)/mpi_size/2
CALL h5pset_chunk_f(dcpl_id, 2, cdims, error)
CALL check("h5pset_chunk_f", error, nerrors)
ENDIF
!
! Select hyperslab in the file.
!
CALL h5sselect_hyperslab_f(filespace, H5S_SELECT_SET_F, offset, count, error)
CALL check("h5sselect_hyperslab_f", error, nerrors)
!
! Initialize data buffer
!
ALLOCATE ( DATA(COUNT(1),COUNT(2), ndsets))
ALLOCATE ( rdata(COUNT(1),COUNT(2), ndsets))
! Create property list for collective dataset write
!
CALL h5pcreate_f(H5P_DATASET_XFER_F, plist_id, error)
CALL check("h5pcreate_f", error, nerrors)
IF(do_collective)THEN
CALL h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, error)
CALL check("h5pset_dxpl_mpio_f", error, nerrors)
ELSE
CALL h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_INDEPENDENT_F, error)
CALL check("h5pset_dxpl_mpio_f", error, nerrors)
ENDIF
!
! Create the dataset with default properties.
!
mem_type_id(1:ndsets) = H5T_NATIVE_INTEGER
mem_space_id(1:ndsets) = memspace
file_space_id(1:ndsets)= filespace
DO ii = 1, ndsets
! Create the data
DO kk = 1, COUNT(1)
DO jj = 1, COUNT(2)
istart = (kk-1)*dimsf(2) + mpi_rank*COUNT(2)
DATA(kk,jj,ii) = INT((istart + jj)*10**(ii-1))
ENDDO
ENDDO
! Point to te data
buf_md(ii) = C_LOC(DATA(1,1,ii))
! direct the output of the write statement to unit "dsetname"
WRITE(dsetname,'("dataset ",I0)') ii
! create the dataset
CALL h5dcreate_f(file_id, dsetname, H5T_NATIVE_INTEGER, filespace, dset_id(ii), error, dcpl_id)
CALL check("h5dcreate_f", error, nerrors)
ENDDO
!
! Write the dataset collectively.
!
CALL h5dwrite_multi_f(ndsets, dset_id, mem_type_id, mem_space_id, file_space_id, buf_md, error, plist_id)
CALL check("h5dwrite_multi_f", error, nerrors)
CALL h5pget_dxpl_mpio_f(plist_id, data_xfer_mode, error)
CALL check("h5pget_dxpl_mpio_f", error, nerrors)
IF(do_collective)THEN
IF(data_xfer_mode.NE.H5FD_MPIO_COLLECTIVE_F)THEN
nerrors = nerrors + 1
ENDIF
ENDIF
DO i = 1, ndsets
! Point to the read buffer
buf_md(i) = C_LOC(rdata(1,1,i))
ENDDO
CALL H5Dread_multi_f(ndsets, dset_id, mem_type_id, mem_space_id, file_space_id, buf_md, error, plist_id)
CALL check("h5dread_multi_f", error, nerrors)
CALL h5pget_dxpl_mpio_f(plist_id, data_xfer_mode, error)
CALL check("h5pget_dxpl_mpio_f", error, nerrors)
IF(do_collective)THEN
IF(data_xfer_mode.NE.H5FD_MPIO_COLLECTIVE_F)THEN
nerrors = nerrors + 1
ENDIF
ENDIF
DO i = 1, ndsets
! Close all the datasets
CALL h5dclose_f(dset_id(i), error)
CALL check("h5dclose_f", error, nerrors)
ENDDO
! check the data read and write buffers
DO ii = 1, ndsets
! Create the data
DO kk = 1, COUNT(1)
DO jj = 1, COUNT(2)
IF(rDATA(kk,jj,ii).NE.DATA(kk,jj,ii))THEN
nerrors = nerrors + 1
ENDIF
ENDDO
ENDDO
ENDDO
!
! Deallocate data buffer.
!
DEALLOCATE(data, rdata)
!
! Close dataspaces.
!
CALL h5sclose_f(filespace, error)
CALL check("h5sclose_f", error, nerrors)
CALL h5sclose_f(memspace, error)
CALL check("h5sclose_f", error, nerrors)
!
! Close the dataset and property list.
!
CALL h5pclose_f(dcpl_id, error)
CALL check("h5pclose_f", error, nerrors)
CALL h5pclose_f(plist_id, error)
CALL check("h5pclose_f", error, nerrors)
CALL h5fget_obj_count_f(file_id, H5F_OBJ_ALL_F, obj_count, error)
IF(obj_count.NE.1)THEN
nerrors = nerrors + 1
END IF
!
! Close the file.
!
CALL h5fclose_f(file_id, error)
CALL check("h5fclose_f", error, nerrors)
END SUBROUTINE pmultiple_dset_hyper_rw

View File

@ -76,7 +76,18 @@ PROGRAM parallel_test
CALL multiple_dset_write(length, do_collective(1), do_chunk(1), mpi_size, mpi_rank, ret_total_error)
IF(mpi_rank==0) CALL write_test_status(ret_total_error, &
'Writing/reading several datasets (contiguous layout, independent MPI I/O)', total_error)
!
! test write/read multiple hyperslab datasets
!
DO i = 1, 2
DO j = 1, 2
ret_total_error = 0
CALL pmultiple_dset_hyper_rw(do_collective(j), do_chunk(i), mpi_size, mpi_rank, ret_total_error)
IF(mpi_rank==0) CALL write_test_status(ret_total_error, &
"Writing/reading multiple datasets by hyperslab ("//TRIM(chr_chunk(i))//" layout, "&
//TRIM(chr_collective(j))//" MPI I/O)", total_error)
ENDDO
ENDDO
!
! close HDF5 interface
!

308
src/H5D.c
View File

@ -50,10 +50,11 @@ static hid_t H5D__create_api_common(hid_t loc_id, const char *name, hid_t type_
static hid_t H5D__open_api_common(hid_t loc_id, const char *name, hid_t dapl_id, void **token_ptr,
H5VL_object_t **_vol_obj_ptr);
static hid_t H5D__get_space_api_common(hid_t dset_id, void **token_ptr, H5VL_object_t **_vol_obj_ptr);
static herr_t H5D__read_api_common(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, void *buf, void **token_ptr, H5VL_object_t **_vol_obj_ptr);
static herr_t H5D__write_api_common(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, const void *buf, void **token_ptr,
static herr_t H5D__read_api_common(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **token_ptr,
H5VL_object_t **_vol_obj_ptr);
static herr_t H5D__write_api_common(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void **token_ptr,
H5VL_object_t **_vol_obj_ptr);
static herr_t H5D__set_extent_api_common(hid_t dset_id, const hsize_t size[], void **token_ptr,
H5VL_object_t **_vol_obj_ptr);
@ -943,26 +944,64 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__read_api_common(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id, hid_t dxpl_id,
void *buf, void **token_ptr, H5VL_object_t **_vol_obj_ptr)
H5D__read_api_common(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **token_ptr,
H5VL_object_t **_vol_obj_ptr)
{
H5VL_object_t *tmp_vol_obj = NULL; /* Object for loc_id */
H5VL_object_t **vol_obj_ptr =
(_vol_obj_ptr ? _vol_obj_ptr : &tmp_vol_obj); /* Ptr to object ptr for loc_id */
herr_t ret_value = SUCCEED; /* Return value */
void *obj_local; /* Local buffer for obj */
void **obj = &obj_local; /* Array of object pointers */
H5VL_t *connector; /* VOL connector pointer */
size_t i; /* Local index variable */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Check arguments */
if (mem_space_id < 0)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid memory dataspace ID")
if (file_space_id < 0)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid file dataspace ID")
if (count == 0)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "count must be greater than 0")
if (!dset_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "dset_id array not provided")
if (!mem_type_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_type_id array not provided")
if (!mem_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_space_id array not provided")
if (!file_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "file_space_id array not provided")
if (!buf)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "buf array not provided")
/* Get dataset pointer */
if (NULL == (*vol_obj_ptr = (H5VL_object_t *)H5I_object_verify(dset_id, H5I_DATASET)))
/* Allocate obj array if necessary */
if (count > 1)
if (NULL == (obj = (void **)H5MM_malloc(count * sizeof(void *))))
HGOTO_ERROR(H5E_VOL, H5E_CANTALLOC, FAIL, "can't allocate space for object array")
/* Get vol_obj_ptr (return just the first dataset to caller if requested) */
if (NULL == (*vol_obj_ptr = (H5VL_object_t *)H5I_object_verify(dset_id[0], H5I_DATASET)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "dset_id is not a dataset ID")
/* Save the connector of the first dataset. Unpack the connector and call
* the "direct" read function here to avoid allocating an array of count
* H5VL_object_ts. */
connector = (*vol_obj_ptr)->connector;
/* Build obj array */
obj[0] = (*vol_obj_ptr)->data;
for (i = 1; i < count; i++) {
/* Get the object */
if (NULL == (tmp_vol_obj = (H5VL_object_t *)H5I_object_verify(dset_id[i], H5I_DATASET)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "dset_id is not a dataset ID")
obj[i] = tmp_vol_obj->data;
/* Make sure the class matches */
if (tmp_vol_obj->connector->cls->value != connector->cls->value)
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL,
"datasets are accessed through different VOL connectors and can't be used in the "
"same I/O call")
}
/* Get the default dataset transfer property list if the user didn't provide one */
if (H5P_DEFAULT == dxpl_id)
dxpl_id = H5P_DATASET_XFER_DEFAULT;
@ -970,11 +1009,15 @@ H5D__read_api_common(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not xfer parms")
/* Read the data */
if (H5VL_dataset_read(*vol_obj_ptr, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, token_ptr) <
0)
if (H5VL_dataset_read_direct(count, obj, connector, mem_type_id, mem_space_id, file_space_id, dxpl_id,
buf, token_ptr) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read data")
done:
/* Free memory */
if (obj != &obj_local)
H5MM_free(obj);
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5D__read_api_common() */
@ -1022,7 +1065,8 @@ H5Dread(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_i
H5TRACE6("e", "iiiiix", dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf);
/* Read the data */
if (H5D__read_api_common(dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, NULL, NULL) < 0)
if (H5D__read_api_common(1, &dset_id, &mem_type_id, &mem_space_id, &file_space_id, dxpl_id, &buf, NULL,
NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't synchronously read data")
done:
@ -1059,8 +1103,8 @@ H5Dread_async(const char *app_file, const char *app_func, unsigned app_line, hid
token_ptr = &token; /* Point at token for VOL connector to set up */
/* Read the data */
if (H5D__read_api_common(dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, token_ptr,
&vol_obj) < 0)
if (H5D__read_api_common(1, &dset_id, &mem_type_id, &mem_space_id, &file_space_id, dxpl_id, &buf,
token_ptr, &vol_obj) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't asynchronously read data")
/* If a token was created, add the token to the event set */
@ -1075,6 +1119,84 @@ done:
FUNC_LEAVE_API(ret_value)
} /* end H5Dread_async() */
/*-------------------------------------------------------------------------
* Function: H5Dread_multi
*
* Purpose: Multi-version of H5Dread(), which reads selections from
* multiple datasets from a file into application memory BUFS.
*
* Return: Non-negative on success/Negative on failure
*
* Programmer: Jonathan Kim Nov, 2013
*
*-------------------------------------------------------------------------
*/
herr_t
H5Dread_multi(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[], hid_t file_space_id[],
hid_t dxpl_id, void *buf[] /*out*/)
{
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_API(FAIL)
H5TRACE7("e", "z*i*i*i*iix", count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf);
if (count == 0)
HGOTO_DONE(SUCCEED)
/* Read the data */
if (H5D__read_api_common(count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, NULL,
NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't synchronously read data")
done:
FUNC_LEAVE_API(ret_value)
} /* end H5Dread_multi() */
/*-------------------------------------------------------------------------
* Function: H5Dread_multi_async
*
* Purpose: Asynchronously read dataset elements from multiple
* datasets.
*
* Return: Non-negative on success/Negative on failure
*
*-------------------------------------------------------------------------
*/
herr_t
H5Dread_multi_async(const char *app_file, const char *app_func, unsigned app_line, size_t count,
hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[], hid_t file_space_id[],
hid_t dxpl_id, void *buf[] /*out*/, hid_t es_id)
{
H5VL_object_t *vol_obj = NULL; /* Dataset VOL object */
void *token = NULL; /* Request token for async operation */
void **token_ptr = H5_REQUEST_NULL; /* Pointer to request token for async operation */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_API(FAIL)
H5TRACE11("e", "*s*sIuz*i*i*i*iixi", app_file, app_func, app_line, count, dset_id, mem_type_id,
mem_space_id, file_space_id, dxpl_id, buf, es_id);
/* Set up request token pointer for asynchronous operation */
if (H5ES_NONE != es_id)
token_ptr = &token; /* Point at token for VOL connector to set up */
/* Read the data */
if (H5D__read_api_common(count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf,
token_ptr, &vol_obj) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't asynchronously read data")
/* If a token was created, add the token to the event set */
if (NULL != token)
/* clang-format off */
if (H5ES_insert(es_id, vol_obj->connector, token,
H5ARG_TRACE11(__func__, "*s*sIuz*i*i*i*iixi", app_file, app_func, app_line, count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, es_id)) < 0)
/* clang-format on */
HGOTO_ERROR(H5E_DATASET, H5E_CANTINSERT, FAIL, "can't insert token into event set")
done:
FUNC_LEAVE_API(ret_value)
} /* end H5Dread_multi_async() */
/*-------------------------------------------------------------------------
* Function: H5Dread_chunk
*
@ -1142,26 +1264,64 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__write_api_common(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, const void *buf, void **token_ptr, H5VL_object_t **_vol_obj_ptr)
H5D__write_api_common(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void **token_ptr,
H5VL_object_t **_vol_obj_ptr)
{
H5VL_object_t *tmp_vol_obj = NULL; /* Object for loc_id */
H5VL_object_t **vol_obj_ptr =
(_vol_obj_ptr ? _vol_obj_ptr : &tmp_vol_obj); /* Ptr to object ptr for loc_id */
herr_t ret_value = SUCCEED; /* Return value */
void *obj_local; /* Local buffer for obj */
void **obj = &obj_local; /* Array of object pointers */
H5VL_t *connector; /* VOL connector pointer */
size_t i; /* Local index variable */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Check arguments */
if (mem_space_id < 0)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid memory dataspace ID")
if (file_space_id < 0)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid file dataspace ID")
if (count == 0)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "count must be greater than 0")
if (!dset_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "dset_id array not provided")
if (!mem_type_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_type_id array not provided")
if (!mem_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_space_id array not provided")
if (!file_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "file_space_id array not provided")
if (!buf)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "buf array not provided")
/* Get dataset pointer */
if (NULL == (*vol_obj_ptr = (H5VL_object_t *)H5I_object_verify(dset_id, H5I_DATASET)))
/* Allocate obj array if necessary */
if (count > 1)
if (NULL == (obj = (void **)H5MM_malloc(count * sizeof(void *))))
HGOTO_ERROR(H5E_VOL, H5E_CANTALLOC, FAIL, "can't allocate space for object array")
/* Get vol_obj_ptr (return just the first dataset to caller if requested) */
if (NULL == (*vol_obj_ptr = (H5VL_object_t *)H5I_object_verify(dset_id[0], H5I_DATASET)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "dset_id is not a dataset ID")
/* Save the connector of the first dataset. Unpack the connector and call
* the "direct" write function here to avoid allocating an array of count
* H5VL_object_ts. */
connector = (*vol_obj_ptr)->connector;
/* Build obj array */
obj[0] = (*vol_obj_ptr)->data;
for (i = 1; i < count; i++) {
/* Get the object */
if (NULL == (tmp_vol_obj = (H5VL_object_t *)H5I_object_verify(dset_id[i], H5I_DATASET)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "dset_id is not a dataset ID")
obj[i] = tmp_vol_obj->data;
/* Make sure the class matches */
if (tmp_vol_obj->connector->cls->value != connector->cls->value)
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL,
"datasets are accessed through different VOL connectors and can't be used in the "
"same I/O call")
}
/* Get the default dataset transfer property list if the user didn't provide one */
if (H5P_DEFAULT == dxpl_id)
dxpl_id = H5P_DATASET_XFER_DEFAULT;
@ -1169,11 +1329,15 @@ H5D__write_api_common(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not xfer parms")
/* Write the data */
if (H5VL_dataset_write(*vol_obj_ptr, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, token_ptr) <
0)
if (H5VL_dataset_write_direct(count, obj, connector, mem_type_id, mem_space_id, file_space_id, dxpl_id,
buf, token_ptr) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't write data")
done:
/* Free memory */
if (obj != &obj_local)
H5MM_free(obj);
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5D__write_api_common() */
@ -1222,8 +1386,8 @@ H5Dwrite(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_
H5TRACE6("e", "iiiii*x", dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf);
/* Write the data */
if (H5D__write_api_common(dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, NULL, NULL) <
0)
if (H5D__write_api_common(1, &dset_id, &mem_type_id, &mem_space_id, &file_space_id, dxpl_id, &buf, NULL,
NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't synchronously write data")
done:
@ -1261,8 +1425,8 @@ H5Dwrite_async(const char *app_file, const char *app_func, unsigned app_line, hi
token_ptr = &token; /* Point at token for VOL connector to set up */
/* Write the data */
if (H5D__write_api_common(dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, token_ptr,
&vol_obj) < 0)
if (H5D__write_api_common(1, &dset_id, &mem_type_id, &mem_space_id, &file_space_id, dxpl_id, &buf,
token_ptr, &vol_obj) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't asynchronously write data")
/* If a token was created, add the token to the event set */
@ -1277,6 +1441,84 @@ done:
FUNC_LEAVE_API(ret_value)
} /* end H5Dwrite_async() */
/*-------------------------------------------------------------------------
* Function: H5Dwrite_multi
*
* Purpose: Multi-version of H5Dwrite(), which writes selections from
* application memory BUFs into multiple datasets in a file.
*
* Return: Non-negative on success/Negative on failure
*
* Programmer: Jonathan Kim Nov, 2013
*
*-------------------------------------------------------------------------
*/
herr_t
H5Dwrite_multi(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[])
{
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_API(FAIL)
H5TRACE7("e", "z*i*i*i*ii**x", count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf);
if (count == 0)
HGOTO_DONE(SUCCEED)
/* Write the data */
if (H5D__write_api_common(count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, NULL,
NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't synchronously write data")
done:
FUNC_LEAVE_API(ret_value)
} /* end H5Dwrite_multi() */
/*-------------------------------------------------------------------------
* Function: H5Dwrite_multi_async
*
* Purpose: Asynchronously write dataset elements to multiple
* datasets.
*
* Return: Non-negative on success/Negative on failure
*
*-------------------------------------------------------------------------
*/
herr_t
H5Dwrite_multi_async(const char *app_file, const char *app_func, unsigned app_line, size_t count,
hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[], hid_t file_space_id[],
hid_t dxpl_id, const void *buf[], hid_t es_id)
{
H5VL_object_t *vol_obj = NULL; /* Dataset VOL object */
void *token = NULL; /* Request token for async operation */
void **token_ptr = H5_REQUEST_NULL; /* Pointer to request token for async operation */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_API(FAIL)
H5TRACE11("e", "*s*sIuz*i*i*i*ii**xi", app_file, app_func, app_line, count, dset_id, mem_type_id,
mem_space_id, file_space_id, dxpl_id, buf, es_id);
/* Set up request token pointer for asynchronous operation */
if (H5ES_NONE != es_id)
token_ptr = &token; /* Point at token for VOL connector to set up */
/* Write the data */
if (H5D__write_api_common(count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf,
token_ptr, &vol_obj) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't asynchronously write data")
/* If a token was created, add the token to the event set */
if (NULL != token)
/* clang-format off */
if (H5ES_insert(es_id, vol_obj->connector, token,
H5ARG_TRACE11(__func__, "*s*sIuz*i*i*i*ii**xi", app_file, app_func, app_line, count, dset_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, es_id)) < 0)
/* clang-format on */
HGOTO_ERROR(H5E_DATASET, H5E_CANTINSERT, FAIL, "can't insert token into event set")
done:
FUNC_LEAVE_API(ret_value)
} /* end H5Dwrite_multi_async() */
/*-------------------------------------------------------------------------
* Function: H5Dwrite_chunk
*

File diff suppressed because it is too large Load Diff

View File

@ -63,15 +63,16 @@ typedef struct H5D_compact_iovv_memmanage_ud_t {
/* Layout operation callbacks */
static herr_t H5D__compact_construct(H5F_t *f, H5D_t *dset);
static hbool_t H5D__compact_is_space_alloc(const H5O_storage_t *storage);
static herr_t H5D__compact_io_init(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t *cm);
static herr_t H5D__compact_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
static herr_t H5D__compact_iovv_memmanage_cb(hsize_t dst_off, hsize_t src_off, size_t len, void *_udata);
static ssize_t H5D__compact_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_size_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_size_arr[], hsize_t mem_offset_arr[]);
static ssize_t H5D__compact_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_size_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_size_arr[], hsize_t mem_offset_arr[]);
static ssize_t H5D__compact_readvv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
size_t dset_max_nseq, size_t *dset_curr_seq, size_t dset_size_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_size_arr[], hsize_t mem_offset_arr[]);
static ssize_t H5D__compact_writevv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
size_t dset_max_nseq, size_t *dset_curr_seq, size_t dset_size_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_size_arr[], hsize_t mem_offset_arr[]);
static herr_t H5D__compact_flush(H5D_t *dset);
static herr_t H5D__compact_dest(H5D_t *dset);
@ -86,17 +87,14 @@ const H5D_layout_ops_t H5D_LOPS_COMPACT[1] = {{
H5D__compact_is_space_alloc, /* is_space_alloc */
NULL, /* is_data_cached */
H5D__compact_io_init, /* io_init */
NULL, /* mdio_init */
H5D__contig_read, /* ser_read */
H5D__contig_write, /* ser_write */
#ifdef H5_HAVE_PARALLEL
NULL, /* par_read */
NULL, /* par_write */
#endif
H5D__compact_readvv, /* readvv */
H5D__compact_writevv, /* writevv */
H5D__compact_flush, /* flush */
NULL, /* io_term */
H5D__compact_dest /* dest */
H5D__compact_readvv, /* readvv */
H5D__compact_writevv, /* writevv */
H5D__compact_flush, /* flush */
NULL, /* io_term */
H5D__compact_dest /* dest */
}};
/*******************/
@ -247,14 +245,15 @@ H5D__compact_is_space_alloc(const H5O_storage_t H5_ATTR_UNUSED *storage)
*-------------------------------------------------------------------------
*/
static herr_t
H5D__compact_io_init(H5D_io_info_t *io_info, const H5D_type_info_t H5_ATTR_UNUSED *type_info,
hsize_t H5_ATTR_UNUSED nelmts, H5S_t H5_ATTR_UNUSED *file_space,
H5S_t H5_ATTR_UNUSED *mem_space, H5D_chunk_map_t H5_ATTR_UNUSED *cm)
H5D__compact_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo)
{
FUNC_ENTER_PACKAGE_NOERR
io_info->store->compact.buf = io_info->dset->shared->layout.storage.u.compact.buf;
io_info->store->compact.dirty = &io_info->dset->shared->layout.storage.u.compact.dirty;
dinfo->store->compact.buf = dinfo->dset->shared->layout.storage.u.compact.buf;
dinfo->store->compact.dirty = &dinfo->dset->shared->layout.storage.u.compact.dirty;
/* Disable selection I/O */
io_info->use_select_io = FALSE;
FUNC_LEAVE_NOAPI(SUCCEED)
} /* end H5D__compact_io_init() */
@ -320,15 +319,17 @@ done:
*-------------------------------------------------------------------------
*/
static ssize_t
H5D__compact_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_size_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_size_arr[], hsize_t mem_offset_arr[])
H5D__compact_readvv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_size_arr[], hsize_t dset_offset_arr[],
size_t mem_max_nseq, size_t *mem_curr_seq, size_t mem_size_arr[],
hsize_t mem_offset_arr[])
{
ssize_t ret_value = -1; /* Return value */
FUNC_ENTER_PACKAGE
HDassert(io_info);
HDassert(dset_info);
/* Check if file driver wishes to do its own memory management */
if (H5F_SHARED_HAS_FEATURE(io_info->f_sh, H5FD_FEAT_MEMMANAGE)) {
@ -336,8 +337,8 @@ H5D__compact_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *
/* Set up udata for memory copy operation */
udata.f_sh = io_info->f_sh;
udata.dstbuf = io_info->u.rbuf;
udata.srcbuf = io_info->store->compact.buf;
udata.dstbuf = dset_info->buf.vp;
udata.srcbuf = dset_info->store->compact.buf;
/* Request that file driver does the memory copy */
if ((ret_value = H5VM_opvv(mem_max_nseq, mem_curr_seq, mem_size_arr, mem_offset_arr, dset_max_nseq,
@ -347,8 +348,8 @@ H5D__compact_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *
}
else {
/* Use the vectorized memory copy routine to do actual work */
if ((ret_value = H5VM_memcpyvv(io_info->u.rbuf, mem_max_nseq, mem_curr_seq, mem_size_arr,
mem_offset_arr, io_info->store->compact.buf, dset_max_nseq,
if ((ret_value = H5VM_memcpyvv(dset_info->buf.vp, mem_max_nseq, mem_curr_seq, mem_size_arr,
mem_offset_arr, dset_info->store->compact.buf, dset_max_nseq,
dset_curr_seq, dset_size_arr, dset_offset_arr)) < 0)
HGOTO_ERROR(H5E_IO, H5E_WRITEERROR, FAIL, "vectorized memcpy failed")
}
@ -379,15 +380,17 @@ done:
*-------------------------------------------------------------------------
*/
static ssize_t
H5D__compact_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_size_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_size_arr[], hsize_t mem_offset_arr[])
H5D__compact_writevv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_size_arr[], hsize_t dset_offset_arr[],
size_t mem_max_nseq, size_t *mem_curr_seq, size_t mem_size_arr[],
hsize_t mem_offset_arr[])
{
ssize_t ret_value = -1; /* Return value */
FUNC_ENTER_PACKAGE
HDassert(io_info);
HDassert(dset_info);
/* Check if file driver wishes to do its own memory management */
if (H5F_SHARED_HAS_FEATURE(io_info->f_sh, H5FD_FEAT_MEMMANAGE)) {
@ -395,8 +398,8 @@ H5D__compact_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t
/* Set up udata for memory copy operation */
udata.f_sh = io_info->f_sh;
udata.dstbuf = io_info->store->compact.buf;
udata.srcbuf = io_info->u.wbuf;
udata.dstbuf = dset_info->store->compact.buf;
udata.srcbuf = dset_info->buf.cvp;
/* Request that file driver does the memory copy */
if ((ret_value = H5VM_opvv(dset_max_nseq, dset_curr_seq, dset_size_arr, dset_offset_arr, mem_max_nseq,
@ -406,14 +409,14 @@ H5D__compact_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t
}
else {
/* Use the vectorized memory copy routine to do actual work */
if ((ret_value = H5VM_memcpyvv(io_info->store->compact.buf, dset_max_nseq, dset_curr_seq,
dset_size_arr, dset_offset_arr, io_info->u.wbuf, mem_max_nseq,
if ((ret_value = H5VM_memcpyvv(dset_info->store->compact.buf, dset_max_nseq, dset_curr_seq,
dset_size_arr, dset_offset_arr, dset_info->buf.cvp, mem_max_nseq,
mem_curr_seq, mem_size_arr, mem_offset_arr)) < 0)
HGOTO_ERROR(H5E_IO, H5E_WRITEERROR, FAIL, "vectorized memcpy failed")
}
/* Mark the compact dataset's buffer as dirty */
*io_info->store->compact.dirty = TRUE;
*dset_info->store->compact.dirty = TRUE;
done:
FUNC_LEAVE_NOAPI(ret_value)

View File

@ -91,19 +91,24 @@ typedef struct H5D_contig_writevv_ud_t {
/* Layout operation callbacks */
static herr_t H5D__contig_construct(H5F_t *f, H5D_t *dset);
static herr_t H5D__contig_init(H5F_t *f, const H5D_t *dset, hid_t dapl_id);
static herr_t H5D__contig_io_init(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t *cm);
static ssize_t H5D__contig_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_offset_arr[]);
static ssize_t H5D__contig_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_offset_arr[]);
static herr_t H5D__contig_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
static herr_t H5D__contig_mdio_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
static ssize_t H5D__contig_readvv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dinfo,
size_t dset_max_nseq, size_t *dset_curr_seq, size_t dset_len_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_offset_arr[]);
static ssize_t H5D__contig_writevv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dinfo,
size_t dset_max_nseq, size_t *dset_curr_seq, size_t dset_len_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_offset_arr[]);
static herr_t H5D__contig_flush(H5D_t *dset);
static herr_t H5D__contig_io_term(H5D_io_info_t *io_info, H5D_dset_io_info_t *di);
/* Helper routines */
static herr_t H5D__contig_write_one(H5D_io_info_t *io_info, hsize_t offset, size_t size);
static htri_t H5D__contig_may_use_select_io(const H5D_io_info_t *io_info, H5D_io_op_type_t op_type);
static herr_t H5D__contig_write_one(H5D_io_info_t *io_info, H5D_dset_io_info_t *dset_info, hsize_t offset,
size_t size);
static htri_t H5D__contig_may_use_select_io(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
H5D_io_op_type_t op_type);
/*********************/
/* Package Variables */
@ -116,17 +121,14 @@ const H5D_layout_ops_t H5D_LOPS_CONTIG[1] = {{
H5D__contig_is_space_alloc, /* is_space_alloc */
H5D__contig_is_data_cached, /* is_data_cached */
H5D__contig_io_init, /* io_init */
H5D__contig_mdio_init, /* mdio_init */
H5D__contig_read, /* ser_read */
H5D__contig_write, /* ser_write */
#ifdef H5_HAVE_PARALLEL
H5D__contig_collective_read, /* par_read */
H5D__contig_collective_write, /* par_write */
#endif
H5D__contig_readvv, /* readvv */
H5D__contig_writevv, /* writevv */
H5D__contig_flush, /* flush */
NULL, /* io_term */
NULL /* dest */
H5D__contig_readvv, /* readvv */
H5D__contig_writevv, /* writevv */
H5D__contig_flush, /* flush */
H5D__contig_io_term, /* io_term */
NULL /* dest */
}};
/*******************/
@ -139,6 +141,9 @@ H5FL_BLK_DEFINE(sieve_buf);
/* Declare extern the free list to manage blocks of type conversion data */
H5FL_BLK_EXTERN(type_conv);
/* Declare extern the free list to manage the H5D_piece_info_t struct */
H5FL_EXTERN(H5D_piece_info_t);
/*-------------------------------------------------------------------------
* Function: H5D__contig_alloc
*
@ -183,15 +188,15 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5D__contig_fill(const H5D_io_info_t *io_info)
H5D__contig_fill(H5D_t *dset)
{
const H5D_t *dset = io_info->dset; /* the dataset pointer */
H5D_io_info_t ioinfo; /* Dataset I/O info */
H5D_storage_t store; /* Union of storage info for dataset */
hssize_t snpoints; /* Number of points in space (for error checking) */
size_t npoints; /* Number of points in space */
hsize_t offset; /* Offset of dataset */
size_t max_temp_buf; /* Maximum size of temporary buffer */
H5D_io_info_t ioinfo; /* Dataset I/O info */
H5D_dset_io_info_t dset_info; /* Dset info */
H5D_storage_t store; /* Union of storage info for dataset */
hssize_t snpoints; /* Number of points in space (for error checking) */
size_t npoints; /* Number of points in space */
hsize_t offset; /* Offset of dataset */
size_t max_temp_buf; /* Maximum size of temporary buffer */
#ifdef H5_HAVE_PARALLEL
MPI_Comm mpi_comm = MPI_COMM_NULL; /* MPI communicator for file */
int mpi_rank = (-1); /* This process's rank */
@ -252,7 +257,14 @@ H5D__contig_fill(const H5D_io_info_t *io_info)
offset = 0;
/* Simple setup for dataset I/O info struct */
H5D_BUILD_IO_INFO_WRT(&ioinfo, dset, &store, fb_info.fill_buf);
ioinfo.op_type = H5D_IO_OP_WRITE;
dset_info.dset = (H5D_t *)dset;
dset_info.store = &store;
dset_info.buf.cvp = fb_info.fill_buf;
dset_info.mem_space = NULL;
ioinfo.dsets_info = &dset_info;
ioinfo.f_sh = H5F_SHARED(dset->oloc.file);
/*
* Fill the entire current extent with the fill value. We can do
@ -281,7 +293,7 @@ H5D__contig_fill(const H5D_io_info_t *io_info)
/* Write the chunks out from only one process */
/* !! Use the internal "independent" DXPL!! -QAK */
if (H5_PAR_META_WRITE == mpi_rank) {
if (H5D__contig_write_one(&ioinfo, offset, size) < 0) {
if (H5D__contig_write_one(&ioinfo, &dset_info, offset, size) < 0) {
/* If writing fails, push an error and stop writing, but
* still participate in following MPI_Barrier.
*/
@ -297,7 +309,7 @@ H5D__contig_fill(const H5D_io_info_t *io_info)
else {
#endif /* H5_HAVE_PARALLEL */
H5_CHECK_OVERFLOW(size, size_t, hsize_t);
if (H5D__contig_write_one(&ioinfo, offset, size) < 0)
if (H5D__contig_write_one(&ioinfo, &dset_info, offset, size) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to write fill value to dataset")
#ifdef H5_HAVE_PARALLEL
} /* end else */
@ -562,32 +574,159 @@ H5D__contig_is_data_cached(const H5D_shared_t *shared_dset)
*
* Return: Non-negative on success/Negative on failure
*
* Programmer: Quincey Koziol
* Thursday, March 20, 2008
* Programmer: Jonathan Kim
*-------------------------------------------------------------------------
*/
static herr_t
H5D__contig_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo)
{
H5D_t *dataset = dinfo->dset; /* Local pointer to dataset info */
hssize_t old_offset[H5O_LAYOUT_NDIMS]; /* Old selection offset */
htri_t file_space_normalized = FALSE; /* File dataspace was normalized */
int sf_ndims; /* The number of dimensions of the file dataspace (signed) */
htri_t use_selection_io = FALSE; /* Whether to use selection I/O */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
dinfo->store->contig.dset_addr = dataset->shared->layout.storage.u.contig.addr;
dinfo->store->contig.dset_size = dataset->shared->layout.storage.u.contig.size;
/* Initialize piece info */
dinfo->layout_io_info.contig_piece_info = NULL;
/* Get layout for dataset */
dinfo->layout = &(dataset->shared->layout);
/* Get dim number and dimensionality for each dataspace */
if ((sf_ndims = H5S_GET_EXTENT_NDIMS(dinfo->file_space)) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTGET, FAIL, "unable to get dimension number")
/* Normalize hyperslab selections by adjusting them by the offset */
/* (It might be worthwhile to normalize both the file and memory dataspaces
* before any (contiguous, chunked, etc) file I/O operation, in order to
* speed up hyperslab calculations by removing the extra checks and/or
* additions involving the offset and the hyperslab selection -QAK)
*/
if ((file_space_normalized = H5S_hyper_normalize_offset(dinfo->file_space, old_offset)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_BADSELECT, FAIL, "unable to normalize dataspace by offset")
/* if selected elements exist */
if (dinfo->nelmts) {
int u;
H5D_piece_info_t *new_piece_info; /* piece information to insert into skip list */
/* Get copy of dset file_space, so it can be changed temporarily
* purpose
* This tmp_fspace allows multiple write before close dset */
H5S_t *tmp_fspace; /* Temporary file dataspace */
/* Create "temporary" chunk for selection operations (copy file space) */
if (NULL == (tmp_fspace = H5S_copy(dinfo->file_space, TRUE, FALSE)))
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTCOPY, FAIL, "unable to copy memory space")
/* Add temporary chunk to the list of pieces */
/* collect piece_info into Skip List */
/* Allocate the file & memory chunk information */
if (NULL == (new_piece_info = H5FL_MALLOC(H5D_piece_info_t))) {
(void)H5S_close(tmp_fspace);
HGOTO_ERROR(H5E_RESOURCE, H5E_NOSPACE, FAIL, "can't allocate chunk info")
} /* end if */
/* Set the piece index */
new_piece_info->index = 0;
/* Set the file chunk dataspace */
new_piece_info->fspace = tmp_fspace;
new_piece_info->fspace_shared = FALSE;
/* Set the memory chunk dataspace */
/* same as one chunk, just use dset mem space */
new_piece_info->mspace = dinfo->mem_space;
/* set true for sharing mem space with dset, which means
* fspace gets free by application H5Sclose(), and
* doesn't require providing layout_ops.io_term() for H5D_LOPS_CONTIG.
*/
new_piece_info->mspace_shared = TRUE;
/* Set the number of points */
new_piece_info->piece_points = dinfo->nelmts;
/* Copy the piece's coordinates */
for (u = 0; u < sf_ndims; u++)
new_piece_info->scaled[u] = 0;
new_piece_info->scaled[sf_ndims] = 0;
/* make connection to related dset info from this piece_info */
new_piece_info->dset_info = dinfo;
/* get dset file address for piece */
new_piece_info->faddr = dinfo->dset->shared->layout.storage.u.contig.addr;
/* Save piece to dataset info struct so it is freed at the end of the
* operation */
dinfo->layout_io_info.contig_piece_info = new_piece_info;
/* Add piece to piece_count */
io_info->piece_count++;
} /* end if */
/* Check if we're performing selection I/O if it hasn't been disabled
* already */
if (io_info->use_select_io) {
if ((use_selection_io = H5D__contig_may_use_select_io(io_info, dinfo, H5D_IO_OP_READ)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't check if selection I/O is possible")
io_info->use_select_io = (hbool_t)use_selection_io;
}
done:
if (ret_value < 0) {
if (H5D__contig_io_term(io_info, dinfo) < 0)
HDONE_ERROR(H5E_DATASPACE, H5E_CANTRELEASE, FAIL, "unable to release dataset I/O info")
} /* end if */
if (file_space_normalized) {
/* (Casting away const OK -QAK) */
if (H5S_hyper_denormalize_offset(dinfo->file_space, old_offset) < 0)
HDONE_ERROR(H5E_DATASET, H5E_BADSELECT, FAIL, "unable to normalize dataspace by offset")
} /* end if */
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5D__contig_io_init() */
/*-------------------------------------------------------------------------
* Function: H5D__contig_mdio_init
*
* Purpose: Performs second phase of initialization for multi-dataset
* I/O. Currently just adds data block to sel_pieces.
*
* Return: Non-negative on success/Negative on failure
*
*-------------------------------------------------------------------------
*/
static herr_t
H5D__contig_io_init(H5D_io_info_t *io_info, const H5D_type_info_t H5_ATTR_UNUSED *type_info,
hsize_t H5_ATTR_UNUSED nelmts, H5S_t H5_ATTR_UNUSED *file_space,
H5S_t H5_ATTR_UNUSED *mem_space, H5D_chunk_map_t H5_ATTR_UNUSED *cm)
H5D__contig_mdio_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo)
{
htri_t use_selection_io = FALSE; /* Whether to use selection I/O */
htri_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE_NOERR
FUNC_ENTER_PACKAGE
/* Add piece if it exists */
if (dinfo->layout_io_info.contig_piece_info) {
HDassert(io_info->sel_pieces);
HDassert(io_info->pieces_added < io_info->piece_count);
io_info->store->contig.dset_addr = io_info->dset->shared->layout.storage.u.contig.addr;
io_info->store->contig.dset_size = io_info->dset->shared->layout.storage.u.contig.size;
/* Add contiguous data block to sel_pieces */
io_info->sel_pieces[io_info->pieces_added] = dinfo->layout_io_info.contig_piece_info;
/* Check if we're performing selection I/O */
if ((use_selection_io = H5D__contig_may_use_select_io(io_info, H5D_IO_OP_READ)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't check if selection I/O is possible")
io_info->use_select_io = (hbool_t)use_selection_io;
/* Update pieces_added */
io_info->pieces_added++;
}
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5D__contig_io_init() */
FUNC_LEAVE_NOAPI(SUCCEED)
} /* end H5D__contig_mdio_init() */
/*-------------------------------------------------------------------------
* Function: H5D__contig_may_use_select_io
@ -603,7 +742,8 @@ done:
*-------------------------------------------------------------------------
*/
static htri_t
H5D__contig_may_use_select_io(const H5D_io_info_t *io_info, H5D_io_op_type_t op_type)
H5D__contig_may_use_select_io(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
H5D_io_op_type_t op_type)
{
const H5D_t *dataset = NULL; /* Local pointer to dataset info */
htri_t ret_value = FAIL; /* Return value */
@ -612,24 +752,25 @@ H5D__contig_may_use_select_io(const H5D_io_info_t *io_info, H5D_io_op_type_t op_
/* Sanity check */
HDassert(io_info);
HDassert(io_info->dset);
HDassert(dset_info);
HDassert(dset_info->dset);
HDassert(op_type == H5D_IO_OP_READ || op_type == H5D_IO_OP_WRITE);
dataset = io_info->dset;
dataset = dset_info->dset;
/* Don't use selection I/O if it's globally disabled, if there is a type
* conversion, or if it's not a contiguous dataset, or if the sieve buffer
* exists (write) or is dirty (read) */
if (!H5_use_selection_io_g || io_info->io_ops.single_read != H5D__select_read ||
io_info->layout_ops.readvv != H5D__contig_readvv ||
if (dset_info->io_ops.single_read != H5D__select_read ||
dset_info->layout_ops.readvv != H5D__contig_readvv ||
(op_type == H5D_IO_OP_READ && dataset->shared->cache.contig.sieve_dirty) ||
(op_type == H5D_IO_OP_WRITE && dataset->shared->cache.contig.sieve_buf))
ret_value = FALSE;
else {
hbool_t page_buf_enabled;
HDassert(io_info->io_ops.single_write == H5D__select_write);
HDassert(io_info->layout_ops.writevv == H5D__contig_writevv);
HDassert(dset_info->io_ops.single_write == H5D__select_write);
HDassert(dset_info->layout_ops.writevv == H5D__contig_writevv);
/* Check if the page buffer is enabled */
if (H5PB_enabled(io_info->f_sh, H5FD_MEM_DRAW, &page_buf_enabled) < 0)
@ -657,8 +798,7 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5D__contig_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts, H5S_t *file_space,
H5S_t *mem_space, H5D_chunk_map_t H5_ATTR_UNUSED *fm)
H5D__contig_read(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo)
{
herr_t ret_value = SUCCEED; /* Return value */
@ -666,25 +806,49 @@ H5D__contig_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize
/* Sanity check */
HDassert(io_info);
HDassert(io_info->u.rbuf);
HDassert(type_info);
HDassert(mem_space);
HDassert(file_space);
HDassert(dinfo);
HDassert(dinfo->buf.vp);
HDassert(dinfo->mem_space);
HDassert(dinfo->file_space);
if (io_info->use_select_io) {
size_t dst_type_size = type_info->dst_type_size;
/* Only perform I/O if not performing multi dataset I/O with selection
* I/O, otherwise the higher level will handle it after all datasets
* have been processed */
if (H5D_LAYOUT_CB_PERFORM_IO(io_info)) {
size_t dst_type_size = dinfo->type_info.dst_type_size;
/* Issue selection I/O call (we can skip the page buffer because we've
* already verified it won't be used, and the metadata accumulator
* because this is raw data) */
if (H5F_shared_select_read(H5F_SHARED(io_info->dset->oloc.file), H5FD_MEM_DRAW, nelmts > 0 ? 1 : 0,
&mem_space, &file_space, &(io_info->store->contig.dset_addr),
&dst_type_size, &(io_info->u.rbuf)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "contiguous selection read failed")
/* Issue selection I/O call (we can skip the page buffer because we've
* already verified it won't be used, and the metadata accumulator
* because this is raw data) */
if (H5F_shared_select_read(H5F_SHARED(dinfo->dset->oloc.file), H5FD_MEM_DRAW,
dinfo->nelmts > 0 ? 1 : 0, &dinfo->mem_space, &dinfo->file_space,
&(dinfo->store->contig.dset_addr), &dst_type_size,
&(dinfo->buf.vp)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "contiguous selection read failed")
}
else {
if (dinfo->layout_io_info.contig_piece_info) {
/* Add to mdset selection I/O arrays */
HDassert(io_info->mem_spaces);
HDassert(io_info->file_spaces);
HDassert(io_info->addrs);
HDassert(io_info->element_sizes);
HDassert(io_info->rbufs);
HDassert(io_info->pieces_added < io_info->piece_count);
io_info->mem_spaces[io_info->pieces_added] = dinfo->mem_space;
io_info->file_spaces[io_info->pieces_added] = dinfo->file_space;
io_info->addrs[io_info->pieces_added] = dinfo->store->contig.dset_addr;
io_info->element_sizes[io_info->pieces_added] = dinfo->type_info.src_type_size;
io_info->rbufs[io_info->pieces_added] = dinfo->buf.vp;
io_info->pieces_added++;
}
}
} /* end if */
else
/* Read data through legacy (non-selection I/O) pathway */
if ((io_info->io_ops.single_read)(io_info, type_info, nelmts, file_space, mem_space) < 0)
if ((dinfo->io_ops.single_read)(io_info, dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "contiguous read failed")
done:
@ -704,8 +868,7 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5D__contig_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts, H5S_t *file_space,
H5S_t *mem_space, H5D_chunk_map_t H5_ATTR_UNUSED *fm)
H5D__contig_write(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo)
{
herr_t ret_value = SUCCEED; /* Return value */
@ -713,25 +876,49 @@ H5D__contig_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsiz
/* Sanity check */
HDassert(io_info);
HDassert(io_info->u.wbuf);
HDassert(type_info);
HDassert(mem_space);
HDassert(file_space);
HDassert(dinfo);
HDassert(dinfo->buf.cvp);
HDassert(dinfo->mem_space);
HDassert(dinfo->file_space);
if (io_info->use_select_io) {
size_t dst_type_size = type_info->dst_type_size;
/* Only perform I/O if not performing multi dataset I/O with selection
* I/O, otherwise the higher level will handle it after all datasets
* have been processed */
if (H5D_LAYOUT_CB_PERFORM_IO(io_info)) {
size_t dst_type_size = dinfo->type_info.dst_type_size;
/* Issue selection I/O call (we can skip the page buffer because we've
* already verified it won't be used, and the metadata accumulator
* because this is raw data) */
if (H5F_shared_select_write(H5F_SHARED(io_info->dset->oloc.file), H5FD_MEM_DRAW, nelmts > 0 ? 1 : 0,
&mem_space, &file_space, &(io_info->store->contig.dset_addr),
&dst_type_size, &(io_info->u.wbuf)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "contiguous selection write failed")
/* Issue selection I/O call (we can skip the page buffer because we've
* already verified it won't be used, and the metadata accumulator
* because this is raw data) */
if (H5F_shared_select_write(H5F_SHARED(dinfo->dset->oloc.file), H5FD_MEM_DRAW,
dinfo->nelmts > 0 ? 1 : 0, &dinfo->mem_space, &dinfo->file_space,
&(dinfo->store->contig.dset_addr), &dst_type_size,
&(dinfo->buf.cvp)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "contiguous selection write failed")
}
else {
if (dinfo->layout_io_info.contig_piece_info) {
/* Add to mdset selection I/O arrays */
HDassert(io_info->mem_spaces);
HDassert(io_info->file_spaces);
HDassert(io_info->addrs);
HDassert(io_info->element_sizes);
HDassert(io_info->wbufs);
HDassert(io_info->pieces_added < io_info->piece_count);
io_info->mem_spaces[io_info->pieces_added] = dinfo->mem_space;
io_info->file_spaces[io_info->pieces_added] = dinfo->file_space;
io_info->addrs[io_info->pieces_added] = dinfo->store->contig.dset_addr;
io_info->element_sizes[io_info->pieces_added] = dinfo->type_info.dst_type_size;
io_info->wbufs[io_info->pieces_added] = dinfo->buf.cvp;
io_info->pieces_added++;
}
}
} /* end if */
else
/* Write data through legacy (non-selection I/O) pathway */
if ((io_info->io_ops.single_write)(io_info, type_info, nelmts, file_space, mem_space) < 0)
if ((dinfo->io_ops.single_write)(io_info, dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "contiguous write failed")
done:
@ -753,7 +940,7 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__contig_write_one(H5D_io_info_t *io_info, hsize_t offset, size_t size)
H5D__contig_write_one(H5D_io_info_t *io_info, H5D_dset_io_info_t *dset_info, hsize_t offset, size_t size)
{
hsize_t dset_off = offset; /* Offset in dataset */
size_t dset_len = size; /* Length in dataset */
@ -767,7 +954,7 @@ H5D__contig_write_one(H5D_io_info_t *io_info, hsize_t offset, size_t size)
HDassert(io_info);
if (H5D__contig_writevv(io_info, (size_t)1, &dset_curr_seq, &dset_len, &dset_off, (size_t)1,
if (H5D__contig_writevv(io_info, dset_info, (size_t)1, &dset_curr_seq, &dset_len, &dset_off, (size_t)1,
&mem_curr_seq, &mem_len, &mem_off) < 0)
HGOTO_ERROR(H5E_IO, H5E_WRITEERROR, FAIL, "vector write failed")
@ -990,9 +1177,9 @@ done:
*-------------------------------------------------------------------------
*/
static ssize_t
H5D__contig_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_off_arr[])
H5D__contig_readvv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_off_arr[])
{
ssize_t ret_value = -1; /* Return value */
@ -1000,6 +1187,7 @@ H5D__contig_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *d
/* Check args */
HDassert(io_info);
HDassert(dset_info);
HDassert(dset_curr_seq);
HDassert(dset_len_arr);
HDassert(dset_off_arr);
@ -1013,9 +1201,9 @@ H5D__contig_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *d
/* Set up user data for H5VM_opvv() */
udata.f_sh = io_info->f_sh;
udata.dset_contig = &(io_info->dset->shared->cache.contig);
udata.store_contig = &(io_info->store->contig);
udata.rbuf = (unsigned char *)io_info->u.rbuf;
udata.dset_contig = &(dset_info->dset->shared->cache.contig);
udata.store_contig = &(dset_info->store->contig);
udata.rbuf = (unsigned char *)dset_info->buf.vp;
/* Call generic sequence operation routine */
if ((ret_value =
@ -1028,8 +1216,8 @@ H5D__contig_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *d
/* Set up user data for H5VM_opvv() */
udata.f_sh = io_info->f_sh;
udata.dset_addr = io_info->store->contig.dset_addr;
udata.rbuf = (unsigned char *)io_info->u.rbuf;
udata.dset_addr = dset_info->store->contig.dset_addr;
udata.rbuf = (unsigned char *)dset_info->buf.vp;
/* Call generic sequence operation routine */
if ((ret_value = H5VM_opvv(dset_max_nseq, dset_curr_seq, dset_len_arr, dset_off_arr, mem_max_nseq,
@ -1308,9 +1496,9 @@ done:
*-------------------------------------------------------------------------
*/
static ssize_t
H5D__contig_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_off_arr[])
H5D__contig_writevv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_off_arr[])
{
ssize_t ret_value = -1; /* Return value (Size of sequence in bytes) */
@ -1318,6 +1506,7 @@ H5D__contig_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *
/* Check args */
HDassert(io_info);
HDassert(dset_info);
HDassert(dset_curr_seq);
HDassert(dset_len_arr);
HDassert(dset_off_arr);
@ -1331,9 +1520,9 @@ H5D__contig_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *
/* Set up user data for H5VM_opvv() */
udata.f_sh = io_info->f_sh;
udata.dset_contig = &(io_info->dset->shared->cache.contig);
udata.store_contig = &(io_info->store->contig);
udata.wbuf = (const unsigned char *)io_info->u.wbuf;
udata.dset_contig = &(dset_info->dset->shared->cache.contig);
udata.store_contig = &(dset_info->store->contig);
udata.wbuf = (const unsigned char *)dset_info->buf.cvp;
/* Call generic sequence operation routine */
if ((ret_value =
@ -1346,8 +1535,8 @@ H5D__contig_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *
/* Set up user data for H5VM_opvv() */
udata.f_sh = io_info->f_sh;
udata.dset_addr = io_info->store->contig.dset_addr;
udata.wbuf = (const unsigned char *)io_info->u.wbuf;
udata.dset_addr = dset_info->store->contig.dset_addr;
udata.wbuf = (const unsigned char *)dset_info->buf.cvp;
/* Call generic sequence operation routine */
if ((ret_value = H5VM_opvv(dset_max_nseq, dset_curr_seq, dset_len_arr, dset_off_arr, mem_max_nseq,
@ -1390,6 +1579,35 @@ done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5D__contig_flush() */
/*-------------------------------------------------------------------------
* Function: H5D__contig_io_term
*
* Purpose: Destroy I/O operation information.
*
* Return: Non-negative on success/Negative on failure
*
*-------------------------------------------------------------------------
*/
static herr_t
H5D__contig_io_term(H5D_io_info_t H5_ATTR_UNUSED *io_info, H5D_dset_io_info_t *di)
{
herr_t ret_value = SUCCEED; /*return value */
FUNC_ENTER_PACKAGE
HDassert(di);
/* Free piece info */
if (di->layout_io_info.contig_piece_info) {
if (H5D__free_piece_info(di->layout_io_info.contig_piece_info, NULL, NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTFREE, FAIL, "can't free piece info")
di->layout_io_info.contig_piece_info = NULL;
}
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5D__contig_io_term() */
/*-------------------------------------------------------------------------
* Function: H5D__contig_copy
*

View File

@ -61,14 +61,15 @@ typedef struct H5D_efl_writevv_ud_t {
/* Layout operation callbacks */
static herr_t H5D__efl_construct(H5F_t *f, H5D_t *dset);
static herr_t H5D__efl_io_init(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t *cm);
static ssize_t H5D__efl_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_offset_arr[]);
static ssize_t H5D__efl_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_offset_arr[]);
static herr_t H5D__efl_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
static ssize_t H5D__efl_readvv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
size_t dset_max_nseq, size_t *dset_curr_seq, size_t dset_len_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_offset_arr[]);
static ssize_t H5D__efl_writevv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
size_t dset_max_nseq, size_t *dset_curr_seq, size_t dset_len_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_offset_arr[]);
/* Helper routines */
static herr_t H5D__efl_read(const H5O_efl_t *efl, const H5D_t *dset, haddr_t addr, size_t size, uint8_t *buf);
@ -86,17 +87,14 @@ const H5D_layout_ops_t H5D_LOPS_EFL[1] = {{
H5D__efl_is_space_alloc, /* is_space_alloc */
NULL, /* is_data_cached */
H5D__efl_io_init, /* io_init */
NULL, /* mdio_init */
H5D__contig_read, /* ser_read */
H5D__contig_write, /* ser_write */
#ifdef H5_HAVE_PARALLEL
NULL, /* par_read */
NULL, /* par_write */
#endif
H5D__efl_readvv, /* readvv */
H5D__efl_writevv, /* writevv */
NULL, /* flush */
NULL, /* io_term */
NULL /* dest */
H5D__efl_readvv, /* readvv */
H5D__efl_writevv, /* writevv */
NULL, /* flush */
NULL, /* io_term */
NULL /* dest */
}};
/*******************/
@ -209,13 +207,14 @@ H5D__efl_is_space_alloc(const H5O_storage_t H5_ATTR_UNUSED *storage)
*-------------------------------------------------------------------------
*/
static herr_t
H5D__efl_io_init(H5D_io_info_t *io_info, const H5D_type_info_t H5_ATTR_UNUSED *type_info,
hsize_t H5_ATTR_UNUSED nelmts, H5S_t H5_ATTR_UNUSED *file_space,
H5S_t H5_ATTR_UNUSED *mem_space, H5D_chunk_map_t H5_ATTR_UNUSED *cm)
H5D__efl_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo)
{
FUNC_ENTER_PACKAGE_NOERR
H5MM_memcpy(&io_info->store->efl, &(io_info->dset->shared->dcpl_cache.efl), sizeof(H5O_efl_t));
H5MM_memcpy(&dinfo->store->efl, &(dinfo->dset->shared->dcpl_cache.efl), sizeof(H5O_efl_t));
/* Disable selection I/O */
io_info->use_select_io = FALSE;
FUNC_LEAVE_NOAPI(SUCCEED)
} /* end H5D__efl_io_init() */
@ -443,9 +442,9 @@ done:
*-------------------------------------------------------------------------
*/
static ssize_t
H5D__efl_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_off_arr[])
H5D__efl_readvv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_off_arr[])
{
H5D_efl_readvv_ud_t udata; /* User data for H5VM_opvv() operator */
ssize_t ret_value = -1; /* Return value (Total size of sequence in bytes) */
@ -454,10 +453,11 @@ H5D__efl_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset
/* Check args */
HDassert(io_info);
HDassert(io_info->store->efl.nused > 0);
HDassert(io_info->u.rbuf);
HDassert(io_info->dset);
HDassert(io_info->dset->shared);
HDassert(dset_info);
HDassert(dset_info->store->efl.nused > 0);
HDassert(dset_info->buf.vp);
HDassert(dset_info->dset);
HDassert(dset_info->dset->shared);
HDassert(dset_curr_seq);
HDassert(dset_len_arr);
HDassert(dset_off_arr);
@ -466,9 +466,9 @@ H5D__efl_readvv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset
HDassert(mem_off_arr);
/* Set up user data for H5VM_opvv() */
udata.efl = &(io_info->store->efl);
udata.dset = io_info->dset;
udata.rbuf = (unsigned char *)io_info->u.rbuf;
udata.efl = &(dset_info->store->efl);
udata.dset = dset_info->dset;
udata.rbuf = (unsigned char *)dset_info->buf.vp;
/* Call generic sequence operation routine */
if ((ret_value = H5VM_opvv(dset_max_nseq, dset_curr_seq, dset_len_arr, dset_off_arr, mem_max_nseq,
@ -523,9 +523,9 @@ done:
*-------------------------------------------------------------------------
*/
static ssize_t
H5D__efl_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dset_curr_seq,
size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq, size_t *mem_curr_seq,
size_t mem_len_arr[], hsize_t mem_off_arr[])
H5D__efl_writevv(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_len_arr[], hsize_t dset_off_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[], hsize_t mem_off_arr[])
{
H5D_efl_writevv_ud_t udata; /* User data for H5VM_opvv() operator */
ssize_t ret_value = -1; /* Return value (Total size of sequence in bytes) */
@ -534,10 +534,11 @@ H5D__efl_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dse
/* Check args */
HDassert(io_info);
HDassert(io_info->store->efl.nused > 0);
HDassert(io_info->u.wbuf);
HDassert(io_info->dset);
HDassert(io_info->dset->shared);
HDassert(dset_info);
HDassert(dset_info->store->efl.nused > 0);
HDassert(dset_info->buf.cvp);
HDassert(dset_info->dset);
HDassert(dset_info->dset->shared);
HDassert(dset_curr_seq);
HDassert(dset_len_arr);
HDassert(dset_off_arr);
@ -546,9 +547,9 @@ H5D__efl_writevv(const H5D_io_info_t *io_info, size_t dset_max_nseq, size_t *dse
HDassert(mem_off_arr);
/* Set up user data for H5VM_opvv() */
udata.efl = &(io_info->store->efl);
udata.dset = io_info->dset;
udata.wbuf = (const unsigned char *)io_info->u.wbuf;
udata.efl = &(dset_info->store->efl);
udata.dset = dset_info->dset;
udata.wbuf = (const unsigned char *)dset_info->buf.cvp;
/* Call generic sequence operation routine */
if ((ret_value = H5VM_opvv(dset_max_nseq, dset_curr_seq, dset_len_arr, dset_off_arr, mem_max_nseq,

View File

@ -61,7 +61,7 @@ typedef struct {
/* Internal data structure for computing variable-length dataset's total size */
/* (Used for generic 'get vlen buf size' operation) */
typedef struct {
H5VL_object_t *dset_vol_obj; /* VOL object for the dataset */
const H5VL_object_t *dset_vol_obj; /* VOL object for the dataset */
hid_t fspace_id; /* Dataset dataspace ID of the dataset we are working on */
H5S_t *fspace; /* Dataset's dataspace for operation */
hid_t mspace_id; /* Memory dataspace ID of the dataset we are working on */
@ -81,7 +81,7 @@ static herr_t H5D__init_space(H5F_t *file, const H5D_t *dset, const H5S_t
static herr_t H5D__update_oh_info(H5F_t *file, H5D_t *dset, hid_t dapl_id);
static herr_t H5D__build_file_prefix(const H5D_t *dset, H5F_prefix_open_t prefix_type, char **file_prefix);
static herr_t H5D__open_oid(H5D_t *dataset, hid_t dapl_id);
static herr_t H5D__init_storage(const H5D_io_info_t *io_info, hbool_t full_overwrite, hsize_t old_dim[]);
static herr_t H5D__init_storage(H5D_t *dset, hbool_t full_overwrite, hsize_t old_dim[]);
static herr_t H5D__append_flush_setup(H5D_t *dset, hid_t dapl_id);
static herr_t H5D__close_cb(H5VL_object_t *dset_vol_obj, void **request);
static herr_t H5D__use_minimized_dset_headers(H5F_t *file, hbool_t *minimize);
@ -119,8 +119,8 @@ H5FL_DEFINE_STATIC(H5D_shared_t);
/* Declare the external PQ free list for the sieve buffer information */
H5FL_BLK_EXTERN(sieve_buf);
/* Declare the external free list to manage the H5D_chunk_info_t struct */
H5FL_EXTERN(H5D_chunk_info_t);
/* Declare the external free list to manage the H5D_piece_info_t struct */
H5FL_EXTERN(H5D_piece_info_t);
/* Declare extern the free list to manage blocks of type conversion data */
H5FL_BLK_EXTERN(type_conv);
@ -1793,14 +1793,9 @@ H5D__open_oid(H5D_t *dataset, hid_t dapl_id)
*/
if ((H5F_INTENT(dataset->oloc.file) & H5F_ACC_RDWR) &&
!(*dataset->shared->layout.ops->is_space_alloc)(&dataset->shared->layout.storage) &&
H5F_HAS_FEATURE(dataset->oloc.file, H5FD_FEAT_ALLOCATE_EARLY)) {
H5D_io_info_t io_info;
io_info.dset = dataset;
if (H5D__alloc_storage(&io_info, H5D_ALLOC_OPEN, FALSE, NULL) < 0)
H5F_HAS_FEATURE(dataset->oloc.file, H5FD_FEAT_ALLOCATE_EARLY))
if (H5D__alloc_storage(dataset, H5D_ALLOC_OPEN, FALSE, NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize file storage")
} /* end if */
done:
if (ret_value < 0) {
@ -1894,10 +1889,10 @@ H5D_close(H5D_t *dataset)
} /* end if */
/* Check for cached single element chunk info */
if (dataset->shared->cache.chunk.single_chunk_info) {
dataset->shared->cache.chunk.single_chunk_info =
H5FL_FREE(H5D_chunk_info_t, dataset->shared->cache.chunk.single_chunk_info);
dataset->shared->cache.chunk.single_chunk_info = NULL;
if (dataset->shared->cache.chunk.single_piece_info) {
dataset->shared->cache.chunk.single_piece_info =
H5FL_FREE(H5D_piece_info_t, dataset->shared->cache.chunk.single_piece_info);
dataset->shared->cache.chunk.single_piece_info = NULL;
} /* end if */
break;
@ -2088,10 +2083,10 @@ H5D_mult_refresh_close(hid_t dset_id)
} /* end if */
/* Check for cached single element chunk info */
if (dataset->shared->cache.chunk.single_chunk_info) {
dataset->shared->cache.chunk.single_chunk_info =
H5FL_FREE(H5D_chunk_info_t, dataset->shared->cache.chunk.single_chunk_info);
dataset->shared->cache.chunk.single_chunk_info = NULL;
if (dataset->shared->cache.chunk.single_piece_info) {
dataset->shared->cache.chunk.single_piece_info =
H5FL_FREE(H5D_piece_info_t, dataset->shared->cache.chunk.single_piece_info);
dataset->shared->cache.chunk.single_piece_info = NULL;
} /* end if */
break;
@ -2209,11 +2204,9 @@ H5D_nameof(H5D_t *dataset)
*-------------------------------------------------------------------------
*/
herr_t
H5D__alloc_storage(const H5D_io_info_t *io_info, H5D_time_alloc_t time_alloc, hbool_t full_overwrite,
hsize_t old_dim[])
H5D__alloc_storage(H5D_t *dset, H5D_time_alloc_t time_alloc, hbool_t full_overwrite, hsize_t old_dim[])
{
const H5D_t *dset = io_info->dset; /* The dataset object */
H5F_t *f = dset->oloc.file; /* The dataset's file pointer */
H5F_t *f; /* The dataset's file pointer */
H5O_layout_t *layout; /* The dataset's layout information */
hbool_t must_init_space = FALSE; /* Flag to indicate that space should be initialized */
hbool_t addr_set = FALSE; /* Flag to indicate that the dataset's storage address was set */
@ -2223,6 +2216,7 @@ H5D__alloc_storage(const H5D_io_info_t *io_info, H5D_time_alloc_t time_alloc, hb
/* check args */
HDassert(dset);
f = dset->oloc.file;
HDassert(f);
/* If the data is stored in external files, don't set an address for the layout
@ -2333,7 +2327,7 @@ H5D__alloc_storage(const H5D_io_info_t *io_info, H5D_time_alloc_t time_alloc, hb
*/
if (!(dset->shared->dcpl_cache.fill.alloc_time == H5D_ALLOC_TIME_INCR &&
time_alloc == H5D_ALLOC_WRITE))
if (H5D__init_storage(io_info, full_overwrite, old_dim) < 0)
if (H5D__init_storage(dset, full_overwrite, old_dim) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL,
"unable to initialize dataset with fill value")
} /* end if */
@ -2349,7 +2343,7 @@ H5D__alloc_storage(const H5D_io_info_t *io_info, H5D_time_alloc_t time_alloc, hb
if (dset->shared->dcpl_cache.fill.fill_time == H5D_FILL_TIME_ALLOC ||
(dset->shared->dcpl_cache.fill.fill_time == H5D_FILL_TIME_IFSET &&
fill_status == H5D_FILL_VALUE_USER_DEFINED))
if (H5D__init_storage(io_info, full_overwrite, old_dim) < 0)
if (H5D__init_storage(dset, full_overwrite, old_dim) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL,
"unable to initialize dataset with fill value")
} /* end else */
@ -2383,10 +2377,9 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__init_storage(const H5D_io_info_t *io_info, hbool_t full_overwrite, hsize_t old_dim[])
H5D__init_storage(H5D_t *dset, hbool_t full_overwrite, hsize_t old_dim[])
{
const H5D_t *dset = io_info->dset; /* dataset pointer */
herr_t ret_value = SUCCEED; /* Return value */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
@ -2408,7 +2401,7 @@ H5D__init_storage(const H5D_io_info_t *io_info, hbool_t full_overwrite, hsize_t
/* If we will be immediately overwriting the values, don't bother to clear them */
if ((dset->shared->dcpl_cache.efl.nused == 0 || dset->shared->dcpl_cache.fill.buf) &&
!full_overwrite)
if (H5D__contig_fill(io_info) < 0)
if (H5D__contig_fill(dset) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to allocate all chunks of dataset")
break;
@ -2424,7 +2417,7 @@ H5D__init_storage(const H5D_io_info_t *io_info, hbool_t full_overwrite, hsize_t
if (old_dim == NULL)
old_dim = zero_dim;
if (H5D__chunk_allocate(io_info, full_overwrite, old_dim) < 0)
if (H5D__chunk_allocate(dset, full_overwrite, old_dim) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to allocate all chunks of dataset")
break;
} /* end block */
@ -2599,7 +2592,8 @@ H5D__vlen_get_buf_size_cb(void H5_ATTR_UNUSED *elem, hid_t type_id, unsigned H5_
const hsize_t *point, void *op_data)
{
H5D_vlen_bufsize_native_t *vlen_bufsize = (H5D_vlen_bufsize_native_t *)op_data;
herr_t ret_value = H5_ITER_CONT; /* Return value */
H5D_dset_io_info_t dset_info; /* Internal multi-dataset info placeholder */
herr_t ret_value = H5_ITER_CONT; /* Return value */
FUNC_ENTER_PACKAGE
@ -2612,10 +2606,17 @@ H5D__vlen_get_buf_size_cb(void H5_ATTR_UNUSED *elem, hid_t type_id, unsigned H5_
if (H5S_select_elements(vlen_bufsize->fspace, H5S_SELECT_SET, (size_t)1, point) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCREATE, H5_ITER_ERROR, "can't select point")
/* Read in the point (with the custom VL memory allocator) */
if (H5D__read(vlen_bufsize->dset, type_id, vlen_bufsize->mspace, vlen_bufsize->fspace,
vlen_bufsize->common.fl_tbuf) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, H5_ITER_ERROR, "can't read point")
{
dset_info.dset = vlen_bufsize->dset;
dset_info.mem_space = vlen_bufsize->mspace;
dset_info.file_space = vlen_bufsize->fspace;
dset_info.buf.vp = vlen_bufsize->common.fl_tbuf;
dset_info.mem_type_id = type_id;
/* Read in the point (with the custom VL memory allocator) */
if (H5D__read(1, &dset_info) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read data")
}
done:
FUNC_LEAVE_NOAPI(ret_value)
@ -2767,8 +2768,8 @@ H5D__vlen_get_buf_size_gen_cb(void H5_ATTR_UNUSED *elem, hid_t type_id, unsigned
HGOTO_ERROR(H5E_DATASET, H5E_CANTCREATE, FAIL, "can't select point")
/* Read in the point (with the custom VL memory allocator) */
if (H5VL_dataset_read(vlen_bufsize->dset_vol_obj, type_id, vlen_bufsize->mspace_id,
vlen_bufsize->fspace_id, vlen_bufsize->dxpl_id, vlen_bufsize->common.fl_tbuf,
if (H5VL_dataset_read(1, &vlen_bufsize->dset_vol_obj, &type_id, &vlen_bufsize->mspace_id,
&vlen_bufsize->fspace_id, vlen_bufsize->dxpl_id, &vlen_bufsize->common.fl_tbuf,
H5_REQUEST_NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read point")
@ -2814,7 +2815,7 @@ H5D__vlen_get_buf_size_gen(H5VL_object_t *vol_obj, hid_t type_id, hid_t space_id
HGOTO_ERROR(H5E_DATASET, H5E_BADVALUE, FAIL, "dataspace does not have extent set")
/* Save the dataset */
vlen_bufsize.dset_vol_obj = vol_obj;
vlen_bufsize.dset_vol_obj = (const H5VL_object_t *)vol_obj;
/* Set up VOL callback arguments */
vol_cb_args.op_type = H5VL_DATASET_GET_SPACE;
@ -3095,14 +3096,10 @@ H5D__set_extent(H5D_t *dset, const hsize_t *size)
} /* end if */
/* Allocate space for the new parts of the dataset, if appropriate */
if (expand && dset->shared->dcpl_cache.fill.alloc_time == H5D_ALLOC_TIME_EARLY) {
H5D_io_info_t io_info;
io_info.dset = dset;
if (H5D__alloc_storage(&io_info, H5D_ALLOC_EXTEND, FALSE, curr_dims) < 0)
if (expand && dset->shared->dcpl_cache.fill.alloc_time == H5D_ALLOC_TIME_EARLY)
if (H5D__alloc_storage(dset, H5D_ALLOC_EXTEND, FALSE, curr_dims) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to extend dataset storage")
}
/*-------------------------------------------------------------------------
* Remove chunk information in the case of chunked datasets
* This removal takes place only in case we are shrinking the dataset

File diff suppressed because it is too large Load Diff

View File

@ -489,14 +489,9 @@ H5D__layout_oh_create(H5F_t *file, H5O_t *oh, H5D_t *dset, hid_t dapl_id)
* Allocate storage if space allocate time is early; otherwise delay
* allocation until later.
*/
if (fill_prop->alloc_time == H5D_ALLOC_TIME_EARLY) {
H5D_io_info_t io_info;
io_info.dset = dset;
if (H5D__alloc_storage(&io_info, H5D_ALLOC_CREATE, FALSE, NULL) < 0)
if (fill_prop->alloc_time == H5D_ALLOC_TIME_EARLY)
if (H5D__alloc_storage(dset, H5D_ALLOC_CREATE, FALSE, NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize storage")
}
/* Update external storage message, if it's used */
if (dset->shared->dcpl_cache.efl.nused > 0) {

File diff suppressed because it is too large Load Diff

View File

@ -33,6 +33,7 @@
#include "H5ACprivate.h" /* Metadata cache */
#include "H5B2private.h" /* v2 B-trees */
#include "H5Fprivate.h" /* File access */
#include "H5FLprivate.h" /* Free Lists */
#include "H5Gprivate.h" /* Groups */
#include "H5SLprivate.h" /* Skip lists */
#include "H5Tprivate.h" /* Datatypes */
@ -44,20 +45,6 @@
/* Set the minimum object header size to create objects with */
#define H5D_MINHDR_SIZE 256
/* [Simple] Macro to construct a H5D_io_info_t from it's components */
#define H5D_BUILD_IO_INFO_WRT(io_info, ds, str, buf) \
(io_info)->dset = ds; \
(io_info)->f_sh = H5F_SHARED((ds)->oloc.file); \
(io_info)->store = str; \
(io_info)->op_type = H5D_IO_OP_WRITE; \
(io_info)->u.wbuf = buf
#define H5D_BUILD_IO_INFO_RD(io_info, ds, str, buf) \
(io_info)->dset = ds; \
(io_info)->f_sh = H5F_SHARED((ds)->oloc.file); \
(io_info)->store = str; \
(io_info)->op_type = H5D_IO_OP_READ; \
(io_info)->u.rbuf = buf
/* Flags for marking aspects of a dataset dirty */
#define H5D_MARK_SPACE 0x01
#define H5D_MARK_LAYOUT 0x02
@ -83,6 +70,9 @@
#define H5D_BT2_SPLIT_PERC 100
#define H5D_BT2_MERGE_PERC 40
/* Macro to determine if the layout I/O callback should perform I/O */
#define H5D_LAYOUT_CB_PERFORM_IO(IO_INFO) (!(IO_INFO)->use_select_io || (IO_INFO)->count == 1)
/****************************/
/* Package Private Typedefs */
/****************************/
@ -97,23 +87,20 @@ typedef struct H5D_type_info_t {
hid_t dst_type_id; /* Destination datatype ID */
/* Computed/derived values */
size_t src_type_size; /* Size of source type */
size_t dst_type_size; /* Size of destination type */
size_t max_type_size; /* Size of largest source/destination type */
hbool_t is_conv_noop; /* Whether the type conversion is a NOOP */
hbool_t is_xform_noop; /* Whether the data transform is a NOOP */
const H5T_subset_info_t *cmpd_subset; /* Info related to the compound subset conversion functions */
H5T_bkg_t need_bkg; /* Type of background buf needed */
size_t request_nelmts; /* Requested strip mine */
uint8_t *tconv_buf; /* Datatype conv buffer */
hbool_t tconv_buf_allocated; /* Whether the type conversion buffer was allocated */
uint8_t *bkg_buf; /* Background buffer */
hbool_t bkg_buf_allocated; /* Whether the background buffer was allocated */
size_t src_type_size; /* Size of source type */
size_t dst_type_size; /* Size of destination type */
hbool_t is_conv_noop; /* Whether the type conversion is a NOOP */
hbool_t is_xform_noop; /* Whether the data transform is a NOOP */
const H5T_subset_info_t *cmpd_subset; /* Info related to the compound subset conversion functions */
H5T_bkg_t need_bkg; /* Type of background buf needed */
size_t request_nelmts; /* Requested strip mine */
uint8_t *bkg_buf; /* Background buffer */
hbool_t bkg_buf_allocated; /* Whether the background buffer was allocated */
} H5D_type_info_t;
/* Forward declaration of structs used below */
struct H5D_io_info_t;
struct H5D_chunk_map_t;
struct H5D_dset_io_info_t;
typedef struct H5D_shared_t H5D_shared_t;
/* Function pointers for I/O on particular types of dataset layouts */
@ -121,27 +108,27 @@ typedef herr_t (*H5D_layout_construct_func_t)(H5F_t *f, H5D_t *dset);
typedef herr_t (*H5D_layout_init_func_t)(H5F_t *f, const H5D_t *dset, hid_t dapl_id);
typedef hbool_t (*H5D_layout_is_space_alloc_func_t)(const H5O_storage_t *storage);
typedef hbool_t (*H5D_layout_is_data_cached_func_t)(const H5D_shared_t *shared_dset);
typedef herr_t (*H5D_layout_io_init_func_t)(struct H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space,
struct H5D_chunk_map_t *cm);
typedef herr_t (*H5D_layout_read_func_t)(struct H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space,
struct H5D_chunk_map_t *fm);
typedef herr_t (*H5D_layout_write_func_t)(struct H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space,
struct H5D_chunk_map_t *fm);
typedef ssize_t (*H5D_layout_readvv_func_t)(const struct H5D_io_info_t *io_info, size_t dset_max_nseq,
typedef herr_t (*H5D_layout_io_init_func_t)(struct H5D_io_info_t *io_info, struct H5D_dset_io_info_t *dinfo);
typedef herr_t (*H5D_layout_mdio_init_func_t)(struct H5D_io_info_t *io_info,
struct H5D_dset_io_info_t *dinfo);
typedef herr_t (*H5D_layout_read_func_t)(struct H5D_io_info_t *io_info, struct H5D_dset_io_info_t *dinfo);
typedef herr_t (*H5D_layout_write_func_t)(struct H5D_io_info_t *io_info, struct H5D_dset_io_info_t *dinfo);
typedef herr_t (*H5D_layout_read_md_func_t)(struct H5D_io_info_t *io_info);
typedef herr_t (*H5D_layout_write_md_func_t)(struct H5D_io_info_t *io_info);
typedef ssize_t (*H5D_layout_readvv_func_t)(const struct H5D_io_info_t *io_info,
const struct H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_len_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[],
hsize_t mem_offset_arr[]);
typedef ssize_t (*H5D_layout_writevv_func_t)(const struct H5D_io_info_t *io_info, size_t dset_max_nseq,
typedef ssize_t (*H5D_layout_writevv_func_t)(const struct H5D_io_info_t *io_info,
const struct H5D_dset_io_info_t *dset_info, size_t dset_max_nseq,
size_t *dset_curr_seq, size_t dset_len_arr[],
hsize_t dset_offset_arr[], size_t mem_max_nseq,
size_t *mem_curr_seq, size_t mem_len_arr[],
hsize_t mem_offset_arr[]);
typedef herr_t (*H5D_layout_flush_func_t)(H5D_t *dataset);
typedef herr_t (*H5D_layout_io_term_func_t)(const struct H5D_chunk_map_t *cm);
typedef herr_t (*H5D_layout_io_term_func_t)(struct H5D_io_info_t *io_info, struct H5D_dset_io_info_t *di);
typedef herr_t (*H5D_layout_dest_func_t)(H5D_t *dataset);
/* Typedef for grouping layout I/O routines */
@ -152,27 +139,28 @@ typedef struct H5D_layout_ops_t {
H5D_layout_is_data_cached_func_t
is_data_cached; /* Query routine to determine if any raw data is cached. If routine is not present
then the layout type never caches raw data. */
H5D_layout_io_init_func_t io_init; /* I/O initialization routine */
H5D_layout_read_func_t ser_read; /* High-level I/O routine for reading data in serial */
H5D_layout_write_func_t ser_write; /* High-level I/O routine for writing data in serial */
#ifdef H5_HAVE_PARALLEL
H5D_layout_read_func_t par_read; /* High-level I/O routine for reading data in parallel */
H5D_layout_write_func_t par_write; /* High-level I/O routine for writing data in parallel */
#endif /* H5_HAVE_PARALLEL */
H5D_layout_readvv_func_t readvv; /* Low-level I/O routine for reading data */
H5D_layout_writevv_func_t writevv; /* Low-level I/O routine for writing data */
H5D_layout_flush_func_t flush; /* Low-level I/O routine for flushing raw data */
H5D_layout_io_term_func_t io_term; /* I/O shutdown routine */
H5D_layout_dest_func_t dest; /* Destroy layout info */
H5D_layout_io_init_func_t io_init; /* I/O initialization routine */
H5D_layout_mdio_init_func_t mdio_init; /* Multi Dataset I/O initialization routine - called after all
datasets have done io_init and sel_pieces has been allocated */
H5D_layout_read_func_t ser_read; /* High-level I/O routine for reading data in serial */
H5D_layout_write_func_t ser_write; /* High-level I/O routine for writing data in serial */
H5D_layout_readvv_func_t readvv; /* Low-level I/O routine for reading data */
H5D_layout_writevv_func_t writevv; /* Low-level I/O routine for writing data */
H5D_layout_flush_func_t flush; /* Low-level I/O routine for flushing raw data */
H5D_layout_io_term_func_t io_term; /* I/O shutdown routine for multi-dset */
H5D_layout_dest_func_t dest; /* Destroy layout info */
} H5D_layout_ops_t;
/* Function pointers for either multiple or single block I/O access */
typedef herr_t (*H5D_io_single_read_func_t)(const struct H5D_io_info_t *io_info,
const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space);
typedef herr_t (*H5D_io_single_write_func_t)(const struct H5D_io_info_t *io_info,
const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space);
typedef herr_t (*H5D_io_single_read_func_t)(const struct H5D_io_info_t *io_info,
const struct H5D_dset_io_info_t *dset_info);
typedef herr_t (*H5D_io_single_write_func_t)(const struct H5D_io_info_t *io_info,
const struct H5D_dset_io_info_t *dset_info);
typedef herr_t (*H5D_io_single_read_md_func_t)(const struct H5D_io_info_t *io_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space);
typedef herr_t (*H5D_io_single_write_md_func_t)(const struct H5D_io_info_t *io_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space);
/* Typedef for raw data I/O framework info */
typedef struct H5D_io_ops_t {
@ -182,6 +170,14 @@ typedef struct H5D_io_ops_t {
H5D_io_single_write_func_t single_write; /* I/O routine for writing single block */
} H5D_io_ops_t;
/* Typedef for raw data I/O framework info (multi-dataset I/O) */
typedef struct H5D_md_io_ops_t {
H5D_layout_read_md_func_t multi_read_md; /* High-level I/O routine for reading data for multi-dset */
H5D_layout_write_md_func_t multi_write_md; /* High-level I/O routine for writing data for multi-dset */
H5D_io_single_read_md_func_t single_read_md; /* I/O routine for reading single block for multi-dset */
H5D_io_single_write_md_func_t single_write_md; /* I/O routine for writing single block for multi-dset */
} H5D_md_io_ops_t;
/* Typedefs for dataset storage information */
typedef struct {
haddr_t dset_addr; /* Address of dataset in file */
@ -210,25 +206,79 @@ typedef enum H5D_io_op_type_t {
H5D_IO_OP_WRITE /* Write operation */
} H5D_io_op_type_t;
/* Piece info for a data chunk/block during I/O */
typedef struct H5D_piece_info_t {
haddr_t faddr; /* File address */
hsize_t index; /* "Index" of chunk in dataset */
hsize_t piece_points; /* Number of elements selected in piece */
hsize_t scaled[H5O_LAYOUT_NDIMS]; /* Scaled coordinates of chunk (in file dataset's dataspace) */
H5S_t *fspace; /* Dataspace describing chunk & selection in it */
unsigned fspace_shared; /* Indicate that the file space for a chunk is shared and shouldn't be freed */
H5S_t *mspace; /* Dataspace describing selection in memory corresponding to this chunk */
unsigned mspace_shared; /* Indicate that the memory space for a chunk is shared and shouldn't be freed */
struct H5D_dset_io_info_t *dset_info; /* Pointer to dset_info */
} H5D_piece_info_t;
/* I/O info for a single dataset */
typedef struct H5D_dset_io_info_t {
H5D_t *dset; /* Pointer to dataset being operated on */
H5D_storage_t *store; /* Dataset storage info */
H5D_layout_ops_t layout_ops; /* Dataset layout I/O operation function pointers */
H5_flexible_const_ptr_t buf; /* Buffer pointer */
H5D_io_ops_t io_ops; /* I/O operations for this dataset */
H5O_layout_t *layout; /* Dataset layout information*/
hsize_t nelmts; /* Number of elements selected in file & memory dataspaces */
H5S_t *file_space; /* Pointer to the file dataspace */
H5S_t *mem_space; /* Pointer to the memory dataspace */
union {
struct H5D_chunk_map_t *chunk_map; /* Chunk specific I/O info */
H5D_piece_info_t *contig_piece_info; /* Piece info for contiguous dataset */
} layout_io_info;
hid_t mem_type_id; /* memory datatype ID */
H5D_type_info_t type_info;
hbool_t skip_io; /* Whether to skip I/O for this dataset */
} H5D_dset_io_info_t;
/* I/O info for entire I/O operation */
typedef struct H5D_io_info_t {
const H5D_t *dset; /* Pointer to dataset being operated on */
/* QAK: Delete the f_sh field when oloc has a shared file pointer? */
/* QAK: Delete the f_sh field when oloc has a shared file pointer? */
H5F_shared_t *f_sh; /* Pointer to shared file struct that dataset is within */
#ifdef H5_HAVE_PARALLEL
MPI_Comm comm; /* MPI communicator for file */
hbool_t using_mpi_vfd; /* Whether the file is using an MPI-based VFD */
#endif /* H5_HAVE_PARALLEL */
H5D_storage_t *store; /* Dataset storage info */
H5D_layout_ops_t layout_ops; /* Dataset layout I/O operation function pointers */
H5D_io_ops_t io_ops; /* I/O operation function pointers */
H5D_io_op_type_t op_type;
hbool_t use_select_io; /* Whether to use selection I/O */
union {
void *rbuf; /* Pointer to buffer for read */
const void *wbuf; /* Pointer to buffer to write */
} u;
MPI_Comm comm; /* MPI communicator for file */
hbool_t using_mpi_vfd; /* Whether the file is using an MPI-based VFD */
#endif /* H5_HAVE_PARALLEL */
H5D_md_io_ops_t md_io_ops; /* Multi dataset I/O operation function pointers */
H5D_io_op_type_t op_type;
size_t count; /* Number of datasets in I/O request */
H5D_dset_io_info_t *dsets_info; /* dsets info where I/O is done to/from */
size_t piece_count; /* Number of pieces in I/O request */
size_t pieces_added; /* Number of pieces added so far to arrays */
H5D_piece_info_t **sel_pieces; /* Array of info struct for all pieces in I/O */
H5S_t **mem_spaces; /* Array of chunk memory spaces */
H5S_t **file_spaces; /* Array of chunk file spaces */
haddr_t *addrs; /* Array of chunk addresses */
size_t *element_sizes; /* Array of element sizes */
void **rbufs; /* Array of read buffers */
const void **wbufs; /* Array of write buffers */
haddr_t store_faddr; /* lowest file addr for read/write */
H5_flexible_const_ptr_t base_maddr; /* starting mem address */
hbool_t use_select_io; /* Whether to use selection I/O */
uint8_t *tconv_buf; /* Datatype conv buffer */
hbool_t tconv_buf_allocated; /* Whether the type conversion buffer was allocated */
size_t max_type_size; /* Largest of all source and destination type sizes */
} H5D_io_info_t;
/* Created to pass both at once for callback func */
typedef struct H5D_io_info_wrap_t {
H5D_io_info_t *io_info;
H5D_dset_io_info_t *dinfo;
} H5D_io_info_wrap_t;
/******************/
/* Chunk typedefs */
/******************/
@ -330,46 +380,26 @@ typedef struct H5D_chunk_ops_t {
H5D_chunk_dest_func_t dest; /* Routine to destroy indexing information in memory */
} H5D_chunk_ops_t;
/* Structure holding information about a chunk's selection for mapping */
typedef struct H5D_chunk_info_t {
hsize_t index; /* "Index" of chunk in dataset */
uint32_t chunk_points; /* Number of elements selected in chunk */
hsize_t scaled[H5O_LAYOUT_NDIMS]; /* Scaled coordinates of chunk (in file dataset's dataspace) */
H5S_t *fspace; /* Dataspace describing chunk & selection in it */
hbool_t fspace_shared; /* Indicate that the file space for a chunk is shared and shouldn't be freed */
H5S_t *mspace; /* Dataspace describing selection in memory corresponding to this chunk */
hbool_t mspace_shared; /* Indicate that the memory space for a chunk is shared and shouldn't be freed */
} H5D_chunk_info_t;
/* Main structure holding the mapping between file chunks and memory */
typedef struct H5D_chunk_map_t {
H5O_layout_t *layout; /* Dataset layout information*/
hsize_t nelmts; /* Number of elements selected in file & memory dataspaces */
unsigned f_ndims; /* Number of dimensions for file dataspace */
H5S_t *file_space; /* Pointer to the file dataspace */
unsigned f_ndims; /* Number of dimensions for file dataspace */
H5S_t *mem_space; /* Pointer to the memory dataspace */
H5S_t *mchunk_tmpl; /* Dataspace template for new memory chunks */
H5S_sel_iter_t mem_iter; /* Iterator for elements in memory selection */
unsigned m_ndims; /* Number of dimensions for memory dataspace */
H5S_sel_type msel_type; /* Selection type in memory */
H5S_sel_type fsel_type; /* Selection type in file */
H5SL_t *sel_chunks; /* Skip list containing information for each chunk selected */
H5SL_t *dset_sel_pieces; /* Skip list containing information for each chunk selected */
H5S_t *single_space; /* Dataspace for single chunk */
H5D_chunk_info_t *single_chunk_info; /* Pointer to single chunk's info */
H5D_piece_info_t *single_piece_info; /* Pointer to single chunk's info */
hbool_t use_single; /* Whether I/O is on a single element */
hsize_t last_index; /* Index of last chunk operated on */
H5D_chunk_info_t *last_chunk_info; /* Pointer to last chunk's info */
H5D_piece_info_t *last_piece_info; /* Pointer to last chunk's info */
hsize_t chunk_dim[H5O_LAYOUT_NDIMS]; /* Size of chunk in each dimension */
#ifdef H5_HAVE_PARALLEL
H5D_chunk_info_t **select_chunk; /* Store the information about whether this chunk is selected or not */
#endif /* H5_HAVE_PARALLEL */
} H5D_chunk_map_t;
/* Cached information about a particular chunk */
@ -415,7 +445,7 @@ typedef struct H5D_rdcc_t {
struct H5D_rdcc_ent_t **slot; /* Chunk slots, each points to a chunk*/
H5SL_t *sel_chunks; /* Skip list containing information for each chunk selected */
H5S_t *single_space; /* Dataspace for single element I/O on chunks */
H5D_chunk_info_t *single_chunk_info; /* Pointer to single chunk's info */
H5D_piece_info_t *single_piece_info; /* Pointer to single piece's info */
/* Cached information about scaled dataspace dimensions */
hsize_t scaled_dims[H5S_MAX_RANK]; /* The scaled dim sizes */
@ -458,12 +488,13 @@ struct H5D_shared_t {
/* Buffered/cached information for types of raw data storage*/
struct {
H5D_rdcdc_t contig; /* Information about contiguous data */
/* (Note that the "contig" cache
* information can be used by a chunked
* dataset in certain circumstances)
*/
H5D_rdcc_t chunk; /* Information about chunked data */
H5D_rdcdc_t contig; /* Information about contiguous data */
/* (Note that the "contig" cache
* information can be used by a chunked
* dataset in certain circumstances)
*/
H5D_rdcc_t chunk; /* Information about chunked data */
H5SL_t *sel_pieces; /* Skip list containing information for each piece selected */
} cache;
H5D_append_flush_t append_flush; /* Append flush property information */
@ -556,8 +587,8 @@ H5_DLL H5D_t *H5D__open_name(const H5G_loc_t *loc, const char *name, hid_t dapl
H5_DLL hid_t H5D__get_space(const H5D_t *dset);
H5_DLL hid_t H5D__get_type(const H5D_t *dset);
H5_DLL herr_t H5D__get_space_status(const H5D_t *dset, H5D_space_status_t *allocation);
H5_DLL herr_t H5D__alloc_storage(const H5D_io_info_t *io_info, H5D_time_alloc_t time_alloc,
hbool_t full_overwrite, hsize_t old_dim[]);
H5_DLL herr_t H5D__alloc_storage(H5D_t *dset, H5D_time_alloc_t time_alloc, hbool_t full_overwrite,
hsize_t old_dim[]);
H5_DLL herr_t H5D__get_storage_size(const H5D_t *dset, hsize_t *storage_size);
H5_DLL herr_t H5D__get_chunk_storage_size(H5D_t *dset, const hsize_t *offset, hsize_t *storage_size);
H5_DLL herr_t H5D__chunk_index_empty(const H5D_t *dset, hbool_t *empty);
@ -582,16 +613,12 @@ H5_DLL herr_t H5D__refresh(H5D_t *dataset, hid_t dset_id);
H5_DLL herr_t H5D__format_convert(H5D_t *dataset);
/* Internal I/O routines */
H5_DLL herr_t H5D__read(H5D_t *dataset, hid_t mem_type_id, H5S_t *mem_space, H5S_t *file_space,
void *buf /*out*/);
H5_DLL herr_t H5D__write(H5D_t *dataset, hid_t mem_type_id, H5S_t *mem_space, H5S_t *file_space,
const void *buf);
H5_DLL herr_t H5D__read(size_t count, H5D_dset_io_info_t *dset_info);
H5_DLL herr_t H5D__write(size_t count, H5D_dset_io_info_t *dset_info);
/* Functions that perform direct serial I/O operations */
H5_DLL herr_t H5D__select_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space);
H5_DLL herr_t H5D__select_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space);
H5_DLL herr_t H5D__select_read(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info);
H5_DLL herr_t H5D__select_write(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info);
/* Functions that perform direct copying between memory buffers */
H5_DLL herr_t H5D_select_io_mem(void *dst_buf, H5S_t *dst_space, const void *src_buf, H5S_t *src_space,
@ -601,10 +628,8 @@ H5_DLL herr_t H5D_select_io_mem(void *dst_buf, H5S_t *dst_space, const void *src
H5_DLL herr_t H5D__scatter_mem(const void *_tscat_buf, H5S_sel_iter_t *iter, size_t nelmts, void *_buf);
H5_DLL size_t H5D__gather_mem(const void *_buf, H5S_sel_iter_t *iter, size_t nelmts,
void *_tgath_buf /*out*/);
H5_DLL herr_t H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space);
H5_DLL herr_t H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space);
H5_DLL herr_t H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info);
H5_DLL herr_t H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info);
/* Functions that operate on dataset's layout information */
H5_DLL herr_t H5D__layout_set_io_ops(const H5D_t *dataset);
@ -620,25 +645,23 @@ H5_DLL herr_t H5D__layout_oh_write(const H5D_t *dataset, H5O_t *oh, unsigned upd
H5_DLL herr_t H5D__contig_alloc(H5F_t *f, H5O_storage_contig_t *storage);
H5_DLL hbool_t H5D__contig_is_space_alloc(const H5O_storage_t *storage);
H5_DLL hbool_t H5D__contig_is_data_cached(const H5D_shared_t *shared_dset);
H5_DLL herr_t H5D__contig_fill(const H5D_io_info_t *io_info);
H5_DLL herr_t H5D__contig_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t *fm);
H5_DLL herr_t H5D__contig_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t *fm);
H5_DLL herr_t H5D__contig_fill(H5D_t *dset);
H5_DLL herr_t H5D__contig_read(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
H5_DLL herr_t H5D__contig_write(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
H5_DLL herr_t H5D__contig_copy(H5F_t *f_src, const H5O_storage_contig_t *storage_src, H5F_t *f_dst,
H5O_storage_contig_t *storage_dst, H5T_t *src_dtype, H5O_copy_t *cpy_info);
H5_DLL herr_t H5D__contig_delete(H5F_t *f, const H5O_storage_t *store);
/* Functions that operate on chunked dataset storage */
H5_DLL htri_t H5D__chunk_cacheable(const H5D_io_info_t *io_info, haddr_t caddr, hbool_t write_op);
H5_DLL herr_t H5D__chunk_create(const H5D_t *dset /*in,out*/);
H5_DLL herr_t H5D__chunk_set_info(const H5D_t *dset);
H5_DLL htri_t H5D__chunk_cacheable(const H5D_io_info_t *io_info, H5D_dset_io_info_t *dset_info, haddr_t caddr,
hbool_t write_op);
H5_DLL herr_t H5D__chunk_create(const H5D_t *dset /*in,out*/);
H5_DLL herr_t H5D__chunk_set_info(const H5D_t *dset);
H5_DLL hbool_t H5D__chunk_is_space_alloc(const H5O_storage_t *storage);
H5_DLL hbool_t H5D__chunk_is_data_cached(const H5D_shared_t *shared_dset);
H5_DLL herr_t H5D__chunk_lookup(const H5D_t *dset, const hsize_t *scaled, H5D_chunk_ud_t *udata);
H5_DLL herr_t H5D__chunk_allocated(const H5D_t *dset, hsize_t *nbytes);
H5_DLL herr_t H5D__chunk_allocate(const H5D_io_info_t *io_info, hbool_t full_overwrite,
const hsize_t old_dim[]);
H5_DLL herr_t H5D__chunk_allocate(const H5D_t *dset, hbool_t full_overwrite, const hsize_t old_dim[]);
H5_DLL herr_t H5D__chunk_file_alloc(const H5D_chk_idx_info_t *idx_info, const H5F_block_t *old_chunk,
H5F_block_t *new_chunk, hbool_t *need_insert, const hsize_t *scaled);
H5_DLL void *H5D__chunk_mem_alloc(size_t size, void *pline);
@ -651,7 +674,7 @@ H5_DLL hbool_t H5D__chunk_is_partial_edge_chunk(unsigned dset_ndims, const uint3
H5_DLL herr_t H5D__chunk_prune_by_extent(H5D_t *dset, const hsize_t *old_dim);
H5_DLL herr_t H5D__chunk_set_sizes(H5D_t *dset);
#ifdef H5_HAVE_PARALLEL
H5_DLL herr_t H5D__chunk_addrmap(const H5D_io_info_t *io_info, haddr_t chunk_addr[]);
H5_DLL herr_t H5D__chunk_addrmap(const H5D_t *dset, haddr_t chunk_addr[]);
#endif /* H5_HAVE_PARALLEL */
H5_DLL herr_t H5D__chunk_update_cache(H5D_t *dset);
H5_DLL herr_t H5D__chunk_copy(H5F_t *f_src, H5O_storage_chunk_t *storage_src, H5O_layout_chunk_t *layout_src,
@ -662,8 +685,8 @@ H5_DLL herr_t H5D__chunk_bh_info(const H5O_loc_t *loc, H5O_t *oh, H5O_layout_t *
H5_DLL herr_t H5D__chunk_dump_index(H5D_t *dset, FILE *stream);
H5_DLL herr_t H5D__chunk_delete(H5F_t *f, H5O_t *oh, H5O_storage_t *store);
H5_DLL herr_t H5D__chunk_get_offset_copy(const H5D_t *dset, const hsize_t *offset, hsize_t *offset_copy);
H5_DLL herr_t H5D__chunk_direct_write(const H5D_t *dset, uint32_t filters, hsize_t *offset,
uint32_t data_size, const void *buf);
H5_DLL herr_t H5D__chunk_direct_write(H5D_t *dset, uint32_t filters, hsize_t *offset, uint32_t data_size,
const void *buf);
H5_DLL herr_t H5D__chunk_direct_read(const H5D_t *dset, hsize_t *offset, uint32_t *filters, void *buf);
#ifdef H5D_CHUNK_DEBUG
H5_DLL herr_t H5D__chunk_stats(const H5D_t *dset, hbool_t headers);
@ -711,39 +734,31 @@ H5_DLL herr_t H5D__fill_term(H5D_fill_buf_info_t *fb_info);
#define H5Dmpio_DEBUG
#endif /*H5Dmpio_DEBUG*/
#endif /*H5D_DEBUG*/
/* MPI-IO function to read, it will select either regular or irregular read */
H5_DLL herr_t H5D__mpio_select_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space);
/* MPI-IO function to read multi-dsets (Chunk, Contig), it will select either
* regular or irregular read */
H5_DLL herr_t H5D__mpio_select_read(const H5D_io_info_t *io_info, hsize_t nelmts, H5S_t *file_space,
H5S_t *mem_space);
/* MPI-IO function to write, it will select either regular or irregular read */
H5_DLL herr_t H5D__mpio_select_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space);
/* MPI-IO function to write multi-dsets (Chunk, Contig), it will select either
* regular or irregular write */
H5_DLL herr_t H5D__mpio_select_write(const H5D_io_info_t *io_info, hsize_t nelmts, H5S_t *file_space,
H5S_t *mem_space);
/* MPI-IO functions to handle contiguous collective IO */
H5_DLL herr_t H5D__contig_collective_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space,
H5D_chunk_map_t *fm);
H5_DLL herr_t H5D__contig_collective_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space,
H5D_chunk_map_t *fm);
/* MPI-IO functions to handle chunked collective IO */
H5_DLL herr_t H5D__chunk_collective_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space,
H5D_chunk_map_t *fm);
H5_DLL herr_t H5D__chunk_collective_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
hsize_t nelmts, H5S_t *file_space, H5S_t *mem_space,
H5D_chunk_map_t *fm);
/* MPI-IO functions to handle collective IO for multiple dsets (CONTIG, CHUNK) */
H5_DLL herr_t H5D__collective_read(H5D_io_info_t *io_info);
H5_DLL herr_t H5D__collective_write(H5D_io_info_t *io_info);
/* MPI-IO function to check if a direct I/O transfer is possible between
* memory and the file */
H5_DLL htri_t H5D__mpio_opt_possible(const H5D_io_info_t *io_info, const H5S_t *file_space,
const H5S_t *mem_space, const H5D_type_info_t *type_info);
H5_DLL htri_t H5D__mpio_opt_possible(H5D_io_info_t *io_info);
H5_DLL herr_t H5D__mpio_get_no_coll_cause_strings(char *local_cause, size_t local_cause_len,
char *global_cause, size_t global_cause_len);
#endif /* H5_HAVE_PARALLEL */
/* Free a piece (chunk or contiguous dataset data block) info struct */
H5_DLL herr_t H5D__free_piece_info(void *item, void *key, void *opdata);
/* Testing functions */
#ifdef H5D_TESTING
H5_DLL herr_t H5D__layout_version_test(hid_t did, unsigned *version);

View File

@ -850,6 +850,52 @@ H5_DLL haddr_t H5Dget_offset(hid_t dset_id);
H5_DLL herr_t H5Dread(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, void *buf /*out*/);
/**
* --------------------------------------------------------------------------
* \ingroup H5D
*
* \brief Reads raw data from a set of datasets into the provided buffers
*
* \param[in] count Number of datasets to read from
* \param[in] dset_id Identifiers of the datasets to read from
* \param[in] mem_type_id Identifiers of the memory datatypes
* \param[in] mem_space_id Identifiers of the memory dataspaces
* \param[in] file_space_id Identifiers of the datasets' dataspaces in the file
* \param[in] dxpl_id Identifier of a transfer property list
* \param[out] buf Buffers to receive data read from file
*
* \return \herr_t
*
* \details H5Dread_multi() reads data from \p count datasets, whose identifiers
* are listed in the \p dset_id array, from the file into multiple
* application memory buffers listed in the \p buf array. Data transfer
* properties are defined by the argument \p dxpl_id. The memory
* datatypes of each dataset are listed by identifier in the \p
* mem_type_id array. The parts of each dataset to read are listed by
* identifier in the \p file_space_id array, and the parts of each
* application memory buffer to read to are listed by identifier in the
* \p mem_space_id array. All array parameters have length \p count.
*
* This function will produce the same results as \p count calls to
* H5Dread(). Information listed in that function about the specifics
* of its behaviour also apply to H5Dread_multi(). By calling
* H5Dread_multi() instead of multiple calls to H5Dread(), however, the
* library can in some cases pass information about the entire I/O
* operation to the file driver, which can improve performance.
*
* All datasets must be in the same HDF5 file, and each unique dataset
* may only be listed once. If this function is called collectively in
* parallel, each rank must pass exactly the same list of datasets in
* \p dset_id , though the other parameters may differ.
*
* \since 1.13.3
*
* \see H5Dread()
*
*/
H5_DLL herr_t H5Dread_multi(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[] /*out*/);
/**
* --------------------------------------------------------------------------
* \ingroup ASYNC
@ -859,6 +905,15 @@ H5_DLL herr_t H5Dread_async(const char *app_file, const char *app_func, unsigned
hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id, hid_t dxpl_id,
void *buf /*out*/, hid_t es_id);
/**
* --------------------------------------------------------------------------
* \ingroup ASYNC
* \async_variant_of{H5Dread_multi}
*/
H5_DLL herr_t H5Dread_multi_async(const char *app_file, const char *app_func, unsigned app_line, size_t count,
hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[] /*out*/, hid_t es_id);
/**
* --------------------------------------------------------------------------
* \ingroup H5D
@ -975,6 +1030,53 @@ H5_DLL herr_t H5Dread_async(const char *app_file, const char *app_func, unsigned
H5_DLL herr_t H5Dwrite(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, const void *buf);
/**
* --------------------------------------------------------------------------
* \ingroup H5D
*
* \brief Writes raw data from a set buffers to a set of datasets
*
* \param[in] count Number of datasets to write to
* \param[in] dset_id Identifiers of the datasets to write to
* \param[in] mem_type_id Identifiers of the memory datatypes
* \param[in] mem_space_id Identifiers of the memory dataspaces
* \param[in] file_space_id Identifiers of the datasets' dataspaces in the file
* \param[in] dxpl_id Identifier of a transfer property list
* \param[in] buf Buffers with data to be written to the file
*
* \return \herr_t
*
* \details H5Dwrite_multi() writes data to \p count datasets, whose identifiers
* are listed in the \p dset_id array, from multiple application memory
* buffers listed in the \p buf array. Data transfer properties are
* defined by the argument \p dxpl_id. The memory datatypes of each
* dataset are listed by identifier in the \p mem_type_id array. The
* parts of each dataset to write are listed by identifier in the \p
* file_space_id array, and the parts of each application memory buffer
* to write from are listed by identifier in the \p mem_space_id array.
* All array parameters have length \p count.
*
* This function will produce the same results as \p count calls to
* H5Dwrite(). Information listed in that function's documentation
* about the specifics of its behaviour also apply to H5Dwrite_multi().
* By calling H5Dwrite_multi() instead of multiple calls to H5Dwrite(),
* however, the library can in some cases pass information about the
* entire I/O operation to the file driver, which can improve
* performance.
*
* All datasets must be in the same HDF5 file, and each unique dataset
* may only be listed once. If this function is called collectively in
* parallel, each rank must pass exactly the same list of datasets in
* \p dset_id , though the other parameters may differ.
*
* \since 1.13.3
*
* \see H5Dwrite()
*
*/
H5_DLL herr_t H5Dwrite_multi(size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[]);
/**
* --------------------------------------------------------------------------
* \ingroup ASYNC
@ -984,6 +1086,15 @@ H5_DLL herr_t H5Dwrite_async(const char *app_file, const char *app_func, unsigne
hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id, hid_t dxpl_id,
const void *buf, hid_t es_id);
/**
* --------------------------------------------------------------------------
* \ingroup ASYNC
* \async_variant_of{H5Dwrite_multi}
*/
H5_DLL herr_t H5Dwrite_multi_async(const char *app_file, const char *app_func, unsigned app_line,
size_t count, hid_t dset_id[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], hid_t es_id);
/**
* --------------------------------------------------------------------------
* \ingroup H5D

View File

@ -39,13 +39,13 @@
/********************/
/* Local Prototypes */
/********************/
static herr_t H5D__scatter_file(const H5D_io_info_t *io_info, H5S_sel_iter_t *file_iter, size_t nelmts,
const void *buf);
static size_t H5D__gather_file(const H5D_io_info_t *io_info, H5S_sel_iter_t *file_iter, size_t nelmts,
void *buf);
static herr_t H5D__scatter_file(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
H5S_sel_iter_t *file_iter, size_t nelmts, const void *buf);
static size_t H5D__gather_file(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
H5S_sel_iter_t *file_iter, size_t nelmts, void *buf);
static herr_t H5D__compound_opt_read(size_t nelmts, H5S_sel_iter_t *iter, const H5D_type_info_t *type_info,
void *user_buf /*out*/);
static herr_t H5D__compound_opt_write(size_t nelmts, const H5D_type_info_t *type_info);
uint8_t *tconv_buf, void *user_buf /*out*/);
static herr_t H5D__compound_opt_write(size_t nelmts, const H5D_type_info_t *type_info, uint8_t *tconv_buf);
/*********************/
/* Package Variables */
@ -81,33 +81,40 @@ H5FL_SEQ_EXTERN(hsize_t);
*-------------------------------------------------------------------------
*/
static herr_t
H5D__scatter_file(const H5D_io_info_t *_io_info, H5S_sel_iter_t *iter, size_t nelmts, const void *_buf)
H5D__scatter_file(const H5D_io_info_t *_io_info, const H5D_dset_io_info_t *_dset_info, H5S_sel_iter_t *iter,
size_t nelmts, const void *_buf)
{
H5D_io_info_t tmp_io_info; /* Temporary I/O info object */
hsize_t *off = NULL; /* Pointer to sequence offsets */
hsize_t mem_off; /* Offset in memory */
size_t mem_curr_seq; /* "Current sequence" in memory */
size_t dset_curr_seq; /* "Current sequence" in dataset */
size_t *len = NULL; /* Array to store sequence lengths */
size_t orig_mem_len, mem_len; /* Length of sequence in memory */
size_t nseq; /* Number of sequences generated */
size_t nelem; /* Number of elements used in sequences */
size_t dxpl_vec_size; /* Vector length from API context's DXPL */
size_t vec_size; /* Vector length */
herr_t ret_value = SUCCEED; /* Return value */
H5D_io_info_t tmp_io_info; /* Temporary I/O info object */
H5D_dset_io_info_t tmp_dset_info; /* Temporary I/O info object */
hsize_t *off = NULL; /* Pointer to sequence offsets */
hsize_t mem_off; /* Offset in memory */
size_t mem_curr_seq; /* "Current sequence" in memory */
size_t dset_curr_seq; /* "Current sequence" in dataset */
size_t *len = NULL; /* Array to store sequence lengths */
size_t orig_mem_len, mem_len; /* Length of sequence in memory */
size_t nseq; /* Number of sequences generated */
size_t nelem; /* Number of elements used in sequences */
size_t dxpl_vec_size; /* Vector length from API context's DXPL */
size_t vec_size; /* Vector length */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Check args */
HDassert(_io_info);
HDassert(_dset_info);
HDassert(_dset_info->dset);
HDassert(_dset_info->store);
HDassert(iter);
HDassert(nelmts > 0);
HDassert(_buf);
/* Set up temporary I/O info object */
H5MM_memcpy(&tmp_io_info, _io_info, sizeof(*_io_info));
tmp_io_info.op_type = H5D_IO_OP_WRITE;
tmp_io_info.u.wbuf = _buf;
HDmemcpy(&tmp_dset_info, _dset_info, sizeof(*_dset_info));
tmp_io_info.op_type = H5D_IO_OP_WRITE;
tmp_dset_info.buf.cvp = _buf;
tmp_io_info.dsets_info = &tmp_dset_info;
/* Get info from API context */
if (H5CX_get_vec_size(&dxpl_vec_size) < 0)
@ -135,12 +142,12 @@ H5D__scatter_file(const H5D_io_info_t *_io_info, H5S_sel_iter_t *iter, size_t ne
mem_off = 0;
/* Write sequence list out */
if ((*tmp_io_info.layout_ops.writevv)(&tmp_io_info, nseq, &dset_curr_seq, len, off, (size_t)1,
&mem_curr_seq, &mem_len, &mem_off) < 0)
if ((*tmp_dset_info.layout_ops.writevv)(&tmp_io_info, &tmp_dset_info, nseq, &dset_curr_seq, len, off,
(size_t)1, &mem_curr_seq, &mem_len, &mem_off) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_WRITEERROR, FAIL, "write error")
/* Update buffer */
tmp_io_info.u.wbuf = (const uint8_t *)tmp_io_info.u.wbuf + orig_mem_len;
tmp_dset_info.buf.cvp = (const uint8_t *)tmp_dset_info.buf.cvp + orig_mem_len;
/* Decrement number of elements left to process */
nelmts -= nelem;
@ -178,35 +185,40 @@ done:
*-------------------------------------------------------------------------
*/
static size_t
H5D__gather_file(const H5D_io_info_t *_io_info, H5S_sel_iter_t *iter, size_t nelmts, void *_buf /*out*/)
H5D__gather_file(const H5D_io_info_t *_io_info, const H5D_dset_io_info_t *_dset_info, H5S_sel_iter_t *iter,
size_t nelmts, void *_buf /*out*/)
{
H5D_io_info_t tmp_io_info; /* Temporary I/O info object */
hsize_t *off = NULL; /* Pointer to sequence offsets */
hsize_t mem_off; /* Offset in memory */
size_t mem_curr_seq; /* "Current sequence" in memory */
size_t dset_curr_seq; /* "Current sequence" in dataset */
size_t *len = NULL; /* Pointer to sequence lengths */
size_t orig_mem_len, mem_len; /* Length of sequence in memory */
size_t nseq; /* Number of sequences generated */
size_t nelem; /* Number of elements used in sequences */
size_t dxpl_vec_size; /* Vector length from API context's DXPL */
size_t vec_size; /* Vector length */
size_t ret_value = nelmts; /* Return value */
H5D_io_info_t tmp_io_info; /* Temporary I/O info object */
H5D_dset_io_info_t tmp_dset_info; /* Temporary I/O info object */
hsize_t *off = NULL; /* Pointer to sequence offsets */
hsize_t mem_off; /* Offset in memory */
size_t mem_curr_seq; /* "Current sequence" in memory */
size_t dset_curr_seq; /* "Current sequence" in dataset */
size_t *len = NULL; /* Pointer to sequence lengths */
size_t orig_mem_len, mem_len; /* Length of sequence in memory */
size_t nseq; /* Number of sequences generated */
size_t nelem; /* Number of elements used in sequences */
size_t dxpl_vec_size; /* Vector length from API context's DXPL */
size_t vec_size; /* Vector length */
size_t ret_value = nelmts; /* Return value */
FUNC_ENTER_PACKAGE
/* Check args */
HDassert(_io_info);
HDassert(_io_info->dset);
HDassert(_io_info->store);
HDassert(_dset_info);
HDassert(_dset_info->dset);
HDassert(_dset_info->store);
HDassert(iter);
HDassert(nelmts > 0);
HDassert(_buf);
/* Set up temporary I/O info object */
H5MM_memcpy(&tmp_io_info, _io_info, sizeof(*_io_info));
tmp_io_info.op_type = H5D_IO_OP_READ;
tmp_io_info.u.rbuf = _buf;
HDmemcpy(&tmp_dset_info, _dset_info, sizeof(*_dset_info));
tmp_io_info.op_type = H5D_IO_OP_READ;
tmp_dset_info.buf.vp = _buf;
tmp_io_info.dsets_info = &tmp_dset_info;
/* Get info from API context */
if (H5CX_get_vec_size(&dxpl_vec_size) < 0)
@ -234,12 +246,12 @@ H5D__gather_file(const H5D_io_info_t *_io_info, H5S_sel_iter_t *iter, size_t nel
mem_off = 0;
/* Read sequence list in */
if ((*tmp_io_info.layout_ops.readvv)(&tmp_io_info, nseq, &dset_curr_seq, len, off, (size_t)1,
&mem_curr_seq, &mem_len, &mem_off) < 0)
if ((*tmp_dset_info.layout_ops.readvv)(&tmp_io_info, &tmp_dset_info, nseq, &dset_curr_seq, len, off,
(size_t)1, &mem_curr_seq, &mem_len, &mem_off) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_READERROR, 0, "read error")
/* Update buffer */
tmp_io_info.u.rbuf = (uint8_t *)tmp_io_info.u.rbuf + orig_mem_len;
tmp_dset_info.buf.vp = (uint8_t *)tmp_dset_info.buf.vp + orig_mem_len;
/* Decrement number of elements left to process */
nelmts -= nelem;
@ -436,11 +448,10 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space)
H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info)
{
void *buf = io_info->u.rbuf; /* Local pointer to application buffer */
H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info*/
void *buf; /* Local pointer to application buffer */
H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info*/
hbool_t mem_iter_init = FALSE; /* Memory selection iteration info has been initialized */
H5S_sel_iter_t *bkg_iter = NULL; /* Background iteration info*/
hbool_t bkg_iter_init = FALSE; /* Background iteration info has been initialized */
@ -454,13 +465,16 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf
/* Sanity check */
HDassert(io_info);
HDassert(type_info);
HDassert(mem_space);
HDassert(file_space);
HDassert(buf);
HDassert(dset_info);
HDassert(dset_info->mem_space);
HDassert(dset_info->file_space);
HDassert(dset_info->buf.vp);
/* Set buf pointer */
buf = dset_info->buf.vp;
/* Check for NOOP read */
if (nelmts == 0)
if (dset_info->nelmts == 0)
HGOTO_DONE(SUCCEED)
/* Allocate the iterators */
@ -472,24 +486,24 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf
HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate file iterator")
/* Figure out the strip mine size. */
if (H5S_select_iter_init(file_iter, file_space, type_info->src_type_size,
if (H5S_select_iter_init(file_iter, dset_info->file_space, dset_info->type_info.src_type_size,
H5S_SEL_ITER_GET_SEQ_LIST_SORTED) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize file selection information")
file_iter_init = TRUE; /*file selection iteration info has been initialized */
if (H5S_select_iter_init(mem_iter, mem_space, type_info->dst_type_size, 0) < 0)
if (H5S_select_iter_init(mem_iter, dset_info->mem_space, dset_info->type_info.dst_type_size, 0) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize memory selection information")
mem_iter_init = TRUE; /*file selection iteration info has been initialized */
if (H5S_select_iter_init(bkg_iter, mem_space, type_info->dst_type_size, 0) < 0)
if (H5S_select_iter_init(bkg_iter, dset_info->mem_space, dset_info->type_info.dst_type_size, 0) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize background selection information")
bkg_iter_init = TRUE; /*file selection iteration info has been initialized */
/* Start strip mining... */
for (smine_start = 0; smine_start < nelmts; smine_start += smine_nelmts) {
for (smine_start = 0; smine_start < dset_info->nelmts; smine_start += smine_nelmts) {
size_t n; /* Elements operated on */
/* Go figure out how many elements to read from the file */
HDassert(H5S_SELECT_ITER_NELMTS(file_iter) == (nelmts - smine_start));
smine_nelmts = (size_t)MIN(type_info->request_nelmts, (nelmts - smine_start));
HDassert(H5S_SELECT_ITER_NELMTS(file_iter) == (dset_info->nelmts - smine_start));
smine_nelmts = (size_t)MIN(dset_info->type_info.request_nelmts, (dset_info->nelmts - smine_start));
/*
* Gather the data from disk into the datatype conversion
@ -500,7 +514,7 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf
/*
* Gather data
*/
n = H5D__gather_file(io_info, file_iter, smine_nelmts, type_info->tconv_buf /*out*/);
n = H5D__gather_file(io_info, dset_info, file_iter, smine_nelmts, io_info->tconv_buf /*out*/);
if (n != smine_nelmts)
HGOTO_ERROR(H5E_IO, H5E_READERROR, FAIL, "file gather failed")
@ -508,13 +522,15 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf
* and no conversion is needed, copy the data directly into user's buffer and
* bypass the rest of steps.
*/
if (type_info->cmpd_subset && H5T_SUBSET_FALSE != type_info->cmpd_subset->subset) {
if (H5D__compound_opt_read(smine_nelmts, mem_iter, type_info, buf /*out*/) < 0)
if (dset_info->type_info.cmpd_subset &&
H5T_SUBSET_FALSE != dset_info->type_info.cmpd_subset->subset) {
if (H5D__compound_opt_read(smine_nelmts, mem_iter, &dset_info->type_info, io_info->tconv_buf,
buf /*out*/) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "datatype conversion failed")
} /* end if */
else {
if (H5T_BKG_YES == type_info->need_bkg) {
n = H5D__gather_mem(buf, bkg_iter, smine_nelmts, type_info->bkg_buf /*out*/);
if (H5T_BKG_YES == dset_info->type_info.need_bkg) {
n = H5D__gather_mem(buf, bkg_iter, smine_nelmts, dset_info->type_info.bkg_buf /*out*/);
if (n != smine_nelmts)
HGOTO_ERROR(H5E_IO, H5E_READERROR, FAIL, "mem gather failed")
} /* end if */
@ -522,25 +538,26 @@ H5D__scatgath_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_inf
/*
* Perform datatype conversion.
*/
if (H5T_convert(type_info->tpath, type_info->src_type_id, type_info->dst_type_id, smine_nelmts,
(size_t)0, (size_t)0, type_info->tconv_buf, type_info->bkg_buf) < 0)
if (H5T_convert(dset_info->type_info.tpath, dset_info->type_info.src_type_id,
dset_info->type_info.dst_type_id, smine_nelmts, (size_t)0, (size_t)0,
io_info->tconv_buf, dset_info->type_info.bkg_buf) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCONVERT, FAIL, "datatype conversion failed")
/* Do the data transform after the conversion (since we're using type mem_type) */
if (!type_info->is_xform_noop) {
if (!dset_info->type_info.is_xform_noop) {
H5Z_data_xform_t *data_transform; /* Data transform info */
/* Retrieve info from API context */
if (H5CX_get_data_transform(&data_transform) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't get data transform info")
if (H5Z_xform_eval(data_transform, type_info->tconv_buf, smine_nelmts, type_info->mem_type) <
0)
if (H5Z_xform_eval(data_transform, io_info->tconv_buf, smine_nelmts,
dset_info->type_info.mem_type) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_BADVALUE, FAIL, "Error performing data transform")
}
/* Scatter the data into memory */
if (H5D__scatter_mem(type_info->tconv_buf, mem_iter, smine_nelmts, buf /*out*/) < 0)
if (H5D__scatter_mem(io_info->tconv_buf, mem_iter, smine_nelmts, buf /*out*/) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "scatter failed")
} /* end else */
} /* end for */
@ -576,11 +593,10 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space)
H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info)
{
const void *buf = io_info->u.wbuf; /* Local pointer to application buffer */
H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info*/
const void *buf; /* Local pointer to application buffer */
H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info*/
hbool_t mem_iter_init = FALSE; /* Memory selection iteration info has been initialized */
H5S_sel_iter_t *bkg_iter = NULL; /* Background iteration info*/
hbool_t bkg_iter_init = FALSE; /* Background iteration info has been initialized */
@ -594,13 +610,16 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in
/* Sanity check */
HDassert(io_info);
HDassert(type_info);
HDassert(mem_space);
HDassert(file_space);
HDassert(buf);
HDassert(dset_info);
HDassert(dset_info->mem_space);
HDassert(dset_info->file_space);
HDassert(dset_info->buf.vp);
/* Set buf pointer */
buf = dset_info->buf.cvp;
/* Check for NOOP write */
if (nelmts == 0)
if (dset_info->nelmts == 0)
HGOTO_DONE(SUCCEED)
/* Allocate the iterators */
@ -612,32 +631,32 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in
HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate file iterator")
/* Figure out the strip mine size. */
if (H5S_select_iter_init(file_iter, file_space, type_info->dst_type_size,
if (H5S_select_iter_init(file_iter, dset_info->file_space, dset_info->type_info.dst_type_size,
H5S_SEL_ITER_GET_SEQ_LIST_SORTED) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize file selection information")
file_iter_init = TRUE; /*file selection iteration info has been initialized */
if (H5S_select_iter_init(mem_iter, mem_space, type_info->src_type_size, 0) < 0)
if (H5S_select_iter_init(mem_iter, dset_info->mem_space, dset_info->type_info.src_type_size, 0) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize memory selection information")
mem_iter_init = TRUE; /*file selection iteration info has been initialized */
if (H5S_select_iter_init(bkg_iter, file_space, type_info->dst_type_size,
if (H5S_select_iter_init(bkg_iter, dset_info->file_space, dset_info->type_info.dst_type_size,
H5S_SEL_ITER_GET_SEQ_LIST_SORTED) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to initialize background selection information")
bkg_iter_init = TRUE; /*file selection iteration info has been initialized */
/* Start strip mining... */
for (smine_start = 0; smine_start < nelmts; smine_start += smine_nelmts) {
for (smine_start = 0; smine_start < dset_info->nelmts; smine_start += smine_nelmts) {
size_t n; /* Elements operated on */
/* Go figure out how many elements to read from the file */
HDassert(H5S_SELECT_ITER_NELMTS(file_iter) == (nelmts - smine_start));
smine_nelmts = (size_t)MIN(type_info->request_nelmts, (nelmts - smine_start));
HDassert(H5S_SELECT_ITER_NELMTS(file_iter) == (dset_info->nelmts - smine_start));
smine_nelmts = (size_t)MIN(dset_info->type_info.request_nelmts, (dset_info->nelmts - smine_start));
/*
* Gather data from application buffer into the datatype conversion
* buffer. Also gather data from the file into the background buffer
* if necessary.
*/
n = H5D__gather_mem(buf, mem_iter, smine_nelmts, type_info->tconv_buf /*out*/);
n = H5D__gather_mem(buf, mem_iter, smine_nelmts, io_info->tconv_buf /*out*/);
if (n != smine_nelmts)
HGOTO_ERROR(H5E_IO, H5E_WRITEERROR, FAIL, "mem gather failed")
@ -647,44 +666,46 @@ H5D__scatgath_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_in
* is a subset of the destination, the optimization is done in conversion
* function H5T_conv_struct_opt to protect the background data.
*/
if (type_info->cmpd_subset && H5T_SUBSET_DST == type_info->cmpd_subset->subset &&
type_info->dst_type_size == type_info->cmpd_subset->copy_size) {
if (H5D__compound_opt_write(smine_nelmts, type_info) < 0)
if (dset_info->type_info.cmpd_subset && H5T_SUBSET_DST == dset_info->type_info.cmpd_subset->subset &&
dset_info->type_info.dst_type_size == dset_info->type_info.cmpd_subset->copy_size) {
if (H5D__compound_opt_write(smine_nelmts, &dset_info->type_info, io_info->tconv_buf) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "datatype conversion failed")
} /* end if */
else {
if (H5T_BKG_YES == type_info->need_bkg) {
n = H5D__gather_file(io_info, bkg_iter, smine_nelmts, type_info->bkg_buf /*out*/);
if (H5T_BKG_YES == dset_info->type_info.need_bkg) {
n = H5D__gather_file(io_info, dset_info, bkg_iter, smine_nelmts,
dset_info->type_info.bkg_buf /*out*/);
if (n != smine_nelmts)
HGOTO_ERROR(H5E_IO, H5E_READERROR, FAIL, "file gather failed")
} /* end if */
/* Do the data transform before the type conversion (since
* transforms must be done in the memory type). */
if (!type_info->is_xform_noop) {
if (!dset_info->type_info.is_xform_noop) {
H5Z_data_xform_t *data_transform; /* Data transform info */
/* Retrieve info from API context */
if (H5CX_get_data_transform(&data_transform) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't get data transform info")
if (H5Z_xform_eval(data_transform, type_info->tconv_buf, smine_nelmts, type_info->mem_type) <
0)
if (H5Z_xform_eval(data_transform, io_info->tconv_buf, smine_nelmts,
dset_info->type_info.mem_type) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_BADVALUE, FAIL, "Error performing data transform")
}
/*
* Perform datatype conversion.
*/
if (H5T_convert(type_info->tpath, type_info->src_type_id, type_info->dst_type_id, smine_nelmts,
(size_t)0, (size_t)0, type_info->tconv_buf, type_info->bkg_buf) < 0)
if (H5T_convert(dset_info->type_info.tpath, dset_info->type_info.src_type_id,
dset_info->type_info.dst_type_id, smine_nelmts, (size_t)0, (size_t)0,
io_info->tconv_buf, dset_info->type_info.bkg_buf) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCONVERT, FAIL, "datatype conversion failed")
} /* end else */
/*
* Scatter the data out to the file.
*/
if (H5D__scatter_file(io_info, file_iter, smine_nelmts, type_info->tconv_buf) < 0)
if (H5D__scatter_file(io_info, dset_info, file_iter, smine_nelmts, io_info->tconv_buf) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "scatter failed")
} /* end for */
@ -740,7 +761,7 @@ done:
*/
static herr_t
H5D__compound_opt_read(size_t nelmts, H5S_sel_iter_t *iter, const H5D_type_info_t *type_info,
void *user_buf /*out*/)
uint8_t *tconv_buf, void *user_buf /*out*/)
{
uint8_t *ubuf = (uint8_t *)user_buf; /* Cast for pointer arithmetic */
uint8_t *xdbuf; /* Pointer into dataset buffer */
@ -784,7 +805,7 @@ H5D__compound_opt_read(size_t nelmts, H5S_sel_iter_t *iter, const H5D_type_info_
copy_size = type_info->cmpd_subset->copy_size;
/* Loop until all elements are written */
xdbuf = type_info->tconv_buf;
xdbuf = tconv_buf;
while (nelmts > 0) {
size_t nseq; /* Number of sequences generated */
size_t curr_seq; /* Current sequence being processed */
@ -869,7 +890,7 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__compound_opt_write(size_t nelmts, const H5D_type_info_t *type_info)
H5D__compound_opt_write(size_t nelmts, const H5D_type_info_t *type_info, uint8_t *tconv_buf)
{
uint8_t *xsbuf, *xdbuf; /* Source & destination pointers into dataset buffer */
size_t src_stride, dst_stride; /* Strides through source & destination datatypes */
@ -886,8 +907,8 @@ H5D__compound_opt_write(size_t nelmts, const H5D_type_info_t *type_info)
dst_stride = type_info->dst_type_size;
/* Loop until all elements are written */
xsbuf = (uint8_t *)type_info->tconv_buf;
xdbuf = (uint8_t *)type_info->tconv_buf;
xsbuf = tconv_buf;
xdbuf = tconv_buf;
for (i = 0; i < nelmts; i++) {
HDmemmove(xdbuf, xsbuf, dst_stride);

View File

@ -44,8 +44,8 @@
/* Local Prototypes */
/********************/
static herr_t H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, H5S_t *file_space,
H5S_t *mem_space);
static herr_t H5D__select_io(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info,
size_t elmt_size);
/*********************/
/* Package Variables */
@ -77,8 +77,7 @@ H5FL_EXTERN(H5S_sel_iter_t);
*-------------------------------------------------------------------------
*/
static herr_t
H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, H5S_t *file_space,
H5S_t *mem_space)
H5D__select_io(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info, size_t elmt_size)
{
H5S_sel_iter_t *mem_iter = NULL; /* Memory selection iteration info */
hbool_t mem_iter_init = FALSE; /* Memory selection iteration info has been initialized */
@ -95,19 +94,23 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, H5
size_t dxpl_vec_size; /* Vector length from API context's DXPL */
size_t vec_size; /* Vector length */
ssize_t tmp_file_len; /* Temporary number of bytes in file sequence */
size_t nelmts; /* Number of elements to process */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Check args */
HDassert(io_info);
HDassert(io_info->dset);
HDassert(io_info->store);
HDassert(io_info->u.rbuf);
HDassert(dset_info->dset);
HDassert(dset_info->store);
HDassert(dset_info->buf.vp);
if (elmt_size == 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADVALUE, FAIL, "invalid elmt_size of 0")
/* Initialize nelmts */
nelmts = dset_info->nelmts;
/* Check for only one element in selection */
if (nelmts == 1) {
hsize_t single_mem_off; /* Offset in memory */
@ -116,9 +119,9 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, H5
size_t single_file_len; /* Length in the file */
/* Get offset of first element in selections */
if (H5S_SELECT_OFFSET(file_space, &single_file_off) < 0)
if (H5S_SELECT_OFFSET(dset_info->file_space, &single_file_off) < 0)
HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "can't retrieve file selection offset")
if (H5S_SELECT_OFFSET(mem_space, &single_mem_off) < 0)
if (H5S_SELECT_OFFSET(dset_info->mem_space, &single_mem_off) < 0)
HGOTO_ERROR(H5E_INTERNAL, H5E_UNSUPPORTED, FAIL, "can't retrieve memory selection offset")
/* Set up necessary information for I/O operation */
@ -130,16 +133,16 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, H5
/* Perform I/O on memory and file sequences */
if (io_info->op_type == H5D_IO_OP_READ) {
if ((tmp_file_len = (*io_info->layout_ops.readvv)(
io_info, file_nseq, &curr_file_seq, &single_file_len, &single_file_off, mem_nseq,
&curr_mem_seq, &single_mem_len, &single_mem_off)) < 0)
if ((tmp_file_len = (*dset_info->layout_ops.readvv)(
io_info, dset_info, file_nseq, &curr_file_seq, &single_file_len, &single_file_off,
mem_nseq, &curr_mem_seq, &single_mem_len, &single_mem_off)) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_READERROR, FAIL, "read error")
} /* end if */
else {
HDassert(io_info->op_type == H5D_IO_OP_WRITE);
if ((tmp_file_len = (*io_info->layout_ops.writevv)(
io_info, file_nseq, &curr_file_seq, &single_file_len, &single_file_off, mem_nseq,
&curr_mem_seq, &single_mem_len, &single_mem_off)) < 0)
if ((tmp_file_len = (*dset_info->layout_ops.writevv)(
io_info, dset_info, file_nseq, &curr_file_seq, &single_file_len, &single_file_off,
mem_nseq, &curr_mem_seq, &single_mem_len, &single_mem_off)) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_WRITEERROR, FAIL, "write error")
} /* end else */
@ -175,12 +178,13 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, H5
HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "can't allocate file iterator")
/* Initialize file iterator */
if (H5S_select_iter_init(file_iter, file_space, elmt_size, H5S_SEL_ITER_GET_SEQ_LIST_SORTED) < 0)
if (H5S_select_iter_init(file_iter, dset_info->file_space, elmt_size,
H5S_SEL_ITER_GET_SEQ_LIST_SORTED) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator")
file_iter_init = 1; /* File selection iteration info has been initialized */
/* Initialize memory iterator */
if (H5S_select_iter_init(mem_iter, mem_space, elmt_size, 0) < 0)
if (H5S_select_iter_init(mem_iter, dset_info->mem_space, elmt_size, 0) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_CANTINIT, FAIL, "unable to initialize selection iterator")
mem_iter_init = 1; /* Memory selection iteration info has been initialized */
@ -214,16 +218,16 @@ H5D__select_io(const H5D_io_info_t *io_info, size_t elmt_size, size_t nelmts, H5
/* Perform I/O on memory and file sequences */
if (io_info->op_type == H5D_IO_OP_READ) {
if ((tmp_file_len =
(*io_info->layout_ops.readvv)(io_info, file_nseq, &curr_file_seq, file_len, file_off,
mem_nseq, &curr_mem_seq, mem_len, mem_off)) < 0)
if ((tmp_file_len = (*dset_info->layout_ops.readvv)(
io_info, dset_info, file_nseq, &curr_file_seq, file_len, file_off, mem_nseq,
&curr_mem_seq, mem_len, mem_off)) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_READERROR, FAIL, "read error")
} /* end if */
else {
HDassert(io_info->op_type == H5D_IO_OP_WRITE);
if ((tmp_file_len = (*io_info->layout_ops.writevv)(io_info, file_nseq, &curr_file_seq,
file_len, file_off, mem_nseq,
&curr_mem_seq, mem_len, mem_off)) < 0)
if ((tmp_file_len = (*dset_info->layout_ops.writevv)(
io_info, dset_info, file_nseq, &curr_file_seq, file_len, file_off, mem_nseq,
&curr_mem_seq, mem_len, mem_off)) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_WRITEERROR, FAIL, "write error")
} /* end else */
@ -452,16 +456,14 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5D__select_read(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space)
H5D__select_read(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info)
{
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Call generic selection operation */
H5_CHECK_OVERFLOW(nelmts, hsize_t, size_t);
if (H5D__select_io(io_info, type_info->src_type_size, (size_t)nelmts, file_space, mem_space) < 0)
if (H5D__select_io(io_info, dset_info, dset_info->type_info.src_type_size) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_READERROR, FAIL, "read error")
done:
@ -481,16 +483,14 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5D__select_write(const H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space)
H5D__select_write(const H5D_io_info_t *io_info, const H5D_dset_io_info_t *dset_info)
{
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Call generic selection operation */
H5_CHECK_OVERFLOW(nelmts, hsize_t, size_t);
if (H5D__select_io(io_info, type_info->dst_type_size, (size_t)nelmts, file_space, mem_space) < 0)
if (H5D__select_io(io_info, dset_info, dset_info->type_info.dst_type_size) < 0)
HGOTO_ERROR(H5E_DATASPACE, H5E_WRITEERROR, FAIL, "write error")
done:

View File

@ -83,10 +83,9 @@
/* Layout operation callbacks */
static hbool_t H5D__virtual_is_data_cached(const H5D_shared_t *shared_dset);
static herr_t H5D__virtual_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t *fm);
static herr_t H5D__virtual_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t *fm);
static herr_t H5D__virtual_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
static herr_t H5D__virtual_read(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
static herr_t H5D__virtual_write(H5D_io_info_t *io_info, H5D_dset_io_info_t *dinfo);
static herr_t H5D__virtual_flush(H5D_t *dset);
/* Other functions */
@ -103,13 +102,13 @@ static herr_t H5D__virtual_build_source_name(char
size_t static_strlen, size_t nsubs, hsize_t blockno,
char **built_name);
static herr_t H5D__virtual_init_all(const H5D_t *dset);
static herr_t H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_t *file_space,
H5S_t *mem_space, hsize_t *tot_nelmts);
static herr_t H5D__virtual_pre_io(H5D_dset_io_info_t *dset_info, H5O_storage_virtual_t *storage,
H5S_t *file_space, H5S_t *mem_space, hsize_t *tot_nelmts);
static herr_t H5D__virtual_post_io(H5O_storage_virtual_t *storage);
static herr_t H5D__virtual_read_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
H5S_t *file_space, H5O_storage_virtual_srcdset_t *source_dset);
static herr_t H5D__virtual_write_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
H5S_t *file_space, H5O_storage_virtual_srcdset_t *source_dset);
static herr_t H5D__virtual_read_one(H5D_dset_io_info_t *dset_info,
H5O_storage_virtual_srcdset_t *source_dset);
static herr_t H5D__virtual_write_one(H5D_dset_io_info_t *dset_info,
H5O_storage_virtual_srcdset_t *source_dset);
/*********************/
/* Package Variables */
@ -121,18 +120,15 @@ const H5D_layout_ops_t H5D_LOPS_VIRTUAL[1] = {{
H5D__virtual_init, /* init */
H5D__virtual_is_space_alloc, /* is_space_alloc */
H5D__virtual_is_data_cached, /* is_data_cached */
NULL, /* io_init */
H5D__virtual_io_init, /* io_init */
NULL, /* mdio_init */
H5D__virtual_read, /* ser_read */
H5D__virtual_write, /* ser_write */
#ifdef H5_HAVE_PARALLEL
NULL, /* par_read */
NULL, /* par_write */
#endif
NULL, /* readvv */
NULL, /* writevv */
H5D__virtual_flush, /* flush */
NULL, /* io_term */
NULL /* dest */
NULL, /* readvv */
NULL, /* writevv */
H5D__virtual_flush, /* flush */
NULL, /* io_term */
NULL /* dest */
}};
/*******************/
@ -2370,6 +2366,29 @@ done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5D__virtual_is_data_cached() */
/*-------------------------------------------------------------------------
* Function: H5D__virtual_io_init
*
* Purpose: Performs initialization before any sort of I/O on the raw data
*
* Return: Non-negative on success/Negative on failure
*
* Programmer: Neil Fortner
* Sunday, May 22, 2022
*
*-------------------------------------------------------------------------
*/
static herr_t
H5D__virtual_io_init(H5D_io_info_t *io_info, H5D_dset_io_info_t H5_ATTR_UNUSED *dinfo)
{
FUNC_ENTER_PACKAGE_NOERR
/* Disable selection I/O */
io_info->use_select_io = FALSE;
FUNC_LEAVE_NOAPI(SUCCEED)
} /* end H5D__virtual_io_init() */
/*-------------------------------------------------------------------------
* Function: H5D__virtual_pre_io
*
@ -2386,16 +2405,17 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_t *file_space,
H5D__virtual_pre_io(H5D_dset_io_info_t *dset_info, H5O_storage_virtual_t *storage, H5S_t *file_space,
H5S_t *mem_space, hsize_t *tot_nelmts)
{
hssize_t select_nelmts; /* Number of elements in selection */
hsize_t bounds_start[H5S_MAX_RANK]; /* Selection bounds start */
hsize_t bounds_end[H5S_MAX_RANK]; /* Selection bounds end */
int rank = 0;
hbool_t bounds_init = FALSE; /* Whether bounds_start, bounds_end, and rank are valid */
size_t i, j, k; /* Local index variables */
herr_t ret_value = SUCCEED; /* Return value */
const H5D_t *dset = dset_info->dset; /* Local pointer to dataset info */
hssize_t select_nelmts; /* Number of elements in selection */
hsize_t bounds_start[H5S_MAX_RANK]; /* Selection bounds start */
hsize_t bounds_end[H5S_MAX_RANK]; /* Selection bounds end */
int rank = 0;
hbool_t bounds_init = FALSE; /* Whether bounds_start, bounds_end, and rank are valid */
size_t i, j, k; /* Local index variables */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
@ -2407,7 +2427,7 @@ H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_
/* Initialize layout if necessary */
if (!storage->init)
if (H5D__virtual_init_all(io_info->dset) < 0)
if (H5D__virtual_init_all(dset) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "can't initialize virtual layout")
/* Initialize tot_nelmts */
@ -2427,7 +2447,7 @@ H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_
/* Get selection bounds if necessary */
if (!bounds_init) {
/* Get rank of VDS */
if ((rank = H5S_GET_EXTENT_NDIMS(io_info->dset->shared->space)) < 0)
if ((rank = H5S_GET_EXTENT_NDIMS(dset->shared->space)) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "unable to get number of dimensions")
/* Get selection bounds */
@ -2469,7 +2489,7 @@ H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_
* open the source dataset to patch it */
if (storage->list[i].source_space_status != H5O_VIRTUAL_STATUS_CORRECT) {
HDassert(!storage->list[i].sub_dset[j].dset);
if (H5D__virtual_open_source_dset(io_info->dset, &storage->list[i],
if (H5D__virtual_open_source_dset(dset, &storage->list[i],
&storage->list[i].sub_dset[j]) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTOPENOBJ, FAIL, "unable to open source dataset")
} /* end if */
@ -2499,7 +2519,7 @@ H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to modify size of dataspace")
/* Get current VDS dimensions */
if (H5S_get_simple_extent_dims(io_info->dset->shared->space, tmp_dims, NULL) < 0)
if (H5S_get_simple_extent_dims(dset->shared->space, tmp_dims, NULL) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't get VDS dimensions")
/* Copy virtual selection */
@ -2554,7 +2574,7 @@ H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_
/* Open source dataset */
if (!storage->list[i].sub_dset[j].dset)
/* Try to open dataset */
if (H5D__virtual_open_source_dset(io_info->dset, &storage->list[i],
if (H5D__virtual_open_source_dset(dset, &storage->list[i],
&storage->list[i].sub_dset[j]) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTOPENOBJ, FAIL,
"unable to open source dataset")
@ -2599,7 +2619,7 @@ H5D__virtual_pre_io(H5D_io_info_t *io_info, H5O_storage_virtual_t *storage, H5S_
/* Open source dataset */
if (!storage->list[i].source_dset.dset)
/* Try to open dataset */
if (H5D__virtual_open_source_dset(io_info->dset, &storage->list[i],
if (H5D__virtual_open_source_dset(dset, &storage->list[i],
&storage->list[i].source_dset) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTOPENOBJ, FAIL, "unable to open source dataset")
@ -2697,11 +2717,11 @@ H5D__virtual_post_io(H5O_storage_virtual_t *storage)
*-------------------------------------------------------------------------
*/
static herr_t
H5D__virtual_read_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, H5S_t *file_space,
H5O_storage_virtual_srcdset_t *source_dset)
H5D__virtual_read_one(H5D_dset_io_info_t *dset_info, H5O_storage_virtual_srcdset_t *source_dset)
{
H5S_t *projected_src_space = NULL; /* File space for selection in a single source dataset */
herr_t ret_value = SUCCEED; /* Return value */
H5S_t *projected_src_space = NULL; /* File space for selection in a single source dataset */
H5D_dset_io_info_t source_dinfo; /* Dataset info for source dataset read */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
@ -2717,15 +2737,23 @@ H5D__virtual_read_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
/* Project intersection of file space and mapping virtual space onto
* mapping source space */
if (H5S_select_project_intersection(source_dset->clipped_virtual_select,
source_dset->clipped_source_select, file_space,
source_dset->clipped_source_select, dset_info->file_space,
&projected_src_space, TRUE) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCLIP, FAIL,
"can't project virtual intersection onto source space")
/* Perform read on source dataset */
if (H5D__read(source_dset->dset, type_info->dst_type_id, source_dset->projected_mem_space,
projected_src_space, io_info->u.rbuf) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read source dataset")
{
/* Initialize source_dinfo */
source_dinfo.dset = source_dset->dset;
source_dinfo.mem_space = source_dset->projected_mem_space;
source_dinfo.file_space = projected_src_space;
source_dinfo.buf.vp = dset_info->buf.vp;
source_dinfo.mem_type_id = dset_info->type_info.dst_type_id;
/* Read in the point (with the custom VL memory allocator) */
if (H5D__read(1, &source_dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read source dataset")
}
/* Close projected_src_space */
if (H5S_close(projected_src_space) < 0)
@ -2734,7 +2762,7 @@ H5D__virtual_read_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
} /* end if */
done:
/* Release allocated resources on failure */
/* Release allocated resources */
if (projected_src_space) {
HDassert(ret_value < 0);
if (H5S_close(projected_src_space) < 0)
@ -2757,12 +2785,12 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__virtual_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts, H5S_t *file_space,
H5S_t *mem_space, H5D_chunk_map_t H5_ATTR_UNUSED *fm)
H5D__virtual_read(H5D_io_info_t *io_info, H5D_dset_io_info_t *dset_info)
{
H5O_storage_virtual_t *storage; /* Convenient pointer into layout struct */
hsize_t tot_nelmts; /* Total number of elements mapped to mem_space */
H5S_t *fill_space = NULL; /* Space to fill with fill value */
size_t nelmts; /* Number of elements to process */
size_t i, j; /* Local index variables */
herr_t ret_value = SUCCEED; /* Return value */
@ -2770,22 +2798,25 @@ H5D__virtual_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsiz
/* Sanity check */
HDassert(io_info);
HDassert(io_info->u.rbuf);
HDassert(type_info);
HDassert(mem_space);
HDassert(file_space);
HDassert(dset_info);
HDassert(dset_info->buf.vp);
HDassert(dset_info->mem_space);
HDassert(dset_info->file_space);
storage = &io_info->dset->shared->layout.storage.u.virt;
storage = &(dset_info->dset->shared->layout.storage.u.virt);
HDassert((storage->view == H5D_VDS_FIRST_MISSING) || (storage->view == H5D_VDS_LAST_AVAILABLE));
/* Initialize nelmts */
nelmts = H5S_GET_SELECT_NPOINTS(dset_info->file_space);
#ifdef H5_HAVE_PARALLEL
/* Parallel reads are not supported (yet) */
if (H5F_HAS_FEATURE(io_info->dset->oloc.file, H5FD_FEAT_HAS_MPI))
if (H5F_HAS_FEATURE(dset_info->dset->oloc.file, H5FD_FEAT_HAS_MPI))
HGOTO_ERROR(H5E_DATASET, H5E_UNSUPPORTED, FAIL, "parallel reads not supported on virtual datasets")
#endif /* H5_HAVE_PARALLEL */
/* Prepare for I/O operation */
if (H5D__virtual_pre_io(io_info, storage, file_space, mem_space, &tot_nelmts) < 0)
if (H5D__virtual_pre_io(dset_info, storage, dset_info->file_space, dset_info->mem_space, &tot_nelmts) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCLIP, FAIL, "unable to prepare for I/O operation")
/* Iterate over mappings */
@ -2797,12 +2828,12 @@ H5D__virtual_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsiz
if (storage->list[i].psfn_nsubs || storage->list[i].psdn_nsubs) {
/* Iterate over sub-source dsets */
for (j = storage->list[i].sub_dset_io_start; j < storage->list[i].sub_dset_io_end; j++)
if (H5D__virtual_read_one(io_info, type_info, file_space, &storage->list[i].sub_dset[j]) < 0)
if (H5D__virtual_read_one(dset_info, &storage->list[i].sub_dset[j]) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "unable to read source dataset")
} /* end if */
else
/* Read from source dataset */
if (H5D__virtual_read_one(io_info, type_info, file_space, &storage->list[i].source_dset) < 0)
if (H5D__virtual_read_one(dset_info, &storage->list[i].source_dset) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "unable to read source dataset")
} /* end for */
@ -2811,13 +2842,13 @@ H5D__virtual_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsiz
H5D_fill_value_t fill_status; /* Fill value status */
/* Check the fill value status */
if (H5P_is_fill_value_defined(&io_info->dset->shared->dcpl_cache.fill, &fill_status) < 0)
if (H5P_is_fill_value_defined(&dset_info->dset->shared->dcpl_cache.fill, &fill_status) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "can't tell if fill value defined")
/* Always write fill value to memory buffer unless it is undefined */
if (fill_status != H5D_FILL_VALUE_UNDEFINED) {
/* Start with fill space equal to memory space */
if (NULL == (fill_space = H5S_copy(mem_space, FALSE, TRUE)))
if (NULL == (fill_space = H5S_copy(dset_info->mem_space, FALSE, TRUE)))
HGOTO_ERROR(H5E_DATASET, H5E_CANTCOPY, FAIL, "unable to copy memory selection")
/* Iterate over mappings */
@ -2837,8 +2868,8 @@ H5D__virtual_read(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsiz
HGOTO_ERROR(H5E_DATASET, H5E_CANTCLIP, FAIL, "unable to clip fill selection")
/* Write fill values to memory buffer */
if (H5D__fill(io_info->dset->shared->dcpl_cache.fill.buf, io_info->dset->shared->type,
io_info->u.rbuf, type_info->mem_type, fill_space) < 0)
if (H5D__fill(dset_info->dset->shared->dcpl_cache.fill.buf, dset_info->dset->shared->type,
dset_info->buf.vp, dset_info->type_info.mem_type, fill_space) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "filling buf failed")
#ifndef NDEBUG
@ -2887,11 +2918,11 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__virtual_write_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, H5S_t *file_space,
H5O_storage_virtual_srcdset_t *source_dset)
H5D__virtual_write_one(H5D_dset_io_info_t *dset_info, H5O_storage_virtual_srcdset_t *source_dset)
{
H5S_t *projected_src_space = NULL; /* File space for selection in a single source dataset */
herr_t ret_value = SUCCEED; /* Return value */
H5S_t *projected_src_space = NULL; /* File space for selection in a single source dataset */
H5D_dset_io_info_t source_dinfo; /* Dataset info for source dataset write */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
@ -2909,15 +2940,23 @@ H5D__virtual_write_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
/* Project intersection of file space and mapping virtual space onto
* mapping source space */
if (H5S_select_project_intersection(source_dset->clipped_virtual_select,
source_dset->clipped_source_select, file_space,
source_dset->clipped_source_select, dset_info->file_space,
&projected_src_space, TRUE) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCLIP, FAIL,
"can't project virtual intersection onto source space")
/* Perform write on source dataset */
if (H5D__write(source_dset->dset, type_info->dst_type_id, source_dset->projected_mem_space,
projected_src_space, io_info->u.wbuf) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't write to source dataset")
{
/* Initialize source_dinfo */
source_dinfo.dset = source_dset->dset;
source_dinfo.mem_space = source_dset->projected_mem_space;
source_dinfo.file_space = projected_src_space;
source_dinfo.buf.cvp = dset_info->buf.cvp;
source_dinfo.mem_type_id = dset_info->type_info.dst_type_id;
/* Read in the point (with the custom VL memory allocator) */
if (H5D__write(1, &source_dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read source dataset")
}
/* Close projected_src_space */
if (H5S_close(projected_src_space) < 0)
@ -2926,7 +2965,7 @@ H5D__virtual_write_one(H5D_io_info_t *io_info, const H5D_type_info_t *type_info,
} /* end if */
done:
/* Release allocated resources on failure */
/* Release allocated resources */
if (projected_src_space) {
HDassert(ret_value < 0);
if (H5S_close(projected_src_space) < 0)
@ -2949,11 +2988,11 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5D__virtual_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsize_t nelmts,
H5S_t *file_space, H5S_t *mem_space, H5D_chunk_map_t H5_ATTR_UNUSED *fm)
H5D__virtual_write(H5D_io_info_t *io_info, H5D_dset_io_info_t *dset_info)
{
H5O_storage_virtual_t *storage; /* Convenient pointer into layout struct */
hsize_t tot_nelmts; /* Total number of elements mapped to mem_space */
size_t nelmts; /* Number of elements to process */
size_t i, j; /* Local index variables */
herr_t ret_value = SUCCEED; /* Return value */
@ -2961,22 +3000,25 @@ H5D__virtual_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsi
/* Sanity check */
HDassert(io_info);
HDassert(io_info->u.wbuf);
HDassert(type_info);
HDassert(mem_space);
HDassert(file_space);
HDassert(dset_info);
HDassert(dset_info->buf.cvp);
HDassert(dset_info->mem_space);
HDassert(dset_info->file_space);
storage = &io_info->dset->shared->layout.storage.u.virt;
storage = &(dset_info->dset->shared->layout.storage.u.virt);
HDassert((storage->view == H5D_VDS_FIRST_MISSING) || (storage->view == H5D_VDS_LAST_AVAILABLE));
/* Initialize nelmts */
nelmts = H5S_GET_SELECT_NPOINTS(dset_info->file_space);
#ifdef H5_HAVE_PARALLEL
/* Parallel writes are not supported (yet) */
if (H5F_HAS_FEATURE(io_info->dset->oloc.file, H5FD_FEAT_HAS_MPI))
if (H5F_HAS_FEATURE(dset_info->dset->oloc.file, H5FD_FEAT_HAS_MPI))
HGOTO_ERROR(H5E_DATASET, H5E_UNSUPPORTED, FAIL, "parallel writes not supported on virtual datasets")
#endif /* H5_HAVE_PARALLEL */
/* Prepare for I/O operation */
if (H5D__virtual_pre_io(io_info, storage, file_space, mem_space, &tot_nelmts) < 0)
if (H5D__virtual_pre_io(dset_info, storage, dset_info->file_space, dset_info->mem_space, &tot_nelmts) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCLIP, FAIL, "unable to prepare for I/O operation")
/* Fail if there are unmapped parts of the selection as they would not be
@ -2994,12 +3036,12 @@ H5D__virtual_write(H5D_io_info_t *io_info, const H5D_type_info_t *type_info, hsi
if (storage->list[i].psfn_nsubs || storage->list[i].psdn_nsubs) {
/* Iterate over sub-source dsets */
for (j = storage->list[i].sub_dset_io_start; j < storage->list[i].sub_dset_io_end; j++)
if (H5D__virtual_write_one(io_info, type_info, file_space, &storage->list[i].sub_dset[j]) < 0)
if (H5D__virtual_write_one(dset_info, &storage->list[i].sub_dset[j]) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "unable to write to source dataset")
} /* end if */
else
/* Write to source dataset */
if (H5D__virtual_write_one(io_info, type_info, file_space, &storage->list[i].source_dset) < 0)
if (H5D__virtual_write_one(dset_info, &storage->list[i].source_dset) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "unable to write to source dataset")
} /* end for */

View File

@ -400,7 +400,7 @@ done:
PURPOSE
Get the number of elements in current selection
USAGE
hssize_t H5Sget_select_npoints(space)
hsize_t H5Sget_select_npoints(space)
H5S_t *space; IN: Dataspace of selection to query
RETURNS
The number of elements in selection on success, 0 on failure

View File

@ -88,10 +88,12 @@ static void *H5VL__dataset_create(void *obj, const H5VL_loc_params_t *loc_param
hid_t dcpl_id, hid_t dapl_id, hid_t dxpl_id, void **req);
static void *H5VL__dataset_open(void *obj, const H5VL_loc_params_t *loc_params, const H5VL_class_t *cls,
const char *name, hid_t dapl_id, hid_t dxpl_id, void **req);
static herr_t H5VL__dataset_read(void *dset, const H5VL_class_t *cls, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t dxpl_id, void *buf, void **req);
static herr_t H5VL__dataset_write(void *obj, const H5VL_class_t *cls, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t dxpl_id, const void *buf, void **req);
static herr_t H5VL__dataset_read(size_t count, void *obj[], const H5VL_class_t *cls, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id, void *buf[],
void **req);
static herr_t H5VL__dataset_write(size_t count, void *obj[], const H5VL_class_t *cls, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id,
const void *buf[], void **req);
static herr_t H5VL__dataset_get(void *obj, const H5VL_class_t *cls, H5VL_dataset_get_args_t *args,
hid_t dxpl_id, void **req);
static herr_t H5VL__dataset_specific(void *obj, const H5VL_class_t *cls, H5VL_dataset_specific_args_t *args,
@ -2020,9 +2022,9 @@ done:
} /* end H5VLdataset_open() */
/*-------------------------------------------------------------------------
* Function: H5VL__dataset_read
* Function: H5VL__dataset_read
*
* Purpose: Reads data from dataset through the VOL
* Purpose: Reads data from dataset through the VOL
*
* Return: Success: Non-negative
* Failure: Negative
@ -2030,8 +2032,8 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5VL__dataset_read(void *obj, const H5VL_class_t *cls, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t dxpl_id, void *buf, void **req)
H5VL__dataset_read(size_t count, void *obj[], const H5VL_class_t *cls, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **req)
{
herr_t ret_value = SUCCEED; /* Return value */
@ -2042,13 +2044,61 @@ H5VL__dataset_read(void *obj, const H5VL_class_t *cls, hid_t mem_type_id, hid_t
HGOTO_ERROR(H5E_VOL, H5E_UNSUPPORTED, FAIL, "VOL connector has no 'dataset read' method")
/* Call the corresponding VOL callback */
if ((cls->dataset_cls.read)(obj, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
if ((cls->dataset_cls.read)(count, obj, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_READERROR, FAIL, "dataset read failed")
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL__dataset_read() */
/*-------------------------------------------------------------------------
* Function: H5VL_dataset_read_direct
*
* Purpose: Reads data from dataset through the VOL. This is like
* H5VL_dataset_read, but takes an array of void * for the
* objects and a class pointer instead of an array of
* H5VL_object_t. This allows us to avoid allocating and
* copying an extra array (of H5VL_object_ts).
*
* Return: Success: Non-negative
* Failure: Negative
*
*-------------------------------------------------------------------------
*/
herr_t
H5VL_dataset_read_direct(size_t count, void *obj[], H5VL_t *connector, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **req)
{
hbool_t vol_wrapper_set = FALSE; /* Whether the VOL object wrapping context was set up */
H5VL_object_t tmp_vol_obj; /* Temporary VOL object for setting VOL wrapper */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_NOAPI(FAIL)
HDassert(obj);
HDassert(connector);
/* Set wrapper info in API context */
tmp_vol_obj.data = obj[0];
tmp_vol_obj.connector = connector;
tmp_vol_obj.rc = 1;
if (H5VL_set_vol_wrapper(&tmp_vol_obj) < 0)
HGOTO_ERROR(H5E_VOL, H5E_CANTSET, FAIL, "can't set VOL wrapper info")
vol_wrapper_set = TRUE;
/* Call the corresponding internal VOL routine */
if (H5VL__dataset_read(count, obj, connector->cls, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf,
req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_READERROR, FAIL, "dataset read failed")
done:
/* Reset object wrapping info in API context */
if (vol_wrapper_set && H5VL_reset_vol_wrapper() < 0)
HDONE_ERROR(H5E_VOL, H5E_CANTRESET, FAIL, "can't reset VOL wrapper info")
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL_dataset_read_direct() */
/*-------------------------------------------------------------------------
* Function: H5VL_dataset_read
*
@ -2060,21 +2110,44 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5VL_dataset_read(const H5VL_object_t *vol_obj, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, void *buf, void **req)
H5VL_dataset_read(size_t count, const H5VL_object_t *vol_obj[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **req)
{
hbool_t vol_wrapper_set = FALSE; /* Whether the VOL object wrapping context was set up */
herr_t ret_value = SUCCEED; /* Return value */
hbool_t vol_wrapper_set = FALSE; /* Whether the VOL object wrapping context was set up */
void *obj_local; /* Local buffer for obj */
void **obj = &obj_local; /* Array of object pointers */
size_t i; /* Local index variable */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_NOAPI(FAIL)
HDassert(vol_obj);
HDassert(vol_obj[0]);
/* Set wrapper info in API context */
if (H5VL_set_vol_wrapper(vol_obj) < 0)
if (H5VL_set_vol_wrapper(vol_obj[0]) < 0)
HGOTO_ERROR(H5E_VOL, H5E_CANTSET, FAIL, "can't set VOL wrapper info")
vol_wrapper_set = TRUE;
/* Allocate obj array if necessary */
if (count > 1)
if (NULL == (obj = (void **)H5MM_malloc(count * sizeof(void *))))
HGOTO_ERROR(H5E_VOL, H5E_CANTALLOC, FAIL, "can't allocate space for object array")
/* Build obj array */
for (i = 0; i < count; i++) {
/* Get the object */
obj[i] = vol_obj[i]->data;
/* Make sure the class matches */
if (vol_obj[i]->connector->cls->value != vol_obj[0]->connector->cls->value)
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL,
"datasets are accessed through different VOL connectors and can't be used in the "
"same I/O call")
}
/* Call the corresponding internal VOL routine */
if (H5VL__dataset_read(vol_obj->data, vol_obj->connector->cls, mem_type_id, mem_space_id, file_space_id,
if (H5VL__dataset_read(count, obj, vol_obj[0]->connector->cls, mem_type_id, mem_space_id, file_space_id,
dxpl_id, buf, req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_READERROR, FAIL, "dataset read failed")
@ -2083,6 +2156,10 @@ done:
if (vol_wrapper_set && H5VL_reset_vol_wrapper() < 0)
HDONE_ERROR(H5E_VOL, H5E_CANTRESET, FAIL, "can't reset VOL wrapper info")
/* Free memory */
if (obj != &obj_local)
H5MM_free(obj);
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL_dataset_read() */
@ -2097,24 +2174,36 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5VLdataset_read(void *obj, hid_t connector_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, void *buf, void **req /*out*/)
H5VLdataset_read(size_t count, void *obj[], hid_t connector_id, hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **req /*out*/)
{
H5VL_class_t *cls; /* VOL connector's class struct */
size_t i; /* Local index variable */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_API_NOINIT
H5TRACE8("e", "*xiiiii*xx", obj, connector_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf,
req);
H5TRACE9("e", "z**xi*i*i*ii**xx", count, obj, connector_id, mem_type_id, mem_space_id, file_space_id,
dxpl_id, buf, req);
/* Check args and get class pointer */
if (NULL == obj)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid object")
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "obj array not provided")
for (i = 1; i < count; i++)
if (NULL == obj[i])
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid object")
if (NULL == mem_type_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_type_id array not provided")
if (NULL == mem_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_space_id array not provided")
if (NULL == file_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "file_space_id array not provided")
if (NULL == buf)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "buf array not provided")
if (NULL == (cls = (H5VL_class_t *)H5I_object_verify(connector_id, H5I_VOL)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a VOL connector ID")
/* Call the corresponding internal VOL routine */
if (H5VL__dataset_read(obj, cls, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
if (H5VL__dataset_read(count, obj, cls, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_CANTINIT, FAIL, "unable to read dataset")
done:
@ -2122,9 +2211,9 @@ done:
} /* end H5VLdataset_read() */
/*-------------------------------------------------------------------------
* Function: H5VL__dataset_write
* Function: H5VL__dataset_write
*
* Purpose: Writes data from dataset through the VOL
* Purpose: Writes data from dataset through the VOL
*
* Return: Success: Non-negative
* Failure: Negative
@ -2132,8 +2221,8 @@ done:
*-------------------------------------------------------------------------
*/
static herr_t
H5VL__dataset_write(void *obj, const H5VL_class_t *cls, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t dxpl_id, const void *buf, void **req)
H5VL__dataset_write(size_t count, void *obj[], const H5VL_class_t *cls, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void **req)
{
herr_t ret_value = SUCCEED; /* Return value */
@ -2144,13 +2233,62 @@ H5VL__dataset_write(void *obj, const H5VL_class_t *cls, hid_t mem_type_id, hid_t
HGOTO_ERROR(H5E_VOL, H5E_UNSUPPORTED, FAIL, "VOL connector has no 'dataset write' method")
/* Call the corresponding VOL callback */
if ((cls->dataset_cls.write)(obj, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
if ((cls->dataset_cls.write)(count, obj, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_WRITEERROR, FAIL, "dataset write failed")
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL__dataset_write() */
/*-------------------------------------------------------------------------
* Function: H5VL_dataset_write_direct
*
* Purpose: Writes data from dataset through the VOL. This is like
* H5VL_dataset_write, but takes an array of void * for the
* objects and a class pointer instead of an array of
* H5VL_object_t. This allows us to avoid allocating and
* copying an extra array (of H5VL_object_ts).
*
* Return: Success: Non-negative
* Failure: Negative
*
*-------------------------------------------------------------------------
*/
herr_t
H5VL_dataset_write_direct(size_t count, void *obj[], H5VL_t *connector, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id, const void *buf[],
void **req)
{
hbool_t vol_wrapper_set = FALSE; /* Whether the VOL object wrapping context was set up */
H5VL_object_t tmp_vol_obj; /* Temporary VOL object for setting VOL wrapper */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_NOAPI(FAIL)
HDassert(obj);
HDassert(connector);
/* Set wrapper info in API context */
tmp_vol_obj.data = obj[0];
tmp_vol_obj.connector = connector;
tmp_vol_obj.rc = 1;
if (H5VL_set_vol_wrapper(&tmp_vol_obj) < 0)
HGOTO_ERROR(H5E_VOL, H5E_CANTSET, FAIL, "can't set VOL wrapper info")
vol_wrapper_set = TRUE;
/* Call the corresponding internal VOL routine */
if (H5VL__dataset_write(count, obj, connector->cls, mem_type_id, mem_space_id, file_space_id, dxpl_id,
buf, req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_WRITEERROR, FAIL, "dataset write failed")
done:
/* Reset object wrapping info in API context */
if (vol_wrapper_set && H5VL_reset_vol_wrapper() < 0)
HDONE_ERROR(H5E_VOL, H5E_CANTRESET, FAIL, "can't reset VOL wrapper info")
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL_dataset_write_direct() */
/*-------------------------------------------------------------------------
* Function: H5VL_dataset_write
*
@ -2162,21 +2300,44 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5VL_dataset_write(const H5VL_object_t *vol_obj, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, const void *buf, void **req)
H5VL_dataset_write(size_t count, const H5VL_object_t *vol_obj[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void **req)
{
hbool_t vol_wrapper_set = FALSE; /* Whether the VOL object wrapping context was set up */
herr_t ret_value = SUCCEED; /* Return value */
hbool_t vol_wrapper_set = FALSE; /* Whether the VOL object wrapping context was set up */
void *obj_local; /* Local buffer for obj */
void **obj = &obj_local; /* Array of object pointers */
size_t i; /* Local index variable */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_NOAPI(FAIL)
HDassert(vol_obj);
HDassert(vol_obj[0]);
/* Set wrapper info in API context */
if (H5VL_set_vol_wrapper(vol_obj) < 0)
if (H5VL_set_vol_wrapper(vol_obj[0]) < 0)
HGOTO_ERROR(H5E_VOL, H5E_CANTSET, FAIL, "can't set VOL wrapper info")
vol_wrapper_set = TRUE;
/* Allocate obj array if necessary */
if (count > 1)
if (NULL == (obj = (void **)H5MM_malloc(count * sizeof(void *))))
HGOTO_ERROR(H5E_VOL, H5E_CANTALLOC, FAIL, "can't allocate space for object array")
/* Build obj array */
for (i = 0; i < count; i++) {
/* Get the object */
obj[i] = vol_obj[i]->data;
/* Make sure the class matches */
if (vol_obj[i]->connector->cls->value != vol_obj[0]->connector->cls->value)
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL,
"datasets are accessed through different VOL connectors and can't be used in the "
"same I/O call")
}
/* Call the corresponding internal VOL routine */
if (H5VL__dataset_write(vol_obj->data, vol_obj->connector->cls, mem_type_id, mem_space_id, file_space_id,
if (H5VL__dataset_write(count, obj, vol_obj[0]->connector->cls, mem_type_id, mem_space_id, file_space_id,
dxpl_id, buf, req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_WRITEERROR, FAIL, "dataset write failed")
@ -2185,6 +2346,10 @@ done:
if (vol_wrapper_set && H5VL_reset_vol_wrapper() < 0)
HDONE_ERROR(H5E_VOL, H5E_CANTRESET, FAIL, "can't reset VOL wrapper info")
/* Free memory */
if (obj != &obj_local)
H5MM_free(obj);
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL_dataset_write() */
@ -2199,24 +2364,36 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5VLdataset_write(void *obj, hid_t connector_id, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, const void *buf, void **req /*out*/)
H5VLdataset_write(size_t count, void *obj[], hid_t connector_id, hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void **req /*out*/)
{
H5VL_class_t *cls; /* VOL connector's class struct */
size_t i; /* Local index variable */
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_API_NOINIT
H5TRACE8("e", "*xiiiii*xx", obj, connector_id, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf,
req);
H5TRACE9("e", "z**xi*i*i*ii**xx", count, obj, connector_id, mem_type_id, mem_space_id, file_space_id,
dxpl_id, buf, req);
/* Check args and get class pointer */
if (NULL == obj)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid object")
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "obj array not provided")
for (i = 1; i < count; i++)
if (NULL == obj[i])
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "invalid object")
if (NULL == mem_type_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_type_id array not provided")
if (NULL == mem_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "mem_space_id array not provided")
if (NULL == file_space_id)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "file_space_id array not provided")
if (NULL == buf)
HGOTO_ERROR(H5E_ARGS, H5E_BADVALUE, FAIL, "buf array not provided")
if (NULL == (cls = (H5VL_class_t *)H5I_object_verify(connector_id, H5I_VOL)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "not a VOL connector ID")
/* Call the corresponding internal VOL routine */
if (H5VL__dataset_write(obj, cls, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
if (H5VL__dataset_write(count, obj, cls, mem_type_id, mem_space_id, file_space_id, dxpl_id, buf, req) < 0)
HGOTO_ERROR(H5E_VOL, H5E_CANTINIT, FAIL, "unable to write dataset")
done:

View File

@ -879,10 +879,10 @@ typedef struct H5VL_dataset_class_t {
hid_t type_id, hid_t space_id, hid_t dcpl_id, hid_t dapl_id, hid_t dxpl_id, void **req);
void *(*open)(void *obj, const H5VL_loc_params_t *loc_params, const char *name, hid_t dapl_id,
hid_t dxpl_id, void **req);
herr_t (*read)(void *dset, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id, hid_t dxpl_id,
void *buf, void **req);
herr_t (*write)(void *dset, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id, hid_t dxpl_id,
const void *buf, void **req);
herr_t (*read)(size_t count, void *dset[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **req);
herr_t (*write)(size_t count, void *dset[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void **req);
herr_t (*get)(void *obj, H5VL_dataset_get_args_t *args, hid_t dxpl_id, void **req);
herr_t (*specific)(void *obj, H5VL_dataset_specific_args_t *args, hid_t dxpl_id, void **req);
herr_t (*optional)(void *obj, H5VL_optional_args_t *args, hid_t dxpl_id, void **req);

View File

@ -107,10 +107,12 @@ H5_DLL void *H5VLdataset_create(void *obj, const H5VL_loc_params_t *loc_params,
hid_t dapl_id, hid_t dxpl_id, void **req);
H5_DLL void *H5VLdataset_open(void *obj, const H5VL_loc_params_t *loc_params, hid_t connector_id,
const char *name, hid_t dapl_id, hid_t dxpl_id, void **req);
H5_DLL herr_t H5VLdataset_read(void *dset, hid_t connector_id, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t plist_id, void *buf, void **req);
H5_DLL herr_t H5VLdataset_write(void *dset, hid_t connector_id, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t plist_id, const void *buf, void **req);
H5_DLL herr_t H5VLdataset_read(size_t count, void *dset[], hid_t connector_id, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t plist_id, void *buf[],
void **req);
H5_DLL herr_t H5VLdataset_write(size_t count, void *dset[], hid_t connector_id, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t plist_id,
const void *buf[], void **req);
H5_DLL herr_t H5VLdataset_get(void *dset, hid_t connector_id, H5VL_dataset_get_args_t *args, hid_t dxpl_id,
void **req);
H5_DLL herr_t H5VLdataset_specific(void *obj, hid_t connector_id, H5VL_dataset_specific_args_t *args,

View File

@ -50,8 +50,11 @@
/********************/
/* Helper routines for read/write API calls */
static herr_t H5VL__native_dataset_io_setup(H5D_t *dset, hid_t dxpl_id, hid_t file_space_id,
hid_t mem_space_id, H5S_t **file_space, H5S_t **mem_space);
static herr_t H5VL__native_dataset_io_setup(size_t count, void *obj[], hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id,
H5_flexible_const_ptr_t buf[], H5D_dset_io_info_t *dinfo);
static herr_t H5VL__native_dataset_io_cleanup(size_t count, hid_t mem_space_id[], hid_t file_space_id[],
H5D_dset_io_info_t *dinfo);
/*********************/
/* Package Variables */
@ -75,89 +78,153 @@ static herr_t H5VL__native_dataset_io_setup(H5D_t *dset, hid_t dxpl_id, hid_t fi
*-------------------------------------------------------------------------
*/
static herr_t
H5VL__native_dataset_io_setup(H5D_t *dset, hid_t dxpl_id, hid_t file_space_id, hid_t mem_space_id,
H5S_t **file_space, H5S_t **mem_space)
H5VL__native_dataset_io_setup(size_t count, void *obj[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, H5_flexible_const_ptr_t buf[],
H5D_dset_io_info_t *dinfo)
{
H5F_shared_t *f_sh;
size_t i;
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Sanity checks */
HDassert(dinfo);
/* Get shared file */
f_sh = H5F_SHARED(((H5D_t *)obj[0])->oloc.file);
/* Iterate over datasets */
for (i = 0; i < count; i++) {
/* Set up dset */
dinfo[i].dset = (H5D_t *)obj[i];
HDassert(dinfo[i].dset);
/* Check dataset's file pointer is valid */
if (NULL == dinfo[i].dset->oloc.file)
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "dataset is not associated with a file")
if (f_sh != H5F_SHARED(dinfo[i].dset->oloc.file))
HGOTO_ERROR(H5E_ARGS, H5E_UNSUPPORTED, FAIL,
"different files detected in multi dataset I/O request")
/* Set up memory type */
dinfo[i].mem_type_id = mem_type_id[i];
/* Set up file dataspace */
if (H5S_ALL == file_space_id[i])
/* Use dataspace for dataset */
dinfo[i].file_space = dinfo[i].dset->shared->space;
else if (H5S_BLOCK == file_space_id[i])
HGOTO_ERROR(H5E_DATASET, H5E_BADTYPE, FAIL, "H5S_BLOCK is not allowed for file dataspace")
else if (H5S_PLIST == file_space_id[i]) {
H5P_genplist_t *plist; /* Property list pointer */
H5S_t *space; /* Dataspace to hold selection */
/* Get the plist structure */
if (NULL == (plist = H5P_object_verify(dxpl_id, H5P_DATASET_XFER)))
HGOTO_ERROR(H5E_DATASET, H5E_BADID, FAIL, "bad dataset transfer property list")
/* Get a pointer to the file space in the property list */
if (H5P_peek(plist, H5D_XFER_DSET_IO_SEL_NAME, &space) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "error getting dataset I/O selection")
/* Use dataspace for dataset */
dinfo[i].file_space = dinfo[i].dset->shared->space;
/* Copy, but share, selection from property list to dataset's dataspace */
if (H5S_SELECT_COPY(dinfo[i].file_space, space, TRUE) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCOPY, FAIL, "can't copy dataset I/O selection")
} /* end else-if */
else {
/* Get the dataspace pointer */
if (NULL == (dinfo[i].file_space = (H5S_t *)H5I_object_verify(file_space_id[i], H5I_DATASPACE)))
HGOTO_ERROR(H5E_DATASET, H5E_BADTYPE, FAIL, "file_space_id is not a dataspace ID")
} /* end else */
/* Get dataspace for memory buffer */
if (H5S_ALL == mem_space_id[i])
dinfo[i].mem_space = dinfo[i].file_space;
else if (H5S_BLOCK == mem_space_id[i]) {
hsize_t nelmts; /* # of selected elements in file */
/* Get the # of elements selected */
nelmts = H5S_GET_SELECT_NPOINTS(dinfo[i].file_space);
/* Check for any elements */
if (nelmts > 0) {
/* Create a 1-D dataspace of the same # of elements */
if (NULL == (dinfo[i].mem_space = H5S_create_simple(1, &nelmts, NULL)))
HGOTO_ERROR(H5E_DATASET, H5E_CANTCREATE, FAIL, "unable to create simple memory dataspace")
} /* end if */
else {
/* Create a NULL dataspace of the same # of elements */
if (NULL == (dinfo[i].mem_space = H5S_create(H5S_NULL)))
HGOTO_ERROR(H5E_DATASET, H5E_CANTCREATE, FAIL, "unable to create NULL memory dataspace")
} /* end else */
} /* end if */
else if (H5S_PLIST == mem_space_id[i])
HGOTO_ERROR(H5E_DATASET, H5E_BADTYPE, FAIL, "H5S_PLIST is not allowed for memory dataspace")
else {
/* Get the dataspace pointer */
if (NULL == (dinfo[i].mem_space = (H5S_t *)H5I_object_verify(mem_space_id[i], H5I_DATASPACE)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "mem_space_id is not a dataspace ID")
} /* end else */
/* Check for valid selections */
if (H5S_SELECT_VALID(dinfo[i].file_space) != TRUE)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADRANGE, FAIL,
"selection + offset not within extent for file dataspace")
if (H5S_SELECT_VALID(dinfo[i].mem_space) != TRUE)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADRANGE, FAIL,
"selection + offset not within extent for memory dataspace")
/* Set up buf */
dinfo[i].buf = buf[i];
}
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL__native_dataset_io_setup() */
/*-------------------------------------------------------------------------
* Function: H5VL__native_dataset_io_cleanup
*
* Purpose: Frees memory allocated by H5VL__native_dataset_io_setup()
*
* Return: SUCCEED/FAIL
*
*-------------------------------------------------------------------------
*/
static herr_t
H5VL__native_dataset_io_cleanup(size_t count, hid_t mem_space_id[], hid_t file_space_id[],
H5D_dset_io_info_t *dinfo)
{
size_t i;
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Sanity checks */
HDassert(dset);
HDassert(file_space && NULL == *file_space);
HDassert(mem_space && NULL == *mem_space);
HDassert(dinfo);
/* Set up file dataspace */
if (H5S_ALL == file_space_id)
/* Use dataspace for dataset */
*file_space = dset->shared->space;
else if (H5S_BLOCK == file_space_id)
HGOTO_ERROR(H5E_DATASET, H5E_BADTYPE, FAIL, "H5S_BLOCK is not allowed for file dataspace")
else if (H5S_PLIST == file_space_id) {
H5P_genplist_t *plist; /* Property list pointer */
H5S_t *space; /* Dataspace to hold selection */
/* Iterate over datasets */
for (i = 0; i < count; i++) {
/* Free memory dataspace if it was created. Use HDONE_ERROR in this function so we always
* try to free everything we can. */
if (H5S_BLOCK == mem_space_id[i] && dinfo[i].mem_space)
if (H5S_close(dinfo[i].mem_space) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL,
"unable to release temporary memory dataspace for H5S_BLOCK")
/* Get the plist structure */
if (NULL == (plist = H5P_object_verify(dxpl_id, H5P_DATASET_XFER)))
HGOTO_ERROR(H5E_DATASET, H5E_BADID, FAIL, "bad dataset transfer property list")
/* Reset file dataspace selection if it was copied from the property list */
if (H5S_PLIST == file_space_id[i] && dinfo[i].file_space)
if (H5S_select_all(dinfo[i].file_space, TRUE) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL,
"unable to release file dataspace selection for H5S_PLIST")
}
/* See if a dataset I/O selection is already set, and free it if it is */
if (H5P_peek(plist, H5D_XFER_DSET_IO_SEL_NAME, &space) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTGET, FAIL, "error getting dataset I/O selection")
/* Use dataspace for dataset */
*file_space = dset->shared->space;
/* Copy, but share, selection from property list to dataset's dataspace */
if (H5S_SELECT_COPY(*file_space, space, TRUE) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTCOPY, FAIL, "can't copy dataset I/O selection")
} /* end else-if */
else {
/* Get the dataspace pointer */
if (NULL == (*file_space = (H5S_t *)H5I_object_verify(file_space_id, H5I_DATASPACE)))
HGOTO_ERROR(H5E_DATASET, H5E_BADTYPE, FAIL, "file_space_id is not a dataspace ID")
} /* end else */
/* Get dataspace for memory buffer */
if (H5S_ALL == mem_space_id)
*mem_space = *file_space;
else if (H5S_BLOCK == mem_space_id) {
hsize_t nelmts; /* # of selected elements in file */
/* Get the # of elements selected */
nelmts = H5S_GET_SELECT_NPOINTS(*file_space);
/* Check for any elements */
if (nelmts > 0) {
/* Create a 1-D dataspace of the same # of elements */
if (NULL == (*mem_space = H5S_create_simple(1, &nelmts, NULL)))
HGOTO_ERROR(H5E_DATASET, H5E_CANTCREATE, FAIL, "unable to create simple memory dataspace")
} /* end if */
else {
/* Create a NULL dataspace of the same # of elements */
if (NULL == (*mem_space = H5S_create(H5S_NULL)))
HGOTO_ERROR(H5E_DATASET, H5E_CANTCREATE, FAIL, "unable to create NULL memory dataspace")
} /* end else */
} /* end if */
else if (H5S_PLIST == mem_space_id)
HGOTO_ERROR(H5E_DATASET, H5E_BADTYPE, FAIL, "H5S_PLIST is not allowed for memory dataspace")
else {
/* Get the dataspace pointer */
if (NULL == (*mem_space = (H5S_t *)H5I_object_verify(mem_space_id, H5I_DATASPACE)))
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "mem_space_id is not a dataspace ID")
} /* end else */
/* Check for valid selections */
if (H5S_SELECT_VALID(*file_space) != TRUE)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADRANGE, FAIL,
"selection + offset not within extent for file dataspace")
if (H5S_SELECT_VALID(*mem_space) != TRUE)
HGOTO_ERROR(H5E_DATASPACE, H5E_BADRANGE, FAIL,
"selection + offset not within extent for memory dataspace")
done:
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL__native_dataset_io_setup() */
} /* end H5VL__native_dataset_io_cleanup() */
/*-------------------------------------------------------------------------
* Function: H5VL__native_dataset_create
@ -267,43 +334,39 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5VL__native_dataset_read(void *obj, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, void *buf, void H5_ATTR_UNUSED **req)
H5VL__native_dataset_read(size_t count, void *obj[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[], void H5_ATTR_UNUSED **req)
{
H5D_t *dset = (H5D_t *)obj;
H5S_t *mem_space = NULL;
H5S_t *file_space = NULL;
herr_t ret_value = SUCCEED; /* Return value */
H5D_dset_io_info_t dinfo_local;
H5D_dset_io_info_t *dinfo = &dinfo_local;
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* Check arguments */
if (NULL == dset->oloc.file)
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "dataset is not associated with a file")
/* Allocate dataset info array if necessary */
if (count > 1)
if (NULL == (dinfo = (H5D_dset_io_info_t *)H5MM_malloc(count * sizeof(H5D_dset_io_info_t))))
HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "couldn't allocate dset info array buffer")
/* Get file & memory dataspaces */
if (H5VL__native_dataset_io_setup(dset, dxpl_id, file_space_id, mem_space_id, &file_space, &mem_space) <
0)
if (H5VL__native_dataset_io_setup(count, obj, mem_type_id, mem_space_id, file_space_id, dxpl_id,
(H5_flexible_const_ptr_t *)buf, dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to set up file and memory dataspaces")
/* Set DXPL for operation */
H5CX_set_dxpl(dxpl_id);
/* Read raw data */
if (H5D__read(dset, mem_type_id, mem_space, file_space, buf /*out*/) < 0)
/* Read raw data. Call H5D__read directly in single dset case. */
if (H5D__read(count, dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_READERROR, FAIL, "can't read data")
done:
/* Clean up */
if (H5S_BLOCK == mem_space_id && mem_space) {
if (H5S_close(mem_space) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL,
"unable to release temporary memory dataspace for H5S_BLOCK")
} /* end if */
else if (H5S_PLIST == file_space_id && file_space)
if (H5S_select_all(file_space, TRUE) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL,
"unable to release file dataspace selection for H5S_PLIST")
if (H5VL__native_dataset_io_cleanup(count, mem_space_id, file_space_id, dinfo) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL, "unable to release dataset info")
if (dinfo != &dinfo_local)
H5MM_xfree(dinfo);
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL__native_dataset_read() */
@ -318,43 +381,39 @@ done:
*-------------------------------------------------------------------------
*/
herr_t
H5VL__native_dataset_write(void *obj, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t dxpl_id, const void *buf, void H5_ATTR_UNUSED **req)
H5VL__native_dataset_write(size_t count, void *obj[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void H5_ATTR_UNUSED **req)
{
H5D_t *dset = (H5D_t *)obj;
H5S_t *mem_space = NULL;
H5S_t *file_space = NULL;
herr_t ret_value = SUCCEED; /* Return value */
H5D_dset_io_info_t dinfo_local;
H5D_dset_io_info_t *dinfo = &dinfo_local;
herr_t ret_value = SUCCEED; /* Return value */
FUNC_ENTER_PACKAGE
/* check arguments */
if (NULL == dset->oloc.file)
HGOTO_ERROR(H5E_ARGS, H5E_BADTYPE, FAIL, "dataset is not associated with a file")
/* Allocate dataset info array if necessary */
if (count > 1)
if (NULL == (dinfo = (H5D_dset_io_info_t *)H5MM_malloc(count * sizeof(H5D_dset_io_info_t))))
HGOTO_ERROR(H5E_DATASET, H5E_CANTALLOC, FAIL, "couldn't allocate dset info array buffer")
/* Get file & memory dataspaces */
if (H5VL__native_dataset_io_setup(dset, dxpl_id, file_space_id, mem_space_id, &file_space, &mem_space) <
0)
if (H5VL__native_dataset_io_setup(count, obj, mem_type_id, mem_space_id, file_space_id, dxpl_id,
(H5_flexible_const_ptr_t *)buf, dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_CANTINIT, FAIL, "unable to set up file and memory dataspaces")
/* Set DXPL for operation */
H5CX_set_dxpl(dxpl_id);
/* Write the data */
if (H5D__write(dset, mem_type_id, mem_space, file_space, buf) < 0)
/* Write raw data. Call H5D__write directly in single dset case. */
if (H5D__write(count, dinfo) < 0)
HGOTO_ERROR(H5E_DATASET, H5E_WRITEERROR, FAIL, "can't write data")
done:
/* Clean up */
if (H5S_BLOCK == mem_space_id && mem_space) {
if (H5S_close(mem_space) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL,
"unable to release temporary memory dataspace for H5S_BLOCK")
} /* end if */
else if (H5S_PLIST == file_space_id && file_space)
if (H5S_select_all(file_space, TRUE) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL,
"unable to release file dataspace selection for H5S_PLIST")
if (H5VL__native_dataset_io_cleanup(count, mem_space_id, file_space_id, dinfo) < 0)
HDONE_ERROR(H5E_DATASET, H5E_CANTRELEASE, FAIL, "unable to release dataset info")
if (dinfo != &dinfo_local)
H5MM_xfree(dinfo);
FUNC_LEAVE_NOAPI(ret_value)
} /* end H5VL__native_dataset_write() */

View File

@ -61,10 +61,10 @@ H5_DLL void *H5VL__native_dataset_create(void *obj, const H5VL_loc_params_t *lo
hid_t dapl_id, hid_t dxpl_id, void **req);
H5_DLL void *H5VL__native_dataset_open(void *obj, const H5VL_loc_params_t *loc_params, const char *name,
hid_t dapl_id, hid_t dxpl_id, void **req);
H5_DLL herr_t H5VL__native_dataset_read(void *dset, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t plist_id, void *buf, void **req);
H5_DLL herr_t H5VL__native_dataset_write(void *dset, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t plist_id, const void *buf, void **req);
H5_DLL herr_t H5VL__native_dataset_read(size_t count, void *obj[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, void *buf[], void **req);
H5_DLL herr_t H5VL__native_dataset_write(size_t count, void *obj[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t dxpl_id, const void *buf[], void **req);
H5_DLL herr_t H5VL__native_dataset_get(void *dset, H5VL_dataset_get_args_t *args, hid_t dxpl_id, void **req);
H5_DLL herr_t H5VL__native_dataset_specific(void *dset, H5VL_dataset_specific_args_t *args, hid_t dxpl_id,
void **req);

View File

@ -121,11 +121,12 @@ static void *H5VL_pass_through_dataset_create(void *obj, const H5VL_loc_params_
hid_t dcpl_id, hid_t dapl_id, hid_t dxpl_id, void **req);
static void *H5VL_pass_through_dataset_open(void *obj, const H5VL_loc_params_t *loc_params, const char *name,
hid_t dapl_id, hid_t dxpl_id, void **req);
static herr_t H5VL_pass_through_dataset_read(void *dset, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t plist_id, void *buf, void **req);
static herr_t H5VL_pass_through_dataset_write(void *dset, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t plist_id, const void *buf,
void **req);
static herr_t H5VL_pass_through_dataset_read(size_t count, void *dset[], hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t plist_id,
void *buf[], void **req);
static herr_t H5VL_pass_through_dataset_write(size_t count, void *dset[], hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t plist_id,
const void *buf[], void **req);
static herr_t H5VL_pass_through_dataset_get(void *dset, H5VL_dataset_get_args_t *args, hid_t dxpl_id,
void **req);
static herr_t H5VL_pass_through_dataset_specific(void *obj, H5VL_dataset_specific_args_t *args, hid_t dxpl_id,
@ -1197,22 +1198,43 @@ H5VL_pass_through_dataset_open(void *obj, const H5VL_loc_params_t *loc_params, c
*-------------------------------------------------------------------------
*/
static herr_t
H5VL_pass_through_dataset_read(void *dset, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t plist_id, void *buf, void **req)
H5VL_pass_through_dataset_read(size_t count, void *dset[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t plist_id, void *buf[], void **req)
{
H5VL_pass_through_t *o = (H5VL_pass_through_t *)dset;
herr_t ret_value;
void *obj_local; /* Local buffer for obj */
void **obj = &obj_local; /* Array of object pointers */
size_t i; /* Local index variable */
herr_t ret_value;
#ifdef ENABLE_PASSTHRU_LOGGING
printf("------- PASS THROUGH VOL DATASET Read\n");
#endif
ret_value = H5VLdataset_read(o->under_object, o->under_vol_id, mem_type_id, mem_space_id, file_space_id,
plist_id, buf, req);
/* Allocate obj array if necessary */
if (count > 1)
if (NULL == (obj = (void **)malloc(count * sizeof(void *))))
return -1;
/* Build obj array */
for (i = 0; i < count; i++) {
/* Get the object */
obj[i] = ((H5VL_pass_through_t *)dset[i])->under_object;
/* Make sure the class matches */
if (((H5VL_pass_through_t *)dset[i])->under_vol_id != ((H5VL_pass_through_t *)dset[0])->under_vol_id)
return -1;
}
ret_value = H5VLdataset_read(count, obj, ((H5VL_pass_through_t *)dset[0])->under_vol_id, mem_type_id,
mem_space_id, file_space_id, plist_id, buf, req);
/* Check for async request */
if (req && *req)
*req = H5VL_pass_through_new_obj(*req, o->under_vol_id);
*req = H5VL_pass_through_new_obj(*req, ((H5VL_pass_through_t *)dset[0])->under_vol_id);
/* Free memory */
if (obj != &obj_local)
free(obj);
return ret_value;
} /* end H5VL_pass_through_dataset_read() */
@ -1228,22 +1250,43 @@ H5VL_pass_through_dataset_read(void *dset, hid_t mem_type_id, hid_t mem_space_id
*-------------------------------------------------------------------------
*/
static herr_t
H5VL_pass_through_dataset_write(void *dset, hid_t mem_type_id, hid_t mem_space_id, hid_t file_space_id,
hid_t plist_id, const void *buf, void **req)
H5VL_pass_through_dataset_write(size_t count, void *dset[], hid_t mem_type_id[], hid_t mem_space_id[],
hid_t file_space_id[], hid_t plist_id, const void *buf[], void **req)
{
H5VL_pass_through_t *o = (H5VL_pass_through_t *)dset;
herr_t ret_value;
void *obj_local; /* Local buffer for obj */
void **obj = &obj_local; /* Array of object pointers */
size_t i; /* Local index variable */
herr_t ret_value;
#ifdef ENABLE_PASSTHRU_LOGGING
printf("------- PASS THROUGH VOL DATASET Write\n");
#endif
ret_value = H5VLdataset_write(o->under_object, o->under_vol_id, mem_type_id, mem_space_id, file_space_id,
plist_id, buf, req);
/* Allocate obj array if necessary */
if (count > 1)
if (NULL == (obj = (void **)malloc(count * sizeof(void *))))
return -1;
/* Build obj array */
for (i = 0; i < count; i++) {
/* Get the object */
obj[i] = ((H5VL_pass_through_t *)dset[i])->under_object;
/* Make sure the class matches */
if (((H5VL_pass_through_t *)dset[i])->under_vol_id != ((H5VL_pass_through_t *)dset[0])->under_vol_id)
return -1;
}
ret_value = H5VLdataset_write(count, obj, ((H5VL_pass_through_t *)dset[0])->under_vol_id, mem_type_id,
mem_space_id, file_space_id, plist_id, buf, req);
/* Check for async request */
if (req && *req)
*req = H5VL_pass_through_new_obj(*req, o->under_vol_id);
*req = H5VL_pass_through_new_obj(*req, ((H5VL_pass_through_t *)dset[0])->under_vol_id);
/* Free memory */
if (obj != &obj_local)
free(obj);
return ret_value;
} /* end H5VL_pass_through_dataset_write() */

View File

@ -177,10 +177,18 @@ H5_DLL void *H5VL_dataset_create(const H5VL_object_t *vol_obj, const H5VL_loc_p
hid_t dcpl_id, hid_t dapl_id, hid_t dxpl_id, void **req);
H5_DLL void *H5VL_dataset_open(const H5VL_object_t *vol_obj, const H5VL_loc_params_t *loc_params,
const char *name, hid_t dapl_id, hid_t dxpl_id, void **req);
H5_DLL herr_t H5VL_dataset_read(const H5VL_object_t *vol_obj, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t dxpl_id, void *buf, void **req);
H5_DLL herr_t H5VL_dataset_write(const H5VL_object_t *vol_obj, hid_t mem_type_id, hid_t mem_space_id,
hid_t file_space_id, hid_t dxpl_id, const void *buf, void **req);
H5_DLL herr_t H5VL_dataset_read(size_t count, const H5VL_object_t *vol_obj[], hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id, void *buf[],
void **req);
H5_DLL herr_t H5VL_dataset_read_direct(size_t count, void *obj[], H5VL_t *connector, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id,
void *buf[], void **req);
H5_DLL herr_t H5VL_dataset_write(size_t count, const H5VL_object_t *vol_obj[], hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id,
const void *buf[], void **req);
H5_DLL herr_t H5VL_dataset_write_direct(size_t count, void *obj[], H5VL_t *connector, hid_t mem_type_id[],
hid_t mem_space_id[], hid_t file_space_id[], hid_t dxpl_id,
const void *buf[], void **req);
H5_DLL herr_t H5VL_dataset_get(const H5VL_object_t *vol_obj, H5VL_dataset_get_args_t *args, hid_t dxpl_id,
void **req);
H5_DLL herr_t H5VL_dataset_specific(const H5VL_object_t *cls, H5VL_dataset_specific_args_t *args,

View File

@ -2512,7 +2512,9 @@ H5_DLL herr_t H5CX_pop(hbool_t update_dxpl_props);
/* Union for const/non-const pointer for use by functions that manipulate
* pointers but do not write to their targets or return pointers to const
* specified locations. This helps us avoid compiler warnings. */
* specified locations. Also used for I/O functions that work for read and
* write - these functions are expected to never write to these locations in the
* write case. This helps us avoid compiler warnings. */
typedef union {
void *vp;
const void *cvp;

View File

@ -339,6 +339,7 @@ set (H5_TESTS
dsets
chunk_info # compression lib link
cmpd_dset
mdset
filter_fail
extend
direct_chunk # compression lib link

View File

@ -64,7 +64,7 @@ TEST_PROG= testhdf5 \
cache cache_api cache_image cache_tagging lheap ohdr \
stab gheap evict_on_close farray earray btree2 fheap \
accum hyperslab istore bittests dt_arith page_buffer \
dtypes dsets chunk_info cmpd_dset cmpd_dtransform filter_fail extend direct_chunk \
dtypes dsets chunk_info cmpd_dset mdset cmpd_dtransform filter_fail extend direct_chunk \
external efc objcopy objcopy_ref links unlink twriteorder big mtime \
fillval mount \
flush1 flush2 app_ref enum set_extent ttsafe enc_dec_plist \
@ -184,7 +184,7 @@ flush2.chkexe_: flush1.chkexe_
# specifying a file prefix or low-level driver. Changing the file
# prefix or low-level driver with environment variables will influence
# the temporary file name in ways that the makefile is not aware of.
CHECK_CLEANFILES+=accum.h5 cmpd_dset.h5 compact_dataset.h5 dataset.h5 dset_offset.h5 \
CHECK_CLEANFILES+=accum.h5 cmpd_dset.h5 mdset.h5 compact_dataset.h5 dataset.h5 dset_offset.h5 \
max_compact_dataset.h5 simple.h5 set_local.h5 random_chunks.h5 \
huge_chunks.h5 chunk_cache.h5 big_chunk.h5 chunk_fast.h5 chunk_expand.h5 \
chunk_fixed.h5 copy_dcpl_newfile.h5 partial_chunks.h5 layout_extend.h5 \

714
test/mdset.c Normal file
View File

@ -0,0 +1,714 @@
/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* Copyright by The HDF Group. *
* Copyright by the Board of Trustees of the University of Illinois. *
* All rights reserved. *
* *
* This file is part of HDF5. The full HDF5 copyright notice, including *
* terms governing use, modification, and redistribution, is contained in *
* the files COPYING and Copyright.html. COPYING can be found at the root *
* of the source code distribution tree; Copyright.html can be found at the *
* root level of an installed copy of the electronic HDF5 document set and *
* is linked from the top-level documents page. It can also be found at *
* http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
* access to either file, you may request a copy from help@hdfgroup.org. *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
/*
* Programmer: Neil Fortner
* March 10, 2014
*
* Purpose: Test H5Dwrite_multi() and H5Dread_multi using randomized
* parameters. Also tests H5Dwrite() and H5Dread() using a similar
* method.
*/
#include "h5test.h"
#define NAME_BUF_SIZE 1024
#define MAX_DSETS 6
#define MAX_DSET_X 10
#define MAX_DSET_Y 10
#define MAX_CHUNK_X 4
#define MAX_CHUNK_Y 4
#define MAX_HS_X 6
#define MAX_HS_Y 6
#define MAX_HS 3
#define MAX_POINTS 6
#define OPS_PER_FILE 50
#define DSET_MAX_NAME_LEN 8
#define EXT_FILENAME "mdset_ext.h5"
#define SOURCE_DS_NAME "vds_source"
/* Option flags */
#define MDSET_FLAG_CHUNK 0x01u
#define MDSET_FLAG_MLAYOUT 0x02u
#define MDSET_FLAG_SHAPESAME 0x04u
#define MDSET_FLAG_MDSET 0x08u
#define MDSET_FLAG_TCONV 0x10u
#define MDSET_FLAG_FILTER 0x20u
#define MDSET_ALL_FLAGS \
(MDSET_FLAG_CHUNK | MDSET_FLAG_MLAYOUT | MDSET_FLAG_SHAPESAME | MDSET_FLAG_MDSET | MDSET_FLAG_TCONV | \
MDSET_FLAG_FILTER)
const char *FILENAME[] = {"mdset", "mdset1", "mdset2", NULL};
/* Names for datasets */
char dset_name[MAX_DSETS][DSET_MAX_NAME_LEN];
/* Whether these filters are available */
htri_t deflate_avail = FALSE;
htri_t fletcher32_avail = FALSE;
static int
test_mdset_location(hid_t fapl_id)
{
hid_t file_id1, file_id2;
herr_t ret;
hid_t dset_ids[2];
hid_t mem_type_ids[2];
hid_t mem_space_ids[2];
hid_t file_space_ids[2];
void *rbufs[2];
const void *wbufs[2];
hsize_t dset_dims[2];
int *buf = NULL;
char filename1[NAME_BUF_SIZE];
char filename2[NAME_BUF_SIZE];
TESTING("mdset location");
h5_fixname(FILENAME[1], fapl_id, filename1, sizeof filename1);
h5_fixname(FILENAME[2], fapl_id, filename2, sizeof filename2);
/* Create files */
if ((file_id1 = H5Fcreate(filename1, H5F_ACC_TRUNC, H5P_DEFAULT, fapl_id)) < 0)
TEST_ERROR;
if ((file_id2 = H5Fcreate(filename2, H5F_ACC_TRUNC, H5P_DEFAULT, fapl_id)) < 0)
TEST_ERROR;
if (NULL == (buf = (int *)HDcalloc(2 * MAX_DSET_X * MAX_DSET_Y, sizeof(int))))
TEST_ERROR;
/* Generate memory dataspace */
dset_dims[0] = MAX_DSET_X;
dset_dims[1] = MAX_DSET_Y;
if ((file_space_ids[0] = H5Screate_simple(2, dset_dims, NULL)) < 0)
TEST_ERROR;
if ((file_space_ids[1] = H5Screate_simple(2, dset_dims, NULL)) < 0)
TEST_ERROR;
mem_space_ids[0] = H5S_ALL;
mem_space_ids[1] = H5S_ALL;
mem_type_ids[0] = H5T_NATIVE_UINT;
mem_type_ids[1] = H5T_NATIVE_UINT;
if ((dset_ids[0] = H5Dcreate2(file_id1, dset_name[0], H5T_NATIVE_UINT, file_space_ids[0], H5P_DEFAULT,
H5P_DEFAULT, H5P_DEFAULT)) < 0)
TEST_ERROR;
if ((dset_ids[1] = H5Dcreate2(file_id2, dset_name[1], H5T_NATIVE_UINT, file_space_ids[1], H5P_DEFAULT,
H5P_DEFAULT, H5P_DEFAULT)) < 0)
TEST_ERROR;
wbufs[0] = buf;
wbufs[1] = buf + (MAX_DSET_X * MAX_DSET_Y);
H5E_BEGIN_TRY
{
ret = H5Dwrite_multi(2, dset_ids, mem_type_ids, mem_space_ids, file_space_ids, H5P_DEFAULT, wbufs);
}
H5E_END_TRY
if (ret >= 0) {
fprintf(stderr, "H5Dmulti_write with datasets in multiple files should fail.\n");
TEST_ERROR;
}
rbufs[0] = buf;
rbufs[1] = buf + (MAX_DSET_X * MAX_DSET_Y);
H5E_BEGIN_TRY
{
ret = H5Dread_multi(2, dset_ids, mem_type_ids, mem_space_ids, file_space_ids, H5P_DEFAULT, rbufs);
}
H5E_END_TRY
if (ret >= 0) {
fprintf(stderr, "H5Dmulti_read with datasets in multiple files should fail.\n");
TEST_ERROR;
}
H5Dclose(dset_ids[0]);
H5Sclose(file_space_ids[0]);
H5Dclose(dset_ids[1]);
H5Sclose(file_space_ids[1]);
H5Fclose(file_id1);
H5Fclose(file_id2);
if (buf)
free(buf);
PASSED();
return 0;
error:
if (buf)
free(buf);
return -1;
}
/*-------------------------------------------------------------------------
* Function: test_mdset
*
* Purpose: Test randomized I/O using one or more datasets. Creates a
* file, runs OPS_PER_FILE read or write operations verifying
* that reads return the expected data, then closes the file.
* Runs the test with a new file niter times.
*
* The operations can use either hyperslab or point
* selections. Options are available for chunked or
* contiguous layout, use of multiple datasets and H5D*_multi
* calls, and use of the "shapesame" algorithm code path. To
* avoid the shapesame path when that option is not set, this
* function simply adds a dimension to the memory buffer in a
* way that the shapesame code is not designed to handle.
*
* Return: Number of errors
*
* Programmer: Neil Fortner
* Monday, March 10, 2014
*
*-------------------------------------------------------------------------
*/
static int
test_mdset(size_t niter, unsigned flags, hid_t fapl_id)
{
hid_t dset_ids[MAX_DSETS];
hid_t mem_type_ids[MAX_DSETS];
hid_t mem_space_ids[MAX_DSETS];
hid_t file_space_ids[MAX_DSETS];
void *rbufs[MAX_DSETS];
const void *wbufs[MAX_DSETS];
size_t max_dsets;
size_t buf_size;
size_t ndsets;
hid_t file_id = -1;
hid_t dcpl_id[MAX_DSETS];
hsize_t dset_dims[MAX_DSETS][3];
hsize_t chunk_dims[2];
hsize_t max_dims[2] = {H5S_UNLIMITED, H5S_UNLIMITED};
unsigned *rbuf = NULL;
unsigned *rbufi[MAX_DSETS][MAX_DSET_X];
unsigned *erbuf = NULL;
unsigned *erbufi[MAX_DSETS][MAX_DSET_X];
unsigned *wbuf = NULL;
unsigned *wbufi[MAX_DSETS][MAX_DSET_X];
unsigned *efbuf = NULL;
unsigned *efbufi[MAX_DSETS][MAX_DSET_X];
hbool_t do_read;
hsize_t start[3];
hsize_t count[3];
hsize_t points[3 * MAX_POINTS];
char filename[NAME_BUF_SIZE];
size_t i, j, k, l, m, n;
TESTING("random I/O");
h5_fixname(FILENAME[0], fapl_id, filename, sizeof filename);
/* Calculate maximum number of datasets */
max_dsets = (flags & MDSET_FLAG_MDSET) ? MAX_DSETS : 1;
/* Calculate buffer size */
buf_size = max_dsets * MAX_DSET_X * MAX_DSET_Y * sizeof(unsigned);
/* Initialize dcpl_id array */
for (i = 0; i < max_dsets; i++)
dcpl_id[i] = -1;
/* Allocate buffers */
if (NULL == (rbuf = (unsigned *)HDmalloc(buf_size)))
TEST_ERROR;
if (NULL == (erbuf = (unsigned *)HDmalloc(buf_size)))
TEST_ERROR;
if (NULL == (wbuf = (unsigned *)HDmalloc(buf_size)))
TEST_ERROR;
if (NULL == (efbuf = (unsigned *)HDmalloc(buf_size)))
TEST_ERROR;
/* Initialize buffer indices */
for (i = 0; i < max_dsets; i++)
for (j = 0; j < MAX_DSET_X; j++) {
rbufi[i][j] = rbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
erbufi[i][j] = erbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
wbufi[i][j] = wbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
efbufi[i][j] = efbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
} /* end for */
/* Initialize 3rd dimension information (for tricking library into using
* non-"shapesame" code */
for (i = 0; i < max_dsets; i++)
dset_dims[i][2] = 1;
start[2] = 0;
count[2] = 1;
/* Initialize IDs */
for (i = 0; i < max_dsets; i++) {
dset_ids[i] = -1;
file_space_ids[i] = -1;
mem_type_ids[i] = H5T_NATIVE_UINT;
mem_space_ids[i] = -1;
} /* end for */
/* Generate memory dataspace */
dset_dims[0][0] = MAX_DSET_X;
dset_dims[0][1] = MAX_DSET_Y;
if ((mem_space_ids[0] = H5Screate_simple((flags & MDSET_FLAG_SHAPESAME) ? 2 : 3, dset_dims[0], NULL)) < 0)
TEST_ERROR;
for (i = 1; i < max_dsets; i++)
if ((mem_space_ids[i] = H5Scopy(mem_space_ids[0])) < 0)
TEST_ERROR;
/* Create dcpl 0 */
if ((dcpl_id[0] = H5Pcreate(H5P_DATASET_CREATE)) < 0)
TEST_ERROR;
/* Set fill time to alloc, and alloc time to early (so we always know
* what's in the file) */
if (H5Pset_fill_time(dcpl_id[0], H5D_FILL_TIME_ALLOC) < 0)
TEST_ERROR;
if (H5Pset_alloc_time(dcpl_id[0], H5D_ALLOC_TIME_EARLY) < 0)
TEST_ERROR;
/* Set filters if requested */
if (flags & MDSET_FLAG_FILTER) {
if (fletcher32_avail)
if (H5Pset_fletcher32(dcpl_id[0]) < 0)
TEST_ERROR;
if (deflate_avail)
if (H5Pset_deflate(dcpl_id[0], 1) < 0)
TEST_ERROR;
}
/* Copy dcpl 0 to other slots in dcpl_id array */
for (i = 1; i < MAX_DSETS; i++)
if ((dcpl_id[i] = H5Pcopy(dcpl_id[0])) < 0)
TEST_ERROR;
/* If this is a multi layout run, set up different filters and layouts. Chunked and virtual
* datasets will be set every iteration (with different dims), and contiguous is the default, so
* no need to set either of those. */
if (flags & MDSET_FLAG_MLAYOUT) {
/* Set filters on dataset 2 */
if (fletcher32_avail)
if (H5Pset_fletcher32(dcpl_id[2]) < 0)
TEST_ERROR;
if (deflate_avail)
if (H5Pset_deflate(dcpl_id[2], 1) < 0)
TEST_ERROR;
/* Dataset 3 is compact */
if (H5Pset_layout(dcpl_id[3], H5D_COMPACT) < 0)
TEST_ERROR;
/* Dataset 4 is external */
if (H5Pset_external(dcpl_id[4], EXT_FILENAME, 0, H5F_UNLIMITED) < 0)
TEST_ERROR;
}
for (i = 0; i < niter; i++) {
/* Determine number of datasets */
ndsets = (flags & MDSET_FLAG_MLAYOUT) ? 6
: (flags & MDSET_FLAG_MDSET) ? (size_t)((size_t)HDrandom() % max_dsets) + 1
: 1;
/* Create file */
if ((file_id = H5Fcreate(filename, H5F_ACC_TRUNC, H5P_DEFAULT, fapl_id)) < 0)
TEST_ERROR;
/* Create datasets */
for (j = 0; j < ndsets; j++) {
hid_t source_dset;
hbool_t use_chunk =
(flags & MDSET_FLAG_CHUNK) || ((flags & MDSET_FLAG_MLAYOUT) && (j == 1 || j == 2));
/* Generate file dataspace */
dset_dims[j][0] = (hsize_t)((HDrandom() % MAX_DSET_X) + 1);
dset_dims[j][1] = (hsize_t)((HDrandom() % MAX_DSET_Y) + 1);
if ((file_space_ids[j] = H5Screate_simple(2, dset_dims[j], use_chunk ? max_dims : NULL)) < 0)
TEST_ERROR;
/* Generate chunk if called for by configuration (multi layout uses chunked for datasets
* 1 and 2) */
if (use_chunk) {
chunk_dims[0] = (hsize_t)((HDrandom() % MAX_CHUNK_X) + 1);
chunk_dims[1] = (hsize_t)((HDrandom() % MAX_CHUNK_Y) + 1);
if (H5Pset_chunk(dcpl_id[j], 2, chunk_dims) < 0)
TEST_ERROR;
} /* end if */
else if ((flags & MDSET_FLAG_CHUNK) && j == 5) {
/* Dataset 5 is virtual in multi layout case */
/* Set to contiguous to clear previous VDS settings */
if (H5Pset_layout(dcpl_id[j], H5D_CONTIGUOUS) < 0)
TEST_ERROR;
/* Set virtual dataset layout, ALL<>ALL mapping */
if (H5Pset_virtual(dcpl_id[j], file_space_ids[j], ".", SOURCE_DS_NAME, file_space_ids[j]) < 0)
TEST_ERROR;
}
/* Create dataset */
/* If MDSET_FLAG_TCONV is set, use a different datatype with 50% probability, so
* some datasets require type conversion and others do not */
if ((dset_ids[j] = H5Dcreate2(file_id, dset_name[j],
(flags & MDSET_FLAG_TCONV && HDrandom() % 2) ? H5T_NATIVE_LONG
: H5T_NATIVE_UINT,
file_space_ids[j], H5P_DEFAULT, dcpl_id[j], H5P_DEFAULT)) < 0)
TEST_ERROR;
/* Create virtual source dataset if necessary. Use dcpl_id[0] for a contiguous dataset
*/
if ((flags & MDSET_FLAG_MLAYOUT) && (j == 6)) {
if ((source_dset = H5Dcreate2(file_id, SOURCE_DS_NAME,
(flags & MDSET_FLAG_TCONV && HDrandom() % 2) ? H5T_NATIVE_LONG
: H5T_NATIVE_UINT,
file_space_ids[j], H5P_DEFAULT, dcpl_id[0], H5P_DEFAULT)) < 0)
TEST_ERROR;
if (H5Dclose(source_dset) < 0)
TEST_ERROR;
}
} /* end for */
/* Initialize read buffer and expected read buffer */
(void)HDmemset(rbuf, 0, buf_size);
(void)HDmemset(erbuf, 0, buf_size);
/* Initialize write buffer */
for (j = 0; j < max_dsets; j++)
for (k = 0; k < MAX_DSET_X; k++)
for (l = 0; l < MAX_DSET_Y; l++)
wbufi[j][k][l] = (unsigned)((j * MAX_DSET_X * MAX_DSET_Y) + (k * MAX_DSET_Y) + l);
/* Initialize expected file buffer */
(void)HDmemset(efbuf, 0, buf_size);
/* Perform read/write operations */
for (j = 0; j < OPS_PER_FILE; j++) {
/* Decide whether to read or write. Can't read on the first iteration with external
* layout because the write is needed to create the external file. */
do_read = (j == 0 && flags & MDSET_FLAG_MLAYOUT) ? FALSE : (hbool_t)(HDrandom() % 2);
/* Loop over datasets */
for (k = 0; k < ndsets; k++) {
int sel_type;
/* Reset selection */
if (H5Sselect_none(mem_space_ids[k]) < 0)
TEST_ERROR;
if (H5Sselect_none(file_space_ids[k]) < 0)
TEST_ERROR;
/* Decide whether to do a hyperslab, point, or all selection */
sel_type = HDrandom() % 3;
if (sel_type == 0) {
/* Hyperslab */
size_t nhs = (size_t)((HDrandom() % MAX_HS) + 1); /* Number of hyperslabs */
size_t max_hs_x = (MAX_HS_X <= dset_dims[k][0])
? MAX_HS_X
: dset_dims[k][0]; /* Determine maximum hyperslab size in X */
size_t max_hs_y = (MAX_HS_Y <= dset_dims[k][1])
? MAX_HS_Y
: dset_dims[k][1]; /* Determine maximum hyperslab size in Y */
for (l = 0; l < nhs; l++) {
/* Generate hyperslab */
count[0] = (hsize_t)(((hsize_t)HDrandom() % max_hs_x) + 1);
count[1] = (hsize_t)(((hsize_t)HDrandom() % max_hs_y) + 1);
start[0] = (count[0] == dset_dims[k][0])
? 0
: (hsize_t)HDrandom() % (dset_dims[k][0] - count[0] + 1);
start[1] = (count[1] == dset_dims[k][1])
? 0
: (hsize_t)HDrandom() % (dset_dims[k][1] - count[1] + 1);
/* Select hyperslab */
if (H5Sselect_hyperslab(mem_space_ids[k], H5S_SELECT_OR, start, NULL, count, NULL) <
0)
TEST_ERROR;
if (H5Sselect_hyperslab(file_space_ids[k], H5S_SELECT_OR, start, NULL, count, NULL) <
0)
TEST_ERROR;
/* Update expected buffers */
if (do_read) {
for (m = start[0]; m < (start[0] + count[0]); m++)
for (n = start[1]; n < (start[1] + count[1]); n++)
erbufi[k][m][n] = efbufi[k][m][n];
} /* end if */
else
for (m = start[0]; m < (start[0] + count[0]); m++)
for (n = start[1]; n < (start[1] + count[1]); n++)
efbufi[k][m][n] = wbufi[k][m][n];
} /* end for */
} /* end if */
else if (sel_type == 1) {
/* Point selection */
size_t npoints = (size_t)(((size_t)HDrandom() % MAX_POINTS) + 1); /* Number of points */
/* Generate points */
for (l = 0; l < npoints; l++) {
points[2 * l] = (unsigned)((hsize_t)HDrandom() % dset_dims[k][0]);
points[(2 * l) + 1] = (unsigned)((hsize_t)HDrandom() % dset_dims[k][1]);
} /* end for */
/* Select points in file */
if (H5Sselect_elements(file_space_ids[k], H5S_SELECT_APPEND, npoints, points) < 0)
TEST_ERROR;
/* Update expected buffers */
if (do_read) {
for (l = 0; l < npoints; l++)
erbufi[k][points[2 * l]][points[(2 * l) + 1]] =
efbufi[k][points[2 * l]][points[(2 * l) + 1]];
} /* end if */
else
for (l = 0; l < npoints; l++)
efbufi[k][points[2 * l]][points[(2 * l) + 1]] =
wbufi[k][points[2 * l]][points[(2 * l) + 1]];
/* Convert to 3D for memory selection, if not using
* "shapesame" */
if (!(flags & MDSET_FLAG_SHAPESAME)) {
for (l = npoints - 1; l > 0; l--) {
points[(3 * l) + 2] = 0;
points[(3 * l) + 1] = points[(2 * l) + 1];
points[3 * l] = points[2 * l];
} /* end for */
points[2] = 0;
} /* end if */
/* Select points in memory */
if (H5Sselect_elements(mem_space_ids[k], H5S_SELECT_APPEND, npoints, points) < 0)
TEST_ERROR;
} /* end else */
else {
/* All selection */
/* Select entire dataset in file */
if (H5Sselect_all(file_space_ids[k]) < 0)
TEST_ERROR;
/* Select entire dataset in memory using hyperslab */
start[0] = 0;
start[1] = 0;
count[0] = dset_dims[k][0];
count[1] = dset_dims[k][1];
if (H5Sselect_hyperslab(mem_space_ids[k], H5S_SELECT_SET, start, NULL, count, NULL) < 0)
TEST_ERROR;
/* Update expected buffers */
if (do_read) {
for (m = 0; m < dset_dims[k][0]; m++)
for (n = 0; n < dset_dims[k][1]; n++)
erbufi[k][m][n] = efbufi[k][m][n];
} /* end if */
else
for (m = 0; m < dset_dims[k][0]; m++)
for (n = 0; n < dset_dims[k][1]; n++)
efbufi[k][m][n] = wbufi[k][m][n];
}
} /* end for */
/* Perform I/O */
if (do_read) {
if (flags & MDSET_FLAG_MDSET) {
/* Set buffers */
for (k = 0; k < ndsets; k++)
rbufs[k] = rbufi[k][0];
/* Read datasets */
if (H5Dread_multi(ndsets, dset_ids, mem_type_ids, mem_space_ids, file_space_ids,
H5P_DEFAULT, rbufs) < 0)
TEST_ERROR;
} /* end if */
else
/* Read */
if (H5Dread(dset_ids[0], mem_type_ids[0], mem_space_ids[0], file_space_ids[0],
H5P_DEFAULT, rbuf) < 0)
TEST_ERROR;
/* Verify data */
if (0 != memcmp(rbuf, erbuf, buf_size))
TEST_ERROR;
} /* end if */
else {
if (flags & MDSET_FLAG_MDSET) {
/* Set buffers */
for (k = 0; k < ndsets; k++)
wbufs[k] = wbufi[k][0];
/* Write datasets */
if (H5Dwrite_multi(ndsets, dset_ids, mem_type_ids, mem_space_ids, file_space_ids,
H5P_DEFAULT, wbufs) < 0)
TEST_ERROR;
} /* end if */
else
/* Write */
if (H5Dwrite(dset_ids[0], mem_type_ids[0], mem_space_ids[0], file_space_ids[0],
H5P_DEFAULT, wbuf) < 0)
TEST_ERROR;
/* Update wbuf */
for (l = 0; l < max_dsets; l++)
for (m = 0; m < MAX_DSET_X; m++)
for (n = 0; n < MAX_DSET_Y; n++)
wbufi[l][m][n] += (unsigned)max_dsets * MAX_DSET_X * MAX_DSET_Y;
} /* end else */
} /* end for */
/* Close */
for (j = 0; j < ndsets; j++) {
if (H5Dclose(dset_ids[j]) < 0)
TEST_ERROR;
dset_ids[j] = -1;
if (H5Sclose(file_space_ids[j]) < 0)
TEST_ERROR;
file_space_ids[j] = -1;
} /* end for */
if (H5Fclose(file_id) < 0)
TEST_ERROR;
file_id = -1;
/* Cleanup external file. Need to do this because otherwise there is garbage when the
* dataset is created, even with early allocation and fill time. */
HDremove(EXT_FILENAME);
} /* end for */
/* Close */
for (i = 0; i < max_dsets; i++) {
if (H5Sclose(mem_space_ids[i]) < 0)
TEST_ERROR;
mem_space_ids[i] = -1;
} /* end for */
for (i = 0; i < MAX_DSETS; i++) {
if (H5Pclose(dcpl_id[i]) < 0)
TEST_ERROR;
dcpl_id[i] = -1;
}
free(rbuf);
rbuf = NULL;
free(erbuf);
erbuf = NULL;
free(wbuf);
wbuf = NULL;
free(efbuf);
efbuf = NULL;
PASSED();
return 0;
error:
H5E_BEGIN_TRY
{
for (i = 0; i < max_dsets; i++) {
H5Dclose(dset_ids[i]);
H5Sclose(mem_space_ids[i]);
H5Sclose(file_space_ids[i]);
H5Pclose(dcpl_id[i]);
} /* end for */
H5Fclose(file_id);
}
H5E_END_TRY
if (rbuf)
free(rbuf);
if (erbuf)
free(erbuf);
if (wbuf)
free(wbuf);
if (efbuf)
free(efbuf);
return -1;
} /* end test_mdset() */
/*-------------------------------------------------------------------------
* Function: main
*
* Purpose: Runs all tests with all combinations of configuration
* flags.
*
* Return: Success: 0
* Failure: 1
*
* Programmer: Neil Fortner
* Monday, March 10, 2014
*
*-------------------------------------------------------------------------
*/
int
main(void)
{
hid_t fapl_id;
int nerrors = 0;
unsigned i;
int ret;
h5_reset();
fapl_id = h5_fileaccess();
/* Initialize random number seed */
HDsrandom((unsigned)HDtime(NULL));
/* Fill dset_name array */
for (i = 0; i < MAX_DSETS; i++) {
if ((ret = snprintf(dset_name[i], DSET_MAX_NAME_LEN, "dset%u", i)) < 0)
TEST_ERROR;
if (ret >= DSET_MAX_NAME_LEN)
TEST_ERROR;
} /* end for */
/* Check if deflate and fletcher32 filters are available */
if ((deflate_avail = H5Zfilter_avail(H5Z_FILTER_DEFLATE)) < 0)
TEST_ERROR;
if ((fletcher32_avail = H5Zfilter_avail(H5Z_FILTER_FLETCHER32)) < 0)
TEST_ERROR;
for (i = 0; i <= MDSET_ALL_FLAGS; i++) {
/* Skip incompatible flag combinations */
if (((i & MDSET_FLAG_MLAYOUT) && (i & MDSET_FLAG_CHUNK)) ||
((i & MDSET_FLAG_MLAYOUT) && !(i & MDSET_FLAG_MDSET)) ||
((i & MDSET_FLAG_FILTER) && !(i & MDSET_FLAG_CHUNK)))
continue;
/* Print flag configuration */
puts("\nConfiguration:");
printf(" Layout: %s\n", (i & MDSET_FLAG_MLAYOUT) ? "Multi"
: (i & MDSET_FLAG_CHUNK) ? "Chunked"
: "Contiguous");
printf(" Shape same: %s\n", (i & MDSET_FLAG_SHAPESAME) ? "Yes" : "No");
printf(" I/O type: %s\n", (i & MDSET_FLAG_MDSET) ? "Multi" : "Single");
printf(" Type conversion: %s\n", (i & MDSET_FLAG_TCONV) ? "Yes" : "No");
printf(" Data filter: %s\n", (i & MDSET_FLAG_MLAYOUT) ? "Mixed"
: (i & MDSET_FLAG_FILTER) ? "Yes"
: "No");
nerrors += test_mdset(50, i, fapl_id);
}
/* test all datasets in same container */
nerrors += test_mdset_location(fapl_id);
h5_cleanup(FILENAME, fapl_id);
if (nerrors)
goto error;
puts("All multi dataset tests passed.");
return 0;
error:
nerrors = MAX(1, nerrors);
printf("***** %d multi dataset TEST%s FAILED! *****\n", nerrors, 1 == nerrors ? "" : "S");
return 1;
} /* end main() */

View File

@ -50,7 +50,7 @@ HDF5-DIAG: Error detected in HDF5 (version (number)) thread (IDs):
#001: (file name) line (number) in H5D__read_api_common(): can't read data
major: Dataset
minor: Read failed
#002: (file name) line (number) in H5VL_dataset_read(): dataset read failed
#002: (file name) line (number) in H5VL_dataset_read_direct(): dataset read failed
major: Virtual Object Layer
minor: Read failed
#003: (file name) line (number) in H5VL__dataset_read(): dataset read failed

View File

@ -95,6 +95,7 @@ set (H5P_TESTS
t_pshutdown
t_prestart
t_init_term
t_pmulti_dset
t_shapesame
t_filters_parallel
t_subfiling_vfd

View File

@ -34,7 +34,7 @@ check_SCRIPTS = $(TEST_SCRIPT_PARA)
# Test programs. These are our main targets.
#
TEST_PROG_PARA=t_mpi t_bigio testphdf5 t_cache t_cache_image t_pread t_pshutdown t_prestart t_init_term t_shapesame t_filters_parallel t_2Gio t_vfd
TEST_PROG_PARA=t_mpi t_bigio testphdf5 t_cache t_cache_image t_pread t_pshutdown t_prestart t_init_term t_pmulti_dset t_shapesame t_filters_parallel t_2Gio t_vfd
if SUBFILING_VFD_CONDITIONAL
TEST_PROG_PARA += t_subfiling_vfd
@ -59,6 +59,6 @@ LDADD = $(LIBH5TEST) $(LIBHDF5)
# after_mpi_fin.h5 is from t_init_term
# go is used for debugging. See testphdf5.c.
CHECK_CLEANFILES+=MPItest.h5 Para*.h5 bigio_test.h5 CacheTestDummy.h5 \
ShapeSameTest.h5 shutdown.h5 after_mpi_fin.h5 go
ShapeSameTest.h5 shutdown.h5 pmulti_dset.h5 after_mpi_fin.h5 go
include $(top_srcdir)/config/conclude.am

767
testpar/t_pmulti_dset.c Normal file
View File

@ -0,0 +1,767 @@
/* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
* Copyright by The HDF Group. *
* Copyright by the Board of Trustees of the University of Illinois. *
* All rights reserved. *
* *
* This file is part of HDF5. The full HDF5 copyright notice, including *
* terms governing use, modification, and redistribution, is contained in *
* the files COPYING and Copyright.html. COPYING can be found at the root *
* of the source code distribution tree; Copyright.html can be found at the *
* root level of an installed copy of the electronic HDF5 document set and *
* is linked from the top-level documents page. It can also be found at *
* http://hdfgroup.org/HDF5/doc/Copyright.html. If you do not have *
* access to either file, you may request a copy from help@hdfgroup.org. *
* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * */
/*
* Programmer: Neil Fortner
* March 10, 2014
*
* Purpose: Test H5Dwrite_multi() and H5Dread_multi using randomized
* parameters in parallel. Also tests H5Dwrite() and H5Dread()
* using a similar method.
*
* Note that this test currently relies on all processes generating
* the same sequence of random numbers after using a shared seed
* value, therefore it may not work across multiple machines.
*/
#include "h5test.h"
#include "testpar.h"
#define T_PMD_ERROR \
do { \
nerrors++; \
H5_FAILED(); \
AT(); \
printf("seed = %u\n", seed); \
} while (0)
#define FILENAME "pmulti_dset.h5"
#define MAX_DSETS 5
#define MAX_DSET_X 15
#define MAX_DSET_Y 10
#define MAX_CHUNK_X 8
#define MAX_CHUNK_Y 6
#define MAX_HS_X 4
#define MAX_HS_Y 2
#define MAX_HS 2
#define MAX_POINTS 6
#define MAX_SEL_RETRIES 10
#define OPS_PER_FILE 25
#define DSET_MAX_NAME_LEN 8
/* Option flags */
#define MDSET_FLAG_CHUNK 0x01u
#define MDSET_FLAG_MLAYOUT 0x02u
#define MDSET_FLAG_SHAPESAME 0x04u
#define MDSET_FLAG_MDSET 0x08u
#define MDSET_FLAG_COLLECTIVE 0x10u
#define MDSET_FLAG_COLLECTIVE_OPT 0x20u
#define MDSET_FLAG_TCONV 0x40u
#define MDSET_FLAG_FILTER 0x80u
#define MDSET_ALL_FLAGS \
(MDSET_FLAG_CHUNK | MDSET_FLAG_MLAYOUT | MDSET_FLAG_SHAPESAME | MDSET_FLAG_MDSET | \
MDSET_FLAG_COLLECTIVE | MDSET_FLAG_COLLECTIVE_OPT | MDSET_FLAG_TCONV | MDSET_FLAG_FILTER)
/* MPI variables */
int mpi_size;
int mpi_rank;
/* Names for datasets */
char dset_name[MAX_DSETS][DSET_MAX_NAME_LEN];
/* Random number seed */
unsigned seed;
/* Number of errors */
int nerrors = 0;
/* Whether these filters are available */
htri_t deflate_avail = FALSE;
htri_t fletcher32_avail = FALSE;
/*-------------------------------------------------------------------------
* Function: test_pmdset
*
* Purpose: Test randomized I/O using one or more datasets. Creates a
* file, runs OPS_PER_FILE read or write operations verifying
* that reads return the expected data, then closes the file.
* Runs the test with a new file niter times.
*
* The operations can use either hyperslab or point
* selections. Options are available for chunked or
* contiguous layout, use of multiple datasets and H5D*_multi
* calls, and use of the "shapesame" algorithm code path. To
* avoid the shapesame path when that option is not set, this
* function simply adds a dimension to the memory buffer in a
* way that the shapesame code is not designed to handle.
*
* Return: Number of errors
*
* Programmer: Neil Fortner
* Monday, March 10, 2014
*
*-------------------------------------------------------------------------
*/
static void
test_pmdset(size_t niter, unsigned flags)
{
hid_t dset_ids[MAX_DSETS];
hid_t mem_type_ids[MAX_DSETS];
hid_t mem_space_ids[MAX_DSETS];
hid_t file_space_ids[MAX_DSETS];
void *rbufs[MAX_DSETS];
const void *wbufs[MAX_DSETS];
size_t max_dsets;
size_t buf_size;
size_t ndsets;
hid_t file_id = -1;
hid_t fapl_id = -1;
hid_t dcpl_id[MAX_DSETS];
hid_t dxpl_id = -1;
hsize_t dset_dims[MAX_DSETS][3];
hsize_t chunk_dims[2];
hsize_t max_dims[2] = {H5S_UNLIMITED, H5S_UNLIMITED};
unsigned *rbuf = NULL;
unsigned *rbufi[MAX_DSETS][MAX_DSET_X];
unsigned *erbuf = NULL;
unsigned *erbufi[MAX_DSETS][MAX_DSET_X];
unsigned *wbuf = NULL;
unsigned *wbufi[MAX_DSETS][MAX_DSET_X];
unsigned *efbuf = NULL;
unsigned *efbufi[MAX_DSETS][MAX_DSET_X];
unsigned char *dset_usage;
unsigned char *dset_usagei[MAX_DSETS][MAX_DSET_X];
hbool_t do_read;
hbool_t last_read;
hbool_t overlap;
hsize_t start[MAX_HS][3];
hsize_t count[MAX_HS][3];
hsize_t points[3 * MAX_POINTS];
int rank_data_diff;
unsigned op_data_incr;
size_t i, j, k, l, m, n, o, p;
if (mpi_rank == 0)
TESTING("random I/O");
/* Skipped configurations */
if (!(flags & MDSET_FLAG_COLLECTIVE_OPT)) {
if (mpi_rank == 0)
SKIPPED();
return;
}
/* Calculate maximum number of datasets */
max_dsets = (flags & MDSET_FLAG_MDSET) ? MAX_DSETS : 1;
/* Calculate data increment per write operation */
op_data_incr = (unsigned)max_dsets * MAX_DSET_X * MAX_DSET_Y * (unsigned)mpi_size;
/* Calculate buffer size */
buf_size = max_dsets * MAX_DSET_X * MAX_DSET_Y * sizeof(unsigned);
/* Initialize dcpl_id array */
for (i = 0; i < max_dsets; i++)
dcpl_id[i] = -1;
/* Allocate buffers */
if (NULL == (rbuf = (unsigned *)HDmalloc(buf_size)))
T_PMD_ERROR;
if (NULL == (erbuf = (unsigned *)HDmalloc(buf_size)))
T_PMD_ERROR;
if (NULL == (wbuf = (unsigned *)HDmalloc(buf_size)))
T_PMD_ERROR;
if (NULL == (efbuf = (unsigned *)HDmalloc(buf_size)))
T_PMD_ERROR;
if (NULL == (dset_usage = (unsigned char *)HDmalloc(max_dsets * MAX_DSET_X * MAX_DSET_Y)))
T_PMD_ERROR;
/* Initialize buffer indices */
for (i = 0; i < max_dsets; i++)
for (j = 0; j < MAX_DSET_X; j++) {
rbufi[i][j] = rbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
erbufi[i][j] = erbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
wbufi[i][j] = wbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
efbufi[i][j] = efbuf + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
dset_usagei[i][j] = dset_usage + (i * MAX_DSET_X * MAX_DSET_Y) + (j * MAX_DSET_Y);
} /* end for */
/* Initialize 3rd dimension information (for tricking library into using
* non-"shapesame" code */
for (i = 0; i < max_dsets; i++)
dset_dims[i][2] = 1;
for (i = 0; i < MAX_HS; i++) {
start[i][2] = 0;
count[i][2] = 1;
} /* end for */
/* Initialize IDs */
for (i = 0; i < max_dsets; i++) {
dset_ids[i] = -1;
file_space_ids[i] = -1;
mem_type_ids[i] = H5T_NATIVE_UINT;
mem_space_ids[i] = -1;
} /* end for */
/* Generate memory dataspace */
dset_dims[0][0] = MAX_DSET_X;
dset_dims[0][1] = MAX_DSET_Y;
if ((mem_space_ids[0] = H5Screate_simple((flags & MDSET_FLAG_SHAPESAME) ? 2 : 3, dset_dims[0], NULL)) < 0)
T_PMD_ERROR;
for (i = 1; i < max_dsets; i++)
if ((mem_space_ids[i] = H5Scopy(mem_space_ids[0])) < 0)
T_PMD_ERROR;
/* Create fapl */
if ((fapl_id = H5Pcreate(H5P_FILE_ACCESS)) < 0)
T_PMD_ERROR;
/* Set MPIO file driver */
if ((H5Pset_fapl_mpio(fapl_id, MPI_COMM_WORLD, MPI_INFO_NULL)) < 0)
T_PMD_ERROR;
/* Create dcpl 0 */
if ((dcpl_id[0] = H5Pcreate(H5P_DATASET_CREATE)) < 0)
T_PMD_ERROR;
/* Set fill time to alloc, and alloc time to early (so we always know
* what's in the file) */
if (H5Pset_fill_time(dcpl_id[0], H5D_FILL_TIME_ALLOC) < 0)
T_PMD_ERROR;
if (H5Pset_alloc_time(dcpl_id[0], H5D_ALLOC_TIME_EARLY) < 0)
T_PMD_ERROR;
/* Set filters if requested */
if (flags & MDSET_FLAG_FILTER) {
if (fletcher32_avail)
if (H5Pset_fletcher32(dcpl_id[0]) < 0)
T_PMD_ERROR;
if (deflate_avail)
if (H5Pset_deflate(dcpl_id[0], 1) < 0)
T_PMD_ERROR;
}
/* Copy dcpl 0 to other slots in dcpl_id array */
for (i = 1; i < MAX_DSETS; i++)
if ((dcpl_id[i] = H5Pcopy(dcpl_id[0])) < 0)
T_PMD_ERROR;
/* If this is a multi layout run, dataset 2 will use filters, set them now */
if (flags & MDSET_FLAG_MLAYOUT) {
if (fletcher32_avail)
if (H5Pset_fletcher32(dcpl_id[2]) < 0)
T_PMD_ERROR;
if (deflate_avail)
if (H5Pset_deflate(dcpl_id[2], 1) < 0)
T_PMD_ERROR;
}
/* Create dxpl */
if ((dxpl_id = H5Pcreate(H5P_DATASET_XFER)) < 0)
T_PMD_ERROR;
/* Set collective or independent I/O */
if (flags & MDSET_FLAG_COLLECTIVE) {
if (H5Pset_dxpl_mpio(dxpl_id, H5FD_MPIO_COLLECTIVE) < 0)
T_PMD_ERROR;
/* Set low level I/O mode */
if (flags & MDSET_FLAG_COLLECTIVE_OPT) {
if (H5Pset_dxpl_mpio_collective_opt(dxpl_id, H5FD_MPIO_COLLECTIVE_IO) < 0)
T_PMD_ERROR;
}
else if (H5Pset_dxpl_mpio_collective_opt(dxpl_id, H5FD_MPIO_INDIVIDUAL_IO) < 0)
T_PMD_ERROR;
} /* end if */
else if (H5Pset_dxpl_mpio(dxpl_id, H5FD_MPIO_INDEPENDENT) < 0)
T_PMD_ERROR;
for (i = 0; i < niter; i++) {
/* Determine number of datasets */
ndsets = (flags & MDSET_FLAG_MLAYOUT) ? 3
: (flags & MDSET_FLAG_MDSET) ? (size_t)((size_t)HDrandom() % max_dsets) + 1
: 1;
/* Create file */
if ((file_id = H5Fcreate(FILENAME, H5F_ACC_TRUNC, H5P_DEFAULT, fapl_id)) < 0)
T_PMD_ERROR;
/* Create datasets */
for (j = 0; j < ndsets; j++) {
hbool_t use_chunk =
(flags & MDSET_FLAG_CHUNK) || ((flags & MDSET_FLAG_MLAYOUT) && (j == 1 || j == 2));
/* Generate file dataspace */
dset_dims[j][0] = (hsize_t)((HDrandom() % MAX_DSET_X) + 1);
dset_dims[j][1] = (hsize_t)((HDrandom() % MAX_DSET_Y) + 1);
if ((file_space_ids[j] = H5Screate_simple(2, dset_dims[j], use_chunk ? max_dims : NULL)) < 0)
T_PMD_ERROR;
/* Generate chunk if called for by configuration (multi layout uses chunked for datasets
* 1 and 2) */
if (use_chunk) {
chunk_dims[0] = (hsize_t)((HDrandom() % MAX_CHUNK_X) + 1);
chunk_dims[1] = (hsize_t)((HDrandom() % MAX_CHUNK_Y) + 1);
if (H5Pset_chunk(dcpl_id[j], 2, chunk_dims) < 0)
T_PMD_ERROR;
} /* end if */
/* Create dataset */
/* If MDSET_FLAG_TCONV is set, use a different datatype with 50% probability, so
* some datasets require type conversion and others do not */
if ((dset_ids[j] = H5Dcreate2(file_id, dset_name[j],
(flags & MDSET_FLAG_TCONV && HDrandom() % 2) ? H5T_NATIVE_LONG
: H5T_NATIVE_UINT,
file_space_ids[j], H5P_DEFAULT, dcpl_id[j], H5P_DEFAULT)) < 0)
T_PMD_ERROR;
} /* end for */
/* Initialize read buffer and expected read buffer */
(void)HDmemset(rbuf, 0, buf_size);
(void)HDmemset(erbuf, 0, buf_size);
/* Initialize write buffer */
for (j = 0; j < max_dsets; j++)
for (k = 0; k < MAX_DSET_X; k++)
for (l = 0; l < MAX_DSET_Y; l++)
wbufi[j][k][l] = (unsigned)(((unsigned)mpi_rank * max_dsets * MAX_DSET_X * MAX_DSET_Y) +
(j * MAX_DSET_X * MAX_DSET_Y) + (k * MAX_DSET_Y) + l);
/* Initialize expected file buffer */
(void)HDmemset(efbuf, 0, buf_size);
/* Set last_read to TRUE so we don't reopen the file on the first
* iteration */
last_read = TRUE;
/* Perform read/write operations */
for (j = 0; j < OPS_PER_FILE; j++) {
/* Decide whether to read or write */
do_read = (hbool_t)(HDrandom() % 2);
/* Barrier to ensure processes have finished the previous operation
*/
MPI_Barrier(MPI_COMM_WORLD);
/* If the last operation was a write we must close and reopen the
* file to ensure consistency */
/* Possibly change to MPI_FILE_SYNC at some point? -NAF */
if (!last_read) {
/* Close datasets */
for (k = 0; k < ndsets; k++) {
if (H5Dclose(dset_ids[k]) < 0)
T_PMD_ERROR;
dset_ids[k] = -1;
} /* end for */
/* Close file */
if (H5Fclose(file_id) < 0)
T_PMD_ERROR;
file_id = -1;
/* Barrier */
MPI_Barrier(MPI_COMM_WORLD);
/* Reopen file */
if ((file_id = H5Fopen(FILENAME, H5F_ACC_RDWR, fapl_id)) < 0)
T_PMD_ERROR;
/* Reopen datasets */
for (k = 0; k < ndsets; k++) {
if ((dset_ids[k] = H5Dopen2(file_id, dset_name[k], H5P_DEFAULT)) < 0)
T_PMD_ERROR;
} /* end for */
/* Barrier */
MPI_Barrier(MPI_COMM_WORLD);
} /* end if */
/* Keep track of whether the last operation was a read */
last_read = do_read;
/* Loop over datasets */
for (k = 0; k < ndsets; k++) {
/* Reset selection */
if (H5Sselect_none(mem_space_ids[k]) < 0)
T_PMD_ERROR;
if (H5Sselect_none(file_space_ids[k]) < 0)
T_PMD_ERROR;
/* Reset dataset usage array, if writing */
if (!do_read)
HDmemset(dset_usage, 0, max_dsets * MAX_DSET_X * MAX_DSET_Y);
/* Iterate over processes */
for (l = 0; l < (size_t)mpi_size; l++) {
/* Calculate difference between data in process being
* iterated over and that in this process */
rank_data_diff =
(int)((unsigned)max_dsets * MAX_DSET_X * MAX_DSET_Y) * ((int)l - (int)mpi_rank);
/* Decide whether to do a hyperslab or point selection */
if (HDrandom() % 2) {
/* Hyperslab */
size_t nhs = (size_t)((HDrandom() % MAX_HS) + 1); /* Number of hyperslabs */
size_t max_hs_x = (MAX_HS_X <= dset_dims[k][0])
? MAX_HS_X
: dset_dims[k][0]; /* Determine maximum hyperslab size in X */
size_t max_hs_y = (MAX_HS_Y <= dset_dims[k][1])
? MAX_HS_Y
: dset_dims[k][1]; /* Determine maximum hyperslab size in Y */
for (m = 0; m < nhs; m++) {
overlap = TRUE;
for (n = 0; overlap && (n < MAX_SEL_RETRIES); n++) {
/* Generate hyperslab */
count[m][0] = (hsize_t)(((hsize_t)HDrandom() % max_hs_x) + 1);
count[m][1] = (hsize_t)(((hsize_t)HDrandom() % max_hs_y) + 1);
start[m][0] = (count[m][0] == dset_dims[k][0])
? 0
: (hsize_t)HDrandom() % (dset_dims[k][0] - count[m][0] + 1);
start[m][1] = (count[m][1] == dset_dims[k][1])
? 0
: (hsize_t)HDrandom() % (dset_dims[k][1] - count[m][1] + 1);
/* If writing, check for overlap with other processes */
overlap = FALSE;
if (!do_read)
for (o = start[m][0]; (o < (start[m][0] + count[m][0])) && !overlap; o++)
for (p = start[m][1]; (p < (start[m][1] + count[m][1])) && !overlap;
p++)
if (dset_usagei[k][o][p])
overlap = TRUE;
} /* end for */
/* If we did not find a non-overlapping hyperslab
* quit trying to generate new ones */
if (overlap) {
nhs = m;
break;
} /* end if */
/* Select hyperslab if this is the current process
*/
if (l == (size_t)mpi_rank) {
if (H5Sselect_hyperslab(mem_space_ids[k], H5S_SELECT_OR, start[m], NULL,
count[m], NULL) < 0)
T_PMD_ERROR;
if (H5Sselect_hyperslab(file_space_ids[k], H5S_SELECT_OR, start[m], NULL,
count[m], NULL) < 0)
T_PMD_ERROR;
} /* end if */
/* Update expected buffers */
if (do_read) {
if (l == (size_t)mpi_rank)
for (n = start[m][0]; n < (start[m][0] + count[m][0]); n++)
for (o = start[m][1]; o < (start[m][1] + count[m][1]); o++)
erbufi[k][n][o] = efbufi[k][n][o];
} /* end if */
else
for (n = start[m][0]; n < (start[m][0] + count[m][0]); n++)
for (o = start[m][1]; o < (start[m][1] + count[m][1]); o++)
efbufi[k][n][o] = (unsigned)((int)wbufi[k][n][o] + rank_data_diff);
} /* end for */
/* Update dataset usage array if writing */
if (!do_read)
for (m = 0; m < nhs; m++)
for (n = start[m][0]; n < (start[m][0] + count[m][0]); n++)
for (o = start[m][1]; o < (start[m][1] + count[m][1]); o++)
dset_usagei[k][n][o] = (unsigned char)1;
} /* end if */
else {
/* Point selection */
size_t npoints =
(size_t)(((size_t)HDrandom() % MAX_POINTS) + 1); /* Number of points */
/* Reset dataset usage array if reading, since in this case we don't care
* about overlapping selections between processes */
if (do_read)
HDmemset(dset_usage, 0, max_dsets * MAX_DSET_X * MAX_DSET_Y);
/* Generate points */
for (m = 0; m < npoints; m++) {
overlap = TRUE;
for (n = 0; overlap && (n < MAX_SEL_RETRIES); n++) {
/* Generate point */
points[2 * m] = (unsigned)((hsize_t)HDrandom() % dset_dims[k][0]);
points[(2 * m) + 1] = (unsigned)((hsize_t)HDrandom() % dset_dims[k][1]);
/* Check for overlap with other processes (write) or this process
* (always) */
overlap = FALSE;
if (dset_usagei[k][points[2 * m]][points[(2 * m) + 1]])
overlap = TRUE;
} /* end for */
/* If we did not find a non-overlapping point quit
* trying to generate new ones */
if (overlap) {
npoints = m;
break;
} /* end if */
/* Update dataset usage array after each point to prevent the same point
* being selected twice by a single process, since this is not supported
* by MPI */
dset_usagei[k][points[2 * m]][points[(2 * m) + 1]] = (unsigned char)1;
} /* end for */
/* Select points in file if this is the current process
*/
if ((l == (size_t)mpi_rank) && (npoints > 0))
if (H5Sselect_elements(file_space_ids[k], H5S_SELECT_APPEND, npoints, points) < 0)
T_PMD_ERROR;
/* Update expected buffers */
if (do_read) {
if (l == (size_t)mpi_rank)
for (m = 0; m < npoints; m++)
erbufi[k][points[2 * m]][points[(2 * m) + 1]] =
efbufi[k][points[2 * m]][points[(2 * m) + 1]];
} /* end if */
else
for (m = 0; m < npoints; m++)
efbufi[k][points[2 * m]][points[(2 * m) + 1]] =
(unsigned)((int)wbufi[k][points[2 * m]][points[(2 * m) + 1]] +
rank_data_diff);
/* Select points in memory if this is the current
* process */
if ((l == (size_t)mpi_rank) && (npoints > 0)) {
/* Convert to 3D for memory selection, if not using
* "shapesame" */
if (!(flags & MDSET_FLAG_SHAPESAME)) {
for (m = npoints - 1; m > 0; m--) {
points[(3 * m) + 2] = 0;
points[(3 * m) + 1] = points[(2 * m) + 1];
points[3 * m] = points[2 * m];
} /* end for */
points[2] = 0;
} /* end if */
/* Select elements */
if (H5Sselect_elements(mem_space_ids[k], H5S_SELECT_APPEND, npoints, points) < 0)
T_PMD_ERROR;
} /* end if */
} /* end else */
} /* end for */
} /* end for */
/* Perform I/O */
if (do_read) {
if (flags & MDSET_FLAG_MDSET) {
/* Set buffers */
for (k = 0; k < ndsets; k++)
rbufs[k] = rbufi[k][0];
/* Read datasets */
if (H5Dread_multi(ndsets, dset_ids, mem_type_ids, mem_space_ids, file_space_ids, dxpl_id,
rbufs) < 0)
T_PMD_ERROR;
} /* end if */
else
/* Read */
if (H5Dread(dset_ids[0], mem_type_ids[0], mem_space_ids[0], file_space_ids[0], dxpl_id,
rbuf) < 0)
T_PMD_ERROR;
/* Verify data */
if (0 != memcmp(rbuf, erbuf, buf_size))
T_PMD_ERROR;
} /* end if */
else {
if (flags & MDSET_FLAG_MDSET) {
/* Set buffers */
for (k = 0; k < ndsets; k++)
wbufs[k] = wbufi[k][0];
/* Write datasets */
if (H5Dwrite_multi(ndsets, dset_ids, mem_type_ids, mem_space_ids, file_space_ids, dxpl_id,
wbufs) < 0)
T_PMD_ERROR;
} /* end if */
else
/* Write */
if (H5Dwrite(dset_ids[0], mem_type_ids[0], mem_space_ids[0], file_space_ids[0], dxpl_id,
wbuf) < 0)
T_PMD_ERROR;
/* Update wbuf */
for (l = 0; l < max_dsets; l++)
for (m = 0; m < MAX_DSET_X; m++)
for (n = 0; n < MAX_DSET_Y; n++)
wbufi[l][m][n] += op_data_incr;
} /* end else */
} /* end for */
/* Close */
for (j = 0; j < ndsets; j++) {
if (H5Dclose(dset_ids[j]) < 0)
T_PMD_ERROR;
dset_ids[j] = -1;
if (H5Sclose(file_space_ids[j]) < 0)
T_PMD_ERROR;
file_space_ids[j] = -1;
} /* end for */
if (H5Fclose(file_id) < 0)
T_PMD_ERROR;
file_id = -1;
} /* end for */
/* Close */
for (i = 0; i < max_dsets; i++) {
if (H5Sclose(mem_space_ids[i]) < 0)
T_PMD_ERROR;
mem_space_ids[i] = -1;
} /* end for */
if (H5Pclose(dxpl_id) < 0)
T_PMD_ERROR;
dxpl_id = -1;
for (i = 0; i < MAX_DSETS; i++) {
if (H5Pclose(dcpl_id[i]) < 0)
T_PMD_ERROR;
dcpl_id[i] = -1;
}
if (H5Pclose(fapl_id) < 0)
T_PMD_ERROR;
fapl_id = -1;
free(rbuf);
rbuf = NULL;
free(erbuf);
erbuf = NULL;
free(wbuf);
wbuf = NULL;
free(efbuf);
efbuf = NULL;
free(dset_usage);
dset_usage = NULL;
if (mpi_rank == 0)
PASSED();
return;
} /* end test_mdset() */
/*-------------------------------------------------------------------------
* Function: main
*
* Purpose: Runs all tests with all combinations of configuration
* flags.
*
* Return: Success: 0
* Failure: 1
*
* Programmer: Neil Fortner
* Monday, March 10, 2014
*
*-------------------------------------------------------------------------
*/
int
main(int argc, char *argv[])
{
unsigned i;
int ret;
h5_reset();
/* Initialize MPI */
MPI_Init(&argc, &argv);
MPI_Comm_size(MPI_COMM_WORLD, &mpi_size);
MPI_Comm_rank(MPI_COMM_WORLD, &mpi_rank);
/* Generate random number seed, if rank 0 */
if (MAINPROCESS)
seed = (unsigned)HDtime(NULL);
/* Broadcast seed from rank 0 (other ranks will receive rank 0's seed) */
if (MPI_SUCCESS != MPI_Bcast(&seed, 1, MPI_UNSIGNED, 0, MPI_COMM_WORLD))
T_PMD_ERROR;
/* Seed random number generator with shared seed (so all ranks generate the
* same sequence) */
HDsrandom(seed);
/* Fill dset_name array */
for (i = 0; i < MAX_DSETS; i++) {
if ((ret = snprintf(dset_name[i], DSET_MAX_NAME_LEN, "dset%u", i)) < 0)
T_PMD_ERROR;
if (ret >= DSET_MAX_NAME_LEN)
T_PMD_ERROR;
} /* end for */
/* Check if deflate and fletcher32 filters are available */
if ((deflate_avail = H5Zfilter_avail(H5Z_FILTER_DEFLATE)) < 0)
T_PMD_ERROR;
if ((fletcher32_avail = H5Zfilter_avail(H5Z_FILTER_FLETCHER32)) < 0)
T_PMD_ERROR;
for (i = 0; i <= MDSET_ALL_FLAGS; i++) {
/* Skip incompatible flag combinations */
if (((i & MDSET_FLAG_MLAYOUT) && (i & MDSET_FLAG_CHUNK)) ||
((i & MDSET_FLAG_MLAYOUT) && !(i & MDSET_FLAG_MDSET)) ||
((i & MDSET_FLAG_MLAYOUT) && !(i & MDSET_FLAG_COLLECTIVE)) ||
((i & MDSET_FLAG_MLAYOUT) && (i & MDSET_FLAG_TCONV)) ||
((i & MDSET_FLAG_FILTER) && !(i & MDSET_FLAG_CHUNK)) ||
((i & MDSET_FLAG_FILTER) && !(i & MDSET_FLAG_COLLECTIVE)) ||
((i & MDSET_FLAG_FILTER) && (i & MDSET_FLAG_TCONV)) ||
(!(i & MDSET_FLAG_COLLECTIVE_OPT) && !(i & MDSET_FLAG_COLLECTIVE)))
continue;
/* Print flag configuration */
if (MAINPROCESS) {
puts("\nConfiguration:");
printf(" Layout: %s\n", (i & MDSET_FLAG_MLAYOUT) ? "Multi"
: (i & MDSET_FLAG_CHUNK) ? "Chunked"
: "Contiguous");
printf(" Shape same: %s\n", (i & MDSET_FLAG_SHAPESAME) ? "Yes" : "No");
printf(" I/O type: %s\n", (i & MDSET_FLAG_MDSET) ? "Multi" : "Single");
printf(" MPI I/O type: %s\n", (i & MDSET_FLAG_COLLECTIVE) ? "Collective" : "Independent");
if (i & MDSET_FLAG_COLLECTIVE)
printf(" Low level MPI I/O:%s\n",
(i & MDSET_FLAG_COLLECTIVE_OPT) ? "Collective" : "Independent");
printf(" Type conversion: %s\n", (i & MDSET_FLAG_TCONV) ? "Yes" : "No");
printf(" Data filter: %s\n", (i & MDSET_FLAG_MLAYOUT) ? "Mixed"
: (i & MDSET_FLAG_FILTER) ? "Yes"
: "No");
} /* end if */
test_pmdset(10, i);
} /* end for */
/* Barrier to make sure all ranks are done before deleting the file, and
* also to clean up output (make sure PASSED is printed before any of the
* following messages) */
if (MPI_SUCCESS != MPI_Barrier(MPI_COMM_WORLD))
T_PMD_ERROR;
/* Delete file */
if (mpi_rank == 0)
if (MPI_SUCCESS != MPI_File_delete(FILENAME, MPI_INFO_NULL))
T_PMD_ERROR;
/* Gather errors from all processes */
MPI_Allreduce(&nerrors, &ret, 1, MPI_INT, MPI_MAX, MPI_COMM_WORLD);
nerrors = ret;
if (MAINPROCESS) {
printf("===================================\n");
if (nerrors)
printf("***Parallel multi dataset tests detected %d errors***\n", nerrors);
else
printf("Parallel multi dataset tests finished with no errors\n");
printf("===================================\n");
} /* end if */
/* close HDF5 library */
H5close();
/* MPI_Finalize must be called AFTER H5close which may use MPI calls */
MPI_Finalize();
/* cannot just return (nerrors) because exit code is limited to 1 byte */
return (nerrors != 0);
} /* end main() */