ouroboros-consensus-0.3.1.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)) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → ConsensusConfig (PBft c) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (PBft c) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (PBft c)) → String #

PBftCrypto c ⇒ ConsensusProtocol (PBft c) Source # 
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.3.1.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
type ChainDepState (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type IsLeader (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type CanBeLeader (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 LedgerView (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type ValidationErr (PBft c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type ValidateView (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

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) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftCanBeLeader c → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftCanBeLeader c → IO (Maybe ThunkInfo) #

showTypeOfProxy (PBftCanBeLeader c) → String #

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.3.1.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
PBftCrypto c ⇒ Eq (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

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

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

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

showsPrecIntPBftFields c toSign → ShowS Source #

showPBftFields c toSign → String Source #

showList ∷ [PBftFields c toSign] → ShowS Source #

Generic (PBftFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftFields c toSign) ∷ TypeType Source #

Methods

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

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

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftFields c toSign → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftFields c toSign → IO (Maybe ThunkInfo) #

showTypeOfProxy (PBftFields c toSign) → String #

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.3.1.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.

Constructors

PBftIsLeader 

Fields

Instances

Instances details
Generic (PBftIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftIsLeader c) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftIsLeader c → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftIsLeader c → IO (Maybe ThunkInfo) #

showTypeOfProxy (PBftIsLeader c) → String #

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.3.1.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
Eq (PBftVerKeyHash c) ⇒ Eq (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Generic (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftLedgerView c) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

encodePBftLedgerView c → Encoding #

decode ∷ Decoder s (PBftLedgerView c) #

encodeList ∷ [PBftLedgerView c] → Encoding #

decodeList ∷ Decoder s [PBftLedgerView c] #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftLedgerView c → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftLedgerView c → IO (Maybe ThunkInfo) #

showTypeOfProxy (PBftLedgerView c) → String #

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.3.1.0-inplace" 'True) (C1 ('MetaCons "PBftLedgerView" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftDelegates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bimap (PBftVerKeyHash c) (PBftVerKeyHash c)))))
newtype Ticked (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data PBftParams Source #

Protocol parameters

Constructors

PBftParams 

Fields

Instances

Instances details
Show PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Generic PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftParamsTypeType Source #

NoThunks PBftParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftParamsIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftParamsIO (Maybe ThunkInfo) #

showTypeOfProxy PBftParamsString #

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.3.1.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
Eq PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Ord PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Show PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Generic PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftSelectViewTypeType Source #

NoThunks PBftSelectView Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftSelectViewIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftSelectViewIO (Maybe ThunkInfo) #

showTypeOfProxy PBftSelectViewString #

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.3.1.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)))

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
Eq PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Show PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Generic PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep PBftSignatureThresholdTypeType Source #

NoThunks PBftSignatureThreshold Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftSignatureThresholdIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftSignatureThresholdIO (Maybe ThunkInfo) #

showTypeOfProxy PBftSignatureThresholdString #

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.3.1.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

∷ ∀ c toSign. (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)) ⇒ 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 ∷ Type Source #

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

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

Methods

dlgCertGenVerKeyPBftDelegationCert c → VerKeyDSIGN (PBftDSIGN c) Source #

dlgCertDlgVerKeyPBftDelegationCert c → VerKeyDSIGN (PBftDSIGN c) Source #

hashVerKey ∷ VerKeyDSIGN (PBftDSIGN c) → PBftVerKeyHash c Source #

newtype PBftMockVerKeyHash Source #

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

Constructors

PBftMockVerKeyHash 

Fields

Instances

Instances details
Eq PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Ord PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Show PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Generic PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Associated Types

type Rep PBftMockVerKeyHashTypeType Source #

Serialise PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Methods

encodePBftMockVerKeyHash → Encoding #

decode ∷ Decoder s PBftMockVerKeyHash #

encodeList ∷ [PBftMockVerKeyHash] → Encoding #

decodeList ∷ Decoder s [PBftMockVerKeyHash] #

NoThunks PBftMockVerKeyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT.Crypto

Methods

noThunks ∷ Context → PBftMockVerKeyHashIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftMockVerKeyHashIO (Maybe ThunkInfo) #

showTypeOfProxy PBftMockVerKeyHashString #

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.3.1.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

∀ signed.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
PBftCrypto c ⇒ Show (PBftCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Generic (PBftCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftCannotForge c) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftCannotForge c → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftCannotForge c → IO (Maybe ThunkInfo) #

showTypeOfProxy (PBftCannotForge c) → String #

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.3.1.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 ∷ Type 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 (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

Associated Types

type Rep (ConsensusConfig (ModChainSel p s)) ∷ TypeType Source #

Generic (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

Associated Types

type Rep (ConsensusConfig (Bft c)) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (ConsensusConfig (HardForkProtocol xs)) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (ConsensusConfig (PBft c)) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.ModChainSel

Methods

noThunks ∷ Context → ConsensusConfig (ModChainSel p s) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (ModChainSel p s) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (ModChainSel p s)) → String #

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

Defined in Ouroboros.Consensus.Protocol.BFT

Methods

noThunks ∷ Context → ConsensusConfig (Bft c) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (Bft c) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (Bft c)) → String #

CanHardFork xs ⇒ NoThunks (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → ConsensusConfig (HardForkProtocol xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (HardForkProtocol xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (HardForkProtocol xs)) → String #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → ConsensusConfig (PBft c) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (PBft c) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (PBft c)) → String #

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.3.1.0-inplace" 'True) (C1 ('MetaCons "McsConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "mcsConfigP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConsensusConfig p))))
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.3.1.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 (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.3.1.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 (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.3.1.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
data ConsensusConfig (Bft c) Source #

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

data ConsensusConfig (Bft c) = BftConfig {}
data ConsensusConfig (HardForkProtocol xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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 ∷ Type Source #

" Ticked " piece of state (LedgerState, LedgerView, ChainIndepState)

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 (or forecast).

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 Source #

showTicked () → String Source #

showList ∷ [Ticked ()] → ShowS Source #

Show (Ticked a) ⇒ Show (Ticked (K a x)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked (K a x) → ShowS Source #

showTicked (K a x) → String Source #

showList ∷ [Ticked (K a x)] → ShowS Source #

(SListI xs, Show (Ticked a)) ⇒ Show (Ticked (HardForkLedgerView_ (K a ∷ TypeType) xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

Generic (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (Ticked (LedgerState (HardForkBlock xs))) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → Ticked (LedgerState (DualBlock m a)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (DualBlock m a)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (DualBlock m a))) → String #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (HardForkBlock xs))) → String #

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Extended

Isomorphic (Ticked :.: LedgerState) Source # 
Instance details

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

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

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → (Ticked :.: f) a → ShowS Source #

show ∷ (Ticked :.: f) a → String Source #

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

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

Defined in Ouroboros.Consensus.Ticked

Methods

noThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

showTypeOfProxy ((Ticked :.: f) a) → String #

data Ticked () Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

type Rep (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type HeaderHash (Ticked l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data Ticked (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

newtype Ticked (WrapLedgerView blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype Ticked (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (PBftState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data Ticked (HardForkLedgerView_ f xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

newtype Ticked (K a x) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype Ticked (K a x) = TickedK {}

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
PBftCrypto c ⇒ Eq (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Generic (PBftValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (PBftValidationErr c) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → PBftValidationErr c → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PBftValidationErr c → IO (Maybe ThunkInfo) #

showTypeOfProxy (PBftValidationErr c) → String #

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.3.1.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)))