Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.Ledger.Basics
Description
Definition is IsLedger
Normally this is imported from Ouroboros.Consensus.Ledger.Abstract. We pull this out to avoid circular module dependencies.
Synopsis
- type family LedgerCfg (l ∷ LedgerStateKind)
- data family LedgerState blk (mk ∷ MapKind)
- type TickedLedgerState blk = Ticked (LedgerState blk)
- data ComputeLedgerEvents
- class (∀ (mk ∷ MapKind). EqMK mk ⇒ Eq (l mk), ∀ (mk ∷ MapKind). NoThunksMK mk ⇒ NoThunks (l mk), ∀ (mk ∷ MapKind). ShowMK mk ⇒ Show (l mk), NoThunks (LedgerCfg l), Show (LedgerErr l), Eq (LedgerErr l), NoThunks (LedgerErr l), GetTip l, GetTip (Ticked l)) ⇒ IsLedger (l ∷ LedgerStateKind) where
- type LedgerErr (l ∷ LedgerStateKind)
- type AuxLedgerEvent (l ∷ LedgerStateKind)
- applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg l → SlotNo → l EmptyMK → LedgerResult l (Ticked l DiffMK)
- applyChainTick ∷ IsLedger l ⇒ ComputeLedgerEvents → LedgerCfg l → SlotNo → l EmptyMK → Ticked l DiffMK
- data LedgerResult (l ∷ LedgerStateKind) a = LedgerResult {
- lrEvents ∷ [AuxLedgerEvent l]
- lrResult ∷ !a
- data VoidLedgerEvent (l ∷ LedgerStateKind)
- castLedgerResult ∷ ∀ (l ∷ LedgerStateKind) (l' ∷ LedgerStateKind) a. AuxLedgerEvent l ~ AuxLedgerEvent l' ⇒ LedgerResult l a → LedgerResult l' a
- embedLedgerResult ∷ ∀ (l ∷ LedgerStateKind) (l' ∷ LedgerStateKind) a. (AuxLedgerEvent l → AuxLedgerEvent l') → LedgerResult l a → LedgerResult l' a
- pureLedgerResult ∷ ∀ a (l ∷ LedgerStateKind). a → LedgerResult l a
- class GetTip (l ∷ LedgerStateKind) where
- class GetTipSTM (m ∷ Type → Type) l where
- getTipHash ∷ ∀ l (mk ∷ MapKind). GetTip l ⇒ l mk → ChainHash l
- getTipM ∷ (GetTipSTM m l, MonadSTM m) ⇒ l → m (Point l)
- getTipSlot ∷ ∀ l (mk ∷ MapKind). GetTip l ⇒ l mk → WithOrigin SlotNo
- type LedgerConfig blk = LedgerCfg (LedgerState blk)
- type LedgerError blk = LedgerErr (LedgerState blk)
- module Ouroboros.Consensus.Ledger.Tables
The LedgerState
definition
type family LedgerCfg (l ∷ LedgerStateKind) Source #
Static environment required for the ledger
Types that inhabit this family will come from the Ledger code.
Instances
type LedgerCfg (LedgerState (HardForkBlock xs)) Source # | |
type LedgerCfg (LedgerState (DualBlock m a)) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
type LedgerCfg (ExtLedgerState blk) Source # | |
Defined in Ouroboros.Consensus.Ledger.Extended |
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
type TickedLedgerState blk = Ticked (LedgerState blk) Source #
Definition of a ledger independent of a choice of block
data ComputeLedgerEvents Source #
Whether we tell the ledger layer to compute ledger events
At the moment events are not emitted in any case in the consensus layer (i.e. there is no handler for those events, nor are they traced), so they are not really forced, we always discard them. This behavior does not incur big costs thanks to laziness.
By passing OmitLedgerEvents
we tell the Ledger layer to not even
allocate thunks for those events, as we explicitly don't want them.
Constructors
ComputeLedgerEvents | |
OmitLedgerEvents |
Instances
Generic ComputeLedgerEvents Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Basics Associated Types
Methods | |||||
Show ComputeLedgerEvents Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Basics Methods showsPrec ∷ Int → ComputeLedgerEvents → ShowS # show ∷ ComputeLedgerEvents → String # showList ∷ [ComputeLedgerEvents] → ShowS # | |||||
Eq ComputeLedgerEvents Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Basics Methods | |||||
NoThunks ComputeLedgerEvents Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||
type Rep ComputeLedgerEvents Source # | |||||
Defined in Ouroboros.Consensus.Ledger.Basics |
class (∀ (mk ∷ MapKind). EqMK mk ⇒ Eq (l mk), ∀ (mk ∷ MapKind). NoThunksMK mk ⇒ NoThunks (l mk), ∀ (mk ∷ MapKind). ShowMK mk ⇒ Show (l mk), NoThunks (LedgerCfg l), Show (LedgerErr l), Eq (LedgerErr l), NoThunks (LedgerErr l), GetTip l, GetTip (Ticked l)) ⇒ IsLedger (l ∷ LedgerStateKind) where Source #
Associated Types
type LedgerErr (l ∷ LedgerStateKind) Source #
Errors that can arise when updating the ledger
This is defined here rather than in ApplyBlock
, since the type of
these errors does not depend on the type of the block.
type AuxLedgerEvent (l ∷ LedgerStateKind) Source #
Event emitted by the ledger
TODO we call this AuxLedgerEvent
to differentiate from LedgerEvent
in
InspectLedger
. When that module is rewritten to make use of ledger
derived events, we may rename this type.
Methods
applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg l → SlotNo → l EmptyMK → LedgerResult l (Ticked l DiffMK) Source #
Apply "slot based" state transformations
When a block is applied to the ledger state, a number of things happen purely based on the slot number of that block. For example:
- In Byron, scheduled updates are applied, and the update system state is updated.
- In Shelley, delegation state is updated (on epoch boundaries).
The consensus layer must be able to apply such a "chain tick" function, primarily when validating transactions in the mempool (which, conceptually, live in "some block in the future") or when extracting valid transactions from the mempool to insert into a new block to be produced.
This is not allowed to throw any errors. After all, if this could fail, it would mean a previous block set up the ledger state in such a way that as soon as a certain slot was reached, any block would be invalid.
Ticking a ledger state may not use any data from the LedgerTables
,
however it might produce differences in the tables, in particular because
era transitions happen when ticking a ledger state.
PRECONDITION: The slot number must be strictly greater than the slot at the tip of the ledger (except for EBBs, obviously..).
NOTE: applyChainTickLedgerResult
should not change the tip of the
underlying ledger state, which should still refer to the most recent
applied block. In other words, we should have:
ledgerTipPoint (applyChainTick cfg slot st) == ledgerTipPoint st
Instances
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 # | |||||||||
LedgerSupportsProtocol blk ⇒ IsLedger (ExtLedgerState blk) Source # | |||||||||
Defined in Ouroboros.Consensus.Ledger.Extended Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (ExtLedgerState blk) → SlotNo → ExtLedgerState blk EmptyMK → LedgerResult (ExtLedgerState blk) (Ticked (ExtLedgerState blk) DiffMK) Source # |
applyChainTick ∷ IsLedger l ⇒ ComputeLedgerEvents → LedgerCfg l → SlotNo → l EmptyMK → Ticked l DiffMK Source #
Ledger Events
data LedgerResult (l ∷ LedgerStateKind) a Source #
The result of invoke a ledger function that does validation
Note: we do not instantiate Applicative
or Monad
for this type because
those interfaces would typically incur space leaks. We encourage you to
process the events each time you invoke a ledger function.
Constructors
LedgerResult | |
Fields
|
Instances
Functor (LedgerResult l) Source # | |
Defined in Ouroboros.Consensus.Ledger.Basics Methods fmap ∷ (a → b) → LedgerResult l a → LedgerResult l b # (<$) ∷ a → LedgerResult l b → LedgerResult l a # | |
Foldable (LedgerResult l) Source # | |
Defined in Ouroboros.Consensus.Ledger.Basics Methods fold ∷ Monoid m ⇒ LedgerResult l m → m # foldMap ∷ Monoid m ⇒ (a → m) → LedgerResult l a → m # foldMap' ∷ Monoid m ⇒ (a → m) → LedgerResult l a → m # foldr ∷ (a → b → b) → b → LedgerResult l a → b # foldr' ∷ (a → b → b) → b → LedgerResult l a → b # foldl ∷ (b → a → b) → b → LedgerResult l a → b # foldl' ∷ (b → a → b) → b → LedgerResult l a → b # foldr1 ∷ (a → a → a) → LedgerResult l a → a # foldl1 ∷ (a → a → a) → LedgerResult l a → a # toList ∷ LedgerResult l a → [a] # null ∷ LedgerResult l a → Bool # length ∷ LedgerResult l a → Int # elem ∷ Eq a ⇒ a → LedgerResult l a → Bool # maximum ∷ Ord a ⇒ LedgerResult l a → a # minimum ∷ Ord a ⇒ LedgerResult l a → a # sum ∷ Num a ⇒ LedgerResult l a → a # product ∷ Num a ⇒ LedgerResult l a → a # | |
Traversable (LedgerResult l) Source # | |
Defined in Ouroboros.Consensus.Ledger.Basics Methods traverse ∷ Applicative f ⇒ (a → f b) → LedgerResult l a → f (LedgerResult l b) # sequenceA ∷ Applicative f ⇒ LedgerResult l (f a) → f (LedgerResult l a) # mapM ∷ Monad m ⇒ (a → m b) → LedgerResult l a → m (LedgerResult l b) # sequence ∷ Monad m ⇒ LedgerResult l (m a) → m (LedgerResult l a) # |
data VoidLedgerEvent (l ∷ LedgerStateKind) Source #
A Void
isomorph for explicitly declaring that some ledger has
no events
castLedgerResult ∷ ∀ (l ∷ LedgerStateKind) (l' ∷ LedgerStateKind) a. AuxLedgerEvent l ~ AuxLedgerEvent l' ⇒ LedgerResult l a → LedgerResult l' a Source #
embedLedgerResult ∷ ∀ (l ∷ LedgerStateKind) (l' ∷ LedgerStateKind) a. (AuxLedgerEvent l → AuxLedgerEvent l') → LedgerResult l a → LedgerResult l' a Source #
pureLedgerResult ∷ ∀ a (l ∷ LedgerStateKind). a → LedgerResult l a Source #
GetTip
class GetTip (l ∷ LedgerStateKind) where Source #
Methods
getTip ∷ ∀ (mk ∷ MapKind). l mk → Point l Source #
Point of the most recently applied block
Should be GenesisPoint
when no blocks have been applied yet
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 # | |
IsLedger (LedgerState blk) ⇒ GetTip (ExtLedgerState blk) Source # | |
Defined in Ouroboros.Consensus.Ledger.Extended Methods getTip ∷ ∀ (mk ∷ MapKind). ExtLedgerState blk mk → Point (ExtLedgerState blk) 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 # | |
IsLedger l ⇒ GetTip (K (DbChangelog l) ∷ MapKind → Type) Source # | |
getTipSlot ∷ ∀ l (mk ∷ MapKind). GetTip l ⇒ l mk → WithOrigin SlotNo Source #
Associated types by block type
type LedgerConfig blk = LedgerCfg (LedgerState blk) Source #
type LedgerError blk = LedgerErr (LedgerState blk) Source #