ouroboros-network-0.16.0.0: A networking layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Network.PeerSelection.Governor.Types

Synopsis

P2P governor policies

data PeerSelectionPolicy peeraddr m Source #

Constructors

PeerSelectionPolicy 

Fields

data PeerSelectionTargets Source #

Adjustable targets for the peer selection mechanism.

These are used by the peer selection governor as targets. They are used by the peer churn governor loop as knobs to adjust, to influence the peer selection governor.

The known, established and active peer targets are targets both from below and from above: the governor will attempt to grow or shrink the sets to hit these targets.

Unlike the other targets, the root peer target is "one sided", it is only a target from below. The governor does not try to shrink the root set to hit it, it simply stops looking for more.

There is also an implicit target that enough local root peers are selected as active. This comes from the configuration for local roots, and is not an independently adjustable target.

Constructors

PeerSelectionTargets 

Fields

type PickPolicy peeraddr m = (peeraddr → PeerSource) → (peeraddr → Int) → (peeraddr → Bool) → Set peeraddr → Int → m (Set peeraddr) Source #

A peer pick policy is an action that picks a subset of elements from a map of peers.

The pre-condition is that the map of available choices will be non-empty, and the requested number to pick will be strictly positive.

The post-condition is that the picked set is non-empty but must not be bigger than the requested number.

Peer selection API is using `STM m` monad, internally it is using m.

pickPeers ∷ (Ord peeraddr, Functor m, HasCallStack) ⇒ PeerSelectionState peeraddr peerconn → PickPolicy peeraddr m → Set peeraddr → Int → m (Set peeraddr) Source #

Pick some known peers.

pickUnknownPeers ∷ (Ord peeraddr, Functor m, HasCallStack) ⇒ PeerSelectionState peeraddr peerconn → PickPolicy peeraddr m → Set peeraddr → Int → m (Set peeraddr) Source #

Pick some unknown peers.

P2P governor low level API

data PeerStateActions peeraddr peerconn m Source #

Callbacks which are performed to change peer state.

Constructors

PeerStateActions 

Fields

data PeerSelectionActions peeraddr peerconn m Source #

Constructors

PeerSelectionActions 

Fields

data PeerSelectionInterfaces peeraddr peerconn m Source #

Interfaces required by the peer selection governor, which do not need to be shared with actions and thus are not part of PeerSelectionActions.

Constructors

PeerSelectionInterfaces 

Fields

data ChurnMode Source #

Instances

Instances details
Show ChurnMode Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

Methods

showsPrecIntChurnModeShowS #

showChurnModeString #

showList ∷ [ChurnMode] → ShowS #

P2P governor internals

data PeerSelectionState peeraddr peerconn Source #

The internal state used by the peerSelectionGovernor.

The local and public root sets are disjoint, and their union is the overall root set.

Documentation of individual fields describes some of the invariants these structures should maintain. For the entire picture, see assertPeerSelectionState.

Constructors

PeerSelectionState 

Fields

Instances

Instances details
(Ord peeraddr, Show peeraddr, Show peerconn) ⇒ Show (PeerSelectionState peeraddr peerconn) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

Methods

showsPrecIntPeerSelectionState peeraddr peerconn → ShowS #

showPeerSelectionState peeraddr peerconn → String #

showList ∷ [PeerSelectionState peeraddr peerconn] → ShowS #

data AssociationMode Source #

A node is classified as LocalRootsOnly if it is a hidden relay or a BP, e.g. if it is configured such that it can only have a chance to be connected to local roots. This is true if the node is configured in one of two ways:

Note that in the second case a node might transition between LocalRootsOnly and Unrestricted modes, depending on LedgerStateJudgement.

See readAssociationMode.

Instances

Instances details
Show AssociationMode Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

assertPeerSelectionStateOrd peeraddr ⇒ PeerSelectionState peeraddr peerconn → a → a Source #

establishedPeersStatusOrd peeraddr ⇒ PeerSelectionState peeraddr peerconn → Map peeraddr PeerStatus Source #

A view of the status of each established peer, for testing and debugging.

newtype PublicPeerSelectionState peeraddr Source #

Public PeerSelectionState that can be accessed by Peer Sharing mechanisms without any problem.

This data type should not expose too much information and keep only essential data needed for computing the peer sharing request result

Constructors

PublicPeerSelectionState 

Fields

toPublicStatePeerSelectionState peeraddr peerconn → PublicPeerSelectionState peeraddr Source #

Convert a PeerSelectionState into a public record accessible by the Peer Sharing mechanisms so we can know about which peers are available and possibly other needed context.

data Guarded m a where Source #

The governor is using Guarded m (Decision m peeraddr peerconn) where m is an STM monad, to drive its progress.

Bundled Patterns

pattern GuardedSkipMaybe TimeGuarded m a

GuardedSkip is used to instruct that there is no action to be made by the governor. See GuardedSkip.

GuardedSkip is a pattern which hides the usage of Min newtype wrapper in GuardedSkip' constructor (private).

Let us note that the combined value which is computed by guardedDecisions term in peerSelectionGovernorLoop will never return it: this is because there are monitoring decisions which never return this constructor, e.g. targetPeers, jobs, connections, and thus the governor has always something to do.

pattern GuardedMaybe Time → m a → Guarded m a

Guarded is used to provide an action possibly with a timeout, to the governor main loop.

Guarded is a pattern which which hides the use of FirstToFinish and Min newtype wrappers.

Instances

Instances details
Alternative m ⇒ Semigroup (Guarded m a) Source #

Guarded constructor is absorbing in the sense that

Guarded x y <> a = Guarded x' y'
a <> Guarded x y = Guarded x' y'

In the algebraic sense, Guarded (Just minBound) (return x) is a left absorbing element when "m ~ STM m' for some monad m'. There is no right absorbing element since there is no right absorbing element in STM m'@.

Ref. absorbing element

Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

Methods

(<>)Guarded m a → Guarded m a → Guarded m a #

sconcatNonEmpty (Guarded m a) → Guarded m a #

stimesIntegral b ⇒ b → Guarded m a → Guarded m a #

data Decision m peeraddr peerconn Source #

Constructors

Decision 

Fields

type TimedDecision m peeraddr peerconn = TimeDecision m peeraddr peerconn Source #

Decision which has access to the current time, rather than the time when the governor's loop blocked to make a decision.

type MkGuardedDecision peeraddr peerconn m = PeerSelectionPolicy peeraddr m → PeerSelectionState peeraddr peerconn → Guarded (STM m) (TimedDecision m peeraddr peerconn) Source #

Type alias for function types which are used to create governor decisions. Almost all decisions are following this pattern.

newtype Completion m peeraddr peerconn Source #

Constructors

Completion (PeerSelectionState peeraddr peerconn → TimeDecision m peeraddr peerconn) 

data PeerSelectionView a Source #

Peer selection view.

This is a functor which is used to hold computation of various peer sets and their sizes. See peerSelectionStateToView, peerSelectionStateToCounters.

Constructors

PeerSelectionView 

Fields

Bundled Patterns

pattern PeerSelectionCountersIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntIntPeerSelectionCounters 
pattern PeerSelectionCountersHWCIntIntIntIntIntIntIntIntIntPeerSelectionCounters

A Pattern synonym which computes hot, warm, cold counters from PeerSelectionCounters.

peerSelectionStateToViewOrd peeraddr ⇒ PeerSelectionState peeraddr peerconn → PeerSelectionSetsWithSizes peeraddr Source #

Compute peer selection sets & their sizes.

This function is used internally by the outbound-governor and to compute PeerSelectionCounters which are used by churn or are traced (e.g. as EKG metrics). For this reason one has to be very careful when changing the function, as it will affect the outbound governor behaviour.

Peer Sharing Auxiliary data type

data PeerSharingResult peerAddress Source #

PeerSharing Result type.

We need a constructor for the case when the Governor wins the race versus the Mux (when initialising the peer sharing miniprotocol). This leads the Governor to lookup a peer that hasn't been registered yet.

Constructors

PeerSharingResult [peerAddress] 
PeerSharingNotRegisteredYet 

Instances

Instances details
Show peerAddress ⇒ Show (PeerSharingResult peerAddress) 
Instance details

Defined in Ouroboros.Network.Protocol.PeerSharing.Type

Methods

showsPrecIntPeerSharingResult peerAddress → ShowS #

showPeerSharingResult peerAddress → String #

showList ∷ [PeerSharingResult peerAddress] → ShowS #

Eq peerAddress ⇒ Eq (PeerSharingResult peerAddress) 
Instance details

Defined in Ouroboros.Network.Protocol.PeerSharing.Type

Methods

(==)PeerSharingResult peerAddress → PeerSharingResult peerAddress → Bool #

(/=)PeerSharingResult peerAddress → PeerSharingResult peerAddress → Bool #

Traces

data TracePeerSelection peeraddr Source #

Constructors

TraceLocalRootPeersChanged (LocalRootPeers peeraddr) (LocalRootPeers peeraddr) 
TraceTargetsChanged PeerSelectionTargets PeerSelectionTargets

Peer selection targets changed: old targets, new targets.

TracePublicRootsRequest Int Int 
TracePublicRootsResults (PublicRootPeers peeraddr) Int DiffTime 
TracePublicRootsFailure SomeException Int DiffTime 
TraceForgetColdPeers Int Int (Set peeraddr)

target known peers, actual known peers, selected peers

TraceBigLedgerPeersRequest Int Int 
TraceBigLedgerPeersResults (Set peeraddr) Int DiffTime 
TraceBigLedgerPeersFailure SomeException Int DiffTime 
TraceForgetBigLedgerPeers Int Int (Set peeraddr)

target known big ledger peers, actual known big ledger peers, selected peers

TracePeerShareRequests Int Int PeerSharingAmount (Set peeraddr) (Set peeraddr)

target known peers, actual known peers, number of peers to request, peers available for peer sharing, peers selected for peer sharing

TracePeerShareResults [(peeraddr, Either SomeException (PeerSharingResult peeraddr))] 
TracePeerShareResultsFiltered [peeraddr] 
TracePickInboundPeers Int Int (Map peeraddr PeerSharing) (Set peeraddr)

target known peers, actual known peers, selected inbound peers, available peers

TracePromoteColdPeers Int Int (Set peeraddr)

target established, actual established, selected peers

TracePromoteColdLocalPeers [(WarmValency, Int)] (Set peeraddr)

target local established, actual local established, selected peers

TracePromoteColdFailed Int Int peeraddr DiffTime SomeException 
TracePromoteColdDone Int Int peeraddr

target established, actual established, peer

TracePromoteColdBigLedgerPeers Int Int (Set peeraddr)

target established big ledger peers, actual established big ledger peers, selected peers

TracePromoteColdBigLedgerPeerFailed Int Int peeraddr DiffTime SomeException

target established big ledger peers, actual established big ledger peers, peer, delay until next promotion, reason

TracePromoteColdBigLedgerPeerDone Int Int peeraddr

target established big ledger peers, actual established big ledger peers, peer

TracePromoteWarmPeers Int Int (Set peeraddr)

target active, actual active, selected peers

TracePromoteWarmLocalPeers

Promote local peers to warm

Fields

  • [(HotValency, Int)]

    local per-group `(target active, actual active)`, only limited to groups which are below their target.

  • (Set peeraddr)

    selected peers | target active, actual active, peer, reason

TracePromoteWarmFailed Int Int peeraddr SomeException 
TracePromoteWarmDone Int Int peeraddr

target active, actual active, peer

TracePromoteWarmAborted Int Int peeraddr

aborted promotion of a warm peer; likely it was asynchronously demoted in the meantime.

target active, actual active, peer

TracePromoteWarmBigLedgerPeers Int Int (Set peeraddr)

target active big ledger peers, actual active big ledger peers, selected peers

TracePromoteWarmBigLedgerPeerFailed Int Int peeraddr SomeException

target active big ledger peers, actual active big ledger peers, peer, reason

TracePromoteWarmBigLedgerPeerDone Int Int peeraddr

target active big ledger peers, actual active big ledger peers, peer

TracePromoteWarmBigLedgerPeerAborted Int Int peeraddr

aborted promotion of a warm big ledger peer; likely it was asynchronously demoted in the meantime.

target active, actual active, peer

TraceDemoteWarmPeers Int Int (Set peeraddr)

target established, actual established, selected peers

TraceDemoteWarmFailed Int Int peeraddr SomeException

target established, actual established, peer, reason

TraceDemoteWarmDone Int Int peeraddr

target established, actual established, peer

TraceDemoteWarmBigLedgerPeers Int Int (Set peeraddr)

target established big ledger peers, actual established big ledger peers, selected peers

TraceDemoteWarmBigLedgerPeerFailed Int Int peeraddr SomeException

target established big ledger peers, actual established big ledger peers, peer, reason

TraceDemoteWarmBigLedgerPeerDone Int Int peeraddr

target established big ledger peers, actual established big ledger peers, peer

TraceDemoteHotPeers Int Int (Set peeraddr)

target active, actual active, selected peers

TraceDemoteLocalHotPeers [(HotValency, Int)] (Set peeraddr)

local per-group (target active, actual active), selected peers

TraceDemoteHotFailed Int Int peeraddr SomeException

target active, actual active, peer, reason

TraceDemoteHotDone Int Int peeraddr

target active, actual active, peer

TraceDemoteHotBigLedgerPeers Int Int (Set peeraddr)

target active big ledger peers, actual active big ledger peers, selected peers

TraceDemoteHotBigLedgerPeerFailed Int Int peeraddr SomeException

target active big ledger peers, actual active big ledger peers, peer, reason

TraceDemoteHotBigLedgerPeerDone Int Int peeraddr

target active big ledger peers, actual active big ledger peers, peer

TraceDemoteAsynchronous (Map peeraddr (PeerStatus, Maybe RepromoteDelay)) 
TraceDemoteLocalAsynchronous (Map peeraddr (PeerStatus, Maybe RepromoteDelay)) 
TraceDemoteBigLedgerPeersAsynchronous (Map peeraddr (PeerStatus, Maybe RepromoteDelay)) 
TraceGovernorWakeup 
TraceChurnWait DiffTime 
TraceChurnMode ChurnMode 
TraceChurnAction 

Fields

  • DiffTime

    duration of the churn action

  • ChurnAction

    churn action type

  • Int

    how many peers were removed or added within the duration of the action.

TraceChurnTimeout 

Fields

  • DiffTime

    duration of the churn action

  • ChurnAction

    churn action type

  • Int

    how many peers were removed or added within the duration of the action; note that if the action timeouts the governor will still look to remove or add peers as required.

TraceLedgerStateJudgementChanged LedgerStateJudgement 
TraceOnlyBootstrapPeers 
TraceBootstrapPeersFlagChangedWhilstInSensitiveState 
TraceUseBootstrapPeersChanged UseBootstrapPeers 
TraceOutboundGovernorCriticalFailure SomeException 
TraceDebugState Time (DebugPeerSelectionState peeraddr) 

Instances

Instances details
(Ord peeraddr, Show peeraddr) ⇒ Show (TracePeerSelection peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

Methods

showsPrecIntTracePeerSelection peeraddr → ShowS #

showTracePeerSelection peeraddr → String #

showList ∷ [TracePeerSelection peeraddr] → ShowS #

data DebugPeerSelection peeraddr where Source #

Constructors

TraceGovernorState ∷ ∀ peeraddr peerconn. Show peerconn ⇒ TimeMaybe DiffTimePeerSelectionState peeraddr peerconn → DebugPeerSelection peeraddr 

Instances

Instances details
(Ord peeraddr, Show peeraddr) ⇒ Show (DebugPeerSelection peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

Methods

showsPrecIntDebugPeerSelection peeraddr → ShowS #

showDebugPeerSelection peeraddr → String #

showList ∷ [DebugPeerSelection peeraddr] → ShowS #

Error types