InvalidSpec.F90 Source File


This file depends on

sourcefile~~invalidspec.f90~~EfferentGraph sourcefile~invalidspec.f90 InvalidSpec.F90 sourcefile~abstractactionspec.f90 AbstractActionSpec.F90 sourcefile~invalidspec.f90->sourcefile~abstractactionspec.f90 sourcefile~actualconnectionpt.f90 ActualConnectionPt.F90 sourcefile~invalidspec.f90->sourcefile~actualconnectionpt.f90 sourcefile~actualptspecptrmap.f90 ActualPtSpecPtrMap.F90 sourcefile~invalidspec.f90->sourcefile~actualptspecptrmap.f90 sourcefile~actualptvector.f90 ActualPtVector.F90 sourcefile~invalidspec.f90->sourcefile~actualptvector.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~invalidspec.f90->sourcefile~errorhandling.f90 sourcefile~extensionaction.f90 ExtensionAction.F90 sourcefile~invalidspec.f90->sourcefile~extensionaction.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~invalidspec.f90->sourcefile~keywordenforcer.f90 sourcefile~multistate.f90 MultiState.F90 sourcefile~invalidspec.f90->sourcefile~multistate.f90 sourcefile~nullaction.f90 NullAction.F90 sourcefile~invalidspec.f90->sourcefile~nullaction.f90 sourcefile~stateitemspec.f90 StateItemSpec.F90 sourcefile~invalidspec.f90->sourcefile~stateitemspec.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~invalidspec.f90->sourcefile~verticalgrid.f90 sourcefile~actualconnectionpt.f90->sourcefile~keywordenforcer.f90 sourcefile~virtualconnectionpt.f90 VirtualConnectionPt.F90 sourcefile~actualconnectionpt.f90->sourcefile~virtualconnectionpt.f90 sourcefile~actualptspecptrmap.f90->sourcefile~actualconnectionpt.f90 sourcefile~actualptspecptrmap.f90->sourcefile~stateitemspec.f90 sourcefile~actualptvector.f90->sourcefile~actualconnectionpt.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.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~verticalgrid.f90->sourcefile~errorhandling.f90 sourcefile~esmf_utilities.f90->sourcefile~errorhandling.f90 sourcefile~virtualconnectionpt.f90->sourcefile~keywordenforcer.f90

Files dependent on this one

sourcefile~~invalidspec.f90~~AfferentGraph sourcefile~invalidspec.f90 InvalidSpec.F90 sourcefile~make_itemspec.f90 make_itemSpec.F90 sourcefile~make_itemspec.f90->sourcefile~invalidspec.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_InvalidSpec
   use mapl3g_StateItemSpec
   use mapl3g_AbstractActionSpec
   use mapl3g_MultiState
   use mapl3g_ActualConnectionPt
   use mapl3g_ExtensionAction
   use mapl3g_ActualPtVector
   use mapl3g_ActualPtSpecPtrMap
   use mapl3g_NullAction
   use mapl3g_VerticalGrid
   use esmf, only: ESMF_FieldBundle
   use esmf, only: ESMF_Geom
   use esmf, only: ESMF_State
   use esmf, only: ESMF_SUCCESS
   use mapl_KeywordEnforcer
   use mapl_ErrorHandling
   implicit none
   private
  
   public :: InvalidSpec
  
   type, extends(StateItemSpec) :: InvalidSpec
     private
   contains
      procedure :: create
      procedure :: destroy
      procedure :: allocate
      
      procedure :: connect_to
      procedure :: can_connect_to
      procedure :: requires_extension
      procedure :: add_to_state
      procedure :: add_to_bundle

      procedure :: make_extension
      procedure :: extension_cost
      procedure :: set_geometry => set_geometry

      procedure :: make_adapters
   end type InvalidSpec


contains
  


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

      _RETURN(ESMF_SUCCESS)
      _UNUSED_DUMMY(this)
   end subroutine create


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

      integer :: status

      _FAIL('Attempt to use invalid spec')

      _UNUSED_DUMMY(this)
   end subroutine destroy


   subroutine allocate(this, rc)
      class(InvalidSpec), intent(inout) :: this
      integer, optional, intent(out) :: rc

      integer :: status

      _FAIL('Attempt to use invalid spec')

      _UNUSED_DUMMY(this)
   end subroutine allocate


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

      integer :: status

      _FAIL('Attempt to use invalid spec')

      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(src_spec)
      _UNUSED_DUMMY(actual_pt)
   end subroutine connect_to


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

      _FAIL('Attempt to use invalid spec')
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(src_spec)
   end function can_connect_to


   logical function requires_extension(this, src_spec)
      class(InvalidSpec), intent(in) :: this
      class(StateItemSpec), intent(in) :: src_spec

      requires_extension = .false.
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(src_spec)
   end function requires_extension


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

      _FAIL('Attempt to use invalid spec')

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

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

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

      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(bundle)
   end subroutine add_to_bundle

   recursive subroutine make_extension(this, dst_spec, new_spec, action, rc)
      class(InvalidSpec), intent(in) :: this
      class(StateItemSpec), intent(in) :: dst_spec
      class(StateItemSpec), allocatable, intent(out) :: new_spec
      class(ExtensionAction), allocatable, intent(out) :: action
      integer, optional, intent(out) :: rc

      integer :: status

      action = NullAction() ! default
      new_spec = this

      _FAIL('attempt to use item of type InvalidSpec')
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(dst_spec)
   end subroutine make_extension

   integer function extension_cost(this, src_spec, rc) result(cost)
      class(InvalidSpec), intent(in) :: this
      class(StateItemSpec), intent(in) :: src_spec
      integer, optional, intent(out) :: rc

      cost = -1
      _FAIL('Attempt to use item of type InvalidSpec')
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(src_spec)

   end function extension_cost

   subroutine set_geometry(this, geom, vertical_grid, rc)
      class(InvalidSpec), intent(inout) :: this
      type(ESMF_Geom), optional, intent(in) :: geom
      class(VerticalGrid), optional, intent(in) :: vertical_grid
      integer, optional, intent(out) :: rc

      _FAIL('Attempt to initialize item of type InvalidSpec')
      _UNUSED_DUMMY(this)
      _UNUSED_DUMMY(geom)
      _UNUSED_DUMMY(vertical_grid)
   end subroutine set_geometry

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

      allocate(adapters(0))

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


end module mapl3g_InvalidSpec