single_process_element Subroutine

private subroutine single_process_element(targetID, levelDesc, tree, proc, iProc, minLevel, elemPos, stencil, nesting, updated, skip_add_additionalGhost)

Determine the location (which process) of a requested element, which was identified to be located on one single process (can be local or remote) If it is located on a remote process: add to halo list local process: identify if ghost or fluid

Arguments

Type IntentOptional Attributes Name
integer(kind=long_k), intent(in) :: targetID

neighboring treeID

type(tem_levelDesc_type), intent(inout) :: levelDesc(minLevel:)

the level descriptor to be filled

type(treelmesh_type), intent(in) :: tree

tree information

type(tem_comm_env_type), intent(in) :: proc

Process description to use.

integer, intent(in) :: iProc

Process on which targetID is located

integer, intent(in) :: minLevel

minimum level fluid element in the tree

integer, intent(out) :: elemPos

targetID element position in the levelDesc % elem list

type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

integer, intent(in) :: nesting

nesting level

logical, intent(out) :: updated

was the element updated in this call?

logical, intent(in), optional :: skip_add_additionalGhost

logical, optional, if true no ghosts are added


Source Code

  subroutine single_process_element( targetID, levelDesc, tree, proc, iProc, &
    &                                minLevel, elemPos, stencil, nesting,    &
    &                                updated, skip_add_additionalGhost )
    ! -------------------------------------------------------------------- !
    !> neighboring treeID
    integer(kind=long_k), intent(in)         :: targetID
    !> minimum level fluid element in the tree
    integer, intent(in)                      :: minLevel
    !> the level descriptor to be filled
    type(tem_levelDesc_type), intent(inout)  :: levelDesc(minLevel:)
    !> Process description to use.
    type(tem_comm_env_type), intent(in)      :: proc
    !> Process on which targetID is located
    integer, intent(in)                      :: iProc
    !> tree information
    type(treelmesh_type), intent(in)         :: tree
    !> current stencil definition
    type(tem_stencilHeader_type), intent(in) :: stencil
    !> targetID element position in the levelDesc % elem list
    integer, intent(out)                     :: elemPos
    !> nesting level
    integer, intent(in)                      :: nesting
    !> was the element updated in this call?
    logical, intent(out)                     :: updated
    !> logical, optional, if true no ghosts are added
    logical, intent(in), optional :: skip_add_additionalGhost
    ! -------------------------------------------------------------------- !
    type(tem_stencilElement_type) :: emptyStencil(1)
    integer :: targetLevel
    logical :: wasAdded
    logical :: l_skip_add_additionalGhost
    ! -------------------------------------------------------------------- !
    
    if (present(skip_add_additionalGhost)) then 
      l_skip_add_additionalGhost = skip_add_additionalGhost
    else 
      l_skip_add_additionalGhost = .false.
    end if 

    targetLevel = tem_LevelOf(targetID) ! Has to be same as tLevel!?
    if ( (targetLevel < minLevel)                 &
      &  .or. (targetLevel > uBound(levelDesc,1)) ) then
      write(logUnit(1),*) ' ERROR: level which is not included in the fluid'// &
        &                 ' tree was demanded in singleProcNeigh'
      write(logUnit(1),"(2(A,I0))") 'treeID: ', targetID, ', level: ', &
        &                           targetLevel
      call tem_abort()
    end if

    ! Set the element updated flag as a default to false
    updated = .false.

    ! If it is a remote cell on only one process -> regular halo
    if (iProc /= proc%rank + 1) then
      ! REMOTE
      call init( me = emptyStencil(1), QQN=stencil%QQN )

      ! append this targetID as halo element to levelDesc elem list
      call append( me              = levelDesc(targetLevel)%elem, &
        &          tID             = targetID,                    &
        &          eType           = eT_halo,                     &
        &          property        = 0_long_k,                    &
        &          sourceProc      = iProc,                       &
        &          haloNesting     = nesting,                     &
        &          stencilElements = emptyStencil,                &
        &          pos             = elemPos,                     &
        &          wasAdded        = wasAdded                     )

      if (.not. wasAdded) then
        ! If this element was already there, make sure we use the minimal
        ! nesting level requested for this element.
        updated = ( nesting < levelDesc(targetLevel) &
          &                     %elem                &
          &                     %haloNesting         &
          &                     %val(elemPos)        )
        ! If the nesting has been updated (decreased, we need to revisit this
        ! element in search for its neighbors).
        levelDesc(targetLevel)%elem%needsUpdate%val(elemPos) = updated

        levelDesc(targetLevel)%elem%haloNesting%val(elemPos)              &
          &  = min( levelDesc(targetLevel)%elem%haloNesting%val(elemPos), &
          &         nesting                                               )
      else
        ! New halo element added
        updated = .true.
        write(dbgUnit(7),"(A,I0)") 'Added as a Halo: ', targetID, &
          &                        'to level: ', targetLevel
      end if ! wasAdded

    else ! iProc == proc%rank + 1
      ! LOCAL

      ! Either a local ghost or fluid cell
      call identify_local_element(                                 &
        &    targetID                 = targetID,                  &
        &    levelDesc                = levelDesc,                 &
        &    tree                     = tree,                      &
        &    elemPos                  = elemPos,                   &
        &    minLevel                 = minLevel,                  &
        &    nesting                  = nesting,                   &
        &    updated                  = updated,                   &
        &    stencil                  = stencil,                   &
        &    skip_add_additionalGhost = l_skip_add_additionalGhost )
    end if ! iProc /= proc%rank + 1

  end subroutine single_process_element