ESMF_GeomGetPLocalDe Subroutine

public subroutine ESMF_GeomGetPLocalDe(geom, localDe, exclusiveLBound, exclusiveUBound, exclusiveCount, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Geom), intent(in) :: geom
integer, intent(in) :: localDe
integer, intent(out), optional :: exclusiveLBound(:)
integer, intent(out), optional :: exclusiveUBound(:)
integer, intent(out), optional :: exclusiveCount(:)
integer, intent(out), optional :: rc

Source Code

      subroutine ESMF_GeomGetPLocalDe(geom, localDe, &
          exclusiveLBound, exclusiveUBound, exclusiveCount,  rc)

!
! !ARGUMENTS:
      type(ESMF_Geom),        intent(in)            :: geom
      integer,                intent(in)            :: localDe
       integer,                intent(out), optional :: exclusiveLBound(:)
      integer,                intent(out), optional :: exclusiveUBound(:)
      integer,                intent(out), optional :: exclusiveCount(:)
      integer,                intent(out), optional :: rc
!
! !DESCRIPTION:
!  This method gets information about the range of the index space which a
!  localDe occupies.
!
!The arguments are:
!\begin{description}
!\item[{geom}]
!    Grid Base to get the information from.
!\item[{[localDe]}]
!     The local DE from which to get the information.
!\item[{[exclusiveLBound]}]
!     Upon return this holds the lower bounds of the exclusive region.
!     {\tt exclusiveLBound} must be allocated to be of size equal to the Grid dimCount.
!     Please see Section~\ref{sec:grid:usage:bounds} for a description
!     of the regions and their associated bounds and counts.
!\item[{[exclusiveUBound]}]
 !     Upon return this holds the upper bounds of the exclusive region.
!     {\tt exclusiveUBound} must be allocated to be of size equal to the Grid dimCount.
!     Please see Section~\ref{sec:grid:usage:bounds} for a description
!     of the regions and their associated bounds and counts.
!\item[{[exclusiveCount]}]
!     Upon return this holds the number of items in the exclusive region per dimension
!     (i.e. {\tt exclusiveUBound-exclusiveLBound+1}). {\tt exclusiveCount} must
!      be allocated to be of size equal to the Grid dimCount.
!     Please see Section~\ref{sec:grid:usage:bounds} for a description
!     of the regions and their associated bounds and counts.
!\item[{[rc]}]
!     Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!\end{description}
!
!EOPI
    integer :: localrc
    type(ESMF_GeomClass),pointer :: gbcp
    integer :: cl,cu,cc,el,eu,ec

    ! Initialize return code; assume failure until success is certain
    if (present(rc)) rc = ESMF_RC_NOT_IMPL

    ! Check init status of arguments
    ESMF_INIT_CHECK_DEEP_SHORT(ESMF_GeomGetInit, geom, rc)

    ! Get GeomClass
    gbcp=>geom%gbcp

    ! Get info depending on type
    select case(gbcp%type%type)

       case (ESMF_GEOMTYPE_GRID%type) ! Grid
          call ESMF_GridGet(grid=gbcp%grid, localDE=localDE, &
          staggerloc=gbcp%staggerloc,  &
          exclusiveLBound=exclusiveLBound, exclusiveUBound=exclusiveUBound, &
          exclusiveCount=exclusiveCount, rc=localrc)
          if (ESMF_LogFoundError(localrc, &
                                 ESMF_ERR_PASSTHRU, &
                                 ESMF_CONTEXT, rcToReturn=rc)) return

       case  (ESMF_GEOMTYPE_MESH%type) ! Mesh
          if (present(exclusiveLBound)) exclusiveLBound(1) = 1
          if (present(exclusiveUBound)) then
               if (gbcp%meshloc == ESMF_MESHLOC_NODE) then
                  call ESMF_MeshGet(mesh=gbcp%mesh, &
                                    numOwnedNodes=exclusiveUBound(1), &
                                    rc=localrc)
                  if (ESMF_LogFoundError(localrc, &
                                   ESMF_ERR_PASSTHRU, &
                                   ESMF_CONTEXT, rcToReturn=rc)) return
               else if (gbcp%meshloc == ESMF_MESHLOC_ELEMENT) then
                  call ESMF_MeshGet(mesh=gbcp%mesh, &
                                    numOwnedElements=exclusiveUBound(1), &
                                    rc=localrc)
                  if (ESMF_LogFoundError(localrc, &
                                 ESMF_ERR_PASSTHRU, &
                                 ESMF_CONTEXT, rcToReturn=rc)) return
               else
                  if (ESMF_LogFoundError(ESMF_RC_ARG_VALUE, &
                               msg=" Bad Mesh Location value", &
                               ESMF_CONTEXT, rcToReturn=rc)) return
               endif
            endif
          if (present(exclusiveCount)) then
               if (gbcp%meshloc == ESMF_MESHLOC_NODE) then
                  call ESMF_MeshGet(mesh=gbcp%mesh, &
                                    numOwnedNodes=exclusiveCount(1), &
                                    rc=localrc)
                  if (ESMF_LogFoundError(localrc, &
                                   ESMF_ERR_PASSTHRU, &
                                   ESMF_CONTEXT, rcToReturn=rc)) return
               else if (gbcp%meshloc == ESMF_MESHLOC_ELEMENT) then
                  call ESMF_MeshGet(mesh=gbcp%mesh, &
                                    numOwnedElements=exclusiveCount(1), &
                                    rc=localrc)
                  if (ESMF_LogFoundError(localrc, &
                                 ESMF_ERR_PASSTHRU, &
                                 ESMF_CONTEXT, rcToReturn=rc)) return
               else
                  if (ESMF_LogFoundError(ESMF_RC_ARG_VALUE, &
                               msg=" Bad Mesh Location value", &
                               ESMF_CONTEXT, rcToReturn=rc)) return
               endif
            endif

       case  (ESMF_GEOMTYPE_LOCSTREAM%type) ! LocStream
          call ESMF_LocStreamGetBounds(gbcp%locstream, &
               localDE=localDE, &
               exclusiveLBound=el, &
               exclusiveUBound=eu, &
               exclusiveCount=ec,  &
               rc=localrc)
          if (ESMF_LogFoundError(localrc, &
                                 ESMF_ERR_PASSTHRU, &
                                 ESMF_CONTEXT, rcToReturn=rc)) return
          if (present(exclusiveLBound)) exclusiveLBound(1)=el
          if (present(exclusiveUBound)) exclusiveUBound(1)=eu
          if (present(exclusiveCount)) exclusiveCount(1)=ec


       case  (ESMF_GEOMTYPE_XGRID%type) ! Xgrid
          call ESMF_XGridGet(gbcp%xgrid, localDE=localDE, &
              exclusiveLBound=el, &
               exclusiveUBound=eu, &
               exclusiveCount=ec,  &
               rc=localrc)
          if (ESMF_LogFoundError(localrc, &
                                 ESMF_ERR_PASSTHRU, &
                                 ESMF_CONTEXT, rcToReturn=rc)) return

         if (present(exclusiveLBound)) exclusiveLBound(1)=el
         if (present(exclusiveUBound)) exclusiveUBound(1)=eu
         if (present(exclusiveCount)) exclusiveCount(1)=ec

        case default
         if (ESMF_LogFoundError(ESMF_RC_ARG_VALUE, &
                               msg=" Bad type value", &
                               ESMF_CONTEXT, rcToReturn=rc)) return
    end select

    ! Set return value
    if (present(rc)) rc = ESMF_SUCCESS

 end subroutine ESMF_GeomGetPLocalDe