function ESMF_GridCreate1PeriDimUfrmR(minIndex, maxIndex, &
minCornerCoord, maxCornerCoord, &
keywordEnforcer, regDecomp, decompFlag, &
polekindflag, coordSys, staggerLocList, &
ignoreNonPeriCoord, petMap, name, rc)
!
! !RETURN VALUE:
type(ESMF_Grid) :: ESMF_GridCreate1PeriDimUfrmR
!
! !ARGUMENTS:
integer, intent(in), optional :: minIndex(:)
integer, intent(in) :: maxIndex(:)
real(ESMF_KIND_R8), intent(in) :: minCornerCoord(:)
real(ESMF_KIND_R8), intent(in) :: maxCornerCoord(:)
type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
integer, intent(in), optional :: regDecomp(:)
type(ESMF_Decomp_Flag), intent(in), optional :: decompflag(:)
type(ESMF_PoleKind_Flag), intent(in), optional :: polekindflag(2)
type(ESMF_CoordSys_Flag), intent(in), optional :: coordSys
type(ESMF_StaggerLoc), intent(in), optional :: staggerLocList(:)
logical, intent(in), optional :: ignoreNonPeriCoord
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.
! The periodic dimension in the resulting grid will be dimension 1.
! The dimension with the poles at either end (i.e. the pole dimension)
! will be dimension 2.
!
! The grid will have its coordinates uniformly spread between the
! ranges specified by the user. The coordinates are ESMF\_TYPEKIND\_R8.
! Currently, this method only fills the center stagger with coordinates, and
! the {\tt minCornerCoord} and {\tt maxCornerCoord} arguments give the boundaries of
! the center stagger.
!
! 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 following arguments have been set to non-typical values and so
! there is a reasonable possibility that they may change in the future
! to be inconsistent with other Grid create interfaces:
!
! The arguments coordDep1, coordDep2, and coordDep3 have internally
! been set to 1, 2, and 3 respectively.
! This was done because this call creates a uniform grid and so only 1D arrays
! are needed to hold the coordinates. This means the coordinate arrays
! will be 1D.
!
! The argument indexFlag has internally been set to ESMF\_INDEX\_GLOBAL. This
! means that the grid created from this function will have a global index space.
!
! 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[minCornerCoord]
! The coordinates of the corner of the grid that corresponds to {\tt minIndex}.
! size(minCornerCoord) must be equal to size(maxIndex).
! \item[maxCornerCoord]
! The coordinates of the corner of the grid that corresponds to {\tt maxIndex}.
! size(maxCornerCoord) must be equal to size(maxIndex).
! \item[{[regDecomp]}]
! A ndims-element array specifying how the grid is decomposed.
! Each entry is the number of decounts for that dimension.
! \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[{[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[{[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[{[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, then
! no staggers are added or filled.
! \item[{[ignoreNonPeriCoord]}]
! If .true., do not check if the coordinates for the periodic dimension (i.e. dim=1) specify a full periodic range (e.g. 0 to 360 degrees).
! If not specified, defaults to .false. .
! \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_Grid) :: grid
integer :: localrc
integer :: dimCount
integer :: s
logical :: localIgnoreNonPeriCoord
type(ESMF_CoordSys_Flag) :: localCoordSys
real(ESMF_KIND_R8), parameter :: PiX2= &
6.2831853071795862319959269370883703232_ESMF_KIND_R8
! Initialize return code; assume failure until success is certain
localrc = ESMF_RC_NOT_IMPL
if (present(rc)) rc = ESMF_RC_NOT_IMPL
! Create grid structure
if (size(maxIndex) < 3) then
grid=ESMF_GridCreate1PeriDim(regDecomp=regDecomp, &
decompFlag=decompFlag, &
minIndex=minIndex, &
maxIndex=maxIndex, &
coordSys=coordSys, &
coordTypeKind=ESMF_TYPEKIND_R8, &
polekindflag=polekindflag, &
coordDep1=(/1/), &
coordDep2=(/2/), &
indexFlag=ESMF_INDEX_GLOBAL, &
petMap=petMap, &
name=name, &
rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
else
grid=ESMF_GridCreate1PeriDim(regDecomp=regDecomp, &
decompFlag=decompFlag, &
minIndex=minIndex, &
maxIndex=maxIndex, &
coordSys=coordSys, &
coordTypeKind=ESMF_TYPEKIND_R8, &
polekindflag=polekindflag, &
coordDep1=(/1/), &
coordDep2=(/2/), &
coordDep3=(/3/), &
indexFlag=ESMF_INDEX_GLOBAL, &
petMap=petMap, &
name=name, &
rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
endif
! Get CoordSys of Grid
call ESMF_GridGet(grid, coordSys=localCoordSys, rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
! Handle optional ignoreNonPeriCoord argument
if (present(ignoreNonPeriCoord)) then
localIgnoreNonPeriCoord=ignoreNonPeriCoord
else
localIgnoreNonPeriCoord=.false.
endif
! Make sure periodic dimension has periodic coords
if (.not. localIgnoreNonPeriCoord) then
if (localCoordSys .eq. ESMF_COORDSYS_SPH_DEG) then
if (abs(abs(maxCornerCoord(1) - minCornerCoord(1))- &
360.0_ESMF_KIND_R8) > Tiny(maxCornerCoord(1))) then
call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_VALUE, &
msg=" coords in periodic dim (i.e. 1) are not periodic "// &
"(i.e. max coord(1)-min coord(1) /= 360)", &
ESMF_CONTEXT, rcToReturn=rc)
return
endif
else if (coordSys .eq. ESMF_COORDSYS_SPH_RAD) then
if (abs(abs(maxCornerCoord(1) - minCornerCoord(1))- &
PiX2) > Tiny(maxCornerCoord(1))) then
call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_VALUE, &
msg=" coords in periodic dim (i.e. 1) are not periodic "// &
"(i.e. max coord(1)-min coord(1) /= 2Pi)", &
ESMF_CONTEXT, rcToReturn=rc)
return
endif
endif
endif
! Get dimCount
call ESMF_GridGet(grid, dimCount=dimCount, rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
! Check size of coordinate arrays
if (size(minCornerCoord) .ne. dimCount) then
call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
msg="- minCornerCoord array must be the same dimension as the grid (i.e. maxIndex)", &
ESMF_CONTEXT, rcToReturn=rc)
return
endif
if (size(maxCornerCoord) .ne. dimCount) then
call ESMF_LogSetError(rcToCheck=ESMF_RC_ARG_SIZE, &
msg="- maxCornerCoord array must be the same dimension as the grid (i.e. maxIndex)", &
ESMF_CONTEXT, rcToReturn=rc)
return
endif
! Fill staggers
if (present(staggerLocList)) then
do s=1, size(staggerLocList)
call ESMF_GridFillStaggerCoordsUfrm(grid, &
minCornerCoord, maxCornerCoord, &
staggerloc=staggerLocList(s), &
rc=localrc)
if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
enddo
endif
! Set Grid
ESMF_GridCreate1PeriDimUfrmR=grid
! Return successfully
if (present(rc)) rc = ESMF_SUCCESS
end function ESMF_GridCreate1PeriDimUfrmR