ouroboros-network-framework-0.13.1.0: Ouroboros network framework
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Network.ConnectionManager.Types

Description

Connection manager core types.

Connection manager is responsible for managing uni- and bi-directional connections and threads which are running network applications using 'network-mux'. In particular it is responsible for:

  • opening new connection / reusing connections (for bidirectional connections) and exposes a method to register inbound connections;
  • run connection handler, i.e. ConnectionHandler, which runs handshake negotiation, notifies connection manager on the results and starts the multiplexer;
  • error handling for connection threads;
  • keeping track of handshake negotiation: whether a unidirectional or duplex connection was negotiated;
  • tracking state of each connection;
  • keep inbound connections under limits.

Connection manager is designed to work for any MuxMode, though the most useful ones are ResponderMode and InitiatorResponderMode:

  • InitiatorResponderMode - useful for node-to-node applications, which needs to create outbound connections as well as accept inbound ones;
  • ResponderMode - useful for server side of node-to-client; it allows us to share the same server between node-to-client and node-to-node;
  • InitiatorMode - could be used on client side of node-to-client applications.

The calls requestOutboundConnection and includeInboundConnection return once a connection has been negotiated. The returned handle contains all the information that is needed to start and monitor mini-protocols through the mux interface.

For inbound connections, the connection manager will pass handle (also after negotiation).

┌────────────────────────┐
│                        │        ┏━━━━━━━━━━━━━━━━┓
│   ConnectionHandler    │        ┃                ┃
│                        ┝━━━━━━━▶┃     handle     ┃
│  inbound / outbound    │        ┃                ┃
│         ┃              │        ┗━━┳━━━━━━━━━━━━━┛
└─────────╂──────────────┘           ┃
          ┃                          ┃
          ▼                          ┃
   ┏━━━━━━━━━━━━━━━━━┓               ┃
   ┃ Control Channel ┃               ┃
   ┗━━━━━━┳━━━━━━━━━━┛               ┃
          ┃                          ┃
          ┃                          ┃
          ▼                          ┃
┌────────────────────────┐           ┃
│                        │           ┃
│         Server         │◀━━━━━━━━━━┛
│                        │
└────────────────────────┘

Termination procedure as well as connection state machine is not described in this haddock, see associated specification.

The handle is used in `ouroboros-network` package to construct PeerStateActions which allow for the outbound governor to

Synopsis

Connection manager core types

Connection Types

data AddressType Source #

Connection manager supports IPv4 and IPv6 addresses.

Constructors

IPv4Address 
IPv6Address 

Instances

Instances details
Show AddressType Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

data Provenance Source #

Each connection is is either initiated locally (outbound) or by a remote peer (inbound).

Constructors

Inbound

An inbound connection: one that was initiated by a remote peer.

Outbound

An outbound connection: one that was initiated by us.

data DataFlow Source #

Each connection negotiates if it is uni- or bi-directional. DataFlow is a life time property of a connection, once negotiated it never changes.

Constructors

Unidirectional 
Duplex 

Instances

Instances details
Show DataFlow Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntDataFlowShowS #

showDataFlowString #

showList ∷ [DataFlow] → ShowS #

Eq DataFlow Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

(==)DataFlowDataFlowBool #

(/=)DataFlowDataFlowBool #

Ord DataFlow Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

data ConnectionType Source #

Either unnegotiated or negotiated unidirectional or duplex connections. This is not a static property of a connection. It is used by PrunePolicy.

Note: the order matters, it can be used by a PickPolicy, e.g. simplePickPolicy.

Constructors

UnnegotiatedConn !Provenance

An unnegotiated connection.

InboundIdleConn !DataFlow

An inbound idle connection.

OutboundIdleConn !DataFlow

An outbound idle connection.

NegotiatedConn !Provenance !DataFlow

A negotiated connection, which is used in only one direction indicated by Provenance. The connection could itself negotiated either Duplex or Unidirectional data flow.

DuplexConn

A connection which is running in full duplex mode.

Connection Handler

ConnectionHandler provides monadic action which runs handshake negotiation and starts the multiplexer. It's the component which has access to underlying socket. There's one-to-one correspondence between sockets and threads that run the handler.

ConnectionHandlerFn
is the type of callback executed for each connection. All arguments are provided by the connection manager.
ConnectionHandler
is a newtype wrapper which provides inbound / outbound handlers depending on MuxMode.

newtype MaskedAction m a Source #

Handler action is started with asynchronous exceptions masked; this allows to install exception handlers in an async-safe way.

Constructors

MaskedAction 

Fields

type ConnectionHandlerFn handlerTrace socket peerAddr handle handleError version m = socket → PromiseWriter m (Either handleError (HandshakeConnectionResult handle version)) → Tracer m handlerTrace → ConnectionId peerAddr → (DiffTime → socket → m (MuxBearer m)) → MaskedAction m () Source #

MaskedAction which is executed by thread designated for a given connection.

PromiseWriter allows to notify the ConnectionManager about the result of handshake negotiation.

Note: PromiseWriter could be replaced with an stm action which is accessing the TVar which holds state of the connection.

newtype ConnectionHandler muxMode handlerTrace socket peerAddr handle handleError version m Source #

Connection handler action. It is index by muxMode :: MuxMode. There's one ConnectionHandlerFn per provenance, possibly limited by muxMode.

Constructors

ConnectionHandler 

Fields

data Inactive Source #

Boolean like type

Instances

Instances details
Show Inactive Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntInactiveShowS #

showInactiveString #

showList ∷ [Inactive] → ShowS #

Eq Inactive Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

(==)InactiveInactiveBool #

(/=)InactiveInactiveBool #

data ExceptionInHandler where Source #

Exception which where caught in the connection thread and were re-thrown in the main thread by the rethrowPolicy.

Constructors

ExceptionInHandler ∷ ∀ peerAddr. (Typeable peerAddr, Show peerAddr) ⇒ !peerAddr → !SomeExceptionExceptionInHandler 

data HandleErrorType Source #

Data type used to classify handleErrors.

Constructors

HandshakeFailure

Handshake negotiation failed. This is not a protocol error.

HandshakeProtocolViolation

Handshake protocol error. This should include timeout errors or any IO errors.

data HandshakeConnectionResult handle version Source #

Constructors

HandshakeConnectionQuery

Handshake saw a query.

HandshakeConnectionResult handle version

Handshake resulted in a connection and version.

Prune Policy

type PrunePolicy peerAddr = StdGenMap peerAddr ConnectionTypeIntSet peerAddr Source #

PrunePolicy allows to pick a select peers from which we will disconnect (we use TCP reset). The chosen connections will be terminated by the connection manger once it detects that there are too many inbound connections.

simplePrunePolicyOrd peerAddr ⇒ PrunePolicy peerAddr Source #

The simplest PrunePolicy, it should only be used for tests.

Connection Manager

Connection Manager Arguments

data ConnectionManager (muxMode ∷ MuxMode) socket peerAddr handle handleError m Source #

ConnectionManager.

We identify resources (e.g. Socket or HANDLE) by their address. It is enough for us to use just the remote address rather than connection identifier, since we need one connection towards that peer, even if we are connected through multiple local addresses. It is safe to share a connection manager with multiple listening sockets.

Constructors

ConnectionManager 

Fields

API

data Connected peerAddr handle handleError Source #

Constructors

Connected !(ConnectionId peerAddr) !DataFlow !handle

We are connected and mux is running.

Disconnected !(ConnectionId peerAddr) !(Maybe handleError)

There was an error during handshake negotiation.

Implementation detail: we return Maybe handleError, rather than handleError. In case of an existing inbound connection, the implementation of requestOutboundConnection is awaiting on handshake through the connection state. The TerminatingState or TerminatedState are not only used for handshake errors, but also for normal termination, hence the Maybe. We could await on update from the handshake instead, but this would introduce a race between inbound / outbound threads.

data OperationResult a Source #

Custom either type for result of various methods.

Instances

Instances details
Functor OperationResult Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

fmap ∷ (a → b) → OperationResult a → OperationResult b #

(<$) ∷ a → OperationResult b → OperationResult a #

Show a ⇒ Show (OperationResult a) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

data DemotedToColdRemoteTr Source #

Return value of unregisterInboundConnection to inform the caller about the transition.

Constructors

CommitTr

Commit^{dataFlow} transition from InboundIdleState dataFlow.

KeepTr

Either DemotedToCold^{Remote} transition from DuplexState, or a level triggered Awake^{Duplex}_{Local} transition. In both cases the server must keep the responder side of all protocols ready.

type RequestOutboundConnection peerAddr handle handleError m = peerAddr → m (Connected peerAddr handle handleError) Source #

type IncludeInboundConnection socket peerAddr handle handleError m Source #

Arguments

 = Word32

inbound connections hard limit. NOTE: Check TODO over at includeInboundConnectionImpl definition.

→ socket 
→ peerAddr 
→ m (Connected peerAddr handle handleError) 

Outbound side

requestOutboundConnectionHasInitiator muxMode ~ TrueConnectionManager muxMode socket peerAddr handle handleError m → RequestOutboundConnection peerAddr handle handleError m Source #

Include outbound connection into ConnectionManager.

This executes:

  • \(Reserve\) to \(Negotiated^{*}_{Outbound}\) transitions
  • \(PromotedToWarm^{Duplex}_{Local}\) transition
  • \(Awake^{Duplex}_{Local}\) transition

promotedToWarmRemoteHasResponder muxMode ~ TrueConnectionManager muxMode socket peerAddr handle handleError m → peerAddr → m (OperationResult AbstractState) Source #

Notify the ConnectionManager that a remote end promoted us to a warm peer.

This executes either:

  • \(PromotedToWarm^{Duplex}_{Remote}\) transition,
  • \(Awake^{*}_{Remote}\) transition

from the specification.

demotedToColdRemoteHasResponder muxMode ~ TrueConnectionManager muxMode socket peerAddr handle handleError m → peerAddr → m (OperationResult AbstractState) Source #

Notify the ConnectionManager that a remote end demoted us to a /cold peer/.

This executes:

  • \(DemotedToCold^{*}_{Remote}\) transition.

This method is idempotent.

unregisterOutboundConnection Source #

Arguments

HasInitiator muxMode ~ True 
ConnectionManager muxMode socket peerAddr handle handleError m 
→ peerAddr 
→ m (OperationResult AbstractState)

reports the from-state.

Unregister outbound connection.

This executes:

  • \(DemotedToCold^{*}_{Local}\) transitions

Inbound side

includeInboundConnectionHasResponder muxMode ~ TrueConnectionManager muxMode socket peerAddr handle handleError m → IncludeInboundConnection socket peerAddr handle handleError m Source #

Include an inbound connection into ConnectionManager. This executes:

  • \(Reserve\) to \(Negotiated^{*}_{Outbound}\) transitions
  • \(PromotedToWarm^{Duplex}_{Local}\) transition
  • \(Awake^{Duplex}_{Local}\) transition

unregisterInboundConnectionHasResponder muxMode ~ TrueConnectionManager muxMode socket peerAddr handle handleError m → peerAddr → m (OperationResult DemotedToColdRemoteTr) Source #

Unregister outbound connection. Returns if the operation was successful.

This executes:

  • \(Commit*{*}\) transition
  • \(TimeoutExpired\) transition

numberOfConnectionsHasResponder muxMode ~ TrueConnectionManager muxMode socket peerAddr handle handleError m → STM m Int Source #

Number of connections tracked by the server.

Private API

data OutboundConnectionManager (muxMode ∷ MuxMode) socket peerAddr handle handleError m where Source #

Outbound connection manager API.

Constructors

OutboundConnectionManager 

Fields

data InboundConnectionManager (muxMode ∷ MuxMode) socket peerAddr handle handleError m where Source #

Inbound connection manager API. For a server implementation we also need to know how many connections are now managed by the connection manager.

This type is an internal detail of ConnectionManager

Constructors

InboundConnectionManager 

Fields

Exceptions

data ConnectionManagerError peerAddr Source #

Exceptions used by ConnectionManager.

Constructors

ConnectionExists !Provenance !peerAddr !CallStack

A connection manager was asked for an outbound connection and there either exists a connection used in outbound direction or a reservation for an outbound connection.

ForbiddenConnection !(ConnectionId peerAddr) !CallStack

Connection manager was asked for an outbound connection which turned out to be unidirectional inbound, and thus it cannot be re-used..

ImpossibleConnection !(ConnectionId peerAddr) !CallStack

Connections that would be forbidden by the kernel (TCP semantics).

ConnectionTerminating !(ConnectionId peerAddr) !CallStack

Connection is now terminating.

ConnectionTerminated !peerAddr !CallStack

Connection has terminated.

ImpossibleState !peerAddr !CallStack

Connection manager in impossible state.

ForbiddenOperation !peerAddr !AbstractState !CallStack

A forbidden operation in the given connection state.

UnknownPeer !peerAddr !CallStack

A connection does not exists. Only thrown when an existing connection was expected.

Instances

Instances details
(Show peerAddr, Typeable peerAddr) ⇒ Exception (ConnectionManagerError peerAddr) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Show peerAddr ⇒ Show (ConnectionManagerError peerAddr) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntConnectionManagerError peerAddr → ShowS #

showConnectionManagerError peerAddr → String #

showList ∷ [ConnectionManagerError peerAddr] → ShowS #

Counters

data ConnectionManagerCounters Source #

Counters for tracing and analysis purposes

Constructors

ConnectionManagerCounters 

Fields

Instances

Instances details
Monoid ConnectionManagerCounters Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Semigroup ConnectionManagerCounters Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Show ConnectionManagerCounters Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Eq ConnectionManagerCounters Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Ord ConnectionManagerCounters Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Mux types

Promise

Promise interface, backed by a StrictTMVar.

Making two separate interfaces: PromiseWriter and PromiseReader allows us to make a clear distinction between consumer and producers threads.

newtype PromiseReader m a Source #

Constructors

PromiseReader 

Fields

data PromiseWriter m a Source #

Constructors

PromiseWriter 

Fields

Tracing

data AssertionLocation peerAddr Source #

AssertionLocation contains constructors that situate the location of the tracing so one can be sure where the assertion came from as well as the all relevant information.

Instances

Instances details
Show peerAddr ⇒ Show (AssertionLocation peerAddr) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntAssertionLocation peerAddr → ShowS #

showAssertionLocation peerAddr → String #

showList ∷ [AssertionLocation peerAddr] → ShowS #

data ConnectionManagerTrace peerAddr handlerTrace Source #

ConnectionManagerTrace contains a hole for a trace of single connection which is filled with ConnectionHandlerTrace.

Constructors

TrIncludeConnection Provenance peerAddr 
TrUnregisterConnection Provenance peerAddr 
TrConnect 

Fields

  • (Maybe peerAddr)

    local address

  • peerAddr

    remote address

TrConnectError 

Fields

TrTerminatingConnection Provenance (ConnectionId peerAddr) 
TrTerminatedConnection Provenance peerAddr 
TrConnectionHandler (ConnectionId peerAddr) handlerTrace 
TrShutdown 
TrConnectionExists Provenance peerAddr AbstractState 
TrForbiddenConnection (ConnectionId peerAddr) 
TrConnectionFailure (ConnectionId peerAddr) 
TrConnectionNotFound Provenance peerAddr 
TrForbiddenOperation peerAddr AbstractState 
TrPruneConnections 

Fields

  • (Set peerAddr)

    pruning set

  • Int

    number connections that must be pruned

  • (Set peerAddr)

    choice set

TrConnectionCleanup (ConnectionId peerAddr) 
TrConnectionTimeWait (ConnectionId peerAddr) 
TrConnectionTimeWaitDone (ConnectionId peerAddr) 
TrConnectionManagerCounters ConnectionManagerCounters 
TrState (Map peerAddr AbstractState)

traced on SIGUSR1 signal, installed in runDataDiffusion

TrUnexpectedlyFalseAssertion (AssertionLocation peerAddr)

This case is unexpected at call site.

Instances

Instances details
(Show handlerTrace, Show peerAddr) ⇒ Show (ConnectionManagerTrace peerAddr handlerTrace) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntConnectionManagerTrace peerAddr handlerTrace → ShowS #

showConnectionManagerTrace peerAddr handlerTrace → String #

showList ∷ [ConnectionManagerTrace peerAddr handlerTrace] → ShowS #

data MaybeUnknown state Source #

A custom version of Maybe type, which allows to explicitly represent connections which are not registered by the connection manager.

Constructors

Known !state

Known connection in state

Race !state

There is a possible race condition between connection finalizer and either inbound or outbound connection registration. If that happens we use Race constructor.

Unknown

Connection is is not known to the connection manager.

Instances

Instances details
Functor MaybeUnknown Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

fmap ∷ (a → b) → MaybeUnknown a → MaybeUnknown b #

(<$) ∷ a → MaybeUnknown b → MaybeUnknown a #

Show state ⇒ Show (MaybeUnknown state) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntMaybeUnknown state → ShowS #

showMaybeUnknown state → String #

showList ∷ [MaybeUnknown state] → ShowS #

data Transition' state Source #

Constructors

Transition 

Fields

Instances

Instances details
Functor Transition' Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

fmap ∷ (a → b) → Transition' a → Transition' b #

(<$) ∷ a → Transition' b → Transition' a #

Show state ⇒ Show (Transition' state) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntTransition' state → ShowS #

showTransition' state → String #

showList ∷ [Transition' state] → ShowS #

Eq state ⇒ Eq (Transition' state) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

(==)Transition' state → Transition' state → Bool #

(/=)Transition' state → Transition' state → Bool #

mkTransition ∷ state → state → Transition state Source #

type TransitionTrace peerAddr state = TransitionTrace' peerAddr (MaybeUnknown state) Source #

data TransitionTrace' peerAddr state Source #

Constructors

TransitionTrace 

Fields

Instances

Instances details
Functor (TransitionTrace' peerAddr) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

fmap ∷ (a → b) → TransitionTrace' peerAddr a → TransitionTrace' peerAddr b #

(<$) ∷ a → TransitionTrace' peerAddr b → TransitionTrace' peerAddr a #

(Show peerAddr, Show state) ⇒ Show (TransitionTrace' peerAddr state) Source # 
Instance details

Defined in Ouroboros.Network.ConnectionManager.Types

Methods

showsPrecIntTransitionTrace' peerAddr state → ShowS #

showTransitionTrace' peerAddr state → String #

showList ∷ [TransitionTrace' peerAddr state] → ShowS #