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

Ouroboros.Consensus.Mock.Protocol.Praos

Description

Proof of concept implementation of Praos

Synopsis

Documentation

data HotKey c Source #

The key used for the given period or a stub Poisoned value.

A key will be poisoned if it failed to evolve by updateKES, and will remain poisoned forever after that.

Constructors

HotKey 

Fields

HotKeyPoisoned 

Instances

Instances details
Generic (HotKey c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Associated Types

type Rep (HotKey c) ∷ TypeType #

Methods

fromHotKey c → Rep (HotKey c) x #

toRep (HotKey c) x → HotKey c #

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Methods

showsPrecIntHotKey c → ShowS #

showHotKey c → String #

showList ∷ [HotKey c] → ShowS #

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep (HotKey c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep (HotKey c) = D1 ('MetaData "HotKey" "Ouroboros.Consensus.Mock.Protocol.Praos" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "HotKey" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Period) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyKES (PraosKES c)))) :+: C1 ('MetaCons "HotKeyPoisoned" 'PrefixI 'False) (U1TypeType))

newtype HotKeyEvolutionError Source #

The HotKey could not be evolved to the given Period.

data Praos c Source #

An uninhabited type representing the Praos protocol.

Instances

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Associated Types

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

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep (ConsensusConfig (Praos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Mock.Protocol.Praos" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "PraosConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "praosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosParams) :*: (S1 ('MetaSel ('Just "praosInitialEta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Just "praosInitialStake") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeDist))) :*: (S1 ('MetaSel ('Just "praosEvolvingStake") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosEvolvingStake) :*: (S1 ('MetaSel ('Just "praosSignKeyVRF") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyVRF (PraosVRF c))) :*: S1 ('MetaSel ('Just "praosVerKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map CoreNodeId (VerKeyKES (PraosKES c), VerKeyVRF (PraosVRF c))))))))
type CanBeLeader (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type ChainDepState (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

data ConsensusConfig (Praos c) Source #

The configuration that will be provided to every node when running the MockPraos protocol.

Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type IsLeader (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type IsLeader (Praos c)
type LedgerView (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type LedgerView (Praos c) = ()
type SelectView (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type ValidateView (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type ValidationErr (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

newtype PraosChainDepState c Source #

The chain dependent state, in this case as it is a mock, we just will store a list of BlockInfos that allow us to look into the past.

Constructors

PraosChainDepState 

Fields

Instances

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

PraosCrypto c ⇒ Eq (PraosChainDepState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

PraosCrypto c' ⇒ DecodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

PraosCrypto c' ⇒ EncodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

data Ticked (PraosChainDepState c) Source #

Ticking the Praos chain dep state has no effect

For the real Praos implementation, ticking is crucial, as it determines the point where the "nonce under construction" is swapped out for the "active" nonce. However, for the mock implementation, we keep the full history, and choose the right nonce from that; this means that ticking has no effect.

We do however need access to the ticked stake distribution.

Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

newtype PraosEvolvingStake Source #

An association from epoch to stake distributions.

Should be used when checking if someone is the leader of a particular slot. This is sufficiently good for a mock protocol as far as consensus is concerned. It is not strictly necessary that the stake distribution is computed from previous epochs, as we just need to consider that:

1) an attacker cannot influence it. 2) all the nodes agree on the same value for each Slot.

Each pair stores the stake distribution established by the end of the epoch in the first item of the pair. See latestEvolvedStakeDistAsOfEpoch for the intended interface.

If no value is returned, that means we are checking the stake before any changes have happened so we should consult instead the praosInitialStake.

data PraosExtraFields c Source #

Fields that should be included in the signature

Constructors

PraosExtraFields 

data PraosFields crypto typeBeingSigned Source #

The fields that Praos required in the header

Constructors

PraosFields 

Fields

Instances

Instances details
Generic (PraosFields crypto typeBeingSigned) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Associated Types

type Rep (PraosFields crypto typeBeingSigned) ∷ TypeType #

Methods

fromPraosFields crypto typeBeingSigned → Rep (PraosFields crypto typeBeingSigned) x #

toRep (PraosFields crypto typeBeingSigned) x → PraosFields crypto typeBeingSigned #

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Methods

showsPrecIntPraosFields c toSign → ShowS #

showPraosFields c toSign → String #

showList ∷ [PraosFields c toSign] → ShowS #

PraosCrypto c ⇒ Eq (PraosFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Methods

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

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

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

PraosCrypto c ⇒ Condense (PraosFields c toSign) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Methods

condensePraosFields c toSign → String Source #

type Rep (PraosFields crypto typeBeingSigned) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep (PraosFields crypto typeBeingSigned) = D1 ('MetaData "PraosFields" "Ouroboros.Consensus.Mock.Protocol.Praos" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "PraosFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SignedKES (PraosKES crypto) typeBeingSigned)) :*: S1 ('MetaSel ('Just "praosExtraFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PraosExtraFields crypto))))

data PraosParams Source #

Praos parameters that are node independent

Constructors

PraosParams 

Fields

Instances

Instances details
Generic PraosParams Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Associated Types

type Rep PraosParamsTypeType #

NoThunks PraosParams Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep PraosParams Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep PraosParams = D1 ('MetaData "PraosParams" "Ouroboros.Consensus.Mock.Protocol.Praos" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "PraosParams" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosLeaderF") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "praosSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam) :*: S1 ('MetaSel ('Just "praosSlotsPerEpoch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))))

evolveKeyPraosCrypto c ⇒ SlotNoHotKey c → (HotKey c, UpdateInfo (HotKey c) HotKeyEvolutionError) Source #

To be used in conjunction with, e.g., modifyMVar.

NOTE: when the key's period is after the target period, we shouldn't use it, but we currently do. In real TPraos we check this in tpraosCheckCanForge.

forgePraosFields ∷ (PraosCrypto c, Signable (PraosKES c) toSign, HasCallStack) ⇒ PraosProof c → HotKey c → (PraosExtraFields c → toSign) → PraosFields c toSign Source #

Create a PraosFields using a proof, a key and the data to be signed.

It is done by signing whatever is extracted from the extra fields by mkToSign and storing the signature and the extra fields on a PraosFields.

Tags

data PraosValidateView c Source #

A validate view is an association from the (signed) value to the PraosFields that contains the signature that sign it.

In this mock implementation, this could have been simplified to use SignedSimplePraos but from the consensus point of view, it is not relevant which actual value is being signed, that's why we use the existential.

Constructors

∀ signed.Signable (PraosKES c) signed ⇒ PraosValidateView (PraosFields c signed) signed 

data PraosValidationError c Source #

An error that can arise during validation

praosValidateView ∷ (SignedHeader hdr, Signable (PraosKES c) (Signed hdr)) ⇒ (hdr → PraosFields c (Signed hdr)) → hdr → PraosValidateView c Source #

Convenience constructor for PraosValidateView

Type instances

data BlockInfo c Source #

Constructors

BlockInfo 

Fields

Instances

Instances details
Generic (BlockInfo c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Associated Types

type Rep (BlockInfo c) ∷ TypeType #

Methods

fromBlockInfo c → Rep (BlockInfo c) x #

toRep (BlockInfo c) x → BlockInfo c #

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Methods

showsPrecIntBlockInfo c → ShowS #

showBlockInfo c → String #

showList ∷ [BlockInfo c] → ShowS #

PraosCrypto c ⇒ Eq (BlockInfo c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Methods

(==)BlockInfo c → BlockInfo c → Bool #

(/=)BlockInfo c → BlockInfo c → Bool #

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep (BlockInfo c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep (BlockInfo c)

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 (Bft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

Associated Types

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

Methods

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

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

Generic (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

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

Generic (ConsensusConfig (WithLeaderSchedule p)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.LeaderSchedule

Associated Types

type Rep (ConsensusConfig (WithLeaderSchedule p)) ∷ TypeType #

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

Associated Types

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

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

Defined in Ouroboros.Consensus.Protocol.BFT

NoThunks (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

ConsensusProtocol p ⇒ NoThunks (ConsensusConfig (WithLeaderSchedule p)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.LeaderSchedule

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

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

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.18.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 (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.18.0.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
type Rep (ConsensusConfig (WithLeaderSchedule p)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.LeaderSchedule

type Rep (ConsensusConfig (WithLeaderSchedule p)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Mock.Protocol.LeaderSchedule" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "WLSConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "wlsConfigSchedule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LeaderSchedule) :*: (S1 ('MetaSel ('Just "wlsConfigP") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ConsensusConfig p)) :*: S1 ('MetaSel ('Just "wlsConfigNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CoreNodeId))))
type Rep (ConsensusConfig (Praos c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type Rep (ConsensusConfig (Praos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Mock.Protocol.Praos" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "PraosConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "praosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosParams) :*: (S1 ('MetaSel ('Just "praosInitialEta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Just "praosInitialStake") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeDist))) :*: (S1 ('MetaSel ('Just "praosEvolvingStake") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosEvolvingStake) :*: (S1 ('MetaSel ('Just "praosSignKeyVRF") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyVRF (PraosVRF c))) :*: S1 ('MetaSel ('Just "praosVerKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map CoreNodeId (VerKeyKES (PraosKES c), VerKeyVRF (PraosVRF c))))))))
data ConsensusConfig (Bft c)

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

newtype ConsensusConfig (PBft c)

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data ConsensusConfig (WithLeaderSchedule p) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.LeaderSchedule

data ConsensusConfig (Praos c) Source #

The configuration that will be provided to every node when running the MockPraos protocol.

Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

data family Ticked st 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
Generic (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Ticked (LedgerState (SimpleBlock c ext))) ∷ TypeType #

Methods

fromTicked (LedgerState (SimpleBlock c ext)) → Rep (Ticked (LedgerState (SimpleBlock c ext))) x #

toRep (Ticked (LedgerState (SimpleBlock c ext))) x → Ticked (LedgerState (SimpleBlock c ext)) #

(SimpleCrypto c, Typeable ext) ⇒ Show (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

(SimpleCrypto c, Typeable ext) ⇒ Eq (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

(/=)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

(SimpleCrypto c, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

GetTip (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Ledger.Extended

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

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Ticked

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) = HeaderHash l
type Rep (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Ticked (LedgerState (SimpleBlock c ext))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext)))))
data Ticked (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

newtype Ticked (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (PBftState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (PraosChainDepState c) Source #

Ticking the Praos chain dep state has no effect

For the real Praos implementation, ticking is crucial, as it determines the point where the "nonce under construction" is swapped out for the "active" nonce. However, for the mock implementation, we keep the full history, and choose the right nonce from that; this means that ticking has no effect.

We do however need access to the ticked stake distribution.

Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos