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


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