set_entry_point.F90 Source File


This file depends on

sourcefile~~set_entry_point.f90~~EfferentGraph sourcefile~set_entry_point.f90 set_entry_point.F90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~set_entry_point.f90->sourcefile~outermetacomponent.f90 sourcefile~actualptcomponentdrivermap.f90 ActualPtComponentDriverMap.F90 sourcefile~outermetacomponent.f90->sourcefile~actualptcomponentdrivermap.f90 sourcefile~actualptvector.f90 ActualPtVector.F90 sourcefile~outermetacomponent.f90->sourcefile~actualptvector.f90 sourcefile~componentdriver.f90 ComponentDriver.F90 sourcefile~outermetacomponent.f90->sourcefile~componentdriver.f90 sourcefile~componentdrivervector.f90 ComponentDriverVector.F90 sourcefile~outermetacomponent.f90->sourcefile~componentdrivervector.f90 sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~outermetacomponent.f90->sourcefile~componentspec.f90 sourcefile~connection.f90 Connection.F90 sourcefile~outermetacomponent.f90->sourcefile~connection.f90 sourcefile~connectionpt.f90 ConnectionPt.F90 sourcefile~outermetacomponent.f90->sourcefile~connectionpt.f90 sourcefile~connectionvector.f90 ConnectionVector.F90 sourcefile~outermetacomponent.f90->sourcefile~connectionvector.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~outermetacomponent.f90->sourcefile~errorhandling.f90 sourcefile~esmf_interfaces.f90 ESMF_Interfaces.F90 sourcefile~outermetacomponent.f90->sourcefile~esmf_interfaces.f90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~outermetacomponent.f90->sourcefile~geom_mgr.f90 sourcefile~geometryspec.f90 GeometrySpec.F90 sourcefile~outermetacomponent.f90->sourcefile~geometryspec.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~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~outermetacomponent.f90->sourcefile~keywordenforcer.f90 sourcefile~matchconnection.f90 MatchConnection.F90 sourcefile~outermetacomponent.f90->sourcefile~matchconnection.f90 sourcefile~methodphasesmap.f90 MethodPhasesMap.F90 sourcefile~outermetacomponent.f90->sourcefile~methodphasesmap.f90 sourcefile~multistate.f90 MultiState.F90 sourcefile~outermetacomponent.f90->sourcefile~multistate.f90 sourcefile~pflogger_stub.f90 pflogger_stub.F90 sourcefile~outermetacomponent.f90->sourcefile~pflogger_stub.f90 sourcefile~stateitem.f90 StateItem.F90 sourcefile~outermetacomponent.f90->sourcefile~stateitem.f90 sourcefile~stateitemspec.f90 StateItemSpec.F90 sourcefile~outermetacomponent.f90->sourcefile~stateitemspec.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~outermetacomponent.f90->sourcefile~stateregistry.f90 sourcefile~usersetservices.f90 UserSetServices.F90 sourcefile~outermetacomponent.f90->sourcefile~usersetservices.f90 sourcefile~variablespec.f90 VariableSpec.F90 sourcefile~outermetacomponent.f90->sourcefile~variablespec.f90 sourcefile~variablespecvector.f90 VariableSpecVector.F90 sourcefile~outermetacomponent.f90->sourcefile~variablespecvector.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~outermetacomponent.f90->sourcefile~verticalgrid.f90 sourcefile~virtualconnectionpt.f90 VirtualConnectionPt.F90 sourcefile~outermetacomponent.f90->sourcefile~virtualconnectionpt.f90

Source Code

#include "MAPL_Generic.h"

submodule (mapl3g_OuterMetaComponent) set_entry_point_smod
   implicit none

contains

   module subroutine set_entry_point(this, method_flag, userProcedure, unusable, phase_name, rc)
      class(OuterMetaComponent), intent(inout) :: this
      type(ESMF_Method_Flag), intent(in) :: method_flag
      procedure(I_Run) :: userProcedure
      class(KE), optional, intent(in) :: unusable
      character(len=*), optional, intent(in) :: phase_name
      integer, optional, intent(out) ::rc

      integer :: status
      character(:), allocatable :: phase_name_
      type(ESMF_GridComp) :: user_gridcomp
      logical :: found

      if (present(phase_name)) then
         phase_name_ = phase_name
      else
         phase_name_ = get_default_phase_name(method_flag)
      end if
      call add_phase(this%user_phases_map, method_flag=method_flag, phase_name=phase_name_, _RC)

      associate (phase_idx => get_phase_index(this%user_phases_map%of(method_flag), phase_name=phase_name_, found=found))
        _ASSERT(found, "run phase: <"//phase_name_//"> not found.")
        user_gridcomp = this%user_gc_driver%get_gridcomp()
        call ESMF_GridCompSetEntryPoint(user_gridcomp, method_flag, userProcedure, phase=phase_idx, _RC)
      end associate

      _RETURN(ESMF_SUCCESS)
      _UNUSED_DUMMY(unusable)
   end subroutine set_entry_point

end submodule set_entry_point_smod