tem_construction_module Module

This module creates the required treeID lists, from which then the state vector and the neighbor information can be constructed.

Also, the structures for the ghost and halo elements are created. For the ghost cells, this means establishing the dependencies. The source element positions for each ghost is stored. For the halo elements, the information from where to get the element information is stored in the mpi buffers. See the example for stencil construction in the Documentation.

Calculate nearest neighbors. if its fluid then identify its treeID from tem_IdOfCoord If neighbor is boundary then identify the boundary ID from boundary_ID list


Uses

Used by

  • module~~tem_construction_module~~UsedByGraph module~tem_construction_module tem_construction_module module~tem_interpolation_module tem_interpolation_module module~tem_interpolation_module->module~tem_construction_module module~tem_surfacedata_module tem_surfaceData_module module~tem_surfacedata_module->module~tem_construction_module module~tem_face_module tem_face_module module~tem_face_module->module~tem_construction_module module~tem_facedata_module tem_faceData_module module~tem_face_module->module~tem_facedata_module module~tem_facedata_module->module~tem_construction_module module~tem_adaptation_module tem_adaptation_module module~tem_adaptation_module->module~tem_construction_module module~tem_subtree_module tem_subTree_module module~tem_subtree_module->module~tem_construction_module program~tem_construction_test tem_construction_test program~tem_construction_test->module~tem_construction_module program~tem_varsys_stfunvar_test tem_varSys_stfunVar_test program~tem_varsys_stfunvar_test->module~tem_subtree_module module~tem_comptefacerules_module tem_compteFaceRules_module module~tem_comptefacerules_module->module~tem_facedata_module program~tem_varsys_test tem_varSys_test program~tem_varsys_test->module~tem_subtree_module module~tem_spacetime_fun_module tem_spacetime_fun_module module~tem_spacetime_fun_module->module~tem_subtree_module module~hvs_output_module hvs_output_module module~hvs_output_module->module~tem_subtree_module program~tem_face_test tem_face_test program~tem_face_test->module~tem_face_module program~tem_face_test->module~tem_facedata_module program~tem_face_test~2 tem_face_test program~tem_face_test~2->module~tem_face_module program~tem_face_test~2->module~tem_facedata_module module~tem_tracking_module tem_tracking_module module~tem_tracking_module->module~tem_subtree_module program~tem_face_test~3 tem_face_test program~tem_face_test~3->module~tem_face_module program~tem_face_test~3->module~tem_facedata_module program~tem_varsys_opvar_test tem_varSys_opVar_test program~tem_varsys_opvar_test->module~tem_subtree_module module~tem_convergence_module tem_convergence_module module~tem_convergence_module->module~tem_subtree_module

Contents


Variables

TypeVisibilityAttributesNameInitial
integer, private, save:: nestingLimit

limit for searching neighbors * For acoustic scaling (2 coarser elements required) set to 1 * For diffusive scaling (4 coarser elements required) set to 3

integer(kind=long_k), private, allocatable, save:: hash(:)

Hash to quickly identify if an element was reconstructed before. If so, it is part of the hash this array contains treeIDs of recently accessed elements allocated and used in tem_init_elemLevels also used in identify_elements this array contains positions in element_type of recently accessed elements

integer, private, allocatable, save:: hash_elemPos(:)
integer(kind=long_k), private :: nHashes

Entries in the hash


Derived Types

type, public :: tem_levelNeighbor_type

identification parameters for different lists includes the direct neighbors of each tree ID

Components

TypeVisibilityAttributesNameInitial
integer, private, allocatable:: nghElems(:,:)

array of the neighbors in the resulting totalList. Use this one in the solver! size: stencil%QQN, nElems(to treat with stencil)

type, public :: depSource_type

Type to specify the dependencies of ghost and halo cells. E.g.: used to specify which cells have to be known to be able to interpolate a ghost/halo cell

Read more…

Components

TypeVisibilityAttributesNameInitial
integer, private :: dependencyLevel =-1

the source level, from where the current ghost element gets the source elements for the interpolation

type(grw_intarray_type), private :: elem

position of the source elements in the totalList

type(grw_intarray_type), private :: elemBuffer

position of the source elements in the all source elements list i.e. levelDesc( targetLevel )%sourceFromCoarser

real(kind=rk), private, allocatable:: weight(:)

Interpolation weight for each source element specified above

real(kind=rk), private :: coord(3)
integer, private :: childNum
integer, private :: posInIntpMatLSF

Pointer to array of interpolation matrix calculated from available sources

type, public :: tem_levelDesc_type

detailed information of a complete level of elements including all treeIDs, properties and neighbors as well as informations about ghost/halo cells and its dependencies for interpolation/reconstruction

Components

TypeVisibilityAttributesNameInitial
type(tem_element_type), private :: elem
type(dyn_longarray_type), private :: require

This list includes treeIDs for which additionally neighbors have to be identified constructed in tem_init_elemLevels used in routine: identify_additionalNeigh

type(tem_haloList_type), private :: haloList
integer(kind=long_k), private, allocatable:: total(:)

list of treeIDs for this level. Consists of ordered treeIDs of first fluid, then ghost, then halo elements. total: Array size: nElems ( = nElems_fluid+nElems_ghostFromCoarser + nElems_ghostFromFiner+nElems_halo )

Read more…
real(kind=rk), private, allocatable:: baryOfTotal(:,:)

Barycenter for all treeID in total list size: nElems in total, 3

integer, private, allocatable:: totalPnt(:)

pointer to elem%tID list set in routine: identify_lists used in tem_build_listHorizontalDep, assemble_lists Array size: nElems

Read more…
integer(kind=long_k), private, allocatable:: property(:)

list of property bits for this level. the same order as total list array size: nElems

Read more…
integer, private, allocatable:: pntTID(:)

pointer from the levelDescriptor to the original treeID list ( only for fluids ) array size: nElems_fluid

Read more…
type(tem_levelNeighbor_type), private, allocatable:: neigh(:)

neighbor relations for all fluid elements. Dimension: number of stencils We store the positions of the neighbor elements inside the total-list. If a fluid element does not have a neighbor in a direction (e.g. because of a boundary in that direction), we store the boundary ID as negative to indicate, that it is not a regular neighbor.

type(depSource_type), private, allocatable:: depFromFiner(:)

Dependencies for ghost elements To reconstruct all the data you should iterate over this list and reconstruct the ghost elements with source element information from these data types data. Up = to coarser, down = to finer array size: nElems_ghostFromFiner

type(depSource_type), private, allocatable:: depFromCoarser(:)

In treelm, only the parent is stored. If more sources are needed, it has to be extend in the solver. array size: nElems_ghostFromCoarser

type(dyn_intarray_type), private :: sourceFromFiner

Store all the source elements for the ghostFromFiner Their positions in total list on source level

type(dyn_intarray_type), private :: sourceFromCoarser

Store all the source elements that needed for all ghostFromCoarser

real(kind=rk), private, allocatable:: intpBufFromFiner(:,:)

Buffer storing intermediate values of the source elements for the interpolation

Read more…
real(kind=rk), private, allocatable:: intpBufFromCoarser(:,:)
type(grw_intarray_type), private, allocatable:: intpFromCoarser(:)

List to store interpolation from coarser ghost elements How to use: do indElem = 1, intpFromCoarser%nVals posInDepFromCoarser = intpFromCoarser%val( indElem ) posInTotal = depFromCoarser%elem%val( posInDepFromCoarser ) end do Size of intpFromCoarser depends on interpolation order which intern depends on available number of source elements

type(grw_intarray_type), private :: intpFromFiner

List to store interpolation from finer ghost elements

type(dyn_intarray_type), private :: bc_elemBuffer

pointing to the position of boundary elements in the levelDescriptor total list

integer, private :: offset(2,eT_minRelevant:eT_maxRelevant) =0

Offsets in the assembled lists for fluid (1), ghostFromCoarser(2), ghostFromFiner(3) and halo(4) elements for the assembled lists, i.e the totalList, invSorted, ... gets the values (0, nElems_fluid, nElems_fluid+nElems_ghostCoarser, nElems_fluid+nElems_ghostCoarser+nELems_ghostFiner)

type(tem_communication_type), private :: sendBuffer

Local Fluids required by remote processes

type(tem_communication_type), private :: sendBufferFromCoarser

Local ghostFromCoarser required by remote processes

type(tem_communication_type), private :: sendBufferFromFiner

Local ghostFromFiner required by remote processes

type(tem_communication_type), private :: recvBuffer

My halos which are fluids on remote processes

type(tem_communication_type), private :: recvBufferFromCoarser

My halos which are ghostFromCoarser on remote processes

type(tem_communication_type), private :: recvBufferFromFiner

My halos which are ghostFromFiner on remote processes

integer, private :: nElems

total number of elements


Functions

public function tem_treeIDinTotal(tID, levelDesc, eType) result(elemPos)

Returns the absolute position in the total list of a given treeID opposed to PosOfId, where the relative position in one of the separate lists is returned. Herefore, total list has to be created beforehand.

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: tID

the element you are looking for

type(tem_levelDesc_type), intent(in) :: levelDesc

the descriptor you use for searching

integer, intent(in), optional :: eType

element type

Return Value integer

return position of tID in levelDesc%total list

private elemental function stencilToChild(stencilCoord) result(childCoord)

Convert a non-zero stencil direction {-1,1} to child coordinate {0,1}

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: stencilCoord

Return Value integer

private function childToStencil(childCoord) result(stencilCoord)

Convert a child coordinate {0,1} to non-zero stencil direction {-1,1}

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: childCoord

Return Value integer


Subroutines

public subroutine tem_find_allElements(tree, levelDesc, levelPointer, computeStencil, commPattern, cleanup, reqNesting, proc)

call this routine from your geometry initialization routine in the solver create all the necessary level-wise objects, such as element lists, dependencies

Read more…

Arguments

TypeIntentOptionalAttributesName
type(treelmesh_type), intent(inout) :: tree

the global tree

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)

the level descriptor to be filled

integer, intent(out), allocatable:: levelPointer(:)

Pointer from treeIDlist entry to level-wise fluid part of total list

type(tem_stencilHeader_type) :: computeStencil(:)

array of all stencils used in the simulation

type(tem_commPattern_type), intent(in) :: commPattern

the communication pattern used

logical, intent(in), optional :: cleanup

cleanup arrays afterwards?

integer, intent(in), optional :: reqNesting

nesting level

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

Process description to use.

public subroutine tem_init_elemLevels(me, boundary, tree, stencils)

subroutine to find neighbours of cells

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(out), allocatable:: me(:)

neighbor list containing all the neighbours for the cells given in treeidsubset. Result of this routine

type(tem_BC_prop_type), intent(in) :: boundary

boundaries for the elements with bnd property set

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

subset of tree ids for which the neighbours will be specified

type(tem_stencilHeader_type), intent(in) :: stencils(:)

the given stencil

public subroutine tem_find_depProc(depProc, nDepProcs, tree, elemPath, PathFirst, PathLast)

Find the partitions holding data on a given path

Read more…

Arguments

TypeIntentOptionalAttributesName
integer, intent(out) :: depProc

List of partitions

integer, intent(out) :: nDepProcs

Number of partitions

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

tree information

type(tem_path_type), intent(in) :: elemPath

Element to look up

type(tem_path_type), intent(in) :: PathFirst(:)

Left partition bounds

type(tem_path_type), intent(in) :: PathLast(:)

Right partition bounds

public subroutine tem_find_depProc_globSearch(depProc, nDepProcs, elemPath, p_lb, p_ub, PathFirst, PathLast)

Find the remote partitions holding data on a given path

Read more…

Arguments

TypeIntentOptionalAttributesName
integer, intent(out) :: depProc

List of partitions

integer, intent(out) :: nDepProcs

Number of partitions

type(tem_path_type), intent(in) :: elemPath

Element to look up

integer, intent(in) :: p_lb

Left interval bound to search in

integer, intent(in) :: p_ub

Right interval bound to search in

type(tem_path_type), intent(in) :: PathFirst(:)

Left partition bounds

type(tem_path_type), intent(in) :: PathLast(:)

Right partition bounds

public recursive subroutine identify_stencilNeigh(iElem, iLevel, iStencil, tree, pathFirst, pathLast, levelDesc, proc, stencil, nesting)

Invoke the identify_elements for each neighbor of the stencil and store the positions of the encountered elements

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: iElem

element position in levelDesc to identify

integer, intent(in) :: iLevel

element level

integer, intent(in) :: iStencil

stencil within the element to act on

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

tree information

type(tem_path_type), intent(in) :: pathFirst(:)

first treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

last treeID path in every process

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)

the level descriptor to be filled

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

process

type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

integer, intent(in) :: nesting

nesting level

public subroutine tem_cleanupDependencyArrays(levelDesc)

deallocate all dispensable dynamic data structures and arrays

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: levelDesc(:)

the level descriptor

public subroutine tem_cleanup_arrays(levelDesc)

deallocate the stencil treeID neighbor arrays for each element This routine can only be called after build_horizontalDependencies

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: levelDesc(:)

the level descriptor

public subroutine tem_build_verticalDependencies(levelDesc, minlevel, maxLevel)

Build the vertical dependencies of ghost elements

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: levelDesc(minlevel:maxLevel)

the level descriptor

integer, intent(in) :: minlevel

Level range

integer, intent(in) :: maxLevel

Level range

public subroutine tem_build_horizontalDependencies(iStencil, levelDesc, tree, computeStencil)

Building neighor array

Read more…

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: iStencil

Index of your neighbor list??

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)

Level descriptor for each level of your mesh (starting from minimum level).

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

Tree representation of your mesh.

type(tem_stencilHeader_type), intent(in) :: computeStencil

The stencil you build the horizontal dependencies for.

public subroutine tem_debug_HorizontalDependencies(iStencil, levelDesc, tree, computeStencil)

Building neighor array

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: iStencil

Index of your neighbor list.

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)

Level descriptor for each level of your mesh (starting from min level).

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

Tree representation of your mesh.

type(tem_stencilHeader_type) :: computeStencil

The stencil you build the horizontal dependencies for.

public subroutine tem_elemList_dump(me, nUnit, string, stencil, compact)

write out the complete list of elements of a given level

Arguments

TypeIntentOptionalAttributesName
type(tem_element_type), intent(in) :: me
integer, intent(in) :: nUnit
character(len=*), intent(in) :: string
logical, intent(in), optional :: stencil
logical, intent(in), optional :: compact

public subroutine tem_dumpTreeIDlists(minlevel, maxLevel, LD)

output all level-wise treeIDs in a clean way

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: minlevel

minimum level of the global tree

integer, intent(in) :: maxLevel

minimum level of the global tree

type(tem_levelDesc_type), intent(in) :: LD(minlevel:maxLevel)

level descriptor

public subroutine tem_updateTree_properties(levelDesc, tree)

This routine updates the property bits in the tree with those of the level descriptor.

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(in) :: levelDesc

level descriptor

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

global tree

public subroutine depSource_append(me, sourceList, mySources, n)

Arguments

TypeIntentOptionalAttributesName
type(depSource_type) :: me
type(dyn_intarray_type) :: sourceList
integer, intent(in) :: mySources(n)
integer, intent(in) :: n

private subroutine build_levelElements(levelDesc, tree, proc, stencil, pathFirst, pathLast)

Assemble the fluid list and identify neighbor relations start with building up the ghost and halo element collection as well

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)

the level descriptor to be filled

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

the global tree

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

Process description to use.

type(tem_stencilHeader_type) :: stencil

array of all stencils used in the simulation

type(tem_path_type), intent(in) :: pathFirst(:)

first and last treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

first and last treeID path in every process

private recursive subroutine identify_elements(treeID, tree, pathFirst, pathLast, levelDesc, elemPos, proc, Stencil, nesting, skip_add_additionalGhost)

Check, on which partition a given element is located add required elements to corresponding lists: if remote, add to halo if ghost, add to resp. ghost list

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: treeID

treeID to identify

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

tree information

type(tem_path_type), intent(in) :: pathFirst(:)

first treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

last treeID path in every process

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)

the level descriptor to be filled

integer, intent(out) :: elemPos

nTreeID element position in the levelDesc % elem list

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

Process description to use.

type(tem_stencilHeader_type), intent(in) :: Stencil

current stencil definition

integer, intent(in) :: nesting

nesting level

logical, intent(in), optional :: skip_add_additionalGhost

logical, optional, if true no ghosts are added

private recursive subroutine create_allParentNeighbors(targetID, level, stencil, tree, levelDesc, pathFirst, pathLast, proc)

create all the neighbors of an element's parent

Read more…

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: targetID

requested element position (child element) in LevelDesc elem list

integer, intent(in) :: level

requested element level

type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

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

tree information

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minLevel:)

the level descriptor to be filled

type(tem_path_type), intent(in) :: pathFirst(:)

first treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

last treeID path in every process

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

process

private subroutine single_process_element(targetID, levelDesc, tree, proc, iProc, minLevel, elemPos, stencil, nesting, updated, skip_add_additionalGhost)

Determine the location (which process) of a requested element, which was identified to be located on one single process (can be local or remote) If it is located on a remote process: add to halo list local process: identify if ghost or fluid

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: targetID

neighboring treeID

type(tem_levelDesc_type), intent(inout) :: levelDesc(minLevel:)

the level descriptor to be filled

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

tree information

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

Process description to use.

integer, intent(in) :: iProc

Process on which targetID is located

integer, intent(in) :: minLevel

minimum level fluid element in the tree

integer, intent(out) :: elemPos

targetID element position in the levelDesc % elem list

type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

integer, intent(in) :: nesting

nesting level

logical, intent(out) :: updated

was the element updated in this call?

logical, intent(in), optional :: skip_add_additionalGhost

logical, optional, if true no ghosts are added

private subroutine identify_local_element(targetID, levelDesc, tree, minLevel, elemPos, nesting, updated, stencil, skip_add_additionalGhost)

Determine if the target element (local) targetID is fluid or ghost in the local process If fluid: do nothing, as it will be added later on anyway (or already is) ghostFromFiner (coarser than requested): add all virtual children, i.e. all levels between requested treeID and found one. ghostFromCoarser (finer than requested): not existing( localPos=0): add to halo

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: targetID

neighboring treeID

type(tem_levelDesc_type), intent(inout) :: levelDesc(minLevel:)

the level descriptor to be filled

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

tree information

integer, intent(in) :: minLevel

minimum level fluid element in the tree

integer, intent(out) :: elemPos

targetID element position in the levelDesc % elem list

integer, intent(in) :: nesting

nesting level

logical, intent(out) :: updated

was the element updated in this call?

type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

logical, intent(in), optional :: skip_add_additionalGhost

logical, optional, if true no ghosts are added

private recursive subroutine add_all_virtual_children(sourceID, sourceProperty, foundPos, elemPath, targetLevel, levelDesc, minLevel, tree, stencil, nesting, updated)

Find all the virtual children of the sourceID down to the targetLevel and add to the level-wise ghostFromCoarser list in the level descriptor

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: sourceID

source treeID (existing founded ID in tree%treeID list or children ID from recursion)

integer(kind=long_k), intent(in) :: sourceProperty

property of source element

integer, intent(in) :: foundPos

position of this sourceID in elem%tID list

type(tem_path_type), intent(in) :: elemPath

element path

integer, intent(in) :: targetLevel

level upto which virtual children must be created

type(tem_levelDesc_type), intent(inout) :: levelDesc(minLevel:)

the level descriptor to be filled

integer, intent(in) :: minLevel

minimum level in the tree

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

tree information

type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

integer, intent(in) :: nesting

nesting level

logical, intent(out) :: updated

was the element updated in this call?

private subroutine tem_find_BCs_fromCoarser(dir, childCoord, sourceLevel, sourcePos, neighID, computeStencil, levelDesc, minLevel)

Inherit the neighborhood from the sourceELem to the targetElem

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: dir
integer, intent(in) :: childCoord(4)

coordinate of virtual(ghost) child

integer, intent(in) :: sourceLevel

coarse element level

integer, intent(in) :: sourcePos

position of coarser element in original treeID list

integer(kind=long_k), intent(inout) :: neighID(:)

neighbor treeIDs of child element

type(tem_stencilHeader_type), intent(in) :: computeStencil

current stencil definition

type(tem_levelDesc_type), intent(in) :: levelDesc(minLevel:)

the level descriptor to be filled

integer, intent(in) :: minLevel

minimum level in the tree

private recursive subroutine add_ghostFromFiner(elemID, levelDesc, minLevel, tree, updated, foundPos, stencil)

Add parentID as GhostFromFiner. Then set its BC from its children. If any children do NOT exist, recursively call this routine to add them as GhostFromFiner.

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: elemID

requested treeID

type(tem_levelDesc_type), intent(inout) :: levelDesc(minLevel:)

the level descriptor to be filled

integer, intent(in) :: minLevel

minimum level fluid element in the tree

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

tree information

logical, intent(out) :: updated

was the current element updated in this call?

integer, intent(out) :: foundPos
type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

private subroutine tem_find_BCs_fromFiner(childPos, sourceLevel, targetLevel, targetPos, levelDesc, minLevel, stencil)

Inherit the neighborhood from the sourceELem to the targetElem Note that targetElem is inout, as it might have already values assigned.

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: childPos(8)

position of all childs in the levelDesc elem tID list

integer, intent(in) :: sourceLevel

level of child

integer, intent(in) :: targetLevel

level of parent

integer, intent(in) :: targetPos

added position of parent in the levelDesc elem tID list

type(tem_levelDesc_type) :: levelDesc(minLevel:)

the level descriptor to be filled

integer, intent(in) :: minLevel

minimum level in the tree

type(tem_stencilHeader_type), intent(in) :: stencil

current stencil definition

private subroutine identify_lists(me)

create the intermediate, static list totalPnt, which holds pointers to the elem%TID list, but in an ordered fashion. The order is the same as it will be in the total list later on, i.e.: fluid, ghostFC, ghostFF, halo. this four sub-lists are within sorted by their treeID. Additionally, the process-wise collections of halo elements are collected into haloList by grouping the treeIDs according to their belonging process

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: me

the level descriptor to be filled

private subroutine set_offsets(me, nFluids, nGhostFC, nGhostFF, nHalos)

Set the offsets for accessing totallist, invsorted etc. arrays for fluids, ghosts and halos

Arguments

TypeIntentOptionalAttributesName
integer, intent(out) :: me(2,eT_minRelevant:eT_maxRelevant)

element type offsets

integer, intent(in) :: nFluids
integer, intent(in) :: nGhostFC
integer, intent(in) :: nGhostFF
integer, intent(in) :: nHalos

private subroutine assemble_lists(me, minlevel, maxLevel, tree)

Create the level-wise total lists.

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: me(minlevel:maxLevel)

Level descriptor to fill

integer, intent(in) :: minlevel

Minimal level in the mesh

integer, intent(in) :: maxLevel

Minimal level in the mesh

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

tree information

private subroutine identify_additionalNeigh(tree, proc, levelDesc, pathFirst, pathLast, stencil)

identify additionally required neighbor elements run over the 'require' list of elements, which was accumulated before in init_elemLevels. The list includes neighbor elements of stencil neighbors, for stencils with the requireNeighNeigh attribute set. This is needed for example for LBM boundary stencil elements, which in turn require their compute stencil neighborhood to allow PULL operations from there

Read more…

Arguments

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

the global tree

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

Process description to use.

type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minlevel:)

the level descriptor to be filled

type(tem_path_type), intent(in) :: pathFirst(:)

first treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

last treeID path in every process

type(tem_stencilHeader_type), intent(in) :: stencil

the compute stencil, for which the additional neighbors are reconstructed

private subroutine communicate_elements(tree, proc, me, commPattern, pathFirst, pathLast, computeStencil)

exchange the requested treeIDs between all MPI processs

Read more…

Arguments

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

the global tree

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

Process description to use.

type(tem_levelDesc_type), intent(inout) :: me(tree%global%minlevel:)

the level descriptor to be filled

type(tem_commPattern_type), intent(in) :: commPattern

the communication pattern used

type(tem_path_type), intent(in) :: pathFirst(:)

first and last treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

first and last treeID path in every process

type(tem_stencilHeader_type), intent(in) :: computeStencil(:)

stencil definition

private subroutine identify_halo(haloTreeID, elemPos, haloLevel, levelDesc, tree, updated, nesting, minLevel, stencil)

Map requested halo to a position in my local fluid list or add recursively ghosts until I reach valid fluid elements return type of added element in levelPos(2) Also, non-existing elements are reported as such (levelPos(2))

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(in) :: haloTreeID

neighboring treeID

integer, intent(out) :: elemPos

type and position in list of found treeID

integer, intent(out) :: haloLevel
type(tem_levelDesc_type), intent(inout) :: levelDesc(minlevel:)
type(treelmesh_type), intent(in) :: tree
logical, intent(out) :: updated
integer, intent(in) :: nesting
integer, intent(in) :: minLevel
type(tem_stencilHeader_type), intent(in) :: stencil

private subroutine tem_build_treeHorizontalDep(iStencil, levelDesc, computeStencil, list, nElems, tree)

Update the neighor arrays depending on what is given in the element stencil

Read more…

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: iStencil

Index of your neighbor list.

type(tem_levelDesc_type), intent(inout) :: levelDesc

Level descriptor for each level of your mesh (starting from min level).

type(tem_stencilHeader_type), intent(in) :: computeStencil

The stencil you build the horizontal dependencies for.

integer, intent(in) :: list(:)

stencil elemLvl points to sorted original treeID list

integer, intent(in) :: nElems

number of elements

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

tree information

private subroutine tem_build_listHorizontalDep(iStencil, levelDesc, posInSortElem, nElems, iIndex)

Update the neighor arrays depending on what is given in the element stencil

Read more…

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: iStencil

Index of your neighbor list.

type(tem_levelDesc_type), intent(inout) :: levelDesc

Level descriptor for each level of your mesh (starting from min level).

integer, intent(in) :: posInSortElem(:)

Positions in sorted elem%tID list

integer, intent(in) :: nElems

number of elements

integer, intent(inout) :: iIndex

private subroutine communicate_nElemsToTransfer(me, proc, minLevel, maxLevel)

Communicate with all existing process the number of requested halo elements

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: me(minlevel:maxLevel)

the level descriptor to be filled

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

Process description to use.

integer, intent(in) :: minLevel

level range

integer, intent(in) :: maxLevel

level range

private subroutine request_remoteHalos(levelDesc, proc, tree, iLevel, stencil, pathFirst, pathLast)

Inverse Communication: Communicate, which elements each process needs from me.

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minlevel:)

the level descriptor to be filled

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

Process description to use.

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

the global tree

integer, intent(in) :: iLevel

current level

type(tem_stencilHeader_type), intent(in) :: stencil

stencil definition

type(tem_path_type), intent(in) :: pathFirst(:)

first and last treeID path in every process

type(tem_path_type), intent(in) :: pathLast(:)

first and last treeID path in every process

private subroutine return_haloCounts(sendbuffer, recvbuffer, comm)

Report the actually existing elements, which were requested as halos from remote

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_communication_type), intent(in) :: sendbuffer

send buffer

type(tem_communication_type), intent(inout) :: recvbuffer

recv buffer

integer, intent(in) :: comm

MPI communicator

private subroutine check_additionalComm(levelDesc, proc, doAdditional, minlevel)

Check if additional communications have to be performed

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(in) :: levelDesc(minlevel:)

level descriptor

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

Process description to use.

logical, intent(out) :: doAdditional

do addtional steps to identify neighbors of elems in require list

integer, intent(in) :: minlevel

minlevel in tree

private subroutine redefine_halos(levelDesc, sendbuffer, recvbuffer, proc, commPattern, computeStencil)

Report the actually existing elements, which were requested as halos from remote

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: levelDesc

the level descriptor of specific level

type(tem_communication_type), intent(inout) :: sendbuffer

send and receive communication buffer type

type(tem_communication_type), intent(inout) :: recvbuffer

send and receive communication buffer type

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

Process description to use.

type(tem_commPattern_type) :: commPattern

communication pattern

type(tem_stencilHeader_type) :: computeStencil(:)

array of all stencils used in the simulation

private subroutine tem_stencil_communicate(send, recv, elem, computeStencil, proc, commPattern, iStencil)

Communicate the complete stencil

Read more…

Arguments

TypeIntentOptionalAttributesName
type(tem_communication_type), intent(inout) :: send

send and recv communication buffers

type(tem_communication_type), intent(inout) :: recv

send and recv communication buffers

type(tem_element_type), intent(inout) :: elem

levelDesc element list

type(tem_stencilHeader_type), intent(in) :: computeStencil

array of all stencils used in the simulation

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

Process description to use.

type(tem_commPattern_type), intent(in) :: commPattern

communication pattern

integer, intent(in) :: iStencil

amount of values to communicate

private subroutine update_elemPosToTotalPos(levelDesc, levelPointer, tree, computeStencil)

Update the found dependencies, which were built for non-ordered lists Out of fluid, ghost and halo lists, the totalList is constructed in an ordered fashion. The element order as in the TotalList is later passed on to the solver.

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(inout) :: levelDesc(tree%global%minlevel:)

the level descriptor to be filled

integer, intent(in) :: levelPointer(:)

Pointer from original treeID list to level wise fluid list

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

the global tree

type(tem_stencilHeader_type), intent(inout) :: computeStencil(:)

array of all stencils used in the simulation

private subroutine update_buffer_elemPos(buffer, levelDesc, iError)

Update the position of the elements inside the buffers from the original tID list to the later totalList

Arguments

TypeIntentOptionalAttributesName
type(tem_communication_type), intent(inout) :: buffer

communication buffer

type(tem_levelDesc_type), intent(in) :: levelDesc

levelDesc to be used

integer, intent(out) :: iError

return encountered error

private subroutine appendGhostDependency(sourcePos, sourceLevel, tgtDep)

add here the dependency for interpolation between the levels For each target cell, there are one or more source cells. The source cell can be of type fluid, ghost or halo. We save the type to update the correct element position later on, when the lists have been assembled.

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: sourcePos

position of the source cell in total list

integer, intent(in) :: sourceLevel

level of the source ghost cell

type(depSource_type), intent(inout) :: tgtDep

dependent source elements for this target

private subroutine update_childNeighborID(neighID, childCoord, childPos, iStencilElem, elem, iStencil)

Update the link into a given direction, based on the childs neighbor relations. Define here the trumping rule to decide, which of the neighbors or boundarie is taken for the ghostFromFiner element

Arguments

TypeIntentOptionalAttributesName
integer(kind=long_k), intent(inout) :: neighID

neighID for coarser

integer, intent(in) :: childCoord(4)

child coordinates

integer, intent(in) :: childPos(8)

position of childIds in levelDesc elem tID list

integer, intent(in) :: iStencilElem

current stencil direction

type(tem_element_type), intent(in) :: elem
integer, intent(in) :: iStencil

private subroutine tem_require_dump(me, nUnit, string)

write out the complete list of elements of a given level

Arguments

TypeIntentOptionalAttributesName
type(dyn_longarray_type), intent(in) :: me
integer, intent(in) :: nUnit
character(len=*), intent(in) :: string

private subroutine tem_calc_neighbors(posInBCID, boundary_ID, stencil, x, neighIDs)

Arguments

TypeIntentOptionalAttributesName
integer, intent(in) :: posInBCID
integer(kind=long_k), intent(in) :: boundary_ID(:,:)
type(tem_stencilHeader_type), intent(in) :: stencil
integer, intent(in) :: x(4)
integer(kind=long_k), intent(out) :: neighIDs(stencil%QQN)

private subroutine tem_alloc_levelDesc(me, minLevel, maxLevel, initlen, nStencils)

Allocate level descriptor and initilize its variables

Arguments

TypeIntentOptionalAttributesName
type(tem_levelDesc_type), intent(out), allocatable:: me(:)
integer, intent(in) :: minLevel
integer, intent(in) :: maxLevel
integer, intent(in) :: initlen
integer, intent(in) :: nStencils

private subroutine tem_build_levelPointer(levelPointer, tree, levelDesc)

Arguments

TypeIntentOptionalAttributesName
integer, intent(out), allocatable:: levelPointer(:)

Pointer from original treeID list to level wise fluid list

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

the global tree

type(tem_levelDesc_type), intent(in) :: levelDesc(tree%global%minlevel:)

the level descriptor to be filled