gen_treelm_line_global Subroutine

private subroutine gen_treelm_line_global(me, conf, thandle, myPart, nParts, comm, predefined)

Generate the simple single level mesh of a line in the full cube.

Arguments

Type IntentOptional Attributes Name
type(tem_global_type), intent(out) :: me

Structure to load the mesh to

type(flu_State) :: conf

Directory containing the mesh informations

integer, intent(in) :: thandle

Handle for the table to read the description of the mesh from.

integer, intent(in) :: myPart

Partition to use on the calling process (= MPI Rank in comm)

integer, intent(in) :: nParts

Number of partitions, the mesh is partitioned into (= Number of MPI processes in comm).

integer, intent(in) :: comm

MPI Communicator to use

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

Calls

proc~~gen_treelm_line_global~~CallsGraph proc~gen_treelm_line_global gen_treelm_line_global proc~aot_get_val~2 aot_get_val proc~gen_treelm_line_global->proc~aot_get_val~2 proc~tem_abort tem_abort proc~gen_treelm_line_global->proc~tem_abort mpi_abort mpi_abort proc~tem_abort->mpi_abort

Called by

proc~~gen_treelm_line_global~~CalledByGraph proc~gen_treelm_line_global gen_treelm_line_global proc~tem_global_mesh_internal tem_global_mesh_internal proc~tem_global_mesh_internal->proc~gen_treelm_line_global proc~tem_global_mesh_read tem_global_mesh_read proc~tem_global_mesh_read->proc~tem_global_mesh_internal

Contents


Source Code

  subroutine gen_treelm_line_global( me, conf, thandle, myPart, nParts, comm, &
    &                                predefined )
    ! -------------------------------------------------------------------- !
    !> Structure to load the mesh to
    type(tem_global_type), intent(out) :: me
    !> Directory containing the mesh informations
    type(flu_State) :: conf
    !> Handle for the table to read the description
    !! of the mesh from.
    integer, intent(in) :: thandle
    !> Partition to use on the calling process (= MPI Rank in comm)
    integer, intent(in) :: myPart
    !> Number of partitions, the mesh is partitioned into (= Number of MPI
    !! processes in comm).
    integer, intent(in) :: nParts
    !> MPI Communicator to use
    integer, intent(in) :: comm
    character(len=*), intent(in) :: predefined
    ! -------------------------------------------------------------------- !
    integer :: iError
    integer :: orig_err(3)
    integer :: level
    integer :: elementcount
    ! -------------------------------------------------------------------- !

    write(logUnit(1),*) 'Creating HEADER for a line mesh'

    me%nParts = nParts
    me%myPart = myPart
    me%comm = comm

    ! Get the origin of the cube:
    call aot_get_val( L       = conf,                    &
      &               thandle = thandle,                 &
      &               key     = 'origin',                &
      &               val     = me%origin,               &
      &               ErrCode = orig_err,                &
      &               default = [0.0_rk, 0.0_rk, 0.0_rk] )

    ! Get the length of the cube:
    call aot_get_val( L       = conf,                  &
      &               thandle = thandle,               &
      &               val     = me%BoundingCubeLength, &
      &               ErrCode = iError,                &
      &               key     = 'length',              &
      &               default = 1.0_rk                 )

    ! Get the refinement level:
    call aot_get_val( L       = conf,              &
      &               thandle = thandle,           &
      &               val     = level,             &
      &               ErrCode = iError,            &
      &               key     = 'refinementLevel', &
      &               default = -1                 )

    ! Get the element count:
    call aot_get_val( L       = conf,            &
      &               thandle = thandle,         &
      &               val     = elementcount,    &
      &               ErrCode = iError,          &
      &               key     = 'element_count', &
      &               default = -1               )

    me%label = 'Generic_Line'
    me%predefined = trim(predefined)

    if (predefined == 'line_bounded') then
      ! Need a padding of at least 1 element, to allow boundary definitions
      ! at both ends in Ateles.
      me%minlevel = max( ceiling(log(real(elementcount+1,kind=rk)) &
        &                        / log(2.0_rk)),                 1 )
      me%BoundingCubeLength = (me%BoundingCubeLength * 2**me%minlevel) &
        &                    / elementcount
    else if (elementcount > 1) then
      me%minlevel = ceiling(log(real(elementcount,kind=rk))/log(2.0_rk))
    else if (level > 0) then
      me%minlevel = level
    else if ((level == 0) .or. (elementcount == 1)) then
      me%BoundingCubeLength = me%BoundingCubeLength*2
      me%minlevel = 1
      me%label = 'Generic_Single'
      me%predefined = 'single'
      ! Reset elementcount, to avoid overwriting of the settings later on.
      elementcount = -1
    else
      write(logunit(1),*) 'For a line you need to state either refinementLevel'
      write(logunit(1),*) 'or element_count. None of them found!'
      write(logunit(1),*) 'STOPPING'
      call tem_abort()
    end if

    if (elementcount > 1) then
      me%BoundingCubeLength = (me%BoundingCubeLength * 2**me%minlevel) &
        &                    / elementcount
    end if

    me%maxLevel = me%minLevel

    write(me%comment,'(a15,i7,a16,i2,a1)') &
      &   'Generated with ', nParts, ' parts on Level ', me%minlevel, '.'
    me%dirname = './'

    ! Only boundary property in this mesh.
    me%nProperties = 1
    if (associated(me%Property)) deallocate(me%property)
    allocate(me%Property(me%nProperties))

  end subroutine gen_treelm_line_global