ESMF_GridCreateMosaicReg Function

private function ESMF_GridCreateMosaicReg(filename, keywordEnforcer, regDecompPTile, decompflagPTile, coordTypeKind, deLabelList, staggerLocList, delayout, indexflag, name, tileFilePath, rc)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
integer, intent(in), optional :: regDecompPTile(:,:)
type(ESMF_Decomp_Flag), intent(in), optional, target :: decompflagPTile(:,:)
type(ESMF_TypeKind_Flag), intent(in), optional :: coordTypeKind
integer, intent(in), optional :: deLabelList(:)
type(ESMF_StaggerLoc), intent(in), optional :: staggerLocList(:)
type(ESMF_DELayout), intent(in), optional :: delayout
type(ESMF_Index_Flag), intent(in), optional :: indexflag
character(len=*), intent(in), optional :: name
character(len=*), intent(in), optional :: tileFilePath
integer, intent(out), optional :: rc

Return Value type(ESMF_Grid)


Source Code

  function ESMF_GridCreateMosaicReg(filename,keywordEnforcer, regDecompPTile, decompflagPTile, &
        coordTypeKind, deLabelList, staggerLocList, delayout, indexflag, name, tileFilePath, rc)
!
! !RETURN VALUE:
    type(ESMF_Grid) :: ESMF_GridCreateMosaicReg
!
! !ARGUMENTS:
    character(len=*),               intent(in)            :: filename
type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
    integer,                        intent(in),  optional :: regDecompPTile(:,:)
    type(ESMF_Decomp_Flag), target, intent(in),  optional :: decompflagPTile(:,:)
    type(ESMF_TypeKind_Flag),       intent(in),  optional :: coordTypeKind
    integer,                        intent(in),  optional :: deLabelList(:)
    type(ESMF_StaggerLoc),          intent(in),  optional :: staggerLocList(:)
    type(ESMF_DELayout),            intent(in),  optional :: delayout
    type(ESMF_Index_Flag),          intent(in),  optional :: indexflag
    character(len=*),               intent(in),  optional :: name
    character(len=*),               intent(in),  optional :: tileFilePath
    integer,                        intent(out), optional :: rc

!
! !DESCRIPTION:
!   Create a multiple-tile {\tt ESMF\_Grid} based on the definition from a GRIDSPEC Mosaic file and its associated
!   tile files using regular decomposition.  Each tile can have different decomposition.  The tile connections
!   are defined in a GRIDSPEC format Mosaic file.
!   And each tile's coordination is defined in a separate NetCDF file.  The coordinates defined
!   in the tile file is so-called "Super Grid".  In other words, the dimensions of the coordinate variables are
!   {\tt (2*xdim+1, 2*ydim+1)} if {\tt (xdim, ydim)} is the size of the tile.  The Super Grid combines the corner,
!   the edge and the center coordinates in one big array.  A Mosaic file may contain just one tile.  If a Mosaic contains
!   multiple tiles.  Each tile is a logically rectangular lat/lon grid.  Currently, all the tiles have to be the same size.
!   We will remove this limitation in the future release.
!
!
!     The arguments are:
!     \begin{description}
!     \item[filename]
!          The name of the GRIDSPEC Mosaic file.
!     \item[{[regDecompPTile]}]
!          List of DE counts for each dimension. The second index steps through
!          the tiles. The total {\tt deCount} is determined as the sum over
!          the products of {\tt regDecompPTile} elements for each tile.
!          By default every tile is decomposed in the same way.  If the total
!          PET count is less than the tile count, one tile will be assigned to one DE and the DEs
!          will be assigned to PETs sequentially, therefore, some PETs may have
!          more than one DE.  If the total PET count is greater than the tile count, the total
!          number of DEs will be a multiple of the tile count and less than or equal to the total
!          PET count.  For instance, if the total PET count is 16 and the tile count is 6, the total DE count
!          will be 12 with each tile decomposed into 1x2 blocks.  The 12 DEs are mapped
!          to the first 12 PETs and the remaining 4 PETs have no DEs locally, unless
!          an optional {\tt delayout} is provided.
!     \item[{[decompflagPTile]}]
!          List of decomposition flags indicating how each dimension of each
!          tile is to be divided between the DEs. The default setting
!          is {\tt ESMF\_DECOMP\_BALANCED} in all dimensions for all tiles.
!          See section \ref{const:decompflag} for a list of valid decomposition
!          flag options. The second index indicates the tile number.
!     \item[{[coordTypeKind]}]
!          The type/kind of the grid coordinate data. Only ESMF\_TYPEKIND\_R4
!          and ESMF\_TYPEKIND\_R8 are supported.
!          If not specified then defaults to ESMF\_TYPEKIND\_R8.
!     \item[{[deLabelList]}]
!          List assigning DE labels to the default sequence of DEs. The default
!          sequence is given by the column major order of the {\tt regDecompPTile}
!          elements in the sequence as they appear following the tile index.
!     \item[{[staggerLocList]}]
!          The list of stagger locations to fill with coordinates. Please see Section~\ref{const:staggerloc}
!          for a description of the available stagger locations. If not present, no coordinates
!          will be added or filled.
!     \item[{[delayout]}]
!          Optional {\tt ESMF\_DELayout} object to be used. By default a new
!          DELayout object will be created with as many DEs as there are PETs,
!          or tiles, which ever is greater. If a DELayout object is specified,
!          the number of DEs must match {\tt regDecompPTile}, if present. In the
!          case that {\tt regDecompPTile} was not specified, the {\tt deCount}
!          must be at least that of the default DELayout. The
!          {\tt regDecompPTile} will be constructed accordingly.
!     \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[{[name]}]
!          {\tt ESMF\_Grid} name.
!     \item[{[tileFilePath]}]
!          Optional argument to define the path where the tile files reside. If it
!          is given, it overwrites the path defined in {\tt gridlocation} variable
!          in the mosaic file.
!     \item[{[rc]}]
!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!     \end{description}
!
!EOP

    type(ESMF_VM)                               :: vm
    integer                                     :: PetNo, PetCnt
    integer                                     :: totalDE, nxy, nx, ny, bigFac
    integer                                     :: sizex, sizey
    type(ESMF_DELayout)                         :: defaultDELayout
    type(ESMF_Grid)                             :: grid, newgrid
    type(ESMF_DistGrid)                         :: distgrid, newdistgrid
    integer                                     :: localrc
    type(ESMF_DistGridConnection), allocatable :: connectionList(:)
    integer                                    :: i, j, k, conn
    integer                                    :: localDeCount, localDe, DeNo, tile
    real(kind=ESMF_KIND_R8),  pointer          :: lonPtrR8(:,:), latPtrR8(:,:)
    real(kind=ESMF_KIND_R8),  pointer          :: lonCornerPtrR8(:,:), latCornerPtrR8(:,:)
    real(kind=ESMF_KIND_R4),  pointer          :: lonPtrR4(:,:), latPtrR4(:,:)
    real(kind=ESMF_KIND_R4),  pointer          :: lonCornerPtrR4(:,:), latCornerPtrR4(:,:)
    integer                                    :: tileCount
    integer                                    :: connectionCount
    integer                                    :: tileSize
    integer                                    :: starti, startj, sizei, sizej
    integer                                    :: ind, rem, rem1, rem2
    integer                                    :: start(2), count(2)
    integer, pointer                           :: minIndexPTile(:,:)
    integer, pointer                           :: maxIndexPTile(:,:)
    integer, pointer                           :: minIndexPDe(:,:)
    integer, pointer                           :: maxIndexPDe(:,:)
    integer, allocatable                       :: regDecomp2(:,:)
    integer, allocatable                       :: demap(:)
    integer                                    :: decount
    !real(ESMF_KIND_R8)                        :: starttime, endtime
    character(len=ESMF_MAXPATHLEN)             :: tempname
    type(ESMF_Mosaic)                          :: mosaic
    integer                                    :: totallen
    integer                                    :: posVec(2), orientVec(2)
    integer                                    :: regDecomp(2)
    type(ESMF_Decomp_Flag)                     :: decompflag(2)
    type(ESMF_Index_Flag)                      :: localIndexFlag
    logical                                    :: isGlobal
    integer, pointer                           :: PetMap1D(:), PetMap(:,:,:)
    integer                                    :: lbnd(2), ubnd(2)
    integer                                    :: s
    type(ESMF_TypeKind_Flag)                   :: coordTypeKindLocal

    if (present(rc)) rc=ESMF_SUCCESS

    if (present(indexflag)) then
       localIndexFlag = indexflag
    else
       localIndexFlag = ESMF_INDEX_DELOCAL
    endif

   ! Set Default coordTypeKind
   if (present(coordTypeKind)) then
      if (coordTypeKind .ne. ESMF_TYPEKIND_R4 .and. &
          coordTypeKind .ne. ESMF_TYPEKIND_R8) then
         call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_WRONG, &
            msg="- only ESMF_TYPEKIND_R4 and ESMF_TYPEKIND_R8 are allowed", &
            ESMF_CONTEXT, rcToReturn=rc)
         return
      endif      
      coordTypeKindLocal=coordTypeKind
   else
      coordTypeKindLocal=ESMF_TYPEKIND_R8
   endif

  !------------------------------------------------------------------------
  !------------------------------------------------------------------------
  ! get global vm information
  !
  call ESMF_VMGetCurrent(vm, rc=localrc)
  if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
    ESMF_CONTEXT, rcToReturn=rc)) return

  ! set up local pet info
  call ESMF_VMGet(vm, localPet=PetNo, petCount=PetCnt, rc=localrc)
  if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

  call ESMF_GridSpecReadMosaic(filename, mosaic, tileFilePath=tileFilePath, rc=localrc)
  if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

  tileCount = mosaic%ntiles
  sizex = mosaic%nx
  sizey = mosaic%ny

  if (tileCount > 1) then
    ! use local index for everytile
    ! should support different tile sizes -- TBD
    allocate(minIndexPTile(2,tileCount))
    allocate(maxIndexPTile(2,tileCount))
    minIndexPTile(1,:)=1
    minIndexPTile(2,:)=1
    maxIndexPTile(1,:)=sizex
    maxIndexPTile(2,:)=sizey

    ! build connectionList for each connecation
    connectionCount = mosaic%ncontacts

    allocate(connectionList(connectionCount))
    do i=1,connectionCount
      call calculateConnect(minIndexPTile, maxIndexPTile, mosaic%contact(:,i), &
           mosaic%connindex(:,:,i), orientVec, posVec)
      call ESMF_DistGridConnectionSet(connection=connectionList(i), &
        tileIndexA=mosaic%contact(1,i), tileIndexB=mosaic%contact(2,i), &
        positionVector=(/posVec(1), posVec(2)/), &
        orientationVector = (/orientVec(1), orientVec(2)/), rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
    enddo

  !------------------------------------------------------------------------
  ! default decomposition. The number of DEs has to be multiple of the tile count.
  ! If the total PET count is less than the tile count, some PETs will get more than one DE.
  ! Otherwise, total DEs is always less than or equal to total PETs.

    if (PetCnt < tileCount) then
        totalDE=tileCount
    else
        totalDE = (PetCnt/tileCount)*tileCount
    endif

    nxy = totalDE/tileCount
    bigFac = 1
    do i=2, int(sqrt(float(nxy)))
      if ((nxy/i)*i == nxy) then
        bigFac = i
      endif
    enddo
    nx = bigFac
    ny = nxy/nx

    defaultDELayout = ESMF_DELayoutCreate(deCount = totalDE, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

    call ESMF_DELayoutGet(defaultDElayout, localDeCount = decount, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return
    if (decount > 0) then
       allocate(demap(0:decount-1))
       call ESMF_DELayoutGet(defaultDElayout, localDeToDeMap = demap, rc=localrc)
       if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
          ESMF_CONTEXT, rcToReturn=rc)) return
       !print *, PetNo, ' demap ', decount, demap
     endif
     allocate(regDecomp2(2,tileCount))
       regDecomp2(1,:)=nx
       regDecomp2(2,:)=ny
    !-------------------------------------------
    ! - create DistGrid with default decomposition
    ! must create with ESMF_INDEX_DELOCAL because of how connections were defined
    distgrid = ESMF_DistGridCreate(&
      minIndexPTile=minIndexPTile, maxIndexPTile=maxIndexPTile, &
      regDecompPTile=regDecomp2, &
      indexflag=ESMF_INDEX_DELOCAL, connectionList=connectionList, &
      delayout = defaultDelayout, &
      rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
      ESMF_CONTEXT, rcToReturn=rc)) return

    ! - create Grid
    ! coordinates from the cubedSphereTileCreate() routine
    grid = ESMF_GridCreate(distgrid, coordSys=ESMF_COORDSYS_SPH_DEG, &
      coordTypeKind=coordTypeKindLocal, &
       indexflag=localIndexFlag, name=name, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
         ESMF_CONTEXT, rcToReturn=rc)) return

    if (present(staggerLocList)) then
      do s=1, size(staggerLocList)
         call ESMF_GridAddCoord(grid, staggerloc=staggerLocList(s), rc=localrc)
         if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) return
      enddo
      ! calculate the actual cubed sphere coordiantes for each DE
      do localDe = 0,decount-1
         DeNo = demap(localDe)
         tile = DeNo/(nx*ny)+1
         rem = mod(DeNo,nx*ny)
         sizei = sizex/nx
         sizej = sizey/ny
         rem1 = mod(sizex, nx)
         rem2 = mod(sizey, ny)
         ind = mod(rem,nx)
         if (rem1 > 0) then
            if (ind < rem1) then
               sizei=sizei+1
               starti=sizei*ind+1
            else
               starti=sizei*ind+rem1+1
            endif
         else
            starti = sizei*ind+1
         endif
         ind = rem/nx
         if (rem2 > 0) then
            if (ind < rem2) then
               sizej=sizej+1
               startj=sizej*ind+1
            else
               startj=sizej*ind+rem2+1
            endif
         else
            startj = sizej*ind+1
         endif
         !print *, DeNo, 'block:', starti, startj, sizei, sizej, tile

         start(1)=starti
         start(2)=startj
         !count(1)=sizei
         !count(2)=sizej

         do s=1, size(staggerLocList)
            if (coordTypeKindLocal == ESMF_TYPEKIND_R8) then
              call ESMF_GridGetCoord(grid, coordDim=1, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=lonPtrR8, rc=localrc)
              if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
              count=ubound(lonPtrR8)-lbound(lonPtrR8)+1
              call ESMF_GridGetCoord(grid, coordDim=2, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=latPtrR8, rc=localrc)
              if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
              !call ESMF_VMWtime(starttime, rc=localrc)
              ! Generate glocal edge coordinates and local center coordinates
              ! need to adjust the count???
              totallen = len_trim(mosaic%filenames(tile))+len_trim(mosaic%tileDirectory)
              tempname = trim(mosaic%tileDirectory)//trim(mosaic%filenames(tile))
              call ESMF_GridSpecReadStagger(trim(tempname),sizex, sizey, lonPtrR8, latPtrR8, &
                  staggerLoc=staggerLocList(s), &
                  start=start, count=count, rc=localrc)
              if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
            else
              call ESMF_GridGetCoord(grid, coordDim=1, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=lonPtrR4, rc=localrc)
              if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
              count=ubound(lonPtrR4)-lbound(lonPtrR4)+1
              call ESMF_GridGetCoord(grid, coordDim=2, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=latPtrR4, rc=localrc)
              if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
              !call ESMF_VMWtime(starttime, rc=localrc)
              ! Generate glocal edge coordinates and local center coordinates
              ! need to adjust the count???
              totallen = len_trim(mosaic%filenames(tile))+len_trim(mosaic%tileDirectory)
              tempname = trim(mosaic%tileDirectory)//trim(mosaic%filenames(tile))
              call ESMF_GridSpecReadStagger(trim(tempname),sizex, sizey, lonPtrR4, latPtrR4, &
                  staggerLoc=staggerLocList(s), &
                  start=start, count=count, rc=localrc)
              if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
            endif
         enddo
         !call ESMF_VMWtime(starttime, rc=localrc)
         !call ESMF_GridSpecReadTile(trim(tempname),sizex, sizey, lonPtr, latPtr, &
         !   cornerLon=lonCornerPtr, cornerLat=latCornerPtr, &
         !   start=start, count=count, rc=localrc)
         !if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
         !   ESMF_CONTEXT, rcToReturn=rc)) return
         !call ESMF_VMWtime(endtime, rc=localrc)

         !print *, 'Create CS size ', sizex, sizey, 'in', (endtime-starttime)*1000.0, ' msecs'
       enddo !localDe
    endif  !present(staggerLocList)

    ! Create another distgrid with user specified decomposition
    if (present(decompflagPTile) .or. present(regDecompPTile) .or. &
        present(delabelList) .or. present(delayout)) then
      newdistgrid = ESMF_DistGridCreate(&
        minIndexPTile=minIndexPTile, maxIndexPTile=maxIndexPTile, &
        regDecompPTile=regDecompPTile, &
        decompflagPTile=decompflagPTile, &
        delabelList = delabelList, &
        indexflag=ESMF_INDEX_DELOCAL, connectionList=connectionList, &
        delayout = delayout, &
        rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return
      newgrid = ESMF_GridCreate(grid, newdistgrid, name=name, rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
         ESMF_CONTEXT, rcToReturn=rc)) return
      ! Destroy old grid
      call ESMF_GridDestroy(grid, rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

      ! Destroy old distgrid
      call ESMF_DistGridDestroy(distgrid, rc=localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

      ESMF_GridCreateMosaicReg = newgrid
    else
      ESMF_GridCreateMosaicReg = grid
    endif

    ! - deallocate connectionList
    deallocate(connectionList)
    deallocate(minIndexPTile, maxIndexPTile)
  else  ! one tile case
    ! Figure out if it is a global grid or a regional grid
    totallen = len_trim(mosaic%filenames(1))+len_trim(mosaic%tileDirectory)
    tempname = trim(mosaic%tileDirectory)//trim(mosaic%filenames(1))
    call ESMF_GridspecQueryTileGlobal(trim(tempname), isGlobal, rc=localrc)
    if (present(regDecompPTile)) then
      regDecomp = regDecompPTile(:,1)
    else
      ! use default decomposition
      regDecomp(1) = PetCnt
      regDecomp(2) = 1
    endif
    totalDE = regDecomp(1)*regDecomp(2)
    if (present(decompflagPTile)) then
      decompflag = decompflagPTile(:,1)
    else
      decompflag = ESMF_DECOMP_BALANCED
    endif
    allocate(PetMap(regDecomp(1), regDecomp(2), 1))
    allocate(PetMap1D(totalDE))
    allocate(demap(0:totalDE-1))
    if (present(delayout)) then
       call ESMF_DELayoutGet(delayout, petMap = petMap1D, &
            localDeCount=decount, localDeToDeMap=demap, rc=localrc)
       if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
           ESMF_CONTEXT, rcToReturn=rc)) return
    else
       !Create a default delayout
       defaultdelayout = ESMF_DELayoutCreate(decount=totalDE, rc=localrc)
       if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
           ESMF_CONTEXT, rcToReturn=rc)) return
       call ESMF_DELayoutGet(defaultdelayout, petMap = petMap1D, &
            localDeCount=decount, localDeToDeMap=demap, rc=localrc)
       if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
           ESMF_CONTEXT, rcToReturn=rc)) return
    endif
    k=1
    do j=1,regDecomp(2)
      do i=1,regDecomp(1)
         PetMap(i,j,1)=PetMap1D(k)
         k=k+1
      enddo
    enddo
    deallocate(PetMap1D)

    if (isGlobal) then
     grid = ESMF_GridCreate1PeriDim(regDecomp, decompFlag, &
        minIndex=(/1,1/), maxIndex=(/sizex,sizey/), &
        indexflag=localIndexFlag, &
        coordTypeKind=coordTypeKindLocal, &
        coordSys=ESMF_COORDSYS_SPH_DEG, name=name, &
        petMap = petMap, &
        rc=localrc)
    else
     grid = ESMF_GridCreateNoPeriDim(regDecomp, decompFlag, &
        minIndex=(/1,1/), maxIndex=(/sizex,sizey/), &
        indexflag=localIndexFlag, &
        coordTypeKind=coordTypeKindLocal, &
        coordSys=ESMF_COORDSYS_SPH_DEG, name=name, &
        petMap = petMap, &
        rc=localrc)
    endif
    deallocate(PetMap)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
         ESMF_CONTEXT, rcToReturn=rc)) return

    call ESMF_GridGet(grid, distgrid=distgrid, rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
         ESMF_CONTEXT, rcToReturn=rc)) return

    allocate(minIndexPDe(2,totalDE), maxIndexPDe(2,totalDE))
    call ESMF_DistgridGet(distgrid, minIndexPDe=minIndexPDe, maxIndexPDe = maxIndexPDe, &
                          rc=localrc)
    if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
         ESMF_CONTEXT, rcToReturn=rc)) return

    if (present(staggerLocList)) then
       do s=1, size(staggerLocList)
          if (coordTypeKindLocal == ESMF_TYPEKIND_R8) then
            call ESMF_GridAddCoord(grid, staggerloc=staggerLocList(s), rc=localrc)
            if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                ESMF_CONTEXT, rcToReturn=rc)) return
            do localDe = 0,decount-1
               call ESMF_GridGetCoord(grid, coordDim=1, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=lonPtrR8, rc=localrc)
               if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return

               start(1)=minIndexPDe(1,demap(localDe)+1)
               start(2)=minIndexPDe(2,demap(localDe)+1)
               count=ubound(lonPtrR8)-lbound(lonPtrR8)+1
               call ESMF_GridGetCoord(grid, coordDim=2, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=latPtrR8, rc=localrc)
               if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
               !call ESMF_VMWtime(starttime, rc=localrc)
               ! Generate glocal edge coordinates and local center coordinates
               ! need to adjust the count???
               call ESMF_GridSpecReadStagger(trim(tempname),sizex, sizey, lonPtrR8, latPtrR8, &
                  staggerLoc=staggerLocList(s), &
                  start=start, count=count, rc=localrc)
               if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
            enddo
          else  !! R4
            call ESMF_GridAddCoord(grid, staggerloc=staggerLocList(s), rc=localrc)
            if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                ESMF_CONTEXT, rcToReturn=rc)) return
            do localDe = 0,decount-1
               call ESMF_GridGetCoord(grid, coordDim=1, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=lonPtrR4, rc=localrc)
               if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return

               start(1)=minIndexPDe(1,demap(localDe)+1)
               start(2)=minIndexPDe(2,demap(localDe)+1)
               count=ubound(lonPtrR4)-lbound(lonPtrR4)+1
               call ESMF_GridGetCoord(grid, coordDim=2, localDe=localDe, &
                  staggerloc=staggerLocList(s), farrayPtr=latPtrR4, rc=localrc)
               if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
               !call ESMF_VMWtime(starttime, rc=localrc)
               ! Generate glocal edge coordinates and local center coordinates
               ! need to adjust the count???
               call ESMF_GridSpecReadStagger(trim(tempname),sizex, sizey, lonPtrR4, latPtrR4, &
                  staggerLoc=staggerLocList(s), &
                  start=start, count=count, rc=localrc)
               if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
                  ESMF_CONTEXT, rcToReturn=rc)) return
            enddo
         endif  
      enddo
    endif

    ESMF_GridCreateMosaicReg = grid
    deallocate(minIndexPDe, maxIndexPDe)
  endif

  ! Get rid of mosaic info
  call ESMF_MosaicDestroy(mosaic, rc=localrc)
  if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
       ESMF_CONTEXT, rcToReturn=rc)) return 

  return

end function ESMF_GridCreateMosaicReg