SimpleLeafGridComp.F90 Source File


This file depends on

sourcefile~~simpleleafgridcomp.f90~~EfferentGraph sourcefile~simpleleafgridcomp.f90 SimpleLeafGridComp.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~simpleleafgridcomp.f90->sourcefile~errorhandling.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~simpleleafgridcomp.f90->sourcefile~mapl_generic.f90~2 sourcefile~scratchpad.f90 scratchpad.F90 sourcefile~simpleleafgridcomp.f90->sourcefile~scratchpad.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~mapl_generic.f90~2->sourcefile~errorhandling.f90 sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~mapl_generic.f90~2->sourcefile~componentspec.f90 sourcefile~esmf_interfaces.f90 ESMF_Interfaces.F90 sourcefile~mapl_generic.f90~2->sourcefile~esmf_interfaces.f90 sourcefile~extensionfamily.f90 ExtensionFamily.F90 sourcefile~mapl_generic.f90~2->sourcefile~extensionfamily.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~mapl_generic.f90~2->sourcefile~griddedcomponentdriver.f90 sourcefile~hconfig_get.f90 hconfig_get.F90 sourcefile~mapl_generic.f90~2->sourcefile~hconfig_get.f90 sourcefile~innermetacomponent.f90 InnerMetaComponent.F90 sourcefile~mapl_generic.f90~2->sourcefile~innermetacomponent.f90 sourcefile~internalconstants.f90 InternalConstants.F90 sourcefile~mapl_generic.f90~2->sourcefile~internalconstants.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~mapl_generic.f90~2->sourcefile~keywordenforcer.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~mapl_generic.f90~2->sourcefile~outermetacomponent.f90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~mapl_generic.f90~2->sourcefile~pflogger_stub.f90 sourcefile~stateitemextension.f90 StateItemExtension.F90 sourcefile~mapl_generic.f90~2->sourcefile~stateitemextension.f90 sourcefile~stateitemspec.f90 StateItemSpec.F90 sourcefile~mapl_generic.f90~2->sourcefile~stateitemspec.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~mapl_generic.f90~2->sourcefile~stateregistry.f90 sourcefile~ungriddeddims.f90 UngriddedDims.F90 sourcefile~mapl_generic.f90~2->sourcefile~ungriddeddims.f90 sourcefile~usersetservices.f90 UserSetServices.F90 sourcefile~mapl_generic.f90~2->sourcefile~usersetservices.f90 sourcefile~validation.f90 Validation.F90 sourcefile~mapl_generic.f90~2->sourcefile~validation.f90 sourcefile~variablespec.f90 VariableSpec.F90 sourcefile~mapl_generic.f90~2->sourcefile~variablespec.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~mapl_generic.f90~2->sourcefile~verticalgrid.f90 sourcefile~virtualconnectionpt.f90 VirtualConnectionPt.F90 sourcefile~mapl_generic.f90~2->sourcefile~virtualconnectionpt.f90

Source Code

#include "MAPL_ErrLog.h"

! See external setservices() procedure at end of file


module SimpleLeafGridComp
   use mapl_ErrorHandling
   use esmf
   implicit none
   private

   public :: setservices

   
contains

   subroutine setservices(gc, rc)
      use mapl3g_Generic, only: MAPL_GridCompSetEntryPoint
      type(ESMF_GridComp) :: gc
      integer, intent(out) :: rc

      integer :: status

      call MAPL_GridCompSetEntryPoint(gc, ESMF_METHOD_RUN, run, _RC)
      call MAPL_GridCompSetEntryPoint(gc, ESMF_METHOD_RUN, run_extra, phase_name='extra', _RC)
      call MAPL_GridCompSetEntryPoint(gc, ESMF_METHOD_INITIALIZE, init, _RC)
      call MAPL_GridCompSetEntryPoint(gc, ESMF_METHOD_FINALIZE, finalize, _RC)
      
      _RETURN(ESMF_SUCCESS)
   end subroutine setservices

   subroutine run(gc, importState, exportState, clock, rc)
      type(ESMF_GridComp) :: gc
      type(ESMF_State) :: importState
      type(ESMF_State) :: exportState
      type(ESMF_Clock) :: clock
      integer, intent(out) :: rc

      call append_message(gc, 'wasRun')
      
      _RETURN(ESMF_SUCCESS)
   end subroutine run
   
   subroutine run_extra(gc, importState, exportState, clock, rc)
      type(ESMF_GridComp) :: gc
      type(ESMF_State) :: importState
      type(ESMF_State) :: exportState
      type(ESMF_Clock) :: clock
      integer, intent(out) :: rc

      call append_message(gc, 'wasRun_extra')

      _RETURN(ESMF_SUCCESS)
   end subroutine run_extra

   subroutine init(gc, importState, exportState, clock, rc)
      type(ESMF_GridComp) :: gc
      type(ESMF_State) :: importState
      type(ESMF_State) :: exportState
      type(ESMF_Clock) :: clock
      integer, intent(out) :: rc

      call append_message(gc, 'wasInit')
      
      _RETURN(ESMF_SUCCESS)
   end subroutine init
   
   subroutine finalize(gc, importState, exportState, clock, rc)
      type(ESMF_GridComp) :: gc
      type(ESMF_State) :: importState
      type(ESMF_State) :: exportState
      type(ESMF_Clock) :: clock
      integer, intent(out) :: rc

      call append_message(gc, 'wasFinal')
      
      _RETURN(ESMF_SUCCESS)
   end subroutine finalize

   subroutine append_message(gc, message)
      use scratchpad, only: append_scratchpad_message => append_message
      type(ESMF_GridComp), intent(in) :: gc
      character(*), intent(in) :: message

      character(ESMF_MAXSTR) :: name
      call ESMF_GridCompGet(gc, name=name)

      call append_scratchpad_message(message // '_' // trim(name))
   end subroutine append_message

end module SimpleLeafGridComp

subroutine setServices(gc, rc)
   use esmf, only: ESMF_GridComp
   use esmf, only: ESMF_SUCCESS
   use mapl_ErrorHandling
   use SimpleLeafGridComp, only: inner_setservices => setservices
   type(ESMF_GridComp) :: gc
   integer, intent(out) :: rc

   integer :: status

   call inner_setservices(gc, _RC)

   _RETURN(ESMF_SUCCESS)
end subroutine setServices