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

Ouroboros.Consensus.HardFork.Combinator.Ledger

Synopsis

Documentation

data HardForkEnvelopeErr xs Source #

Constructors

HardForkEnvelopeErrFromEra (OneEraEnvelopeErr xs)

Validation error from one of the eras

HardForkEnvelopeErrWrongEra (MismatchEraInfo xs)

We tried to apply a block from the wrong era

Instances

Instances details
Generic (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkEnvelopeErr xs) ∷ TypeType #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkEnvelopeErr xs) = D1 ('MetaData "HardForkEnvelopeErr" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "HardForkEnvelopeErrFromEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraEnvelopeErr xs))) :+: C1 ('MetaCons "HardForkEnvelopeErrWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MismatchEraInfo xs))))

data HardForkLedgerError xs Source #

Constructors

HardForkLedgerErrorFromEra (OneEraLedgerError xs)

Validation error from one of the eras

HardForkLedgerErrorWrongEra (MismatchEraInfo xs)

We tried to apply a block from the wrong era

Instances

Instances details
Generic (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkLedgerError xs) ∷ TypeType #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkLedgerError xs) = D1 ('MetaData "HardForkLedgerError" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "HardForkLedgerErrorFromEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraLedgerError xs))) :+: C1 ('MetaCons "HardForkLedgerErrorWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MismatchEraInfo xs))))

data HardForkLedgerUpdate xs Source #

Constructors

HardForkUpdateInEra (OneEraLedgerUpdate xs) 
HardForkUpdateTransitionConfirmed (EraIndex xs) (EraIndex xs) EpochNo

Hard fork transition got confirmed

HardForkUpdateTransitionDone (EraIndex xs) (EraIndex xs) EpochNo

Hard fork transition happened

We record the EpochNo at the start of the era after the transition

HardForkUpdateTransitionRolledBack (EraIndex xs) (EraIndex xs)

The hard fork transition rolled back

data HardForkLedgerWarning xs Source #

Constructors

HardForkWarningInEra (OneEraLedgerWarning xs)

Warning from the underlying era

HardForkWarningTransitionMismatch (EraIndex xs) EraParams EpochNo

The transition to the next era does not match the EraParams

The EraParams can specify a lower bound on when the transition to the next era will happen. If the actual transition, when confirmed, is before this lower bound, the node is misconfigured and will likely not work correctly. This should be taken care of as soon as possible (before the transition happens).

HardForkWarningTransitionInFinalEra (EraIndex xs) EpochNo

Transition in the final era

The final era should never confirm any transitions. For clarity, we also record the index of that final era.

HardForkWarningTransitionUnconfirmed (EraIndex xs)

An already-confirmed transition got un-confirmed

HardForkWarningTransitionReconfirmed (EraIndex xs) (EraIndex xs) EpochNo EpochNo

An already-confirmed transition got changed

We record the indices of the era we are transitioning from and to, as well as the old and new EpochNo of that transition, in that order.

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

Low-level API (exported for the benefit of testing)

data AnnForecast state view blk Source #

Forecast annotated with details about the ledger it was derived from

Constructors

AnnForecast 

mkHardForkForecast ∷ ∀ state view xs. SListI xs ⇒ InPairs (CrossEraForecaster state view) xs → HardForkState (AnnForecast state view) xs → Forecast (HardForkLedgerView_ view xs) Source #

Change a telescope of a forecast into a forecast of a telescope

Orphan instances

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

Associated Types

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

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

All SingleEraBlock xs ⇒ HasHardForkHistory (HardForkBlock xs) Source # 
Instance details

Associated Types

type HardForkIndices (HardForkBlock xs) ∷ [Type] Source #

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

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

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

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

CanHardFork xs ⇒ IsLedger (LedgerState (HardForkBlock xs)) Source # 
Instance details

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

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

CanHardFork xs ⇒ ApplyBlock (LedgerState (HardForkBlock xs)) (HardForkBlock xs) Source # 
Instance details