tem_cano_storePntsInSubTree Subroutine

public subroutine tem_cano_storePntsInSubTree(me, inTree, map2global, countPoints, grwPnts)

Generate points using segments on canoND and add those points to a growing array of points if a point is found in subTree

Arguments

Type IntentOptional Attributes Name
type(tem_canonicalND_type), intent(in) :: me(:)

canonicalND objects on which to work

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

Global tree

type(dyn_intarray_type), intent(in) :: map2global

growing array for the map2global

integer, intent(inout) :: countPoints

How many points there will be

type(tem_grwPoints_type), intent(inout) :: grwPnts

growing array to store tracking points


Calls

proc~~tem_cano_storepntsinsubtree~~CallsGraph proc~tem_cano_storepntsinsubtree tem_cano_storePntsInSubTree proc~tem_idofcoord tem_IdOfCoord proc~tem_cano_storepntsinsubtree->proc~tem_idofcoord proc~tem_firstidatlevel tem_FirstIdAtLevel proc~tem_cano_storepntsinsubtree->proc~tem_firstidatlevel interface~append~9 append proc~tem_cano_storepntsinsubtree->interface~append~9 proc~tem_coordofid tem_CoordOfId proc~tem_cano_storepntsinsubtree->proc~tem_coordofid proc~tem_posofid tem_PosOfId proc~tem_cano_storepntsinsubtree->proc~tem_posofid proc~tem_coordofreal tem_CoordOfReal proc~tem_cano_storepntsinsubtree->proc~tem_coordofreal proc~append_da_label append_da_label interface~append~9->proc~append_da_label proc~append_da_veclabel append_da_veclabel interface~append~9->proc~append_da_veclabel proc~tem_levelof tem_LevelOf proc~tem_coordofid->proc~tem_levelof proc~tem_pathcomparison tem_PathComparison proc~tem_posofid->proc~tem_pathcomparison proc~tem_pathof tem_PathOf proc~tem_posofid->proc~tem_pathof interface~sortedposofval~5 sortedposofval proc~append_da_label->interface~sortedposofval~5 interface~expand~9 expand proc~append_da_label->interface~expand~9 proc~append_da_veclabel->interface~expand~9 proc~sortposofval_label sortposofval_label interface~sortedposofval~5->proc~sortposofval_label proc~expand_da_label expand_da_label interface~expand~9->proc~expand_da_label

Called by

proc~~tem_cano_storepntsinsubtree~~CalledByGraph proc~tem_cano_storepntsinsubtree tem_cano_storePntsInSubTree proc~tem_shape_subtreefromgeominters tem_shape_subTreeFromGeomInters proc~tem_shape_subtreefromgeominters->proc~tem_cano_storepntsinsubtree proc~tem_shape2subtree tem_shape2subTree proc~tem_shape2subtree->proc~tem_shape_subtreefromgeominters proc~tem_create_subtree_of tem_create_subTree_of proc~tem_create_subtree_of->proc~tem_shape2subtree proc~tem_init_convergence tem_init_convergence proc~tem_init_convergence->proc~tem_create_subtree_of proc~tem_init_tracker_subtree tem_init_tracker_subTree proc~tem_init_tracker_subtree->proc~tem_create_subtree_of proc~tem_write_debugmesh tem_write_debugMesh proc~tem_write_debugmesh->proc~tem_create_subtree_of proc~tem_create_subtree_of_st_funlist tem_create_subTree_of_st_funList proc~tem_create_subtree_of_st_funlist->proc~tem_create_subtree_of

Contents


Source Code

  subroutine tem_cano_storePntsInSubTree( me, inTree, map2global, countPoints, &
    &                                     grwPnts )
    ! --------------------------------------------------------------------------
    !> canonicalND objects on which to work
    type(tem_canonicalND_type ),intent(in) :: me(:)
    !> Global tree
    type(treelmesh_type), intent(in) :: inTree
    !> How many points there will be
    integer, intent(inout) :: countPoints
    !> growing array for the map2global
    type(dyn_intArray_type), intent(in) :: map2global
    !> growing array to store tracking points
    type(tem_grwPoints_type), intent(inout) :: grwPnts
    ! --------------------------------------------------------------------------
    integer :: nElems, nPoints, maxLevel, elemPos, neighPos, coordOfId(4)
    integer :: iCano, iPnt, iQQN
    real(kind=rk) :: coord(3), offset_a, offset_b, offset_c
    real(kind=rk) :: unit_vec_a(3),unit_vec_b(3), unit_vec_c(3)
    integer(kind=long_k) :: treeID, tOffset, neighID
    integer(kind=long_k), allocatable :: subTreeID(:)
    ! --------------------------------------------------------------------------
    maxLevel = inTree%global%maxLevel
    ! Append the physical points to the growing array of points
    nElems = map2global%nVals
    allocate(subTreeID(nElems))
    subTreeID = inTree%treeID(map2global%val(map2global%sorted(1:nElems)))
    do iCano = 1, size(me)
      ! total number of elements
      nPoints = me(iCano)%segments(1) &
        &     * me(iCano)%segments(2) &
        &     * me(iCano)%segments(3)

      unit_vec_a =  me(iCano)%vec(:,1)                      &
        &        / real( max(me(iCano)%segments(1)-1,1), rk )
      unit_vec_b =  me(iCano)%vec(:,2)                      &
        &        / real( max(me(iCano)%segments(2)-1,1), rk )
      unit_vec_c =  me(iCano)%vec(:,3)                      &
        &        / real( max(me(iCano)%segments(3)-1,1), rk )

      ! Generate points and append only the points available in tree
      do iPnt = 1, nPoints
        offset_a = real(mod((iPnt-1),me(iCano)%segments(1)), kind=rk)
        offset_b = real(mod((iPnt-1)/me(iCano)%segments(1), &
          &                 me(iCano)%segments(2)), kind=rk)
        offset_c = real(mod((iPnt-1)/(me(iCano)%segments(1)  &
          &                          *me(iCano)%segments(2)), &
          &                 me(iCano)%segments(3)), kind=rk)

        coord = me(iCano)%origin + offset_a * unit_vec_a &
          &                      + offset_b * unit_vec_b &
          &                      + offset_c * unit_vec_c

        ! Get the treeID on the highest level
        treeID = tem_IdOfCoord( tem_CoordOfReal(inTree, coord(1:3), maxLevel) )
        ! get position of the treeID in subTree
        elemPos = tem_PosOfId( treeID, subTreeID )

        neighPos = 0
        if (elemPos <= 0) then
          ! Point must be outside fluid domain, its neighbor must be in subTreeID
          ! since it was added in tem_cano_initSubTree
          coordOfId = tem_CoordOfId( treeID )
          tOffset = tem_FirstIdAtLevel( coordOfId(4) )
          directionLoop: do iQQN = 1, qQQQ
            neighID = tem_IdOfCoord(                          &
              &         [ coordOfId(1) + qOffset( iQQN, 1 ),  &
              &           coordOfId(2) + qOffset( iQQN, 2 ),  &
              &           coordOfId(3) + qOffset( iQQN, 3 ),  &
              &           coordOfId(4) ], tOffset)
            neighPos = tem_PosOfId( neighID, subTreeID)
            if (neighPos > 0) exit directionLoop
          end do directionLoop
        end if

        if( elempos > 0 .or. neighPos > 0 ) then
          ! append the physical points to the growing array of points
          call append( me  = grwpnts, &
            &          val = coord    )

          countPoints = countPoints + 1
        end if
      end do !iPoint
    end do !iCano
    deallocate(subTreeID)

  end subroutine tem_cano_storePntsInSubTree