read_restart.F90 Source File


This file depends on

sourcefile~~read_restart.f90~2~~EfferentGraph sourcefile~read_restart.f90~2 read_restart.F90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~read_restart.f90~2->sourcefile~outermetacomponent.f90 sourcefile~restarthandler.f90 RestartHandler.F90 sourcefile~read_restart.f90~2->sourcefile~restarthandler.f90

Source Code

#include "MAPL_Generic.h"

submodule (mapl3g_OuterMetaComponent) read_restart_smod
   use mapl3g_RestartHandler
   implicit none

contains

   module recursive subroutine read_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
      type(ESMF_GridComp) :: gc
      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 reads a restart
      if ((name /= "cap") .and. (name /= "HIST") .and. (name /= "EXTDATA")) then
         gc = driver%get_gridcomp()
         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%read("import", import_state, _RC)
         call restart_handler%read("internal", internal_state, _RC)
      end if
      if (name /= "HIST") then
         call recurse_read_restart(this, _RC)
      end if

      _RETURN(ESMF_SUCCESS)
   end subroutine read_restart

end submodule read_restart_smod