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

Ouroboros.Consensus.HardFork.Combinator.State

Description

Intended for qualified import

import Ouroboros.Consensus.HardFork.Combinator.State (HardForkState(..))
import qualified Ouroboros.Consensus.HardFork.Combinator.State as State
Synopsis

Documentation

newtype HardForkState f xs Source #

Generic hard fork state

This is used both for the consensus state and the ledger state.

By using a telescope with f ~ LedgerState, we will keep track of Past information for eras before the current one:

TZ currentByronState
TZ pastByronState $ TZ currentShelleyState
TZ pastByronState $ TS pastShelleyState $ TZ currentAllegraState
...

These are some intuitions on how the Telescope operations behave for this type:

extend

Suppose we have a telescope containing the ledger state. The "how to extend" argument would take, say, the final Byron state to the initial Shelley state; and "where to extend from" argument would indicate when we want to extend: when the current slot number has gone past the end of the Byron era.

retract

Suppose we have a telescope containing the consensus state. When we rewind the consensus state, we might cross a hard fork transition point. So we first retract the telescope to the era containing the slot number that we want to rewind to, and only then call rewindChainDepState on that era. Of course, retraction may fail (we might not have past consensus state to rewind to anymore); this failure would require a choice for a particular monad m.

align

Suppose we have one telescope containing the already-ticked ledger state, and another telescope containing the consensus state. Since the ledger state has already been ticked, it might have been advanced to the next era. If this happens, we should then align the consensus state with the ledger state, moving it also to the next era, before we can do the consensus header validation check. Note that in this particular example, the ledger state will always be ahead of the consensus state, never behind; alignExtend can be used in this case.

Constructors

HardForkState 

Fields

Instances

Instances details
HAp HardForkState Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

hap ∷ ∀ (f ∷ k → Type) (g ∷ k → Type) (xs ∷ l). Prod HardForkState (f -.-> g) xs → HardForkState f xs → HardForkState g xs Source #

HCollapse HardForkState Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

hcollapse ∷ ∀ (xs ∷ l) a. SListIN HardForkState xs ⇒ HardForkState (K a) xs → CollapseTo HardForkState a Source #

HSequence HardForkState Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

hsequence' ∷ ∀ (xs ∷ l) f (g ∷ k → Type). (SListIN HardForkState xs, Applicative f) ⇒ HardForkState (f :.: g) xs → f (HardForkState g xs) Source #

hctraverse' ∷ ∀ c (xs ∷ l) g proxy f f'. (AllN HardForkState c xs, Applicative g) ⇒ proxy c → (∀ (a ∷ k). c a ⇒ f a → g (f' a)) → HardForkState f xs → g (HardForkState f' xs) Source #

htraverse' ∷ ∀ (xs ∷ l) g f f'. (SListIN HardForkState xs, Applicative g) ⇒ (∀ (a ∷ k). f a → g (f' a)) → HardForkState f xs → g (HardForkState f' xs) Source #

HTrans HardForkState HardForkState Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

htrans ∷ ∀ c (xs ∷ l1) (ys ∷ l2) proxy f g. AllZipN (Prod HardForkState) c xs ys ⇒ proxy c → (∀ (x ∷ k1) (y ∷ k2). c x y ⇒ f x → g y) → HardForkState f xs → HardForkState g ys Source #

hcoerce ∷ ∀ (f ∷ k1 → Type) (g ∷ k2 → Type) (xs ∷ l1) (ys ∷ l2). AllZipN (Prod HardForkState) (LiftedCoercible f g) xs ys ⇒ HardForkState f xs → HardForkState g ys Source #

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

(All SingleEraBlock xs, ∀ blk. SingleEraBlock blk ⇒ Show (f blk)) ⇒ Show (HardForkState f xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

showsPrecIntHardForkState f xs → ShowS #

showHardForkState f xs → String #

showList ∷ [HardForkState f xs] → ShowS #

(All SingleEraBlock xs, ∀ blk. SingleEraBlock blk ⇒ Eq (f blk)) ⇒ Eq (HardForkState f xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

(==)HardForkState f xs → HardForkState f xs → Bool #

(/=)HardForkState f xs → HardForkState f xs → Bool #

(All SingleEraBlock xs, ∀ blk. SingleEraBlock blk ⇒ NoThunks (f blk)) ⇒ NoThunks (HardForkState f xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type Prod HardForkState Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type Prod HardForkState = NP ∷ (TypeType) → [Type] → Type
type SListIN HardForkState Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type CollapseTo HardForkState a Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type AllN HardForkState (c ∷ TypeConstraint) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type AllN HardForkState (c ∷ TypeConstraint) = All c
type Same HardForkState Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

data Ticked (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Current f blk Source #

Information about the current era

Constructors

Current 

Fields

Instances

Instances details
Generic (Current f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Associated Types

type Rep (Current f blk) ∷ TypeType #

Methods

fromCurrent f blk → Rep (Current f blk) x #

toRep (Current f blk) x → Current f blk #

Show (f blk) ⇒ Show (Current f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

showsPrecIntCurrent f blk → ShowS #

showCurrent f blk → String #

showList ∷ [Current f blk] → ShowS #

Eq (f blk) ⇒ Eq (Current f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

(==)Current f blk → Current f blk → Bool #

(/=)Current f blk → Current f blk → Bool #

NoThunks (f blk) ⇒ NoThunks (Current f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Serialise (f blk) ⇒ Serialise (Current f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

encodeCurrent f blk → Encoding Source #

decodeDecoder s (Current f blk) Source #

encodeList ∷ [Current f blk] → Encoding Source #

decodeListDecoder s [Current f blk] Source #

type Rep (Current f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

type Rep (Current f blk) = D1 ('MetaData "Current" "Ouroboros.Consensus.HardFork.Combinator.State.Types" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "Current" 'PrefixI 'True) (S1 ('MetaSel ('Just "currentStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bound) :*: S1 ('MetaSel ('Just "currentState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f blk))))

data Past Source #

Information about a past era

Constructors

Past 

Fields

Instances

Instances details
Generic Past Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Associated Types

type Rep PastTypeType #

Methods

fromPastRep Past x #

toRep Past x → Past #

Show Past Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Methods

showsPrecIntPastShowS #

showPastString #

showList ∷ [Past] → ShowS #

Eq Past Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Methods

(==)PastPastBool #

(/=)PastPastBool #

NoThunks Past Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Serialise Past Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type Rep Past Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

type Rep Past = D1 ('MetaData "Past" "Ouroboros.Consensus.HardFork.Combinator.State.Types" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "Past" 'PrefixI 'True) (S1 ('MetaSel ('Just "pastStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bound) :*: S1 ('MetaSel ('Just "pastEnd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bound)))

data Situated h f xs where Source #

A h situated in time

Constructors

SituatedCurrentCurrent f x → h x → Situated h f (x ': xs) 
SituatedNextCurrent f x → h y → Situated h f (x ': (y ': xs)) 
SituatedFutureCurrent f x → NS h xs → Situated h f (x ': (y ': xs)) 
SituatedPastK Past x → h x → Situated h f (x ': xs) 
SituatedShiftSituated h f xs → Situated h f (x ': xs) 

newtype Translate f x y Source #

Translate f x to f y across an era transition

Typically f will be LedgerState or WrapChainDepState.

Constructors

Translate 

Fields

newtype CrossEraForecaster state view x y Source #

Forecast a view y from a state x across an era transition.

In addition to the Bound of the transition, this is also told the SlotNo we're constructing a forecast for. This enables the translation function to take into account any scheduled changes that the final ledger view in the preceding era might have.

Constructors

CrossEraForecaster 

Fields

data TransitionInfo Source #

Knowledge in a particular era of the transition to the next era

Constructors

TransitionUnknown !(WithOrigin SlotNo)

No transition is yet known for this era We instead record the ledger tip (which must be in this era)

NOTE: If we are forecasting, this will be set to the slot number of the (past) ledger state in which the forecast was created. This means that when we construct an EpochInfo using a HardForkLedgerView, the range of that EpochInfo will extend a safe zone from that past ledger state.

TransitionKnown !EpochNo

Transition to the next era is known to happen at this EpochNo

TransitionImpossible

The transition is impossible

This can be due to one of two reasons:

  • We are in the final era
  • This era has not actually begun yet (we are forecasting). In this case, we cannot look past the safe zone of this era and hence, by definition, the transition to the next era cannot happen.

Instances

Instances details
Generic TransitionInfo Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

Associated Types

type Rep TransitionInfoTypeType #

Show TransitionInfo Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

NoThunks TransitionInfo Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

type Rep TransitionInfo Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types

type Rep TransitionInfo = D1 ('MetaData "TransitionInfo" "Ouroboros.Consensus.HardFork.Combinator.State.Types" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "TransitionUnknown" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin SlotNo))) :+: (C1 ('MetaCons "TransitionKnown" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EpochNo)) :+: C1 ('MetaCons "TransitionImpossible" 'PrefixI 'False) (U1TypeType)))

sequence ∷ ∀ f m xs. (SListI xs, Functor m) ⇒ HardForkState (m :.: f) xs → m (HardForkState f xs) Source #

matchSListI xs ⇒ NS h xs → HardForkState f xs → Either (Mismatch h (Current f) xs) (HardForkState (Product h f) xs) Source #

align Source #

Arguments

∷ ∀ xs f f' f''. All SingleEraBlock xs 
InPairs (Translate f) xs 
NP (f' -.-> (f -.-> f'')) xs 
HardForkState f' xs

State we are aligning with

HardForkState f xs

State we are aligning

HardForkState f'' xs 

tipSListI xs ⇒ HardForkState f xs → NS f xs Source #

fromTZHardForkState f '[blk] → f blk Source #

initHardForkState ∷ f x → HardForkState f (x ': xs) Source #

situateNS h xs → HardForkState f xs → Situated h f xs Source #

reconstructSummary Source #

Arguments

Shape xs 
TransitionInfo

At the tip

HardForkState f xs 
Summary xs 

sequenceHardForkState ∷ ∀ m f xs. (All Top xs, Functor m) ⇒ HardForkState (m :.: f) xs → m (HardForkState f xs) Source #

Thin wrapper around sequence

Support for defining instances

getTip ∷ ∀ f xs. CanHardFork xs ⇒ (∀ blk. SingleEraBlock blk ⇒ f blk → Point blk) → HardForkState f xs → Point (HardForkBlock xs) Source #

Serialisation support

recover ∷ ∀ f xs. CanHardFork xs ⇒ Telescope (K Past) f xs → HardForkState f xs Source #

Recover HardForkState from partial information

The primary goal of this is to make sure that for the current state we really only need to store the underlying f. It is not strictly essential that this is possible but it helps with the unary hardfork case, and it may in general help with binary compatibility.

EpochInfo

epochInfoLedgerAll SingleEraBlock xs ⇒ HardForkLedgerConfig xs → HardForkState LedgerState xs → EpochInfo (Except PastHorizonException) Source #

Construct EpochInfo from the ledger state

NOTE: The resulting EpochInfo is a snapshot only, with a limited range. It should not be stored.

epochInfoPrecomputedTransitionInfoShape xs → TransitionInfoHardForkState f xs → EpochInfo (Except PastHorizonException) Source #

Construct EpochInfo given precomputed TransitionInfo

The transition and state arguments are acquired either from a ticked ledger state or a ledger view.

Ledger specific functionality

extendToSlot ∷ ∀ xs. CanHardFork xs ⇒ HardForkLedgerConfig xs → SlotNoHardForkState LedgerState xs → HardForkState LedgerState xs Source #

Extend the telescope until the specified slot is within the era at the tip