identify_lists Subroutine

private subroutine identify_lists(me)

create the intermediate, static list totalPnt, which holds pointers to the elem%TID list, but in an ordered fashion. The order is the same as it will be in the total list later on, i.e.: fluid, ghostFC, ghostFF, halo. this four sub-lists are within sorted by their treeID. Additionally, the process-wise collections of halo elements are collected into haloList by grouping the treeIDs according to their belonging process

Arguments

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

the level descriptor to be filled


Calls

proc~~identify_lists~~CallsGraph proc~identify_lists identify_lists interface~changetype changeType proc~identify_lists->interface~changetype interface~tem_tostr tem_toStr proc~identify_lists->interface~tem_tostr proc~set_offsets set_offsets proc~identify_lists->proc~set_offsets proc~tem_abort tem_abort proc~identify_lists->proc~tem_abort proc~tem_halo_append tem_halo_append proc~identify_lists->proc~tem_halo_append proc~tem_halo_destroy tem_halo_destroy proc~identify_lists->proc~tem_halo_destroy proc~tem_halo_init tem_halo_init proc~identify_lists->proc~tem_halo_init proc~changetype_element changeType_element interface~changetype->proc~changetype_element proc~changetype_element_vec changeType_element_vec interface~changetype->proc~changetype_element_vec proc~tem_b2str tem_b2str interface~tem_tostr->proc~tem_b2str proc~tem_b2str_arr tem_b2str_arr interface~tem_tostr->proc~tem_b2str_arr proc~tem_d2str tem_d2str interface~tem_tostr->proc~tem_d2str proc~tem_d2str_arr tem_d2str_arr interface~tem_tostr->proc~tem_d2str_arr proc~tem_i2str tem_i2str interface~tem_tostr->proc~tem_i2str proc~tem_i2str_arr tem_i2str_arr interface~tem_tostr->proc~tem_i2str_arr proc~tem_l2str tem_l2str interface~tem_tostr->proc~tem_l2str proc~tem_l2str_arr tem_l2str_arr interface~tem_tostr->proc~tem_l2str_arr proc~tem_r2str tem_r2str interface~tem_tostr->proc~tem_r2str proc~tem_r2str_arr tem_r2str_arr interface~tem_tostr->proc~tem_r2str_arr mpi_abort mpi_abort proc~tem_abort->mpi_abort interface~append~11 append proc~tem_halo_append->interface~append~11 interface~destroy~12 destroy proc~tem_halo_destroy->interface~destroy~12 interface~init~11 init proc~tem_halo_init->interface~init~11 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~destroy_ga_dynlong destroy_ga_dynlong interface~destroy~12->proc~destroy_ga_dynlong proc~init_ga_dynlong init_ga_dynlong interface~init~11->proc~init_ga_dynlong proc~tem_etypeisvalid tem_eTypeIsValid proc~changetype_element->proc~tem_etypeisvalid proc~changetype_element_vec->proc~tem_etypeisvalid interface~expand~9 expand proc~append_ga_dynlong->interface~expand~9 proc~append_ga_dynlong_vec->interface~expand~9

Called by

proc~~identify_lists~~CalledByGraph proc~identify_lists identify_lists proc~communicate_elements communicate_elements proc~communicate_elements->proc~identify_lists proc~tem_find_allelements tem_find_allElements proc~tem_find_allelements->proc~identify_lists proc~tem_find_allelements->proc~communicate_elements proc~tem_create_leveldesc tem_create_levelDesc proc~tem_create_leveldesc->proc~tem_find_allelements proc~tem_dimbydim_construction tem_dimByDim_construction proc~tem_dimbydim_construction->proc~tem_create_leveldesc proc~tem_build_face_info tem_build_face_info proc~tem_build_face_info->proc~tem_dimbydim_construction

Source Code

  subroutine identify_lists( me )
    ! -------------------------------------------------------------------- !
    !> the level descriptor to be filled
    type(tem_levelDesc_type), intent(inout) :: me
    ! -------------------------------------------------------------------- !
    integer :: iElem, indElem
    integer :: iPnt( eT_minNumber:eT_maxNumber ), eType, iVal
    ! -------------------------------------------------------------------- !
    ! Destroy lists
    call tem_halo_destroy(me%haloList)
    ! init lists
    call tem_halo_init(me%haloList)

    ! --------------------------------------------------------------------------
    ! 1. count nElems
    me%nElems = sum( me%elem%nElems(eT_minRelevant:eT_maxRelevant) ) &
      &       + me%elem%nElems(et_distributedGhostFromFiner)

    call set_offsets( me       = me%offset(:,:),                               &
      &               nFluids  = me%elem%nElems( eT_fluid ),                   &
      &               nGhostFC = me%elem%nElems( eT_ghostFromCoarser ),        &
      &               nGhostFF = me%elem%nElems( eT_ghostFromFiner )           &
      &                        + me%elem%nElems(eT_distributedGhostfromFiner), &
      &               nHalos   = me%elem%nElems( eT_halo )                     )

    ! --------------------------------------------------------------------------

    if ( allocated( me%totalPnt )) deallocate( me%totalPnt )
    allocate( me%totalPnt(me%nElems) )
    me%totalPnt = -1

    ! Reset pointers to current eType element in the total list
    ! @todo: first add fluid. do not have to follow sorted order here.
    iPnt = 0
    do indElem = 1, me%elem%tID%nVals
      ! Access sorted list to maintain locality of space-filling curve order
      iElem = me%elem%tID%sorted( indElem )
      eType = me%elem%eType%val( iElem )
      if ( eType == eT_distributedGhostFromFiner) then
        eType = eT_ghostFromFiner
        call changeType( me%elem, iElem, eT_ghostFromFiner )
      end if

      ! increase counter for current element
      iPnt( eType ) = iPnt( eType ) + 1
      ! is the eType a required element (fluid, ghost or halo)?
      ! Get rid of nonExistent elements here.
      if ( eType >= eT_minRelevant .and. eType <= eT_maxRelevant ) then
        ! Add sorted position of tID to the pointer
        me%totalPnt( me%offset(1,eType) + iPnt(eType) ) = iElem
        ! And add the haloList for halo elements
        if ( eType == eT_halo ) then
          ! get the process from where to get the element
          ! Create an entry in the process list for the current source process
          call tem_halo_append( me     = me%haloList,                   &
            &                   proc   = me%elem%sourceProc%val(iElem), &
            &                   elemPos= iElem                          )
        end if ! eT_halo
      end if !  ( eType >= eT_minRelevant )
    end do ! indElem

    ! Security check
    ! Check if there are no entries < 1
    do iElem = 1, me%nElems
      if( me%totalPnt( iElem ) < 1 ) then
        write(dbgUnit(1),*) "Error: Found index < 1 in the totalPnt array."
        write(dbgUnit(1),*) 'Abort!'
        write(dbgUnit(1),*) 'offset: '&
          &     //trim(tem_toStr(me%offset(1,:),'; '))

        do iVal = 1, me%nElems
          write(dbgUnit(1),*)'totalPnt: ',me%totalPnt(iVal)
        end do
        call tem_abort
      end if
    enddo

  end subroutine identify_lists