AbstractComponent.F90 Source File


Files dependent on this one

sourcefile~~abstractcomponent.f90~~AfferentGraph sourcefile~abstractcomponent.f90 AbstractComponent.F90 sourcefile~basecomponent.f90 BaseComponent.F90 sourcefile~basecomponent.f90->sourcefile~abstractcomponent.f90 sourcefile~baseframeworkcomponent.f90 BaseFrameworkComponent.F90 sourcefile~baseframeworkcomponent.f90->sourcefile~abstractcomponent.f90 sourcefile~decoratorcomponent.f90 DecoratorComponent.F90 sourcefile~decoratorcomponent.f90->sourcefile~abstractcomponent.f90 sourcefile~maplcomponent.f90 MaplComponent.F90 sourcefile~decoratorcomponent.f90->sourcefile~maplcomponent.f90 sourcefile~driver.f90~4 driver.F90 sourcefile~driver.f90~4->sourcefile~abstractcomponent.f90 sourcefile~maplgenericcomponent.f90 MaplGenericComponent.F90 sourcefile~driver.f90~4->sourcefile~maplgenericcomponent.f90 sourcefile~usercomponent.f90 UserComponent.F90 sourcefile~driver.f90~4->sourcefile~usercomponent.f90 sourcefile~maplgeneric.f90 MaplGeneric.F90 sourcefile~maplgeneric.f90->sourcefile~abstractcomponent.f90 sourcefile~maplgeneric.f90->sourcefile~maplgenericcomponent.f90 sourcefile~maplgeneric.f90->sourcefile~maplcomponent.f90 sourcefile~stubcomponent.f90 StubComponent.F90 sourcefile~maplgeneric.f90->sourcefile~stubcomponent.f90 sourcefile~maplgenericcomponent.f90->sourcefile~abstractcomponent.f90 sourcefile~maplgenericcomponent.f90->sourcefile~baseframeworkcomponent.f90 sourcefile~maplgenericcomponent.f90->sourcefile~maplcomponent.f90 sourcefile~test_compositecomponent.pf Test_CompositeComponent.pf sourcefile~test_compositecomponent.pf->sourcefile~abstractcomponent.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_generic.f90->sourcefile~maplgeneric.f90 sourcefile~maplcomponent.f90->sourcefile~basecomponent.f90 sourcefile~test_concretecomposite.pf Test_ConcreteComposite.pf sourcefile~test_concretecomposite.pf->sourcefile~maplgenericcomponent.f90 sourcefile~comp_testing_driver.f90 Comp_Testing_Driver.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_generic.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~extdatagridcompmod.f90 ExtDataGridCompMod.F90 sourcefile~extdatagridcompmod.f90->sourcefile~mapl_generic.f90 sourcefile~extdatagridcompng.f90 ExtDataGridCompNG.F90 sourcefile~extdatagridcompng.f90->sourcefile~mapl_generic.f90 sourcefile~mapl.f90->sourcefile~mapl_generic.f90 sourcefile~mapl.f90->sourcefile~stubcomponent.f90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_capgridcomp.f90->sourcefile~extdatagridcompmod.f90 sourcefile~mapl_capgridcomp.f90->sourcefile~extdatagridcompng.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~mapl_capgridcomp.f90->sourcefile~stubcomponent.f90 sourcefile~mapl_historycollection.f90 MAPL_HistoryCollection.F90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_generic.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_historycollection.f90 sourcefile~mapl_orbgridcompmod.f90 MAPL_OrbGridCompMod.F90 sourcefile~mapl_orbgridcompmod.f90->sourcefile~mapl_generic.f90 sourcefile~stubcomponent.f90->sourcefile~maplcomponent.f90 sourcefile~usercomponent.f90->sourcefile~maplcomponent.f90 sourcefile~extdatadriver.f90 ExtDataDriver.F90 sourcefile~extdatadriver.f90->sourcefile~mapl.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~extdatagridcompmod.f90 sourcefile~extdatadrivergridcomp.f90->sourcefile~extdatagridcompng.f90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl.f90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadrivermod.f90->sourcefile~mapl.f90 sourcefile~extdataroot_gridcomp.f90 ExtDataRoot_GridComp.F90 sourcefile~extdataroot_gridcomp.f90->sourcefile~mapl.f90 sourcefile~mapl_cap.f90 MAPL_Cap.F90 sourcefile~mapl_cap.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~mapl_demo_fargparse.f90 MAPL_demo_fargparse.F90 sourcefile~mapl_demo_fargparse.f90->sourcefile~mapl.f90 sourcefile~pfio_mapl_demo.f90 pfio_MAPL_demo.F90 sourcefile~pfio_mapl_demo.f90->sourcefile~mapl.f90 sourcefile~regrid_util.f90 Regrid_Util.F90 sourcefile~regrid_util.f90->sourcefile~mapl.f90 sourcefile~time_ave_util.f90 time_ave_util.F90 sourcefile~time_ave_util.f90->sourcefile~mapl.f90 sourcefile~ut_extdata.f90 ut_ExtData.F90 sourcefile~ut_extdata.f90->sourcefile~extdatagridcompmod.f90 sourcefile~varspecdescription.f90 VarspecDescription.F90 sourcefile~varspecdescription.f90->sourcefile~mapl.f90

Source Code

module mapl_AbstractComponent
   implicit none
   private

   public :: AbstractComponent

   type, abstract :: AbstractComponent
   contains
      ! Primary methods
      procedure(i_Run), deferred :: initialize
      procedure(i_Run), deferred :: run
      procedure(i_Run), deferred :: finalize

      ! Framework methods
      procedure(i_RunChild), deferred :: run_child

      ! Accessors
      procedure(i_SetName), deferred :: set_name
      procedure(i_GetName), deferred :: get_name
      procedure(i_SetFramework), deferred :: set_framework
      procedure(i_GetFramework), deferred :: get_framework
      procedure(i_SetLogger), deferred :: set_logger
      procedure(i_GetLogger), deferred :: get_logger

      !procedure(i_GetState), deferred :: get_internal_state

   end type AbstractComponent


   abstract interface

      subroutine i_Run(this, import_state, export_state, clock, phase, unusable, rc)
         use mapl_KeywordEnforcerMod
         use ESMF
         import AbstractComponent
         implicit none
         class(AbstractComponent), intent(inout) :: this
         type(ESMF_State), intent(inout) :: import_state
         type(ESMF_State), intent(inout) :: export_state
         type(ESMF_Clock), intent(inout) :: clock
         character(*), intent(in) :: phase
         class(KeywordEnforcer), optional, intent(in) :: unusable
         integer, optional, intent(out) :: rc
      end subroutine i_Run

      subroutine i_SetName(this, name)
         import AbstractComponent
         implicit none
         class(AbstractComponent), intent(inout) :: this
         character(*), intent(in) :: name
      end subroutine i_SetName

      function i_GetName(this) result(name)
         import AbstractComponent
         implicit none
         character(:), allocatable :: name
         class(AbstractComponent), intent(in) :: this
      end function i_GetName


      subroutine i_SetFramework(this, framework)
         use mapl_SurrogateFrameworkComponent
         import AbstractComponent
         implicit none
         class(AbstractComponent), intent(inout) :: this
         class(SurrogateFrameworkComponent), target :: framework
      end subroutine i_SetFramework

      function i_GetFramework(this) result(framework)
         use mapl_SurrogateFrameworkComponent
         import AbstractComponent
         implicit none
         class(SurrogateFrameworkComponent), pointer :: framework
         class(AbstractComponent), intent(in) :: this
      end function i_GetFramework

      function i_GetState(this) result(state)
         use ESMF
         import AbstractComponent
         implicit none
         type(ESMF_State), pointer :: state
         class(AbstractComponent), target, intent(in) :: this
      end function i_GetState

      subroutine i_RunChild(this, name, clock, phase, unusable, rc)
         use mapl_KeywordEnforcerMod
         use ESMF
         import AbstractComponent
         implicit none
         class(AbstractComponent), intent(inout) :: this
         character(*), intent(in) :: name
         type(ESMF_Clock), intent(inout) :: clock
         character(*), intent(in) :: phase
         class(KeywordEnforcer), optional, intent(in) :: unusable
         integer, optional, intent(out) :: rc
      end subroutine i_RunChild

      subroutine i_SetLogger(this, logger)
         use pfl_logger, only: t_Logger => Logger
         import AbstractComponent
         implicit none
         class(AbstractComponent), intent(inout) :: this
         class(t_Logger), target :: logger

      end subroutine i_SetLogger

      function i_GetLogger(this) result(logger)
         use pfl_logger, only: t_Logger => Logger
         import AbstractComponent
         implicit none
         class(t_Logger), pointer :: logger
         class(AbstractComponent), intent(in) :: this
      end function i_GetLogger

   end interface
      
end module mapl_AbstractComponent