This subroutine evaluated get_element and dump each chunk
This routine is used in tracking to dump in data in harvester format for single variable system
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(tem_restart_type), | intent(inout) | :: | restart |
The restart object describing how and what to output. |
||
type(tem_varSys_type), | intent(in) | :: | varsys |
Description of the available variable system to get the given varnames from. |
||
type(treelmesh_type), | intent(in) | :: | tree |
Mesh to write the data on. |
||
type(tem_time_type), | intent(in) | :: | time |
Point in time to use for this data. Can be important for space-time function evaluations. |
||
type(tem_subTree_type), | intent(in), | optional | :: | subtree |
Optional restriction of the elements to output. |
subroutine tem_restart_dump_data( restart, varSys, tree, time, subTree )
! & transientReduce )
! -------------------------------------------------------------------- !
!> The restart object describing how and what to output.
type(tem_restart_type), intent(inout) :: restart
!> Description of the available variable system to get the given varnames
!! from.
type(tem_varSys_type), intent(in) :: varsys
!> Mesh to write the data on.
type(treelmesh_type), intent(in) :: tree
!> Point in time to use for this data.
!!
!! Can be important for space-time function evaluations.
type(tem_time_type), intent(in) :: time
!> Optional restriction of the elements to output.
type(tem_subtree_type), optional, intent(in) :: subtree
!> transient reducution
! type(tem_transient_reduction_type), intent(inout) :: transientReduce(:)
! -------------------------------------------------------------------- !
integer :: nVars, nElems, nScalars, elemOff, nChunkElems
integer :: iElem, iChunk
integer :: buf_start, buf_end
real(kind=rk), allocatable :: res(:)
integer, allocatable :: elemPos(:)
integer :: ioStatus( mpi_status_size )
integer :: iError
! -------------------------------------------------------------------- !
allocate(res(io_buffer_size))
! Number of variables to dump
nVars = restart%varMap%varPos%nVals
! Number of scalars in current output
nScalars = restart%varMap%nScalars
if (present(subTree)) then
nElems = subTree%nElems
else
nElems = tree%nElems
end if
! open transient reduction
! call tem_transient_reduction_open( me = transientReduce, &
! & time = time%sim )
! allocate elemPos to size of chunkSize
allocate(elemPos(restart%write_file%chunkSize))
! Process all chunks to derive the quantities defined in the tracking object
do iChunk = 1, restart%write_file%nChunks
! Number of elements read so far in previous chunks.
elemOff = ((iChunk-1)*restart%write_file%chunkSize)
! number of elements written to THIS chunk
nChunkElems = min(restart%write_file%chunkSize, nElems-elemOff)
restart%nChunkElems = nChunkElems
! Compute the element lower and upper bound for the current chunk
buf_start = elemOff + 1
buf_end = elemOff + nChunkElems
if (present(subTree)) then
elemPos(1:nChunkElems) = subTree%map2Global(buf_start:buf_end)
else
elemPos(1:nChunkElems) = (/ (iElem, iElem=buf_start, buf_end) /)
end if
! evaluate all variables on current chunk
call tem_get_element_chunk(varSys = varSys, &
& varPos = restart%varMap%varPos &
& %val(:nVars), &
& elemPos = elemPos(1:nChunkElems), &
& time = time, &
& tree = tree, &
& nElems = nChunkElems, &
& nDofs = restart%write_file%nDofs, &
& res = res )
! perform transient reduction
! @todo KM: Check transientReduction when nDofs>1
! call tem_transient_reduction_apply( me = transientReduce, &
! & chunk = res, &
! & offset = buf_start - 1, &
! & nChunkElems = nChunkElems, &
! & varSys = varSys, &
! & varPos = restart%varMap &
! & %varPos%val(:nVars) )
! Now write the results into the file, using the view defined in
! [[tem_restart_openWrite]]
! arguments:
! file handle = binary unit opened in mpi_file_open
! initial address of buffer = first entry to dump within the chunk
! this is ad
call mpi_file_write_all( restart%binaryUnit, res, &
& restart%nChunkElems, &
& restart%write_file%vectype, &
& iostatus, iError )
call check_mpi_error( iError,'File write all in tem_restart_dump_data')
end do !iChunk
deallocate(elemPos)
deallocate(res)
! close transient reduction
! call tem_transient_reduction_close( me = transientReduce )
end subroutine tem_restart_dump_data