create_allParentNeighbors Subroutine

private recursive subroutine create_allParentNeighbors(targetID, level, stencil, tree, levelDesc, pathFirst, pathLast, proc)

create all the neighbors of an element's parent

Create all elements required up to the actual existing fluid element these include the neighbors of the parents. In a level jump >1, these intermediate levels have to provide valid quantities over two of their computation updates to account for the recursive algorithm.

Here the fromCoarser interpolation should be handed in.

Arguments

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

requested element position (child element) in LevelDesc elem list

integer, intent(in) :: level

requested element level

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

current stencil definition

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

tree information

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_comm_env_type), intent(in) :: proc

process


Calls

proc~~create_allparentneighbors~~CallsGraph proc~create_allparentneighbors create_allParentNeighbors interface~append~11 append proc~create_allparentneighbors->interface~append~11 interface~tem_parentof tem_ParentOf proc~create_allparentneighbors->interface~tem_parentof proc~identify_elements identify_elements proc~create_allparentneighbors->proc~identify_elements proc~identify_stencilneigh identify_stencilNeigh proc~create_allparentneighbors->proc~identify_stencilneigh proc~append_ga_dynlong append_ga_dynlong interface~append~11->proc~append_ga_dynlong proc~append_ga_dynlong_vec append_ga_dynlong_vec interface~append~11->proc~append_ga_dynlong_vec proc~tem_directparent tem_directParent interface~tem_parentof->proc~tem_directparent proc~tem_parentatlevel tem_ParentAtLevel interface~tem_parentof->proc~tem_parentatlevel proc~identify_elements->proc~create_allparentneighbors proc~identify_elements->interface~append~11 proc~identify_elements->proc~identify_elements proc~identify_elements->proc~identify_stencilneigh interface~init~24 init proc~identify_elements->interface~init~24 proc~single_process_element single_process_element proc~identify_elements->proc~single_process_element proc~tem_directchildren tem_directChildren proc~identify_elements->proc~tem_directchildren proc~tem_find_depproc tem_find_depProc proc~identify_elements->proc~tem_find_depproc proc~tem_levelof tem_LevelOf proc~identify_elements->proc~tem_levelof proc~tem_pathof tem_PathOf proc~identify_elements->proc~tem_pathof proc~tem_tidinfo tem_tIDinfo proc~identify_elements->proc~tem_tidinfo proc~identify_stencilneigh->proc~identify_elements proc~init_ga2d_real init_ga2d_real interface~init~24->proc~init_ga2d_real interface~expand~9 expand proc~append_ga_dynlong->interface~expand~9 proc~append_ga_dynlong_vec->interface~expand~9 proc~single_process_element->interface~append~11 proc~single_process_element->interface~init~24 proc~single_process_element->proc~tem_levelof proc~identify_local_element identify_local_element proc~single_process_element->proc~identify_local_element proc~tem_abort tem_abort proc~single_process_element->proc~tem_abort proc~tem_find_depproc_globsearch tem_find_depProc_globSearch proc~tem_find_depproc->proc~tem_find_depproc_globsearch proc~tem_pathcomparison tem_PathComparison proc~tem_find_depproc->proc~tem_pathcomparison proc~tem_parentatlevel->proc~tem_levelof proc~tem_baryofid tem_BaryOfId proc~tem_tidinfo->proc~tem_baryofid proc~tem_coordofid tem_CoordOfId proc~tem_tidinfo->proc~tem_coordofid proc~tem_elemsize tem_ElemSize proc~tem_tidinfo->proc~tem_elemsize proc~expand_ga_dynlong expand_ga_dynlong interface~expand~9->proc~expand_ga_dynlong proc~identify_local_element->interface~append~11 proc~identify_local_element->proc~tem_levelof proc~identify_local_element->proc~tem_pathof proc~identify_local_element->proc~tem_tidinfo interface~positionofval~5 positionofval proc~identify_local_element->interface~positionofval~5 proc~add_all_virtual_children add_all_virtual_children proc~identify_local_element->proc~add_all_virtual_children proc~add_ghostfromfiner add_ghostFromFiner proc~identify_local_element->proc~add_ghostfromfiner proc~tem_posofpath tem_PosOfPath proc~identify_local_element->proc~tem_posofpath mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_baryofid->proc~tem_coordofid proc~tem_elemsizelevel tem_ElemSizeLevel proc~tem_baryofid->proc~tem_elemsizelevel proc~tem_coordofid->proc~tem_levelof proc~tem_elemsize->proc~tem_levelof proc~tem_elemsize->proc~tem_elemsizelevel proc~tem_find_depproc_globsearch->proc~tem_pathcomparison

Called by

proc~~create_allparentneighbors~~CalledByGraph proc~create_allparentneighbors create_allParentNeighbors proc~identify_elements identify_elements proc~create_allparentneighbors->proc~identify_elements proc~identify_stencilneigh identify_stencilNeigh proc~create_allparentneighbors->proc~identify_stencilneigh proc~identify_elements->proc~create_allparentneighbors proc~identify_elements->proc~identify_elements proc~identify_elements->proc~identify_stencilneigh proc~request_remotehalos request_remoteHalos proc~request_remotehalos->proc~create_allparentneighbors proc~request_remotehalos->proc~identify_stencilneigh proc~build_levelelements build_levelElements proc~build_levelelements->proc~identify_elements proc~identify_additionalneigh identify_additionalNeigh proc~build_levelelements->proc~identify_additionalneigh proc~communicate_elements communicate_elements proc~communicate_elements->proc~request_remotehalos proc~identify_additionalneigh->proc~identify_elements proc~identify_stencilneigh->proc~identify_elements proc~tem_find_allelements tem_find_allElements proc~tem_find_allelements->proc~build_levelelements proc~tem_find_allelements->proc~communicate_elements proc~tem_find_allelements->proc~identify_additionalneigh proc~tem_create_leveldesc tem_create_levelDesc proc~tem_create_leveldesc->proc~tem_find_allelements

Source Code

  recursive subroutine create_allParentNeighbors(                          &
    &                           targetID, level, stencil, tree, levelDesc, &
    &                           pathFirst, pathLast, proc                  )
    ! -------------------------------------------------------------------- !
    !> requested element position (child element) in LevelDesc elem list
    integer(kind=long_k), intent(in) :: targetID
    !> requested element level
    integer, intent(in) :: level
    !> 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(:)
    !> tree information
    type(treelmesh_type), intent(in) :: tree
    !> the level descriptor to be filled
    type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)
    !> process
    type(tem_comm_env_type), intent(in) :: proc
    !> current stencil definition
    type(tem_stencilHeader_type), intent(in) :: stencil
    ! -------------------------------------------------------------------- !
    integer(kind=long_k) :: parentID, neighID  ! current tree ID
    integer :: coarserLevel, cPos, parentNesting, addedPos, iStencilElem
    integer :: neighIDpos
    ! -------------------------------------------------------------------- !

    ! exit if we have reached the minimal level
    if ( level == tree%global%minlevel ) return

    ! Get the parent of the current treeID
    parentID = tem_parentOf( targetID )

    ! ... and identify the parent
    parentNesting = -1
    call identify_elements( TreeID     = parentID,  &
      &                     tree       = tree,      &
      &                     pathFirst  = pathFirst, &
      &                     pathLast   = pathLast,  &
      &                     levelDesc  = levelDesc, &
      &                     elemPos    = cPos,      &
      &                     proc       = proc,      &
      &                     stencil    = stencil,   &
      &                     nesting    = -1         )

    if ( cPos <= 0 ) then
      write(dbgUnit(3),*) ' Element not found: ', parentID
      write(dbgUnit(3),*) '              cPos: ', cPos
    end if

    ! identify the stencil neighbors of the parent.
    ! Here we should identify the fromCoarser interpolation stencil neighbors
    ! instead of the compute stencil neighbors
    coarserLevel = level - 1
    call identify_stencilNeigh( iElem     = cPos,         &
      &                         iLevel    = coarserLevel, &
      &                         tree      = tree,         &
      &                         iStencil  = 1,            &
      &                         pathFirst = pathFirst,    &
      &                         pathLast  = pathLast,     &
      &                         levelDesc = levelDesc,    &
      &                         proc      = proc,         &
      &                         stencil   = stencil,      &
      &                         nesting   = parentNesting )
      
    ! adding neighs of neighs for interpolation at ML
    ! this is for the stencil of the fine ghost, composed by coarse fluid 
    do iStencilElem = 1, stencil%QQN
    
      neighIDpos = levelDesc(coarserLevel)%elem%stencil%val(cPos)    &
        &                           %val(1)%tIDpos(iStencilElem)
      if( neighIDpos > 0 ) then
        neighID = &
          & levelDesc( coarserLevel )%elem%neighID%val(cPos)%val(neighIDpos)
        ! This call might add new halo elements
        if ( neighID > 0_long_k ) then
          call append( me       = levelDesc( coarserLevel )%require, &
            &          val      = neighID,                           &
            &          pos      = addedPos )
        end if
      end if ! neighIDpos > 0
    enddo

  end subroutine create_allParentNeighbors