ESMF_DistGridGetPLocalDe Subroutine

private subroutine ESMF_DistGridGetPLocalDe(distgrid, localDe, keywordEnforcer, de, tile, collocation, arbSeqIndexFlag, seqIndexList, seqIndexListI8, elementCount, elementCountI8, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_DistGrid), intent(in) :: distgrid
integer, intent(in) :: localDe
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
integer, intent(out), optional :: de
integer, intent(out), optional :: tile
integer, intent(in), optional :: collocation
logical, intent(out), optional :: arbSeqIndexFlag
integer, intent(out), optional, target :: seqIndexList(:)
integer(kind=ESMF_KIND_I8), intent(out), optional, target :: seqIndexListI8(:)
integer, intent(out), optional :: elementCount
integer, intent(out), optional :: elementCountI8
integer, intent(out), optional :: rc

Source Code

  subroutine ESMF_DistGridGetPLocalDe(distgrid, localDe, keywordEnforcer, &
    de, tile, collocation, arbSeqIndexFlag, seqIndexList, seqIndexListI8, &
    elementCount, elementCountI8, rc)
!
! !ARGUMENTS:
    type(ESMF_DistGrid),      intent(in)            :: distgrid
    integer,                  intent(in)            :: localDe
type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
    integer,                  intent(out), optional :: de
    integer,                  intent(out), optional :: tile
    integer,                  intent(in),  optional :: collocation
    logical,                  intent(out), optional :: arbSeqIndexFlag
    integer,          target, intent(out), optional :: seqIndexList(:)
integer(ESMF_KIND_I8),target, intent(out), optional :: seqIndexListI8(:)
    integer,                  intent(out), optional :: elementCount
    integer,                  intent(out), optional :: elementCountI8
    integer,                  intent(out), optional :: rc
!         
! !STATUS:
! \begin{itemize}
! \item\apiStatusCompatibleVersion{5.2.0r}
! \item\apiStatusModifiedSinceVersion{5.2.0r}
! \begin{description}
! \item[8.0.0] Added arguments {\tt de} and {\tt tile} to simplify usage.
! \item[8.1.0] Added arguments {\tt seqIndexListI8} and {\tt elementCountI8}
!              to provide 64-bit access.
! \end{description}
! \end{itemize}
!
! !DESCRIPTION:
!   Access internal DistGrid information.
!
!   The arguments are:
!   \begin{description}
!   \item[distgrid]
!     Queried {\tt ESMF\_DistGrid} object.
!   \item[localDe]
!     Local DE for which information is requested. {\tt [0,..,localDeCount-1]}
!   \item[{[de]}]
!     The global DE associated with the {\tt localDe}. DE indexing starts at 0.
!   \item[{[tile]}]
!     The tile on which the {\tt localDe} is located. Tile indexing starts at 1.
!   \item[{[collocation]}]
!     Collocation for which information is requested. Default to first
!     collocation in {\tt collocation} list.
!   \item[{[arbSeqIndexFlag]}]
!     A returned value of {\tt .true.} indicates that the {\tt collocation}
!     is associated with arbitrary sequence indices. For {\tt .false.},
!     canoncial sequence indices are used.
!   \item[{[seqIndexList]}]
!     The sequence indices associated with the {\tt localDe}. This argument must
!     enter allocated with a size equal to 
!     {\tt elementCountPDe(localDeToDeMap(localDe))}.
!     An error will be returned if any of the sequence indices are above the
!     32-bit limit.
!   \item[{[seqIndexListI8]}]
!     Same as {\tt seqIndexList}, but of 64-bit integer kind.
!   \item[{[elementCount]}]
!     Number of elements in the localDe, i.e. identical to
!     elementCountPDe(localDeToDeMap(localDe)).
!     An error will be returned if the count is above the 32-bit limit.
!   \item[{[elementCountI8]}]
!     Same as {\tt elementCount}, but of 64-bit integer kind.
!   \item[{[rc]}]
!     Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!   \end{description}
!
!EOP
!------------------------------------------------------------------------------
    integer               :: localrc            ! local return code
    type(ESMF_Logical)    :: arbSeqIndexFlagAux ! helper variable
    type(ESMF_InterArray) :: seqIndexListAux    ! helper variable
    type(ESMF_InterArray) :: seqIndexListI8Aux  ! helper variable
    integer               :: localDeCount, deCount
    integer, allocatable  :: localDeToDeMap(:), deToTileMap(:)

    ! initialize return code; assume routine not implemented
    localrc = ESMF_RC_NOT_IMPL
    if (present(rc)) rc = ESMF_RC_NOT_IMPL
    
    ! Check init status of arguments
    ESMF_INIT_CHECK_DEEP(ESMF_DistGridGetInit, distgrid, rc)

    ! Handle requests that are available on the Fortran side
    if (present(de) .or. present(tile)) then
      call ESMF_DistGridGet(distgrid, localDeCount=localDeCount, &
        deCount=deCount, rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
      ! Sanity check localDeCount
      if (localDeCount <= 0) then
        call ESMF_LogSetError(rcToCheck=ESMF_RC_CANNOT_GET, &
          msg="localDeCount <= 0 prohibits request", &
          ESMF_CONTEXT, rcToReturn=rc)
        return
      endif
      ! Check that localDe is within limits
      if (localDe < 0 .or. localDe > localDeCount-1) then
        call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_OUTOFRANGE, &
          msg="localDe out of range", &
          ESMF_CONTEXT, rcToReturn=rc)
        return
      endif
      if (present(de) .or. present(tile)) then
        ! query more information
        allocate(localDeToDeMap(0:localDeCount-1))
        allocate(deToTileMap(0:deCount-1))
        call ESMF_DistGridGet(distgrid, localDeToDeMap=localDeToDeMap, &
          deToTileMap=deToTileMap, rc=localrc)
        if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
          ESMF_CONTEXT, rcToReturn=rc)) return
        ! now can determine return values
        if (present(de)) de = localDeToDeMap(localDe)
        if (present(tile)) tile = deToTileMap(localDeToDeMap(localDe))
        ! clean-up
        deallocate(localDeToDeMap, deToTileMap)
      endif
    endif

    ! Deal with (optional) array arguments
    seqIndexListAux = ESMF_InterArrayCreate(seqIndexList, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return
    seqIndexListI8Aux = &
      ESMF_InterArrayCreate(farray1DI8=seqIndexListI8, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

    ! call into the C++ interface, which will sort out optional arguments
    call c_ESMC_DistGridGetPLocalDe(distgrid, localDe, collocation, &
      arbSeqIndexFlagAux, seqIndexListAux, seqIndexListI8Aux, &
      elementCount, elementCountI8, localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return
      
    ! logicals
    if (present (arbSeqIndexFlag)) &
      arbSeqIndexFlag = arbSeqIndexFlagAux
    
    ! garbage collection
    call ESMF_InterArrayDestroy(seqIndexListAux, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return
    call ESMF_InterArrayDestroy(seqIndexListI8Aux, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

    ! return successfully
    if (present(rc)) rc = ESMF_SUCCESS

  end subroutine ESMF_DistGridGetPLocalDe