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

Ouroboros.Consensus.Ledger.Dual

Synopsis

Documentation

class (HasHeader m, GetHeader m, HasHeader (Header m), LedgerSupportsProtocol m, HasHardForkHistory m, LedgerSupportsMempool m, CommonProtocolParams m, HasTxId (GenTx m), Show (ApplyTxErr m), Typeable a, UpdateLedger a, LedgerSupportsMempool a, Show (ApplyTxErr a), NoThunks (LedgerConfig a), NoThunks (CodecConfig a), NoThunks (StorageConfig a), Show (BridgeLedger m a), Eq (BridgeLedger m a), Serialise (BridgeLedger m a), Serialise (BridgeBlock m a), Serialise (BridgeTx m a), Show (BridgeTx m a)) ⇒ Bridge m a where Source #

Bridge the two ledgers

Associated Types

type BridgeLedger m a ∷ Type Source #

Additional information relating both ledgers

type BridgeBlock m a ∷ Type Source #

Information required to update the bridge when applying a block

type BridgeTx m a ∷ Type Source #

Information required to update the bridge when applying a transaction

Pair types

data DualBlock m a Source #

Dual block

The dual block is used to instantiate the consensus with a dual ledger, consisting of two ledger states associated with two types of blocks. The (consensus) chain state will still be updated based on one block type only, which is therefore designed as the main block, while the other block is designated as the auxiliary block.

The auxiliary block is optional; this can be used if some " main " blocks should have no effect on the auxiliary ledger state at all. The motivating example is EBBs: if the main blocks are real Byron blocks, and the auxiliary blocks are Byron spec blocks, then regular Byron blocks correspond to Byron spec blocks, but EBBs don't correspond to a spec block at all and should leave the Byron spec ledger state unchanged.

NOTE: The dual ledger is used for testing purposes only; we do not do any meaningful NoThunks checks here.

Constructors

DualBlock 

Instances

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

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

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

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

StandardHash m ⇒ StandardHash (DualBlock m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualBlock m a) → String Source #

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

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

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

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 #

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntGenTx (DualBlock m a) → ShowS #

showGenTx (DualBlock m a) → String #

showList ∷ [GenTx (DualBlock m a)] → 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 #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)LedgerState (DualBlock m a) → LedgerState (DualBlock m a) → Bool #

(/=)LedgerState (DualBlock m a) → LedgerState (DualBlock m a) → 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 #

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

txIdGenTx (DualBlock m a) → TxId (GenTx (DualBlock m a)) Source #

SameDepIndex (BlockQuery (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndexBlockQuery (DualBlock m a) a0 → BlockQuery (DualBlock m a) b → Maybe (a0 :~: b) Source #

ShowQuery (BlockQuery (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showResultBlockQuery (DualBlock m a) result → result → String Source #

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

Defined in Ouroboros.Consensus.Ledger.Dual

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 m, Show a, Show (BridgeBlock m a)) ⇒ Show (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualBlock m a → ShowS #

showDualBlock m a → String #

showList ∷ [DualBlock m a] → ShowS #

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 #

Show (BlockQuery (DualBlock m a) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntBlockQuery (DualBlock m a) result → ShowS #

showBlockQuery (DualBlock m a) result → String #

showList ∷ [BlockQuery (DualBlock m a) result] → ShowS #

(Eq m, Eq a, Eq (BridgeBlock m a)) ⇒ Eq (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

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

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

ConvertRawHash m ⇒ ConvertRawHash (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Bridge m a ⇒ GetHeader (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Bridge m a ⇒ GetPrevHash (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Bridge m a ⇒ BlockSupportsProtocol (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ConfigSupportsNode m ⇒ ConfigSupportsNode (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Bridge m a ⇒ HasHardForkHistory (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type HardForkIndices (DualBlock m a) ∷ [Type] Source #

Bridge m a ⇒ BasicEnvelopeValidation (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Bridge m a ⇒ HasAnnTip (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type TipInfo (DualBlock m a) Source #

Methods

getTipInfoHeader (DualBlock m a) → TipInfo (DualBlock m a) Source #

tipInfoHash ∷ proxy (DualBlock m a) → TipInfo (DualBlock m a) → HeaderHash (DualBlock m a) Source #

Bridge m a ⇒ ValidateEnvelope (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type OtherHeaderEnvelopeError (DualBlock m a) Source #

Bridge m a ⇒ UpdateLedger (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Bridge m a ⇒ CommonProtocolParams (DualBlock m a) Source #

Forward to the main ledger

Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

InspectLedger m ⇒ InspectLedger (DualBlock m a) Source #

InspectLedger just refers to the main block

InspectLedger is intended to check the ledger state against the node's configuration, and hence takes a full TopLevelConfig. However, we cannot construct that for the auxiliary block, since we have no protocol config for it. We therefore just use the main block.

Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type LedgerWarning (DualBlock m a) Source #

type LedgerUpdate (DualBlock m a) Source #

Bridge m a ⇒ BlockSupportsLedgerQuery (DualBlock m a) Source #

Not used in the tests: no constructors

Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

answerBlockQueryExtLedgerCfg (DualBlock m a) → BlockQuery (DualBlock m a) result → ExtLedgerState (DualBlock m a) → result Source #

Bridge m a ⇒ LedgerSupportsMempool (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

LedgerSupportsPeerSelection m ⇒ LedgerSupportsPeerSelection (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Bridge m a ⇒ LedgerSupportsProtocol (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

HasBinaryBlockInfo m ⇒ HasBinaryBlockInfo (DualBlock m a) Source #

The binary info just refers to the main block

This is sufficient, because we never need just the header of the auxiliary.

Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Condense m ⇒ Condense (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

condenseDualBlock m a → String Source #

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 #

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

(Typeable m, Typeable a) ⇒ ShowProxy (BlockQuery (DualBlock m a) ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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 #

type HeaderHash (DualBlock m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type HeaderHash (DualBlock m a ∷ Type) = HeaderHash m
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.18.0.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))))
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.18.0.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))))
data Validated (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type AuxLedgerEvent (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerCfg (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerErr (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type BlockProtocol (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data CodecConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data StorageConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type CannotForge (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type ForgeStateInfo (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type ForgeStateUpdateError (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

newtype NestedCtxt_ (DualBlock m a) f x where
type HardForkIndices (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type OtherHeaderEnvelopeError (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TipInfo (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TipInfo (DualBlock m a) = TipInfo m
data LedgerState (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerUpdate (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerWarning (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockQuery (DualBlock m a) result Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockQuery (DualBlock m a) result
type ApplyTxErr (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data GenTx (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data DualGenTxErr m a Source #

Instances

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualGenTxErr m a) → String Source #

Bridge m a ⇒ Show (DualGenTxErr m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualGenTxErr m a → ShowS #

showDualGenTxErr m a → String #

showList ∷ [DualGenTxErr m a] → ShowS #

data DualLedgerError m a Source #

Both ledger rules threw an error

We do not verify that the errors agree, merely that they both report some error.

If only one of the two semantics reports an error, we fail with an error (see agreeOnError), rather than a regular chain failure; if this happens, it indicates a bug, and the node should fail (rather than just, for example, reject a block).

Instances

Instances details
(Show (LedgerError m), Show (LedgerError a)) ⇒ Show (DualLedgerError m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualLedgerError m a → ShowS #

showDualLedgerError m a → String #

showList ∷ [DualLedgerError m a] → ShowS #

(Eq (LedgerError m), Eq (LedgerError a)) ⇒ Eq (DualLedgerError m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)DualLedgerError m a → DualLedgerError m a → Bool #

(/=)DualLedgerError m a → DualLedgerError m a → Bool #

NoThunks (DualLedgerError m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Lifted functions

dualTopLevelConfigMainTopLevelConfig (DualBlock m a) → TopLevelConfig m Source #

This is only used for block production

Type class family instances

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.18.0.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 GenTx blk ∷ Type Source #

Generalized transaction

The mempool (and, accordingly, blocks) consist of "generalized transactions"; this could be "proper" transactions (transferring funds) but also other kinds of things such as update proposals, delegations, etc.

Instances

Instances details
Inject GenTx Source # 
Instance details

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

Methods

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

Isomorphic GenTx Source # 
Instance details

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

Methods

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

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

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 (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)) #

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntGenTx (DualBlock m a) → ShowS #

showGenTx (DualBlock m a) → String #

showList ∷ [GenTx (DualBlock m a)] → 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 #

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 (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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 #

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

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 #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

txIdGenTx (DualBlock m a) → TxId (GenTx (DualBlock m a)) Source #

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

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

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

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

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

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

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

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

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

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.18.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.18.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
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.18.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId 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 GenTx (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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 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 family LedgerState blk ∷ Type Source #

Ledger state associated with a block

This is the Consensus notion of a ledger state. Each block type is associated with one of the Ledger types for the ledger state. Virtually every concept in this codebase revolves around this type, or the referenced blk. Whenever we use the type variable l, we intend to denote that the expected instantiation is either a LedgerState or some wrapper over it (like the ExtLedgerState).

The main operations we can do with a LedgerState are ticking (defined in IsLedger), and applying a block (defined in ApplyBlock).

Instances

Instances details
Inject LedgerState Source # 
Instance details

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

Methods

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

Isomorphic LedgerState Source # 
Instance details

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

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 (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)LedgerState (DualBlock m a) → LedgerState (DualBlock m a) → Bool #

(/=)LedgerState (DualBlock m a) → LedgerState (DualBlock m a) → Bool #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Ledger.Dual

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 (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a ⇒ GetTip (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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

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

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

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

Isomorphic (Ticked :.: LedgerState) Source # 
Instance details

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

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

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ Type) = HeaderHash blk
type Rep (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerCfg (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerErr (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype LedgerState (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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 LedgerState (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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 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.18.0.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.18.0.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
data Ticked (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (PBftState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

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

Serialisation

encodeDualBlock ∷ (Bridge m a, Serialise a) ⇒ (m → Encoding) → DualBlock m a → Encoding Source #