write_restart.F90 Source File


This file depends on

sourcefile~~write_restart.f90~~EfferentGraph sourcefile~write_restart.f90 write_restart.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~write_restart.f90->sourcefile~errorhandling.f90 sourcefile~multistate.f90 MultiState.F90 sourcefile~write_restart.f90->sourcefile~multistate.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~write_restart.f90->sourcefile~outermetacomponent.f90 sourcefile~restarthandler.f90 RestartHandler.F90 sourcefile~write_restart.f90->sourcefile~restarthandler.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~multistate.f90->sourcefile~errorhandling.f90 sourcefile~esmf_utilities.f90 ESMF_Utilities.F90 sourcefile~multistate.f90->sourcefile~esmf_utilities.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~multistate.f90->sourcefile~keywordenforcer.f90 sourcefile~componentdrivervector.f90 ComponentDriverVector.F90 sourcefile~outermetacomponent.f90->sourcefile~componentdrivervector.f90 sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~outermetacomponent.f90->sourcefile~componentspec.f90 sourcefile~esmf_interfaces.f90 ESMF_Interfaces.F90 sourcefile~outermetacomponent.f90->sourcefile~esmf_interfaces.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~outermetacomponent.f90->sourcefile~griddedcomponentdriver.f90 sourcefile~griddedcomponentdrivermap.f90 GriddedComponentDriverMap.F90 sourcefile~outermetacomponent.f90->sourcefile~griddedcomponentdrivermap.f90 sourcefile~innermetacomponent.f90 InnerMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~innermetacomponent.f90 sourcefile~outermetacomponent.f90->sourcefile~keywordenforcer.f90 sourcefile~methodphasesmap.f90 MethodPhasesMap.F90 sourcefile~outermetacomponent.f90->sourcefile~methodphasesmap.f90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~outermetacomponent.f90->sourcefile~pflogger_stub.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~outermetacomponent.f90->sourcefile~stateregistry.f90 sourcefile~usersetservices.f90 UserSetServices.F90 sourcefile~outermetacomponent.f90->sourcefile~usersetservices.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~outermetacomponent.f90->sourcefile~verticalgrid.f90 sourcefile~restarthandler.f90->sourcefile~errorhandling.f90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~restarthandler.f90->sourcefile~geom_mgr.f90 sourcefile~geomio.f90 GeomIO.F90 sourcefile~restarthandler.f90->sourcefile~geomio.f90 sourcefile~pfio.f90 pFIO.F90 sourcefile~restarthandler.f90->sourcefile~pfio.f90 sourcefile~restarthandler.f90->sourcefile~pflogger_stub.f90 sourcefile~sharedio.f90 SharedIO.F90 sourcefile~restarthandler.f90->sourcefile~sharedio.f90 sourcefile~stateget.f90 StateGet.F90 sourcefile~restarthandler.f90->sourcefile~stateget.f90

Source Code

#include "MAPL_Generic.h"

submodule (mapl3g_OuterMetaComponent) write_restart_smod
   use mapl3g_RestartHandler
   use mapl3g_MultiState
   use mapl_ErrorHandling
   implicit none (type, external)

contains

   module recursive subroutine write_restart(this, importState, exportState, clock, unusable, rc)
      class(OuterMetaComponent), target, intent(inout) :: this
      type(ESMF_State) :: importState
      type(ESMF_State) :: exportState
      type(ESMF_Clock) :: clock
      ! optional arguments
      class(KE), optional, intent(in) :: unusable
      integer, optional, intent(out) :: rc

      ! Locals
      type(GriddedComponentDriver), pointer :: driver
      character(:), allocatable :: name
      type(MultiState) :: states
      type(ESMF_State) :: internal_state, import_state
      type(ESMF_Geom) :: geom
      type(RestartHandler) :: restart_handler
      integer :: status

      driver => this%get_user_gc_driver()
      name = driver%get_name()
      ! TODO: Need a better way of identifying a gridcomp that writes restart
      if ((name /= "cap") .and. (name /= "HIST") .and. (name/="EXTDATA")) then
         geom = this%get_geom()
         states = driver%get_states()
         call states%get_state(import_state, "import", _RC)
         call states%get_state(internal_state, "internal", _RC)
         restart_handler = RestartHandler(name, geom, clock, _RC)
         call restart_handler%write("import", import_state, _RC)
         call restart_handler%write("internal", internal_state, _RC)
      end if
      if (name /= "HIST") then
         call recurse_write_restart_(this, _RC)
      end if

      _RETURN(ESMF_SUCCESS)
      _UNUSED_DUMMY(unusable)
      _UNUSED_DUMMY(exportState)
      _UNUSED_DUMMY(importState)
   end subroutine write_restart

end submodule write_restart_smod