Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.Ledger.Dual
Synopsis
- 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
- type BridgeLedger m a
- type BridgeBlock m a
- type BridgeTx m a
- updateBridgeWithBlock ∷ DualBlock m a → BridgeLedger m a → BridgeLedger m a
- updateBridgeWithTx ∷ Validated (GenTx (DualBlock m a)) → BridgeLedger m a → BridgeLedger m a
- data DualBlock m a = DualBlock {
- dualBlockMain ∷ m
- dualBlockAux ∷ Maybe a
- dualBlockBridge ∷ BridgeBlock m a
- data DualGenTxErr m a = DualGenTxErr {}
- type DualHeader m a = Header (DualBlock m a)
- data DualLedgerConfig m a = DualLedgerConfig {}
- data DualLedgerError m a = DualLedgerError {}
- ctxtDualMain ∷ ∀ m a (f ∷ Type → Type) x. NestedCtxt_ (DualBlock m a) f x → NestedCtxt_ m f x
- dualExtValidationErrorMain ∷ ExtValidationError (DualBlock m a) → ExtValidationError m
- dualTopLevelConfigMain ∷ TopLevelConfig (DualBlock m a) → TopLevelConfig m
- data family BlockConfig blk
- data family CodecConfig blk
- data family GenTx blk
- data family Header blk
- data family LedgerState blk (mk ∷ MapKind)
- newtype LedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) = LedgerTables {
- getLedgerTables ∷ mk (TxIn l) (TxOut l)
- data family NestedCtxt_ blk ∷ (Type → Type) → Type → Type
- data family StorageConfig blk
- data family Ticked (st ∷ k) ∷ k
- data family TxId blk
- data family Validated x
- decodeDualBlock ∷ (Bridge m a, Serialise a) ⇒ Decoder s (ByteString → m) → Decoder s (ByteString → DualBlock m a)
- decodeDualGenTx ∷ (Bridge m a, Serialise (GenTx a)) ⇒ Decoder s (GenTx m) → Decoder s (GenTx (DualBlock m a))
- decodeDualGenTxErr ∷ Serialise (ApplyTxErr a) ⇒ Decoder s (ApplyTxErr m) → Decoder s (ApplyTxErr (DualBlock m a))
- decodeDualGenTxId ∷ Decoder s (GenTxId m) → Decoder s (GenTxId (DualBlock m a))
- decodeDualHeader ∷ Decoder s (ByteString → Header m) → Decoder s (ByteString → Header (DualBlock m a))
- decodeDualLedgerConfig ∷ Decoder s (LedgerCfg (LedgerState m)) → Decoder s (LedgerCfg (LedgerState a)) → Decoder s (DualLedgerConfig m a)
- decodeDualLedgerState ∷ ∀ m a s (mk ∷ MapKind). (Bridge m a, Serialise (LedgerState a ValuesMK)) ⇒ Decoder s (LedgerState m mk) → Decoder s (LedgerState (DualBlock m a) mk)
- encodeDualBlock ∷ (Bridge m a, Serialise a) ⇒ (m → Encoding) → DualBlock m a → Encoding
- encodeDualGenTx ∷ (Bridge m a, Serialise (GenTx a)) ⇒ (GenTx m → Encoding) → GenTx (DualBlock m a) → Encoding
- encodeDualGenTxErr ∷ Serialise (ApplyTxErr a) ⇒ (ApplyTxErr m → Encoding) → ApplyTxErr (DualBlock m a) → Encoding
- encodeDualGenTxId ∷ (GenTxId m → Encoding) → GenTxId (DualBlock m a) → Encoding
- encodeDualHeader ∷ (Header m → Encoding) → Header (DualBlock m a) → Encoding
- encodeDualLedgerConfig ∷ (LedgerCfg (LedgerState m) → Encoding) → (LedgerCfg (LedgerState a) → Encoding) → DualLedgerConfig m a → Encoding
- encodeDualLedgerState ∷ ∀ m a (mk ∷ MapKind). (Bridge m a, Serialise (LedgerState a ValuesMK)) ⇒ (LedgerState m mk → Encoding) → LedgerState (DualBlock m a) mk → Encoding
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 Source #
Additional information relating both ledgers
type BridgeBlock m a Source #
Information required to update the bridge when applying a block
Information required to update the bridge when applying a transaction
Methods
updateBridgeWithBlock ∷ DualBlock m a → BridgeLedger m a → BridgeLedger m a Source #
updateBridgeWithTx ∷ Validated (GenTx (DualBlock m a)) → BridgeLedger m a → BridgeLedger m a Source #
Pair types
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 | |
Fields
|
Instances
data DualGenTxErr m a Source #
Constructors
DualGenTxErr | |
Fields |
Instances
(Typeable m, Typeable a) ⇒ ShowProxy (DualGenTxErr m a ∷ Type) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
Bridge m a ⇒ Show (DualGenTxErr m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods showsPrec ∷ Int → DualGenTxErr m a → ShowS # show ∷ DualGenTxErr m a → String # showList ∷ [DualGenTxErr m a] → ShowS # |
type DualHeader m a = Header (DualBlock m a) Source #
data DualLedgerConfig m a Source #
Constructors
DualLedgerConfig | |
Fields |
Instances
NoThunks (DualLedgerConfig m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual |
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).
Constructors
DualLedgerError | |
Fields |
Instances
(Show (LedgerError m), Show (LedgerError a)) ⇒ Show (DualLedgerError m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods showsPrec ∷ Int → DualLedgerError m a → ShowS # show ∷ DualLedgerError m a → String # showList ∷ [DualLedgerError m a] → ShowS # | |
(Eq (LedgerError m), Eq (LedgerError a)) ⇒ Eq (DualLedgerError m a) Source # | |
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 # | |
Defined in Ouroboros.Consensus.Ledger.Dual |
Lifted functions
ctxtDualMain ∷ ∀ m a (f ∷ Type → Type) x. NestedCtxt_ (DualBlock m a) f x → NestedCtxt_ m f x Source #
dualTopLevelConfigMain ∷ TopLevelConfig (DualBlock m a) → TopLevelConfig m Source #
This is only used for block production
Type class family instances
data family BlockConfig blk Source #
Static configuration required to work with this type of blocks
Instances
Isomorphic BlockConfig Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ BlockConfig (HardForkBlock '[blk]) → BlockConfig blk Source # inject ∷ NoHardForks blk ⇒ BlockConfig blk → BlockConfig (HardForkBlock '[blk]) Source # | |
CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (BlockConfig (HardForkBlock xs)) → String Source # | |
NoThunks (BlockConfig (DualBlock m a)) Source # | |
newtype BlockConfig (DisableDiffusionPipelining blk) Source # | |
Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining newtype BlockConfig (DisableDiffusionPipelining blk) = DisableDiffusionPipeliningBlockConfig (BlockConfig blk) | |
newtype BlockConfig (SelectViewDiffusionPipelining blk) Source # | |
Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining newtype BlockConfig (SelectViewDiffusionPipelining blk) = SelectViewDiffusionPipeliningBlockConfig (BlockConfig blk) | |
newtype BlockConfig (HardForkBlock xs) Source # | |
data BlockConfig (DualBlock m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual |
data family CodecConfig blk 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
Isomorphic CodecConfig Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ CodecConfig (HardForkBlock '[blk]) → CodecConfig blk Source # inject ∷ NoHardForks blk ⇒ CodecConfig blk → CodecConfig (HardForkBlock '[blk]) Source # | |||||
Generic (CodecConfig (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods from ∷ CodecConfig (DualBlock m a) → Rep (CodecConfig (DualBlock m a)) x # to ∷ Rep (CodecConfig (DualBlock m a)) x → CodecConfig (DualBlock m a) # | |||||
CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (CodecConfig (HardForkBlock xs)) → String Source # | |||||
(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) Source # | |||||
type Rep (CodecConfig (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.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 # | |||||
data CodecConfig (DualBlock m a) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data CodecConfig (DualBlock m a) = DualCodecConfig {
|
data family GenTx blk 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
Inject GenTx Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → GenTx x → GenTx (HardForkBlock xs) Source # | |||||
Isomorphic GenTx Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ GenTx (HardForkBlock '[blk]) → GenTx blk Source # inject ∷ NoHardForks blk ⇒ GenTx blk → GenTx (HardForkBlock '[blk]) Source # | |||||
Typeable xs ⇒ ShowProxy (GenTx (HardForkBlock xs) ∷ Type) Source # | |||||
(Typeable m, Typeable a) ⇒ ShowProxy (GenTx (DualBlock m a) ∷ Type) Source # | |||||
Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # | |||||
(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) Source # | |||||
Generic (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Associated Types
Methods from ∷ Validated (GenTx (HardForkBlock xs)) → Rep (Validated (GenTx (HardForkBlock xs))) x # to ∷ Rep (Validated (GenTx (HardForkBlock xs))) x → Validated (GenTx (HardForkBlock xs)) # | |||||
Generic (GenTx (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Associated Types
Methods from ∷ GenTx (HardForkBlock xs) → Rep (GenTx (HardForkBlock xs)) x # to ∷ Rep (GenTx (HardForkBlock xs)) x → GenTx (HardForkBlock xs) # | |||||
Generic (TxId (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Associated Types
Methods from ∷ TxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x # to ∷ Rep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) # | |||||
CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) Source # | |||||
CanHardFork xs ⇒ Show (GenTx (HardForkBlock xs)) Source # | |||||
Bridge m a ⇒ Show (GenTx (DualBlock m a)) Source # | |||||
CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # | |||||
Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) Source # | |||||
CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Methods (==) ∷ Validated (GenTx (HardForkBlock xs)) → Validated (GenTx (HardForkBlock xs)) → Bool # (/=) ∷ Validated (GenTx (HardForkBlock xs)) → Validated (GenTx (HardForkBlock xs)) → Bool # | |||||
CanHardFork xs ⇒ Eq (GenTx (HardForkBlock xs)) Source # | |||||
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 # | |||||
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 # | |||||
CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Methods compare ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Ordering # (<) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # (<=) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # (>) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # (>=) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # max ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) # min ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) # | |||||
Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods compare ∷ TxId (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 # max ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # min ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # | |||||
CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # | |||||
NoThunks (Validated (GenTx (DualBlock m a))) Source # | |||||
CanHardFork xs ⇒ NoThunks (GenTx (HardForkBlock xs)) Source # | |||||
NoThunks (GenTx (DualBlock m a)) Source # | |||||
CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # | |||||
NoThunks (TxId (GenTx (DualBlock m a))) Source # | |||||
CanHardFork xs ⇒ HasTxId (GenTx (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Methods txId ∷ GenTx (HardForkBlock xs) → TxId (GenTx (HardForkBlock xs)) Source # | |||||
Bridge m a ⇒ HasTxId (GenTx (DualBlock m a)) Source # | |||||
All CondenseConstraints xs ⇒ Condense (GenTx (HardForkBlock xs)) Source # | |||||
All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # | |||||
SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient Methods encodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → GenTx (HardForkBlock xs) → Encoding Source # decodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → ∀ s. Decoder s (GenTx (HardForkBlock xs)) Source # | |||||
SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient Methods encodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → GenTxId (HardForkBlock xs) → Encoding Source # decodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → ∀ s. Decoder s (GenTxId (HardForkBlock xs)) Source # | |||||
SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode Methods encodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → GenTx (HardForkBlock xs) → Encoding Source # decodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → ∀ s. Decoder s (GenTx (HardForkBlock xs)) Source # | |||||
SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode Methods encodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → GenTxId (HardForkBlock xs) → Encoding Source # decodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → ∀ s. Decoder s (GenTxId (HardForkBlock xs)) Source # | |||||
type Rep (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.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 # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.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 # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.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 # | |||||
data Validated (GenTx (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data Validated (GenTx (DualBlock m a)) = ValidatedDualGenTx {
| |||||
newtype GenTx (HardForkBlock xs) Source # | |||||
newtype TxId (GenTx (HardForkBlock xs)) Source # | |||||
newtype TxId (GenTx (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||
data GenTx (DualBlock m a) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data GenTx (DualBlock m a) = DualGenTx {
|
data family Header blk Source #
Instances
GetHeader1 Header Source # | |
Defined in Ouroboros.Consensus.Block.Abstract Methods getHeader1 ∷ Header blk → Header blk Source # | |
Inject Header Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Header x → Header (HardForkBlock xs) Source # | |
Isomorphic Header Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source # inject ∷ NoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source # | |
CanHardFork xs ⇒ HasNestedContent Header (HardForkBlock xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Block Methods unnest ∷ Header (HardForkBlock xs) → DepPair (NestedCtxt Header (HardForkBlock xs)) Source # nest ∷ DepPair (NestedCtxt Header (HardForkBlock xs)) → Header (HardForkBlock xs) Source # | |
SerialiseHFC xs ⇒ ReconstructNestedCtxt Header (HardForkBlock xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods reconstructPrefixLen ∷ proxy (Header (HardForkBlock xs)) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header (HardForkBlock xs)) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) (HardForkBlock xs) Source # | |
StandardHash blk ⇒ StandardHash (Header blk ∷ Type) Source # | |
Defined in Ouroboros.Consensus.Block.Abstract | |
Typeable xs ⇒ ShowProxy (Header (HardForkBlock xs) ∷ Type) Source # | |
HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) Source # | |
ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods reconstructPrefixLen ∷ proxy (Header (DualBlock m a)) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header (DualBlock m a)) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) (DualBlock m a) Source # | |
CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header ∷ Type → Type) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Block Methods sameDepIndex ∷ NestedCtxt_ (HardForkBlock xs) Header a → NestedCtxt_ (HardForkBlock xs) Header b → Maybe (a :~: b) Source # | |
(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
CanHardFork xs ⇒ Show (Header (HardForkBlock xs)) Source # | |
All (Compose Eq Header) xs ⇒ Eq (Header (HardForkBlock xs)) Source # | |
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 # | |
NoThunks (Header (DualBlock m a)) Source # | |
All CondenseConstraints xs ⇒ Condense (Header (HardForkBlock xs)) Source # | |
CanHardFork xs ⇒ HasHeader (Header (HardForkBlock xs)) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Block Methods getHeaderFields ∷ Header (HardForkBlock xs) → HeaderFields (Header (HardForkBlock xs)) Source # | |
SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (Header (HardForkBlock xs)) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode Methods encodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → Header (HardForkBlock xs) → Encoding Source # decodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → ∀ s. Decoder s (Header (HardForkBlock xs)) Source # | |
SerialiseHFC xs ⇒ DecodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods decodeDiskDep ∷ CodecConfig (HardForkBlock xs) → NestedCtxt Header (HardForkBlock xs) a → ∀ s. Decoder s (ByteString → a) Source # | |
SerialiseHFC xs ⇒ DecodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods decodeDiskDepIx ∷ CodecConfig (HardForkBlock xs) → Decoder s (SomeSecond (NestedCtxt Header) (HardForkBlock xs)) Source # | |
SerialiseHFC xs ⇒ EncodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods encodeDiskDep ∷ CodecConfig (HardForkBlock xs) → NestedCtxt Header (HardForkBlock xs) a → a → Encoding Source # | |
SerialiseHFC xs ⇒ EncodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods encodeDiskDepIx ∷ CodecConfig (HardForkBlock xs) → SomeSecond (NestedCtxt Header) (HardForkBlock xs) → Encoding Source # | |
EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods encodeDiskDep ∷ CodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source # | |
EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods encodeDiskDepIx ∷ CodecConfig (DualBlock m a) → SomeSecond (NestedCtxt Header) (DualBlock m a) → Encoding Source # | |
Show (Header m) ⇒ Show (DualHeader m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods showsPrec ∷ Int → DualHeader m a → ShowS # show ∷ DualHeader m a → String # showList ∷ [DualHeader m a] → ShowS # | |
Bridge m a ⇒ HasHeader (DualHeader m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods getHeaderFields ∷ DualHeader m a → HeaderFields (DualHeader m a) Source # | |
All SingleEraBlock xs ⇒ Show (NestedCtxt_ (HardForkBlock xs) Header a) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Block Methods showsPrec ∷ Int → NestedCtxt_ (HardForkBlock xs) Header a → ShowS # show ∷ NestedCtxt_ (HardForkBlock xs) Header a → String # showList ∷ [NestedCtxt_ (HardForkBlock xs) Header a] → ShowS # | |
type HeaderHash (Header blk ∷ Type) Source # | |
Defined in Ouroboros.Consensus.Block.Abstract | |
type BlockProtocol (Header blk) Source # | |
Defined in Ouroboros.Consensus.Block.Abstract | |
newtype Header (DisableDiffusionPipelining blk) Source # | |
newtype Header (SelectViewDiffusionPipelining blk) Source # | |
Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining newtype Header (SelectViewDiffusionPipelining blk) = SelectViewDiffusionPipeliningHeader (Header blk) | |
newtype Header (HardForkBlock xs) Source # | |
newtype Header (DualBlock m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual |
data family LedgerState blk (mk ∷ MapKind) Source #
Ledger state associated with a block
This is the Consensus notion of a Ledger 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 signal that the
expected instantiation is either a LedgerState
or some wrapper over it
(like the ExtLedgerState
).
This type is parametrized over mk ::
to express the
MapKind
LedgerTables
contained in such a LedgerState
. See LedgerTables
for a
more thorough description.
The main operations we can do with a LedgerState
are ticking (defined in
IsLedger
), and applying a block (defined in
ApplyBlock
).
Instances
CanHardFork xs ⇒ GetTip (LedgerState (HardForkBlock xs)) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (HardForkBlock xs) mk → Point (LedgerState (HardForkBlock xs)) Source # | |||||||||
Bridge m a ⇒ GetTip (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (DualBlock m a) mk → Point (LedgerState (DualBlock m a)) Source # | |||||||||
CanHardFork xs ⇒ IsLedger (LedgerState (HardForkBlock xs)) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (HardForkBlock xs)) → SlotNo → LedgerState (HardForkBlock xs) EmptyMK → LedgerResult (LedgerState (HardForkBlock xs)) (Ticked (LedgerState (HardForkBlock xs)) DiffMK) Source # | |||||||||
Bridge m a ⇒ IsLedger (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → SlotNo → LedgerState (DualBlock m a) EmptyMK → LedgerResult (LedgerState (DualBlock m a)) (Ticked (LedgerState (DualBlock m a)) DiffMK) Source # | |||||||||
All (Compose CanStowLedgerTables LedgerState) xs ⇒ CanStowLedgerTables (LedgerState (HardForkBlock xs)) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods stowLedgerTables ∷ LedgerState (HardForkBlock xs) ValuesMK → LedgerState (HardForkBlock xs) EmptyMK Source # unstowLedgerTables ∷ LedgerState (HardForkBlock xs) EmptyMK → LedgerState (HardForkBlock xs) ValuesMK Source # | |||||||||
CanStowLedgerTables (LedgerState m) ⇒ CanStowLedgerTables (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods stowLedgerTables ∷ LedgerState (DualBlock m a) ValuesMK → LedgerState (DualBlock m a) EmptyMK Source # unstowLedgerTables ∷ LedgerState (DualBlock m a) EmptyMK → LedgerState (DualBlock m a) ValuesMK Source # | |||||||||
(CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ HasLedgerTables (LedgerState (HardForkBlock xs)) Source # | Warning: | ||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (HardForkBlock xs) mk → LedgerTables (LedgerState (HardForkBlock xs)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (HardForkBlock xs) any → LedgerTables (LedgerState (HardForkBlock xs)) mk → LedgerState (HardForkBlock xs) mk Source # | |||||||||
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) mk → LedgerTables (LedgerState (DualBlock m a)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) any → LedgerTables (LedgerState (DualBlock m a)) mk → LedgerState (DualBlock m a) mk Source # | |||||||||
(Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m)), MemPack (TxOut (LedgerState m))) ⇒ SerializeTablesWithHint (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods encodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) → LedgerTables (LedgerState (DualBlock m a)) ValuesMK → Encoding Source # decodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) → Decoder s (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) Source # | |||||||||
(CanHardFork xs, HasHardForkTxOut xs) ⇒ CanUpgradeLedgerTables (LedgerState (HardForkBlock xs)) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (HardForkBlock xs) mk1 → LedgerState (HardForkBlock xs) mk2 → LedgerTables (LedgerState (HardForkBlock xs)) ValuesMK → LedgerTables (LedgerState (HardForkBlock xs)) ValuesMK Source # | |||||||||
CanUpgradeLedgerTables (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (DualBlock m a) mk1 → LedgerState (DualBlock m a) mk2 → LedgerTables (LedgerState (DualBlock m a)) ValuesMK → LedgerTables (LedgerState (DualBlock m a)) ValuesMK Source # | |||||||||
(CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ ApplyBlock (LedgerState (HardForkBlock xs)) (HardForkBlock xs) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState (HardForkBlock xs)) → HardForkBlock xs → Ticked (LedgerState (HardForkBlock xs)) ValuesMK → Except (LedgerErr (LedgerState (HardForkBlock xs))) (LedgerResult (LedgerState (HardForkBlock xs)) (LedgerState (HardForkBlock xs) DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (HardForkBlock xs)) → HardForkBlock xs → Ticked (LedgerState (HardForkBlock xs)) ValuesMK → Except (LedgerErr (LedgerState (HardForkBlock xs))) (LedgerResult (LedgerState (HardForkBlock xs)) (LedgerState (HardForkBlock xs) DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (HardForkBlock xs)) → HardForkBlock xs → Ticked (LedgerState (HardForkBlock xs)) ValuesMK → LedgerResult (LedgerState (HardForkBlock xs)) (LedgerState (HardForkBlock xs) DiffMK) Source # getBlockKeySets ∷ HardForkBlock xs → LedgerTables (LedgerState (HardForkBlock xs)) KeysMK Source # | |||||||||
Bridge m a ⇒ ApplyBlock (LedgerState (DualBlock m a)) (DualBlock m a) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → DualBlock m a → Ticked (LedgerState (DualBlock m a)) ValuesMK → Except (LedgerErr (LedgerState (DualBlock m a))) (LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → DualBlock m a → Ticked (LedgerState (DualBlock m a)) ValuesMK → Except (LedgerErr (LedgerState (DualBlock m a))) (LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → DualBlock m a → Ticked (LedgerState (DualBlock m a)) ValuesMK → LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK) Source # getBlockKeySets ∷ DualBlock m a → LedgerTables (LedgerState (DualBlock m a)) KeysMK Source # | |||||||||
SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods decodeDisk ∷ CodecConfig (HardForkBlock xs) → ∀ s. Decoder s (LedgerState (HardForkBlock xs) EmptyMK) Source # | |||||||||
SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk Methods encodeDisk ∷ CodecConfig (HardForkBlock xs) → LedgerState (HardForkBlock xs) EmptyMK → Encoding Source # | |||||||||
(ShowMK mk, CanHardFork xs) ⇒ Show (LedgerState (HardForkBlock xs) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods showsPrec ∷ Int → LedgerState (HardForkBlock xs) mk → ShowS # show ∷ LedgerState (HardForkBlock xs) mk → String # showList ∷ [LedgerState (HardForkBlock xs) mk] → ShowS # | |||||||||
(Bridge m a, ShowMK mk) ⇒ Show (LedgerState (DualBlock m a) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
(EqMK mk, CanHardFork xs) ⇒ Eq (LedgerState (HardForkBlock xs) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods (==) ∷ LedgerState (HardForkBlock xs) mk → LedgerState (HardForkBlock xs) mk → Bool # (/=) ∷ LedgerState (HardForkBlock xs) mk → LedgerState (HardForkBlock xs) mk → Bool # | |||||||||
(Bridge m a, EqMK mk) ⇒ Eq (LedgerState (DualBlock m a) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods (==) ∷ LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool # (/=) ∷ LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool # | |||||||||
(NoThunksMK mk, CanHardFork xs) ⇒ NoThunks (LedgerState (HardForkBlock xs) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → LedgerState (HardForkBlock xs) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → LedgerState (HardForkBlock xs) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (LedgerState (HardForkBlock xs) mk) → String Source # | |||||||||
NoThunks (LedgerState (DualBlock m a) mk) Source # | |||||||||
CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (HardForkBlock xs)) mk → Point (Ticked (LedgerState (HardForkBlock xs))) Source # | |||||||||
Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
(CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ HasLedgerTables (Ticked (LedgerState (HardForkBlock xs))) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (HardForkBlock xs)) mk → LedgerTables (Ticked (LedgerState (HardForkBlock xs))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (HardForkBlock xs)) any → LedgerTables (Ticked (LedgerState (HardForkBlock xs))) mk → Ticked (LedgerState (HardForkBlock xs)) mk Source # | |||||||||
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) mk → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) any → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk → Ticked (LedgerState (DualBlock m a)) mk Source # | |||||||||
(txout ~ TxOut (LedgerState m), IndexedMemPack (LedgerState m EmptyMK) txout) ⇒ IndexedMemPack (LedgerState (DualBlock m a) EmptyMK) txout Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods indexedPackedByteCount ∷ LedgerState (DualBlock m a) EmptyMK → txout → Int Source # indexedPackM ∷ LedgerState (DualBlock m a) EmptyMK → txout → Pack s () Source # indexedUnpackM ∷ Buffer b ⇒ LedgerState (DualBlock m a) EmptyMK → Unpack b txout Source # indexedTypeName ∷ LedgerState (DualBlock m a) EmptyMK → String Source # | |||||||||
StandardHash blk ⇒ StandardHash (LedgerState blk ∷ MapKind → Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||||||
NoThunks (Ticked (LedgerState (DualBlock m a)) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
Inject (Flip LedgerState mk) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Flip LedgerState mk x → Flip LedgerState mk (HardForkBlock xs) Source # | |||||||||
Isomorphic (Flip LedgerState mk) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ Flip LedgerState mk (HardForkBlock '[blk]) → Flip LedgerState mk blk Source # inject ∷ NoHardForks blk ⇒ Flip LedgerState mk blk → Flip LedgerState mk (HardForkBlock '[blk]) Source # | |||||||||
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) Source # | |||||||||
type AuxLedgerEvent (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerCfg (LedgerState (HardForkBlock xs)) Source # | |||||||||
type LedgerCfg (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerErr (LedgerState (HardForkBlock xs)) Source # | |||||||||
type LedgerErr (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
newtype LedgerState (HardForkBlock xs) mk Source # | |||||||||
type TxIn (LedgerState (HardForkBlock xs)) Source # | Must be the | ||||||||
type TxIn (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type TxOut (LedgerState (HardForkBlock xs)) Source # | Must be the | ||||||||
type TxOut (LedgerState (DualBlock m a)) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
data LedgerState (DualBlock m a) mk Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) = TickedHardForkLedgerState {} | |||||||||
data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) = TickedDualLedgerState {} | |||||||||
type HeaderHash (LedgerState blk ∷ MapKind → Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics |
newtype LedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) Source #
The Ledger Tables represent the portion of the data on disk that has been pulled from disk and attached to the in-memory Ledger State or that will eventually be written to disk.
With UTxO-HD and the split of the Ledger ledger state into the in-memory
part and the on-disk part, this splitting was reflected in the new type
parameter added to the (Consensus)
LedgerState
, to which we refer as "the
MapKind" or mk
.
Every LedgerState
(or LedgerState
-like
type, such as the ExtLedgerState
) is
associated with a LedgerTables
and they both share the mk
. They both are
of kind LedgerStateKind
. LedgerTables
is just a way to refer only to a
partial view of the on-disk data without having the rest of the in-memory
LedgerState
in scope.
The mk
can be instantiated to anything that is map-like, i.e. that expects
two type parameters, the key and the value.
Constructors
LedgerTables | |
Fields
|
Instances
(Ord (TxIn l), Eq (TxOut l), Show (TxIn l), Show (TxOut l), NoThunks (TxIn l), NoThunks (TxOut l), MemPack (TxIn l), IndexedMemPack (MemPackIdx l EmptyMK) (TxOut l)) ⇒ HasLedgerTables (LedgerTables l) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l mk → LedgerTables (LedgerTables l) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l any → LedgerTables (LedgerTables l) mk → LedgerTables l mk Source # | |||||
(∀ k v. LedgerTableConstraints' l k v ⇒ Monoid (mk k v), LedgerTableConstraints l) ⇒ Monoid (LedgerTables l mk) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Combinators Methods mempty ∷ LedgerTables l mk # mappend ∷ LedgerTables l mk → LedgerTables l mk → LedgerTables l mk # mconcat ∷ [LedgerTables l mk] → LedgerTables l mk # | |||||
(∀ k v. LedgerTableConstraints' l k v ⇒ Semigroup (mk k v), LedgerTableConstraints l) ⇒ Semigroup (LedgerTables l mk) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Combinators Methods (<>) ∷ LedgerTables l mk → LedgerTables l mk → LedgerTables l mk # sconcat ∷ NonEmpty (LedgerTables l mk) → LedgerTables l mk # stimes ∷ Integral b ⇒ b → LedgerTables l mk → LedgerTables l mk # | |||||
Generic (LedgerTables l mk) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics Associated Types
Methods from ∷ LedgerTables l mk → Rep (LedgerTables l mk) x # to ∷ Rep (LedgerTables l mk) x → LedgerTables l mk # | |||||
Show (mk (TxIn l) (TxOut l)) ⇒ Show (LedgerTables l mk) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics Methods showsPrec ∷ Int → LedgerTables l mk → ShowS # show ∷ LedgerTables l mk → String # showList ∷ [LedgerTables l mk] → ShowS # | |||||
Eq (mk (TxIn l) (TxOut l)) ⇒ Eq (LedgerTables l mk) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics Methods (==) ∷ LedgerTables l mk → LedgerTables l mk → Bool # (/=) ∷ LedgerTables l mk → LedgerTables l mk → Bool # | |||||
NoThunks (mk (TxIn l) (TxOut l)) ⇒ NoThunks (LedgerTables l mk) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
type TxIn (LedgerTables l) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
type TxOut (LedgerTables l) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
type Rep (LedgerTables l mk) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "LedgerTables" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mk (TxIn l) (TxOut l))))) | |||||
type SerializeTablesHint (LedgerTables l ValuesMK) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Tables | |||||
type InitHint (LedgerTables l ValuesMK) Source # | |||||
type ReadHint (LedgerTables l ValuesMK) Source # | |||||
type WriteHint (LedgerTables l DiffMK) Source # | |||||
data family NestedCtxt_ blk ∷ (Type → Type) → Type → Type Source #
Context identifying what kind of block we have
In almost all places we will use NestedCtxt
rather than NestedCtxt_
.
Instances
CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header ∷ Type → Type) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Block Methods sameDepIndex ∷ NestedCtxt_ (HardForkBlock xs) Header a → NestedCtxt_ (HardForkBlock xs) Header b → Maybe (a :~: b) Source # | |
SameDepIndex (NestedCtxt_ m f) ⇒ SameDepIndex (NestedCtxt_ (DualBlock m a) f ∷ Type → Type) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods sameDepIndex ∷ NestedCtxt_ (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 # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Block Methods showsPrec ∷ Int → NestedCtxt_ (HardForkBlock xs) Header a → ShowS # show ∷ NestedCtxt_ (HardForkBlock xs) Header a → String # showList ∷ [NestedCtxt_ (HardForkBlock xs) Header a] → ShowS # | |
Show (NestedCtxt_ m f x) ⇒ Show (NestedCtxt_ (DualBlock m a) f x) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
data NestedCtxt_ (HardForkBlock xs) a b Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Block data NestedCtxt_ (HardForkBlock xs) a b where
| |
newtype NestedCtxt_ (DualBlock m a) f x Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual newtype NestedCtxt_ (DualBlock m a) f x where
|
data family StorageConfig blk Source #
Config needed for the
NodeInitStorage
class. Defined here to
avoid circular dependencies.
Instances
Isomorphic StorageConfig Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ StorageConfig (HardForkBlock '[blk]) → StorageConfig blk Source # inject ∷ NoHardForks blk ⇒ StorageConfig blk → StorageConfig (HardForkBlock '[blk]) Source # | |||||
Generic (StorageConfig (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods from ∷ StorageConfig (DualBlock m a) → Rep (StorageConfig (DualBlock m a)) x # to ∷ Rep (StorageConfig (DualBlock m a)) x → StorageConfig (DualBlock m a) # | |||||
CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (StorageConfig (HardForkBlock xs)) → String Source # | |||||
(NoThunks (StorageConfig m), NoThunks (StorageConfig a)) ⇒ NoThunks (StorageConfig (DualBlock m a)) Source # | |||||
type Rep (StorageConfig (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.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 # | |||||
data StorageConfig (DualBlock m a) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual |
data family Ticked (st ∷ k) ∷ k 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
must equal
forecastFor
(ledgerViewForecastAt
cfg st)
slot
. Thus a
protocolLedgerView
cfg
(applyChainTick
cfg slot st)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
Show (Ticked ()) Source # | |
CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (HardForkBlock xs)) mk → Point (Ticked (LedgerState (HardForkBlock xs))) Source # | |
Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) Source # | |
Defined in Ouroboros.Consensus.Ledger.Extended Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (ExtLedgerState blk) mk → Point (Ticked (ExtLedgerState blk)) Source # | |
(CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ HasLedgerTables (Ticked (LedgerState (HardForkBlock xs))) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (HardForkBlock xs)) mk → LedgerTables (Ticked (LedgerState (HardForkBlock xs))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (HardForkBlock xs)) any → LedgerTables (Ticked (LedgerState (HardForkBlock xs))) mk → Ticked (LedgerState (HardForkBlock xs)) mk Source # | |
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) mk → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) any → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk → Ticked (LedgerState (DualBlock m a)) mk Source # | |
(HasLedgerTables (Ticked (LedgerState blk)), NoThunks (TxOut (LedgerState blk)), NoThunks (TxIn (LedgerState blk)), Show (TxOut (LedgerState blk)), Show (TxIn (LedgerState blk)), Eq (TxOut (LedgerState blk)), Ord (TxIn (LedgerState blk)), MemPack (TxIn (LedgerState blk))) ⇒ HasLedgerTables (Ticked (ExtLedgerState blk)) Source # | |
Defined in Ouroboros.Consensus.Ledger.Extended Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) mk → LedgerTables (Ticked (ExtLedgerState blk)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) any → LedgerTables (Ticked (ExtLedgerState blk)) mk → Ticked (ExtLedgerState blk) mk Source # | |
LedgerTablesAreTrivial (Ticked (LedgerState blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) Source # | |
Defined in Ouroboros.Consensus.Ledger.Extended Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (ExtLedgerState blk) mk → Ticked (ExtLedgerState blk) mk' Source # | |
NoThunks (Ticked (LedgerState (DualBlock m a)) mk) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
Show (Ticked (f a)) ⇒ Show (((Ticked ∷ Type → Type) :.: f) a) Source # | |
NoThunks (Ticked (f a)) ⇒ NoThunks (((Ticked ∷ Type → Type) :.: f) a) Source # | |
data Ticked () Source # | |
Defined in Ouroboros.Consensus.Ticked | |
data Ticked (HardForkChainDepState xs ∷ Type) Source # | |
data Ticked (HeaderState blk ∷ Type) Source # | |
Defined in Ouroboros.Consensus.HeaderValidation | |
data Ticked (PBftState c ∷ Type) Source # | |
Defined in Ouroboros.Consensus.Protocol.PBFT | |
newtype Ticked (WrapChainDepState blk ∷ Type) Source # | |
Defined in Ouroboros.Consensus.TypeFamilyWrappers | |
type HeaderHash (Ticked l ∷ k) Source # | |
Defined in Ouroboros.Consensus.Ticked | |
type TxIn (Ticked l) Source # | |
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |
type TxOut (Ticked l) Source # | |
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) = TickedHardForkLedgerState {} | |
data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) = TickedDualLedgerState {} | |
data Ticked (ExtLedgerState blk ∷ MapKind → Type) (mk ∷ MapKind) Source # | |
Defined in Ouroboros.Consensus.Ledger.Extended data Ticked (ExtLedgerState blk ∷ MapKind → Type) (mk ∷ MapKind) = TickedExtLedgerState {
|
A generalized transaction, GenTx
, identifier.
Instances
Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # | |||||
(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) Source # | |||||
Generic (TxId (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Associated Types
Methods from ∷ TxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x # to ∷ Rep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) # | |||||
CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # | |||||
Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) Source # | |||||
CanHardFork xs ⇒ Eq (TxId (GenTx (HardForkBlock xs))) Source # | |||||
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 # | |||||
CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Methods compare ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Ordering # (<) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # (<=) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # (>) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # (>=) ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool # max ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) # min ∷ TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) # | |||||
Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods compare ∷ TxId (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 # max ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # min ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # | |||||
CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # | |||||
NoThunks (TxId (GenTx (DualBlock m a))) Source # | |||||
All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # | |||||
SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient Methods encodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → GenTxId (HardForkBlock xs) → Encoding Source # decodeNodeToClient ∷ CodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → ∀ s. Decoder s (GenTxId (HardForkBlock xs)) Source # | |||||
SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode Methods encodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → GenTxId (HardForkBlock xs) → Encoding Source # decodeNodeToNode ∷ CodecConfig (HardForkBlock xs) → BlockNodeToNodeVersion (HardForkBlock xs) → ∀ s. Decoder s (GenTxId (HardForkBlock xs)) Source # | |||||
type Rep (TxId (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.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 # | |||||
newtype TxId (GenTx (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual |
data family Validated x 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
Generic (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Associated Types
Methods from ∷ Validated (GenTx (HardForkBlock xs)) → Rep (Validated (GenTx (HardForkBlock xs))) x # to ∷ Rep (Validated (GenTx (HardForkBlock xs))) x → Validated (GenTx (HardForkBlock xs)) # | |||||
CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) Source # | |||||
CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool Methods (==) ∷ Validated (GenTx (HardForkBlock xs)) → Validated (GenTx (HardForkBlock xs)) → Bool # (/=) ∷ Validated (GenTx (HardForkBlock xs)) → Validated (GenTx (HardForkBlock xs)) → Bool # | |||||
CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # | |||||
NoThunks (Validated (GenTx (DualBlock m a))) Source # | |||||
type Rep (Validated (GenTx (HardForkBlock xs))) Source # | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.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 # | |||||
data Validated (GenTx (DualBlock m a)) Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data Validated (GenTx (DualBlock m a)) = ValidatedDualGenTx {
|
Serialisation
decodeDualBlock ∷ (Bridge m a, Serialise a) ⇒ Decoder s (ByteString → m) → Decoder s (ByteString → DualBlock m a) Source #
decodeDualGenTx ∷ (Bridge m a, Serialise (GenTx a)) ⇒ Decoder s (GenTx m) → Decoder s (GenTx (DualBlock m a)) Source #
decodeDualGenTxErr ∷ Serialise (ApplyTxErr a) ⇒ Decoder s (ApplyTxErr m) → Decoder s (ApplyTxErr (DualBlock m a)) Source #
decodeDualHeader ∷ Decoder s (ByteString → Header m) → Decoder s (ByteString → Header (DualBlock m a)) Source #
decodeDualLedgerConfig ∷ Decoder s (LedgerCfg (LedgerState m)) → Decoder s (LedgerCfg (LedgerState a)) → Decoder s (DualLedgerConfig m a) Source #
decodeDualLedgerState ∷ ∀ m a s (mk ∷ MapKind). (Bridge m a, Serialise (LedgerState a ValuesMK)) ⇒ Decoder s (LedgerState m mk) → Decoder s (LedgerState (DualBlock m a) mk) Source #
encodeDualGenTx ∷ (Bridge m a, Serialise (GenTx a)) ⇒ (GenTx m → Encoding) → GenTx (DualBlock m a) → Encoding Source #
encodeDualGenTxErr ∷ Serialise (ApplyTxErr a) ⇒ (ApplyTxErr m → Encoding) → ApplyTxErr (DualBlock m a) → Encoding Source #
encodeDualLedgerConfig ∷ (LedgerCfg (LedgerState m) → Encoding) → (LedgerCfg (LedgerState a) → Encoding) → DualLedgerConfig m a → Encoding Source #
encodeDualLedgerState ∷ ∀ m a (mk ∷ MapKind). (Bridge m a, Serialise (LedgerState a ValuesMK)) ⇒ (LedgerState m mk → Encoding) → LedgerState (DualBlock m a) mk → Encoding Source #