ConnectionPt.F90 Source File


This file depends on

sourcefile~~connectionpt.f90~~EfferentGraph sourcefile~connectionpt.f90 ConnectionPt.F90 sourcefile~virtualconnectionpt.f90 VirtualConnectionPt.F90 sourcefile~connectionpt.f90->sourcefile~virtualconnectionpt.f90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~virtualconnectionpt.f90->sourcefile~keywordenforcer.f90

Files dependent on this one

sourcefile~~connectionpt.f90~~AfferentGraph sourcefile~connectionpt.f90 ConnectionPt.F90 sourcefile~componentspecparser.f90 ComponentSpecParser.F90 sourcefile~componentspecparser.f90->sourcefile~connectionpt.f90 sourcefile~matchconnection.f90 MatchConnection.F90 sourcefile~componentspecparser.f90->sourcefile~matchconnection.f90 sourcefile~reexportconnection.f90 ReexportConnection.F90 sourcefile~componentspecparser.f90->sourcefile~reexportconnection.f90 sourcefile~simpleconnection.f90 SimpleConnection.F90 sourcefile~componentspecparser.f90->sourcefile~simpleconnection.f90 sourcefile~stateregistry.f90 StateRegistry.F90 sourcefile~componentspecparser.f90->sourcefile~stateregistry.f90 sourcefile~connect_all.f90 connect_all.F90 sourcefile~connect_all.f90->sourcefile~connectionpt.f90 sourcefile~connect_all.f90->sourcefile~matchconnection.f90 sourcefile~connectionptvector.f90 ConnectionPtVector.F90 sourcefile~connectionptvector.f90->sourcefile~connectionpt.f90 sourcefile~matchconnection.f90->sourcefile~connectionpt.f90 sourcefile~matchconnection.f90->sourcefile~simpleconnection.f90 sourcefile~matchconnection.f90->sourcefile~stateregistry.f90 sourcefile~protoextdatagc.f90 ProtoExtDataGC.F90 sourcefile~protoextdatagc.f90->sourcefile~connectionpt.f90 sourcefile~protoextdatagc.f90->sourcefile~simpleconnection.f90 sourcefile~protoextdatagc.f90->sourcefile~stateregistry.f90 sourcefile~reexportconnection.f90->sourcefile~connectionpt.f90 sourcefile~reexportconnection.f90->sourcefile~stateregistry.f90 sourcefile~simpleconnection.f90->sourcefile~connectionpt.f90 sourcefile~simpleconnection.f90->sourcefile~stateregistry.f90 sourcefile~stateregistry.f90->sourcefile~connectionpt.f90 sourcefile~test_connectionpt.pf Test_ConnectionPt.pf sourcefile~test_connectionpt.pf->sourcefile~connectionpt.f90 sourcefile~test_stateregistry.pf Test_StateRegistry.pf sourcefile~test_stateregistry.pf->sourcefile~connectionpt.f90 sourcefile~test_stateregistry.pf->sourcefile~simpleconnection.f90 sourcefile~test_stateregistry.pf->sourcefile~stateregistry.f90 sourcefile~add_child_by_name.f90 add_child_by_name.F90 sourcefile~add_child_by_name.f90->sourcefile~componentspecparser.f90 sourcefile~make_itemspec.f90 make_itemSpec.F90 sourcefile~make_itemspec.f90->sourcefile~stateregistry.f90 sourcefile~mapl_generic.f90~2 MAPL_Generic.F90 sourcefile~mapl_generic.f90~2->sourcefile~stateregistry.f90 sourcefile~modelverticalgrid.f90 ModelVerticalGrid.F90 sourcefile~modelverticalgrid.f90->sourcefile~stateregistry.f90 sourcefile~outermetacomponent.f90 OuterMetaComponent.F90 sourcefile~outermetacomponent.f90->sourcefile~stateregistry.f90 sourcefile~parse_child.f90 parse_child.F90 sourcefile~parse_child.f90->sourcefile~componentspecparser.f90 sourcefile~parse_children.f90 parse_children.F90 sourcefile~parse_children.f90->sourcefile~componentspecparser.f90 sourcefile~parse_component_spec.f90 parse_component_spec.F90 sourcefile~parse_component_spec.f90->sourcefile~componentspecparser.f90 sourcefile~parse_connections.f90 parse_connections.F90 sourcefile~parse_connections.f90->sourcefile~componentspecparser.f90 sourcefile~parse_geometry_spec.f90 parse_geometry_spec.F90 sourcefile~parse_geometry_spec.f90->sourcefile~componentspecparser.f90 sourcefile~parse_setservices.f90 parse_setservices.F90 sourcefile~parse_setservices.f90->sourcefile~componentspecparser.f90 sourcefile~parse_timestep.f90 parse_timestep.F90 sourcefile~parse_timestep.f90->sourcefile~componentspecparser.f90 sourcefile~parse_var_specs.f90 parse_var_specs.F90 sourcefile~parse_var_specs.f90->sourcefile~componentspecparser.f90 sourcefile~servicespec.f90 ServiceSpec.F90 sourcefile~servicespec.f90->sourcefile~stateregistry.f90 sourcefile~setservices.f90 SetServices.F90 sourcefile~setservices.f90->sourcefile~componentspecparser.f90 sourcefile~test_componentspecparser.pf Test_ComponentSpecParser.pf sourcefile~test_componentspecparser.pf->sourcefile~componentspecparser.f90 sourcefile~test_extensionfamily.pf Test_ExtensionFamily.pf sourcefile~test_extensionfamily.pf->sourcefile~stateregistry.f90 sourcefile~test_modelverticalgrid.pf Test_ModelVerticalGrid.pf sourcefile~test_modelverticalgrid.pf->sourcefile~stateregistry.f90 sourcefile~variablespec.f90 VariableSpec.F90 sourcefile~variablespec.f90->sourcefile~stateregistry.f90

Source Code

module mapl3g_ConnectionPt
   use mapl3g_VirtualConnectionPt
   implicit none
   private

   public :: ConnectionPt
   public :: operator(<)
   public :: operator(==)

   type :: ConnectionPt
      character(:), allocatable :: component_name
      type(VirtualConnectionPt) :: v_pt
   contains
      procedure :: is_import
      procedure :: is_export
      procedure :: is_internal
      procedure :: get_esmf_name
      procedure :: get_state_intent
   end type ConnectionPt

   interface operator(<)
      module procedure less
   end interface operator(<)

   interface operator(==)
      module procedure equal_to
   end interface operator(==)

   interface ConnectionPt
      module procedure new_connection_point_basic
      module procedure new_connection_point_simple
   end interface ConnectionPt

contains


   function new_connection_point_basic(component_name, v_pt) result(conn_pt)
      type(ConnectionPt) :: conn_pt
      character(*), intent(in) :: component_name
      type(VirtualConnectionPt), intent(in) :: v_pt

      conn_pt%component_name = component_name
      conn_pt%v_pt = v_pt
      
   end function new_connection_point_basic

   function new_connection_point_simple(component_name, state_intent, short_name) result(conn_pt)
      type(ConnectionPt) :: conn_pt
      character(*), intent(in) :: component_name
      character(*), intent(in) :: state_intent
      character(*), intent(in) :: short_name

      conn_pt%component_name = component_name
      conn_pt%v_pt = VirtualConnectionPt(state_intent=state_intent, short_name=short_name)
      
   end function new_connection_point_simple

   function get_esmf_name(this) result(esmf_name)
      character(:), allocatable :: esmf_name
      class(ConnectionPt), intent(in) :: this
      esmf_name = this%v_pt%get_esmf_name()
   end function get_esmf_name

   function get_state_intent(this) result(state_intent)
      character(:), allocatable :: state_intent
      class(ConnectionPt), intent(in) :: this
      state_intent = this%v_pt%get_state_intent()
   end function get_state_intent

   ! We need an ordering on ConnectionPt objects such that we can
   ! use them as keys in map containers.  Components are compared in
   ! order of decreasing variability for performance reasons.  E.g.,
   ! short names are all but unique and will almost always distinguish
   ! a connection point.   Whereas, state_intent has only 3 possibilites.
   
   logical function less(lhs, rhs)
      type(ConnectionPt), intent(in) :: lhs, rhs

      logical :: greater

      less = (lhs%component_name < rhs%component_name)
      if (less) return
      greater = (rhs%component_name < lhs%component_name)
      if (greater) return
      
      ! tie so far
      less = (lhs%v_pt < rhs%v_pt)

   end function less

   logical function equal_to(lhs, rhs)
      type(ConnectionPt), intent(in) :: lhs, rhs

      equal_to = (lhs%v_pt == rhs%v_pt)
      if (.not. equal_to) return

      equal_to = (lhs%component_name == rhs%component_name)
      if (.not. equal_to) return

   end function equal_to


   logical function is_import(this)
      class(ConnectionPt), intent(in) :: this
      is_import = (this%get_state_intent() == 'import')
   end function is_import

   logical function is_export(this)
      class(ConnectionPt), intent(in) :: this
      is_export = (this%get_state_intent() == 'export')
   end function is_export

   logical function is_internal(this)
      class(ConnectionPt), intent(in) :: this
      is_internal = (this%get_state_intent() == 'internal')
   end function is_internal

end module mapl3g_ConnectionPt