ESMF_GridCreate1PeriDimR Function

private function ESMF_GridCreate1PeriDimR(regDecomp, decompflag, minIndex, maxIndex, keywordEnforcer, polekindflag, periodicDim, poleDim, coordSys, coordTypeKind, coordDep1, coordDep2, coordDep3, gridEdgeLWidth, gridEdgeUWidth, gridAlign, gridMemLBound, indexflag, petMap, name, rc)

Arguments

Type IntentOptional Attributes Name
integer, intent(in), optional :: regDecomp(:)
type(ESMF_Decomp_Flag), intent(in), optional :: decompflag(:)
integer, intent(in), optional :: minIndex(:)
integer, intent(in) :: maxIndex(:)
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
type(ESMF_PoleKind_Flag), intent(in), optional :: polekindflag(2)
integer, intent(in), optional :: periodicDim
integer, intent(in), optional :: poleDim
type(ESMF_CoordSys_Flag), intent(in), optional :: coordSys
type(ESMF_TypeKind_Flag), intent(in), optional :: coordTypeKind
integer, intent(in), optional :: coordDep1(:)
integer, intent(in), optional :: coordDep2(:)
integer, intent(in), optional :: coordDep3(:)
integer, intent(in), optional :: gridEdgeLWidth(:)
integer, intent(in), optional :: gridEdgeUWidth(:)
integer, intent(in), optional :: gridAlign(:)
integer, intent(in), optional :: gridMemLBound(:)
type(ESMF_Index_Flag), intent(in), optional :: indexflag
integer, intent(in), optional :: petMap(:,:,:)
character(len=*), intent(in), optional :: name
integer, intent(out), optional :: rc

Return Value type(ESMF_Grid)


Source Code

      function ESMF_GridCreate1PeriDimR(regDecomp, decompFlag, &
        minIndex, maxIndex, keywordEnforcer,                                    &
        polekindflag, periodicDim, poleDim,                        &
        coordSys, coordTypeKind,                               &
        coordDep1, coordDep2, coordDep3,                       &
        gridEdgeLWidth, gridEdgeUWidth, gridAlign,             &
        gridMemLBound, indexflag, petMap, name, rc)

!
! !RETURN VALUE:
      type(ESMF_Grid) :: ESMF_GridCreate1PeriDimR
!
! !ARGUMENTS:
       integer,                   intent(in),  optional :: regDecomp(:)
       type(ESMF_Decomp_Flag),    intent(in),  optional :: decompflag(:)
       integer,                   intent(in),  optional :: minIndex(:)
       integer,                   intent(in)            :: maxIndex(:)
type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
       type(ESMF_PoleKind_Flag),  intent(in),  optional :: polekindflag(2)
       integer,                   intent(in),  optional :: periodicDim
       integer,                   intent(in),  optional :: poleDim
       type(ESMF_CoordSys_Flag),  intent(in),  optional :: coordSys
       type(ESMF_TypeKind_Flag),  intent(in),  optional :: coordTypeKind
       integer,                   intent(in),  optional :: coordDep1(:)
       integer,                   intent(in),  optional :: coordDep2(:)
       integer,                   intent(in),  optional :: coordDep3(:)
       integer,                   intent(in),  optional :: gridEdgeLWidth(:)
       integer,                   intent(in),  optional :: gridEdgeUWidth(:)
       integer,                   intent(in),  optional :: gridAlign(:)
       integer,                   intent(in),  optional :: gridMemLBound(:)
       type(ESMF_Index_Flag),     intent(in),  optional :: indexflag
       integer,                   intent(in),  optional :: petMap(:,:,:)
       character (len=*),         intent(in),  optional :: name
       integer,                   intent(out), optional :: rc
!
! !DESCRIPTION:
!
! This method creates a single tile, regularly distributed grid
! (see Figure \ref{fig:GridDecomps}) with one periodic dimension.
! 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. Currently this call
! only supports creating a 2D or 3D Grid, and thus, for example, {\tt maxIndex} must be of size 2 or 3.
!
! The arguments are:
! \begin{description}
! \item[{[regDecomp]}]
!      List that has the same number of elements as {\tt maxIndex}.
!      Each entry is the number of decounts for that dimension.
!      If not specified, the default decomposition will be petCountx1x1..x1.
! \item[{[decompflag]}]
!      List of decomposition flags indicating how each dimension of the
!      tile is to be divided between the DEs. The default setting
!      is {\tt ESMF\_DECOMP\_BALANCED} in all dimensions. Please see
!      Section~\ref{const:decompflag} for a full description of the
 !      possible options. Note that currently the option
!      {\tt ESMF\_DECOMP\_CYCLIC} isn't supported in Grid creation.
! \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[{[polekindflag]}]
!      Two item array which specifies the type of connection which occurs at the pole. The value in polekindflag(1)
!      specifies the connection that occurs at the minimum end of the pole dimension. The value in polekindflag(2)
!      specifies the connection that occurs at the maximum end of the pole dimension. Please see
!      Section~\ref{const:polekind} for a full list of options. If not specified,
!      the default is {\tt ESMF\_POLEKIND\_MONOPOLE} for both.
! \item[{[periodicDim]}]
!      The periodic dimension. If not specified, defaults to 1.
! \item[{[poleDim]}]
!      The dimension at who's ends the poles are located. If not specified defaults to 2.
! \item[{[coordSys]}]
!     The coordinate system of the grid coordinate data.
!     For a full list of options, please see Section~\ref{const:coordsys}.
!     If not specified then defaults to ESMF\_COORDSYS\_SPH\_DEG.
! \item[{[coordTypeKind]}]
!     The type/kind of the grid coordinate data. All {\em numerical} types
!     listed under section~\ref{const:typekind} are supported.
!     If not specified then defaults to ESMF\_TYPEKIND\_R8.
! \item[{[coordDep1]}]
!     This array specifies the dependence of the first
!     coordinate component on the three index dimensions
!     described by {\tt coordsPerDEDim1,2,3}. The size of the
!     array specifies the number of dimensions of the first
!     coordinate component array. The values specify which
!     of the index dimensions the corresponding coordinate
!     arrays map to. If not present the default is 1,2,...,grid rank.
! \item[{[coordDep2]}]
!     This array specifies the dependence of the second
!     coordinate component on the three index dimensions
!     described by {\tt coordsPerDEDim1,2,3}. The size of the
!     array specifies the number of dimensions of the second
!     coordinate component array. The values specify which
!     of the index dimensions the corresponding coordinate
!     arrays map to. If not present the default is 1,2,...,grid rank.
! \item[{[coordDep3]}]
!     This array specifies the dependence of the third
!     coordinate component on the three index dimensions
!     described by {\tt coordsPerDEDim1,2,3}. The size of the
!     array specifies the number of dimensions of the third
!     coordinate component array. The values specify which
!     of the index dimensions the corresponding coordinate
!     arrays map to. If not present the default is 1,2,...,grid rank.
! \item[{[gridEdgeLWidth]}]
!      The padding around the lower edges of the grid. This padding is between
!      the index space corresponding to the cells and the boundary of the
!      the exclusive region. This extra space is to contain the extra
!      padding for non-center stagger locations, and should be big enough
!      to hold any stagger in the grid. If this and gridAlign are not present then
!      defaults to 0, 0, ..., 0 (all zeros).
! \item[{[gridEdgeUWidth]}]
!      The padding around the upper edges of the grid. This padding is between
!      the index space corresponding to the cells and the boundary of the
!      the exclusive region. This extra space is to contain the extra
!      padding for non-center stagger locations, and should be big enough
!      to hold any stagger in the grid. If this and gridAlign are not present then
!      defaults to 1, 1, ..., 1 (all ones).
! \item[{[gridAlign]}]
!     Specification of how the stagger locations should align with the cell
!     index space (can be overridden by the individual staggerAligns). If
!     the gridEdgeWidths are not specified than this argument
!     implies the gridEdgeWidths. If the gridEdgeWidths are specified and this argument isn't
!     then this argument is implied by the gridEdgeWidths.
!     If this and the gridEdgeWidths are not specified, then defaults to
!    -1, -1, ..., -1 (all negative ones).
! \item[{[gridMemLBound]}]
!      Specifies the lower index range of the memory of every DE in this Grid.
!      Only used when indexflag is {\tt ESMF\_INDEX\_USER}. May be overridden
!      by staggerMemLBound.
! \item[{[indexflag]}]
!      Indicates the indexing scheme to be used in the new Grid. Please see
!      Section~\ref{const:indexflag} for the list of options. If not present,
!      defaults to ESMF\_INDEX\_DELOCAL.
! \item[{[petMap]}]
!       Sets the mapping of pets to the created DEs. This 3D
!       should be of size regDecomp(1) x regDecomp(2) x regDecomp(3)
!       If the Grid is 2D, then the last dimension is of size 1.
! \item[{[name]}]
!      {\tt ESMF\_Grid} name.
! \item[{[rc]}]
!      Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
! \end{description}
!
!EOP
    type(ESMF_DistGrid)  :: distgrid
    integer, pointer     :: coordDimCount(:)
    integer, pointer     :: coordDimMap(:,:)
    integer, pointer     :: gridEdgeLWidthLocal(:)
     integer, pointer     :: gridEdgeUWidthLocal(:)
    integer, pointer     :: gridAlignLocal(:)
    integer              :: dimCount
    integer, pointer     :: minIndexLocal(:)
    integer, pointer     :: maxIndexLocal(:)
    integer              :: localrc
    type(ESMF_DistgridConnection), pointer :: connList(:)
    integer             :: periodicDimLocal
    type(ESMF_CoordSys_Flag) :: coordSysLocal

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

#if DEBUG_POLEKIND
    if(present(polekindflag)) then
      print *, "GridCreate1PeriDim", polekindflag(1), polekindflag(2)
    endif
#endif
    
    ! Get IndexSpace
    call GetIndexSpaceReg(minIndex, maxIndex, &
          dimCount, minIndexLocal, maxIndexLocal,  rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

    ! Build connection list
    call Setup1PeriodicConn(dimCount, minIndexLocal, maxIndexLocal, &
                 polekindflag, periodicDim, poleDim, &
                 connList, periodicDimLocal, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
         ESMF_CONTEXT, rcToReturn=rc)) return


    ! Compute regular distgrid and error check associated input and set defaults
    distgrid=ESMF_GridCreateDistgridReg(dimCount, minIndexLocal, maxIndexLocal, &
               regDecomp, decompFlag, indexflag, petMap, connList, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

    if (present(name)) then
      call ESMF_DistGridSet(distgrid, name="DG-"//trim(name), rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
    endif

    ! Set default widths and alignment and error check
    allocate(gridEdgeLWidthLocal(dimCount), stat=localrc)
    if (ESMF_LogFoundAllocError(localrc, msg="Allocating gridEdgeLWidthLocal", &
                                     ESMF_CONTEXT, rcToReturn=rc)) return
    allocate(gridEdgeUWidthLocal(dimCount), stat=localrc)
    if (ESMF_LogFoundAllocError(localrc, msg="Allocating gridEdgeUWidthLocal", &
                                     ESMF_CONTEXT, rcToReturn=rc)) return
    allocate(gridAlignLocal(dimCount), stat=localrc)
    if (ESMF_LogFoundAllocError(localrc, msg="Allocating gridAlignLocal", &
                                     ESMF_CONTEXT, rcToReturn=rc)) return

    call ESMF_GridLUA1PeriDim(dimCount, periodicDimLocal,&
                             gridEdgeLWidth, gridEdgeUWidth, gridAlign, &
                             gridEdgeLWidthLocal, gridEdgeUWidthLocal, gridAlignLocal, &
                             rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return


   ! Convert coordDeps to coordDimCount and coordDimMap
   allocate(coordDimCount(dimCount), stat=localrc)
   if (ESMF_LogFoundAllocError(localrc, msg="Allocating coordDimCount", &
              ESMF_CONTEXT, rcToReturn=rc)) return
   allocate(coordDimMap(dimCount,dimCount), stat=localrc)
   if (ESMF_LogFoundAllocError(localrc, msg="Allocating coordDimMap", &
              ESMF_CONTEXT, rcToReturn=rc)) return

   call  CoordInfoFromCoordDep(dimCount, coordDep1, coordDep2, coordDep3,&
                               coordDimCount, coordDimMap, rc=localrc)
   if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

   ! Set Default coordSys
   if (present(coordSys)) then
      coordSysLocal=coordSys
   else
      coordSysLocal=ESMF_COORDSYS_SPH_DEG
   endif

   ! Create Grid from specification
   ESMF_GridCreate1PeriDimR=ESMF_GridCreateFrmDistGrid(&
                                    distgrid, &
                                    coordSys=coordSysLocal,    &
                                    coordTypeKind=coordTypeKind, &
                                    coordDimCount=coordDimCount, coordDimMap=coordDimMap, &
                                    gridEdgeLWidth=gridEdgeLWidthLocal, &
                                    gridEdgeUWidth=gridEdgeUWidthLocal, &
                                    gridAlign=gridAlignLocal, &
                                    gridMemLBound=gridMemLBound, &
                                    indexflag=indexflag, &
                                    name=name, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

    ! Set internal items to be destroyed with grid
     call ESMF_GridSetDestroyDistgrid(ESMF_GridCreate1PeriDimR,destroy=.true., &
           rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

    call ESMF_GridSetDestroyDELayout(ESMF_GridCreate1PeriDimR,destroy=.true., &
           rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return


    ! Clean up memory
    deallocate(connList)
    deallocate(coordDimCount)
    deallocate(coordDimMap)
    deallocate(gridEdgeLWidthLocal)
    deallocate(gridEdgeUWidthLocal)
    deallocate(gridAlignLocal)
    deallocate(minIndexLocal)
    deallocate(maxIndexLocal)

    ! Return successfully
    if (present(rc)) rc = ESMF_SUCCESS
    end function ESMF_GridCreate1PeriDimR