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

Ouroboros.Consensus.Protocol.PBFT

Synopsis

Documentation

data PBft c Source #

Instances

Instances details
Generic (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (PBft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
NoThunks (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ ConsensusProtocol (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type ChainDepState (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type IsLeader (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type CanBeLeader (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type SelectView (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type LedgerView (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type ValidationErr (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type ValidateView (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (PBft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
type CanBeLeader (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type ChainDepState (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype ConsensusConfig (PBft c) Source #

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type IsLeader (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type LedgerView (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type SelectView (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type ValidateView (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type ValidationErr (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data PBftCanBeLeader c Source #

If we are a core node (i.e. a block producing node) we know which core node we are, and we have the operational key pair and delegation certificate.

Instances

Instances details
Generic (PBftCanBeLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftCanBeLeader c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftCanBeLeader c) = D1 ('MetaData "PBftCanBeLeader" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftCanBeLeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftCanBeLeaderCoreNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreNodeId) :*: (S1 ('MetaSel ('Just "pbftCanBeLeaderSignKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyDSIGN (PBftDSIGN c))) :*: S1 ('MetaSel ('Just "pbftCanBeLeaderDlgCert") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftDelegationCert c)))))
PBftCrypto c ⇒ NoThunks (PBftCanBeLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftCanBeLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftCanBeLeader c) = D1 ('MetaData "PBftCanBeLeader" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftCanBeLeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftCanBeLeaderCoreNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreNodeId) :*: (S1 ('MetaSel ('Just "pbftCanBeLeaderSignKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyDSIGN (PBftDSIGN c))) :*: S1 ('MetaSel ('Just "pbftCanBeLeaderDlgCert") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftDelegationCert c)))))

data PBftFields c toSign Source #

Constructors

PBftFields 

Fields

Instances

Instances details
Generic (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftFields c toSign) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftFields c toSign) = D1 ('MetaData "PBftFields" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftIssuer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN (PBftDSIGN c))) :*: (S1 ('MetaSel ('Just "pbftGenKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN (PBftDSIGN c))) :*: S1 ('MetaSel ('Just "pbftSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SignedDSIGN (PBftDSIGN c) toSign)))))

Methods

fromPBftFields c toSign → Rep (PBftFields c toSign) x #

toRep (PBftFields c toSign) x → PBftFields c toSign #

PBftCrypto c ⇒ Show (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

showsPrecIntPBftFields c toSign → ShowS #

showPBftFields c toSign → String #

showList ∷ [PBftFields c toSign] → ShowS #

PBftCrypto c ⇒ Eq (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

(==)PBftFields c toSign → PBftFields c toSign → Bool #

(/=)PBftFields c toSign → PBftFields c toSign → Bool #

(PBftCrypto c, Typeable toSign) ⇒ NoThunks (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunksContextPBftFields c toSign → IO (Maybe ThunkInfo) Source #

wNoThunksContextPBftFields c toSign → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (PBftFields c toSign) → String Source #

PBftCrypto c ⇒ Condense (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

condensePBftFields c toSign → String Source #

type Rep (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftFields c toSign) = D1 ('MetaData "PBftFields" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftIssuer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN (PBftDSIGN c))) :*: (S1 ('MetaSel ('Just "pbftGenKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN (PBftDSIGN c))) :*: S1 ('MetaSel ('Just "pbftSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SignedDSIGN (PBftDSIGN c) toSign)))))

data PBftIsLeader c Source #

Information required to produce a block.

Instances

Instances details
Generic (PBftIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftIsLeader c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftIsLeader c) = D1 ('MetaData "PBftIsLeader" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftIsLeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftIsLeaderSignKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyDSIGN (PBftDSIGN c))) :*: S1 ('MetaSel ('Just "pbftIsLeaderDlgCert") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftDelegationCert c))))

Methods

fromPBftIsLeader c → Rep (PBftIsLeader c) x #

toRep (PBftIsLeader c) x → PBftIsLeader c #

PBftCrypto c ⇒ NoThunks (PBftIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftIsLeader c) = D1 ('MetaData "PBftIsLeader" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftIsLeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftIsLeaderSignKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyDSIGN (PBftDSIGN c))) :*: S1 ('MetaSel ('Just "pbftIsLeaderDlgCert") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftDelegationCert c))))

newtype PBftLedgerView c Source #

Constructors

PBftLedgerView 

Fields

Instances

Instances details
Generic (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftLedgerView c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftLedgerView c) = D1 ('MetaData "PBftLedgerView" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftLedgerView" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftDelegates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bimap (PBftVerKeyHash c) (PBftVerKeyHash c)))))

Methods

fromPBftLedgerView c → Rep (PBftLedgerView c) x #

toRep (PBftLedgerView c) x → PBftLedgerView c #

Show (PBftVerKeyHash c) ⇒ Show (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Eq (PBftVerKeyHash c) ⇒ Eq (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

(Serialise (PBftVerKeyHash c), Ord (PBftVerKeyHash c)) ⇒ Serialise (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftLedgerView c) = D1 ('MetaData "PBftLedgerView" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftLedgerView" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftDelegates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bimap (PBftVerKeyHash c) (PBftVerKeyHash c)))))

data PBftParams Source #

Protocol parameters

Constructors

PBftParams 

Fields

Instances

Instances details
Generic PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftParams 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftParams = D1 ('MetaData "PBftParams" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftParams" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam) :*: (S1 ('MetaSel ('Just "pbftNumNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes) :*: S1 ('MetaSel ('Just "pbftSignatureThreshold") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PBftSignatureThreshold))))
Show PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

NoThunks PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftParams = D1 ('MetaData "PBftParams" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftParams" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam) :*: (S1 ('MetaSel ('Just "pbftNumNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes) :*: S1 ('MetaSel ('Just "pbftSignatureThreshold") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PBftSignatureThreshold))))

data PBftSelectView Source #

Part of the header required for chain selection

EBBs share a block number with regular blocks, and so for chain selection we need to know if a block is an EBB or not (because a chain ending on an EBB with a particular block number is longer than a chain on a regular block with that same block number).

Instances

Instances details
Generic PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftSelectView 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftSelectView = D1 ('MetaData "PBftSelectView" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftSelectView" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftSelectViewBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "pbftSelectViewIsEBB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IsEBB)))
Show PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Eq PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Ord PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

NoThunks PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

ChainOrder PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftSelectView = D1 ('MetaData "PBftSelectView" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftSelectView" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftSelectViewBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "pbftSelectViewIsEBB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IsEBB)))
type ChainOrderConfig PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype PBftSignatureThreshold Source #

Signature threshold. This represents the proportion of blocks in a pbftSignatureWindow-sized window which may be signed by any single key.

Instances

Instances details
Generic PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftSignatureThreshold 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftSignatureThreshold = D1 ('MetaData "PBftSignatureThreshold" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftSignatureThreshold" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPBftSignatureThreshold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))
Show PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Eq PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

NoThunks PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep PBftSignatureThreshold = D1 ('MetaData "PBftSignatureThreshold" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftSignatureThreshold" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPBftSignatureThreshold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

pbftWindowExceedsThresholdPBftCrypto c ⇒ PBftWindowParams → PBftState c → PBftVerKeyHash c → Either Word64 () Source #

Does the number of blocks signed by this key exceed the threshold?

Returns Just the number of blocks signed if exceeded.

pbftWindowSizeSecurityParamWindowSize Source #

Window size used by PBFT

We set the window size to be equal to k.

Forging

forgePBftFields Source #

Arguments

∷ (PBftCrypto c, Signable (PBftDSIGN c) toSign) 
⇒ (VerKeyDSIGN (PBftDSIGN c) → ContextDSIGN (PBftDSIGN c))

Construct DSIGN context given pbftGenKey

IsLeader (PBft c) 
→ toSign 
PBftFields c toSign 

Classes

class (Typeable c, DSIGNAlgorithm (PBftDSIGN c), Condense (SigDSIGN (PBftDSIGN c)), Show (PBftVerKeyHash c), Ord (PBftVerKeyHash c), Eq (PBftVerKeyHash c), Show (PBftVerKeyHash c), NoThunks (PBftVerKeyHash c), NoThunks (PBftDelegationCert c), Serialise (PBftVerKeyHash c)) ⇒ PBftCrypto c where Source #

Crypto primitives required by BFT

Cardano stores a map of stakeholder IDs rather than the verification key directly. We make this family injective for convenience - whilst it's _possible_ that there could be non-injective instances, the chances of there being more than the two instances here are basically non-existent.

Associated Types

type PBftDSIGN c Source #

type PBftDelegationCert c = (d ∷ Type) | d → c Source #

type PBftVerKeyHash c = (d ∷ Type) | d → c Source #

data PBftMockCrypto Source #

newtype PBftMockVerKeyHash Source #

We don't hash and just use the underlying Word64.

Instances

Instances details
Generic PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Associated Types

type Rep PBftMockVerKeyHash 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

type Rep PBftMockVerKeyHash = D1 ('MetaData "PBftMockVerKeyHash" "Ouroboros.Consensus.Protocol.PBFT.Crypto" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftMockVerKeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPBftMockVerKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN MockDSIGN))))
Show PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Eq PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Ord PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

NoThunks PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Serialise PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

type Rep PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

type Rep PBftMockVerKeyHash = D1 ('MetaData "PBftMockVerKeyHash" "Ouroboros.Consensus.Protocol.PBFT.Crypto" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftMockVerKeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPBftMockVerKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN MockDSIGN))))

data PBftValidateView c Source #

Part of the header that we validate

Constructors

Signable (PBftDSIGN c) signed ⇒ PBftValidateRegular (PBftFields c signed) signed (ContextDSIGN (PBftDSIGN c))

Regular block

Regular blocks are signed, and so we need to validate them. We also need to know the slot number of the block

PBftValidateBoundary

Boundary block (EBB)

EBBs are not signed and they do not affect the consensus state.

pbftValidateBoundary ∷ hdr → PBftValidateView c Source #

Convenience constructor for PBftValidateView for boundary blocks

pbftValidateRegular ∷ (SignedHeader hdr, Signable (PBftDSIGN c) (Signed hdr)) ⇒ ContextDSIGN (PBftDSIGN c) → (hdr → PBftFields c (Signed hdr)) → hdr → PBftValidateView c Source #

Convenience constructor for PBftValidateView for regular blocks

CannotForge

data PBftCannotForge c Source #

Expresses that, whilst we believe ourselves to be a leader for this slot, we are nonetheless unable to forge a block.

Constructors

PBftCannotForgeInvalidDelegation !(PBftVerKeyHash c)

We cannot forge a block because we are not the current delegate of the genesis key we have a delegation certificate from.

PBftCannotForgeThresholdExceeded !Word64

We cannot lead because delegates of the genesis key we have a delegation from have already forged the maximum number of blocks in this signing window.

Instances

Instances details
Generic (PBftCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftCannotForge c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftCannotForge c) = D1 ('MetaData "PBftCannotForge" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftCannotForgeInvalidDelegation" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftVerKeyHash c))) :+: C1 ('MetaCons "PBftCannotForgeThresholdExceeded" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)))
PBftCrypto c ⇒ Show (PBftCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftCannotForge c) = D1 ('MetaData "PBftCannotForge" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "PBftCannotForgeInvalidDelegation" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftVerKeyHash c))) :+: C1 ('MetaCons "PBftCannotForgeThresholdExceeded" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)))

Type instances

data family ConsensusConfig p Source #

Static configuration required to run the consensus protocol

Every method in the ConsensusProtocol class takes the consensus configuration as a parameter, so having this as a data family rather than a type family resolves most ambiguity.

Defined out of the class so that protocols can define this type without having to define the entire protocol at the same time (or indeed in the same module).

Instances

Instances details
Generic (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (ConsensusConfig (HardForkProtocol xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type Rep (ConsensusConfig (HardForkProtocol xs)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HardForkConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkConsensusConfigK") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam) :*: (S1 ('MetaSel ('Just "hardForkConsensusConfigShape") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Shape xs)) :*: S1 ('MetaSel ('Just "hardForkConsensusConfigPerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PerEraConsensusConfig xs)))))
Generic (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

Associated Types

type Rep (ConsensusConfig (Bft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

type Rep (ConsensusConfig (Bft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.BFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "BftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "bftParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BftParams) :*: (S1 ('MetaSel ('Just "bftSignKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyDSIGN (BftDSIGN c))) :*: S1 ('MetaSel ('Just "bftVerKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map NodeId (VerKeyDSIGN (BftDSIGN c)))))))

Methods

fromConsensusConfig (Bft c) → Rep (ConsensusConfig (Bft c)) x #

toRep (ConsensusConfig (Bft c)) x → ConsensusConfig (Bft c) #

Generic (ConsensusConfig (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

Associated Types

type Rep (ConsensusConfig (ModChainSel p s)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

type Rep (ConsensusConfig (ModChainSel p s)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.ModChainSel" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "McsConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "mcsConfigP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConsensusConfig p))))
Generic (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (PBft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
CanHardFork xs ⇒ NoThunks (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

BftCrypto c ⇒ NoThunks (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

ConsensusProtocol p ⇒ NoThunks (ConsensusConfig (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

NoThunks (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type Rep (ConsensusConfig (HardForkProtocol xs)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "HardForkConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkConsensusConfigK") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam) :*: (S1 ('MetaSel ('Just "hardForkConsensusConfigShape") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Shape xs)) :*: S1 ('MetaSel ('Just "hardForkConsensusConfigPerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PerEraConsensusConfig xs)))))
type Rep (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

type Rep (ConsensusConfig (Bft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.BFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "BftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "bftParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BftParams) :*: (S1 ('MetaSel ('Just "bftSignKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyDSIGN (BftDSIGN c))) :*: S1 ('MetaSel ('Just "bftVerKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map NodeId (VerKeyDSIGN (BftDSIGN c)))))))
type Rep (ConsensusConfig (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

type Rep (ConsensusConfig (ModChainSel p s)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.ModChainSel" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "McsConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "mcsConfigP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConsensusConfig p))))
type Rep (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (PBft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
data ConsensusConfig (HardForkProtocol xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data ConsensusConfig (Bft c) Source #

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

newtype ConsensusConfig (PBft c) Source #

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype ConsensusConfig (ModChainSel p s) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

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

Exported for tracing errors

data PBftValidationErr c Source #

NOTE: this type is stored in the state, so it must be in normal form to avoid space leaks.

Instances

Instances details
Generic (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftValidationErr c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftValidationErr c) = D1 ('MetaData "PBftValidationErr" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) ((C1 ('MetaCons "PBftInvalidSignature" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "PBftNotGenesisDelegate" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftVerKeyHash c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftLedgerView c)))) :+: (C1 ('MetaCons "PBftExceededSignThreshold" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftVerKeyHash c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :+: C1 ('MetaCons "PBftInvalidSlot" 'PrefixI 'False) (U1TypeType)))
PBftCrypto c ⇒ Show (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ Eq (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

PBftCrypto c ⇒ NoThunks (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (PBftValidationErr c) = D1 ('MetaData "PBftValidationErr" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.26.0.0-inplace" 'False) ((C1 ('MetaCons "PBftInvalidSignature" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "PBftNotGenesisDelegate" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftVerKeyHash c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftLedgerView c)))) :+: (C1 ('MetaCons "PBftExceededSignThreshold" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PBftVerKeyHash c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :+: C1 ('MetaCons "PBftInvalidSlot" 'PrefixI 'False) (U1TypeType)))