tem_build_faceRecvBuffers Subroutine

private subroutine tem_build_faceRecvBuffers(levelDesc, faces, buf)

process will receive information for (before it can make the compute step).

Arguments

Type IntentOptional Attributes Name
type(tem_levelDesc_type), intent(in) :: levelDesc

Dimension-by-dimension level descriptor for the current level and direction.

type(tem_face_descriptor_type), intent(inout) :: faces

The communication pattern you want use for the buffer. The created face descriptor.

type(tem_communication_type), intent(out) :: buf(2)

The created receive buffer. Size is two, due to left and right limes of the face values. To access it use tem_left and tem_right.


Calls

proc~~tem_build_facerecvbuffers~~CallsGraph proc~tem_build_facerecvbuffers tem_build_faceRecvBuffers proc~tem_isrecvface tem_isRecvFace proc~tem_build_facerecvbuffers->proc~tem_isrecvface interface~positionofval~5 positionofval proc~tem_build_facerecvbuffers->interface~positionofval~5 interface~append~23 append proc~tem_build_facerecvbuffers->interface~append~23 proc~tem_abort tem_abort proc~tem_build_facerecvbuffers->proc~tem_abort interface~init~22 init proc~tem_build_facerecvbuffers->interface~init~22 proc~posofval_label posofval_label interface~positionofval~5->proc~posofval_label proc~append_arrayga2d_real append_arrayga2d_real interface~append~23->proc~append_arrayga2d_real proc~append_singlega2d_real append_singlega2d_real interface~append~23->proc~append_singlega2d_real mpi_abort mpi_abort proc~tem_abort->mpi_abort proc~init_ga2d_real init_ga2d_real interface~init~22->proc~init_ga2d_real interface~sortedposofval~5 sortedposofval proc~posofval_label->interface~sortedposofval~5 interface~expand~22 expand proc~append_arrayga2d_real->interface~expand~22 proc~append_singlega2d_real->interface~expand~22 proc~sortposofval_label sortposofval_label interface~sortedposofval~5->proc~sortposofval_label proc~expand_ga2d_real expand_ga2d_real interface~expand~22->proc~expand_ga2d_real

Called by

proc~~tem_build_facerecvbuffers~~CalledByGraph proc~tem_build_facerecvbuffers tem_build_faceRecvBuffers proc~tem_build_facebuffers tem_build_faceBuffers proc~tem_build_facebuffers->proc~tem_build_facerecvbuffers proc~tem_build_face_info tem_build_face_info proc~tem_build_face_info->proc~tem_build_facebuffers

Contents


Source Code

  subroutine tem_build_faceRecvBuffers( levelDesc, faces, buf )
    ! -------------------------------------------------------------------------
    !> Dimension-by-dimension level descriptor for the current level and
    !! direction.
    type(tem_levelDesc_type), intent(in) :: levelDesc
    !> The communication pattern you want use for the buffer.
    ! type(tem_commpattern_type), intent(in) :: commPattern
    !> The created face descriptor.
    type(tem_face_descriptor_type),intent(inout)  :: faces
    !> The created receive buffer. Size is two, due to left and right limes of
    !! the face values. To access it use tem_left and tem_right.
    type(tem_communication_type), intent(out) :: buf(2)
    ! --------------------------------------------------------------------------
    integer :: iFace, iProc, iSide, elemPos, faceSide, tIdPos, rank, rankPos,  &
      &        elemAddPos, faceIndex
    logical :: wasAdded
    integer(kind=long_k) :: elemId
    ! The elements ids I will receive data for. We have to differentiate the
    ! left and right face of a face here.
    type(dyn_longArray_type) :: elemIds(2)
    ! The elements positions I will receive data for. We have to differentiate
    ! the left and right face of a face here.
    type(grw_intArray_type) :: elemPositions(2)
    ! The source ranks.
    type(dyn_intArray_type) :: srcRank(2)
    ! The position of the source ranks.
    type(grw_intArray_type) :: srcRankPos(2)
    ! --------------------------------------------------------------------------

    ! Init our growing arrays.
    call init( me = elemIds(1) , length = 16 )
    call init( me = elemIds(2) , length = 16 )
    call init( me = elemPositions(1) , length = 16 )
    call init( me = elemPositions(2) , length = 16 )
    call init( me = srcRankPos(1) , length = 16)
    call init( me = srcRankPos(2) , length = 16)
    call init( me = srcRank(1) , length = 16 )
    call init( me = srcRank(2) , length = 16 )

    ! Iterate over all the faces and count the communicate faces.
    do iFace = 1, faces%faceList%faceId%nVals

      ! Check whether we will receive info of one of the adjacent elements
      ! of this face.
      faceSide = tem_isRecvFace(iFace, faces)
      if (faceSide /= 0) then

        ! Check for which adjacent element (left or right) the current rank
        ! will receive information about and count it.
        if (faceSide == tem_left) then
          elemPos = faces%faceList%leftElemPos%val(iFace)
          elemId = faces%faceList%faceId%val(iFace)
          ! If we receive information about the left element, we receive
          ! information about it's right face!
          faceSide = tem_right
        else
          elemPos = faces%faceList%rightElemPos%val(iFace)
          elemId = faces%faceList%rightElemId%val(iFace)
          ! If we receive information about the right element, we receive
          ! information about it's left face!
          faceSide = tem_left
        end if

        ! Get the source rank. Therefore we have a look at the level
        ! descriptor of the current spatial direction and level.
        tIdPos = PositionOfVal( me = levelDesc%elem%tId, val = elemId )
        if (tIdPos <= 0) then
          write(*,*) 'ERROR in tem_build_faceRecvBuffers: not able to '//  &
            &        'identify source rank for a certain face, stopping ...'
          call tem_abort()
        else
          rank = levelDesc%elem%sourceProc%val(tIdPos)
        end if

        ! Store element position and source proc in a dynamic array.
        call append( me       = elemIds(faceSide), &
          &          val      = elemId,            &
          &          pos      = elemAddPos,        &
          &          wasAdded = wasAdded           )
        if (wasAdded) then
          call append( me = elemPositions(faceSide), val = elemPos )
          call append( me = srcRank(faceSide), val = rank, pos = rankPos )
          call append( me = srcRankPos(faceSide), val = rankPos )
        end if

      end if
    end do

    ! Now, we build the buffer for the faces (left and right values).
    do iSide = 1, 2
      ! Init the datastructures in the buffer
      buf(iSide)%nProcs = srcRank(iSide)%nVals
      allocate(buf(iSide)%proc( srcRank(iSide)%nVals ))
      allocate(buf(iSide)%nElemsProc( srcRank(iSide)%nVals ))
      allocate(buf(iSide)%elemPos( srcRank(iSide)%nVals ))
      do iProc = 1, buf(iSide)%nProcs
        call init( me = buf(iSide)%elemPos(iProc), length = 16 )
      end do

      ! Set the positions of the elements I will receive.
      do iFace = 1, elemPositions(iSide)%nVals
        faceIndex = elemIds(iSide)%sorted(iFace)
        elemPos = elemPositions(iSide)%val(faceIndex)
        rankPos = srcRankPos(iSide)%val(faceIndex)
        call append( me = buf(iSide)%elemPos(rankPos), val = elemPos )
      end do

      ! Count the number of elements we recv from each proc.
      do iProc = 1, buf(iSide)%nProcs
        buf(iSide)%proc(iProc) = srcRank(iSide)%val(iProc) - 1
        buf(iSide)%nElemsProc(iProc) = buf(iSide)%elemPos(iProc)%nVals
      end do
    end do

  end subroutine tem_build_faceRecvBuffers