tem_create_subTree_of Subroutine

public subroutine tem_create_subTree_of(inTree, subTree, inShape, levelDesc, bc_prop, storePnts, stencil, prefix)

Create a subTree from a given inTree and an array of shapes.

All elements to the inTree%treeID are collected into the subTree%map2global array and a sub-communicator with participating processes is created. Additionally how many and which elements exist on my local process and are requested from the shapes is identified.

Arguments

Type IntentOptional Attributes Name
type(treelmesh_type), intent(in) :: inTree

Global mesh from which the elements are identified and then stored to

type(tem_subTree_type), intent(out) :: subTree

new mesh

type(tem_shape_type), intent(in) :: inShape(:)

shape objects on which to work

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

optional level descriptor needed for local shape

type(tem_BC_prop_type), intent(in), optional :: bc_prop

bc property which is used to identify elements belong to certain BCs

logical, intent(in), optional :: storePnts

To store space points in subTree

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

stencil used to find bcID on certain links

character(len=*), intent(in), optional :: prefix

prefix for the subTree


Source Code

  subroutine tem_create_subTree_of( inTree, subTree, inShape, levelDesc,       &
    &                               bc_prop, storePnts, stencil, prefix )
    ! ---------------------------------------------------------------------------
    !> Global mesh from which the elements are identified and then stored to
    type(treelmesh_type), intent(in)                     :: inTree
    !> new mesh
    type(tem_subTree_type), intent(out)                  :: subTree
    !> shape objects on which to work
    type(tem_shape_type),intent(in)                      :: inShape(:)
    !> optional level descriptor needed for local shape
    type(tem_levelDesc_type ), optional, intent(in)      :: levelDesc(:)
    !> bc property which is used to identify elements belong to certain BCs
    type( tem_bc_prop_type ), optional, intent(in)       :: bc_prop
    !> To store space points in subTree
    logical, optional, intent(in)                        :: storePnts
    !> stencil used to find bcID on certain links
    type( tem_stencilHeader_type ), optional, intent(in) :: stencil
    !> prefix for the subTree
    character(len=*), optional, intent(in)               :: prefix
    ! ---------------------------------------------------------------------------
    ! local growing array for the map to the global tree
    type(dyn_intArray_type) :: local_map2global
    type(tem_grwPoints_type) :: local_grwPnts
    integer, allocatable :: map2globalTemp(:)
    integer(kind=long_k), allocatable :: tmp_treeID(:)
    integer :: iShape, iElem
    ! mpi variables for parallel writing of the log-wise trees
    integer :: color, iError
    ! if the local rank has part of the tracking object
    logical :: participateInMesh, globalParticipateInMesh
    ! if any element be found for this iShape
    integer :: local_countElems( globalMaxLevels )
    integer :: local_countPnts
    logical :: local_storePnts
    ! --------------------------------------------------------------------------

    if (present(storePnts)) then
      local_storePnts = storePnts
    else
      local_storePnts = .false.
    end if

    subTree%useGlobalMesh = any(inShape(:)%shapeID == tem_global_shape)
    subTree%useLocalMesh = any(inShape(:)%shapeID == tem_local_shape)
    subTree%created_new_comm = .false.

    if (subTree%useGlobalMesh) then
      write(logUnit(5),*) 'Subtree encompasses all fluid elements'
    else
      if (subTree%useLocalMesh) then
        if (present(levelDesc)) then
          write(logUnit(5),*) 'Subtree encompasses all elements of local domain'
        else
          write(logUnit(1),*) 'ERROR:levelDesc is not passed to ' &
            &                 // 'tem_create_subTree_of'
          write(logUnit(1),*) '      levelDesc is required to create ' &
            &                 // 'subTree for tem_local_shape!'
          call tem_abort()
        end if
      end if
    end if

    ! Prepare output structure
    ! init here the sub-tree mesh
    subTree%global = inTree%global
    ! initialize the number of elements on this partition with 0
    subTree%nElems = 0
    subTree%global%nElems = 0
    if ( present(prefix) ) subTree%global%dirname = trim(prefix)

    check_shapes: if (.not. (subTree%useGlobalMesh .or. subTree%useLocalMesh) ) then
      local_countElems = 0
      local_countPnts  = 0
      call init( local_map2global, length = 128)

      do iShape = 1, size( inShape )

        call tem_shape2subTree(me         = inShape(iShape),  &
          &                    iShape     = iShape,           &
          &                    inTree     = inTree,           &
          &                    storePnts  = local_storePnts,  &
          &                    map2global = local_map2global, &
          &                    grwPnts    = local_grwPnts,    &
          &                    countElems = local_countElems, &
          &                    countPnts  = local_countPnts,  &
          &                    bcIDs      = subTree%bc_ID,    &
          &                    bc_prop    = bc_prop,          &
          &                    stencil    = stencil           )

      end do ! iShape

      participateInMesh = ( sum(local_countElems) > 0 .or. local_countPnts > 0 )

      ! abort if no elements are found for the given shape
      call MPI_ALLREDUCE( participateInMesh, globalParticipateInMesh, 1,   &
        &                 MPI_LOGICAL, MPI_LOR, inTree%global%comm, iError )
      if (.not. globalParticipateInMesh) then
        write(logUnit(1),*) 'Error: No elements found for ' &
          &                 // trim(subTree%global%dirname) // ' in the mesh'
        call tem_abort()
      end if

    else check_shapes
      ! For local or global shapes we always participate
      participateInMesh = .true.
    end if check_shapes

    if ( .not. subTree%useGlobalMesh ) then
      subTree%global%predefined = ''
    end if

    ! Exchange information about the mesh
    ! Now create a new communicator with ranks that own parts of the sub-mesh
    ! This is done with the color
    if (participateInMesh) then
      color = 1
    else
      ! Not participating, set color to undefined
      color = MPI_UNDEFINED
    end if

    ! Input rank as a key to keep sorting as in global communicator
    ! reorder process ranks into tracking communicator
    if (subTree%useLocalMesh) then
      subTree%global%comm = MPI_COMM_SELF
      call tem_shape_initLocal(levelDesc, tmp_treeID)
    else
      call mpi_comm_split( inTree%global%comm, color, inTree%global%myPart, &
        &                  subTree%global%comm, iError                      )
      if (iError .ne. mpi_success) then
        write(logUnit(1),*)' There was an error splitting the communicator'
        write(logUnit(1),*)' for the tracking subset. Aborting...'
        call tem_abort()
      end if
      subTree%created_new_comm = .true.
    end if

    if (participateInMesh) then
      call mpi_comm_size( subTree%global%comm, subTree%global%nParts, iError )
      call mpi_comm_rank( subTree%global%comm, subTree%global%myPart, iError )

      if (.not. subTree%useGlobalmesh) then

        if (subTree%useLocalMesh) then
          call tem_subTree_from( me     = subTree,   &
            &                    treeID = tmp_treeID )
          ! update the property list of the newly defined tree according to the
          ! the local shape (simply copy the bits)
          call tem_copyPropertyBits( levelDesc = levelDesc, subTree = subTree )
        else ! NOT useLocalMesh
          ! Copy the created dynamic local_tIDlist to a long integer array
          allocate( map2globalTemp(local_map2global%nVals) )
          ! Assign list of links to the temporary list, first sorting
          do iElem = 1, local_map2global%nVals
            map2globalTemp(iElem) = local_map2global                       &
              &                       %val( local_map2global%sorted(iElem) )
          end do

          call tem_subTree_from( me         = subTree,        &
            &                    map2global = map2globalTemp, &
            &                    grwPnts    = local_grwPnts   )
          call destroy( me = local_grwPnts )

          ! copy property bits from the global tree
          call tem_copyPropertyBits( inTree = inTree, subTree = subTree )
         deallocate( map2globalTemp )
        end if ! useLocalMesh with level desc

        ! Calculate the effective extents of the tracking sub-tree bounding box
        call tem_setEffBoundingBox( subTree, inTree )

      else ! useGlobalMesh

        ! assign the global properties to the subTree
        subTree%nElems = inTree%nElems
        subTree%global%nElems = inTree%global%nElems

      end if ! not global mesh?

    else ! NOT participating in subtree
      subTree%nElems = 0
      subTree%global%nElems = 0
      allocate( subTree%map2global(0) )
      subTree%nPoints = 0
      subTree%glob_nPoints = 0_long_k
      allocate( subTree%points(0,0) )
    end if ! Participate in subtree?

    write(logUnit(5),"(A,I0)") 'Found corresponding nElems: ', &
      &                        subTree%global%nElems

    call destroy( me = local_map2global )
    call tem_horizontalSpacer( fUnit= logUnit(5) )

  end subroutine tem_create_subTree_of