CapGridComp.F90 Source File


This file depends on

sourcefile~~capgridcomp.f90~~EfferentGraph sourcefile~capgridcomp.f90 CapGridComp.F90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~capgridcomp.f90->sourcefile~errorhandling.f90 sourcefile~generic3g.f90 Generic3g.F90 sourcefile~capgridcomp.f90->sourcefile~generic3g.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~componentdriver.f90 ComponentDriver.F90 sourcefile~generic3g.f90->sourcefile~componentdriver.f90 sourcefile~esmf_hconfigutilities.f90 ESMF_HConfigUtilities.F90 sourcefile~generic3g.f90->sourcefile~esmf_hconfigutilities.f90 sourcefile~esmf_interfaces.f90 ESMF_Interfaces.F90 sourcefile~generic3g.f90->sourcefile~esmf_interfaces.f90 sourcefile~genericgridcomp.f90 GenericGridComp.F90 sourcefile~generic3g.f90->sourcefile~genericgridcomp.f90 sourcefile~griddedcomponentdriver.f90 GriddedComponentDriver.F90 sourcefile~generic3g.f90->sourcefile~griddedcomponentdriver.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~generic3g.f90->sourcefile~mapl_generic.f90~2 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~generic3g.f90->sourcefile~outermetacomponent.f90 sourcefile~outputinfo.f90 OutputInfo.F90 sourcefile~generic3g.f90->sourcefile~outputinfo.f90 sourcefile~usersetservices.f90 UserSetServices.F90 sourcefile~generic3g.f90->sourcefile~usersetservices.f90 sourcefile~verticaldimspec.f90 VerticalDimSpec.F90 sourcefile~generic3g.f90->sourcefile~verticaldimspec.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~generic3g.f90->sourcefile~verticalgrid.f90

Files dependent on this one

sourcefile~~capgridcomp.f90~~AfferentGraph sourcefile~capgridcomp.f90 CapGridComp.F90 sourcefile~cap.f90 Cap.F90 sourcefile~cap.f90->sourcefile~capgridcomp.f90 sourcefile~mapl3g.f90 mapl3g.F90 sourcefile~mapl3g.f90->sourcefile~cap.f90 sourcefile~geos.f90 GEOS.F90 sourcefile~geos.f90->sourcefile~mapl3g.f90

Source Code

#include "MAPL_Generic.h"
module mapl3g_CapGridComp
   use :: generic3g
   use :: mapl_ErrorHandling 
   use :: esmf, only: ESMF_GridComp
   use :: esmf, only: ESMF_Config
   use :: esmf, only: ESMF_HConfig
   use :: esmf, only: ESMF_State
   use :: esmf, only: ESMF_Clock
   use :: esmf, only: ESMF_METHOD_INITIALIZE
   use :: esmf, only: ESMF_METHOD_RUN
   use :: esmf, only: ESMF_SUCCESS
   implicit none

   private

   public :: setServices

   type :: CapGridComp
      character(:), allocatable :: extdata_name
      character(:), allocatable :: history_name
      character(:), allocatable :: root_name
      logical :: run_extdata
      logical :: run_history
   end type CapGridComp

   character(*), parameter :: PRIVATE_STATE = 'CapGridComp'
    
contains
   
   subroutine setServices(gridcomp, rc)
      type(ESMF_GridComp) :: gridcomp
      integer, intent(out) :: rc

      integer :: status
      type(CapGridComp), pointer :: cap
      character(:), allocatable :: extdata, history
      type(OuterMetaComponent), pointer :: outer_meta

      ! Set entry points
      call MAPL_GridCompSetEntryPoint(gridcomp, ESMF_METHOD_INITIALIZE, init, phase_name='GENERIC::INIT_USER', _RC)
      call MAPL_GridCompSetEntryPoint(gridcomp, ESMF_METHOD_RUN, run, phase_name='run', _RC)

      ! Attach private state
      _SET_NAMED_PRIVATE_STATE(gridcomp, CapGridComp, PRIVATE_STATE)
      _GET_NAMED_PRIVATE_STATE(gridcomp, CapGridComp, PRIVATE_STATE, cap)

      ! Disable extdata or history
      call MAPL_ResourceGet(gridcomp, keystring='run_extdata', value=cap%run_extdata, default=.true., _RC)
      call MAPL_ResourceGet(gridcomp, keystring='run_history', value=cap%run_history, default=.true., _RC)

      ! Get Names of children
      call MAPL_ResourceGet(gridcomp, keystring='extdata_name', value=cap%extdata_name, default='EXTDATA', _RC)
      call MAPL_ResourceGet(gridcomp, keystring='root_name', value=cap%root_name, _RC)
      call MAPL_ResourceGet(gridcomp, keystring='history_name', value=cap%history_name, default='HIST', _RC)

      if (cap%run_extdata) then 
         call MAPL_ConnectAll(gridcomp, src_comp=cap%extdata_name, dst_comp=cap%root_name, _RC)
      end if
      if (cap%run_history) then
         call MAPL_ConnectAll(gridcomp, src_comp=cap%root_name, dst_comp=cap%history_name, _RC)
      end if
      _RETURN(_SUCCESS)
   end subroutine setServices

   subroutine init(gridcomp, importState, exportState, clock, rc)
      type(ESMF_GridComp)   :: gridcomp
      type(ESMF_State)      :: importState
      type(ESMF_State)      :: exportState
      type(ESMF_Clock)      :: clock      
      integer, intent(out)  :: rc

      integer :: status
      type(CapGridComp), pointer :: cap

  _GET_NAMED_PRIVATE_STATE(gridcomp, CapGridComp, PRIVATE_STATE, cap)

      _RETURN(_SUCCESS)
   end subroutine init


   subroutine run(gridcomp, importState, exportState, clock, rc)
      type(ESMF_GridComp)   :: gridcomp
      type(ESMF_State)      :: importState
      type(ESMF_State)      :: exportState
      type(ESMF_Clock)      :: clock      
      integer, intent(out)  :: rc

      integer :: status
      type(CapGridComp), pointer :: cap

      _GET_NAMED_PRIVATE_STATE(gridcomp, CapGridComp, PRIVATE_STATE, cap)

      if (cap%run_extdata) then
         call MAPL_RunChild(gridcomp, cap%extdata_name, _RC)
      end if
      call MAPL_RunChild(gridcomp, cap%root_name, _RC)
      if (cap%run_history) then
         call MAPL_RunChild(gridcomp, cap%history_name, phase_name='run', _RC)
      end if

      _RETURN(_SUCCESS)
   end subroutine run

end module mapl3g_CapGridComp