tem_init_tracker_subTree Subroutine

public subroutine tem_init_tracker_subTree(me, tree, solver, bc_prop, stencil, prefix)

Routine creates subTree for each tracking object and removes tracking objects on process which do not include any elements to track

Identify, how many and which elements exist on my local process and are requested from the trackers Empty tracking entities are removed, so the track(:) might be re-allocated

Arguments

Type IntentOptional Attributes Name
type(tem_tracking_type), intent(inout) :: me

tracking entities

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

Global mesh from which the elements are identified and then stored to sub-meshes inside the trackers

type(tem_solveHead_type), intent(in) :: solver

Global solver information

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

bc property that used to identify elements of certain BCs

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

stencil used to create subTree of boundary type

character(len=labelLen), intent(in), optional :: prefix

Prefix for output filename Usually: solver%simName


Calls

proc~~tem_init_tracker_subtree~~CallsGraph proc~tem_init_tracker_subtree tem_init_tracker_subTree proc~tem_horizontalspacer tem_horizontalSpacer proc~tem_init_tracker_subtree->proc~tem_horizontalspacer proc~tem_create_subtree_of tem_create_subTree_of proc~tem_init_tracker_subtree->proc~tem_create_subtree_of proc~tem_create_subtree_of->proc~tem_horizontalspacer proc~tem_shape_initlocal tem_shape_initLocal proc~tem_create_subtree_of->proc~tem_shape_initlocal mpi_comm_split mpi_comm_split proc~tem_create_subtree_of->mpi_comm_split mpi_comm_size mpi_comm_size proc~tem_create_subtree_of->mpi_comm_size mpi_comm_rank mpi_comm_rank proc~tem_create_subtree_of->mpi_comm_rank proc~tem_subtree_from tem_subTree_from proc~tem_create_subtree_of->proc~tem_subtree_from interface~tem_copypropertybits tem_copyPropertyBits proc~tem_create_subtree_of->interface~tem_copypropertybits proc~tem_abort tem_abort proc~tem_create_subtree_of->proc~tem_abort mpi_allreduce mpi_allreduce proc~tem_create_subtree_of->mpi_allreduce proc~tem_shape2subtree tem_shape2subTree proc~tem_create_subtree_of->proc~tem_shape2subtree interface~init~22 init proc~tem_create_subtree_of->interface~init~22 interface~destroy~22 destroy proc~tem_create_subtree_of->interface~destroy~22 interface~tem_seteffboundingbox tem_setEffBoundingBox proc~tem_create_subtree_of->interface~tem_seteffboundingbox proc~tem_subtree_from->mpi_comm_size proc~tem_subtree_from->mpi_comm_rank proc~tem_subtree_from->proc~tem_abort mpi_bcast mpi_bcast proc~tem_subtree_from->mpi_bcast mpi_reduce mpi_reduce proc~tem_subtree_from->mpi_reduce mpi_exscan mpi_exscan proc~tem_subtree_from->mpi_exscan proc~tem_copypropertybitsfromleveldesc tem_copyPropertyBitsFromLevelDesc interface~tem_copypropertybits->proc~tem_copypropertybitsfromleveldesc proc~tem_copypropertybitsfromtree tem_copyPropertyBitsFromTree interface~tem_copypropertybits->proc~tem_copypropertybitsfromtree mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~tem_shape2subtree->proc~tem_abort 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_shape_subtreefromgeominters tem_shape_subTreeFromGeomInters proc~tem_shape2subtree->proc~tem_shape_subtreefromgeominters proc~tem_shape_initbylevels tem_shape_initByLevels proc~tem_shape2subtree->proc~tem_shape_initbylevels proc~init_ga2d_real init_ga2d_real interface~init~22->proc~init_ga2d_real proc~destroy_ga2d_real destroy_ga2d_real interface~destroy~22->proc~destroy_ga2d_real proc~tem_seteffboundingbox_fromtree tem_setEffBoundingBox_fromTree interface~tem_seteffboundingbox->proc~tem_seteffboundingbox_fromtree proc~tem_seteffboundingbox_fromsubtree tem_setEffBoundingBox_fromSubTree interface~tem_seteffboundingbox->proc~tem_seteffboundingbox_fromsubtree

Contents


Source Code

  subroutine tem_init_tracker_subTree( me, tree, solver, bc_prop, stencil, &
    &                                  prefix )
    ! -------------------------------------------------------------------- !
    !> tracking entities
    type(tem_tracking_type), intent(inout)             :: me
    !> Global mesh from which the elements are identified and then stored to
    !! sub-meshes inside the trackers
    type(treelmesh_type), intent(in)                   :: tree
    !> bc property that used to identify elements of certain BCs
    type( tem_bc_prop_type ), intent(in)               :: bc_prop
    !> Global solver information
    type(tem_solveHead_type), intent(in)               :: solver
    !> stencil used to create subTree of boundary type
    type(tem_stencilHeader_type), optional, intent(in) :: stencil
    !> Prefix for output filename
    !! Usually: solver%simName
    character(len=labelLen), optional, intent(in)      :: prefix
    ! -------------------------------------------------------------------- !
    integer :: iLog, nActive
    ! temporary tracker array
    type( tem_tracking_instance_type ), allocatable :: tempTrack(:)
    ! prefix for tracking label
    character(len=pathLen) :: prefix_loc
    ! tracking%config%prefix//tracking%config%label
    character(len=pathLen) :: basename
    ! -------------------------------------------------------------------- !
    call tem_horizontalSpacer(fUnit=logUnit(1))
    write(logUnit(3),*) 'Initialize tracking subTree to remove empty objects'
    call tem_horizontalSpacer(fUnit=logUnit(1))

    nActive = 0

    if (present(prefix)) then
      prefix_loc = trim(prefix)
    else
      ! prefix for tracking label
      prefix_loc = trim(solver%simName)//'_'
    end if

    if( me%control%active ) then
      ! Allocate the temporary track
      allocate(tempTrack( me%control%nDefined ) )

      do iLog = 1, me%control%nDefined

        basename = trim(me%config(iLog)%prefix) // trim(prefix_loc) // &
          &        trim(me%config(iLog)%label)

        write(logUnit(3),*) 'Creating subTree for tracking object ' &
          &                 // trim( me%config(iLog)%label )

        !-----------------------------------------------------------------------
        ! identify tracker elements
        !-----------------------------------------------------------------------
        call tem_create_subTree_of( inTree    = tree,                       &
          &                         bc_prop   = bc_prop,                    &
          &                         stencil   = stencil,                    &
          &                         subTree   = me%instance(iLog)%subTree,  &
          &                         inShape   = me%config(iLog)%geometry,   &
          &                         storePnts = me%config(iLog)             &
          &                                     %output_config%useGetPoint, &
          &                         prefix    = trim(basename)              )

        ! get rid of the empty track in order to avoid empty writes to disk
        if ( me%instance(iLog)%subTree%useGlobalMesh .or. &
          &  ( me%instance(iLog)%subTree%nElems > 0 ) .or. &
          &  ( me%instance(iLog)%subTree%nPoints > 0) ) then
          nActive = nActive + 1
          tempTrack( nActive ) = me%instance(iLog)
          ! Pointer to array of tracking headers loaded from config file
          tempTrack( nActive )%pntConfig = iLog
        end if

      end do  ! nActive

      deallocate(me%instance)
      allocate( me%instance(nActive) )
      me%control%nActive = nActive

      do iLog = 1, nActive
        ! Copy the stuff from the temporary track
        me%instance(iLog) = temptrack(iLog)
      end do

      deallocate(temptrack)
    end if ! if tracking active

  end subroutine tem_init_tracker_subTree