ouroboros-consensus-0.26.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.HeaderValidation

Description

Header validation

Synopsis

Documentation

revalidateHeader ∷ (BlockSupportsProtocol blk, ValidateEnvelope blk, HasCallStack) ⇒ TopLevelConfig blk → LedgerView (BlockProtocol blk) → Header blk → Ticked (HeaderState blk) → HeaderState blk Source #

Header revalidation

Same as validateHeader but used when the header has been validated before w.r.t. the same exact HeaderState.

Expensive validation checks are skipped (reupdateChainDepState vs. updateChainDepState).

validateHeader ∷ (BlockSupportsProtocol blk, ValidateEnvelope blk) ⇒ TopLevelConfig blk → LedgerView (BlockProtocol blk) → Header blk → Ticked (HeaderState blk) → Except (HeaderError blk) (HeaderState blk) Source #

Header validation

Header validation (as opposed to block validation) is done by the chain sync client: as we download headers from other network nodes, we validate those headers before deciding whether or not to download the corresponding blocks.

Before we adopt any blocks we have downloaded, however, we will do a full block validation. As such, the header validation check can omit some checks (provided that we do those checks when we do the full validation); at worst, this would mean we might download some blocks that we will reject as being invalid where we could have detected that sooner.

For this reason, the header validation currently only checks two things:

  • It verifies the consensus part of the header.

For example, for Praos this means checking the VRF proofs.

  • It verifies the HasHeader part of the header.

By default, we verify that

  • Block numbers are consecutive
  • The block number of the first block is firstBlockNo
  • Slot numbers are strictly increasing
  • The slot number of the first block is at least minimumPossibleSlotNo
  • Hashes line up

If a particular ledger wants to verify additional fields in the header, it will get the chance to do so in applyBlockLedgerResult, which is passed the entire block (not just the block body).

Annotated tips

data AnnTip blk Source #

Annotated information about the tip of the chain

The annotation is the additional information we need to validate the header envelope. Under normal circumstances no additional information is required, but for instance for Byron we need to know if the previous header was an EBB.

Constructors

AnnTip 

Instances

Instances details
Inject AnnTip Source # 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → AnnTip x → AnnTip (HardForkBlock xs) Source #

Isomorphic AnnTip Source # 
Instance details

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

Methods

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

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

Generic (AnnTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (AnnTip blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (AnnTip blk) = D1 ('MetaData "AnnTip" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "AnnTip" 'PrefixI 'True) (S1 ('MetaSel ('Just "annTipSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "annTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "annTipInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TipInfo blk)))))

Methods

fromAnnTip blk → Rep (AnnTip blk) x #

toRep (AnnTip blk) x → AnnTip blk #

HasAnnTip blk ⇒ Show (AnnTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

showsPrecIntAnnTip blk → ShowS #

showAnnTip blk → String #

showList ∷ [AnnTip blk] → ShowS #

HasAnnTip blk ⇒ Eq (AnnTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

(==)AnnTip blk → AnnTip blk → Bool #

(/=)AnnTip blk → AnnTip blk → Bool #

HasAnnTip blk ⇒ NoThunks (AnnTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (AnnTip (HardForkBlock xs)) Source # 
Instance details

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

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (AnnTip (HardForkBlock xs)) Source # 
Instance details

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

type Rep (AnnTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (AnnTip blk) = D1 ('MetaData "AnnTip" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "AnnTip" 'PrefixI 'True) (S1 ('MetaSel ('Just "annTipSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "annTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "annTipInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TipInfo blk)))))

class (StandardHash blk, Show (TipInfo blk), Eq (TipInfo blk), NoThunks (TipInfo blk)) ⇒ HasAnnTip blk where Source #

Minimal complete definition

Nothing

Associated Types

type TipInfo blk Source #

type TipInfo blk = HeaderHash blk

Methods

getTipInfoHeader blk → TipInfo blk Source #

Extract TipInfo from a block header

default getTipInfo ∷ (TipInfo blk ~ HeaderHash blk, HasHeader (Header blk)) ⇒ Header blk → TipInfo blk Source #

tipInfoHash ∷ proxy blk → TipInfo blk → HeaderHash blk Source #

The tip info must at least include the hash

default tipInfoHashTipInfo blk ~ HeaderHash blk ⇒ proxy blk → TipInfo blk → HeaderHash blk Source #

Instances

Instances details
CanHardFork xs ⇒ HasAnnTip (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Associated Types

type TipInfo (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Bridge m a ⇒ HasAnnTip (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type TipInfo (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TipInfo (DualBlock m a) = TipInfo m

Methods

getTipInfoHeader (DualBlock m a) → TipInfo (DualBlock m a) Source #

tipInfoHash ∷ proxy (DualBlock m a) → TipInfo (DualBlock m a) → HeaderHash (DualBlock m a) Source #

annTipHashHasAnnTip blk ⇒ AnnTip blk → HeaderHash blk Source #

annTipPointHasAnnTip blk ⇒ AnnTip blk → Point blk Source #

castAnnTipTipInfo blk ~ TipInfo blk' ⇒ AnnTip blk → AnnTip blk' Source #

getAnnTip ∷ (HasHeader (Header blk), HasAnnTip blk) ⇒ Header blk → AnnTip blk Source #

mapAnnTip ∷ (TipInfo blk → TipInfo blk') → AnnTip blk → AnnTip blk' Source #

Header state

data HeaderState blk Source #

State required to validate the header

See validateHeader for details

Instances

Instances details
Inject HeaderState Source # 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → HeaderState x → HeaderState (HardForkBlock xs) Source #

Isomorphic HeaderState Source # 
Instance details

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

Generic (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderState blk) = D1 ('MetaData "HeaderState" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HeaderState" 'PrefixI 'True) (S1 ('MetaSel ('Just "headerStateTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (AnnTip blk))) :*: S1 ('MetaSel ('Just "headerStateChainDep") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ChainDepState (BlockProtocol blk)))))

Methods

fromHeaderState blk → Rep (HeaderState blk) x #

toRep (HeaderState blk) x → HeaderState blk #

(BlockSupportsProtocol blk, HasAnnTip blk) ⇒ Show (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

showsPrecIntHeaderState blk → ShowS #

showHeaderState blk → String #

showList ∷ [HeaderState blk] → ShowS #

(BlockSupportsProtocol blk, HasAnnTip blk) ⇒ Eq (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

(==)HeaderState blk → HeaderState blk → Bool #

(/=)HeaderState blk → HeaderState blk → Bool #

(BlockSupportsProtocol blk, HasAnnTip blk) ⇒ NoThunks (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (HeaderState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderState blk) = D1 ('MetaData "HeaderState" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HeaderState" 'PrefixI 'True) (S1 ('MetaSel ('Just "headerStateTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (AnnTip blk))) :*: S1 ('MetaSel ('Just "headerStateChainDep") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ChainDepState (BlockProtocol blk)))))

Validate header envelope

class (HasHeader (Header blk), HasAnnTip blk) ⇒ BasicEnvelopeValidation blk where Source #

Ledger-independent envelope validation (block, slot, hash)

Minimal complete definition

Nothing

Methods

expectedFirstBlockNo ∷ proxy blk → BlockNo Source #

The block number of the first block on the chain

expectedNextBlockNo Source #

Arguments

∷ proxy blk 
TipInfo blk

Old tip

TipInfo blk

New block

BlockNo 
BlockNo 

Next block number

minimumPossibleSlotNoProxy blk → SlotNo Source #

The smallest possible SlotNo

NOTE: This does not affect the translation between SlotNo and EpochNo. Ouroboros.Consensus.HardFork.History for details.

minimumNextSlotNo Source #

Arguments

∷ proxy blk 
TipInfo blk

Old tip

TipInfo blk

New block

SlotNo 
SlotNo 

Minimum next slot number

data HeaderEnvelopeError blk Source #

Constructors

UnexpectedBlockNo !BlockNo !BlockNo

Invalid block number

We record both the expected and actual block number

UnexpectedSlotNo !SlotNo !SlotNo

Invalid slot number

We record both the expected (minimum) and actual slot number

UnexpectedPrevHash !(WithOrigin (HeaderHash blk)) !(ChainHash blk)

Invalid hash (in the reference to the previous block)

We record the current tip as well as the prev hash of the new block.

CheckpointMismatch !BlockNo !(HeaderHash blk) !(HeaderHash blk)

The block at the given block number has a hash which does not match the expected checkpoint hash.

CheckpointMismatch blockNo expected actual
OtherHeaderEnvelopeError !(OtherHeaderEnvelopeError blk)

Block specific envelope error

Instances

Instances details
Generic (HeaderEnvelopeError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (HeaderEnvelopeError blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderEnvelopeError blk) = D1 ('MetaData "HeaderEnvelopeError" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) ((C1 ('MetaCons "UnexpectedBlockNo" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo)) :+: C1 ('MetaCons "UnexpectedSlotNo" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo))) :+: (C1 ('MetaCons "UnexpectedPrevHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (HeaderHash blk))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ChainHash blk))) :+: (C1 ('MetaCons "CheckpointMismatch" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash blk)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash blk)))) :+: C1 ('MetaCons "OtherHeaderEnvelopeError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OtherHeaderEnvelopeError blk))))))
ValidateEnvelope blk ⇒ Show (HeaderEnvelopeError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

ValidateEnvelope blk ⇒ Eq (HeaderEnvelopeError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

(ValidateEnvelope blk, Typeable blk) ⇒ NoThunks (HeaderEnvelopeError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderEnvelopeError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderEnvelopeError blk) = D1 ('MetaData "HeaderEnvelopeError" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) ((C1 ('MetaCons "UnexpectedBlockNo" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo)) :+: C1 ('MetaCons "UnexpectedSlotNo" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo))) :+: (C1 ('MetaCons "UnexpectedPrevHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (HeaderHash blk))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ChainHash blk))) :+: (C1 ('MetaCons "CheckpointMismatch" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash blk)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash blk)))) :+: C1 ('MetaCons "OtherHeaderEnvelopeError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OtherHeaderEnvelopeError blk))))))

class (BasicEnvelopeValidation blk, GetPrevHash blk, Eq (OtherHeaderEnvelopeError blk), Show (OtherHeaderEnvelopeError blk), NoThunks (OtherHeaderEnvelopeError blk)) ⇒ ValidateEnvelope blk where Source #

Validate header envelope

Minimal complete definition

Nothing

Associated Types

type OtherHeaderEnvelopeError blk Source #

A block-specific error that validateEnvelope can return.

Methods

additionalEnvelopeChecksTopLevelConfig blk → LedgerView (BlockProtocol blk) → Header blk → Except (OtherHeaderEnvelopeError blk) () Source #

Do additional envelope checks

Errors

data HeaderError blk Source #

Invalid header

Constructors

HeaderProtocolError !(ValidationErr (BlockProtocol blk))

Invalid consensus protocol fields

HeaderEnvelopeError !(HeaderEnvelopeError blk)

Failed to validate the envelope

Instances

Instances details
Generic (HeaderError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (HeaderError blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderError blk) = D1 ('MetaData "HeaderError" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HeaderProtocolError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ValidationErr (BlockProtocol blk)))) :+: C1 ('MetaCons "HeaderEnvelopeError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderEnvelopeError blk))))

Methods

fromHeaderError blk → Rep (HeaderError blk) x #

toRep (HeaderError blk) x → HeaderError blk #

(BlockSupportsProtocol blk, ValidateEnvelope blk) ⇒ Show (HeaderError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

showsPrecIntHeaderError blk → ShowS #

showHeaderError blk → String #

showList ∷ [HeaderError blk] → ShowS #

(BlockSupportsProtocol blk, ValidateEnvelope blk) ⇒ Eq (HeaderError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

(==)HeaderError blk → HeaderError blk → Bool #

(/=)HeaderError blk → HeaderError blk → Bool #

(BlockSupportsProtocol blk, ValidateEnvelope blk) ⇒ NoThunks (HeaderError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderError blk) = D1 ('MetaData "HeaderError" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HeaderProtocolError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ValidationErr (BlockProtocol blk)))) :+: C1 ('MetaCons "HeaderEnvelopeError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderEnvelopeError blk))))

TipInfoIsEBB

data TipInfoIsEBB blk Source #

Reusable strict data type for TipInfo in case the TipInfo should contain IsEBB in addition to the HeaderHash.

Constructors

TipInfoIsEBB !(HeaderHash blk) !IsEBB 

Instances

Instances details
Generic (TipInfoIsEBB blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (TipInfoIsEBB blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (TipInfoIsEBB blk) = D1 ('MetaData "TipInfoIsEBB" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "TipInfoIsEBB" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash blk)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IsEBB)))

Methods

fromTipInfoIsEBB blk → Rep (TipInfoIsEBB blk) x #

toRep (TipInfoIsEBB blk) x → TipInfoIsEBB blk #

StandardHash blk ⇒ Show (TipInfoIsEBB blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

showsPrecIntTipInfoIsEBB blk → ShowS #

showTipInfoIsEBB blk → String #

showList ∷ [TipInfoIsEBB blk] → ShowS #

StandardHash blk ⇒ Eq (TipInfoIsEBB blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

(==)TipInfoIsEBB blk → TipInfoIsEBB blk → Bool #

(/=)TipInfoIsEBB blk → TipInfoIsEBB blk → Bool #

StandardHash blk ⇒ NoThunks (TipInfoIsEBB blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (TipInfoIsEBB blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (TipInfoIsEBB blk) = D1 ('MetaData "TipInfoIsEBB" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "TipInfoIsEBB" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash blk)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IsEBB)))

Serialization

decodeAnnTipIsEBBTipInfo blk ~ TipInfoIsEBB blk ⇒ (∀ s. Decoder s (HeaderHash blk)) → ∀ s. Decoder s (AnnTip blk) Source #

decodeHeaderState ∷ (∀ s. Decoder s (ChainDepState (BlockProtocol blk))) → (∀ s. Decoder s (AnnTip blk)) → ∀ s. Decoder s (HeaderState blk) Source #

defaultDecodeAnnTipTipInfo blk ~ HeaderHash blk ⇒ (∀ s. Decoder s (HeaderHash blk)) → ∀ s. Decoder s (AnnTip blk) Source #

Type family instances

data family Ticked (st ∷ k) ∷ k Source #

" Ticked " piece of state, either LedgerState or ChainDepState

Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state. There are exactly two methods in the interface that do that: tickChainDepState and applyChainTickLedgerResult.

Also note that a successful forecast forecastFor (ledgerViewForecastAt cfg st) slot must equal protocolLedgerView cfg (applyChainTick cfg slot st). Thus a LedgerView can only be projected from a Ticked state, but cannot itself be ticked.

Some examples of time related changes:

  • Scheduled delegations might have been applied in Byron
  • New leader schedule computed for Shelley
  • Transition from Byron to Shelley activated in the hard fork combinator.
  • Nonces switched out at the start of a new epoch.

Instances

Instances details
Show (Ticked ()) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (HardForkBlock xs)) mk → Point (Ticked (LedgerState (HardForkBlock xs))) Source #

Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (ExtLedgerState blk) mk → Point (Ticked (ExtLedgerState blk)) Source #

(CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ HasLedgerTables (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(HasLedgerTables (Ticked (LedgerState blk)), NoThunks (TxOut (LedgerState blk)), NoThunks (TxIn (LedgerState blk)), Show (TxOut (LedgerState blk)), Show (TxIn (LedgerState blk)), Eq (TxOut (LedgerState blk)), Ord (TxIn (LedgerState blk)), MemPack (TxIn (LedgerState blk))) ⇒ HasLedgerTables (Ticked (ExtLedgerState blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) mk → LedgerTables (Ticked (ExtLedgerState blk)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) any → LedgerTables (Ticked (ExtLedgerState blk)) mk → Ticked (ExtLedgerState blk) mk Source #

LedgerTablesAreTrivial (Ticked (LedgerState blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (ExtLedgerState blk) mk → Ticked (ExtLedgerState blk) mk' Source #

NoThunks (Ticked (LedgerState (DualBlock m a)) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Ticked (f a)) ⇒ Show (((TickedTypeType) :.: f) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → ((TickedTypeType) :.: f) a → ShowS #

show ∷ ((TickedTypeType) :.: f) a → String #

showList ∷ [((TickedTypeType) :.: f) a] → ShowS #

NoThunks (Ticked (f a)) ⇒ NoThunks (((TickedTypeType) :.: f) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

noThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

wNoThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (((TickedTypeType) :.: f) a) → String Source #

data Ticked () Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked (HardForkChainDepState xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (PBftState c ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

type HeaderHash (Ticked l ∷ k) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ k) = HeaderHash l
type TxIn (Ticked l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (Ticked l) = TxIn l
type TxOut (Ticked l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (Ticked l) = TxOut l
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (ExtLedgerState blk ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Header with time

data HeaderWithTime blk Source #

A header paired with the time of the slot that it inhabits.

Note that the header's slot was translated to this time (in the ChainSync client) according to the header's chain. This clarification may be helpful, since it's possible that some other chain would translate that same slot to a different time.

Constructors

HeaderWithTime 

Instances

Instances details
GetHeader1 HeaderWithTime Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

getHeader1HeaderWithTime blk → Header blk Source #

(Show (HeaderHash blk), Eq (HeaderHash blk), Ord (HeaderHash blk), Typeable (HeaderHash blk), NoThunks (HeaderHash blk)) ⇒ StandardHash (HeaderWithTime blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Generic (HeaderWithTime blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Associated Types

type Rep (HeaderWithTime blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderWithTime blk) = D1 ('MetaData "HeaderWithTime" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HeaderWithTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "hwtHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Header blk)) :*: S1 ('MetaSel ('Just "hwtSlotRelativeTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RelativeTime)))

Methods

fromHeaderWithTime blk → Rep (HeaderWithTime blk) x #

toRep (HeaderWithTime blk) x → HeaderWithTime blk #

Show (Header blk) ⇒ Show (HeaderWithTime blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

showsPrecIntHeaderWithTime blk → ShowS #

showHeaderWithTime blk → String #

showList ∷ [HeaderWithTime blk] → ShowS #

Eq (Header blk) ⇒ Eq (HeaderWithTime blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

Methods

(==)HeaderWithTime blk → HeaderWithTime blk → Bool #

(/=)HeaderWithTime blk → HeaderWithTime blk → Bool #

NoThunks (Header blk) ⇒ NoThunks (HeaderWithTime blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

(HasHeader (Header blk), StandardHash (HeaderWithTime blk), Typeable blk) ⇒ HasHeader (HeaderWithTime blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

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

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderWithTime blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

type Rep (HeaderWithTime blk) = D1 ('MetaData "HeaderWithTime" "Ouroboros.Consensus.HeaderValidation" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HeaderWithTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "hwtHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Header blk)) :*: S1 ('MetaSel ('Just "hwtSlotRelativeTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RelativeTime)))

mkHeaderWithTime ∷ ∀ blk (mk ∷ MapKind). (HasHardForkHistory blk, HasHeader (Header blk)) ⇒ LedgerConfig blk → LedgerState blk mk → Header blk → HeaderWithTime blk Source #

Convert Header to HeaderWithTime

PREREQ: The given ledger must be able to translate the slot of the given header.

This is INLINEed since the summary can usually be reused.