ouroboros-network
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Network.PeerSelection

Synopsis

Documentation

data PeerSelectionActions extraState extraFlags extraPeers extraAPI extraCounters peeraddr peerconn (m :: Type -> Type) Source #

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

data PeerSelectionState extraState extraFlags extraPeers 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.

Instances

Instances details
(Ord peeraddr, Show extraFlags, Show peeraddr, Show extraPeers, Show peerconn, Show extraState) => Show (PeerSelectionState extraState extraFlags extraPeers peeraddr peerconn) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

Methods

showsPrec :: Int -> PeerSelectionState extraState extraFlags extraPeers peeraddr peerconn -> ShowS #

show :: PeerSelectionState extraState extraFlags extraPeers peeraddr peerconn -> String #

showList :: [PeerSelectionState extraState extraFlags extraPeers peeraddr peerconn] -> ShowS #

data PeerSelectionInterfaces extraState extraFlags extraPeers extraCounters peeraddr peerconn (m :: Type -> Type) 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 DebugPeerSelection extraState extraFlags extraPeers peeraddr where Source #

Constructors

TraceGovernorState :: forall extraState extraFlags extraPeers peeraddr peerconn. Show peerconn => Time -> Maybe DiffTime -> PeerSelectionState extraState extraFlags extraPeers peeraddr peerconn -> DebugPeerSelection extraState extraFlags extraPeers peeraddr 

Instances

Instances details
(Show extraState, Show extraFlags, Show extraPeers, Ord peeraddr, Show peeraddr) => Show (DebugPeerSelection extraState extraFlags extraPeers peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.Governor.Types

Methods

showsPrec :: Int -> DebugPeerSelection extraState extraFlags extraPeers peeraddr -> ShowS #

show :: DebugPeerSelection extraState extraFlags extraPeers peeraddr -> String #

showList :: [DebugPeerSelection extraState extraFlags extraPeers peeraddr] -> ShowS #

data PeerStateActions peeraddr peerconn (m :: Type -> Type) Source #

Callbacks which are performed to change peer state.

data PeerSelectionPolicy peeraddr (m :: Type -> Type) Source #

Constructors

PeerSelectionPolicy 

Fields

type PickPolicy peeraddr (m :: Type -> Type) = (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.

data PublicRootPeers extraPeers peeraddr Source #

Public Root Peers consist of either a set of manually configured bootstrap peers.

There's an implicit precedence that will priorise bootstrap peers over the other sets, so if we are adding a bootstrap peer and that peer is already a member of other public root set, it is going to be removed from that set and added to the bootstrap peer set.

Instances

Instances details
Ord peeraddr => Monoid (PublicRootPeers (ExtraPeers peeraddr) peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PublicRootPeers

Methods

mempty :: PublicRootPeers (ExtraPeers peeraddr) peeraddr #

mappend :: PublicRootPeers (ExtraPeers peeraddr) peeraddr -> PublicRootPeers (ExtraPeers peeraddr) peeraddr -> PublicRootPeers (ExtraPeers peeraddr) peeraddr #

mconcat :: [PublicRootPeers (ExtraPeers peeraddr) peeraddr] -> PublicRootPeers (ExtraPeers peeraddr) peeraddr #

Ord peeraddr => Semigroup (PublicRootPeers (ExtraPeers peeraddr) peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PublicRootPeers

Methods

(<>) :: PublicRootPeers (ExtraPeers peeraddr) peeraddr -> PublicRootPeers (ExtraPeers peeraddr) peeraddr -> PublicRootPeers (ExtraPeers peeraddr) peeraddr #

sconcat :: NonEmpty (PublicRootPeers (ExtraPeers peeraddr) peeraddr) -> PublicRootPeers (ExtraPeers peeraddr) peeraddr #

stimes :: Integral b => b -> PublicRootPeers (ExtraPeers peeraddr) peeraddr -> PublicRootPeers (ExtraPeers peeraddr) peeraddr #

(Show peeraddr, Show extraPeers) => Show (PublicRootPeers extraPeers peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PublicRootPeers

Methods

showsPrec :: Int -> PublicRootPeers extraPeers peeraddr -> ShowS #

show :: PublicRootPeers extraPeers peeraddr -> String #

showList :: [PublicRootPeers extraPeers peeraddr] -> ShowS #

(Eq peeraddr, Eq extraPeers) => Eq (PublicRootPeers extraPeers peeraddr) Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PublicRootPeers

Methods

(==) :: PublicRootPeers extraPeers peeraddr -> PublicRootPeers extraPeers peeraddr -> Bool #

(/=) :: PublicRootPeers extraPeers peeraddr -> PublicRootPeers extraPeers peeraddr -> Bool #

data AfterSlot #

Only use the ledger after the given slot number.

Constructors

Always 
After SlotNo 

Instances

Instances details
Generic AfterSlot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Associated Types

type Rep AfterSlot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

type Rep AfterSlot = D1 ('MetaData "AfterSlot" "Ouroboros.Network.PeerSelection.LedgerPeers.Type" "ouroboros-network-api-0.13.0.0-inplace" 'False) (C1 ('MetaCons "Always" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "After" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo)))
Show AfterSlot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Eq AfterSlot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

NoThunks AfterSlot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

type Rep AfterSlot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

type Rep AfterSlot = D1 ('MetaData "AfterSlot" "Ouroboros.Network.PeerSelection.LedgerPeers.Type" "ouroboros-network-api-0.13.0.0-inplace" 'False) (C1 ('MetaCons "Always" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "After" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo)))

data IsBigLedgerPeer #

A boolean like type. Big ledger peers are the largest SPOs which control 90% of staked stake.

Note that IsBigLedgerPeer indicates a role that peer plays in the eclipse evasion, e.g. that a peer was explicitly selected as a big ledger peer, e.g. IsNotBigLedgerPeer does not necessarily mean that the peer isn't a big ledger peer. This is because we select root peers from all ledger peers (including big ones).

data LedgerPeerSnapshot #

The type of big ledger peers that is serialised or later provided by node configuration for the networking layer to connect to when syncing.

Constructors

LedgerPeerSnapshotV2 (WithOrigin SlotNo, [(AccPoolStake, (PoolStake, NonEmpty RelayAccessPoint))])

Internal use for version 2, use pattern synonym for public API

Bundled Patterns

pattern LedgerPeerSnapshot :: (WithOrigin SlotNo, [(AccPoolStake, (PoolStake, NonEmpty RelayAccessPoint))]) -> LedgerPeerSnapshot

Public API to access snapshot data. Currently access to only most recent version is available. Nonetheless, serialisation from the node into JSON is supported for older versions via internal api so that newer CLI can still support older node formats.

Instances

Instances details
FromJSON LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

ToJSON LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

FromCBOR LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

ToCBOR LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Show LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Eq LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

data LedgerPeersConsensusInterface extraAPI (m :: Type -> Type) #

Return ledger state information and ledger peers.

Constructors

LedgerPeersConsensusInterface 

Fields

data LedgerPeersKind #

Which ledger peers to pick.

data UseLedgerPeers #

Only use the ledger after the given slot number.

Instances

Instances details
Generic UseLedgerPeers 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Associated Types

type Rep UseLedgerPeers 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

type Rep UseLedgerPeers = D1 ('MetaData "UseLedgerPeers" "Ouroboros.Network.PeerSelection.LedgerPeers.Type" "ouroboros-network-api-0.13.0.0-inplace" 'False) (C1 ('MetaCons "DontUseLedgerPeers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UseLedgerPeers" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AfterSlot)))
Show UseLedgerPeers 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Eq UseLedgerPeers 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

NoThunks UseLedgerPeers 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

type Rep UseLedgerPeers 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

type Rep UseLedgerPeers = D1 ('MetaData "UseLedgerPeers" "Ouroboros.Network.PeerSelection.LedgerPeers.Type" "ouroboros-network-api-0.13.0.0-inplace" 'False) (C1 ('MetaCons "DontUseLedgerPeers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UseLedgerPeers" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AfterSlot)))

data LedgerPeers Source #

Ledger Peer request result

Constructors

LedgerPeers [(PoolStake, NonEmpty RelayAccessPoint)]

Ledger peers

BeforeSlot

No result because the node is still before the configured UseLedgerAfter slot number

newtype NumberOfPeers Source #

Number of peers to pick.

Constructors

NumberOfPeers 

Instances

Instances details
Show NumberOfPeers Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers

data TraceLedgerPeers Source #

Trace LedgerPeers events.

Constructors

PickedBigLedgerPeer RelayAccessPoint AccPoolStake PoolStake

Trace for a significant ledger peer picked with accumulated and relative stake of its pool.

PickedLedgerPeer RelayAccessPoint AccPoolStake PoolStake

Trace for a ledger peer picked with accumulated and relative stake of its pool.

PickedBigLedgerPeers NumberOfPeers [RelayAccessPoint] 
PickedLedgerPeers NumberOfPeers [RelayAccessPoint]

Trace for the number of peers and we wanted to pick and the list of peers picked.

FetchingNewLedgerState Int Int

Trace for fetching a new list of peers from the ledger. The first Int is the number of ledger peers returned the latter is the number of big ledger peers.

TraceLedgerPeersDomains [RelayAccessPoint] 
DisabledLedgerPeers

Trace for when getting peers from the ledger is disabled, that is DontUseLedgerPeers.

TraceUseLedgerPeers UseLedgerPeers

Trace UseLedgerPeers value

WaitingOnRequest 
RequestForPeers NumberOfPeers 
ReusingLedgerState Int DiffTime 
FallingBackToPublicRootPeers 
NotEnoughBigLedgerPeers NumberOfPeers Int 
NotEnoughLedgerPeers NumberOfPeers Int 
UsingBigLedgerPeerSnapshot 

data WithLedgerPeersArgs extraAPI (m :: Type -> Type) Source #

Argument record for withLedgerPeers

Constructors

WithLedgerPeersArgs 

Fields

withLedgerPeers :: forall peerAddr resolver exception extraAPI m a. (MonadAsync m, MonadThrow m, MonadMonotonicTime m, Exception exception, Ord peerAddr) => PeerActionsDNS peerAddr resolver exception m -> WithLedgerPeersArgs extraAPI m -> ((NumberOfPeers -> LedgerPeersKind -> m (Maybe (Set peerAddr, DiffTime))) -> Async m Void -> m a) -> m a Source #

For a LedgerPeers worker thread and submit request and receive responses.

data ReportPeerMetrics (m :: Type -> Type) peerAddr #

Constructors

ReportPeerMetrics 

data PeerMetrics (m :: Type -> Type) p Source #

Mutable peer metrics state accessible via STM.

newtype PeerMetricsConfiguration Source #

Constructors

PeerMetricsConfiguration 

Fields

  • maxEntriesToTrack :: Int

    The maximum numbers of slots we will store data for. On some chains sometimes this corresponds to 1h worth of metrics *sighs*.

    this number MUST correspond to number of headers / blocks which are produced in one hour.

Instances

Instances details
NFData PeerMetricsConfiguration Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PeerMetric

Generic PeerMetricsConfiguration Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PeerMetric

Associated Types

type Rep PeerMetricsConfiguration 
Instance details

Defined in Ouroboros.Network.PeerSelection.PeerMetric

type Rep PeerMetricsConfiguration = D1 ('MetaData "PeerMetricsConfiguration" "Ouroboros.Network.PeerSelection.PeerMetric" "ouroboros-network-0.20.0.0-inplace" 'True) (C1 ('MetaCons "PeerMetricsConfiguration" 'PrefixI 'True) (S1 ('MetaSel ('Just "maxEntriesToTrack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
Show PeerMetricsConfiguration Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PeerMetric

NoThunks PeerMetricsConfiguration Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PeerMetric

type Rep PeerMetricsConfiguration Source # 
Instance details

Defined in Ouroboros.Network.PeerSelection.PeerMetric

type Rep PeerMetricsConfiguration = D1 ('MetaData "PeerMetricsConfiguration" "Ouroboros.Network.PeerSelection.PeerMetric" "ouroboros-network-0.20.0.0-inplace" 'True) (C1 ('MetaCons "PeerMetricsConfiguration" 'PrefixI 'True) (S1 ('MetaSel ('Just "maxEntriesToTrack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

nullMetric :: forall (m :: Type -> Type) p. MonadSTM m => ReportPeerMetrics m p Source #