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

Ouroboros.Consensus.HardFork.Combinator

Description

The hard fork combinator

Intended for unqualified import

Synopsis

Documentation

data family TxId tx ∷ Type Source #

A generalized transaction, GenTx, identifier.

Instances

Instances details
Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (TxId (GenTx (DualBlock m a))) → String Source #

Generic (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (TxId (GenTx (HardForkBlock xs))) ∷ TypeType #

Methods

fromTxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x #

toRep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) #

CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

showsPrecIntTxId (GenTx (HardForkBlock xs)) → ShowS #

showTxId (GenTx (HardForkBlock xs)) → String #

showList ∷ [TxId (GenTx (HardForkBlock xs))] → ShowS #

Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntTxId (GenTx (DualBlock m a)) → ShowS #

showTxId (GenTx (DualBlock m a)) → String #

showList ∷ [TxId (GenTx (DualBlock m a))] → ShowS #

CanHardFork xs ⇒ Eq (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

(==)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

(/=)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

Eq (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(/=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

compareTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering #

(<)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(<=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

maxTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

minTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

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

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

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

type Rep (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.20.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
newtype TxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family Header blk ∷ Type Source #

Instances

Instances details
Inject Header Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → Header x → Header (HardForkBlock xs) Source #

Isomorphic Header Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source #

injectNoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source #

CanHardFork xs ⇒ HasNestedContent Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ ReconstructNestedCtxt Header (HardForkBlock xs) Source # 
Instance details

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

HasHeader blk ⇒ StandardHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Typeable xs ⇒ ShowProxy (Header (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → String Source #

CanHardFork xs ⇒ Show (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

All (Compose Eq Header) xs ⇒ Eq (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Methods

(==)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

(/=)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

CanHardFork xs ⇒ NoThunks (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

NoThunks (Header (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All CondenseConstraints xs ⇒ Condense (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

CanHardFork xs ⇒ HasHeader (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (Header (HardForkBlock xs)) Source # 
Instance details

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

SerialiseHFC xs ⇒ DecodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ DecodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ EncodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ EncodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

encodeDiskDepCodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source #

EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Header m) ⇒ Show (DualHeader m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualHeader m a → ShowS #

showDualHeader m a → String #

showList ∷ [DualHeader m a] → ShowS #

CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Bridge m a ⇒ HasHeader (DualHeader m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All SingleEraBlock xs ⇒ Show (NestedCtxt_ (HardForkBlock xs) Header a) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type HeaderHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk ∷ Type) = HeaderHash blk
type BlockProtocol (Header blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data EpochInfo (m ∷ TypeType) Source #

Information about epochs

Different epochs may have different sizes and different slot lengths. This information is encapsulated by EpochInfo. It is parameterized over a monad m because the information about how long each epoch is may depend on information derived from the blockchain itself. It ultimately requires acess to state, and so either uses the monad for that or uses the monad to reify failure due to cached state information being too stale for the current query.

Constructors

EpochInfo 

Fields

Instances

Instances details
Show (EpochInfo f)

Unhelpful instance, but this type occurs in records (eg Shelley.Globals) that we want to be able to show

Instance details

Defined in Cardano.Slotting.EpochInfo.API

Methods

showsPrecIntEpochInfo f → ShowS #

showEpochInfo f → String #

showList ∷ [EpochInfo f] → ShowS #

NoThunks (EpochInfo m) 
Instance details

Defined in Cardano.Slotting.EpochInfo.API

type Except e = ExceptT e Identity #

The parameterizable exception monad.

Computations are either exceptions or normal values.

The return function returns a normal value, while >>= exits on the first exception. For a variant that continues after an error and collects all the errors, see Errors.

data Product2 (f ∷ TypeTypeType) (g ∷ TypeTypeType) x y Source #

Constructors

Pair2 (f x y) (g x y) 

Instances

Instances details
Generic (Product2 f g x y) 
Instance details

Defined in Data.SOP.Functors

Associated Types

type Rep (Product2 f g x y) ∷ TypeType #

Methods

fromProduct2 f g x y → Rep (Product2 f g x y) x0 #

toRep (Product2 f g x y) x0 → Product2 f g x y #

(Show (f x y), Show (g x y)) ⇒ Show (Product2 f g x y) 
Instance details

Defined in Data.SOP.Functors

Methods

showsPrecIntProduct2 f g x y → ShowS #

showProduct2 f g x y → String #

showList ∷ [Product2 f g x y] → ShowS #

(Eq (f x y), Eq (g x y)) ⇒ Eq (Product2 f g x y) 
Instance details

Defined in Data.SOP.Functors

Methods

(==)Product2 f g x y → Product2 f g x y → Bool #

(/=)Product2 f g x y → Product2 f g x y → Bool #

type Rep (Product2 f g x y) 
Instance details

Defined in Data.SOP.Functors

type Rep (Product2 f g x y) = D1 ('MetaData "Product2" "Data.SOP.Functors" "sop-extras-0.2.1.0-inplace" 'False) (C1 ('MetaCons "Pair2" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f x y)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (g x y))))

class IsNonEmpty (xs ∷ [a]) where Source #

Methods

isNonEmpty ∷ proxy xs → ProofNonEmpty xs Source #

Instances

Instances details
IsNonEmpty (x ': xs ∷ [a]) 
Instance details

Defined in Data.SOP.NonEmpty

Methods

isNonEmpty ∷ proxy (x ': xs) → ProofNonEmpty (x ': xs) Source #

data ProofNonEmpty (xs ∷ [a]) where Source #

Constructors

ProofNonEmpty ∷ ∀ {a} (x ∷ a) (xs1 ∷ [a]). Proxy x → Proxy xs1 → ProofNonEmpty (x ': xs1) 

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

Constructors

PNil ∷ ∀ {k} (f ∷ k → k → Type) (x ∷ k). InPairs f '[x] 
PCons ∷ ∀ {k} (f ∷ k → k → Type) (x ∷ k) (y ∷ k) (zs ∷ [k]). f x y → InPairs f (y ': zs) → InPairs f (x ': (y ': zs)) 

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

Instances details
(∀ (x ∷ k2) (y ∷ k2). LiftedCoercible g g x y) ⇒ HTrans (Telescope g ∷ (k2 → Type) → [k2] → Type) (Telescope g ∷ (k2 → Type) → [k2] → Type) 
Instance details

Defined in Data.SOP.Telescope

Methods

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

hcoerce ∷ ∀ (f ∷ k1 → Type) (g0 ∷ k20 → Type) (xs ∷ l1) (ys ∷ l2). 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) 
Instance details

Defined in Data.SOP.Telescope

Methods

hap ∷ ∀ (f ∷ k0 → Type) (g0 ∷ k0 → Type) (xs ∷ l). Prod (Telescope g) (f -.-> g0) xs → Telescope g f xs → Telescope g g0 xs Source #

HSequence (Telescope g ∷ (k → Type) → [k] → Type) 
Instance details

Defined in Data.SOP.Telescope

Methods

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

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

htraverse' ∷ ∀ (xs ∷ l) g0 f f'. (SListIN (Telescope g) xs, Applicative g0) ⇒ (∀ (a ∷ k0). f a → g0 (f' a)) → Telescope g f xs → g0 (Telescope g f' xs) Source #

HTraverse_ (Telescope g ∷ (k → Type) → [k] → Type) 
Instance details

Defined in Data.SOP.Telescope

Methods

hctraverse_ ∷ ∀ c (xs ∷ l) g0 proxy f. (AllN (Telescope g) c xs, Applicative g0) ⇒ proxy c → (∀ (a ∷ k0). c a ⇒ f a → g0 ()) → Telescope g f xs → g0 () Source #

htraverse_ ∷ ∀ (xs ∷ l) g0 f. (SListIN (Telescope g) xs, Applicative g0) ⇒ (∀ (a ∷ k0). f a → g0 ()) → Telescope g f xs → g0 () Source #

(All (Compose Show g) xs, All (Compose Show f) xs) ⇒ Show (Telescope g f xs) 
Instance details

Defined in Data.SOP.Telescope

Methods

showsPrecIntTelescope g f xs → ShowS #

showTelescope g f xs → String #

showList ∷ [Telescope g f xs] → ShowS #

(All (Compose Eq g) xs, All (Compose Eq f) xs) ⇒ Eq (Telescope g f xs) 
Instance details

Defined in Data.SOP.Telescope

Methods

(==)Telescope g f xs → Telescope g f xs → Bool #

(/=)Telescope g f xs → Telescope g f xs → Bool #

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

Defined in Data.SOP.Telescope

Methods

compareTelescope 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 #

maxTelescope g f xs → Telescope g f xs → Telescope g f xs #

minTelescope 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) 
Instance details

Defined in Data.SOP.Telescope

type Same (Telescope g ∷ (k2 → Type) → [k2] → Type) 
Instance details

Defined in Data.SOP.Telescope

type Same (Telescope g ∷ (k2 → Type) → [k2] → Type) = Telescope g
type Prod (Telescope g ∷ (k → Type) → [k] → Type) 
Instance details

Defined in Data.SOP.Telescope

type Prod (Telescope g ∷ (k → Type) → [k] → Type) = NP ∷ (k → Type) → [k] → Type
type SListIN (Telescope g ∷ (k → Type) → [k] → Type) 
Instance details

Defined in Data.SOP.Telescope

type SListIN (Telescope g ∷ (k → Type) → [k] → Type) = SListI ∷ [k] → Constraint
type AllN (Telescope g ∷ (k → Type) → [k] → Type) (c ∷ k → Constraint) 
Instance details

Defined in Data.SOP.Telescope

type AllN (Telescope g ∷ (k → Type) → [k] → Type) (c ∷ k → Constraint) = All c

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 x and the right is somewhere in the later xs

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 x and the left is somewhere in the later xs

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 xs

Instances

Instances details
(∀ (x ∷ k2) (y ∷ k2). LiftedCoercible p p x y) ⇒ HTrans (Mismatch p ∷ (k2 → Type) → [k2] → Type) (Mismatch p ∷ (k2 → Type) → [k2] → Type) 
Instance details

Defined in Data.SOP.Match

Methods

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

hcoerce ∷ ∀ (f ∷ k1 → Type) (g ∷ k20 → Type) (xs ∷ l1) (ys ∷ l2). 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) 
Instance details

Defined in Data.SOP.Match

Methods

hap ∷ ∀ (f0 ∷ k0 → Type) (g ∷ k0 → Type) (xs ∷ l). Prod (Mismatch f) (f0 -.-> g) xs → Mismatch f f0 xs → Mismatch f g xs Source #

(All (Compose Show f) xs, All (Compose Show g) xs) ⇒ Show (Mismatch f g xs) 
Instance details

Defined in Data.SOP.Match

Methods

showsPrecIntMismatch f g xs → ShowS #

showMismatch f g xs → String #

showList ∷ [Mismatch f g xs] → ShowS #

(All (Compose Eq f) xs, All (Compose Eq g) xs) ⇒ Eq (Mismatch f g xs) 
Instance details

Defined in Data.SOP.Match

Methods

(==)Mismatch f g xs → Mismatch f g xs → Bool #

(/=)Mismatch f g xs → Mismatch f g xs → Bool #

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

Defined in Data.SOP.Match

Methods

compareMismatch 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 #

maxMismatch f g xs → Mismatch f g xs → Mismatch f g xs #

minMismatch f g xs → Mismatch f g xs → Mismatch f g xs #

(All (Compose NoThunks f) xs, All (Compose NoThunks g) xs) ⇒ NoThunks (Mismatch f g xs) 
Instance details

Defined in Data.SOP.Match

type Same (Mismatch f ∷ (k2 → Type) → [k2] → Type) 
Instance details

Defined in Data.SOP.Match

type Same (Mismatch f ∷ (k2 → Type) → [k2] → Type) = Mismatch f
type Prod (Mismatch f ∷ (k → Type) → [k] → Type) 
Instance details

Defined in Data.SOP.Match

type Prod (Mismatch f ∷ (k → Type) → [k] → Type) = NP ∷ (k → Type) → [k] → Type
type SListIN (Mismatch f ∷ (k → Type) → [k] → Type) 
Instance details

Defined in Data.SOP.Match

type SListIN (Mismatch f ∷ (k → Type) → [k] → Type) = SListI ∷ [k] → Constraint
type AllN (Mismatch f ∷ (k → Type) → [k] → Type) (c ∷ k → Constraint) 
Instance details

Defined in Data.SOP.Match

type AllN (Mismatch f ∷ (k → Type) → [k] → Type) (c ∷ k → Constraint) = All c

data family BlockConfig blk ∷ Type Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Isomorphic BlockConfig Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype BlockConfig (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family CodecConfig blk ∷ Type Source #

Static configuration required for serialisation and deserialisation of types pertaining to this type of block.

Data family instead of type family to get better type inference.

Instances

Instances details
Isomorphic CodecConfig Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Generic (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type Rep (CodecConfig (DualBlock m a)) ∷ TypeType #

Methods

fromCodecConfig (DualBlock m a) → Rep (CodecConfig (DualBlock m a)) x #

toRep (CodecConfig (DualBlock m a)) x → CodecConfig (DualBlock m a) #

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.20.1.0-inplace" 'False) (C1 ('MetaCons "DualCodecConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualCodecConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig m)) :*: S1 ('MetaSel ('Just "dualCodecConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig a))))
newtype CodecConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data CodecConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family StorageConfig blk ∷ Type Source #

Config needed for the NodeInitStorage class. Defined here to avoid circular dependencies.

Instances

Instances details
Isomorphic StorageConfig Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Generic (StorageConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type Rep (StorageConfig (DualBlock m a)) ∷ TypeType #

CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (StorageConfig m), NoThunks (StorageConfig a)) ⇒ NoThunks (StorageConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.20.1.0-inplace" 'False) (C1 ('MetaCons "DualStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualStorageConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig m)) :*: S1 ('MetaSel ('Just "dualStorageConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig a))))
newtype StorageConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data StorageConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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.20.1.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

data family NestedCtxt_ blk ∷ (TypeType) → TypeType Source #

Context identifying what kind of block we have

In almost all places we will use NestedCtxt rather than NestedCtxt_.

Instances

Instances details
CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SameDepIndex (NestedCtxt_ m f) ⇒ SameDepIndex (NestedCtxt_ (DualBlock m a) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndexNestedCtxt_ (DualBlock m a) f a0 → NestedCtxt_ (DualBlock m a) f b → Maybe (a0 :~: b) Source #

All SingleEraBlock xs ⇒ Show (NestedCtxt_ (HardForkBlock xs) Header a) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Show (NestedCtxt_ m f x) ⇒ Show (NestedCtxt_ (DualBlock m a) f x) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntNestedCtxt_ (DualBlock m a) f x → ShowS #

showNestedCtxt_ (DualBlock m a) f x → String #

showList ∷ [NestedCtxt_ (DualBlock m a) f x] → ShowS #

data NestedCtxt_ (HardForkBlock xs) a b Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
newtype NestedCtxt_ (DualBlock m a) f x Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype NestedCtxt_ (DualBlock m a) f x where

data PastHorizonException Source #

We tried to convert something that is past the horizon

That is, we tried to convert something that is past the point in time beyond which we lack information due to uncertainty about the next hard fork.

data family Validated x ∷ Type Source #

" Validated " transaction or block

The ledger defines how to validate transactions and blocks. It's possible the type before and after validation may be distinct (eg Alonzo transactions), which originally motivated this family.

We also gain the related benefit that certain interface functions, such as those that reapply blocks, can have a more precise type now. TODO

Similarly, the Node-to-Client mini protocols can explicitly indicate that the client trusts the blocks from the local server, by having the server send Validated blocks to the client. TODO

Note that validation has different implications for a transaction than for a block. In particular, a validated transaction can be " reapplied " to different ledger states, whereas a validated block must only be " reapplied " to the exact same ledger state (eg as part of rebuilding from an on-disk ledger snapshot).

Since the ledger defines validation, see the ledger details for concrete examples of what determines the validity (wrt to a LedgerState) of a transaction and/or block. Example properties include: a transaction's claimed inputs exist and are still unspent, a block carries a sufficient cryptographic signature, etc.

Instances

Instances details
Generic (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (Validated (GenTx (HardForkBlock xs))) ∷ TypeType #

CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntValidated (GenTx (DualBlock m a)) → ShowS #

showValidated (GenTx (DualBlock m a)) → String #

showList ∷ [Validated (GenTx (DualBlock m a))] → ShowS #

CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.20.1.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
newtype Validated (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data Validated (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype MismatchEraInfo xs Source #

Constructors

MismatchEraInfo 

Fields

newtype OneEraBlock xs Source #

Constructors

OneEraBlock 

Fields

Instances

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

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Methods

showsPrecIntOneEraBlock xs → ShowS #

showOneEraBlock xs → String #

showList ∷ [OneEraBlock xs] → ShowS #

newtype OneEraGenTx xs Source #

Constructors

OneEraGenTx 

Fields

newtype OneEraGenTxId xs Source #

Constructors

OneEraGenTxId 

Instances

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

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Methods

showsPrecIntOneEraGenTxId xs → ShowS #

showOneEraGenTxId xs → String #

showList ∷ [OneEraGenTxId xs] → ShowS #

CanHardFork xs ⇒ Eq (OneEraGenTxId xs) Source #

This instance compares the underlying raw hash (toRawTxIdHash) of the TxId.

Note that this means that transactions in different eras can have equal TxIds. This should only be the case when the transaction format is backwards compatible from one era to the next.

Instance details

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 Eq instance.

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

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

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

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 

Instances

Instances details
Show (OneEraHash xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Methods

showsPrecIntOneEraHash xs → ShowS #

showOneEraHash xs → String #

showList ∷ [OneEraHash xs] → ShowS #

Eq (OneEraHash xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Methods

(==)OneEraHash xs → OneEraHash xs → Bool #

(/=)OneEraHash xs → OneEraHash xs → Bool #

Ord (OneEraHash xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Methods

compareOneEraHash xs → OneEraHash xs → Ordering #

(<)OneEraHash xs → OneEraHash xs → Bool #

(<=)OneEraHash xs → OneEraHash xs → Bool #

(>)OneEraHash xs → OneEraHash xs → Bool #

(>=)OneEraHash xs → OneEraHash xs → Bool #

maxOneEraHash xs → OneEraHash xs → OneEraHash xs #

minOneEraHash xs → OneEraHash xs → OneEraHash xs #

NoThunks (OneEraHash xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Condense (OneEraHash xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Methods

condenseOneEraHash xs → String Source #

Serialise (OneEraHash xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

data HardForkForgeStateInfo xs 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

CurrentEraLacksBlockForgingEraIndex (x ': (y ': xs)) → HardForkForgeStateInfo (x ': (y ': xs))

There is no BlockForging record for the current era.

CurrentEraForgeStateUpdatedOneEraForgeStateInfo xs → HardForkForgeStateInfo xs

The ForgeState of the current era was updated.

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

class (All SingleEraBlock xs, Typeable xs, IsNonEmpty xs, Measure (HardForkTxMeasure xs), HasByteSize (HardForkTxMeasure xs), NoThunks (HardForkTxMeasure xs), Show (HardForkTxMeasure xs)) ⇒ CanHardFork xs where Source #

Associated Types

type HardForkTxMeasure xs Source #

A measure that can accurately represent the TxMeasure of any era.

Usually, this can simply be the union of the sets of components of each individual era's TxMeasure. (Which is too awkward of a type to express in Haskell.)

Methods

hardForkEraTranslationEraTranslation xs Source #

hardForkChainSelTails AcrossEraSelection xs Source #

hardForkInjectTxsInPairs (RequiringBoth WrapLedgerConfig (Product2 InjectTx InjectValidatedTx)) xs Source #

hardForkInjTxMeasureNS WrapTxMeasure xs → HardForkTxMeasure xs Source #

This is ideally exact.

If that's not possible, the result must not be too small, since this is relied upon to determine which prefix of the mempool's txs will fit in a valid block.

class SingleEraBlock blk ⇒ NoHardForks blk where Source #

Methods

getEraParamsTopLevelConfig blk → EraParams Source #

Extract EraParams from the top-level config

The HFC itself does not care about this, as it must be given the full shape across all eras.

toPartialLedgerConfig ∷ proxy blk → LedgerConfig blk → PartialLedgerConfig blk Source #

Construct partial ledger config from full ledger config

See also toPartialConsensusConfig

class (LedgerSupportsProtocol blk, InspectLedger blk, LedgerSupportsMempool blk, ConvertRawTxId (GenTx blk), BlockSupportsLedgerQuery blk, HasPartialConsensusConfig (BlockProtocol blk), HasPartialLedgerConfig blk, ConvertRawHash blk, ReconstructNestedCtxt Header blk, CommonProtocolParams blk, LedgerSupportsPeerSelection blk, ConfigSupportsNode blk, NodeInitStorage blk, BlockSupportsDiffusionPipelining blk, BlockSupportsMetrics blk, Eq (GenTx blk), Eq (Validated (GenTx blk)), Eq (ApplyTxErr blk), Show blk, Show (Header blk), Show (CannotForge blk), Show (ForgeStateInfo blk), Show (ForgeStateUpdateError blk), Show (LedgerState blk), Eq (LedgerState blk), NoThunks (LedgerState blk)) ⇒ SingleEraBlock blk where Source #

Blocks from which we can assemble a hard fork

Methods

singleEraTransition Source #

Arguments

PartialLedgerConfig blk 
EraParams

Current era parameters

Bound

Start of this era

LedgerState blk 
Maybe EpochNo 

Era transition

This should only report the transition point once it is stable (rollback cannot affect it anymore).

Since we need this to construct the HardForkSummary (and hence the EpochInfo), this takes the partial config, not the full config (or we'd end up with a catch-22).

singleEraInfo ∷ proxy blk → SingleEraInfo blk Source #

Era information (for use in error messages)

newtype EraIndex xs Source #

Constructors

EraIndex 

Fields

newtype HardForkBlock xs Source #

Constructors

HardForkBlock 

Instances

Instances details
CanHardFork xs ⇒ HasNestedContent Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ ReconstructNestedCtxt Header (HardForkBlock xs) Source # 
Instance details

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

CanHardFork xs ⇒ StandardHash (HardForkBlock xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Typeable xs ⇒ ShowProxy (Header (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Typeable xs ⇒ ShowProxy (HardForkBlock xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Typeable xs ⇒ ShowProxy (GenTx (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Generic (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (Validated (GenTx (HardForkBlock xs))) ∷ TypeType #

Generic (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (GenTx (HardForkBlock xs)) ∷ TypeType #

Methods

fromGenTx (HardForkBlock xs) → Rep (GenTx (HardForkBlock xs)) x #

toRep (GenTx (HardForkBlock xs)) x → GenTx (HardForkBlock xs) #

Generic (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (TxId (GenTx (HardForkBlock xs))) ∷ TypeType #

Methods

fromTxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x #

toRep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

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

CanHardFork xs ⇒ Show (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

showsPrecIntHardForkBlock xs → ShowS #

showHardForkBlock xs → String #

showList ∷ [HardForkBlock xs] → ShowS #

CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ Show (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

showsPrecIntGenTx (HardForkBlock xs) → ShowS #

showGenTx (HardForkBlock xs) → String #

showList ∷ [GenTx (HardForkBlock xs)] → ShowS #

CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

showsPrecIntTxId (GenTx (HardForkBlock xs)) → ShowS #

showTxId (GenTx (HardForkBlock xs)) → String #

showList ∷ [TxId (GenTx (HardForkBlock xs))] → ShowS #

All (Compose Eq Header) xs ⇒ Eq (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Methods

(==)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

(/=)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

All Eq xs ⇒ Eq (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Methods

(==)HardForkBlock xs → HardForkBlock xs → Bool #

(/=)HardForkBlock xs → HardForkBlock xs → Bool #

CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ Eq (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

(==)GenTx (HardForkBlock xs) → GenTx (HardForkBlock xs) → Bool #

(/=)GenTx (HardForkBlock xs) → GenTx (HardForkBlock xs) → Bool #

CanHardFork xs ⇒ Eq (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

(==)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

(/=)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ NoThunks (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ NoThunks (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ BlockSupportsDiffusionPipelining (HardForkBlock xs) Source #

The BlockSupportsDiffusionPipelining instance for the HFC is compositional:

This behavior guarantees the "Consistent validity under subsequences" requirement if it is satisfied for every era.

Note that at an era boundary, the tip of the selection might switch multiple times between two adjacent eras. Compared to the scenario where the pipelining criteria in both eras are compatible and make sense even across eras, this might lead to unnecessarily strict/relaxed diffusion pipelining. However, the tip switching between different eras is rare and rather short, so there is no direct need to address this, so we rather avoid the extra complexity for now.

Still, a possible future refinement would be to allow custom logic for "upgrading" the TentativeHeaderState to a new era.

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Node.DiffusionPipelining

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Node.Metrics

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Node.SanityCheck

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Node

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Associated Types

type TipInfo (HardForkBlock xs) Source #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.CommonProtocolParams

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

CanHardFork xs ⇒ HasTxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

txIdGenTx (HardForkBlock xs) → TxId (GenTx (HardForkBlock xs)) Source #

All HasTxs xs ⇒ HasTxs (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type TxMeasure (HardForkBlock xs) Source #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.PeerSelection

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Node.InitStorage

SerialiseHFC xs ⇒ HasNetworkProtocolVersion (HardForkBlock xs) Source # 
Instance details

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

(CanHardFork xs, SupportedNetworkProtocolVersion (HardForkBlock xs), SerialiseHFC xs) ⇒ RunNode (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Node

SerialiseHFC xs ⇒ SerialiseNodeToClientConstraints (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ SerialiseNodeToNodeConstraints (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ SerialiseDiskConstraints (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ HasBinaryBlockInfo (HardForkBlock xs) Source # 
Instance details

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

All CondenseConstraints xs ⇒ Condense (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All SingleEraBlock xs ⇒ SameDepIndex (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

CanHardFork xs ⇒ HasHeader (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

All SingleEraBlock xs ⇒ ShowQuery (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

Methods

showResultBlockQuery (HardForkBlock xs) result → result → String Source #

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) SlotNo Source # 
Instance details

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (HardForkApplyTxErr xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # 
Instance details

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