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

Ouroboros.Network.BlockFetch.ClientState

Contents

Synopsis

Documentation

data FetchClientContext header block m Source #

The context that is passed into the block fetch protocol client when it is started.

data FetchClientPolicy header block m Source #

The policy used by the fetch clients. It is set by the central block fetch logic, and passed to them via the FetchClientRegistry.

Constructors

FetchClientPolicy 

Fields

data FetchClientStateVars m header Source #

A set of variables shared between the block fetch logic thread and each thread executing the client side of the block fetch protocol. That is, these are the shared variables per peer. The FetchClientRegistry contains the mapping of these for all peers.

The variables are used for communicating from the protocol thread to the decision making thread the status of things with that peer. And in the other direction one shared variable is for providing new fetch requests.

Constructors

FetchClientStateVars 

Fields

  • fetchClientStatusVarStrictTVar m (PeerFetchStatus header)

    The current status of communication with the peer. It is written by the protocol thread and monitored and read by the decision logic thread. Changes in this state trigger re-evaluation of fetch decisions.

  • fetchClientInFlightVarStrictTVar m (PeerFetchInFlight header)

    The current number of requests in-flight and the amount of data in-flight with the peer. It is written by the protocol thread and read by the decision logic thread. This is used in fetch decisions but changes here do not trigger re-evaluation of fetch decisions.

  • fetchClientRequestVar ∷ TFetchRequestVar m header

    The shared variable used to communicate fetch requests to the thread running the block fetch protocol. Fetch requests are posted by the decision logic thread. The protocol thread accepts the requests and acts on them, updating the in-flight stats. While this is a TMVar, it is not used as a one-place queue: the requests can be updated before being accepted.

data PeerFetchStatus header Source #

The status of the block fetch communication with a peer. This is maintained by fetch protocol threads and used in the block fetch decision making logic. Changes in this status trigger re-evaluation of fetch decisions.

Constructors

PeerFetchStatusShutdown

Communication with the peer has failed. This is a temporary status that may occur during the process of shutting down the thread that runs the block fetch protocol. The peer will promptly be removed from the peer registry and so will not be considered at all.

PeerFetchStatusStarting

Blockfetch is starting up and waiting on corresponding Chainsync

PeerFetchStatusAberrant

The peer is in a potentially-temporary state in which it has not responded to us within a certain expected time limit. This is not a hard protocol timeout where the whole connection will be abandoned, it is simply a reply that has taken longer than expected. This status is used to trigger re-evaluating which peer to ask for blocks from, so that we can swiftly ask other peers for blocks if one unexpectedly responds too slowly

Peers in this state may later return to normal states if communication resumes, or they may eventually hit a hard timeout and fail.

PeerFetchStatusBusy

Communication with the peer is in a normal state, and the peer is considered too busy to accept new requests. Changing from this state to the ready state is used to trigger re-evaluating fetch decisions and may eventually result in new fetch requests. This state is used as part of a policy to batch new requests: instead of switching to the ready state the moment there is tiny bit of capacity available, the state is changed once the capacity reaches a certain threshold.

PeerFetchStatusReady (Set (Point header)) IsIdle

Communication with the peer is in a normal state, and the peer is considered ready to accept new requests.

The Set is the blocks in flight.

Instances

Instances details
StandardHash header ⇒ Show (PeerFetchStatus header) Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

showsPrecIntPeerFetchStatus header → ShowS #

showPeerFetchStatus header → String #

showList ∷ [PeerFetchStatus header] → ShowS #

StandardHash header ⇒ Eq (PeerFetchStatus header) Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

(==)PeerFetchStatus header → PeerFetchStatus header → Bool #

(/=)PeerFetchStatus header → PeerFetchStatus header → Bool #

data IsIdle Source #

Whether this mini protocol instance is in the Idle State

Constructors

IsIdle 
IsNotIdle 

Instances

Instances details
Show IsIdle Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

showsPrecIntIsIdleShowS #

showIsIdleString #

showList ∷ [IsIdle] → ShowS #

Eq IsIdle Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

(==)IsIdleIsIdleBool #

(/=)IsIdleIsIdleBool #

data PeerFetchInFlight header Source #

The number of requests in-flight and the amount of data in-flight with a peer. This is maintained by fetch protocol threads and used in the block fetch decision making logic.

Constructors

PeerFetchInFlight 

Fields

  • peerFetchReqsInFlight ∷ !Word

    The number of block fetch requests that are currently in-flight. This is the number of requests not the number of blocks. Each request is for a range of blocks.

    We track this because there is a fixed maximum number of outstanding requests that the protocol allows.

  • peerFetchBytesInFlight ∷ !SizeInBytes

    The sum of the byte count of blocks expected from all in-flight fetch requests. This is a close approximation of the amount of data we expect to receive, assuming no failures.

    We track this because we pipeline fetch requests and we want to keep some but not too much data in flight at once.

  • peerFetchBlocksInFlightSet (Point header)

    The points for the set of blocks that are currently in-flight. Note that since requests are for ranges of blocks this does not correspond to the number of requests in flight.

    We track this because as part of the decision for which blocks to fetch from which peers we take into account what blocks are already in-flight with peers.

  • peerFetchMaxSlotNo ∷ !MaxSlotNo

    The maximum slot of a block that has ever been in flight for this peer.

    We track this to more efficiently remove blocks that are already in-flight from the candidate fragments: blocks with a slot number higher than this one do not have to be filtered out.

Instances

Instances details
StandardHash header ⇒ Show (PeerFetchInFlight header) Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

showsPrecIntPeerFetchInFlight header → ShowS #

showPeerFetchInFlight header → String #

showList ∷ [PeerFetchInFlight header] → ShowS #

StandardHash header ⇒ Eq (PeerFetchInFlight header) Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

(==)PeerFetchInFlight header → PeerFetchInFlight header → Bool #

(/=)PeerFetchInFlight header → PeerFetchInFlight header → Bool #

newtype FetchRequest header Source #

Constructors

FetchRequest 

Instances

Instances details
HasHeader header ⇒ Semigroup (FetchRequest header) Source #

We sometimes have the opportunity to merge fetch request fragments to reduce the number of separate range request messages that we send. We send one message per fragment. It is better to send fewer requests for bigger ranges, rather than lots of requests for small ranges.

We never expect fetch requests to overlap (ie have blocks in common) but we do expect a common case that requests will "touch" so that two ranges could be merged into a single contiguous range.

This semigroup instance implements this merging when possible, otherwise the two lists of fragments are just appended.

A consequence of merging and sending fewer request messages is that tracking the number of requests in-flight a bit more subtle. To track this accurately we have to look at the old request as well a the updated request after any merging. We meed to account for the difference in the number of fragments in the existing request (if any) and in new request.

Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

(<>)FetchRequest header → FetchRequest header → FetchRequest header #

sconcatNonEmpty (FetchRequest header) → FetchRequest header #

stimesIntegral b ⇒ b → FetchRequest header → FetchRequest header #

(StandardHash header, Show header) ⇒ Show (FetchRequest header) Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

Methods

showsPrecIntFetchRequest header → ShowS #

showFetchRequest header → String #

showList ∷ [FetchRequest header] → ShowS #

addNewFetchRequest ∷ (MonadSTM m, HasHeader header) ⇒ Tracer m (TraceFetchClientState header) → (header → SizeInBytes) → FetchRequest header → PeerGSVFetchClientStateVars m header → m (PeerFetchStatus header) Source #

Add a new fetch request for a single peer. This is used by the fetch decision logic thread to add new fetch requests.

We have as a pre-condition that all requested blocks are new, i.e. none should appear in the existing peerFetchBlocksInFlight. This is a relatively easy precondition to satisfy since the decision logic can filter its requests based on this in-flight blocks state, and this operation is the only operation that grows the in-flight blocks, and is only used by the fetch decision logic thread.

acknowledgeFetchRequestMonadSTM m ⇒ Tracer m (TraceFetchClientState header) → ControlMessageSTM m → FetchClientStateVars m header → m (Maybe (FetchRequest header, PeerGSV, PeerFetchInFlightLimits)) Source #

This is used by the fetch client threads.

completeBlockDownload ∷ (MonadSTM m, HasHeader header) ⇒ Tracer m (TraceFetchClientState header) → (header → SizeInBytes) → PeerFetchInFlightLimits → header → NominalDiffTimeFetchClientStateVars m header → m () Source #

rejectedFetchBatch ∷ (MonadSTM m, HasHeader header) ⇒ Tracer m (TraceFetchClientState header) → (header → SizeInBytes) → PeerFetchInFlightLimitsChainRange (Point header) → [header] → FetchClientStateVars m header → m () Source #

data TraceFetchClientState header Source #

Tracing types for the various events that change the state (i.e. FetchClientStateVars) for a block fetch client.

Note that while these are all state changes, the AddedFetchRequest occurs in the decision thread while the other state changes occur in the block fetch client threads.

Constructors

AddedFetchRequest (FetchRequest header) (PeerFetchInFlight header) PeerFetchInFlightLimits (PeerFetchStatus header)

The block fetch decision thread has added a new fetch instruction consisting of one or more individual request ranges.

AcknowledgedFetchRequest (FetchRequest header)

Mark the point when the fetch client picks up the request added by the block fetch decision thread. Note that this event can happen fewer times than the AddedFetchRequest due to fetch request merging.

SendFetchRequest (AnchoredFragment header) PeerGSV

Mark the point when fetch request for a fragment is actually sent over the wire.

StartedFetchBatch (ChainRange (Point header)) (PeerFetchInFlight header) PeerFetchInFlightLimits (PeerFetchStatus header)

Mark the start of receiving a streaming batch of blocks. This will be followed by one or more CompletedBlockFetch and a final CompletedFetchBatch.

CompletedBlockFetch (Point header) (PeerFetchInFlight header) PeerFetchInFlightLimits (PeerFetchStatus header) NominalDiffTime SizeInBytes

Mark the completion of of receiving a single block within a streaming batch of blocks.

CompletedFetchBatch (ChainRange (Point header)) (PeerFetchInFlight header) PeerFetchInFlightLimits (PeerFetchStatus header)

Mark the successful end of receiving a streaming batch of blocks

RejectedFetchBatch (ChainRange (Point header)) (PeerFetchInFlight header) PeerFetchInFlightLimits (PeerFetchStatus header)

If the other peer rejects our request then we have this event instead of StartedFetchBatch and CompletedFetchBatch.

ClientTerminating Int

The client is terminating. Log the number of outstanding requests.

Instances

Instances details
(StandardHash header, Show header) ⇒ Show (TraceFetchClientState header) Source # 
Instance details

Defined in Ouroboros.Network.BlockFetch.ClientState

data TraceLabelPeer peerid a Source #

A peer label for use in Tracers. This annotates tracer output as being associated with a given peer identifier.

Constructors

TraceLabelPeer peerid a 

Instances

Instances details
Bifunctor TraceLabelPeer 
Instance details

Defined in Network.Mux.Trace

Methods

bimap ∷ (a → b) → (c → d) → TraceLabelPeer a c → TraceLabelPeer b d #

first ∷ (a → b) → TraceLabelPeer a c → TraceLabelPeer b c #

second ∷ (b → c) → TraceLabelPeer a b → TraceLabelPeer a c #

Functor (TraceLabelPeer peerid) 
Instance details

Defined in Network.Mux.Trace

Methods

fmap ∷ (a → b) → TraceLabelPeer peerid a → TraceLabelPeer peerid b #

(<$) ∷ a → TraceLabelPeer peerid b → TraceLabelPeer peerid a #

(Show peerid, Show a) ⇒ Show (TraceLabelPeer peerid a) 
Instance details

Defined in Network.Mux.Trace

Methods

showsPrecIntTraceLabelPeer peerid a → ShowS #

showTraceLabelPeer peerid a → String #

showList ∷ [TraceLabelPeer peerid a] → ShowS #

(Eq peerid, Eq a) ⇒ Eq (TraceLabelPeer peerid a) 
Instance details

Defined in Network.Mux.Trace

Methods

(==)TraceLabelPeer peerid a → TraceLabelPeer peerid a → Bool #

(/=)TraceLabelPeer peerid a → TraceLabelPeer peerid a → Bool #

data ChainRange point Source #

Range of blocks, defined by a lower and upper point, inclusive.

Constructors

ChainRange !point !point 

Instances

Instances details
Generic (ChainRange point) 
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

Associated Types

type Rep (ChainRange point) ∷ TypeType #

Methods

fromChainRange point → Rep (ChainRange point) x #

toRep (ChainRange point) x → ChainRange point #

Show point ⇒ Show (ChainRange point) 
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

Methods

showsPrecIntChainRange point → ShowS #

showChainRange point → String #

showList ∷ [ChainRange point] → ShowS #

NFData point ⇒ NFData (ChainRange point) 
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

Methods

rnfChainRange point → () #

Eq point ⇒ Eq (ChainRange point) 
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

Methods

(==)ChainRange point → ChainRange point → Bool #

(/=)ChainRange point → ChainRange point → Bool #

Ord point ⇒ Ord (ChainRange point) 
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

Methods

compareChainRange point → ChainRange point → Ordering #

(<)ChainRange point → ChainRange point → Bool #

(<=)ChainRange point → ChainRange point → Bool #

(>)ChainRange point → ChainRange point → Bool #

(>=)ChainRange point → ChainRange point → Bool #

maxChainRange point → ChainRange point → ChainRange point #

minChainRange point → ChainRange point → ChainRange point #

type Rep (ChainRange point) 
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

type Rep (ChainRange point) = D1 ('MetaData "ChainRange" "Ouroboros.Network.Protocol.BlockFetch.Type" "ouroboros-network-protocols-0.8.1.0-inplace" 'False) (C1 ('MetaCons "ChainRange" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 point) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 point)))

Ancillary

newtype FromConsensus a Source #

A new type used to emphasize the precondition of headerForgeUTCTime and blockForgeUTCTime at each call site.

At time of writing, the a is either a header or a block. The headers are literally from Consensus (ie provided by ChainSync). Blocks, on the other hand, are indirectly from Consensus: they were fetched only because we favored the corresponding header that Consensus provided.

Constructors

FromConsensus 

Fields

Instances

Instances details
Applicative FromConsensus 
Instance details

Defined in Ouroboros.Network.BlockFetch.ConsensusInterface

Methods

pure ∷ a → FromConsensus a #

(<*>)FromConsensus (a → b) → FromConsensus a → FromConsensus b #

liftA2 ∷ (a → b → c) → FromConsensus a → FromConsensus b → FromConsensus c #

(*>)FromConsensus a → FromConsensus b → FromConsensus b #

(<*)FromConsensus a → FromConsensus b → FromConsensus a #

Functor FromConsensus 
Instance details

Defined in Ouroboros.Network.BlockFetch.ConsensusInterface

Methods

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

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

data WhetherReceivingTentativeBlocks Source #

Whether the block fetch peer is sending tentative blocks, which are understood to possibly be invalid