identify_additionalNeigh Subroutine

private subroutine identify_additionalNeigh(tree, proc, levelDesc, pathFirst, pathLast, stencil)

identify additionally required neighbor elements run over the 'require' list of elements, which was accumulated before in init_elemLevels. The list includes neighbor elements of stencil neighbors, for stencils with the requireNeighNeigh attribute set. This is needed for example for LBM boundary stencil elements, which in turn require their compute stencil neighborhood to allow PULL operations from there

What exactly is the require list for? - Used ONLY for boundary stencil with higher order neighbors i.e only when require nVals > 0

Arguments

Type IntentOptional Attributes Name
type(treelmesh_type), intent(in) :: tree

the global tree

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

Process description to use.

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minlevel:)

the level descriptor to be filled

type(tem_path_type), intent(in) :: pathFirst(:)

first treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

last treeID path in every process

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

the compute stencil, for which the additional neighbors are reconstructed


Source Code

  subroutine identify_additionalNeigh( tree, proc, levelDesc, pathFirst,        &
    &                                  pathLast, stencil )
    ! ---------------------------------------------------------------------------
    !> the global tree
    type(treelmesh_type), intent(in) :: tree
    !> Process description to use.
    type(tem_comm_env_type), intent(in) :: proc
    !> the level descriptor to be filled
    type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minlevel:)
    !> first treeID path in every process
    type(tem_path_type), intent(in) :: pathFirst(:)
    !> last treeID path in every process
    type(tem_path_type), intent(in) :: pathLast(:)
    !> the compute stencil, for which the additional neighbors are reconstructed
    type(tem_stencilHeader_type), intent(in) :: stencil
    ! ---------------------------------------------------------------------------
    integer :: iLevel, posInElem, neighPos, elemPos, iNeighElem, iElem
    integer(kind=long_k) :: treeID
    ! ---------------------------------------------------------------------------

    call tem_horizontalSpacer( fUnit = dbgUnit(1), before = 1 )
    write(dbgUnit(3),*) 'Inside routine: identify_additionalNeigh'

    ! The position of the compute stencil
    do iLevel = tree%global%minlevel, tree%global%maxLevel
      ! Run over the additionally required element list
      do iElem = 1, levelDesc( iLevel )%require%nVals
        ! get the position of the treeID in the element list
        posInElem = PositionOfVal( me  = levelDesc( iLevel )%elem%tID,             &
          &                        val = levelDesc( iLevel )%require%val( iElem ))
        ! get the element position
        if( posInElem > 0 ) then
          if ( levelDesc( iLevel )%elem%eType%val( posInElem ) > 0) then
            ! Run over all the neighbors of the compute stencil
            do iNeighElem = 1, stencil%QQN
              ! position of neighbor treeID in dynamic array of neighID
              neighPos = levelDesc( iLevel )%elem%stencil%val( posInElem )         &
                &                         %val(1)%tIDpos( iNeighElem )
              if( neighPos > 0 ) then
                treeID = &
                  & levelDesc( iLevel )%elem%neighID%val( posInElem )%val( neighPos )
                call identify_elements( TreeID     = treeID,        &
                  &                     tree       = tree,           &
                  &                     pathFirst  = pathFirst,      &
                  &                     pathLast   = pathLast,       &
                  &                     levelDesc  = levelDesc,      &
                  &                     elemPos    = elemPos,        &
                  &                     proc       = proc,           &
                  &                     nesting    = 0,              &
                  &                     stencil    = stencil,        &
                  &       skip_add_additionalGhost = .true.             )
              else ! neighPos =< 0, i.e. no additional neighbor
                elemPos = 0
              end if
              levelDesc( iLevel )%elem%stencil%val( posInElem )%val(1)    &
                &                %totalPos( iNeighElem ) = elemPos
            end do ! neighPos > 0
          else ! eType <= 0
            write(logUnit(8),*) 'Can not find additional neighbor: ', treeID
          end if  ! valid elemType
        else ! posInElem <= 0
          write(logUnit(2),*) 'element which requires additional neighbor is not part of total list'
        end if ! posInElem > 0
      end do ! iElem
    end do ! iLevel

    write(dbgUnit(1),*) 'Leave routine: identify_additionalNeigh'
    call tem_horizontalSpacer( fUnit = dbgUnit(1), after = 1 )

  end subroutine identify_additionalNeigh