run.F90 Source File


This file depends on

sourcefile~~run.f90~~EfferentGraph sourcefile~run.f90 run.F90 sourcefile~couplermetacomponent.f90 CouplerMetaComponent.F90 sourcefile~run.f90->sourcefile~couplermetacomponent.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~run.f90->sourcefile~errorhandling.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~run.f90->sourcefile~griddedcomponentdriver.f90 sourcefile~methodphasesmap.f90 MethodPhasesMap.F90 sourcefile~run.f90->sourcefile~methodphasesmap.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~run.f90->sourcefile~outermetacomponent.f90

Source Code

#include "MAPL_ErrLog.h"

submodule(mapl3g_GriddedComponentDriver) run_smod
   use :: mapl_ErrorHandling
   use :: mapl3g_OuterMetaComponent
   use :: mapl3g_MethodPhasesMapUtils
   use mapl3g_CouplerMetaComponent, only: GENERIC_COUPLER_INVALIDATE, GENERIC_COUPLER_UPDATE
   implicit none

contains

   module recursive subroutine run(this, unusable, phase_idx, rc)
      class(GriddedComponentDriver), intent(inout) :: this
      class(KE), optional, intent(in) :: unusable
      integer, optional, intent(in) :: phase_idx
      integer, optional, intent(out) :: rc

      integer :: status, user_status

      _ASSERT(present(phase_idx), 'until made not optional')
      call this%run_import_couplers(_RC)
      
      associate ( &
           importState => this%states%importState, &
           exportState => this%states%exportState)

        call ESMF_GridCompRun(this%gridcomp, &
             importState=importState, &
             exportState=exportState, &
             clock=this%clock, &
             phase=phase_idx, _USERRC)

      end associate

      call this%run_export_couplers(phase_idx=phase_idx, _RC)

      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(unusable)
   end subroutine run

end submodule run_smod