tem_shape2subTree Subroutine

public subroutine tem_shape2subTree(me, iShape, inTree, storePnts, map2global, grwPnts, countElems, countPnts, bcIDs, bc_prop, stencil)

Identify elements matching a given shape to build a subTree.

Arguments

Type IntentOptional Attributes Name
type(tem_shape_type), intent(in) :: me

The shape to identify elements for

integer, intent(in) :: iShape

Numbering of the shape (only for logging)

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

The tree to look in for elements that match the shape definition

logical, intent(in) :: storePnts

Whether to store point values

type(dyn_intarray_type), intent(inout) :: map2global

Mapping to global elements in the tree

type(tem_grwPoints_type), intent(inout) :: grwPnts

Growing list of Points to be observed

integer, intent(out) :: countElems(globalMaxLevels)

Number of elements on each level matching the shape

integer, intent(out) :: countPnts

Number of points to be observed

integer, intent(out), allocatable :: bcIDs(:)

Field of boundary ids that are to be tracked

type(tem_BC_prop_type), intent(in), optional :: bc_prop

Boundary condition property to identify boundary elements

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

Stencil associated with the boundary to find respective neighbors


Calls

proc~~tem_shape2subtree~~CallsGraph proc~tem_shape2subtree tem_shape2subTree proc~tem_shape_initpropelements tem_shape_initPropElements proc~tem_shape2subtree->proc~tem_shape_initpropelements proc~tem_shape_findelembybclabels tem_shape_findElemByBCLabels proc~tem_shape2subtree->proc~tem_shape_findelembybclabels proc~tem_abort tem_abort proc~tem_shape2subtree->proc~tem_abort proc~tem_shape_initbylevels tem_shape_initByLevels proc~tem_shape2subtree->proc~tem_shape_initbylevels proc~tem_shape_subtreefromgeominters tem_shape_subTreeFromGeomInters proc~tem_shape2subtree->proc~tem_shape_subtreefromgeominters interface~append~9 append proc~tem_shape_initpropelements->interface~append~9 proc~tem_levelof tem_LevelOf proc~tem_shape_initpropelements->proc~tem_levelof proc~tem_elemsize tem_ElemSize proc~tem_shape_findelembybclabels->proc~tem_elemsize proc~tem_shape_findelembybclabels->interface~append~9 proc~tem_baryofid tem_BaryOfId proc~tem_shape_findelembybclabels->proc~tem_baryofid mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_shape_initbylevels->interface~append~9 proc~tem_firstidatlevel tem_FirstIdAtLevel proc~tem_shape_initbylevels->proc~tem_firstidatlevel proc~tem_shape_initbylevels->proc~tem_levelof interface~tem_tostr tem_toStr proc~tem_shape_initbylevels->interface~tem_tostr proc~tem_lastidatlevel tem_LastIdAtLevel proc~tem_shape_initbylevels->proc~tem_lastidatlevel interface~tem_log tem_log proc~tem_shape_initbylevels->interface~tem_log proc~tem_shape_subtreefromgeominters->proc~tem_abort proc~tem_converttreeidtocube tem_convertTreeIDtoCube proc~tem_shape_subtreefromgeominters->proc~tem_converttreeidtocube proc~tem_cano_initsubtree tem_cano_initSubTree proc~tem_shape_subtreefromgeominters->proc~tem_cano_initsubtree proc~tem_cylindercubeoverlap tem_cylinderCubeOverlap proc~tem_shape_subtreefromgeominters->proc~tem_cylindercubeoverlap proc~tem_shape_subtreefromgeominters->interface~append~9 proc~tem_shape_subtreefromgeominters->proc~tem_levelof mpi_wtime mpi_wtime proc~tem_shape_subtreefromgeominters->mpi_wtime proc~tem_cano_checkneigh tem_cano_checkNeigh proc~tem_shape_subtreefromgeominters->proc~tem_cano_checkneigh proc~tem_stlcubeoverlap tem_stlCubeOverlap proc~tem_shape_subtreefromgeominters->proc~tem_stlcubeoverlap proc~tem_spherecubeoverlap tem_sphereCubeOverlap proc~tem_shape_subtreefromgeominters->proc~tem_spherecubeoverlap interface~init~22 init proc~tem_shape_subtreefromgeominters->interface~init~22 proc~tem_trianglecubeoverlap tem_triangleCubeOverlap proc~tem_shape_subtreefromgeominters->proc~tem_trianglecubeoverlap proc~tem_ellipsoidcubeoverlap tem_ellipsoidCubeOverlap proc~tem_shape_subtreefromgeominters->proc~tem_ellipsoidcubeoverlap proc~tem_cano_storepntsinsubtree tem_cano_storePntsInSubTree proc~tem_shape_subtreefromgeominters->proc~tem_cano_storepntsinsubtree mpi_allreduce mpi_allreduce proc~tem_shape_subtreefromgeominters->mpi_allreduce

Called by

proc~~tem_shape2subtree~~CalledByGraph proc~tem_shape2subtree tem_shape2subTree proc~tem_create_subtree_of tem_create_subTree_of proc~tem_create_subtree_of->proc~tem_shape2subtree proc~tem_init_convergence tem_init_convergence proc~tem_init_convergence->proc~tem_create_subtree_of proc~tem_init_tracker_subtree tem_init_tracker_subTree proc~tem_init_tracker_subtree->proc~tem_create_subtree_of proc~tem_write_debugmesh tem_write_debugMesh proc~tem_write_debugmesh->proc~tem_create_subtree_of proc~tem_create_subtree_of_st_funlist tem_create_subTree_of_st_funList proc~tem_create_subtree_of_st_funlist->proc~tem_create_subtree_of

Contents

Source Code


Source Code

  subroutine tem_shape2subTree( me, iShape, inTree, storePnts, map2global, &
    &                           grwPnts, countElems, countPnts, bcIDs,     &
    &                           bc_prop, stencil                           )
    ! ---------------------------------------------------------------------- !
    !> The shape to identify elements for
    type(tem_shape_type), intent(in) :: me

    !> Numbering of the shape (only for logging)
    integer, intent(in) :: iShape

    !> The tree to look in for elements that match the shape definition
    type(treelmesh_type), intent(in) :: inTree

    !> Whether to store point values
    logical, intent(in) :: storePnts

    !> Mapping to global elements in the tree
    type(dyn_intArray_type), intent(inout) :: map2global

    !> Growing list of Points to be observed
    type(tem_grwPoints_type), intent(inout) :: grwPnts

    !> Number of elements on each level matching the shape
    integer, intent(out) :: countElems(globalMaxLevels)

    !> Number of points to be observed
    integer, intent(out) :: countPnts

    !> Field of boundary ids that are to be tracked
    integer, allocatable, intent(out) :: bcIDs(:)

    !> Boundary condition property to identify boundary elements
    type(tem_bc_prop_type), optional, intent(in) :: bc_prop

    !> Stencil associated with the boundary to find respective neighbors
    type(tem_stencilHeader_type), optional, intent(in) :: stencil
    ! ---------------------------------------------------------------------- !
    logical :: foundAny
    integer :: nShapeElems(globalMaxLevels)
    ! ---------------------------------------------------------------------- !

    foundAny = .false.
    nShapeElems = 0

    select case( me%shapeID )
    case( tem_geometrical_shape )
      ! Use elements intersecting a geometrical object
      write(logUnit(5),*) 'iShape ', iShape, ' is a geometrical shape.'
      call tem_shape_subTreeFromGeomInters( me          = me,          &
        &                                   inTree      = inTree,      &
        &                                   countElems  = nShapeElems, &
        &                                   countPoints = countPnts,   &
        &                                   grwPnts     = grwPnts,     &
        &                                   storePnts   = storePnts,   &
        &                                   map2global  = map2global   )

    case( tem_property_shape )
      ! Only use elements with a certain property
      write(logUnit(5),*) 'iShape ', iShape, ' is a property shape.'
      call tem_shape_initPropElements( me%propBits, inTree,   &
        &                              nShapeElems, map2global )

    case( tem_boundary_shape )
      ! Only use elements belong to certain boundaries
      write(logUnit(5),*) 'iShape ', iShape, ' is a boundary shape.'
      if (present(bc_prop) .and. present(stencil)) then
        call tem_shape_findElemByBCLabels( bcLabels    = me%bcLabels,   &
          &                                cutOffQVal  = me%cutOffQVal, &
          &                                bc_prop     = bc_prop,       &
          &                                foundAny    = foundAny,      &
          &                                map2global  = map2Global,    &
          &                                inTree      = inTree,        &
          &                                countPoints = countPnts,     &
          &                                grwPnts     = grwPnts,       &
          &                                storePnts   = storePnts,     &
          &                                bcIDs       = bcIDs,         &
          &                                stencil     = stencil        )
        if (foundAny) nShapeElems = 1
      else
        call tem_abort('In tem_shape2subTree: Stencil or bc_prop not passed!')
      end if

    case( tem_level_shape )
      write(logUnit(5),*) 'iShape ', iShape, ' is a level shape.'
      call tem_shape_initByLevels( inTree, me%minLevel,   &
        &                          me%maxLevel,           &
        &                          nShapeElems, map2global )
    end select ! shapeID

    countElems = countElems + nShapeElems

  end subroutine tem_shape2subTree