ESMFL_MOD Module

MODULE: ESMFL_MOD

Author: GMAO SI-Team

The following macro causes a variable to appear to be “used” according to the compiler. This is a kludge to avoid excessive warnings. In most cases, a better fix would be to modify the the procedure interface, but it is impractical in the short term.

Note that the conditional is never satisfied and a reasonable compiler will optimize the line away. (Hopefully without reintroducing the warning!)


Uses

  • module~~esmfl_mod~~UsesGraph module~esmfl_mod ESMFL_MOD ESMF ESMF module~esmfl_mod->ESMF iso_fortran_env iso_fortran_env module~esmfl_mod->iso_fortran_env module~mapl_basemod MAPL_BaseMod module~esmfl_mod->module~mapl_basemod module~mapl_commsmod MAPL_CommsMod module~esmfl_mod->module~mapl_commsmod module~mapl_constants MAPL_Constants module~esmfl_mod->module~mapl_constants module~mapl_exceptionhandling MAPL_ExceptionHandling module~esmfl_mod->module~mapl_exceptionhandling module~mapl_basemod->module~mapl_constants module~mapl_base MAPL_Base module~mapl_basemod->module~mapl_base module~mapl_maplgrid mapl_MaplGrid module~mapl_basemod->module~mapl_maplgrid module~mapl_rangemod MAPL_RangeMod module~mapl_basemod->module~mapl_rangemod module~mapl_commsmod->ESMF module~mapl_commsmod->module~mapl_basemod module~mapl_commsmod->module~mapl_constants module~mapl_commsmod->module~mapl_exceptionhandling module~mapl_shmemmod MAPL_ShmemMod module~mapl_commsmod->module~mapl_shmemmod mpi mpi module~mapl_commsmod->mpi module~mapl_constants->iso_fortran_env module~mapl_internalconstantsmod MAPL_InternalConstantsMod module~mapl_constants->module~mapl_internalconstantsmod module~mapl_mathconstantsmod MAPL_MathConstantsMod module~mapl_constants->module~mapl_mathconstantsmod module~mapl_physicalconstantsmod MAPL_PhysicalConstantsMod module~mapl_constants->module~mapl_physicalconstantsmod module~mapl_errorhandlingmod MAPL_ErrorHandlingMod module~mapl_exceptionhandling->module~mapl_errorhandlingmod module~mapl_throwmod MAPL_ThrowMod module~mapl_exceptionhandling->module~mapl_throwmod module~mapl_base->ESMF module~mapl_base->iso_fortran_env module~mapl_errorhandlingmod->module~mapl_throwmod module~mapl_errorhandlingmod->mpi module~mapl_internalconstantsmod->iso_fortran_env module~mapl_maplgrid->ESMF module~mapl_maplgrid->module~mapl_errorhandlingmod module~mapl_constantsmod MAPL_ConstantsMod module~mapl_maplgrid->module~mapl_constantsmod module~mapl_keywordenforcermod MAPL_KeywordEnforcerMod module~mapl_maplgrid->module~mapl_keywordenforcermod module~pflogger pflogger module~mapl_maplgrid->module~pflogger module~mapl_mathconstantsmod->iso_fortran_env module~mapl_physicalconstantsmod->iso_fortran_env module~mapl_physicalconstantsmod->module~mapl_mathconstantsmod module~mapl_rangemod->iso_fortran_env module~mapl_rangemod->module~mapl_exceptionhandling module~mapl_shmem MAPL_Shmem module~mapl_shmemmod->module~mapl_shmem module~mapl_constantsmod->module~mapl_constants module~mapl_shmem->iso_fortran_env module~mapl_shmem->module~mapl_constants module~mapl_shmem->mpi iso_c_binding iso_c_binding module~mapl_shmem->iso_c_binding module~pfl_keywordenforcermod PFL_KeywordEnforcerMod module~pflogger->module~pfl_keywordenforcermod module~pfl_logger PFL_Logger module~pflogger->module~pfl_logger module~pfl_loggermanager PFL_LoggerManager module~pflogger->module~pfl_loggermanager module~pfl_severitylevels PFL_SeverityLevels module~pflogger->module~pfl_severitylevels module~pfl_wraparray PFL_WrapArray module~pflogger->module~pfl_wraparray

Used by

  • module~~esmfl_mod~~UsedByGraph module~esmfl_mod ESMFL_MOD module~bundletestsupport BundleTestSupport module~bundletestsupport->module~esmfl_mod module~mapl_capgridcompmod MAPL_CapGridCompMod module~mapl_capgridcompmod->module~esmfl_mod module~mapl_cfiomod MAPL_CFIOMod module~mapl_cfiomod->module~esmfl_mod module~mapl_epochswathmod MAPL_EpochSwathMod module~mapl_epochswathmod->module~esmfl_mod module~mapl_extdatagridcomp2g MAPL_ExtDataGridComp2G module~mapl_extdatagridcomp2g->module~esmfl_mod module~mapl_extdatagridcompmod MAPL_ExtDataGridCompMod module~mapl_extdatagridcompmod->module~esmfl_mod module~mapl_extdatamask MAPL_ExtDataMask module~mapl_extdatamask->module~esmfl_mod module~mapl_genericcplcompmod MAPL_GenericCplCompMod module~mapl_genericcplcompmod->module~esmfl_mod module~mapl_genericmod MAPL_GenericMod module~mapl_genericmod->module~esmfl_mod module~mapl_griddediomod MAPL_GriddedIOMod module~mapl_griddediomod->module~esmfl_mod module~mapl_historygridcompmod MAPL_HistoryGridCompMod module~mapl_historygridcompmod->module~esmfl_mod module~mapl_locstreammod MAPL_LocStreamMod module~mapl_locstreammod->module~esmfl_mod module~mapl_orbgridcompmod MAPL_OrbGridCompMod module~mapl_orbgridcompmod->module~esmfl_mod module~mapl_resourcemod MAPL_ResourceMod module~mapl_resourcemod->module~esmfl_mod module~mapl_simplebundlemod MAPL_SimpleBundleMod module~mapl_simplebundlemod->module~esmfl_mod module~maplbase_mod MAPLBase_Mod module~maplbase_mod->module~esmfl_mod program~comp_testing_driver comp_testing_driver program~comp_testing_driver->module~esmfl_mod program~regrid_util Regrid_Util program~regrid_util->module~esmfl_mod

Interfaces

public interface ESMFL_Add2Bundle

  • private subroutine Add2Bundle(BUN, mergedBUN, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUN
    type(ESMF_FieldBundle), intent(inout) :: mergedBUN
    integer, intent(out), optional :: rc

public interface ESMFL_Bundle2State

  • private subroutine Bundle2State(BUN, STA, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUN
    type(ESMF_State), intent(inout) :: STA
    integer, intent(out), optional :: rc

public interface ESMFL_BundleAddState

  • private recursive subroutine BundleAddState_(BUNDLE, STATE, rc, GRID, VALIDATE)

    The recursive subrountine BundleAddState_ adds contents of State to Bundle. Extracts fields from an ESMF State and adds them to a ESMF Bundle. In essesence, it serializes an ESMF state in a flat Bundle. The BUNDLE must have been created prior to calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUNDLE
    type(ESMF_State), intent(inout) :: STATE
    integer, optional :: rc
    type(ESMF_Grid), intent(in), optional :: GRID
    logical, intent(in), optional :: VALIDATE

public interface ESMFL_BundleGetPointerToData

  • private subroutine ESMFL_BundleGetPointerByIndex2(BUNDLE, INDEX, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUNDLE
    integer, intent(in) :: INDEX
    real, pointer :: PTR(:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_BundleGetPointerByIndex3(BUNDLE, INDEX, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUNDLE
    integer, intent(in) :: INDEX
    real, pointer :: PTR(:,:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_BundleGetPointerByName2(BUNDLE, NAME, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUNDLE
    character(len=*), intent(in) :: NAME
    real, pointer :: PTR(:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_BundleGetPointerByName3(BUNDLE, NAME, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUNDLE
    character(len=*), intent(in) :: NAME
    real, pointer :: PTR(:,:,:)
    integer, intent(out), optional :: RC

public interface ESMFL_Bundles2Bundle

  • private subroutine Bundles2Bundle(BUN1, BUN2, mergedBUN, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: BUN1
    type(ESMF_FieldBundle), intent(inout) :: BUN2
    type(ESMF_FieldBundle), intent(inout) :: mergedBUN
    integer, intent(out), optional :: rc

public interface ESMFL_Diff

  • private subroutine StateDiff(srcSTA, dstSTA, rc)

    Determine the diff of two state.

    History

    • 19Apr2006 Cruz Initial code.

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: srcSTA
    type(ESMF_State), intent(inout), optional :: dstSTA
    integer, intent(out), optional :: rc
  • private subroutine BundleDiff(srcBUN, dstBUN, rc)

    The subroutine BundleDiff determines the diff of two bundles.

    History

    • 24Apr2006 Cruz Initial code.

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: srcBUN
    type(ESMF_FieldBundle), intent(inout), optional :: dstBUN
    integer, intent(out), optional :: rc

    return code

public interface ESMFL_FCOLLECT

  • private subroutine ESMFL_FCOLLECT_I4(GRID, FULLINPUT, INPUT, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Grid), intent(in) :: GRID
    integer, intent(inout) :: FULLINPUT(:)
    integer, intent(in) :: INPUT(:)
    integer, intent(out), optional :: rc
  • private subroutine ESMFL_FCOLLECT_R4(GRID, FULLINPUT, INPUT, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Grid), intent(in) :: GRID
    real, intent(inout) :: FULLINPUT(:)
    real, intent(in) :: INPUT(:)
    integer, intent(out), optional :: rc
  • private subroutine ESMFL_FCOLLECT_R8(GRID, FULLINPUT, INPUT, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Grid), intent(in) :: GRID
    real(kind=ESMF_KIND_R8), intent(inout) :: FULLINPUT(:)
    real(kind=ESMF_KIND_R8), intent(in) :: INPUT(:)
    integer, intent(out), optional :: rc

public interface ESMFL_FieldGetPointerToData

  • private subroutine ESMFL_FieldGetPtrToDataR4_1(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R4), pointer :: PTR(:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_FieldGetPtrToDataR4_2(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R4), pointer :: PTR(:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_FieldGetPtrToDataR4_3(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R4), pointer :: PTR(:,:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_FieldGetPtrToDataR4_4(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R4), pointer :: PTR(:,:,:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_FieldGetPtrToDataR8_1(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R8), pointer :: PTR(:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_FieldGetPtrToDataR8_2(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R8), pointer :: PTR(:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_FieldGetPtrToDataR8_3(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R8), pointer :: PTR(:,:,:)
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_FieldGetPtrToDataR8_4(Field, PTR, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(inout) :: Field
    real(kind=ESMF_KIND_R8), pointer :: PTR(:,:,:,:)
    integer, intent(out), optional :: RC

public interface ESMFL_HALO

  • private subroutine ESMFL_HALO_R4_2D(GRID, INPUT, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Grid), intent(inout) :: GRID
    real, intent(inout) :: INPUT(:,:)
    integer, intent(out), optional :: RC

public interface ESMFL_Regrid

  • private subroutine BundleRegrid(srcBUN, dstBUN, rc)

    The subroutine BundleRegrid regrids a source bundle (srcBUN) into a destination bundle (dstBUN) using hinterp. A bundle is thought of as being comprised of n 2D slices (nslices) distributed among the n PEs (ns_per_pe). The limits among each ns_per_pe region are given by n1 and n2 which are functions of mype (the local PE):

                                                         slice_pe
               1 --- n1(pe=0)  -                     -->    0
               2 ---            |                    -->    0
                  .             |_  ns_per_pe(pe=0)         .
                  .             |                           0
                  .             |                           0
                 --- n2(pe=0)  -                            0
                 --- n1(pe=1)                               1
                  .                                         .
                  .                                         .
                  .                                         .
                 --- n2(pe=1)                               1
                 --- n1(pe=2)                               2
                  .                                         .
                  .                                         .
                  .                                         .
              ns ---                                  slice_pe(ns)
                  .                                         .
                  .                                         .
                  .                                         .
         nslices --- n2(pe=n)                        -->   npe
    

    Each slice is gathered, regridded (hinterp), and scattered on a PE determined by a slice-to-PE map (slice_pe) to “load balance” the work of the serial hinterp function.

    History

    • 24Apr2006 Cruz Initial code.

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: srcBUN

    source bundle

    type(ESMF_FieldBundle), intent(inout) :: dstBUN

    destination bundle

    integer, intent(out), optional :: rc

    return code

  • private subroutine StateRegrid(srcSTA, dstSTA, rc)

    The subroutine StateRegrid regrids a state.

    History

    • 19Apr2006 Cruz Initial code.

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: srcSTA
    type(ESMF_State), intent(inout) :: dstSTA
    integer, intent(out), optional :: rc

    return code

  • private subroutine FieldRegrid1(srcFLD, Sgrid2D, dstFLD, Dgrid2D, vm, rh, fname, rc)

    The subroutine FieldRegrid1 regrids 3D fields using ESMF_FieldRegrid.

    History

    • 17Oct2005 Cruz Initial code.

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_Field), intent(in) :: srcFLD
    type(ESMF_Grid), intent(in) :: Sgrid2D
    type(ESMF_Field), intent(inout) :: dstFLD
    type(ESMF_Grid), intent(in) :: Dgrid2D
    type(ESMF_VM), intent(inout) :: vm
    type(ESMF_RouteHandle), intent(inout) :: rh
    character(len=*), intent(in) :: fname
    integer, intent(out), optional :: rc
  • private subroutine BundleRegrid1(srcBUN, Sgrid2D, dstBUN, Dgrid2D, vm, rh, rc)

    The subroutine BundleRegrid1 regrids members of a bundle using ESMF_FieldRegrid.

    History

    • 17Apr2006 Cruz Initial code.

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: srcBUN
    type(ESMF_Grid), intent(in) :: Sgrid2D
    type(ESMF_FieldBundle), intent(inout) :: dstBUN
    type(ESMF_Grid), intent(in) :: Dgrid2D
    type(ESMF_VM), intent(inout) :: vm
    type(ESMF_RouteHandle), intent(inout) :: rh
    integer, intent(out), optional :: rc

public interface ESMFL_State2Bundle

  • private subroutine State2Bundle(STA, BUN, usrfldlist, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STA
    type(ESMF_FieldBundle), intent(inout) :: BUN
    character(len=*), intent(in), optional :: usrfldlist
    integer, intent(out), optional :: rc

public interface ESMFL_StateGetPointerToData

  • private subroutine ESMFL_StateGetPtrToDataR4_1(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R4), pointer :: PTR(:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_StateGetPtrToDataR4_2(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R4), pointer :: PTR(:,:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_StateGetPtrToDataR4_3(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R4), pointer :: PTR(:,:,:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_StateGetPtrToDataR4_4(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R4), pointer :: PTR(:,:,:,:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_StateGetPtrToDataR8_1(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R8), pointer :: PTR(:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_StateGetPtrToDataR8_2(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R8), pointer :: PTR(:,:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_StateGetPtrToDataR8_3(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R8), pointer :: PTR(:,:,:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC
  • private subroutine ESMFL_StateGetPtrToDataR8_4(STATE, PTR, NAME, alloc, notFoundOK, RC)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: STATE
    real(kind=ESMF_KIND_R8), pointer :: PTR(:,:,:,:)
    character(len=*), intent(in) :: NAME
    logical, intent(in), optional :: alloc
    logical, intent(in), optional :: notFoundOK
    integer, intent(out), optional :: RC

public interface ESMFL_statistics

  • private subroutine StateStatistics(srcSTA, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_State), intent(inout) :: srcSTA
    integer, intent(out), optional :: rc
  • private subroutine BundleStatistics(srcBUN, rc)

    Arguments

    Type IntentOptional Attributes Name
    type(ESMF_FieldBundle), intent(inout) :: srcBUN
    integer, intent(out), optional :: rc

public interface MAPL_AreaMean

  • private subroutine MAPL_AreaMean_2d_r8_bitrep(qave, q, area, grid, bitreproducible, rc)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=REAL64), intent(out) :: qave
    real, intent(in) :: q(:,:)
    real, intent(in) :: area(:,:)
    type(ESMF_Grid), intent(inout) :: grid
    logical, intent(in) :: bitreproducible
    integer, intent(out), optional :: rc
  • private subroutine MAPL_AreaMean_2d_r8(qave, q, area, grid, rc)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=REAL64), intent(out) :: qave
    real, intent(in) :: q(:,:)
    real, intent(in) :: area(:,:)
    type(ESMF_Grid), intent(inout) :: grid
    integer, intent(out), optional :: rc

Functions

public function ESMFL_StateFieldIsNeeded(STATE, NAME, RC) result(NEEDED)

Arguments

Type IntentOptional Attributes Name
type(ESMF_State), intent(inout) :: STATE
character(len=*), intent(in) :: NAME
integer, intent(out), optional :: RC

Return Value logical

public function ESMFL_field_is_undefined(field, rc) result(field_is_undefined)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Field), intent(in) :: field
integer, intent(out), optional :: rc

Return Value logical


Subroutines

public subroutine ESMFL_BundleCpyField(BUNDLE, FIELD, NAME, RC)

Arguments

Type IntentOptional Attributes Name
type(ESMF_FieldBundle), intent(inout) :: BUNDLE
type(ESMF_Field), intent(inout) :: FIELD
character(len=ESMF_MAXSTR), intent(in), optional :: NAME
integer, intent(out), optional :: RC

public subroutine ESMFL_FieldGetDims(FLD, gCPD, lCPD, lm, ar)

The subroutine ESMFL_FieldGetDims returns some grid information associated from an ESMF field.

Read more…

Arguments

Type IntentOptional Attributes Name
type(ESMF_Field), intent(inout) :: FLD
integer, intent(out), optional :: gCPD(3)
integer, intent(out), optional :: lCPD(3)
integer, intent(out), optional :: lm
integer, intent(out), optional :: ar

public subroutine ESMFL_FieldRegrid(src, dst, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Field) :: src
type(ESMF_Field) :: dst
integer, intent(out), optional :: rc

public subroutine ESMFL_GridCoordGet(GRID, coord, name, location, units, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Grid), intent(inout) :: GRID
real, dimension(:,:), pointer :: coord
character(len=*), intent(in) :: name
type(ESMF_StaggerLoc) :: location
integer :: units
integer, optional :: rc

public subroutine ESMFL_GridDistBlockSet(Egrid, ist, jst, il, jl, rlons, rlats, rc)

ESMFL_GridDistBlockSet

Read more…

Arguments

Type IntentOptional Attributes Name
type(ESMF_Grid), intent(inout) :: Egrid
integer, intent(in), dimension(:) :: ist
integer, intent(in), dimension(:) :: jst
integer, intent(in), dimension(:) :: il
integer, intent(in), dimension(:) :: jl
real(kind=REAL64), optional, dimension(:) :: rlons
real(kind=REAL64), optional, dimension(:) :: rlats
integer, intent(out), optional :: rc

return code

public subroutine ESMFL_RegridStore(srcFLD, SRCgrid2D, dstFLD, DSTgrid2D, vm, rh, rc)

Given a srcFLD and its associated 3dGrid and a dstFLD and its associated 3DGrid, the subroutine ESMFL_RegridStore creates their corresponding 2DGrids and a 2D routehandle.

Read more…

Arguments

Type IntentOptional Attributes Name
type(ESMF_Field), intent(inout) :: srcFLD
type(ESMF_Grid), intent(out) :: SRCgrid2D
type(ESMF_Field), intent(inout) :: dstFLD
type(ESMF_Grid), intent(out) :: DSTgrid2D
type(ESMF_VM), intent(in) :: vm
type(ESMF_RouteHandle), intent(inout) :: rh
integer, intent(out), optional :: rc

public subroutine ESMFL_StateFreePointers(STATE, RC)

Arguments

Type IntentOptional Attributes Name
type(ESMF_State), intent(inout) :: STATE
integer, intent(out), optional :: RC

public subroutine ESMFL_StateGetField(State, FieldName, Bundle, FieldAlias, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_State), intent(in) :: State
character(len=*), intent(in) :: FieldName(:)
type(ESMF_FieldBundle), intent(inout) :: Bundle
character(len=*), intent(in), optional :: FieldAlias(:)
integer, intent(out), optional :: rc

public subroutine ESMFL_StateGetFieldArray(state, name, array, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_State), intent(in) :: state
character(len=*), intent(in) :: name
type(ESMF_Array), intent(out) :: array
integer, intent(out), optional :: rc

public subroutine ESMFL_StateSetFieldNeeded(STATE, NAME, RC)

Arguments

Type IntentOptional Attributes Name
type(ESMF_State), intent(inout) :: STATE
character(len=*), intent(in) :: NAME
integer, intent(out), optional :: RC