gather_property Subroutine

public subroutine gather_property(Property, Header, BitField, comm)

Gather the information on a property from the bit fields of all elements

Arguments

Type IntentOptional Attributes Name
type(tem_property_type), intent(out) :: Property

Property to gather

type(tem_prophead_type), intent(in) :: Header

Header for this property

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

The BitField for the properties of all local elements

integer, intent(in) :: comm

Communicator to act on


Calls

proc~~gather_property~~CallsGraph proc~gather_property gather_property mpi_exscan mpi_exscan proc~gather_property->mpi_exscan

Called by

proc~~gather_property~~CalledByGraph proc~gather_property gather_property proc~tem_copypropertybitsfromtree tem_copyPropertyBitsFromTree proc~tem_copypropertybitsfromtree->proc~gather_property proc~load_treelmesh load_treelmesh proc~load_treelmesh->proc~gather_property proc~tem_create_tree_from_sub tem_create_tree_from_sub proc~tem_create_tree_from_sub->proc~gather_property proc~exchange_elements exchange_elements proc~exchange_elements->proc~gather_property interface~tem_copypropertybits tem_copyPropertyBits interface~tem_copypropertybits->proc~tem_copypropertybitsfromtree proc~load_tem load_tem proc~load_tem->proc~load_treelmesh proc~load_tem->proc~exchange_elements proc~tem_create_subtree_of tem_create_subTree_of proc~tem_create_subtree_of->interface~tem_copypropertybits proc~tem_restart_readheader tem_restart_readHeader proc~tem_restart_readheader->proc~load_tem proc~tem_init_convergence tem_init_convergence proc~tem_init_convergence->proc~tem_create_subtree_of proc~tem_write_debugmesh tem_write_debugMesh proc~tem_write_debugmesh->proc~tem_create_subtree_of proc~tem_load_restart tem_load_restart proc~tem_load_restart->proc~tem_restart_readheader proc~tem_init_tracker_subtree tem_init_tracker_subTree proc~tem_init_tracker_subtree->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


Source Code

  subroutine gather_property(Property, Header, BitField, comm)
    ! ---------------------------------------------------------------------- !
    !> Property to gather
    type(tem_property_type), intent(out) :: Property
    !> Header for this property
    type(tem_prophead_type), intent(in) :: Header
    !> The BitField for the properties of all local elements
    integer(kind=long_k), intent(in) :: BitField(:)
    !> Communicator to act on
    integer, intent(in) :: comm
    ! ---------------------------------------------------------------------- !
    integer :: nElems
    integer :: iElem, PropElem
    integer(kind=long_k) :: myElems
    integer :: iError
    ! ---------------------------------------------------------------------- !

    nElems = size(BitField)

    ! First count the number of local elements with the given property.
    Property%nElems = count(btest(BitField, Header%BitPos))
    myElems = Property%nElems

    Property%Offset = 0
    ! Calculate offset on each process, by summing the number of elements
    ! on all lower ranks.
    call MPI_Exscan( myElems, Property%Offset, 1, MPI_INTEGER8, MPI_SUM, &
      &              comm, iError)

    ! Allocate an array to store the link from the list of elements with this
    ! property to the list of all elements.
    ! (Property%ElemID -> tree%treeID)
    allocate(Property%ElemID(Property%nElems))

    PropElem = 0
    do iElem=1,nElems
      ! Run over all elements.
      if (btest(BitField(iElem), Header%BitPos)) then
        ! If the element has the property, increase the counter for elements
        ! with this property and store this position for later lookups.
        PropElem = PropElem + 1
        Property%ElemID(PropElem) = iElem
      end if
    end do

  end subroutine gather_property