finalize.F90 Source File


This file depends on

sourcefile~~finalize.f90~2~~EfferentGraph sourcefile~finalize.f90~2 finalize.F90 sourcefile~griddedcomponentdrivermap.f90 GriddedComponentDriverMap.F90 sourcefile~finalize.f90~2->sourcefile~griddedcomponentdrivermap.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~finalize.f90~2->sourcefile~outermetacomponent.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~griddedcomponentdrivermap.f90->sourcefile~griddedcomponentdriver.f90 sourcefile~outermetacomponent.f90->sourcefile~griddedcomponentdrivermap.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~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~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) finalize_smod
   use mapl3g_GriddedComponentDriverMap
   implicit none (type, external)

contains

   module recursive subroutine finalize(this, importState, exportState, clock, unusable, rc)
      class(OuterMetaComponent), 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

      type(GriddedComponentDriver), pointer :: child
      type(GriddedComponentDriverMapIterator) :: iter
      integer :: status
      character(*), parameter :: PHASE_NAME = 'GENERIC::FINALIZE_USER'
      type(StringVector), pointer :: finalize_phases
      logical :: found

      finalize_phases => this%user_phases_map%at(ESMF_METHOD_FINALIZE, _RC)
      ! User gridcomp may not have any given phase; not an error condition if not found.
      associate (phase => get_phase_index(finalize_phases, phase_name=phase_name, found=found))
        _RETURN_UNLESS(found)

        ! TODO:  Should user finalize be after children finalize?

        ! TODO:  Should there be a phase option here?  Probably not
        ! right as is when things get more complicated.

        call this%run_custom(ESMF_METHOD_FINALIZE, PHASE_NAME, _RC)

        associate(b => this%children%begin(), e => this%children%end())
          iter = b
          do while (iter /= e)
             child => iter%second()
             call child%finalize(phase_idx=GENERIC_FINALIZE_USER, _RC)
             call iter%next()
          end do
        end associate
      end associate

      _RETURN(ESMF_SUCCESS)
      _UNUSED_DUMMY(importState)
      _UNUSED_DUMMY(exportState)
      _UNUSED_DUMMY(clock)
      _UNUSED_DUMMY(unusable)
   end subroutine finalize

end submodule finalize_smod