GetIndexSpaceArb Subroutine

private subroutine GetIndexSpaceArb(minIndex, maxIndex, arbIndexCount, arbIndexList, distDim, dimCount, distDimCount, isDistOut, distDimOut, minIndexOut, maxIndexOut, rc)

Arguments

Type IntentOptional Attributes Name
integer, intent(in), optional :: minIndex(:)
integer, intent(in) :: maxIndex(:)
integer, intent(in) :: arbIndexCount
integer, intent(in) :: arbIndexList(:,:)
integer, intent(in), optional :: distDim(:)
integer, intent(inout) :: dimCount
integer, intent(inout) :: distDimCount
logical, pointer :: isDistOut(:)
integer, pointer :: distDimOut(:)
integer, pointer :: minIndexOut(:)
integer, pointer :: maxIndexOut(:)
integer, intent(out), optional :: rc

Calls

proc~~getindexspacearb~~CallsGraph proc~getindexspacearb GetIndexSpaceArb proc~esmf_logfoundallocerror ESMF_LogFoundAllocError proc~getindexspacearb->proc~esmf_logfoundallocerror proc~esmf_logseterror ESMF_LogSetError proc~getindexspacearb->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~~getindexspacearb~~CalledByGraph proc~getindexspacearb GetIndexSpaceArb proc~esmf_gridcreate1peridima ESMF_GridCreate1PeriDimA proc~esmf_gridcreate1peridima->proc~getindexspacearb proc~esmf_gridcreate2peridima ESMF_GridCreate2PeriDimA proc~esmf_gridcreate2peridima->proc~getindexspacearb proc~esmf_gridcreateedgeconna ESMF_GridCreateEdgeConnA proc~esmf_gridcreateedgeconna->proc~getindexspacearb proc~esmf_gridcreatenoperidima ESMF_GridCreateNoPeriDimA proc~esmf_gridcreatenoperidima->proc~getindexspacearb proc~esmf_gridemptycompleteeconna ESMF_GridEmptyCompleteEConnA proc~esmf_gridemptycompleteeconna->proc~getindexspacearb interface~esmf_gridcreate ESMF_GridCreate interface~esmf_gridcreate->proc~esmf_gridcreateedgeconna interface~esmf_gridcreate1peridim ESMF_GridCreate1PeriDim interface~esmf_gridcreate1peridim->proc~esmf_gridcreate1peridima interface~esmf_gridcreate2peridim ESMF_GridCreate2PeriDim interface~esmf_gridcreate2peridim->proc~esmf_gridcreate2peridima interface~esmf_gridcreatenoperidim ESMF_GridCreateNoPeriDim interface~esmf_gridcreatenoperidim->proc~esmf_gridcreatenoperidima interface~esmf_gridemptycomplete ESMF_GridEmptyComplete interface~esmf_gridemptycomplete->proc~esmf_gridemptycompleteeconna

Source Code

      subroutine GetIndexSpaceArb(minIndex, maxIndex, &
          arbIndexCount, arbIndexList, distDim,       &
          dimCount, distDimCount, isDistOut, distDimOut, minIndexOut, maxIndexOut,  rc)

!
! !ARGUMENTS:
       integer,               intent(in),  optional :: minIndex(:)
       integer,               intent(in)            :: maxIndex(:)
       integer,               intent(in)            :: arbIndexCount
       integer,               intent(in)            :: arbIndexList(:,:)
       integer,               intent(in),  optional :: distDim(:)
       integer,               intent(inout)         :: dimCount
       integer,               intent(inout)         :: distDimCount
       logical,               pointer               :: isDistOut(:)
       integer,               pointer               :: distDimOut(:)
       integer,               pointer               :: minIndexOut(:)
       integer,               pointer               :: maxIndexOut(:)
       integer,               intent(out), optional :: rc
!
! !DESCRIPTION:
!
! This internal method creates a single tile, regularly distributed distgrid
! (see Figure \ref{fig:GridDecomps}).
! To specify the distribution, the user passes in an array
! ({\tt regDecomp}) specifying the number of DEs to divide each
! dimension into. The array {\tt decompFlag} indicates how the division into DEs is to
! occur.  The default is to divide the range as evenly as possible.
!
! The arguments are:
! \begin{description}
! \item[{[minIndex]}]
!      The bottom extent of the grid array. If not given then the value defaults
!      to /1,1,1,.../.
! \item[{maxIndex}]
!      The upper extent of the grid array.
! \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 and Derivatives ---------------------------------------------------
    ! dimCount
    dimCount=size(maxIndex)
    if ((dimCount < 2) .or. (dimCount > 3)) then
        call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
               msg="- maxIndex size and thus Grid dimCount must be either 2 or 3 when using create shape ", &
               ESMF_CONTEXT, rcToReturn=rc)
         return
    endif

    ! Error check index size
    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

    ! number of distributed dimension, distDimCount, is determined by the second dim of
    ! arbIndexList
    distDimCount = size(arbIndexList,2)
    if (distDimCount > dimCount) then
        call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
               msg="- the second dim of arbIndexList must be equal or less than grid dimension", &
               ESMF_CONTEXT, rcToReturn=rc)
         return
    endif


    ! compute distributed dimensions and isDist list
    allocate(distDimOut(distDimCount), stat=localrc)
    allocate(isDistOut(dimCount), stat=localrc)
    if (ESMF_LogFoundAllocError(localrc, msg="Allocating distDimLocal or isDist", &
                                     ESMF_CONTEXT, rcToReturn=rc)) return

    isDistOut(:)=.false.
    ! check distribution info
    if (present(distDim)) then
       if (size(distDim) /= distDimCount) then
          call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
                 msg="- distDim must match with the second dimension of arbIndexList", &
                 ESMF_CONTEXT, rcToReturn=rc)
            return
       endif
       distDimOut(:)=distDim(:)
       do i=1,distDimCount
          isDistOut(distDimOut(i))=.true.
       enddo
    else
       do i=1,distDimCount
         distDimOut(i)=i
       enddo
       isDistOut(1:distDimCount)=.true.
    endif

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

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


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


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