ouroboros-consensus-0.26.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Ledger.Extended

Synopsis

Extended ledger state

newtype ExtLedgerCfg blk Source #

" Ledger " configuration for the extended ledger

Since the extended ledger also does the consensus protocol validation, we also need the consensus config.

Constructors

ExtLedgerCfg 

Instances

Instances details
Generic (ExtLedgerCfg blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtLedgerCfg blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerCfg blk) = D1 ('MetaData "ExtLedgerCfg" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "ExtLedgerCfg" 'PrefixI 'True) (S1 ('MetaSel ('Just "getExtLedgerCfg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TopLevelConfig blk))))

Methods

fromExtLedgerCfg blk → Rep (ExtLedgerCfg blk) x #

toRep (ExtLedgerCfg blk) x → ExtLedgerCfg blk #

(ConsensusProtocol (BlockProtocol blk), NoThunks (BlockConfig blk), NoThunks (CodecConfig blk), NoThunks (LedgerConfig blk), NoThunks (StorageConfig blk), NoThunks (HeaderHash blk)) ⇒ NoThunks (ExtLedgerCfg blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerCfg blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerCfg blk) = D1 ('MetaData "ExtLedgerCfg" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "ExtLedgerCfg" 'PrefixI 'True) (S1 ('MetaSel ('Just "getExtLedgerCfg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TopLevelConfig blk))))

data ExtLedgerState blk (mk ∷ MapKind) Source #

Extended ledger state

This is the combination of the header state and the ledger state proper.

Constructors

ExtLedgerState 

Fields

Instances

Instances details
IsLedger (LedgerState blk) ⇒ GetTip (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip ∷ ∀ (mk ∷ MapKind). ExtLedgerState blk mk → Point (ExtLedgerState blk) Source #

LedgerSupportsProtocol blk ⇒ IsLedger (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

CanStowLedgerTables (LedgerState blk) ⇒ CanStowLedgerTables (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

(HasLedgerTables (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 (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ ExtLedgerState blk mk → LedgerTables (ExtLedgerState blk) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ ExtLedgerState blk any → LedgerTables (ExtLedgerState blk) mk → ExtLedgerState blk mk Source #

LedgerTablesAreTrivial (LedgerState blk) ⇒ LedgerTablesAreTrivial (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

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

SerializeTablesWithHint (LedgerState blk) ⇒ SerializeTablesWithHint (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

CanUpgradeLedgerTables (LedgerState blk) ⇒ CanUpgradeLedgerTables (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.API

Methods

upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). ExtLedgerState blk mk1 → ExtLedgerState blk mk2 → LedgerTables (ExtLedgerState blk) ValuesMKLedgerTables (ExtLedgerState blk) ValuesMK Source #

LedgerSupportsProtocol blk ⇒ ApplyBlock (ExtLedgerState blk) blk Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Generic (ExtLedgerState blk mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtLedgerState blk mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerState blk mk) = D1 ('MetaData "ExtLedgerState" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "ExtLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerState blk mk)) :*: S1 ('MetaSel ('Just "headerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderState blk))))

Methods

fromExtLedgerState blk mk → Rep (ExtLedgerState blk mk) x #

toRep (ExtLedgerState blk mk) x → ExtLedgerState blk mk #

(ShowMK mk, LedgerSupportsProtocol blk) ⇒ Show (ExtLedgerState blk mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

showsPrecIntExtLedgerState blk mk → ShowS #

showExtLedgerState blk mk → String #

showList ∷ [ExtLedgerState blk mk] → ShowS #

(EqMK mk, LedgerSupportsProtocol blk) ⇒ Eq (ExtLedgerState blk mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

(==)ExtLedgerState blk mk → ExtLedgerState blk mk → Bool #

(/=)ExtLedgerState blk mk → ExtLedgerState blk mk → Bool #

(NoThunksMK mk, LedgerSupportsProtocol blk) ⇒ NoThunks (ExtLedgerState blk mk) Source #

We override showTypeOf to show the type of the block

This makes debugging a bit easier, as the block gets used to resolve all kinds of type families.

Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

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

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

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

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

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

(txout ~ TxOut (LedgerState blk), IndexedMemPack (LedgerState blk EmptyMK) txout) ⇒ IndexedMemPack (ExtLedgerState blk EmptyMK) txout Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

(NoThunks (HeaderHash blk), Typeable (HeaderHash blk), Show (HeaderHash blk), Ord (HeaderHash blk), Eq (HeaderHash blk)) ⇒ StandardHash (ExtLedgerState blk ∷ MapKindType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Inject (Flip ExtLedgerState mk) Source # 
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 ExtLedgerState mk x → Flip ExtLedgerState mk (HardForkBlock xs) Source #

Isomorphic (Flip ExtLedgerState mk) Source # 
Instance details

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

type AuxLedgerEvent (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type LedgerCfg (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type LedgerErr (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type TxIn (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type TxIn (ExtLedgerState blk) = TxIn (LedgerState blk)
type TxOut (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerState blk mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerState blk mk) = D1 ('MetaData "ExtLedgerState" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "ExtLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerState blk mk)) :*: S1 ('MetaSel ('Just "headerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderState blk))))
data Ticked (ExtLedgerState blk ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type HeaderHash (ExtLedgerState blk ∷ MapKindType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data ExtValidationError blk Source #

Instances

Instances details
Generic (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtValidationError blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtValidationError blk) = D1 ('MetaData "ExtValidationError" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "ExtValidationErrorLedger" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerError blk))) :+: C1 ('MetaCons "ExtValidationErrorHeader" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderError blk))))
LedgerSupportsProtocol blk ⇒ Show (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

LedgerSupportsProtocol blk ⇒ Eq (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

LedgerSupportsProtocol blk ⇒ NoThunks (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtValidationError blk) = D1 ('MetaData "ExtValidationError" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "ExtValidationErrorLedger" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerError blk))) :+: C1 ('MetaCons "ExtValidationErrorHeader" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderError blk))))

Serialisation

decodeExtLedgerState ∷ (∀ s. Decoder s (LedgerState blk EmptyMK)) → (∀ s. Decoder s (ChainDepState (BlockProtocol blk))) → (∀ s. Decoder s (AnnTip blk)) → ∀ s. Decoder s (ExtLedgerState blk EmptyMK) Source #

encodeExtLedgerState ∷ ∀ blk (mk ∷ MapKind). (LedgerState blk mk → Encoding) → (ChainDepState (BlockProtocol blk) → Encoding) → (AnnTip blk → Encoding) → ExtLedgerState blk mk → Encoding Source #

Type family instances

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

(∀ k v. LedgerTableConstraints' l k v ⇒ Monoid (mk k v), LedgerTableConstraints l) ⇒ Monoid (LedgerTables l mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

memptyLedgerTables l mk #

mappendLedgerTables 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 # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

(<>)LedgerTables l mk → LedgerTables l mk → LedgerTables l mk #

sconcatNonEmpty (LedgerTables l mk) → LedgerTables l mk #

stimesIntegral b ⇒ b → LedgerTables l mk → LedgerTables l mk #

Generic (LedgerTables l mk) Source # 
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.26.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) Source # 
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) Source # 
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) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (LedgerTables l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

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

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (LedgerTables l) = TxOut l
type Rep (LedgerTables l mk) Source # 
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.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 # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables

type InitHint (LedgerTables l ValuesMK) Source # 
Instance details

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

type ReadHint (LedgerTables l ValuesMK) Source # 
Instance details

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

type WriteHint (LedgerTables l DiffMK) Source # 
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 ()) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.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))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(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 # 
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 blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) Source # 
Instance details

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

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Ticked (f a)) ⇒ Show (((TickedTypeType) :.: f) a) Source # 
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) Source # 
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 () Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked (HardForkChainDepState xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (PBftState c ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

type HeaderHash (Ticked l ∷ k) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

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

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

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

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Extended