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

Ouroboros.Consensus.HardFork.Combinator.Protocol

Synopsis

Documentation

newtype HardForkSelectView xs Source #

Instances

Instances details
CanHardFork xs ⇒ Show (HardForkSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ Eq (HardForkSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ Ord (HardForkSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ NoThunks (HardForkSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ ChainOrder (HardForkSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

Associated Types

type ChainOrderConfig (HardForkSelectView xs) Source #

type ChainOrderConfig (HardForkSelectView xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

Re-exports to keep State an internal module

type HardForkCanBeLeader xs = SomeErasCanBeLeader xs Source #

We have one or more BlockForgings, and thus CanBeLeader proofs, for each era in which we can forge blocks.

type HardForkIsLeader xs = OneEraIsLeader xs Source #

We are a leader if we have a proof from one of the eras

data HardForkValidationErr xs Source #

Constructors

HardForkValidationErrFromEra (OneEraValidationErr xs)

Validation error from one of the eras

HardForkValidationErrWrongEra (MismatchEraInfo xs)

We tried to apply a block from the wrong era

Instances

Instances details
Generic (HardForkValidationErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

Associated Types

type Rep (HardForkValidationErr xs) ∷ TypeType #

CanHardFork xs ⇒ Show (HardForkValidationErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ Eq (HardForkValidationErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ NoThunks (HardForkValidationErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

type Rep (HardForkValidationErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

type Rep (HardForkValidationErr xs) = D1 ('MetaData "HardForkValidationErr" "Ouroboros.Consensus.HardFork.Combinator.Protocol" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "HardForkValidationErrFromEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidationErr xs))) :+: C1 ('MetaCons "HardForkValidationErrWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MismatchEraInfo xs))))

Re-exports to keep LedgerView an internal module

data HardForkLedgerView_ f xs Source #

Constructors

HardForkLedgerView 

Fields

Type family instances

data family Ticked st ∷ Type 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 (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

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

Show (Ticked ()) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

NoThunks (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

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

Defined in Ouroboros.Consensus.Ledger.Dual

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 #

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

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

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

Defined in Ouroboros.Consensus.Ticked

data Ticked () Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

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

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) = HeaderHash l
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.18.0.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))))
data Ticked (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (PBftState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Orphan instances

CanHardFork xs ⇒ BlockSupportsProtocol (HardForkBlock xs) Source # 
Instance details

CanHardFork xs ⇒ ConsensusProtocol (HardForkProtocol xs) Source # 
Instance details