ComponentSpec.F90 Source File


This file depends on

sourcefile~~componentspec.f90~~EfferentGraph sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~childspecmap.f90 ChildSpecMap.F90 sourcefile~componentspec.f90->sourcefile~childspecmap.f90 sourcefile~connection.f90 Connection.F90 sourcefile~componentspec.f90->sourcefile~connection.f90 sourcefile~connectionvector.f90 ConnectionVector.F90 sourcefile~componentspec.f90->sourcefile~connectionvector.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~componentspec.f90->sourcefile~errorhandling.f90 sourcefile~geometryspec.f90 GeometrySpec.F90 sourcefile~componentspec.f90->sourcefile~geometryspec.f90 sourcefile~variablespec.f90 VariableSpec.F90 sourcefile~componentspec.f90->sourcefile~variablespec.f90 sourcefile~variablespecvector.f90 VariableSpecVector.F90 sourcefile~componentspec.f90->sourcefile~variablespecvector.f90 sourcefile~childspec.f90 ChildSpec.F90 sourcefile~childspecmap.f90->sourcefile~childspec.f90 sourcefile~connectionvector.f90->sourcefile~connection.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90 sourcefile~geom_mgr.f90 geom_mgr.F90 sourcefile~geometryspec.f90->sourcefile~geom_mgr.f90 sourcefile~verticalgrid.f90 VerticalGrid.F90 sourcefile~geometryspec.f90->sourcefile~verticalgrid.f90 sourcefile~variablespec.f90->sourcefile~errorhandling.f90 sourcefile~actualconnectionpt.f90 ActualConnectionPt.F90 sourcefile~variablespec.f90->sourcefile~actualconnectionpt.f90 sourcefile~actualptvector.f90 ActualPtVector.F90 sourcefile~variablespec.f90->sourcefile~actualptvector.f90 sourcefile~fielddictionary.f90 FieldDictionary.F90 sourcefile~variablespec.f90->sourcefile~fielddictionary.f90 sourcefile~horizontaldimsspec.f90 HorizontalDimsSpec.F90 sourcefile~variablespec.f90->sourcefile~horizontaldimsspec.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~variablespec.f90->sourcefile~keywordenforcer.f90 sourcefile~stateitem.f90 StateItem.F90 sourcefile~variablespec.f90->sourcefile~stateitem.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~variablespec.f90->sourcefile~stateregistry.f90 sourcefile~ungriddeddims.f90 UngriddedDims.F90 sourcefile~variablespec.f90->sourcefile~ungriddeddims.f90 sourcefile~verticaldimspec.f90 VerticalDimSpec.F90 sourcefile~variablespec.f90->sourcefile~verticaldimspec.f90 sourcefile~variablespec.f90->sourcefile~verticalgrid.f90 sourcefile~virtualconnectionpt.f90 VirtualConnectionPt.F90 sourcefile~variablespec.f90->sourcefile~virtualconnectionpt.f90 sourcefile~variablespecvector.f90->sourcefile~variablespec.f90

Files dependent on this one

sourcefile~~componentspec.f90~~AfferentGraph sourcefile~componentspec.f90 ComponentSpec.F90 sourcefile~componentspecparser.f90 ComponentSpecParser.F90 sourcefile~componentspecparser.f90->sourcefile~componentspec.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~mapl_generic.f90~2->sourcefile~componentspec.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~componentspec.f90

Source Code

#include "MAPL_Generic.h"

module mapl3g_ComponentSpec
   use mapl3g_ConnectionVector
   use mapl3g_Connection
   use mapl3g_VariableSpec
   use mapl3g_VariableSpecVector
   use mapl3g_ChildSpecMap
   use mapl3g_GeometrySpec
   use mapl_ErrorHandling
   use ESMF
   implicit none
   private

   public :: ComponentSpec

   type :: ComponentSpec
      !!$      private
      type(GeometrySpec) :: geometry_spec
      type(VariableSpecVector) :: var_specs
      type(ConnectionVector) :: connections
      type(ChildSpecMap) :: children
      type(ESMF_HConfig), allocatable :: geom_hconfig ! optional
   contains
      procedure :: has_geom_hconfig
      procedure :: add_var_spec
      procedure :: add_connection
   end type ComponentSpec

   interface ComponentSpec
      module procedure new_ComponentSpec
   end interface ComponentSpec

contains

   function new_ComponentSpec(var_specs, connections) result(spec)
      type(ComponentSpec) :: spec
      type(VariableSpecVector), optional, intent(in) :: var_specs
      type(ConnectionVector), optional, intent(in) :: connections

      if (present(var_specs)) spec%var_specs = var_specs
      if (present(connections)) spec%connections = connections
   end function new_ComponentSpec

   logical function has_geom_hconfig(this)
      class(ComponentSpec), intent(in) :: this
      has_geom_hconfig = allocated(this%geom_hconfig)
   end function has_geom_hconfig

   subroutine add_var_spec(this, var_spec)
      class(ComponentSpec), intent(inout) :: this
      class(VariableSpec), intent(in) :: var_spec
      call this%var_specs%push_back(var_spec)
   end subroutine add_var_spec


   subroutine add_connection(this, conn)
      class(ComponentSpec), intent(inout) :: this
      class(Connection), intent(in) :: conn
      call this%connections%push_back(conn)
   end subroutine add_connection




end module mapl3g_ComponentSpec