GetIndexSpaceIrreg Subroutine

private subroutine GetIndexSpaceIrreg(minIndex, countsPerDEDim1, countsPerDEDim2, countsPerDEDim3, dimCount, minIndexOut, maxIndexOut, rc)

Arguments

Type IntentOptional Attributes Name
integer, intent(in), optional :: minIndex(:)
integer, intent(in) :: countsPerDEDim1(:)
integer, intent(in) :: countsPerDEDim2(:)
integer, intent(in), optional :: countsPerDEDim3(:)
integer, intent(inout) :: dimCount
integer, pointer :: minIndexOut(:)
integer, pointer :: maxIndexOut(:)
integer, intent(out), optional :: rc

Calls

proc~~getindexspaceirreg~~CallsGraph proc~getindexspaceirreg GetIndexSpaceIrreg proc~esmf_logfoundallocerror ESMF_LogFoundAllocError proc~getindexspaceirreg->proc~esmf_logfoundallocerror proc~esmf_logseterror ESMF_LogSetError proc~getindexspaceirreg->proc~esmf_logseterror esmf_breakpoint esmf_breakpoint proc~esmf_logfoundallocerror->esmf_breakpoint proc~esmf_logrc2msg ESMF_LogRc2Msg proc~esmf_logfoundallocerror->proc~esmf_logrc2msg proc~esmf_logwrite ESMF_LogWrite proc~esmf_logfoundallocerror->proc~esmf_logwrite proc~esmf_logseterror->esmf_breakpoint proc~esmf_logseterror->proc~esmf_logrc2msg proc~esmf_logseterror->proc~esmf_logwrite c_esmc_loggeterrormsg c_esmc_loggeterrormsg proc~esmf_logrc2msg->c_esmc_loggeterrormsg c_esmc_vmwtime c_esmc_vmwtime proc~esmf_logwrite->c_esmc_vmwtime proc~esmf_logclose ESMF_LogClose proc~esmf_logwrite->proc~esmf_logclose proc~esmf_logflush ESMF_LogFlush proc~esmf_logwrite->proc~esmf_logflush proc~esmf_logopenfile ESMF_LogOpenFile proc~esmf_logwrite->proc~esmf_logopenfile proc~esmf_utiliounitflush ESMF_UtilIOUnitFlush proc~esmf_logwrite->proc~esmf_utiliounitflush proc~esmf_utilstring2array ESMF_UtilString2Array proc~esmf_logwrite->proc~esmf_utilstring2array proc~esmf_logclose->proc~esmf_logflush proc~esmf_logflush->proc~esmf_utiliounitflush proc~esmf_utilarray2string ESMF_UtilArray2String proc~esmf_logflush->proc~esmf_utilarray2string proc~esmf_logopenfile->proc~esmf_utiliounitflush proc~esmf_utiliounitget ESMF_UtilIOUnitGet proc~esmf_logopenfile->proc~esmf_utiliounitget

Called by

proc~~getindexspaceirreg~~CalledByGraph proc~getindexspaceirreg GetIndexSpaceIrreg proc~esmf_gridcreate1peridimi ESMF_GridCreate1PeriDimI proc~esmf_gridcreate1peridimi->proc~getindexspaceirreg proc~esmf_gridcreate2peridimi ESMF_GridCreate2PeriDimI proc~esmf_gridcreate2peridimi->proc~getindexspaceirreg proc~esmf_gridcreateedgeconni ESMF_GridCreateEdgeConnI proc~esmf_gridcreateedgeconni->proc~getindexspaceirreg proc~esmf_gridcreatenoperidimi ESMF_GridCreateNoPeriDimI proc~esmf_gridcreatenoperidimi->proc~getindexspaceirreg proc~esmf_gridemptycompleteeconni ESMF_GridEmptyCompleteEConnI proc~esmf_gridemptycompleteeconni->proc~getindexspaceirreg interface~esmf_gridcreate ESMF_GridCreate interface~esmf_gridcreate->proc~esmf_gridcreateedgeconni interface~esmf_gridcreate1peridim ESMF_GridCreate1PeriDim interface~esmf_gridcreate1peridim->proc~esmf_gridcreate1peridimi interface~esmf_gridcreate2peridim ESMF_GridCreate2PeriDim interface~esmf_gridcreate2peridim->proc~esmf_gridcreate2peridimi interface~esmf_gridcreatenoperidim ESMF_GridCreateNoPeriDim interface~esmf_gridcreatenoperidim->proc~esmf_gridcreatenoperidimi interface~esmf_gridemptycomplete ESMF_GridEmptyComplete interface~esmf_gridemptycomplete->proc~esmf_gridemptycompleteeconni

Source Code

      subroutine GetIndexSpaceIrreg(minIndex,  &
           countsPerDEDim1,countsPerDeDim2, &
           countsPerDEDim3, dimCount, minIndexOut, maxIndexOut, rc)
!!
! !ARGUMENTS:

       integer,               intent(in),  optional   :: minIndex(:)
       integer,               intent(in)              :: countsPerDEDim1(:)
       integer,               intent(in)              :: countsPerDEDim2(:)
       integer,               intent(in),  optional   :: countsPerDEDim3(:)
       integer,               intent(inout)           :: dimCount
       integer,               pointer                 :: minIndexOut(:)
       integer,               pointer                 :: maxIndexOut(:)
       integer,               intent(out), optional   :: rc
!
! !DESCRIPTION:
!
! This is a routine to calculate the minIndex and maxIndex of an irregular distribution.

! The arguments are:
! \begin{description}
! \item[{[minIndex]}]
!      Tuple to start the index ranges at. If not present, defaults
!      to /1,1,1,.../.
! \item[{countsPerDEDim1}]
!     This arrays specifies the number of cells per DE for index dimension 1
!     for the exclusive region (the center stagger location).
! \item[{countsPerDEDim2}]
!     This array specifies the number of cells per DE for index dimension 2
!     for the exclusive region (center stagger location).
! \item[{[countsPerDEDim3]}]
!     This array specifies the number of cells per DE for index dimension 3
!     for the exclusive region (center stagger location).
!     If not specified  then grid is 2D.
! \item[{minIndexOut}]
!     MinIndex of range, needs to be allocated to dimCount.
! \item[{maxIndexOut}]
!     MaxIndex of range, needs to be allocated to dimCount.
! \item[{[rc]}]
!      Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
! \end{description}
!
!EOPI
    integer              :: localrc
    integer              :: i


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


    ! Compute the Grid DimCount
    ! dimCount
    if (present(countsPerDEDim3)) then
        dimCount=3
    else
        dimCount=2
    endif


    ! Argument Consistency Checking
    if (size(countsPerDEDim1) .lt. 1) then
        call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
               msg="- size 0 countsPerDEDim1 not allowed", &
               ESMF_CONTEXT, rcToReturn=rc)
         return
    endif

    if (size(countsPerDEDim2) .lt. 1) then
        call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
               msg="- size 0 countsPerDEDim2 not allowed", &
               ESMF_CONTEXT, rcToReturn=rc)
         return
    endif

    if (present(countsPerDEDim3)) then
        if (size(countsPerDEDim3) .lt. 1) then
            call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
                    msg="- size 0 countsPerDEDim3 not allowed", &
                    ESMF_CONTEXT, rcToReturn=rc)
            return
        endif
    endif

    if (present(minIndex)) then
       if (size(minIndex) /= dimCount) then
          call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
               msg="- minIndex size must equal grid dimCount", &
               ESMF_CONTEXT, rcToReturn=rc)
          return
       endif
    endif


    ! Allocate minIndex
    allocate(minIndexOut(dimCount), stat=localrc)
    if (ESMF_LogFoundAllocError(localrc, msg="Allocating minIndexOut", &
                                     ESMF_CONTEXT, rcToReturn=rc)) return

    ! Set minIndex
    if (present(minIndex)) then
       minIndexOut(:)=minIndex(:)
    else
       do i=1,dimCount
          minIndexOut(i)=1
       enddo
    endif

    ! Allocate maxIndex
    allocate(maxIndexOut(dimCount), stat=localrc)
    if (ESMF_LogFoundAllocError(localrc, msg="Allocating maxIndexOut", &
                                     ESMF_CONTEXT, rcToReturn=rc)) return

    ! Set maxIndex
    maxIndexOut(1)=sum(countsPerDEDim1)+minIndexOut(1)-1
    maxIndexOut(2)=sum(countsPerDEDim2)+minIndexOut(2)-1

    if (dimCount > 2) then
      maxIndexOut(3)=sum(countsPerDEDim3)+minIndexOut(3)-1
    endif


    ! Return successfully
    if (present(rc)) rc = ESMF_SUCCESS
    end subroutine GetIndexSpaceIrreg