tem_init_tracker Subroutine

public subroutine tem_init_tracker(me, tree, solver, varSys, nDofs, globProc, solSpec_unit)

Initialize the tracker entities: * create varMap, i.e. map requested variables to global variable system * initialize spatial reduction * initialize hvs output

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_varSys_type), intent(in) :: varSys

solver-provided variable systems

integer, intent(in), optional :: nDofs

The number of dofs for each scalar variable of the equation system

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

Process description to use.

integer, intent(in), optional :: solSpec_unit

Solver specific unit for restart header


Calls

proc~~tem_init_tracker~~CallsGraph proc~tem_init_tracker tem_init_tracker proc~tem_horizontalspacer tem_horizontalSpacer proc~tem_init_tracker->proc~tem_horizontalspacer proc~tem_reduction_spatial_init tem_reduction_spatial_init proc~tem_init_tracker->proc~tem_reduction_spatial_init proc~tem_abort tem_abort proc~tem_init_tracker->proc~tem_abort proc~tem_create_varmap tem_create_varMap proc~tem_init_tracker->proc~tem_create_varmap proc~hvs_output_init hvs_output_init proc~tem_init_tracker->proc~hvs_output_init mpi_abort mpi_abort proc~tem_abort->mpi_abort interface~truncate~9 truncate proc~tem_create_varmap->interface~truncate~9 interface~append~25 append proc~tem_create_varmap->interface~append~25 interface~positionofval~5 positionofval proc~tem_create_varmap->interface~positionofval~5 interface~init~9 init proc~tem_create_varmap->interface~init~9 proc~hvs_output_init->proc~tem_create_varmap proc~hvs_asciispatial_init hvs_asciiSpatial_init proc~hvs_output_init->proc~hvs_asciispatial_init proc~tem_dump_subtree tem_dump_subTree proc~hvs_output_init->proc~tem_dump_subtree proc~hvs_ascii_init hvs_ascii_init proc~hvs_output_init->proc~hvs_ascii_init proc~tem_baryofid tem_BaryOfId proc~hvs_output_init->proc~tem_baryofid proc~tem_init_restart tem_init_restart proc~hvs_output_init->proc~tem_init_restart proc~tem_calc_vrtx_coord tem_calc_vrtx_coord proc~hvs_output_init->proc~tem_calc_vrtx_coord proc~hvs_vtk_init hvs_vtk_init proc~hvs_output_init->proc~hvs_vtk_init

Contents

Source Code


Source Code

  subroutine tem_init_tracker( me, tree, solver, varSys, nDofs, globProc, &
    &                          solSpec_unit                               )
    ! -------------------------------------------------------------------- !
    !> 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
    !> Global solver information
    type(tem_solveHead_type),intent(in)               :: solver
    !> solver-provided variable systems
    type(tem_varSys_type), intent(in)                 :: varSys
    !> The number of dofs for each scalar variable of the equation system
    integer, intent(in), optional                     :: nDofs
    !> Process description to use.
    type(tem_comm_env_type), intent(in)               :: globProc
    !> Solver specific unit for restart header
    integer, optional, intent(in)                  :: solSpec_unit
    ! -------------------------------------------------------------------- !
    integer :: iLog, nVars, iVar, iConfig
    ! prefix for tracking label to differiate tracking for different scheme
    ! with same tracking label
    character(len=pathLen) :: prefix
    ! tracking%config%prefix//tracking%config%label
    character(len=pathLen) :: basename
    ! -------------------------------------------------------------------- !

    call tem_horizontalSpacer(fUnit=logUnit(1))
    write(logUnit(1),*) 'Initialize tracking objects'
    call tem_horizontalSpacer(fUnit=logUnit(1))

    ! prefix for tracking label to differiate tracking for different scheme
    ! with same tracking label
    prefix = trim(solver%simName)//'_'

    if( me%control%active ) then

      do iLog = 1, me%control%nActive
        iConfig = me%instance(iLog)%pntConfig

        write(logUnit(3),"(A,I0,A)") 'Track object: ', iLog, ', label: ' &
          &                          // trim( me%config(iConfig)%label )

        ! map variables
        ! create tracking variable position in the global varSys
        call tem_create_varMap( varname = me%config(iConfig)%varname, &
          &                     varSys  = varSys,                     &
          &                     varMap  = me%instance(iLog)%varMap    )

        nVars = me%instance(iLog)%varMap%varPos%nVals
        ! Abort if none variables of the variable defined in current
        ! tracking object are found in varSys
        if ( nVars /= size( me%config(iConfig)%varname ) ) then
          write(logUnit(1),*) ' Some of the following variables are not found:'
          do iVar = 1, size(me%config(iConfig)%varName)
            write(logUnit(1),*) trim(me%config(iConfig)%varName(iVar))
          end do
          call tem_abort()
        end if

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

        ! Init spatial reduction
        me%instance(iLog)%output_file%ascii%isReduce = me%config(iConfig)     &
          &                                            %redSpatial_config%active
        if ( me%config(iConfig)%redSpatial_config%active ) then
          ! Initialize reduction
          call tem_reduction_spatial_init(                                     &
            &                 me = me%instance(iLog)%output_file%ascii         &
            &                        %redSpatial,                              &
            &  redSpatial_config = me%config(iConfig)%redSpatial_config,       &
            &             varSys = varSys,                                     &
            &             varPos = me%instance(iLog)%varMap%varPos%val(:nVars) )
        end if

        ! Initialize output
        if ( me%instance(iLog)%subTree%useGlobalMesh ) then
          call hvs_output_init(out_file    = me%instance(iLog)%output_file,    &
            &                  out_config  = me%config(iConfig)%output_config, &
            &                  tree        = tree,                             &
            &                  varSys      = varSys,                           &
            &                  varPos      = me%instance(iLog)%varMap%varPos   &
            &                                                 %val(:nVars),    &
            &                  basename    = trim(basename),                   &
            &                  globProc    = globProc,                         &
            &                  timeControl = me%config(iConfig)%timeControl,   &
            &                  solver      = solver,                           &
            &                  geometry    = me%config(iConfig)%geometry,      &
            &                  nDofs       = nDofs,                            &
            &                  solSpec_unit = solSpec_unit                     )
        else
          call hvs_output_init(out_file    = me%instance(iLog)%output_file,    &
            &                  out_config  = me%config(iConfig)%output_config, &
            &                  tree        = tree,                             &
            &                  varSys      = varSys,                           &
            &                  varPos      = me%instance(iLog)%varMap%varPos   &
            &                                                 %val(:nVars),    &
            &                  subTree     = me%instance(iLog)%subTree,        &
            &                  basename    = trim(basename),                   &
            &                  globProc    = globProc,                         &
            &                  timeControl = me%config(iConfig)%timeControl,   &
            &                  solver      = solver,                           &
            &                  geometry    = me%config(iConfig)%geometry,      &
            &                  nDofs       = nDofs,                            &
            &                  solspec_unit = solSpec_unit                     )
        end if
      end do

    end if ! if tracking active

  end subroutine tem_init_tracker