run_clock_advance.F90 Source File


This file depends on

sourcefile~~run_clock_advance.f90~~EfferentGraph sourcefile~run_clock_advance.f90 run_clock_advance.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~run_clock_advance.f90->sourcefile~errorhandling.f90 sourcefile~griddedcomponentdrivermap.f90 GriddedComponentDriverMap.F90 sourcefile~run_clock_advance.f90->sourcefile~griddedcomponentdrivermap.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~run_clock_advance.f90->sourcefile~outermetacomponent.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~griddedcomponentdrivermap.f90->sourcefile~griddedcomponentdriver.f90 sourcefile~outermetacomponent.f90->sourcefile~griddedcomponentdrivermap.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~outermetacomponent.f90->sourcefile~griddedcomponentdriver.f90 sourcefile~innermetacomponent.f90 InnerMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~innermetacomponent.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.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

Source Code

#include "MAPL_Generic.h"

submodule (mapl3g_OuterMetaComponent) run_clock_advance_smod
   use mapl3g_GenericPhases
   use mapl3g_GriddedComponentDriverMap
   use mapl_ErrorHandling
   implicit none

contains

   module recursive subroutine run_clock_advance(this, unusable, rc)
      class(OuterMetaComponent), target, intent(inout) :: this
      ! optional arguments
      class(KE), optional, intent(in) :: unusable
      integer, optional, intent(out) :: rc

      integer :: status
      type(GriddedComponentDriverMapIterator) :: iter
      type(GriddedComponentDriver), pointer :: child
      type(StringVector), pointer :: run_phases
      logical :: found
      integer :: phase

      associate(e => this%children%ftn_end())
        iter = this%children%ftn_begin()
        do while (iter /= e)
           call iter%next()
           child => iter%second()
           call child%run(phase_idx=GENERIC_RUN_CLOCK_ADVANCE, _RC)
        end do
      end associate

      call this%user_gc_driver%clock_advance(_RC)

      run_phases => this%get_phases(ESMF_METHOD_RUN)
      phase = get_phase_index(run_phases, phase_name='GENERIC::RUN_CLOCK_ADVANCE', found=found)
      if (found) then
         call this%user_gc_driver%run(phase_idx=phase, _RC)
      end if

      _RETURN(ESMF_SUCCESS)
      _UNUSED_DUMMY(unusable)
   end subroutine run_clock_advance

end submodule run_clock_advance_smod