initialize_modify_advertised.F90 Source File


This file depends on

sourcefile~~initialize_modify_advertised.f90~~EfferentGraph sourcefile~initialize_modify_advertised.f90 initialize_modify_advertised.F90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~initialize_modify_advertised.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) initialize_modify_advertised_smod
   implicit none

contains

   module recursive subroutine initialize_modify_advertised(this, importState, exportState, clock, unusable, rc)
      class(OuterMetaComponent), target, intent(inout) :: this
      ! optional arguments
      type(ESMF_State) :: importState
      type(ESMF_State) :: exportState
      type(ESMF_Clock) :: clock
      class(KE), optional, intent(in) :: unusable
      integer, optional, intent(out) :: rc

      integer :: status
      character(*), parameter :: PHASE_NAME = 'GENERIC::INIT_MODIFY_ADVERTISED'

      call apply_to_children(this, set_child_geom, _RC)
      call this%run_custom(ESMF_METHOD_INITIALIZE, PHASE_NAME, _RC)
      call recurse(this, phase_idx=GENERIC_INIT_MODIFY_ADVERTISED, _RC)

      call self_advertise(this, _RC)
      call process_connections(this, _RC)

      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(unusable)
      _UNUSED_DUMMY(importState)
      _UNUSED_DUMMY(exportState)
      _UNUSED_DUMMY(clock)
   contains

      subroutine set_child_geom(this, child_meta, rc)
         class(OuterMetaComponent), target, intent(inout) :: this
         type(OuterMetaComponent), target, intent(inout) ::  child_meta
         integer, optional, intent(out) :: rc
         
         associate(kind => child_meta%component_spec%geometry_spec%kind)
           _RETURN_IF(kind /= GEOMETRY_FROM_PARENT)

           if (allocated(this%geom)) then
              call child_meta%set_geom(this%geom)
           end if
           if (allocated(this%vertical_grid)) then
              call child_meta%set_vertical_grid(this%vertical_grid)
           end if
         end associate
      
         _RETURN(ESMF_SUCCESS)
      end subroutine set_child_geom

   end subroutine initialize_modify_advertised
   

   subroutine self_advertise(this, unusable, rc)
      class(OuterMetaComponent), target, intent(inout) :: this
      class(KE), optional, intent(in) :: unusable
      integer, optional, intent(out) :: rc
      
      integer :: status

      call this%registry%set_blanket_geometry(this%geom, this%vertical_grid, _RC)

      _RETURN(_SUCCESS)
      _UNUSED_DUMMY(unusable)
   end subroutine self_advertise

   subroutine process_connections(this, rc)
      class(OuterMetaComponent), intent(inout) :: this
      integer, optional, intent(out) :: rc

      integer :: status
      type(ConnectionVectorIterator) :: iter
      class(Connection), pointer :: c

      associate (e => this%component_spec%connections%end())
        iter = this%component_spec%connections%begin()
        do while (iter /= e)
           c => iter%of()
           call c%connect(this%registry, _RC)
           call iter%next()
        end do
      end associate

      _RETURN(_SUCCESS)
   end subroutine process_connections

end submodule initialize_modify_advertised_smod