function ESMF_GridCreateFrmGridCoord(grid, staggerloc, coord, scale, offset, rc)
!
! !RETURN VALUE:
type(ESMF_Grid) :: ESMF_GridCreateFrmGridCoord
!
! !ARGUMENTS:
type(ESMF_Grid), intent(in) :: grid
type(ESMF_StaggerLoc), intent(in), optional :: staggerloc
real(ESMF_KIND_R8), intent(in) :: coord(:)
real(ESMF_KIND_R8), intent(in), optional :: scale
real(ESMF_KIND_R8), intent(in), optional :: offset
integer, intent(out), optional :: rc
!
! !DESCRIPTION:
!
! This function creates a new 3D {\tt ESMF\_Grid} object by adding an
! undistributed vertical dimension to an existing 2D {\tt ESMF\_Grid} object,
! then setting the values of the new vertical coordinate to those provided in
! the Fortran array {\tt coord}. These values can be linearly transformed
! before being set as vertical coordinates using the optional arguments
! {\tt scale} and {\tt offset}, according the the formula:
! \begin{equation}
! \vec v' = \texttt{(scale)}\,\vec v + \texttt{offset}.
! \end{equation}
!
! The arguments are:
! \begin{description}
! \item[grid]
! The original 2D {\tt ESMF\_Grid} object.
! \item[{[staggerloc]}]
! The stagger location for the new vertical coordinate.
! Please see Section~\ref{const:staggerloc} for a list
! of predefined stagger locations. If not present, defaults to
! ESMF\_STAGGERLOC\_CENTER.
! \item[coord]
! Valid native Fortran array containing the values of the undistributed vertical
! coordinate in the new 3D grid.
! \item[{[scale]}]
! Scale factor to apply to the provided {\tt coord} data.
! \item[{[offset]}]
! Offset to apply to the provided {\tt coord} data.
! \item[{[rc]}]
! Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
! \end{description}
!
!EOPI
! local variables
logical :: isPresent
integer :: localrc
integer :: localDe, localDeCount
integer :: k, lsize
integer :: minIndx, maxIndx
integer, dimension(3) :: lbnd, ubnd
real(ESMF_KIND_R8) :: scale_factor, add_offset
real(ESMF_KIND_R8), pointer :: fptrIn3d(:,:,:)
type(ESMF_Grid) :: newgrid
! begin
if (present(rc)) rc = ESMF_SUCCESS
newgrid = ESMF_GridCreateFrmGrid(grid, maxIndex=size(coord), rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
! if staggerloc provided, check if present in new 3D grid
isPresent = .false.
call ESMF_GridGetCoord(newgrid, staggerloc=staggerloc, &
isPresent=isPresent, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
if (.not.isPresent) then
call ESMF_LogSetError(ESMF_RC_NOT_VALID, &
msg="This stagger location was not included in the new grid", &
ESMF_CONTEXT, rcToReturn=rc)
return
end if
! get localDeCount
call ESMF_GridGet(newgrid, localDeCount=localDeCount, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
! load vertical coordinate
scale_factor = 1._ESMF_KIND_R8
add_offset = 0._ESMF_KIND_R8
if (present(scale)) scale_factor = scale
if (present(offset)) add_offset = offset
do localDe = 0, localDeCount - 1
! get coordinate pointer from new grid
call ESMF_GridGetCoord(newgrid, coordDim=3, localDE=localDe, &
staggerloc=staggerloc, &
computationalLBound=lbnd, computationalUBound=ubnd, &
farrayPtr=fptrIn3d, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, ESMF_ERR_PASSTHRU, &
ESMF_CONTEXT, rcToReturn=rc)) return
! check allocated memory size
lsize = ubnd(3)-lbnd(3)+1
if (lsize /= size(coord)) then
call ESMF_LogSetError(ESMF_RC_NOT_VALID, &
msg="size of coord array does not match internal coordinate size",&
ESMF_CONTEXT, rcToReturn=rc)
return
end if
do k = 1, lsize
fptrIn3d(lbnd(1):ubnd(1),lbnd(2):ubnd(2),k+lbnd(3)-1) = scale_factor * coord(k) + add_offset
end do
end do
ESMF_GridCreateFrmGridCoord = newgrid
end function ESMF_GridCreateFrmGridCoord