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

Ouroboros.Consensus.Ledger.Tables.MapKind

Description

Classes for MapKinds and concrete MapKinds

Synopsis

Classes

class CanMapKeysMK (mk ∷ MapKind) where Source #

Methods

mapKeysMKOrd k' ⇒ (k → k') → mk k v → mk k' v Source #

Instances defined for the standard mapkinds suffer from the same caveats as mapKeys or map

Instances

Instances details
CanMapKeysMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → DiffMK k v → DiffMK k' v Source #

CanMapKeysMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → EmptyMK k v → EmptyMK k' v Source #

CanMapKeysMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → KeysMK k v → KeysMK k' v Source #

CanMapKeysMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → TrackingMK k v → TrackingMK k' v Source #

CanMapKeysMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → ValuesMK k v → ValuesMK k' v Source #

class CanMapMK (mk ∷ MapKind) where Source #

Methods

mapMK ∷ (v → v') → mk k v → mk k v' Source #

Instances

Instances details
CanMapMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → DiffMK k v → DiffMK k v' Source #

CanMapMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → EmptyMK k v → EmptyMK k v' Source #

CanMapMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → KeysMK k v → KeysMK k v' Source #

CanMapMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → TrackingMK k v → TrackingMK k v' Source #

CanMapMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → ValuesMK k v → ValuesMK k v' Source #

class (∀ k v. (Eq k, Eq v) ⇒ Eq (mk k v)) ⇒ EqMK (mk ∷ MapKind) Source #

For convenience, such that we don't have to include QuantifiedConstraints everywhere.

class (∀ k v. (NoThunks k, NoThunks v) ⇒ NoThunks (mk k v)) ⇒ NoThunksMK (mk ∷ MapKind) Source #

For convenience, such that we don't have to include QuantifiedConstraints everywhere.

class (∀ k v. (Show k, Show v) ⇒ Show (mk k v)) ⇒ ShowMK (mk ∷ MapKind) Source #

For convenience, such that we don't have to include QuantifiedConstraints everywhere.

class ZeroableMK (mk ∷ MapKind) where Source #

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ mk k v Source #

Instances

Instances details
ZeroableMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ DiffMK k v Source #

ZeroableMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ EmptyMK k v Source #

ZeroableMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ KeysMK k v Source #

ZeroableMK SeqDiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ SeqDiffMK k v Source #

ZeroableMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ TrackingMK k v Source #

ZeroableMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ ValuesMK k v Source #

bimapLedgerTables ∷ ∀ (x ∷ LedgerStateKind) (y ∷ LedgerStateKind) (mk ∷ MapKind). (CanMapKeysMK mk, CanMapMK mk, Ord (TxIn y)) ⇒ (TxIn x → TxIn y) → (TxOut x → TxOut y) → LedgerTables x mk → LedgerTables y mk Source #

Map both keys and values in ledger tables.

For keys, it has the same caveats as mapKeys or map, namely that only injective functions are suitable to be used here.

Concrete MapKinds

data CodecMK k v Source #

A codec MapKind that will be used to refer to LedgerTables l CodecMK as the codecs that can encode every key and value in the LedgerTables l mk.

It is important to note that in the context of the HardForkCombinator, the key k has to be accessible from any era we are currently in, regardless of which era it was created in. Because of that, we need that the serialization of the key remains stable accross eras.

Ledger will provide more efficient encoders than CBOR, which will produce a ShortByteString directly.

See also HasCanonicalTxIn in Ouroboros.Consensus.HardFork.Combinator.Ledger.

We will serialize UTxO maps as unstowed ledger tables when storing snapshots while using an in-memory backend for the LedgerDB.

Constructors

CodecMK 

Fields

newtype DiffMK k v Source #

Constructors

DiffMK 

Fields

Instances

Instances details
CanMapKeysMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → DiffMK k v → DiffMK k' v Source #

CanMapMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → DiffMK k v → DiffMK k v' Source #

EqMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

NoThunksMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ShowMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ZeroableMK DiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ DiffMK k v Source #

Functor (DiffMK k) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

fmap ∷ (a → b) → DiffMK k a → DiffMK k b #

(<$) ∷ a → DiffMK k b → DiffMK k a #

Generic (DiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Associated Types

type Rep (DiffMK k v) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (DiffMK k v) = D1 ('MetaData "DiffMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "DiffMK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDiffMK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Diff k v))))

Methods

fromDiffMK k v → Rep (DiffMK k v) x #

toRep (DiffMK k v) x → DiffMK k v #

(Show k, Show v) ⇒ Show (DiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

showsPrecIntDiffMK k v → ShowS #

showDiffMK k v → String #

showList ∷ [DiffMK k v] → ShowS #

(Eq k, Eq v) ⇒ Eq (DiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

(==)DiffMK k v → DiffMK k v → Bool #

(/=)DiffMK k v → DiffMK k v → Bool #

(NoThunks k, NoThunks v) ⇒ NoThunks (DiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (DiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (DiffMK k v) = D1 ('MetaData "DiffMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "DiffMK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDiffMK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Diff k v))))
type WriteHint (LedgerTables l DiffMK) Source # 
Instance details

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

data EmptyMK k v Source #

Constructors

EmptyMK 

Instances

Instances details
CanMapKeysMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → EmptyMK k v → EmptyMK k' v Source #

CanMapMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → EmptyMK k v → EmptyMK k v' Source #

EqMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

NoThunksMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ShowMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ZeroableMK EmptyMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ EmptyMK k v Source #

GetTip l ⇒ Anchorable (WithOrigin SlotNo) (l EmptyMK) (l EmptyMK) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.DbChangelog

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs) EmptyMK) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs) EmptyMK) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Generic (EmptyMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Associated Types

type Rep (EmptyMK k v) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (EmptyMK k v) = D1 ('MetaData "EmptyMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "EmptyMK" 'PrefixI 'False) (U1TypeType))

Methods

fromEmptyMK k v → Rep (EmptyMK k v) x #

toRep (EmptyMK k v) x → EmptyMK k v #

Show (EmptyMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

showsPrecIntEmptyMK k v → ShowS #

showEmptyMK k v → String #

showList ∷ [EmptyMK k v] → ShowS #

Eq (EmptyMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

(==)EmptyMK k v → EmptyMK k v → Bool #

(/=)EmptyMK k v → EmptyMK k v → Bool #

NoThunks (EmptyMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Extended

IndexedMemPack (TrivialLedgerTables l EmptyMK) Void Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables

type Rep (EmptyMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (EmptyMK k v) = D1 ('MetaData "EmptyMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "EmptyMK" 'PrefixI 'False) (U1TypeType))

newtype KeysMK k v Source #

Constructors

KeysMK (Set k) 

Instances

Instances details
CanMapKeysMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → KeysMK k v → KeysMK k' v Source #

CanMapMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → KeysMK k v → KeysMK k v' Source #

EqMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

NoThunksMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ShowMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ZeroableMK KeysMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ KeysMK k v Source #

Ord k ⇒ Monoid (KeysMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

memptyKeysMK k v #

mappendKeysMK k v → KeysMK k v → KeysMK k v #

mconcat ∷ [KeysMK k v] → KeysMK k v #

Ord k ⇒ Semigroup (KeysMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

(<>)KeysMK k v → KeysMK k v → KeysMK k v #

sconcatNonEmpty (KeysMK k v) → KeysMK k v #

stimesIntegral b ⇒ b → KeysMK k v → KeysMK k v #

Generic (KeysMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Associated Types

type Rep (KeysMK k v) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (KeysMK k v) = D1 ('MetaData "KeysMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "KeysMK" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set k))))

Methods

fromKeysMK k v → Rep (KeysMK k v) x #

toRep (KeysMK k v) x → KeysMK k v #

Show k ⇒ Show (KeysMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

showsPrecIntKeysMK k v → ShowS #

showKeysMK k v → String #

showList ∷ [KeysMK k v] → ShowS #

Eq k ⇒ Eq (KeysMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

(==)KeysMK k v → KeysMK k v → Bool #

(/=)KeysMK k v → KeysMK k v → Bool #

NoThunks k ⇒ NoThunks (KeysMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (KeysMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (KeysMK k v) = D1 ('MetaData "KeysMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "KeysMK" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set k))))

newtype SeqDiffMK k v Source #

Constructors

SeqDiffMK 

Fields

Instances

Instances details
EqMK SeqDiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

NoThunksMK SeqDiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ShowMK SeqDiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ZeroableMK SeqDiffMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ SeqDiffMK k v Source #

Generic (SeqDiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Associated Types

type Rep (SeqDiffMK k v) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (SeqDiffMK k v) = D1 ('MetaData "SeqDiffMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "SeqDiffMK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSeqDiffMK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DiffSeq k v))))

Methods

fromSeqDiffMK k v → Rep (SeqDiffMK k v) x #

toRep (SeqDiffMK k v) x → SeqDiffMK k v #

(Show k, Show v) ⇒ Show (SeqDiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

showsPrecIntSeqDiffMK k v → ShowS #

showSeqDiffMK k v → String #

showList ∷ [SeqDiffMK k v] → ShowS #

(Eq k, Eq v) ⇒ Eq (SeqDiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

(==)SeqDiffMK k v → SeqDiffMK k v → Bool #

(/=)SeqDiffMK k v → SeqDiffMK k v → Bool #

(NoThunks k, NoThunks v) ⇒ NoThunks (SeqDiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (SeqDiffMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (SeqDiffMK k v) = D1 ('MetaData "SeqDiffMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "SeqDiffMK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSeqDiffMK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DiffSeq k v))))

data TrackingMK k v Source #

Constructors

TrackingMK !(Map k v) !(Diff k v) 

Instances

Instances details
CanMapKeysMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → TrackingMK k v → TrackingMK k' v Source #

CanMapMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → TrackingMK k v → TrackingMK k v' Source #

EqMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

NoThunksMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ShowMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ZeroableMK TrackingMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ TrackingMK k v Source #

Generic (TrackingMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Associated Types

type Rep (TrackingMK k v) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (TrackingMK k v) = D1 ('MetaData "TrackingMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "TrackingMK" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map k v)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Diff k v))))

Methods

fromTrackingMK k v → Rep (TrackingMK k v) x #

toRep (TrackingMK k v) x → TrackingMK k v #

(Show k, Show v) ⇒ Show (TrackingMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

showsPrecIntTrackingMK k v → ShowS #

showTrackingMK k v → String #

showList ∷ [TrackingMK k v] → ShowS #

(Eq k, Eq v) ⇒ Eq (TrackingMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

(==)TrackingMK k v → TrackingMK k v → Bool #

(/=)TrackingMK k v → TrackingMK k v → Bool #

(NoThunks k, NoThunks v) ⇒ NoThunks (TrackingMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (TrackingMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (TrackingMK k v) = D1 ('MetaData "TrackingMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "TrackingMK" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map k v)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Diff k v))))

newtype ValuesMK k v Source #

Constructors

ValuesMK 

Fields

Instances

Instances details
CanMapKeysMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapKeysMKOrd k' ⇒ (k → k') → ValuesMK k v → ValuesMK k' v Source #

CanMapMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

mapMK ∷ (v → v') → ValuesMK k v → ValuesMK k v' Source #

EqMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

NoThunksMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ShowMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

ZeroableMK ValuesMK Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

emptyMK ∷ (Ord k, Eq v) ⇒ ValuesMK k v Source #

Generic (ValuesMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Associated Types

type Rep (ValuesMK k v) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (ValuesMK k v) = D1 ('MetaData "ValuesMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "ValuesMK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getValuesMK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map k v))))

Methods

fromValuesMK k v → Rep (ValuesMK k v) x #

toRep (ValuesMK k v) x → ValuesMK k v #

(Show k, Show v) ⇒ Show (ValuesMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

showsPrecIntValuesMK k v → ShowS #

showValuesMK k v → String #

showList ∷ [ValuesMK k v] → ShowS #

(Eq k, Eq v) ⇒ Eq (ValuesMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

Methods

(==)ValuesMK k v → ValuesMK k v → Bool #

(/=)ValuesMK k v → ValuesMK k v → Bool #

(NoThunks k, NoThunks v) ⇒ NoThunks (ValuesMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (ValuesMK k v) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.MapKind

type Rep (ValuesMK k v) = D1 ('MetaData "ValuesMK" "Ouroboros.Consensus.Ledger.Tables.MapKind" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "ValuesMK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getValuesMK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map k v))))
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