StateSpec.F90 Source File


This file depends on

sourcefile~~statespec.f90~~EfferentGraph sourcefile~statespec.f90 StateSpec.F90 sourcefile~abstractactionspec.f90 AbstractActionSpec.F90 sourcefile~statespec.f90->sourcefile~abstractactionspec.f90 sourcefile~actualconnectionpt.f90 ActualConnectionPt.F90 sourcefile~statespec.f90->sourcefile~actualconnectionpt.f90 sourcefile~actualptvector.f90 ActualPtVector.F90 sourcefile~statespec.f90->sourcefile~actualptvector.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~statespec.f90->sourcefile~errorhandling.f90 sourcefile~extensionaction.f90 ExtensionAction.F90 sourcefile~statespec.f90->sourcefile~extensionaction.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~statespec.f90->sourcefile~keywordenforcer.f90 sourcefile~multistate.f90 MultiState.F90 sourcefile~statespec.f90->sourcefile~multistate.f90 sourcefile~nullaction.f90 NullAction.F90 sourcefile~statespec.f90->sourcefile~nullaction.f90 sourcefile~stateitemspec.f90 StateItemSpec.F90 sourcefile~statespec.f90->sourcefile~stateitemspec.f90 sourcefile~stateitemspecmap.f90 StateItemSpecMap.F90 sourcefile~statespec.f90->sourcefile~stateitemspecmap.f90 sourcefile~variablespec.f90 VariableSpec.F90 sourcefile~statespec.f90->sourcefile~variablespec.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~statespec.f90->sourcefile~verticalgrid.f90 sourcefile~actualconnectionpt.f90->sourcefile~keywordenforcer.f90 sourcefile~virtualconnectionpt.f90 VirtualConnectionPt.F90 sourcefile~actualconnectionpt.f90->sourcefile~virtualconnectionpt.f90 sourcefile~actualptvector.f90->sourcefile~actualconnectionpt.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~extensionaction.f90->sourcefile~errorhandling.f90 sourcefile~multistate.f90->sourcefile~errorhandling.f90 sourcefile~multistate.f90->sourcefile~keywordenforcer.f90 sourcefile~esmf_utilities.f90 ESMF_Utilities.F90 sourcefile~multistate.f90->sourcefile~esmf_utilities.f90 sourcefile~nullaction.f90->sourcefile~errorhandling.f90 sourcefile~nullaction.f90->sourcefile~extensionaction.f90 sourcefile~stateitemspec.f90->sourcefile~actualptvector.f90 sourcefile~stateitemspec.f90->sourcefile~errorhandling.f90 sourcefile~stateitemspec.f90->sourcefile~extensionaction.f90 sourcefile~aspectcollection.f90 AspectCollection.F90 sourcefile~stateitemspec.f90->sourcefile~aspectcollection.f90 sourcefile~stateitemaspect.f90 StateItemAspect.F90 sourcefile~stateitemspec.f90->sourcefile~stateitemaspect.f90 sourcefile~stateitemspecmap.f90->sourcefile~stateitemspec.f90 sourcefile~variablespec.f90->sourcefile~actualconnectionpt.f90 sourcefile~variablespec.f90->sourcefile~actualptvector.f90 sourcefile~variablespec.f90->sourcefile~errorhandling.f90 sourcefile~variablespec.f90->sourcefile~keywordenforcer.f90 sourcefile~variablespec.f90->sourcefile~verticalgrid.f90 sourcefile~variablespec.f90->sourcefile~aspectcollection.f90 sourcefile~attributesaspect.f90 AttributesAspect.F90 sourcefile~variablespec.f90->sourcefile~attributesaspect.f90 sourcefile~fielddictionary.f90 FieldDictionary.F90 sourcefile~variablespec.f90->sourcefile~fielddictionary.f90 sourcefile~frequencyaspect.f90 FrequencyAspect.F90 sourcefile~variablespec.f90->sourcefile~frequencyaspect.f90 sourcefile~geomaspect.f90 GeomAspect.F90 sourcefile~variablespec.f90->sourcefile~geomaspect.f90 sourcefile~horizontaldimsspec.f90 HorizontalDimsSpec.F90 sourcefile~variablespec.f90->sourcefile~horizontaldimsspec.f90 sourcefile~stateitem.f90 StateItem.F90 sourcefile~variablespec.f90->sourcefile~stateitem.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~variablespec.f90->sourcefile~stateregistry.f90 sourcefile~typekindaspect.f90 TypekindAspect.F90 sourcefile~variablespec.f90->sourcefile~typekindaspect.f90 sourcefile~ungriddeddims.f90 UngriddedDims.F90 sourcefile~variablespec.f90->sourcefile~ungriddeddims.f90 sourcefile~ungriddeddimsaspect.f90 UngriddedDimsAspect.F90 sourcefile~variablespec.f90->sourcefile~ungriddeddimsaspect.f90 sourcefile~unitsaspect.f90 UnitsAspect.F90 sourcefile~variablespec.f90->sourcefile~unitsaspect.f90 sourcefile~verticaldimspec.f90 VerticalDimSpec.F90 sourcefile~variablespec.f90->sourcefile~verticaldimspec.f90 sourcefile~verticalgridaspect.f90 VerticalGridAspect.F90 sourcefile~variablespec.f90->sourcefile~verticalgridaspect.f90 sourcefile~variablespec.f90->sourcefile~virtualconnectionpt.f90 sourcefile~verticalgrid.f90->sourcefile~errorhandling.f90

Files dependent on this one

sourcefile~~statespec.f90~~AfferentGraph sourcefile~statespec.f90 StateSpec.F90 sourcefile~make_itemspec.f90 make_itemSpec.F90 sourcefile~make_itemspec.f90->sourcefile~statespec.f90 sourcefile~test_addfieldspec.pf Test_AddFieldSpec.pf sourcefile~test_addfieldspec.pf->sourcefile~statespec.f90 sourcefile~initialize_advertise.f90 initialize_advertise.F90 sourcefile~initialize_advertise.f90->sourcefile~make_itemspec.f90 sourcefile~test_modelverticalgrid.pf Test_ModelVerticalGrid.pf sourcefile~test_modelverticalgrid.pf->sourcefile~make_itemspec.f90

Source Code

#include "MAPL_Generic.h"

module mapl3g_StateSpec

   use mapl_KeywordEnforcer
   use mapl_ErrorHandling
   use mapl3g_StateItemSpec
   use mapl3g_AbstractActionSpec
   use mapl3g_StateItemSpecMap
   use mapl3g_VariableSpec
   use mapl3g_VerticalGrid
   use mapl3g_MultiState
   use mapl3g_ActualConnectionPt
   use mapl3g_ActualPtVector
   use mapl3g_ExtensionAction
   use mapl3g_NullAction
   use ESMF

   implicit none
   private

   public :: StateSpec
   type, extends(StateItemSpec) :: StateSpec
      private
      type(ESMF_State) :: payload
      type(StateItemSpecMap) :: item_specs
   contains
      procedure :: set_geometry
      procedure :: add_item
      procedure :: get_item

      procedure :: create
      procedure :: destroy
      procedure :: allocate
      
      procedure :: connect_to
      procedure :: can_connect_to
      procedure :: make_adapters

      procedure :: add_to_state
      procedure :: add_to_bundle

      procedure :: write_formatted
   end type StateSpec

contains

   ! Nothing defined at this time.
   subroutine set_geometry(this, geom, vertical_grid, timestep, rc)
      class(StateSpec), intent(inout) :: this
      type(ESMF_Geom), optional, intent(in) :: geom
      class(VerticalGrid), optional, intent(in) :: vertical_grid
      type(ESMF_TimeInterval), optional, intent(in) :: timestep
      integer, optional, intent(out) :: rc

      _RETURN(_SUCCESS)

      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(geom)
      _UNUSED_DUMMY(vertical_grid)
      _UNUSED_DUMMY(timestep)
   end subroutine set_geometry

   subroutine add_item(this, name, item)
      class(StateSpec), target, intent(inout) :: this
      character(len=*), intent(in) :: name
      class(StateItemSpec), intent(in) :: item

      call this%item_specs%insert(name, item)

   end subroutine add_item

   function get_item(this, name) result(item)
      class(StateItemSpec), pointer :: item
      class(StateSpec), target, intent(inout) :: this
      character(len=*), intent(in) :: name

      integer :: status

      item => this%item_specs%at(name, rc=status)

   end function get_item

   subroutine create(this, rc)
      class(StateSpec), intent(inout) :: this
      integer, optional, intent(out) :: rc

      integer :: status
      
      this%payload = ESMF_StateCreate(_RC)

      _RETURN(ESMF_SUCCESS)
   end subroutine create

   subroutine destroy(this, rc)
      class(StateSpec), intent(inout) :: this
      integer, optional, intent(out) :: rc

      integer :: status

      call ESMF_StateDestroy(this%payload, _RC)

      _RETURN(ESMF_SUCCESS)
   end subroutine destroy

   ! NO-OP
   subroutine allocate(this, rc)
      class(StateSpec), intent(inout) :: this
      integer, optional, intent(out) :: rc

      _RETURN(ESMF_SUCCESS)

      _UNUSED_DUMMY(this)
   end subroutine allocate

   subroutine connect_to(this, src_spec, actual_pt, rc)
      class(StateSpec), intent(inout) :: this
      class(StateItemSpec), intent(inout) :: src_spec
      type(ActualConnectionPt), intent(in) :: actual_pt ! unused
      integer, optional, intent(out) :: rc

      select type (src_spec)
      class is (StateSpec)
         this%payload = src_spec%payload
      class default
         _FAIL('Cannot connect field spec to non field spec.')
      end select

      _RETURN(ESMF_SUCCESS)
      _UNUSED_DUMMY(actual_pt)
   end subroutine connect_to

   logical function can_connect_to(this, src_spec, rc)
      class(StateSpec), intent(in) :: this
      class(StateItemSpec), intent(in) :: src_spec
      integer, optional, intent(out) :: rc

      can_connect_to = same_type_as(src_spec, this)

      _RETURN(_SUCCESS)

   end function can_connect_to

   subroutine add_to_state(this, multi_state, actual_pt, rc)
      class(StateSpec), intent(in) :: this
      type(MultiState), intent(inout) :: multi_state
      type(ActualConnectionPt), intent(in) :: actual_pt
      integer, optional, intent(out) :: rc

      _FAIL('unimplemented')

      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(multi_state)
      _UNUSED_DUMMY(actual_pt)
   end subroutine add_to_state

   subroutine add_to_bundle(this, bundle, rc)
      class(StateSpec), intent(in) :: this
      type(ESMF_FieldBundle), intent(inout) :: bundle
      integer, optional, intent(out) :: rc

      _FAIL('Attempt to use item of type InvalidSpec')

      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(bundle)
   end subroutine add_to_bundle

   subroutine write_formatted(this, unit, iotype, v_list, iostat, iomsg)
      class(StateSpec), intent(in) :: this
      integer, intent(in) :: unit
      character(*), intent(in) :: iotype
      integer, intent(in) :: v_list(:)
      integer, intent(out) :: iostat
      character(*), intent(inout) :: iomsg

      write(unit, "(a)", iostat=iostat, iomsg=iomsg) "StateSpec(write not implemented yet)"
   end subroutine write_formatted

   function make_adapters(this, goal_spec, rc) result(adapters)
      type(StateItemAdapterWrapper), allocatable :: adapters(:)
      class(StateSpec), intent(in) :: this
      class(StateItemSpec), intent(in) :: goal_spec
      integer, optional, intent(out) :: rc

      allocate(adapters(0))
      _FAIL('unimplemented')

      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(goal_spec)
   end function make_adapters

end module mapl3g_StateSpec