ouroboros-consensus-protocol-0.3.1.0: Cardano consensus protocols
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Protocol.Praos

Synopsis

Documentation

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 (TPraos c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

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

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

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

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

PraosCrypto c ⇒ NoThunks (ConsensusConfig (TPraos c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Methods

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

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

showTypeOfProxy (ConsensusConfig (TPraos c)) → String #

PraosCrypto c ⇒ NoThunks (ConsensusConfig (Praos c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

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

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

showTypeOfProxy (ConsensusConfig (Praos c)) → String #

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

Defined in Ouroboros.Consensus.Protocol.TPraos

type Rep (ConsensusConfig (TPraos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.TPraos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "TPraosConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "tpraosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TPraosParams) :*: S1 ('MetaSel ('Just "tpraosEpochInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochInfo (Except PastHorizonException)))))
type Rep (ConsensusConfig (Praos c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (ConsensusConfig (Praos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "PraosConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosParams) :*: S1 ('MetaSel ('Just "praosEpochInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochInfo (Except PastHorizonException)))))
data ConsensusConfig (TPraos c) Source #

Static configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

data ConsensusConfig (Praos c) Source #

Static configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data Praos c Source #

Instances

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

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

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

PraosCrypto c ⇒ ConsensusProtocol (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

PraosCrypto c ⇒ NoThunks (ConsensusConfig (Praos c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

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

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

showTypeOfProxy (ConsensusConfig (Praos c)) → String #

PraosCrypto c ⇒ PraosProtocolSupportsNode (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

getPraosNonces ∷ proxy (Praos c) → ChainDepState (Praos c) → PraosNonces Source #

getOpCertCounters ∷ proxy (Praos c) → ChainDepState (Praos c) → Map (KeyHash 'BlockIssuer (PraosProtocolSupportsNodeCrypto (Praos c))) Word64 Source #

(HASH c1 ~ HASH c2, ADDRHASH c1 ~ ADDRHASH c2, VerKeyDSIGN c1 ~ VerKeyDSIGN c2, VerKeyVRF c1 ~ VerKeyVRF c2) ⇒ TranslateProto (TPraos c1) (Praos c2) Source #

We can translate between TPraos and Praos, provided:

  • They share the same HASH algorithm
  • They share the same ADDRHASH algorithm
  • They share the same DSIGN verification keys
  • They share the same VRF verification keys
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Translate

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

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (ConsensusConfig (Praos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "PraosConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosParams) :*: S1 ('MetaSel ('Just "praosEpochInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochInfo (Except PastHorizonException)))))
data ConsensusConfig (Praos c) Source #

Static configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type ValidateView (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type ValidationErr (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type LedgerView (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type SelectView (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type CanBeLeader (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type IsLeader (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type ChainDepState (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type PraosProtocolSupportsNodeCrypto (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data PraosCannotForge c Source #

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

Constructors

PraosCannotForgeKeyNotUsableYet

The KES key in our operational certificate can't be used because the current (wall clock) period is before the start period of the key. current KES period.

Note: the opposite case, i.e., the wall clock period being after the end period of the key, is caught when trying to update the key in updateForgeState.

Fields

  • !KESPeriod

    Current KES period according to the wallclock slot, i.e., the KES period in which we want to use the key.

  • !KESPeriod

    Start KES period of the KES key.

Instances

Instances details
PraosCrypto c ⇒ Show (PraosCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Generic (PraosCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosCannotForge c) ∷ TypeType Source #

type Rep (PraosCannotForge c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (PraosCannotForge c) = D1 ('MetaData "PraosCannotForge" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "PraosCannotForgeKeyNotUsableYet" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KESPeriod) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KESPeriod)))

class (Crypto c, Signable (DSIGN c) (OCertSignable c), Signable (DSIGN c) (Hash c EraIndependentTxBody), Signable (KES c) (HeaderBody c), Signable (VRF c) InputVRF) ⇒ PraosCrypto c Source #

Instances

Instances details
PraosCrypto StandardCrypto Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data PraosFields c toSign Source #

Constructors

PraosFields 

Fields

Instances

Instances details
(Show toSign, PraosCrypto c) ⇒ Show (PraosFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

showsPrecIntPraosFields c toSign → ShowS Source #

showPraosFields c toSign → String Source #

showList ∷ [PraosFields c toSign] → ShowS Source #

Generic (PraosFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosFields c toSign) ∷ TypeType Source #

Methods

fromPraosFields c toSign → Rep (PraosFields c toSign) x Source #

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

(NoThunks toSign, PraosCrypto c) ⇒ NoThunks (PraosFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

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

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

showTypeOfProxy (PraosFields c toSign) → String #

type Rep (PraosFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (PraosFields c toSign) = D1 ('MetaData "PraosFields" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "PraosFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SignedKES c toSign)) :*: S1 ('MetaSel ('Just "praosToSign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 toSign)))

newtype PraosIsLeader c Source #

Assembled proof that the issuer has the right to issue a block in the selected slot.

Constructors

PraosIsLeader 

Fields

Instances

Instances details
Generic (PraosIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosIsLeader c) ∷ TypeType Source #

PraosCrypto c ⇒ NoThunks (PraosIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

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

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

showTypeOfProxy (PraosIsLeader c) → String #

type Rep (PraosIsLeader c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (PraosIsLeader c) = D1 ('MetaData "PraosIsLeader" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'True) (C1 ('MetaCons "PraosIsLeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosIsLeaderVrfRes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CertifiedVRF c InputVRF))))

data PraosParams Source #

Praos parameters that are node independent

Constructors

PraosParams 

Fields

Instances

Instances details
Generic PraosParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep PraosParamsTypeType Source #

NoThunks PraosParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

noThunks ∷ Context → PraosParamsIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → PraosParamsIO (Maybe ThunkInfo) #

showTypeOfProxy PraosParamsString #

type Rep PraosParams Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep PraosParams = D1 ('MetaData "PraosParams" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "PraosParams" 'PrefixI 'True) (((S1 ('MetaSel ('Just "praosSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "praosLeaderF") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ActiveSlotCoeff)) :*: (S1 ('MetaSel ('Just "praosSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam) :*: S1 ('MetaSel ('Just "praosMaxKESEvo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "praosQuorum") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "praosMaxMajorPV") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MaxMajorProtVer)) :*: (S1 ('MetaSel ('Just "praosMaxLovelaceSupply") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "praosNetworkId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Network) :*: S1 ('MetaSel ('Just "praosSystemStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SystemStart))))))

data PraosState c Source #

Praos consensus state.

We track the last slot and the counters for operational certificates, as well as a series of nonces which get updated in different ways over the course of an epoch.

Constructors

PraosState 

Fields

Instances

Instances details
Eq (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

(==)PraosState c → PraosState c → Bool Source #

(/=)PraosState c → PraosState c → Bool Source #

Show (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Generic (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosState c) ∷ TypeType Source #

Methods

fromPraosState c → Rep (PraosState c) x Source #

toRep (PraosState c) x → PraosState c Source #

PraosCrypto c ⇒ Serialise (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

encodePraosState c → Encoding #

decode ∷ Decoder s (PraosState c) #

encodeList ∷ [PraosState c] → Encoding #

decodeList ∷ Decoder s [PraosState c] #

PraosCrypto c ⇒ NoThunks (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

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

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

showTypeOfProxy (PraosState c) → String #

PraosCrypto c ⇒ FromCBOR (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

fromCBOR ∷ Decoder s (PraosState c)

labelProxy (PraosState c) → Text

PraosCrypto c ⇒ ToCBOR (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

toCBORPraosState c → Encoding

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (PraosState c) → Size

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [PraosState c] → Size

type Rep (PraosState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (PraosState c) = D1 ('MetaData "PraosState" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "PraosState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "praosStateLastSlot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin SlotNo)) :*: (S1 ('MetaSel ('Just "praosStateOCertCounters") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'BlockIssuer c) Word64)) :*: S1 ('MetaSel ('Just "praosStateEvolvingNonce") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Nonce))) :*: ((S1 ('MetaSel ('Just "praosStateCandidateNonce") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Nonce) :*: S1 ('MetaSel ('Just "praosStateEpochNonce") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Nonce)) :*: (S1 ('MetaSel ('Just "praosStateLabNonce") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Nonce) :*: S1 ('MetaSel ('Just "praosStateLastEpochBlockNonce") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Nonce)))))
data Ticked (PraosState c) Source #

Ticked PraosState

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data PraosToSign c Source #

Fields arising from praos execution which must be included in the block signature.

Constructors

PraosToSign 

Fields

  • praosToSignIssuerVK ∷ VKey 'BlockIssuer c

    Verification key for the issuer of this block.

  • praosToSignVrfVK ∷ VerKeyVRF c
     
  • praosToSignVrfRes ∷ CertifiedVRF c InputVRF

    Verifiable random value. This is used both to prove the issuer is eligible to issue a block, and to contribute to the evolving nonce.

  • praosToSignOCert ∷ OCert c

    Lightweight delegation certificate mapping the cold (DSIGN) key to the online KES key.

Instances

Instances details
PraosCrypto c ⇒ Show (PraosToSign c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Generic (PraosToSign c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosToSign c) ∷ TypeType Source #

Methods

fromPraosToSign c → Rep (PraosToSign c) x Source #

toRep (PraosToSign c) x → PraosToSign c Source #

PraosCrypto c ⇒ NoThunks (PraosToSign c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

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

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

showTypeOfProxy (PraosToSign c) → String #

type Rep (PraosToSign c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (PraosToSign c) = D1 ('MetaData "PraosToSign" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (C1 ('MetaCons "PraosToSign" 'PrefixI 'True) ((S1 ('MetaSel ('Just "praosToSignIssuerVK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VKey 'BlockIssuer c)) :*: S1 ('MetaSel ('Just "praosToSignVrfVK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyVRF c))) :*: (S1 ('MetaSel ('Just "praosToSignVrfRes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CertifiedVRF c InputVRF)) :*: S1 ('MetaSel ('Just "praosToSignOCert") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OCert c)))))

data PraosValidationErr c Source #

Errors which we might encounter

Constructors

VRFKeyUnknown !(KeyHash StakePool c) 
VRFKeyWrongVRFKey !(KeyHash StakePool c) !(Hash c (VerKeyVRF c)) !(Hash c (VerKeyVRF c)) 
VRFKeyBadProof !SlotNo !Nonce !(CertifiedVRF (VRF c) InputVRF) 
VRFLeaderValueTooBig Natural Rational ActiveSlotCoeff 
KESBeforeStartOCERT !KESPeriod !KESPeriod 
KESAfterEndOCERT !KESPeriod !KESPeriod !Word64 
CounterTooSmallOCERT !Word64 !Word64 
CounterOverIncrementedOCERT !Word64 !Word64

The KES counter has been incremented by more than 1

InvalidSignatureOCERT !Word64 !KESPeriod !String 
InvalidKesSignatureOCERT !Word !Word !Word !String 
NoCounterForKeyHashOCERT !(KeyHash 'BlockIssuer c) 

Instances

Instances details
PraosCrypto c ⇒ Eq (PraosValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

PraosCrypto c ⇒ Show (PraosValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Generic (PraosValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (PraosValidationErr c) ∷ TypeType Source #

PraosCrypto c ⇒ NoThunks (PraosValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

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

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

showTypeOfProxy (PraosValidationErr c) → String #

type Rep (PraosValidationErr c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (PraosValidationErr c) = D1 ('MetaData "PraosValidationErr" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'False) (((C1 ('MetaCons "VRFKeyUnknown" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))) :+: C1 ('MetaCons "VRFKeyWrongVRFKey" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash c (VerKeyVRF c))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash c (VerKeyVRF c)))))) :+: (C1 ('MetaCons "VRFKeyBadProof" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Nonce) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CertifiedVRF (VRF c) InputVRF)))) :+: (C1 ('MetaCons "VRFLeaderValueTooBig" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ActiveSlotCoeff))) :+: C1 ('MetaCons "KESBeforeStartOCERT" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KESPeriod) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KESPeriod))))) :+: ((C1 ('MetaCons "KESAfterEndOCERT" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KESPeriod) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KESPeriod) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :+: (C1 ('MetaCons "CounterTooSmallOCERT" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :+: C1 ('MetaCons "CounterOverIncrementedOCERT" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)))) :+: (C1 ('MetaCons "InvalidSignatureOCERT" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 KESPeriod) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))) :+: (C1 ('MetaCons "InvalidKesSignatureOCERT" 'PrefixI 'False) ((S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))) :+: C1 ('MetaCons "NoCounterForKeyHashOCERT" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'BlockIssuer c)))))))

data family Ticked st 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 ()) 
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)) 
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 #

Show (Ticked (f a)) ⇒ Show ((Ticked :.: f) a) 
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) 
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 () 
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype Ticked (LedgerView c) Source #

Ledger view at a particular slot

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

newtype Ticked (LedgerView c) Source #

Ledger view at a particular slot

Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

newtype Ticked (LedgerView c) = TickedPraosLedgerView {}
data Ticked (TPraosState c) Source #

Ticked TPraosState

Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

data Ticked (PraosState c) Source #

Ticked PraosState

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type HeaderHash (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

newtype Ticked (K a x) 
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype Ticked (K a x) = TickedK {}

forgePraosFields ∷ (PraosCrypto c, KESignable c toSign, Monad m) ⇒ HotKey c m → CanBeLeader (Praos c) → IsLeader (Praos c) → (PraosToSign c → toSign) → m (PraosFields c toSign) Source #