generate_treelm_elements Subroutine

private subroutine generate_treelm_elements(me, origin, length, elementcount, myPart, nParts, comm, predefined, bclabel)

Generate a predefined line with a given number of elements

This serves as an simple grid generation for performance or scaling analysis without being obliged to use Seeder. You have to specify the generic grid parameters in the lua file instead of the mesh folder

mesh = { predefined='line', -- or: 'line_bounded'
         origin = {0.,0.,0.},
         length = 10.,
         elementcount = 6 }

You have to specify the shape 'line', a bounding box origin, its length and the number of elements, which results in different amount elements in the grid.\n The result of this routine is mainly the treeID list with the additional lists for saving the properties. The generated line will be a line of elementcount elements along the X-Axis with periodicity in all directions.

It is also possible to generate a mesh with boundary conditions in the X direction (west and east), by using the predefined 'line_bounded'. In this case these two boundary conditions need to be provided in the solver configuration.

Arguments

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

Mesh to generate

real(kind=rk), intent(in) :: origin(3)

Corner of the cube

real(kind=rk), intent(in) :: length

Length of cube

integer, intent(in) :: elementcount

Number of elements in the line

integer, intent(in) :: myPart

Partition of the caller (starts with 0)

integer, intent(in) :: nParts

Number of partitions

integer, intent(in) :: comm

communicator to be used

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

Label describing the internal mesh.

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

Label describing the boundary conditions to set for this mesh.


Calls

proc~~generate_treelm_elements~~CallsGraph proc~generate_treelm_elements generate_treelm_elements proc~tem_firstidatlevel tem_FirstIdAtLevel proc~generate_treelm_elements->proc~tem_firstidatlevel proc~tem_idofcoord tem_IdOfCoord proc~generate_treelm_elements->proc~tem_idofcoord

Called by

proc~~generate_treelm_elements~~CalledByGraph proc~generate_treelm_elements generate_treelm_elements proc~tem_load_internal tem_load_internal proc~tem_load_internal->proc~generate_treelm_elements proc~load_tem load_tem proc~load_tem->proc~tem_load_internal proc~tem_restart_readheader tem_restart_readHeader proc~tem_restart_readheader->proc~load_tem proc~tem_load_restart tem_load_restart proc~tem_load_restart->proc~tem_restart_readheader

Contents


Source Code

  subroutine generate_treelm_elements( me, origin, length, elementcount, &
    &                                  myPart, nParts, comm, predefined, &
    &                                  bclabel )
    ! -------------------------------------------------------------------- !
    !> Mesh to generate
    type(treelmesh_type), intent(out) :: me
    !> Corner of the cube
    real(kind=rk), intent(in) :: origin(3)
    !> Length of cube
    real(kind=rk), intent(in) :: length
    !> Number of elements in the line
    integer, intent(in) :: elementcount
    !> Partition of the caller (starts with 0)
    integer, intent(in) :: myPart
    !> Number of partitions
    integer, intent(in) :: nParts
    !> communicator to be used
    integer, intent(in) :: comm
    !> Label describing the internal mesh.
    character(len=*), intent(in) :: predefined
    !> Label describing the boundary conditions to set for this mesh.
    character(len=*), intent(in) :: bclabel
    ! -------------------------------------------------------------------- !
    integer :: level
    integer(kind=long_k) :: firstID, lastID
    integer(kind=long_k) :: share
    integer :: remainder
    integer :: iPart, iElem
    integer :: coord(4)
    integer :: lastcoord
    integer :: xbound_pad
    ! -------------------------------------------------------------------- !

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

    ! Face definitions make the first and last face coincide.
    ! To allow boundary definitions on both sides, we need to make sure, there
    ! is at least one additional element.
    if (predefined == 'line_bounded') then
      xbound_pad = 1
    else
      xbound_pad = 0
    end if

    ! Find an appropriate level of at least 1.
    level = max( ceiling(log(real(elementcount+xbound_pad,kind=rk)) &
      &                  / log(2.0_rk)),            1               )

    me%global%origin = origin
    me%global%BoundingCubeLength = length*(real(2**level, kind=rk) &
      &                                    /real(elementcount, kind=rk))
    me%global%minLevel = level
    me%global%maxLevel = level
    me%global%label = 'Generic_Line'
    me%global%predefined = predefined
    write(me%global%comment,'(a15,i7,a16,i2,a1)')                             &
      &               'Generated with ', nParts, ' Parts and ', elementcount, &
      &               ' elements.'
    me%global%dirname = './'

    ! Boundary property to define periodic boundary
    me%global%nProperties = 1
    if (associated(me%global%property)) deallocate(me%global%property)
    if (associated(me%property)) deallocate(me%property)
    allocate(me%global%Property(me%global%nProperties))
    allocate(me%Property(me%global%nProperties))

    allocate(me%Part_First(nParts))
    allocate(me%Part_Last(nParts))

    ! Compute the treeIDs of the mesh:
    firstID = tem_firstIdAtLevel(level)
    lastcoord = elementcount - 1
    lastID = tem_IdOfCoord(coord = [lastcoord, 0, 0, level], offset = firstID )

    ! Total number of elements in this mesh
    me%global%nElems = elementcount

    share = me%global%nElems / int(nParts, kind=long_k)
    remainder = int(mod(me%global%nElems, int(nParts, kind=long_k)))

    ! The first partition starts always with the firstID
    me%Part_First(1) = firstID

    ! Up to remainder partitions have share + 1 elements
    coord = 0
    coord(4) = level
    do iPart=2,remainder+1
      coord(1) =  coord(1) + int(share)
      me%Part_Last(iPart-1) = tem_idofcoord(coord, offset = firstID)
      coord(1) = coord(1) + 1
      me%Part_First(iPart) = tem_idofcoord(coord, offset = firstID)
    end do

    ! The remaining elements get exactly the share elements:
    do iPart=remainder+2,nParts
      coord(1) = coord(1) + int(share) - 1
      me%Part_Last(iPart-1) = tem_idofcoord(coord, offset = firstID)
      coord(1) = coord(1) + 1
      me%Part_First(iPart) = tem_idofcoord(coord, offset = firstID)
    end do

    ! The last partition ends always with the lastID
    me%Part_Last(nParts) = lastID

    ! Local data:
    if (myPart < remainder) then
      me%nElems = int(share+1)
      me%elemOffset = int(myPart, kind=long_k) * (share+1_long_k)
    else
      me%nElems = int(share)
      me%elemOffset = (int(myPart, kind=long_k) * share) &
        &           + int(remainder, kind=long_k)
    end if
    ! All elements have (periodic) boundaries
    me%Property(1)%nElems = me%nElems
    me%Property(1)%offset = me%elemOffset
    allocate(me%Property(1)%ElemID(me%Property(1)%nElems))
    ! Please note, that the tem_bc_prop_module will set boundary conditions
    ! based on this label accordingly!
    me%global%Property(1)%label = trim(bclabel)
    me%global%Property(1)%bitpos = prp_hasBnd
    me%global%Property(1)%nElems = me%Property(1)%nElems

    allocate(me%treeID(me%nElems))
    allocate(me%ElemPropertyBits(me%nElems))

    ! Only has Boundary Property:
    me%ElemPropertyBits = ibset(0_long_k, prp_hasBnd)

    ! Filling the treeIDs:
    do iElem = 1, me%nElems
      me%Property(1)%ElemID(iElem) = iElem
      ! We can only have 2**20 elements per dimension, so in this case where
      ! we create a line, we won't exceed the integer limit. Thus we safely can
      ! cast the long integer elemOffset to a normal integer.
      coord(1) = int(me%elemOffset) + iElem - 1
      me%treeID(iElem) = tem_idofcoord(coord, offset=firstID)
    end do

  end subroutine generate_treelm_elements