ouroboros-consensus-cardano-0.25.1.0: The instantation of the Ouroboros consensus layer used by Cardano
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.ByronSpec.Ledger.Ledger

Synopsis

Documentation

Type family instances

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 :: MapKind to express the 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

Instances details
Bridge m a ⇒ GetTip (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (DualBlock m a) mk → Point (LedgerState (DualBlock m a)) Source #

GetTip (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

IsLedger (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

CanStowLedgerTables (LedgerState m) ⇒ CanStowLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanStowLedgerTables (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

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

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 #

HasLedgerTables (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

LedgerTablesAreTrivial (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

(Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m)), MemPack (TxOut (LedgerState m))) ⇒ SerializeTablesWithHint (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanUpgradeLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ApplyBlock (LedgerState ByronSpecBlock) ByronSpecBlock Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

Generic (LedgerState ByronSpecBlock mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

Associated Types

type Rep (LedgerState ByronSpecBlock mk) 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type Rep (LedgerState ByronSpecBlock mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.ByronSpec.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.1.0-inplace-unstable-byronspec" 'False) (C1 ('MetaCons "ByronSpecLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronSpecLedgerTip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SlotNo)) :*: S1 ('MetaSel ('Just "byronSpecLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (State CHAIN))))
(ShowMK mk, CanHardFork xs) ⇒ Show (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(Bridge m a, ShowMK mk) ⇒ Show (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntLedgerState (DualBlock m a) mk → ShowS #

showLedgerState (DualBlock m a) mk → String #

showList ∷ [LedgerState (DualBlock m a) mk] → ShowS #

Show (LedgerState ByronSpecBlock mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

(EqMK mk, CanHardFork xs) ⇒ Eq (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(Bridge m a, EqMK mk) ⇒ Eq (LedgerState (DualBlock m a) mk) 
Instance details

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 #

Eq (LedgerState ByronSpecBlock mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

(NoThunksMK mk, CanHardFork xs) ⇒ NoThunks (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (LedgerState ByronSpecBlock mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

GetTip (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

HasLedgerTables (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

LedgerTablesAreTrivial (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

Serialise (LedgerState ByronSpecBlock mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

(txout ~ TxOut (LedgerState m), IndexedMemPack (LedgerState m EmptyMK) txout) ⇒ IndexedMemPack (LedgerState (DualBlock m a) EmptyMK) txout 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

IndexedMemPack (LedgerState ByronSpecBlock EmptyMK) Void Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

StandardHash blk ⇒ StandardHash (LedgerState blk ∷ MapKindType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Show (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

Eq (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

NoThunks (Ticked (LedgerState (DualBlock m a)) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

Inject (Flip LedgerState mk) 
Instance details

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

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

Methods

projectNoHardForks blk ⇒ Flip LedgerState mk (HardForkBlock '[blk]) → Flip LedgerState mk blk Source #

injectNoHardForks blk ⇒ Flip LedgerState mk blk → Flip LedgerState mk (HardForkBlock '[blk]) Source #

data LedgerState ByronSpecBlock mk Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

type AuxLedgerEvent (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerCfg (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerErr (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

newtype LedgerState (HardForkBlock xs) mk 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type TxIn (LedgerState (HardForkBlock xs))

Must be the CannonicalTxIn type, but this will probably change in the future to NS WrapTxIn xs. See HasCanonicalTxIn.

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type TxIn (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TxIn (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type TxOut (LedgerState (HardForkBlock xs))

Must be the HardForkTxOut type

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type TxOut (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TxOut (LedgerState ByronSpecBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type Rep (LedgerState ByronSpecBlock mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type Rep (LedgerState ByronSpecBlock mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.ByronSpec.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.1.0-inplace-unstable-byronspec" 'False) (C1 ('MetaCons "ByronSpecLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronSpecLedgerTip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SlotNo)) :*: S1 ('MetaSel ('Just "byronSpecLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (State CHAIN))))
data LedgerState (DualBlock m a) mk 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (LedgerState ByronSpecBlock) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type HeaderHash (LedgerState blk ∷ MapKindType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ MapKindType) = HeaderHash blk

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

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

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 #

Generic (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Associated Types

type Rep (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.27.0.0-inplace" 'True) (C1 ('MetaCons "LedgerTables" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mk (TxIn l) (TxOut l)))))

Methods

fromLedgerTables l mk → Rep (LedgerTables l mk) x #

toRep (LedgerTables l mk) x → LedgerTables l mk #

Show (mk (TxIn l) (TxOut l)) ⇒ Show (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Methods

showsPrecIntLedgerTables l mk → ShowS #

showLedgerTables l mk → String #

showList ∷ [LedgerTables l mk] → ShowS #

Eq (mk (TxIn l) (TxOut l)) ⇒ Eq (LedgerTables l mk) 
Instance details

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

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (LedgerTables l) = TxIn l
type TxOut (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (LedgerTables l) = TxOut l
type Rep (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.27.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) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables

type InitHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

type ReadHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

type WriteHint (LedgerTables l DiffMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

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

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

GetTip (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (ExtLedgerState blk) mk → Point (Ticked (ExtLedgerState blk)) 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))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

HasLedgerTables (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

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

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 ByronSpecBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

LedgerTablesAreTrivial (Ticked (LedgerState blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (ExtLedgerState blk) mk → Ticked (ExtLedgerState blk) mk' Source #

Show (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

Eq (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

NoThunks (Ticked (LedgerState (DualBlock m a)) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

Show (Ticked (f a)) ⇒ Show (((TickedTypeType) :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → ((TickedTypeType) :.: f) a → ShowS #

show ∷ ((TickedTypeType) :.: f) a → String #

showList ∷ [((TickedTypeType) :.: f) a] → ShowS #

NoThunks (Ticked (f a)) ⇒ NoThunks (((TickedTypeType) :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

noThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

wNoThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (((TickedTypeType) :.: f) a) → String Source #

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked (HardForkChainDepState xs ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (PBftState c ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

type HeaderHash (Ticked l ∷ k) 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ k) = HeaderHash l
type TxIn (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (Ticked l) = TxIn l
type TxOut (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (Ticked l) = TxOut l
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (LedgerState ByronSpecBlock) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

data Ticked (ExtLedgerState blk ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Orphan instances

UpdateLedger ByronSpecBlock Source # 
Instance details

CommonProtocolParams ByronSpecBlock Source # 
Instance details

GetTip (LedgerState ByronSpecBlock) Source # 
Instance details

IsLedger (LedgerState ByronSpecBlock) Source # 
Instance details

CanStowLedgerTables (LedgerState ByronSpecBlock) Source # 
Instance details

HasLedgerTables (LedgerState ByronSpecBlock) Source # 
Instance details

LedgerTablesAreTrivial (LedgerState ByronSpecBlock) Source # 
Instance details

ApplyBlock (LedgerState ByronSpecBlock) ByronSpecBlock Source # 
Instance details

Generic (LedgerState ByronSpecBlock mk) Source # 
Instance details

Associated Types

type Rep (LedgerState ByronSpecBlock mk) 
Instance details

Defined in Ouroboros.Consensus.ByronSpec.Ledger.Ledger

type Rep (LedgerState ByronSpecBlock mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.ByronSpec.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.1.0-inplace-unstable-byronspec" 'False) (C1 ('MetaCons "ByronSpecLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronSpecLedgerTip") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SlotNo)) :*: S1 ('MetaSel ('Just "byronSpecLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (State CHAIN))))
Show (LedgerState ByronSpecBlock mk) Source # 
Instance details

Eq (LedgerState ByronSpecBlock mk) Source # 
Instance details

NoThunks (LedgerState ByronSpecBlock mk) Source # 
Instance details

GetTip (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

HasLedgerTables (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

LedgerTablesAreTrivial (Ticked (LedgerState ByronSpecBlock)) Source # 
Instance details

Serialise (LedgerState ByronSpecBlock mk) Source # 
Instance details

IndexedMemPack (LedgerState ByronSpecBlock EmptyMK) Void Source # 
Instance details

Show (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

Eq (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details

NoThunks (Ticked (LedgerState ByronSpecBlock) mk) Source # 
Instance details