MODULE:
module NUOPC_Driver
DESCRIPTION:
Driver component that drives Model, Mediator, and Connector components. The default is to use explicit time stepping. For every Driver time step the same sequence of Model, Mediator, and Connector Run methods are called. The run sequence is fully customizable.
SUPER:
ESMF_GridComp
USE DEPENDENCIES:
use ESMF
SETSERVICES:
subroutine routine_SetServices(gcomp, rc)
type(ESMF_GridComp) :: gcomp
integer, intent(out) :: rc
INITIALIZE:
RUN:
FINALIZE:
INTERNALSTATE:
label_InternalState
type type_InternalState
type(type_InternalStateStruct), pointer :: wrap
end type
type type_InternalStateStruct
integer :: modelCount
type(type_PetList), pointer :: modelPetLists(:)
type(type_PetList), pointer :: connectorPetLists(:,:)
!--- private members ----------------------------------------
type(ESMF_GridComp), pointer :: modelComp(:)
type(ESMF_State), pointer :: modelIS(:), modelES(:)
type(ESMF_CplComp), pointer :: connectorComp(:,:)
type(NUOPC_RunSequence), pointer :: runSeq(:)! size may increase dynamic.
integer :: runPhaseToRunSeqMap(10)
type(ESMF_Clock) :: driverClock ! clock of the parent
end type
type type_PetList
integer, pointer :: petList(:) !lists that are set here transfer ownership
end type
MODULE:
module NUOPC_DriverAtmOcn
DESCRIPTION:
This is a specialization of the NUOPC_Driver generic component, driving a coupled Atmosphere-Ocean model. The default is to use explicit time stepping. Each driver time step, the same sequence of Atmosphere, Ocean and connector Run methods are called. The run sequence is fully customizable for cases where explicit time stepping is not suitable.
SUPER:
NUOPC_Driver
USE DEPENDENCIES:
use ESMF
SETSERVICES:
subroutine routine_SetServices(gcomp, rc)
type(ESMF_GridComp) :: gcomp
integer, intent(out) :: rc
INITIALIZE:
RUN:
FINALIZE:
INTERNALSTATE:
label_InternalState
type type_InternalState
type(type_InternalStateStruct), pointer :: wrap
end type
type type_InternalStateStruct
integer, pointer :: atmPetList(:)
integer, pointer :: ocnPetList(:)
type(ESMF_GridComp) :: atm
type(ESMF_GridComp) :: ocn
type(ESMF_State) :: atmIS, atmES
type(ESMF_State) :: ocnIS, ocnES
integer, pointer :: atm2ocnPetList(:)
integer, pointer :: ocn2atmPetList(:)
type(ESMF_CplComp) :: atm2ocn, ocn2atm
type(NUOPC_RunSequence), pointer :: runSeq(:)
end type
MODULE:
module NUOPC_DriverAtmOcnMed
DESCRIPTION:
This is a specialization of the NUOPC_Driver generic component, driving a coupled Atmosphere-Ocean-Mediator model. The default is to use explicit time stepping. Each driver time step, the same sequence of Atmosphere, Ocean, Mediator, and the connector Run methods are called. The run sequence is fully customizable for cases where explicit time stepping is not suitable.
SUPER:
NUOPC_Driver
USE DEPENDENCIES:
use ESMF
SETSERVICES:
subroutine routine_SetServices(gcomp, rc)
type(ESMF_GridComp) :: gcomp
integer, intent(out) :: rc
INITIALIZE:
RUN:
FINALIZE:
INTERNALSTATE:
label_InternalState
type type_InternalState
type(type_InternalStateStruct), pointer :: wrap
end type
type type_InternalStateStruct
integer, pointer :: atmPetList(:)
integer, pointer :: ocnPetList(:)
integer, pointer :: medPetList(:)
type(ESMF_GridComp) :: atm
type(ESMF_GridComp) :: ocn
type(ESMF_GridComp) :: med
type(ESMF_State) :: atmIS, atmES
type(ESMF_State) :: ocnIS, ocnES
type(ESMF_State) :: medIS, medES
integer, pointer :: atm2medPetList(:)
integer, pointer :: ocn2medPetList(:)
integer, pointer :: med2atmPetList(:)
integer, pointer :: med2ocnPetList(:)
type(ESMF_CplComp) :: atm2med, ocn2med
type(ESMF_CplComp) :: med2atm, med2ocn
type(NUOPC_RunSequence), pointer :: runSeq(:)
end type
MODULE:
module NUOPC_ModelBase
DESCRIPTION:
Model component with a default explicit time dependency. Each time the Run method is called the model integrates one timeStep forward on the provided Clock. The Clock must be advanced between Run calls. The component's Run method flags incompatibility if the current time of the incoming Clock does not match the current time of the model.
SUPER:
ESMF_GridComp
USE DEPENDENCIES:
use ESMF
SETSERVICES:
subroutine routine_SetServices(gcomp, rc)
type(ESMF_GridComp) :: gcomp
integer, intent(out) :: rc
INITIALIZE:
RUN:
FINALIZE:
INTERNALSTATE:
label_InternalState
type type_InternalState
type(type_InternalStateStruct), pointer :: wrap
end type
type type_InternalStateStruct
type(ESMF_Clock) :: driverClock
end type
MODULE:
module NUOPC_Model
DESCRIPTION:
Model component with a default explicit time dependency. Each time the Run method is called the model integrates one timeStep forward on the provided Clock. The Clock must be advanced between Run calls. The component's Run method flags incompatibility if the current time of the incoming Clock does not match the current time of the model.
SUPER:
NUOPC_ModelBase
USE DEPENDENCIES:
use ESMF
SETSERVICES:
subroutine routine_SetServices(gcomp, rc)
type(ESMF_GridComp) :: gcomp
integer, intent(out) :: rc
INITIALIZE:
RUN:
FINALIZE:
INTERNALSTATE:
label_InternalState
type type_InternalState
type(type_InternalStateStruct), pointer :: wrap
end type
type type_InternalStateStruct
type(ESMF_Clock) :: driverClock
end type
MODULE:
module NUOPC_Mediator
DESCRIPTION:
Mediator component with a default explicit time dependency. Each time the Run method is called, the time stamp on the imported Fields must match the current time (on both the incoming and internal Clock). Before returning, the Mediator time stamps the exported Fields with the same current time, before advancing the internal Clock one timeStep forward.
SUPER:
NUOPC_ModelBase
USE DEPENDENCIES:
use ESMF
SETSERVICES:
subroutine routine_SetServices(gcomp, rc)
type(ESMF_GridComp) :: gcomp
integer, intent(out) :: rc
INITIALIZE:
RUN:
FINALIZE:
INTERNALSTATE:
label_InternalState
type type_InternalState
type(type_InternalStateStruct), pointer :: wrap
end type
type type_InternalStateStruct
type(ESMF_Clock) :: driverClock
end type
MODULE:
module NUOPC_Connector
DESCRIPTION:
Connector component that uses a default bilinear regrid method during Run to transfer data from the connected import Fields to the connected export Fields.
SUPER:
ESMF_CplComp
USE DEPENDENCIES:
use ESMF
SETSERVICES:
subroutine routine_SetServices(cplcomp, rc)
type(ESMF_CplComp) :: cplcomp
integer, intent(out) :: rc
INITIALIZE:
RUN:
FINALIZE:
INTERNALSTATE:
label_InternalState
type type_InternalState
type(type_InternalStateStruct), pointer :: wrap
end type
type type_InternalStateStruct
type(ESMF_FieldBundle) :: srcFields
type(ESMF_FieldBundle) :: dstFields
type(ESMF_RouteHandle) :: rh
type(ESMF_State) :: state
end type
The NUOPC_RunSequence class provides a unified data structure that allows simple as well as complex time loops to be encoded and executed. There are entry points that allow different run phases to be mapped against distinctly different time loops.
Figure 2 depicts the data structures surrounding the NUOPC_RunSequence, starting with the InternalState of the NUOPC_Driver generic component.
INTERFACE:
subroutine NUOPC_RunElementAdd(runSeq, i, j, phase, rc)ARGUMENTS:
type(NUOPC_RunSequence), intent(inout), target :: runSeq
integer, intent(in) :: i, j, phase
integer, optional, intent(out) :: rc
DESCRIPTION:
Add a new RunElement at the end of an existing RunSequence. The RunElement is set to the values provided for i, j, phase.
INTERFACE:
subroutine NUOPC_RunElementAddComp(runSeq, i, j, phase, rc)ARGUMENTS:
type(NUOPC_RunSequence), intent(inout), target :: runSeq
integer, intent(in) :: i
integer, intent(in), optional :: j
integer, intent(in), optional :: phase
integer, optional, intent(out) :: rc
DESCRIPTION:
Add a new RunElement for a Component to the end of an existing RunSequence. The RunElement is set to the values provided for i, j, phase, or as determined by their defaults.
The arguments are:
INTERFACE:
subroutine NUOPC_RunElementAddLink(runSeq, slot, rc)ARGUMENTS:
type(NUOPC_RunSequence), intent(inout), target :: runSeq
integer, intent(in) :: slot
integer, optional, intent(out) :: rc
DESCRIPTION:
Add a new RunElement for a link to the end of an existing RunSequence.
The arguments are:
INTERFACE:
subroutine NUOPC_RunElementPrint(runElement, rc)ARGUMENTS:
type(NUOPC_RunElement), intent(in) :: runElement
integer, optional, intent(out) :: rc
DESCRIPTION:
Write information about runElement into the default log file.
INTERFACE:
subroutine NUOPC_RunSequenceAdd(runSeq, addCount, rc)ARGUMENTS:
type(NUOPC_RunSequence), pointer :: runSeq(:)
integer, intent(in) :: addCount
integer, optional, intent(out) :: rc
DESCRIPTION:
The incoming RunSequence vector runSeq is extended by addCount more RunSequence objects. The existing RunSequence objects are copied to the front of the new vector before the old vector is deallocated.
INTERFACE:
! Private name; call using NUOPC_RunSequenceDeallocate() subroutine NUOPC_RunSequenceArrayDeall(runSeq, rc)ARGUMENTS:
type(NUOPC_RunSequence), pointer :: runSeq(:)
integer, optional, intent(out) :: rc
DESCRIPTION:
Deallocate all of the RunElements in all of the RunSequence defined in the runSeq vector.
INTERFACE:
! Private name; call using NUOPC_RunSequenceDeallocate() subroutine NUOPC_RunSequenceSingleDeall(runSeq, rc)ARGUMENTS:
type(NUOPC_RunSequence), intent(inout) :: runSeq
integer, optional, intent(out) :: rc
DESCRIPTION:
Deallocate all of the RunElements in the RunSequence defined by runSeq.
INTERFACE:
function NUOPC_RunSequenceIterate(runSeq, runSeqIndex, runElement, rc)RETURN VALUE:
logical :: NUOPC_RunSequenceIterateARGUMENTS:
type(NUOPC_RunSequence), pointer :: runSeq(:)
integer, intent(in) :: runSeqIndex
type(NUOPC_RunElement), pointer :: runElement
integer, optional, intent(out) :: rc
DESCRIPTION:
Iterate through the RunSequence that is in position runSeqIndex in the runSeq vector. If runElement comes in unassociated, the iteration starts from the beginning. Otherwise this call takes one forward step relative to the incoming runElement, returning the next RunElement in runElement. In either case, the logical function return value is .true. if the end of iteration has not been reached by the forward step, and .false. if the end of iteration has been reached. The returned runElement is only valid for a function return value of .true..
INTERFACE:
! Private name; call using NUOPC_RunSequencePrint() subroutine NUOPC_RunSequenceSinglePrint(runSeq, rc)ARGUMENTS:
type(NUOPC_RunSequence), intent(in) :: runSeq
integer, optional, intent(out) :: rc
DESCRIPTION:
Write information about runSeq into the default log file.
INTERFACE:
! Private name; call using NUOPC_RunSequencePrint() subroutine NUOPC_RunSequenceArrayPrint(runSeq, rc)ARGUMENTS:
type(NUOPC_RunSequence), pointer :: runSeq(:)
integer, optional, intent(out) :: rc
DESCRIPTION:
Write information about the whole runSeq vector into the default log file.
INTERFACE:
subroutine NUOPC_RunSequenceSet(runSeq, clock, rc)ARGUMENTS:
type(NUOPC_RunSequence), intent(inout) :: runSeq
type(ESMF_Clock), intent(in) :: clock
integer, optional, intent(out) :: rc
DESCRIPTION:
Set the Clock member in runSeq.
INTERFACE:
subroutine NUOPC_ClockCheckSetClock(setClock, checkClock, &
setStartTimeToCurrent, rc)
ARGUMENTS:
type(ESMF_Clock), intent(inout) :: setClock
type(ESMF_Clock), intent(in) :: checkClock
logical, intent(in), optional :: setStartTimeToCurrent
integer, intent(out), optional :: rc
DESCRIPTION:
Compares setClock to checkClock to make sure they match in their current Time. Further ensures that checkClock's timeStep is a multiple of setClock's timeStep. If both these condition are satisfied then the stopTime of the setClock is set one checkClock's timeStep ahead of the current Time, taking into account the direction of the Clock.
By default the startTime of the setClock is not modified. However, if setStartTimeToCurrent == .true. the startTime of setClock is set to the currentTime of checkClock.
INTERFACE:
function NUOPC_ClockInitialize(externalClock, stabilityTimeStep, rc)RETURN VALUE:
type(ESMF_Clock) :: NUOPC_ClockInitializeARGUMENTS:
type(ESMF_Clock) :: externalClock
type(ESMF_TimeInterval), intent(in), optional :: stabilityTimeStep
integer, intent(out), optional :: rc
DESCRIPTION:
Returns a new Clock instance that is a copy of the incoming Clock, but potentially with a smaller timestep. The timestep is chosen so that the timestep of the incoming Clock (externalClock) is a multiple of the new Clock's timestep, and at the same time the new timestep is <= the stabilityTimeStep.
INTERFACE:
subroutine NUOPC_ClockPrintCurrTime(clock, string, unit, rc)ARGUMENTS:
type(ESMF_Clock), intent(in) :: clock
character(*), intent(in), optional :: string
character(*), intent(out), optional :: unit
integer, intent(out), optional :: rc
DESCRIPTION:
Writes the formatted current time of clock to unit. Prepends string if provided. If unit is present it must be an internal unit, i.e. a string variable. If unit is not present then the output is written to the default external unit (typically that would be stdout).
INTERFACE:
subroutine NUOPC_ClockPrintStartTime(clock, string, unit, rc)ARGUMENTS:
type(ESMF_Clock), intent(in) :: clock
character(*), intent(in), optional :: string
character(*), intent(out), optional :: unit
integer, intent(out), optional :: rc
DESCRIPTION:
Writes the formatted start time of clock to unit. Prepends string if provided. If unit is present it must be an internal unit, i.e. a string variable. If unit is not present then the output is written to the default external unit (typically that would be stdout).
INTERFACE:
subroutine NUOPC_ClockPrintStopTime(clock, string, unit, rc)ARGUMENTS:
type(ESMF_Clock), intent(in) :: clock
character(*), intent(in), optional :: string
character(*), intent(out), optional :: unit
integer, intent(out), optional :: rc
DESCRIPTION:
Writes the formatted stop time of clock to unit. Prepends string if provided. If unit is present it must be an internal unit, i.e. a string variable. If unit is not present then the output is written to the default external unit (typically that would be stdout).
INTERFACE:
function NUOPC_CplCompAreServicesSet(comp, rc)RETURN VALUE:
logical :: NUOPC_CplCompAreServicesSetARGUMENTS:
type(ESMF_CplComp), intent(in) :: comp
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if SetServices has been called for comp. Otherwise returns .false..
INTERFACE:
subroutine NUOPC_CplCompAttributeAdd(comp, rc)ARGUMENTS:
type(ESMF_CplComp), intent(inout) :: comp
integer, intent(out), optional :: rc
DESCRIPTION:
Adds standard NUOPC Attributes to a Coupler Component. Checks the provided importState and exportState arguments for matching Fields and adds the list as "CplList" Attribute.
This adds the standard NUOPC Coupler Attribute package: convention="NUOPC", purpose="General" to the Field. The NUOPC Coupler Attribute package extends the ESG Component Attribute package: convention="ESG", purpose="General".
The arguments are:
INTERFACE:
subroutine NUOPC_CplCompAttributeGet(comp, cplList, cplListSize, rc)ARGUMENTS:
type(ESMF_CplComp), intent(in) :: comp
character(*), intent(out), optional :: cplList(:)
integer, intent(out), optional :: cplListSize
integer, intent(out), optional :: rc
DESCRIPTION:
Accesses the "CplList" Attribute inside of comp using the convention NUOPC and purpose General. Returns with error if the Attribute is not present or not set.
INTERFACE:
subroutine NUOPC_CplCompAttributeSet(comp, importState, exportState, rc)ARGUMENTS:
type(ESMF_CplComp), intent(inout) :: comp
type(ESMF_State), intent(in) :: importState
type(ESMF_State), intent(in) :: exportState
integer, intent(out), optional :: rc
DESCRIPTION:
Checks the provided importState and exportState arguments for matching Fields and sets the coupling list as "CplList" Attribute in comp.
The arguments are:
INTERFACE:
subroutine NUOPC_FieldAttributeAdd(field, StandardName, Units, LongName, &
ShortName, Connected, rc)
ARGUMENTS:
type(ESMF_Field) :: field
character(*), intent(in) :: StandardName
character(*), intent(in), optional :: Units
character(*), intent(in), optional :: LongName
character(*), intent(in), optional :: ShortName
character(*), intent(in), optional :: Connected
integer, intent(out), optional :: rc
DESCRIPTION:
Adds standard NUOPC Attributes to a Field object. Checks the provided arguments against the NUOPC Field Dictionary. Omitted optional information is filled in using defaults out of the NUOPC Field Dictionary.
This adds the standard NUOPC Field Attribute package: convention="NUOPC", purpose="General" to the Field. The NUOPC Field Attribute package extends the ESG Field Attribute package: convention="ESG", purpose="General".
The arguments are:
INTERFACE:
subroutine NUOPC_FieldAttributeGet(field, name, value, rc)ARGUMENTS:
type(ESMF_Field), intent(in) :: field
character(*), intent(in) :: name
character(*), intent(out) :: value
integer, intent(out), optional :: rc
DESCRIPTION:
Accesses the Attribute name inside of field using the convention NUOPC and purpose General. Returns with error if the Attribute is not present or not set.
INTERFACE:
subroutine NUOPC_FieldAttributeSet(field, name, value, rc)ARGUMENTS:
type(ESMF_Field) :: field
character(*), intent(in) :: name
character(*), intent(in) :: value
integer, intent(out), optional :: rc
DESCRIPTION:
Set the Attribute name inside of field using the convention NUOPC and purpose General.
INTERFACE:
subroutine NUOPC_FieldBundleUpdateTime(srcFields, dstFields, rc)ARGUMENTS:
type(ESMF_FieldBundle), intent(in) :: srcFields
type(ESMF_FieldBundle), intent(inout) :: dstFields
integer, intent(out), optional :: rc
DESCRIPTION:
Updates the time stamp on all Fields in the dstFields FieldBundle to be the same as in the dstFields FieldBundle.
INTERFACE:
subroutine NUOPC_FieldDictionaryAddEntry(standardName, canonicalUnits, &
defaultLongName, defaultShortName, rc)
ARGUMENTS:
character(*), intent(in) :: standardName
character(*), intent(in) :: canonicalUnits
character(*), intent(in), optional :: defaultLongName
character(*), intent(in), optional :: defaultShortName
integer, intent(out), optional :: rc
DESCRIPTION:
Adds an entry to the NUOPC Field dictionary. If necessary the dictionary is first set up.
INTERFACE:
subroutine NUOPC_FieldDictionaryGetEntry(standardName, canonicalUnits, &
defaultLongName, defaultShortName, rc)
ARGUMENTS:
character(*), intent(in) :: standardName
character(*), intent(out), optional :: canonicalUnits
character(*), intent(out), optional :: defaultLongName
character(*), intent(out), optional :: defaultShortName
integer, intent(out), optional :: rc
DESCRIPTION:
Returns the canonical units, the default LongName and the default ShortName that the NUOPC Field dictionary associates with a StandardName.
INTERFACE:
function NUOPC_FieldDictionaryHasEntry(standardName, rc)RETURN VALUE:
logical :: NUOPC_FieldDictionaryHasEntryARGUMENTS:
character(*), intent(in) :: standardName
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if the NUOPC Field dictionary has an entry with the specified StandardName, .false. otherwise.
INTERFACE:
subroutine NUOPC_FieldDictionarySetup(rc)ARGUMENTS:
integer, intent(out), optional :: rcDESCRIPTION:
Setup the NUOPC Field dictionary.
INTERFACE:
function NUOPC_FieldIsAtTime(field, time, rc)RETURN VALUE:
logical :: NUOPC_FieldIsAtTimeARGUMENTS:
type(ESMF_Field), intent(in) :: field
type(ESMF_Time), intent(in) :: time
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if the Field has a timestamp that matches time. Otherwise returns .false..
INTERFACE:
subroutine NUOPC_FillCplList(importState, exportState, cplList, rc)ARGUMENTS:
type(ESMF_State), intent(in) :: importState
type(ESMF_State), intent(in) :: exportState
character(ESMF_MAXSTR), pointer :: cplList(:)
integer, intent(out), optional :: rc
DESCRIPTION:
Constructs a list of matching StandardNames of Fields in the importState and exportState. Returns this list in cplList.
The pointer argument cplList must enter this method unassociated. On return, the deallocation of the potentially associated pointer becomes the caller's responsibility.
INTERFACE:
function NUOPC_GridCompAreServicesSet(comp, rc)RETURN VALUE:
logical :: NUOPC_GridCompAreServicesSetARGUMENTS:
type(ESMF_GridComp), intent(in) :: comp
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if SetServices has been called for comp. Otherwise returns .false..
INTERFACE:
subroutine NUOPC_GridCompAttributeAdd(comp, rc)ARGUMENTS:
type(ESMF_GridComp) :: comp
integer, intent(out), optional :: rc
DESCRIPTION:
Adds standard NUOPC Attributes to a Gridded Component.
This adds the standard NUOPC GridComp Attribute package: convention="NUOPC", purpose="General" to the Gridded Component. The NUOPC GridComp Attribute package extends the CIM Component Attribute package: convention="CIM 1.5", purpose="ModelComp".
INTERFACE:
subroutine NUOPC_GridCompCheckSetClock(comp, externalClock, rc)ARGUMENTS:
type(ESMF_GridComp), intent(inout) :: comp
type(ESMF_Clock), intent(in) :: externalClock
integer, intent(out), optional :: rc
DESCRIPTION:
Compares externalClock to the Component internal Clock to make sure they match in their current Time. Further ensures that the external Clock's timeStep is a multiple of the internal Clock's timeStep. If both these condition are satisfied then the stopTime of the internal Clock is set to be reachable in one timeStep of the external Clock, taking into account the direction of the Clock.
INTERFACE:
subroutine NUOPC_GridCompSetClock(comp, externalClock, stabilityTimeStep, &
rc)
ARGUMENTS:
type(ESMF_GridComp), intent(inout) :: comp
type(ESMF_Clock), intent(in) :: externalClock
type(ESMF_TimeInterval), intent(in), optional :: stabilityTimeStep
integer, intent(out), optional :: rc
DESCRIPTION:
Sets the Component internal Clock as a copy of externalClock, but with a timeStep that is less than or equal to the stabilityTimeStep. At the same time ensures that the timeStep of the external Clock is a multiple of the internal Clock's timeStep. If the stabilityTimeStep argument is not provided then the internal Clock will simply be set as a copy of the externalClock.
INTERFACE:
recursive subroutine NUOPC_GridCompSetServices(comp, sharedObj, userRc, rc)ARGUMENTS:
type(ESMF_GridComp), intent(inout) :: comp
character(len=*), intent(in), optional :: sharedObj
integer, intent(out), optional :: userRc
integer, intent(out), optional :: rc
DESCRIPTION:
Try to find a routine called "SetServices" in the sharedObj and execute it to set the component's services. An attempt is made to find a routine that is close in name to "SetServices", allowing compiler name mangeling, i.e. upper and lower case, as well as trailing underscores.
INTERFACE:
function NUOPC_GridCreateSimpleXY(x_min, y_min, x_max, y_max, &
i_count, j_count, rc)
RETURN VALUE:
type(ESMF_Grid):: NUOPC_GridCreateSimpleXYARGUMENTS:
real(ESMF_KIND_R8), intent(in) :: x_min, x_max, y_min, y_max
integer, intent(in) :: i_count, j_count
integer, intent(out), optional :: rc
DESCRIPTION:
Creates and returns a very simple XY cartesian Grid.
INTERFACE:
! call using generic interface: NUOPC_IsCreated function NUOPC_ClockIsCreated(clock, rc)RETURN VALUE:
logical :: NUOPC_ClockIsCreatedARGUMENTS:
type(ESMF_Clock) :: clock
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if the ESMF object (here clock) is in the created state, .false. otherwise.
INTERFACE:
subroutine NUOPC_StateAdvertiseField(state, StandardName, Units, &
LongName, ShortName, name, TransferOfferGeomObject, rc)
ARGUMENTS:
type(ESMF_State), intent(inout) :: state
character(*), intent(in) :: StandardName
character(*), intent(in), optional :: Units
character(*), intent(in), optional :: LongName
character(*), intent(in), optional :: ShortName
character(*), intent(in), optional :: name
character(*), intent(in), optional :: TransferOfferGeomObject
integer, intent(out), optional :: rc
DESCRIPTION:
Advertises a Field in a State. This call checks the provided information against the NUOPC Field Dictionary. Omitted optional information is filled in using defaults out of the NUOPC Field Dictionary.
The arguments are:
INTERFACE:
subroutine NUOPC_StateAdvertiseFields(state, StandardNames, rc)ARGUMENTS:
type(ESMF_State), intent(inout) :: state
character(*), intent(in) :: StandardNames(:)
integer, intent(out), optional :: rc
DESCRIPTION:
Advertises Fields in a State. Defaults are set according to the NUOPC Field Dictionary.
The arguments are:
INTERFACE:
recursive subroutine NUOPC_StateBuildStdList(state, stdAttrNameList, &
stdItemNameList, stdConnectedList, stdFieldList, rc)
ARGUMENTS:
type(ESMF_State), intent(in) :: state
character(ESMF_MAXSTR), pointer :: stdAttrNameList(:)
character(ESMF_MAXSTR), pointer, optional :: stdItemNameList(:)
character(ESMF_MAXSTR), pointer, optional :: stdConnectedList(:)
type(ESMF_Field), pointer, optional :: stdFieldList(:)
integer, intent(out), optional :: rc
DESCRIPTION:
Constructs lists containing the StandardName, Field name, and connected status of the Fields in the state. Returns this information in the list arguments. Recursively parses through nested States.
All pointer arguments present must enter this method unassociated. On return, the deallocation of an associated pointer becomes the user responsibility.
INTERFACE:
function NUOPC_StateIsAllConnected(state, rc)RETURN VALUE:
logical :: NUOPC_StateIsAllConnectedARGUMENTS:
type(ESMF_State), intent(in) :: state
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if all the Fields in state are connected. Otherwise returns .false..
INTERFACE:
function NUOPC_StateIsAtTime(state, time, rc)RETURN VALUE:
logical :: NUOPC_StateIsAtTimeARGUMENTS:
type(ESMF_State), intent(in) :: state
type(ESMF_Time), intent(in) :: time
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if all the Fields in state have a timestamp that matches time. Otherwise returns .false..
INTERFACE:
function NUOPC_StateIsFieldConnected(state, fieldName, rc)RETURN VALUE:
logical :: NUOPC_StateIsFieldConnectedARGUMENTS:
type(ESMF_State), intent(in) :: state
character(*), intent(in) :: fieldName
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if Fields with name fieldName contained in state is connected. Otherwise returns .false..
INTERFACE:
function NUOPC_StateIsUpdated(state, count, rc)RETURN VALUE:
logical :: NUOPC_StateIsUpdatedARGUMENTS:
type(ESMF_State), intent(in) :: state
integer, intent(out), optional :: count
integer, intent(out), optional :: rc
DESCRIPTION:
Returns .true. if all the Fields in state have their "Updated" Attribute set to "true". Otherwise returns .false.. The count argument returns how many of the FIelds have the Updated" Attribtue set to "true".
INTERFACE:
subroutine NUOPC_StateRealizeField(state, field, rc)ARGUMENTS:
type(ESMF_State), intent(inout) :: state
type(ESMF_Field), intent(in) :: field
integer, intent(out), optional :: rc
DESCRIPTION:
Realizes a previously advertised Field in state.
INTERFACE:
subroutine NUOPC_StateSetTimestamp(state, clock, selective, rc)ARGUMENTS:
type(ESMF_State), intent(inout) :: state
type(ESMF_Clock), intent(in) :: clock
logical, intent(in), optional :: selective
integer, intent(out), optional :: rc
DESCRIPTION:
Sets the TimeStamp Attribute according to clock on all the Fields in state.
INTERFACE:
subroutine NUOPC_StateUpdateTimestamp(state, rootPet, rc)ARGUMENTS:
type(ESMF_State), intent(in) :: state
integer, intent(in) :: rootPet
integer, intent(out), optional :: rc
DESCRIPTION:
Updates the TimeStamp Attribute for all the Fields on all the PETs in the current VM to the TimeStamp Attribute held by the Field instance on the rootPet.
INTERFACE:
subroutine NUOPC_TimePrint(time, string, unit, rc)ARGUMENTS:
type(ESMF_Time), intent(in) :: time
character(*), intent(in), optional :: string
character(*), intent(out), optional :: unit
integer, intent(out), optional :: rc
DESCRIPTION:
Write a formatted time with or without string to unit. If unit is present it must be an internal unit, i.e. a string variable. If unit is not present then the output is written to the default external unit (typically that would be stdout).