hvs_output_init Subroutine

public subroutine hvs_output_init(out_file, out_config, tree, varsys, subtree, varPos, basename, timeControl, nDofs, globProc, solver, geometry, solSpec_unit)

Initialize the output for a given mesh.

This creates vertex for a mesh and fill hvs_output_file_type.

Arguments

Type IntentOptional Attributes Name
type(hvs_output_file_type), intent(inout) :: out_file

Output file settings It must be intent inout since ascii%reduction and trasient%reduction are loaded in tem_load_trackingHeader

type(hvs_output_config_type), intent(in) :: out_config

The output configuration settings to use.

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

Mesh of the data to visualize.

type(tem_varSys_type), intent(in) :: varsys

Description of the available variable system to get the given varnames from.

type(tem_subTree_type), intent(in), optional :: subtree

Optional restriction of the elements to output.

integer, intent(in), optional :: varPos(:)

List of variable positions that should be written in the output.

If this is not provided, all variables from the varsys will be written to the vtk file.

character(len=*), intent(in) :: basename

An extension to the output basename.

The filename will be constructed by tracking%header%prefix// tracking%header%label

type(tem_timeControl_type), intent(in), optional :: timeControl

output timeControl

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

Global communicator type for global rank information

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

Global solver information

type(tem_shape_type), intent(in), optional :: geometry(:)

shape defined for this ascii output

integer, intent(in), optional :: solSpec_unit

Solver specific unit for restart header


Calls

proc~~hvs_output_init~~CallsGraph proc~hvs_output_init hvs_output_init proc~hvs_ascii_init hvs_ascii_init proc~hvs_output_init->proc~hvs_ascii_init proc~hvs_asciispatial_init hvs_asciiSpatial_init proc~hvs_output_init->proc~hvs_asciispatial_init proc~hvs_vtk_init hvs_vtk_init proc~hvs_output_init->proc~hvs_vtk_init proc~tem_baryofid tem_BaryOfId proc~hvs_output_init->proc~tem_baryofid proc~tem_calc_vrtx_coord tem_calc_vrtx_coord proc~hvs_output_init->proc~tem_calc_vrtx_coord proc~tem_create_varmap tem_create_varMap proc~hvs_output_init->proc~tem_create_varmap proc~tem_dump_subtree tem_dump_subTree proc~hvs_output_init->proc~tem_dump_subtree proc~tem_init_restart tem_init_restart proc~hvs_output_init->proc~tem_init_restart proc~hvs_ascii_open hvs_ascii_open proc~hvs_ascii_init->proc~hvs_ascii_open proc~hvs_ascii_write_header hvs_ascii_write_header proc~hvs_ascii_init->proc~hvs_ascii_write_header proc~tem_abort tem_abort proc~hvs_ascii_init->proc~tem_abort proc~hvs_asciispatial_init->proc~hvs_ascii_write_header proc~hvs_asciispatial_init->proc~tem_abort proc~hvs_vtk_init->proc~tem_abort proc~tem_coordofid tem_CoordOfId proc~tem_baryofid->proc~tem_coordofid proc~tem_elemsizelevel tem_ElemSizeLevel proc~tem_baryofid->proc~tem_elemsizelevel interface~append~34 append proc~tem_calc_vrtx_coord->interface~append~34 proc~qsort_vrtx qsort_vrtx proc~tem_calc_vrtx_coord->proc~qsort_vrtx proc~tem_calc_vrtx_coord_noqval tem_calc_vrtx_coord_noqval proc~tem_calc_vrtx_coord->proc~tem_calc_vrtx_coord_noqval proc~tem_calc_vrtxof_qval tem_calc_vrtxOf_qVal proc~tem_calc_vrtx_coord->proc~tem_calc_vrtxof_qval proc~tem_calc_vrtx_coord->proc~tem_coordofid proc~tem_idofcoord tem_IdOfCoord proc~tem_calc_vrtx_coord->proc~tem_idofcoord proc~tem_init_vrtx_prop tem_init_vrtx_prop proc~tem_calc_vrtx_coord->proc~tem_init_vrtx_prop proc~tem_invertrealrkarray tem_invertRealRkArray proc~tem_calc_vrtx_coord->proc~tem_invertrealrkarray proc~tem_treeidfrom_subtree tem_treeIDfrom_subTree proc~tem_calc_vrtx_coord->proc~tem_treeidfrom_subtree proc~tem_unify_vrtx tem_unify_vrtx proc~tem_calc_vrtx_coord->proc~tem_unify_vrtx interface~append~26 append proc~tem_create_varmap->interface~append~26 interface~init~24 init proc~tem_create_varmap->interface~init~24 interface~positionofval~5 positionofval proc~tem_create_varmap->interface~positionofval~5 interface~truncate~18 truncate proc~tem_create_varmap->interface~truncate~18 proc~dump_treelmesh dump_treelmesh proc~tem_dump_subtree->proc~dump_treelmesh proc~newunit newunit proc~tem_init_restart->proc~newunit proc~tem_init_restart_alloc tem_init_restart_alloc proc~tem_init_restart->proc~tem_init_restart_alloc proc~tem_init_restart_create_types tem_init_restart_create_types proc~tem_init_restart->proc~tem_init_restart_create_types proc~tem_restart_gettotalchunks tem_restart_getTotalChunks proc~tem_init_restart->proc~tem_restart_gettotalchunks

Called by

proc~~hvs_output_init~~CalledByGraph proc~hvs_output_init hvs_output_init proc~tem_init_tracker tem_init_tracker proc~tem_init_tracker->proc~hvs_output_init

Source Code

  subroutine hvs_output_init(out_file, out_config, tree, varsys, subtree,      &
    &                        varPos, basename, timeControl, nDofs, globProc,   &
    &                        solver, geometry, solSpec_unit)
    ! --------------------------------------------------------------------------!
    !> Output file settings
    !! It must be intent inout since ascii%reduction and trasient%reduction
    !! are loaded in tem_load_trackingHeader
    type(hvs_output_file_type), intent(inout) :: out_file

    !> The output configuration settings to use.
    type(hvs_output_config_type), intent(in) :: out_config

    !> Mesh of the data to visualize.
    type(treelmesh_type), intent(in) :: tree

    !> Description of the available variable system to get the given varnames
    !! from.
    type(tem_varSys_type), intent(in) :: varsys

    !> Optional restriction of the elements to output.
    type(tem_subtree_type), optional, intent(in) :: subtree

    !> List of variable positions that should be written in the output.
    !!
    !! If this is not provided, all variables from the varsys will be written
    !! to the vtk file.
    integer, optional, intent(in) :: varPos(:)

    !> An extension to the output basename.
    !!
    !! The filename will be constructed by tracking%header%prefix//
    !! tracking%header%label
    character(len=*), intent(in) :: basename

    !> output timeControl
    type(tem_timeControl_type), optional, intent(in) :: timeControl

    !> The number of dofs for each scalar variable of the equation system
    integer, intent(in), optional :: nDofs

    !> Global communicator type for global rank information
    type(tem_comm_env_type ), intent(in) :: globProc

    !> Global solver information
    type(tem_solveHead_type ),intent(in) :: solver

    !> shape defined for this ascii output
    type(tem_shape_type), optional, intent(in) :: geometry(:)

    !> Solver specific unit for restart header
    integer, optional, intent(in) :: solSpec_unit
    ! ----------------------------------------------------------------------!
    integer :: iVar, iElem
    integer(kind=long_k) :: glob_nElems, glob_nPoints
    integer :: nElems
    integer :: nPoints
    integer(kind=long_k) :: tTreeID
    ! local varMap for restart init
    type(tem_varMap_type) :: varMap
    ! ----------------------------------------------------------------------!
    ! Copy visualization kind
    out_file%vis_kind = out_config%vis_kind

    out_file%useGetPoint = out_config%useGetPoint

    ! copy basename
    out_file%basename = trim(basename)

    ! nDofs is valid only for get_element
    if (out_file%useGetPoint) then
      out_file%nDofs = 1
    else
      if (present(nDofs)) then
        ! out_config%nDofs is set to -1 if unspecied
        ! in the config file. In this case all the dof's
        ! should be dumped
        if (out_config%nDofs < 0) then
          out_file%nDofs = nDofs
        else
          ! Otherwise the number of dofs dumped should
          ! be what's specified in the config
          out_file%nDofs = out_config%nDofs
        end if
      else
        out_file%nDofs = 1
      end if
    end if

    ! Gather global nElems, local nElems and communicator environment
    if ( present(subTree) ) then
      if (out_file%useGetPoint) then
        nPoints = subTree%nPoints
        glob_nPoints = subTree%glob_nPoints
      else
        nPoints = subTree%nElems
        glob_nPoints = subTree%global%nElems
      end if

      nElems = subTree%nElems
      glob_nElems = subTree%global%nElems
      ! set output communicator
      out_file%proc%comm      = subTree%global%comm
      out_file%proc%rank      = subTree%global%myPart
      out_file%proc%comm_size = subTree%global%nParts
      out_file%proc%root      = 0
    else
      nElems = tree%nElems
      glob_nElems = tree%global%nElems

      ! @todo KM: use nDofs to convert nElems to nPoints
      nPoints = tree%nElems
      glob_nPoints = tree%global%nElems
      ! set output communicator
      out_file%proc = globProc
    end if

    if (allocated(out_file%varpos)) deallocate(out_file%varpos)

    if (present(varPos)) then

      out_file%nVars = size(varPos)
      allocate(out_file%varpos(out_file%nVars))
      out_file%varpos = varpos

    else

      out_file%nVars = varsys%varname%nVals
      allocate(out_file%varpos(out_file%nVars))
      do iVar=1,out_file%nVars
        out_file%varpos(iVar) = iVar
      end do

    end if

    ! ! Init transient reduction
    ! if (out_file%isTransientReduce) then
    !   ! initialize transient reductions
    !   call tem_transient_reduction_init( me     = out_file%transientReduce,    &
    !     &                                nElems = nElems,                      &
    !     &                                varSys = varSys,                      &
    !     &                                varPos = out_file%varPos,             &
    !     &                                nDofs  = out_file%nDofs,              &
    !     &                                time   = timeControl%min              )
    ! end if

    select case(out_file%vis_kind)
    case(hvs_AsciiTransient)
      call hvs_ascii_init( ascii        = out_file%ascii,       &
        &                  varSys       = varSys,               &
        &                  varPos       = out_file%varPos,      &
        &                  basename     = trim(basename),       &
        &                  globProc     = globProc,             &
        &                  nDofs        = out_file%nDofs,       &
        &                  outproc      = out_file%proc,        &
        &                  nElems       = nElems,               &
        &                  glob_nElems  = glob_nElems,          &
        &                  timeControl  = timeControl,          &
        &                  solver       = solver,               &
        &                  useGetPoint  = out_file%useGetPoint, &
        &                  nPoints      = nPoints,              &
        &                  glob_nPoints = glob_nPoints,         &
        &                  geometry     = geometry              )
    case(hvs_AsciiSpatial)
      ! Store barycenter to dump at every time step
      if ( present(subTree) ) then

        if (out_file%useGetPoint) then
          allocate( out_file%bary( nPoints, 3 ) )
          out_file%bary = subTree%points
        else
          allocate( out_file%bary( nElems, 3 ) )
          do iElem = 1, nElems
            tTreeID = tree%treeID( subTree%map2global(iElem) )
            out_file%bary(iElem, :) = tem_BaryOfId(tree, tTreeID)
          end do
        end if

      else

        allocate( out_file%bary( nElems, 3 ) )
        do iElem = 1, nElems
          tTreeID = tree%treeID( iElem )
          out_file%bary(iElem, :) = tem_BaryOfId(tree, tTreeID)
        end do

      end if

      call hvs_asciiSpatial_init( asciiSpatial = out_file%asciiSpatial, &
        &                         varSys       = varSys,                &
        &                         varPos       = out_file%varPos,       &
        &                         basename     = trim(basename),        &
        &                         globProc     = globProc,              &
        &                         outproc      = out_file%proc,         &
        &                         nDofs        = out_file%nDofs,        &
        &                         nElems       = nElems,                &
        &                         glob_nElems  = glob_nElems,           &
        &                         useGetPoint  = out_file%useGetPoint,  &
        &                         nPoints      = nPoints,               &
        &                         glob_nPoints = glob_nPoints,          &
        &                         timeControl  = timeControl,           &
        &                         solver       = solver,                &
        &                         geometry     = geometry               )
    case(hvs_Internal)
      ! -----------------------------------------------------------------------
      ! Initialize restart header, communicator and chunk info
      ! -----------------------------------------------------------------------
      out_file%restart%controller%writePrefix =  trim(basename) // '_'
      out_file%restart%controller%writeRestart = .true.

      ! this restart object is not meant to read data!
      out_file%restart%controller%readRestart = .false.

      ! create varMap for restart
      call tem_create_varMap(varName = varSys%varName%val(out_file%varPos), &
        &                    varSys  = varSys,                              &
        &                    varMap  = varMap                               )

      ! init the restart typed file format
      ! should be called when the first time the mesh is dumped
      call tem_init_restart( me           = out_file%restart, &
        &                    solver       = solver,           &
        ! &                    varSys       = varsys,           &
        &                    varMap       = varMap,           &
        &                    tree         = tree,             &
        &                    subTree      = subTree,          &
        &                    solSpec_unit = solSpec_unit,     &
        &                    nDofs_write  = out_file%nDofs    )

      ! Dump tree if output is harvester format and shape is not global
      ! i.e subTree is present
      if (present(subTree)) then
        call tem_dump_subTree( subTree, tree )
      end if
    case(hvs_VTK)
      ! Calculate vertex for vtk output
      call tem_calc_vrtx_coord( tree    = tree,          &
        &                       vrtx    = out_file%vrtx, &
        &                       subtree = subtree        )

      call hvs_vtk_init( vtk_file   = out_file%vtk,   &
        &                vtk_config = out_config%vtk, &
        &                basename   = trim(basename), &
        &                proc       = out_file%proc   )
    end select

  end subroutine hvs_output_init