Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.Ledger.Tables
Description
This module defines the LedgerTables
, a portion of the Ledger notion of a
ledger state (not to confuse with our
LedgerState
) that together with it,
conforms a complete Ledger ledger state.
LedgerTables
are parametrized by two types: keys and values. For now, their
only current instantiation is to hold the UTxO set, but future features will
extend this to hold other parts of the ledger state that now live in memory.
However, LedgerTables
don't necessarily have to contain maps from keys to
values, and the particular instantiation might choose to ignore some of those
types (as phantom types). See KeysMK
for an example.
This type is used for two main purposes. Firstly, we use ledger tables to extract data from the ledger state and store it on secondary storage (eg a solid-state hard-drive). Secondly, when we load data from disk onto memory, we use ledger tables to inject data into the ledger state. This mechanism allows us to keep most of the data on disk, which is rarely used, reducing the memory usage of the Consensus layer.
Example
As an example, consider a LedgerState that contains a Ledger ledger state
(such as the NewEpochState
) and a UTxO set:
data instanceLedgerState
(Block era) mk = LedgerState { theLedgerLedgerState :: NewEpochState era , theTables ::LedgerTables
(Block era) mk }
The Ledger ledger state contains a UTxO set as well, and with
stowLedgerTables
and unstowLedgerTables
we move those between the Ledger
ledger state and the LedgerTables
, for example:
unstowLedgerTables
(LedgerState { theLedgerLedgerState = NewEpochState { ... , utxoSet = Map.fromList [('a', 100), ('b', 100), ...] } , theTables =EmptyMK
}) == LedgerState { theLedgerLedgerState = NewEpochState { ... , utxoSet = Map.empty } , theTables =ValuesMK
(Map.fromList [('a', 100), ('b', 100), ...]) })
stowLedgerTables
(LedgerState { theLedgerLedgerState = NewEpochState { ... , utxoSet = Map.empty } , theTables =ValuesMK
(Map.fromList [('a', 100), ('b', 100), ...]) }) == LedgerState { theLedgerLedgerState = NewEpochState { ... , utxoSet = Map.fromList [('a', 100), ('b', 100), ...] } , theTables =EmptyMK
})
Using these functions we can extract the data from the Ledger ledger state for us Consensus to manipulate, and we can then inject it back so that we provide the expected data to the ledger. Note that the Ledger rules for applying a block are defined in a way that it only needs the subset of the UTxO set that the block being applied will consume.
Now using calculateDifference
, we
can compare two (successive) LedgerState
s
to produce differences:
calculateDifference
(LedgerState { ... , theTables =ValuesMK
(Map.fromList [('a', 100), ('b', 100)]) }) (LedgerState { ... , theTables =ValuesMK
(Map.fromList [('a', 100), ('c', 200)]) }) ==TrackingMK
(Map.fromList [('a', 100), ('c', 200)]) (Map.fromList [('b', Delete), ('c', Insert 200)])
This operation provided a TrackingMK
which is in fact just a ValuesMK
and
DiffMK
put together.
We can then use those differences to forward a collection of values, so for example (taking the example above):
let tables1 =ValuesMK
(Map.fromList [('a', 100), ('b', 100)]) tables2 =ValuesMK
(Map.fromList [('a', 100), ('c', 200)]) diffs =rawForgetTrackingValues
$rawCalculateDifference
tables1 tables2 inrawApplyDiffs
tables1 diffs == tables2
Note: we usually don't call the raw*
methods directly but instead call the
corresponding function that operates on
LedgerState
s. See
Ouroboros.Consensus.Ledger.Tables.Utils.
Also when applying a block that contains some transactions, we can produce
LedgerTable
s of KeysMK
, by gathering the txins required by the
transactions:
getBlockKeySets
(Block {..., txs = [Tx { input = ['a', 'b'], outputs = ['c', 'd'] }]}) ==KeysMK
(Set.fromList ['a', 'b'])
We shall use those later on to read the txouts from some storage.
We call those types ending in "MK" mapkinds. They model the different types of collections and contained data in the tables. This example already covered most of the standard mapkinds, in particular:
Synopsis
- module Ouroboros.Consensus.Ledger.Tables.Basics
- module Ouroboros.Consensus.Ledger.Tables.MapKind
- module Ouroboros.Consensus.Ledger.Tables.Combinators
- class CanStowLedgerTables (l ∷ LedgerStateKind) where
- stowLedgerTables ∷ l ValuesMK → l EmptyMK
- unstowLedgerTables ∷ l EmptyMK → l ValuesMK
- class (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 (l ∷ LedgerStateKind) where
- projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ l mk → LedgerTables l mk
- withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ l any → LedgerTables l mk → l mk
- class HasLedgerTables (Ticked l) ⇒ HasTickedLedgerTables (l ∷ LedgerStateKind)
- type family SerializeTablesHint values
- class SerializeTablesWithHint (l ∷ LedgerStateKind) where
- defaultDecodeTablesWithHint ∷ ∀ (l ∷ LedgerStateKind) s. (Ord (TxIn l), MemPack (TxIn l), MemPack (TxOut l)) ⇒ SerializeTablesHint (LedgerTables l ValuesMK) → Decoder s (LedgerTables l ValuesMK)
- defaultEncodeTablesWithHint ∷ ∀ (l ∷ LedgerStateKind). (MemPack (TxIn l), MemPack (TxOut l)) ⇒ SerializeTablesHint (LedgerTables l ValuesMK) → LedgerTables l ValuesMK → Encoding
- valuesMKDecoder ∷ SerializeTablesWithHint l ⇒ l EmptyMK → Decoder s (LedgerTables l ValuesMK)
- valuesMKEncoder ∷ SerializeTablesWithHint l ⇒ l EmptyMK → LedgerTables l ValuesMK → Encoding
- class (TxIn l ~ Void, TxOut l ~ Void) ⇒ LedgerTablesAreTrivial (l ∷ LedgerStateKind)
- newtype TrivialLedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) = TrivialLedgerTables {
- untrivialLedgerTables ∷ l mk
- convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerTablesAreTrivial l ⇒ l mk → l mk'
- trivialLedgerTables ∷ ∀ (mk ∷ MapKind) (l ∷ LedgerStateKind). (ZeroableMK mk, LedgerTablesAreTrivial l) ⇒ LedgerTables l mk
Core
Utilities
Basic LedgerState classes
Stowing ledger tables
class CanStowLedgerTables (l ∷ LedgerStateKind) where Source #
LedgerTables are projections of data from a LedgerState and as such they can be injected back into a LedgerState. This is necessary because the Ledger rules are currently unaware of UTxO-HD changes. Thus, by stowing the ledger tables, we are able to provide a Ledger State with a restricted UTxO set that is enough to execute the Ledger rules.
In particular, HardForkBlock LedgerStates are never given diretly to the ledger but rather unwrapped and then it is the inner ledger state the one we give to the ledger. This means that all the single era blocks must be an instance of this class, but HardForkBlocks might avoid doing so.
Methods
stowLedgerTables ∷ l ValuesMK → l EmptyMK Source #
unstowLedgerTables ∷ l EmptyMK → l ValuesMK Source #
Instances
Extracting and injecting ledger tables
class (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 (l ∷ LedgerStateKind) where Source #
Extracting
from LedgerTables
l mk
(which will share the same mk
),
or replacing the
associated to a particular LedgerTables
l
.
Methods
projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ l mk → LedgerTables l mk Source #
Extract the ledger tables from a ledger state
The constraints on mk
are necessary because the CardanoBlock
instance
uses them.
withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ l any → LedgerTables l mk → l mk Source #
Overwrite the tables in the given ledger state.
The contents of the tables should not be younger than the content of the
ledger state. In particular, for a
HardForkBlock
ledger, the
tables argument should not contain any data from eras that succeed the
current era of the ledger state argument.
The constraints on mk
are necessary because the CardanoBlock
instance
uses them.
Instances
class HasLedgerTables (Ticked l) ⇒ HasTickedLedgerTables (l ∷ LedgerStateKind) Source #
Convenience class, useful for partially applying the composition of
HasLedgerTables
and Ticked
.
Instances
HasLedgerTables (Ticked l) ⇒ HasTickedLedgerTables l Source # | |
Defined in Ouroboros.Consensus.Ledger.Tables |
Serialization
type family SerializeTablesHint values Source #
The hint for SerializeTablesWithHint
Instances
type SerializeTablesHint (LedgerTables l ValuesMK) Source # | |
Defined in Ouroboros.Consensus.Ledger.Tables |
class SerializeTablesWithHint (l ∷ LedgerStateKind) where Source #
When decoding the tables and in particular the UTxO set we want
to share data in the TxOuts in the same way the Ledger did (see the
Share (TxOut era)
instances). We need to provide the state in the
HFC case so that we can call eraDecoder
and also to extract the
interns from the state.
As we will decode with eraDecoder
we also need to use such era
for the encoding thus we need the hint also in the encoding.
See SerializeTablesWithHint (LedgerState (HardForkBlock
(CardanoBlock c)))
for a good example, the rest of the instances
are somewhat degenerate.
Methods
encodeTablesWithHint ∷ SerializeTablesHint (LedgerTables l ValuesMK) → LedgerTables l ValuesMK → Encoding Source #
decodeTablesWithHint ∷ SerializeTablesHint (LedgerTables l ValuesMK) → Decoder s (LedgerTables l ValuesMK) Source #
Instances
defaultDecodeTablesWithHint ∷ ∀ (l ∷ LedgerStateKind) s. (Ord (TxIn l), MemPack (TxIn l), MemPack (TxOut l)) ⇒ SerializeTablesHint (LedgerTables l ValuesMK) → Decoder s (LedgerTables l ValuesMK) Source #
defaultEncodeTablesWithHint ∷ ∀ (l ∷ LedgerStateKind). (MemPack (TxIn l), MemPack (TxOut l)) ⇒ SerializeTablesHint (LedgerTables l ValuesMK) → LedgerTables l ValuesMK → Encoding Source #
valuesMKDecoder ∷ SerializeTablesWithHint l ⇒ l EmptyMK → Decoder s (LedgerTables l ValuesMK) Source #
Default decoder of
to be used by the
in-memory backing store.LedgerTables
l 'ValuesMK
valuesMKEncoder ∷ SerializeTablesWithHint l ⇒ l EmptyMK → LedgerTables l ValuesMK → Encoding Source #
Default encoder of
to be used by the
in-memory backing store.LedgerTables
l 'ValuesMK
Special classes
class (TxIn l ~ Void, TxOut l ~ Void) ⇒ LedgerTablesAreTrivial (l ∷ LedgerStateKind) Source #
For some ledger states we won't be defining LedgerTables
and instead the
ledger state will be fully stored in memory, as before UTxO-HD. The ledger
states that are defined this way can be made instances of this class which
allows for easy manipulation of the types of mk
required at any step of the
program.
Minimal complete definition
Instances
LedgerTablesAreTrivial (LedgerState blk) ⇒ LedgerTablesAreTrivial (ExtLedgerState blk) Source # | |
Defined in Ouroboros.Consensus.Ledger.Extended Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). ExtLedgerState blk mk → ExtLedgerState blk mk' Source # | |
LedgerTablesAreTrivial l ⇒ LedgerTablesAreTrivial (TrivialLedgerTables l) Source # | |
Defined in Ouroboros.Consensus.Ledger.Tables Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). TrivialLedgerTables l mk → TrivialLedgerTables l 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 # |
newtype TrivialLedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) Source #
A newtype to derive via
the instances for blocks with trivial ledger
tables.
Constructors
TrivialLedgerTables | |
Fields
|
Instances
convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerTablesAreTrivial l ⇒ l mk → l mk' Source #
If the ledger state is always in memory, then l mk
will be isomorphic
to l mk'
for all mk
, mk'
. As a result, we can convert between ledgers
states indexed by different map kinds.
This function is useful to combine functions that operate on functions that
transform the map kind on a ledger state (eg applyChainTickLedgerResult
).
trivialLedgerTables ∷ ∀ (mk ∷ MapKind) (l ∷ LedgerStateKind). (ZeroableMK mk, LedgerTablesAreTrivial l) ⇒ LedgerTables l mk Source #