append_element Subroutine

private subroutine append_element(me, tID, property, eType, pntTID, sourceProc, nNeighIDs, haloNesting, needsUpdate, stencilElements, pos, wasAdded)

append an element with its treeID, property, element type, position in Tree, position in boundary_ID, number of neighbors, procID

Arguments

Type IntentOptional Attributes Name
type(tem_element_type), intent(inout) :: me

element object

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

element treeID

integer(kind=long_k), intent(in), optional :: property

property associated with the treeID

integer, intent(in), optional :: eType

element type

integer, intent(in), optional :: pntTID

count of this type pointer of the treeID

integer, intent(in), optional :: sourceProc

the procID which is adding the element

integer, intent(in), optional :: nNeighIDs

number of neighbors

integer, intent(in), optional :: haloNesting

nesting level for haloElems

logical, intent(in), optional :: needsUpdate
type(tem_stencilElement_type), intent(in), optional :: stencilElements(:)
integer, intent(out) :: pos

position of treeID

logical, intent(out), optional :: wasAdded

Calls

proc~~append_element~~CallsGraph proc~append_element append_element interface~append~11 append proc~append_element->interface~append~11 interface~init~24 init proc~append_element->interface~init~24 proc~tem_etypeisvalid tem_eTypeIsValid proc~append_element->proc~tem_etypeisvalid proc~append_ga_dynlong append_ga_dynlong interface~append~11->proc~append_ga_dynlong proc~append_ga_dynlong_vec append_ga_dynlong_vec interface~append~11->proc~append_ga_dynlong_vec proc~init_ga2d_real init_ga2d_real interface~init~24->proc~init_ga2d_real interface~expand~9 expand proc~append_ga_dynlong->interface~expand~9 proc~append_ga_dynlong_vec->interface~expand~9 proc~expand_ga_dynlong expand_ga_dynlong interface~expand~9->proc~expand_ga_dynlong

Called by

proc~~append_element~~CalledByGraph proc~append_element append_element interface~append~34 append interface~append~34->proc~append_element

Source Code

  subroutine append_element( me, tID, property, eType, pntTID, &
    &                        sourceProc, nNeighIDs, haloNesting, needsUpdate,  &
    &                        stencilElements, pos, wasAdded )
    ! ---------------------------------------------------------------------------
    !> element object
    type( tem_element_type ), intent(inout)     :: me
    !> element treeID
    integer(kind=long_k), intent(in)            :: tID
    !> position of treeID
    integer, intent(out)                        :: pos
    !> property associated with the treeID
    integer(kind=long_k), intent(in), optional  :: property
    !> element type
    integer, intent(in), optional               :: eType
    !> count of this type
    ! integer, intent(inout)                      :: nElems
    !> pointer of the treeID
    integer, intent(in), optional               :: pntTID
    !> nesting level for haloElems
    integer, intent(in), optional               :: haloNesting
    !> the procID which is adding the element
    integer, intent(in), optional               :: sourceProc
    !>
    logical, intent(in), optional               :: needsUpdate
    !> number of neighbors
    integer, intent(in), optional               :: nNeighIDs
    !>
    logical, intent(out),optional               :: wasAdded
    !>
    type(tem_stencilElement_type), intent(in), optional :: stencilElements(:)
    ! ---------------------------------------------------------------------------
    integer :: iElem
    integer :: neighIDsize
    logical :: wasAdded_loc
    type(grw_stencilElementArray_type) :: stencilElementArray
    type(dyn_longArray_type) :: tneighID
    ! ---------------------------------------------------------------------------
    call append( me = me%tID, val = tID, pos = pos, wasAdded = wasAdded_loc )
    if( wasAdded_loc ) then
      ! was not in list before, but added. Add all further handed in contents.
      if( present( property )) then
        call append( me = me%property, val = property )
      else
        call append( me = me%property, val = 0_long_k )
      end if

      if( present( eType )) then
        if ( tem_eTypeIsValid( eType ) ) then
          call append( me = me%eType, val = eType )
          me%nElems( eType ) = me%nElems( eType ) + 1
        else
          write(*,"(A,I0)") 'Found eType is NOT valid!', &
            &               ', TreeID: ', tID, &
            &               ',  eType: ', eType
        end if
      else
        call append( me = me%eType, val = eT_undefined)
      end if

      if( present( pntTID )) then
        call append( me = me%pntTID, val = pntTID )
      else
        call append( me = me%pntTID, val = -1 )
      end if

      if( present( sourceProc )) then
        call append( me = me%sourceProc, val = sourceProc )
      else
        call append( me = me%sourceProc, val = -1 )
      end if

      if( present( haloNesting )) then
        call append( me = me%haloNesting, val = haloNesting )
      else
        call append( me = me%haloNesting, val = 1 )
      end if

      if( present( needsUpdate )) then
        call append( me = me%needsUpdate, val = needsUpdate )
      else
        call append( me = me%needsUpdate, val = .false. )
      end if

      call init( me = stencilElementArray, length = 1 )
      call append( me = me%stencil, val = stencilElementArray )
      if( present( stencilElements )) then
        do iElem = 1, size( stencilElements )
          if( stencilElements(iElem)%QQN > 0 )                         &
            &           call append( me  = me%stencil%val( pos ), &
            &                        val = stencilElements( iElem ))
        end do
      end if

      if( present( nNeighIDs )) then
        neighIDsize = max( 0, nNeighIDs )
      else
        neighIDsize = 1
      end if
      ! add empty dynamic array of length neighIDsize for the neighbors
      call init( me = tNeighID, length = neighIDsize )
      call append( me = me%neighID, val = tNeighID )

    end if ! was added to tID list

    if( present( wasAdded )) then
      wasAdded = wasAdded_loc
    end if

  end subroutine append_element