ouroboros-consensus-0.18.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Block.SupportsDiffusionPipelining

Description

Synopsis

Documentation

class (Show (TentativeHeaderState blk), NoThunks (TentativeHeaderState blk), Show (TentativeHeaderView blk)) ⇒ BlockSupportsDiffusionPipelining blk where Source #

Block functionality required to support __Block Diffusion Pipelining via Delayed Validation__ (DPvDV).

High-level context

With DPvDV, a node is, under certain conditions, already announcing a new block to its downstream peers before it has fully validated the block body. Concretely, the node maintains a tentative header that, if present, extends the current selection, and is announced via the ChainSync servers to downstream peers.

Ideally, the body turns out to be valid, in which case the tentative header is set to Nothing, and the selection is updated to now include the header at its tip.

If the body corresponding to the tentative header turns out to be invalid (we call such a header a trap header), the tentative header is cleared, and the ChainSync servers send a rollback instruction. In this case, the network wasted work in diffusing, storing and validating this block. If abused, this could cause an unbounded amount of work for honest nodes. Hence, we need to enforce that our upstream nodes adhere to an appropriate criterion related to trap headers, and so must also restrict ourselves accordingly such that downstream nodes do not disconnect from us.

Semantics

This type class allows to define a block-specific criterion determining whether a header that might turn out to be a trap header is allowed to be set as the tentative header.

This is used in two places:

  • The ChainSel logic. We make sure that we only set the tentative header if this criterion is fulfilled.
  • The BlockFetch clients, in combination with the ChainSel validation logic. For every upstream BlockFetch peer, we make sure that the invalid blocks this peer sent adhere to the pipelining criterion.

Concretely, the abstract Consensus layer maintains TentativeHeaderStates (one in ChainSel, and one for each (BlockFetch) upstream peer). Suppose that hdr either might turn out or is already known to be a trap header. Then

applyTentativeHeaderView (Proxy @blk) thv st

(where thv = tentativeHeaderView bcfg hdr) will return

  • Nothing if hdr does not satisfy the pipelining criterion.

    • In ChainSel, this means that hdr should not be pipelined, as it would violate the criterion if it turns out to be a trap header.
    • In the BlockFetch punishment logic, this means that we disconnect from the peer that sent the corresponding invalid block.
  • Just st' if hdr does satisfy the pipelining criterion. If the hdr is (in the BlockFetch punishment logic) or turns out to be (in ChainSel) a trap header, the TentativeHeaderState should be updated to the returned st'.

Requirements

Safety

The criterion is sufficiently strict such that an adversary can not induce an unbounded amount of work for honest nodes.

Consistent validity under subsequences

Suppose that over some period of time, an honest node advertised the headers hdrs :: [Header blk] as its trap tentative headers. A downstream honest node might only observe a subsequence of this list (there's no guarantee that every ChainSync server sends every selected tip), but must still consider our behavior as valid.

Hence, for every subsequence thvs' of thvs = tentativeHeaderView bcfg <$> hdrs, we need to have

isJust hdrs'Valid

for all st :: TentativeHeaderState blk and

hdrsValid  = foldlM (flip $ applyTentativeHeaderView p) st thvs
hdrs'Valid = foldlM (flip $ applyTentativeHeaderView p) st thvs'

where isJust hdrsValid and p :: Proxy blk.

Efficiently enforcible

The TentativeHeaderState must have bounded size, and applyTentativeHeaderView must be efficient and objective (different nodes must agree on its result for the same header and state).

As a historical example for establishing objectivity, see the removal of the isSelfIssued tiebreaker in the chain order.

Usefulness despite adversarial activity

It must not be possible for an adversary to easily manipulate the TentativeHeaderState in such a way that almost no headers can be pipelined anymore. It is acceptable if DPvDV is less effective in scenarios involving an adversary with a very large amount of resources (like stake).

Associated Types

type TentativeHeaderState blk ∷ Type Source #

State that is maintained to judge whether a header can be pipelined. It can be thought of as a summary of all past trap tentative headers.

type TentativeHeaderView blk ∷ Type Source #

View on a header required for updating the TentativeHeaderState.

Methods

initialTentativeHeaderStateProxy blk → TentativeHeaderState blk Source #

The initial TentativeHeaderState. This is used as the initial value on node startup, as well as by the HFC instance for new eras.

tentativeHeaderViewBlockConfig blk → Header blk → TentativeHeaderView blk Source #

applyTentativeHeaderView Source #

Arguments

Proxy blk 
TentativeHeaderView blk

Extracted using tentativeHeaderView from a (valid) header whose block body is either not yet known to be valid, or definitely invalid.

TentativeHeaderState blk

The most recent TentativeHeaderState in this particular context.

Maybe (TentativeHeaderState blk)

The new TentativeHeaderState in case the header satisfies the pipelining criterion and is a trap header.

Apply a TentativeHeaderView to the TentativeHeaderState. This returns Just st to indicate that the underlying header can be pipelined, and that the TentativeHeaderState must be updated to st if the header turns/turned out to be a trap header (ie the corresponding block body is invalid).

Also see updateTentativeHeaderState.

Instances

Instances details
BlockSupportsDiffusionPipelining (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

(BlockSupportsProtocol blk, Show (SelectView (BlockProtocol blk))) ⇒ BlockSupportsDiffusionPipelining (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

CanHardFork xs ⇒ BlockSupportsDiffusionPipelining (HardForkBlock xs) Source #

The BlockSupportsDiffusionPipelining instance for the HFC is compositional:

This behavior guarantees the "Consistent validity under subsequences" requirement if it is satisfied for every era.

Note that at an era boundary, the tip of the selection might switch multiple times between two adjacent eras. Compared to the scenario where the pipelining criteria in both eras are compatible and make sense even across eras, this might lead to unnecessarily strict/relaxed diffusion pipelining. However, the tip switching between different eras is rare and rather short, so there is no direct need to address this, so we rather avoid the extra complexity for now.

Still, a possible future refinement would be to allow custom logic for "upgrading" the TentativeHeaderState to a new era.

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Node.DiffusionPipelining

DerivingVia helpers

DisableDiffusionPipelining

newtype DisableDiffusionPipelining blk Source #

A DerivingVia helper to implement BlockSupportsDiffusionPipelining for blocks where no header should ever be pipelined.

deriving via DisableDiffusionPipelining MyBlock
  instance BlockSupportsDiffusionPipelining MyBlock

Constructors

DisableDiffusionPipelining blk 

Instances

Instances details
BlockSupportsDiffusionPipelining (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

type TentativeHeaderState (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

type TentativeHeaderView (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

SelectViewDiffusionPipelining

newtype SelectViewDiffusionPipelining blk Source #

A DerivingVia helper to implement BlockSupportsDiffusionPipelining for blocks where a header should be pipelined iff it has a better SelectView than the last tentative trap header.

deriving via DisableDiffusionPipelining MyBlock
  instance BlockSupportsProtocol blk
  => BlockSupportsDiffusionPipelining MyBlock

This requires that the SelectView is totally ordered, in particular that the order is transitive.

For example, if SelectView ~ BlockNo, this means that a header can be pipelined if it has a larger block number than the last tentative trap header. So if someone diffused a trap header for a particular block height, no other block can be pipelined for that block height. This would limit the Usefulness despite adversarial activity if an attacker diffuses a trap header (and later also a valid block) every time they are elected.

Instances

Instances details
(BlockSupportsProtocol blk, Show (SelectView (BlockProtocol blk))) ⇒ BlockSupportsDiffusionPipelining (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

type TentativeHeaderState (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

type TentativeHeaderView (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

data SelectViewTentativeState proto Source #

Instances

Instances details
Generic (SelectViewTentativeState proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

Associated Types

type Rep (SelectViewTentativeState proto) ∷ TypeType #

ConsensusProtocol proto ⇒ Show (SelectViewTentativeState proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

ConsensusProtocol proto ⇒ Eq (SelectViewTentativeState proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

ConsensusProtocol proto ⇒ NoThunks (SelectViewTentativeState proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

type Rep (SelectViewTentativeState proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

type Rep (SelectViewTentativeState proto) = D1 ('MetaData "SelectViewTentativeState" "Ouroboros.Consensus.Block.SupportsDiffusionPipelining" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "LastInvalidSelectView" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SelectView proto))) :+: C1 ('MetaCons "NoLastInvalidSelectView" 'PrefixI 'False) (U1TypeType))

Data family instances

data family BlockConfig blk ∷ Type Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Isomorphic BlockConfig Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype BlockConfig (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family Header blk ∷ Type Source #

Instances

Instances details
Inject Header Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → Header x → Header (HardForkBlock xs) Source #

Isomorphic Header Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source #

injectNoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source #

CanHardFork xs ⇒ HasNestedContent Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ ReconstructNestedCtxt Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

HasHeader blk ⇒ StandardHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Typeable xs ⇒ ShowProxy (Header (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → String Source #

CanHardFork xs ⇒ Show (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

All (Compose Eq Header) xs ⇒ Eq (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Methods

(==)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

(/=)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

CanHardFork xs ⇒ NoThunks (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

NoThunks (Header (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All CondenseConstraints xs ⇒ Condense (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

CanHardFork xs ⇒ HasHeader (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ DecodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ DecodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

encodeDiskDepCodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source #

EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Header m) ⇒ Show (DualHeader m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualHeader m a → ShowS #

showDualHeader m a → String #

showList ∷ [DualHeader m a] → ShowS #

CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Bridge m a ⇒ HasHeader (DualHeader m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All SingleEraBlock xs ⇒ Show (NestedCtxt_ (HardForkBlock xs) Header a) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type HeaderHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk ∷ Type) = HeaderHash blk
type BlockProtocol (Header blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual