| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ouroboros.Consensus.HardFork.Combinator
Description
The hard fork combinator
Intended for unqualified import
Synopsis
- module Ouroboros.Consensus.HardFork.Combinator.Abstract
- module Ouroboros.Consensus.HardFork.Combinator.Basics
- module Ouroboros.Consensus.HardFork.Combinator.Block
- module Ouroboros.Consensus.HardFork.Combinator.Info
- module Ouroboros.Consensus.HardFork.Combinator.Ledger
- module Ouroboros.Consensus.HardFork.Combinator.Ledger.CommonProtocolParams
- module Ouroboros.Consensus.HardFork.Combinator.Ledger.PeerSelection
- module Ouroboros.Consensus.HardFork.Combinator.Ledger.Query
- module Ouroboros.Consensus.HardFork.Combinator.Mempool
- module Ouroboros.Consensus.HardFork.Combinator.Node
- module Ouroboros.Consensus.HardFork.Combinator.Node.DiffusionPipelining
- module Ouroboros.Consensus.HardFork.Combinator.Node.InitStorage
- module Ouroboros.Consensus.HardFork.Combinator.Node.Metrics
- module Ouroboros.Consensus.HardFork.Combinator.PartialConfig
- module Ouroboros.Consensus.HardFork.Combinator.Protocol
- module Ouroboros.Consensus.HardFork.Combinator.Protocol.ChainSel
- module Ouroboros.Consensus.HardFork.Combinator.Translation
- data Mismatch (f ∷ k → Type) (g ∷ k → Type) (xs ∷ [k]) where
- ML ∷ ∀ {k} (f ∷ k → Type) (x ∷ k) (g ∷ k → Type) (xs1 ∷ [k]). f x → NS g xs1 → Mismatch f g (x ': xs1)
- MR ∷ ∀ {k} (f ∷ k → Type) (xs1 ∷ [k]) (g ∷ k → Type) (x ∷ k). NS f xs1 → g x → Mismatch f g (x ': xs1)
- MS ∷ ∀ {k} (f ∷ k → Type) (g ∷ k → Type) (xs1 ∷ [k]) (x ∷ k). Mismatch f g xs1 → Mismatch f g (x ': xs1)
- data Product2 (f ∷ Type → Type → Type) (g ∷ Type → Type → Type) x y = Pair2 (f x y) (g x y)
- data InPairs (f ∷ k → k → Type) (xs ∷ [k]) where
- data Telescope (g ∷ k → Type) (f ∷ k → Type) (xs ∷ [k]) where
- newtype MismatchEraInfo (xs ∷ [Type]) = MismatchEraInfo {}
- newtype OneEraApplyTxErr (xs ∷ [Type]) = OneEraApplyTxErr {}
- newtype OneEraBlock (xs ∷ [Type]) = OneEraBlock {
- getOneEraBlock ∷ NS I xs
- newtype OneEraGenTx (xs ∷ [Type]) = OneEraGenTx {
- getOneEraGenTx ∷ NS GenTx xs
- newtype OneEraGenTxId (xs ∷ [Type]) = OneEraGenTxId {}
- newtype OneEraHash (xs ∷ [k]) = OneEraHash {}
- newtype OneEraHeader (xs ∷ [Type]) = OneEraHeader {
- getOneEraHeader ∷ NS Header xs
- newtype OneEraTipInfo (xs ∷ [Type]) = OneEraTipInfo {}
- newtype PerEraBlockConfig (xs ∷ [Type]) = PerEraBlockConfig {}
- newtype PerEraCodecConfig (xs ∷ [Type]) = PerEraCodecConfig {}
- newtype PerEraConsensusConfig (xs ∷ [Type]) = PerEraConsensusConfig {}
- newtype PerEraLedgerConfig (xs ∷ [Type]) = PerEraLedgerConfig {}
- newtype PerEraStorageConfig (xs ∷ [Type]) = PerEraStorageConfig {}
- data HardForkForgeStateInfo (xs ∷ [Type]) where
- CurrentEraLacksBlockForging ∷ ∀ x y (xs1 ∷ [Type]). EraIndex (x ': (y ': xs1)) → HardForkForgeStateInfo (x ': (y ': xs1))
- CurrentEraForgeStateUpdated ∷ ∀ (xs ∷ [Type]). OneEraForgeStateInfo xs → HardForkForgeStateInfo xs
- hardForkBlockForging ∷ ∀ (m ∷ Type → Type) (xs ∷ [Type]). (CanHardFork xs, Monad m) ⇒ (NonEmptyOptNP (BlockForging m) xs → Text) → NonEmptyOptNP (MkBlockForging m) xs → MkBlockForging m (HardForkBlock xs)
- type InjectTx = InjectPolyTx GenTx
- pattern InjectTx ∷ (GenTx blk → Maybe (GenTx blk')) → InjectTx blk blk'
- type InjectValidatedTx = InjectPolyTx WrapValidatedGenTx
- pattern InjectValidatedTx ∷ (WrapValidatedGenTx blk → Maybe (WrapValidatedGenTx blk')) → InjectValidatedTx blk blk'
- cannotInjectTx ∷ InjectTx blk blk'
- cannotInjectValidatedTx ∷ InjectValidatedTx blk blk'
- newtype HardForkState (f ∷ Type → Type) (xs ∷ [Type]) = HardForkState {}
- initHardForkState ∷ ∀ f x (xs ∷ [Type]). f x → HardForkState f (x ': xs)
Documentation
data Mismatch (f ∷ k → Type) (g ∷ k → Type) (xs ∷ [k]) where Source #
We have a mismatch in the index between two NS
Constructors
| ML ∷ ∀ {k} (f ∷ k → Type) (x ∷ k) (g ∷ k → Type) (xs1 ∷ [k]). f x → NS g xs1 → Mismatch f g (x ': xs1) | The left is at the current |
| MR ∷ ∀ {k} (f ∷ k → Type) (xs1 ∷ [k]) (g ∷ k → Type) (x ∷ k). NS f xs1 → g x → Mismatch f g (x ': xs1) | The right is at the current |
| MS ∷ ∀ {k} (f ∷ k → Type) (g ∷ k → Type) (xs1 ∷ [k]) (x ∷ k). Mismatch f g xs1 → Mismatch f g (x ': xs1) | There is a mismatch later on in the |
Instances
| (∀ (x ∷ k2) (y ∷ k2). LiftedCoercible p p x y) ⇒ HTrans (Mismatch p ∷ (k2 → Type) → [k2] → Type) (Mismatch p ∷ (k2 → Type) → [k2] → Type) | |
Defined in Data.SOP.Match Methods htrans ∷ ∀ c (xs ∷ [k2]) (ys ∷ [k2]) proxy f g. AllZipN (Prod (Mismatch p)) c xs ys ⇒ proxy c → (∀ (x ∷ k2) (y ∷ k2). c x y ⇒ f x → g y) → Mismatch p f xs → Mismatch p g ys Source # hcoerce ∷ ∀ (f ∷ k2 → Type) (g ∷ k2 → Type) (xs ∷ [k2]) (ys ∷ [k2]). AllZipN (Prod (Mismatch p)) (LiftedCoercible f g) xs ys ⇒ Mismatch p f xs → Mismatch p g ys Source # | |
| HAp (Mismatch f ∷ (k → Type) → [k] → Type) | |
| (All (Compose Show f) xs, All (Compose Show g) xs) ⇒ Show (Mismatch f g xs) | |
| (All (Compose Eq f) xs, All (Compose Eq g) xs) ⇒ Eq (Mismatch f g xs) | |
| (All (Compose Eq f) xs, All (Compose Ord f) xs, All (Compose Eq g) xs, All (Compose Ord g) xs) ⇒ Ord (Mismatch f g xs) | |
Defined in Data.SOP.Match Methods compare ∷ Mismatch f g xs → Mismatch f g xs → Ordering # (<) ∷ Mismatch f g xs → Mismatch f g xs → Bool # (<=) ∷ Mismatch f g xs → Mismatch f g xs → Bool # (>) ∷ Mismatch f g xs → Mismatch f g xs → Bool # (>=) ∷ Mismatch f g xs → Mismatch f g xs → Bool # | |
| (All (Compose NoThunks f) xs, All (Compose NoThunks g) xs) ⇒ NoThunks (Mismatch f g xs) | |
| type Same (Mismatch f ∷ (k2 → Type) → [k2] → Type) | |
| type Prod (Mismatch f ∷ (k → Type) → [k] → Type) | |
| type SListIN (Mismatch f ∷ (k → Type) → [k] → Type) | |
Defined in Data.SOP.Match | |
| type AllN (Mismatch f ∷ (k → Type) → [k] → Type) (c ∷ k → Constraint) | |
Defined in Data.SOP.Match | |
data Product2 (f ∷ Type → Type → Type) (g ∷ Type → Type → Type) x y Source #
Constructors
| Pair2 (f x y) (g x y) |
Instances
data InPairs (f ∷ k → k → Type) (xs ∷ [k]) where Source #
We have an f x y for each pair (x, y) of successive list elements
data Telescope (g ∷ k → Type) (f ∷ k → Type) (xs ∷ [k]) where Source #
Telescope
A telescope is an extension of an NS, where every time we "go right" in the
sum we have an additional value.
The Telescope API mostly follows sop-core conventions, supporting
functor (hmap, hcmap), applicative (hap, hpure), foldable
(hcollapse) and traversable (hsequence'). However, since Telescope
is a bi-functor, it cannot reuse the sop-core classes. The naming scheme
of the functions is adopted from sop-core though; for example:
bi h (c) zipWith | | | | | | | \ zipWith: the name from base | | | | | \ constrained: version of the function with a constraint parameter | | | \ higher order: 'Telescope' (like 'NS'/'NP') is a /higher order/ functor | \ bifunctor: 'Telescope' (unlike 'NS'/'NP') is a higher order /bifunctor/
In addition to the standard SOP operators, the new operators that make
a Telescope a telescope are extend, retract and align; see their
documentation for details.
Constructors
| TZ ∷ ∀ {k} (f ∷ k → Type) (x ∷ k) (g ∷ k → Type) (xs1 ∷ [k]). !(f x) → Telescope g f (x ': xs1) | |
| TS ∷ ∀ {k} (g ∷ k → Type) (x ∷ k) (f ∷ k → Type) (xs1 ∷ [k]). !(g x) → !(Telescope g f xs1) → Telescope g f (x ': xs1) |
Instances
| (∀ (x ∷ k2) (y ∷ k2). LiftedCoercible g g x y) ⇒ HTrans (Telescope g ∷ (k2 → Type) → [k2] → Type) (Telescope g ∷ (k2 → Type) → [k2] → Type) | |
Defined in Data.SOP.Telescope Methods htrans ∷ ∀ c (xs ∷ [k2]) (ys ∷ [k2]) proxy f g0. AllZipN (Prod (Telescope g)) c xs ys ⇒ proxy c → (∀ (x ∷ k2) (y ∷ k2). c x y ⇒ f x → g0 y) → Telescope g f xs → Telescope g g0 ys Source # hcoerce ∷ ∀ (f ∷ k2 → Type) (g0 ∷ k2 → Type) (xs ∷ [k2]) (ys ∷ [k2]). AllZipN (Prod (Telescope g)) (LiftedCoercible f g0) xs ys ⇒ Telescope g f xs → Telescope g g0 ys Source # | |
| HAp (Telescope g ∷ (k → Type) → [k] → Type) | |
| HSequence (Telescope g ∷ (k → Type) → [k] → Type) | |
Defined in Data.SOP.Telescope Methods hsequence' ∷ ∀ (xs ∷ [k]) f (g0 ∷ k → Type). (SListIN (Telescope g) xs, Applicative f) ⇒ Telescope g (f :.: g0) xs → f (Telescope g g0 xs) Source # hctraverse' ∷ ∀ c (xs ∷ [k]) g0 proxy f f'. (AllN (Telescope g) c xs, Applicative g0) ⇒ proxy c → (∀ (a ∷ k). c a ⇒ f a → g0 (f' a)) → Telescope g f xs → g0 (Telescope g f' xs) Source # htraverse' ∷ ∀ (xs ∷ [k]) g0 f f'. (SListIN (Telescope g) xs, Applicative g0) ⇒ (∀ (a ∷ k). f a → g0 (f' a)) → Telescope g f xs → g0 (Telescope g f' xs) Source # | |
| HTraverse_ (Telescope g ∷ (k → Type) → [k] → Type) | |
Defined in Data.SOP.Telescope Methods hctraverse_ ∷ ∀ c (xs ∷ [k]) g0 proxy f. (AllN (Telescope g) c xs, Applicative g0) ⇒ proxy c → (∀ (a ∷ k). c a ⇒ f a → g0 ()) → Telescope g f xs → g0 () Source # htraverse_ ∷ ∀ (xs ∷ [k]) g0 f. (SListIN (Telescope g) xs, Applicative g0) ⇒ (∀ (a ∷ k). f a → g0 ()) → Telescope g f xs → g0 () Source # | |
| (All (Compose Show g) xs, All (Compose Show f) xs) ⇒ Show (Telescope g f xs) | |
| (All (Compose Eq g) xs, All (Compose Eq f) xs) ⇒ Eq (Telescope g f xs) | |
| (All (Compose Eq g) xs, All (Compose Ord g) xs, All (Compose Eq f) xs, All (Compose Ord f) xs) ⇒ Ord (Telescope g f xs) | |
Defined in Data.SOP.Telescope Methods compare ∷ Telescope g f xs → Telescope g f xs → Ordering # (<) ∷ Telescope g f xs → Telescope g f xs → Bool # (<=) ∷ Telescope g f xs → Telescope g f xs → Bool # (>) ∷ Telescope g f xs → Telescope g f xs → Bool # (>=) ∷ Telescope g f xs → Telescope g f xs → Bool # max ∷ Telescope g f xs → Telescope g f xs → Telescope g f xs # min ∷ Telescope g f xs → Telescope g f xs → Telescope g f xs # | |
| (All (Compose NoThunks g) xs, All (Compose NoThunks f) xs) ⇒ NoThunks (Telescope g f xs) | |
| type Same (Telescope g ∷ (k2 → Type) → [k2] → Type) | |
| type Prod (Telescope g ∷ (k → Type) → [k] → Type) | |
| type SListIN (Telescope g ∷ (k → Type) → [k] → Type) | |
Defined in Data.SOP.Telescope | |
| type AllN (Telescope g ∷ (k → Type) → [k] → Type) (c ∷ k → Constraint) | |
Defined in Data.SOP.Telescope | |
newtype MismatchEraInfo (xs ∷ [Type]) Source #
Constructors
| MismatchEraInfo | |
Fields
| |
Instances
| All SingleEraBlock xs ⇒ Show (MismatchEraInfo xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → MismatchEraInfo xs → ShowS # show ∷ MismatchEraInfo xs → String # showList ∷ [MismatchEraInfo xs] → ShowS # | |
| All SingleEraBlock xs ⇒ Eq (MismatchEraInfo xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) ∷ MismatchEraInfo xs → MismatchEraInfo xs → Bool # (/=) ∷ MismatchEraInfo xs → MismatchEraInfo xs → Bool # | |
| CanHardFork xs ⇒ NoThunks (MismatchEraInfo xs) Source # | |
newtype OneEraApplyTxErr (xs ∷ [Type]) Source #
Constructors
| OneEraApplyTxErr | |
Fields | |
Instances
| CanHardFork xs ⇒ Show (OneEraApplyTxErr xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → OneEraApplyTxErr xs → ShowS # show ∷ OneEraApplyTxErr xs → String # showList ∷ [OneEraApplyTxErr xs] → ShowS # | |
| CanHardFork xs ⇒ Eq (OneEraApplyTxErr xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) ∷ OneEraApplyTxErr xs → OneEraApplyTxErr xs → Bool # (/=) ∷ OneEraApplyTxErr xs → OneEraApplyTxErr xs → Bool # | |
newtype OneEraBlock (xs ∷ [Type]) Source #
Constructors
| OneEraBlock | |
Fields
| |
Instances
| CanHardFork xs ⇒ Show (OneEraBlock xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → OneEraBlock xs → ShowS # show ∷ OneEraBlock xs → String # showList ∷ [OneEraBlock xs] → ShowS # | |
newtype OneEraGenTx (xs ∷ [Type]) Source #
Constructors
| OneEraGenTx | |
Fields
| |
Instances
| CanHardFork xs ⇒ Show (OneEraGenTx xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → OneEraGenTx xs → ShowS # show ∷ OneEraGenTx xs → String # showList ∷ [OneEraGenTx xs] → ShowS # | |
| CanHardFork xs ⇒ Eq (OneEraGenTx xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) ∷ OneEraGenTx xs → OneEraGenTx xs → Bool # (/=) ∷ OneEraGenTx xs → OneEraGenTx xs → Bool # | |
| CanHardFork xs ⇒ NoThunks (OneEraGenTx xs) Source # | |
newtype OneEraGenTxId (xs ∷ [Type]) Source #
Constructors
| OneEraGenTxId | |
Fields | |
Instances
| CanHardFork xs ⇒ Show (OneEraGenTxId xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → OneEraGenTxId xs → ShowS # show ∷ OneEraGenTxId xs → String # showList ∷ [OneEraGenTxId xs] → ShowS # | |
| CanHardFork xs ⇒ Eq (OneEraGenTxId xs) Source # | This instance compares the underlying raw hash ( Note that this means that transactions in different eras can have equal
|
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) ∷ OneEraGenTxId xs → OneEraGenTxId xs → Bool # (/=) ∷ OneEraGenTxId xs → OneEraGenTxId xs → Bool # | |
| CanHardFork xs ⇒ Ord (OneEraGenTxId xs) Source # | See the corresponding |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods compare ∷ OneEraGenTxId xs → OneEraGenTxId xs → Ordering # (<) ∷ OneEraGenTxId xs → OneEraGenTxId xs → Bool # (<=) ∷ OneEraGenTxId xs → OneEraGenTxId xs → Bool # (>) ∷ OneEraGenTxId xs → OneEraGenTxId xs → Bool # (>=) ∷ OneEraGenTxId xs → OneEraGenTxId xs → Bool # max ∷ OneEraGenTxId xs → OneEraGenTxId xs → OneEraGenTxId xs # min ∷ OneEraGenTxId xs → OneEraGenTxId xs → OneEraGenTxId xs # | |
| CanHardFork xs ⇒ NoThunks (OneEraGenTxId xs) Source # | |
newtype OneEraHash (xs ∷ [k]) Source #
The hash for an era
This type is special: we don't use an NS here, because the hash by itself
should not allow us to differentiate between eras. If it did, the size
of the hash would necessarily have to increase, and that leads to trouble.
So, the type parameter xs here is merely a phantom one, and we just store
the underlying raw hash.
Constructors
| OneEraHash | |
Fields | |
Instances
| Show (OneEraHash xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → OneEraHash xs → ShowS # show ∷ OneEraHash xs → String # showList ∷ [OneEraHash xs] → ShowS # | |
| Eq (OneEraHash xs) Source # | |
| Ord (OneEraHash xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods compare ∷ OneEraHash xs → OneEraHash xs → Ordering # (<) ∷ OneEraHash xs → OneEraHash xs → Bool # (<=) ∷ OneEraHash xs → OneEraHash xs → Bool # (>) ∷ OneEraHash xs → OneEraHash xs → Bool # (>=) ∷ OneEraHash xs → OneEraHash xs → Bool # max ∷ OneEraHash xs → OneEraHash xs → OneEraHash xs # min ∷ OneEraHash xs → OneEraHash xs → OneEraHash xs # | |
| NoThunks (OneEraHash xs) Source # | |
| Condense (OneEraHash xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods condense ∷ OneEraHash xs → String Source # | |
| Serialise (OneEraHash xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods encode ∷ OneEraHash xs → Encoding Source # decode ∷ Decoder s (OneEraHash xs) Source # encodeList ∷ [OneEraHash xs] → Encoding Source # decodeList ∷ Decoder s [OneEraHash xs] Source # | |
newtype OneEraHeader (xs ∷ [Type]) Source #
Constructors
| OneEraHeader | |
Fields
| |
Instances
| CanHardFork xs ⇒ Show (OneEraHeader xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → OneEraHeader xs → ShowS # show ∷ OneEraHeader xs → String # showList ∷ [OneEraHeader xs] → ShowS # | |
| CanHardFork xs ⇒ NoThunks (OneEraHeader xs) Source # | |
newtype OneEraTipInfo (xs ∷ [Type]) Source #
Constructors
| OneEraTipInfo | |
Fields | |
Instances
| CanHardFork xs ⇒ Show (OneEraTipInfo xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → OneEraTipInfo xs → ShowS # show ∷ OneEraTipInfo xs → String # showList ∷ [OneEraTipInfo xs] → ShowS # | |
| CanHardFork xs ⇒ Eq (OneEraTipInfo xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) ∷ OneEraTipInfo xs → OneEraTipInfo xs → Bool # (/=) ∷ OneEraTipInfo xs → OneEraTipInfo xs → Bool # | |
| CanHardFork xs ⇒ NoThunks (OneEraTipInfo xs) Source # | |
newtype PerEraBlockConfig (xs ∷ [Type]) Source #
Constructors
| PerEraBlockConfig | |
Fields | |
Instances
| CanHardFork xs ⇒ NoThunks (PerEraBlockConfig xs) Source # | |
newtype PerEraCodecConfig (xs ∷ [Type]) Source #
Constructors
| PerEraCodecConfig | |
Fields | |
Instances
| CanHardFork xs ⇒ NoThunks (PerEraCodecConfig xs) Source # | |
newtype PerEraConsensusConfig (xs ∷ [Type]) Source #
Constructors
| PerEraConsensusConfig | |
Fields | |
Instances
| CanHardFork xs ⇒ NoThunks (PerEraConsensusConfig xs) Source # | |
newtype PerEraLedgerConfig (xs ∷ [Type]) Source #
Constructors
| PerEraLedgerConfig | |
Fields | |
Instances
| CanHardFork xs ⇒ Show (PerEraLedgerConfig xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods showsPrec ∷ Int → PerEraLedgerConfig xs → ShowS # show ∷ PerEraLedgerConfig xs → String # showList ∷ [PerEraLedgerConfig xs] → ShowS # | |
| CanHardFork xs ⇒ NoThunks (PerEraLedgerConfig xs) Source # | |
| SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (PerEraLedgerConfig xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient Methods encodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → PerEraLedgerConfig xs → Encoding Source # decodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → ∀ s. Decoder s (PerEraLedgerConfig xs) Source # | |
newtype PerEraStorageConfig (xs ∷ [Type]) Source #
Constructors
| PerEraStorageConfig | |
Fields | |
Instances
| CanHardFork xs ⇒ NoThunks (PerEraStorageConfig xs) Source # | |
data HardForkForgeStateInfo (xs ∷ [Type]) where Source #
For each era in which we want to forge blocks, we have a BlockForging,
and thus ForgeStateInfo.
When we update the hard fork forge state, we only update the forge state of
the current era. However, the current era might not have a forge state as
it lacks a BlockForging.
TODO #2766: expire past ForgeState
Constructors
| CurrentEraLacksBlockForging ∷ ∀ x y (xs1 ∷ [Type]). EraIndex (x ': (y ': xs1)) → HardForkForgeStateInfo (x ': (y ': xs1)) | There is no |
| CurrentEraForgeStateUpdated ∷ ∀ (xs ∷ [Type]). OneEraForgeStateInfo xs → HardForkForgeStateInfo xs | The |
Instances
| CanHardFork xs ⇒ Show (HardForkForgeStateInfo xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Forging Methods showsPrec ∷ Int → HardForkForgeStateInfo xs → ShowS # show ∷ HardForkForgeStateInfo xs → String # showList ∷ [HardForkForgeStateInfo xs] → ShowS # | |
Arguments
| ∷ ∀ (m ∷ Type → Type) (xs ∷ [Type]). (CanHardFork xs, Monad m) | |
| ⇒ (NonEmptyOptNP (BlockForging m) xs → Text) | Used as the |
| → NonEmptyOptNP (MkBlockForging m) xs | |
| → MkBlockForging m (HardForkBlock xs) |
type InjectTx = InjectPolyTx GenTx Source #
pattern InjectTx ∷ (GenTx blk → Maybe (GenTx blk')) → InjectTx blk blk' Source #
InjectPolyTx at type InjectTx
pattern InjectValidatedTx ∷ (WrapValidatedGenTx blk → Maybe (WrapValidatedGenTx blk')) → InjectValidatedTx blk blk' Source #
InjectPolyTx at type InjectValidatedTx
cannotInjectTx ∷ InjectTx blk blk' Source #
cannotInjectPolyTx at type InjectTx
cannotInjectValidatedTx ∷ InjectValidatedTx blk blk' Source #
cannotInjectPolyTx at type InjectValidatedTx
newtype HardForkState (f ∷ Type → Type) (xs ∷ [Type]) 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 | |
Instances
| HAp HardForkState Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances Methods hap ∷ ∀ (f ∷ Type → Type) (g ∷ Type → Type) (xs ∷ [Type]). Prod HardForkState (f -.-> g) xs → HardForkState f xs → HardForkState g xs Source # | |||||
| HCollapse HardForkState Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances Methods hcollapse ∷ ∀ (xs ∷ [Type]) a. SListIN HardForkState xs ⇒ HardForkState (K a ∷ Type → Type) xs → CollapseTo HardForkState a Source # | |||||
| HSequence HardForkState Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances Methods hsequence' ∷ ∀ (xs ∷ [Type]) f (g ∷ Type → Type). (SListIN HardForkState xs, Applicative f) ⇒ HardForkState (f :.: g) xs → f (HardForkState g xs) Source # hctraverse' ∷ ∀ c (xs ∷ [Type]) g proxy f f'. (AllN HardForkState c xs, Applicative g) ⇒ proxy c → (∀ a. c a ⇒ f a → g (f' a)) → HardForkState f xs → g (HardForkState f' xs) Source # htraverse' ∷ ∀ (xs ∷ [Type]) g f f'. (SListIN HardForkState xs, Applicative g) ⇒ (∀ a. f a → g (f' a)) → HardForkState f xs → g (HardForkState f' xs) Source # | |||||
| HTrans HardForkState HardForkState Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances Methods htrans ∷ ∀ c (xs ∷ [Type]) (ys ∷ [Type]) proxy f g. AllZipN (Prod HardForkState) c xs ys ⇒ proxy c → (∀ x y. c x y ⇒ f x → g y) → HardForkState f xs → HardForkState g ys Source # hcoerce ∷ ∀ (f ∷ Type → Type) (g ∷ Type → Type) (xs ∷ [Type]) (ys ∷ [Type]). AllZipN (Prod HardForkState) (LiftedCoercible f g) xs ys ⇒ HardForkState f xs → HardForkState g ys Source # | |||||
| SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods decodeDisk ∷ CodecConfig (HardForkBlock xs) → ∀ s. Decoder s (HardForkChainDepState xs) Source # | |||||
| SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods encodeDisk ∷ CodecConfig (HardForkBlock xs) → HardForkChainDepState xs → Encoding Source # | |||||
| Generic (HardForkState f xs) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types Associated Types
Methods from ∷ HardForkState f xs → Rep (HardForkState f xs) x # to ∷ Rep (HardForkState f xs) x → HardForkState f xs # | |||||
| (All SingleEraBlock xs, ∀ blk. SingleEraBlock blk ⇒ Show (f blk)) ⇒ Show (HardForkState f xs) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances Methods showsPrec ∷ Int → HardForkState f xs → ShowS # show ∷ HardForkState f xs → String # showList ∷ [HardForkState f xs] → ShowS # | |||||
| (All SingleEraBlock xs, ∀ blk. SingleEraBlock blk ⇒ Eq (f blk)) ⇒ Eq (HardForkState f xs) Source # | |||||
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 # | |||||
| data Ticked (HardForkChainDepState xs ∷ Type) Source # | |||||
| type Prod HardForkState Source # | |||||
| type SListIN HardForkState Source # | |||||
| type CollapseTo HardForkState a Source # | |||||
| type AllN HardForkState (c ∷ Type → Constraint) Source # | |||||
| type Same HardForkState Source # | |||||
| type Rep (HardForkState f xs) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Types type Rep (HardForkState f xs) = D1 ('MetaData "HardForkState" "Ouroboros.Consensus.HardFork.Combinator.State.Types" "ouroboros-consensus-0.28.0.0-inplace" 'True) (C1 ('MetaCons "HardForkState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Telescope (K Past ∷ Type → Type) (Current f) xs)))) | |||||
initHardForkState ∷ ∀ f x (xs ∷ [Type]). f x → HardForkState f (x ': xs) Source #