cardano-ledger-core-1.12.0.0: Core components of Cardano ledgers from the Shelley release on.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Ledger.UMap

Description

A UMap (for Unified map) represents

  1. 4 Maps with the same domain in one direction, as a single Map and
  2. 1 other Map which is an inverse of one of the other 4 Maps.

The advantage of using UMap is that it stores all the information compactly, by exploiting the large amount of sharing in Map #1.

As for the other Map #2, we don't expect it to have much volume.

Synopsis

Constructing a UMap

data RDPair Source #

A Reward-Deposit Pair Used to represent the reward and the deposit for a given (Credential 'Staking c)

Constructors

RDPair 

Instances

Instances details
Generic RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

Associated Types

type Rep RDPairTypeType Source #

Methods

fromRDPairRep RDPair x Source #

toRep RDPair x → RDPair Source #

Show RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

DecCBOR RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

EncCBOR RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

encCBORRDPairEncoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy RDPairSize Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [RDPair] → Size Source #

NFData RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

rnfRDPair → () Source #

Eq RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

(==)RDPairRDPairBool Source #

(/=)RDPairRDPairBool Source #

Ord RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

NoThunks RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

type Rep RDPair Source # 
Instance details

Defined in Cardano.Ledger.UMap

type Rep RDPair = D1 ('MetaData "RDPair" "Cardano.Ledger.UMap" "cardano-ledger-core-1.12.0.0-inplace" 'False) (C1 ('MetaCons "RDPair" 'PrefixI 'True) (S1 ('MetaSel ('Just "rdReward") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 (CompactForm Coin)) :*: S1 ('MetaSel ('Just "rdDeposit") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 (CompactForm Coin))))

data UMElem c where Source #

A UMElem compactly represents the range of 4 Maps with the same domain as a single n-tuple.

This space-compacting datatype, and the pattern UMElem are equivalent to: data Elem c = Elem { rdPairT :: !(StrictMaybe RDPair), ptrT :: !(Set Ptr), sPoolT :: !(StrictMaybe (KeyHash 'StakePool c)), -- the stake pool identity dRepT :: !(StrictMaybe (DRep c)), } deriving (Show, Eq, Generic, NoThunks, NFData)

To name the constructors of UMElem we use the notation Txxx where each x is either F for full, i.e. the component is present, or E for empty, i.e. the component is not present.

There are four components: 1) the reward-deposit pair as an RDPair (CompactForm Coin) (CompactForm Coin) as a pair of Word64s, the first x, 2) the set of pointers, the second x, 3) the stake pool id (KeyHash 'StakePool c), the third x, and 4) the voting delegatee id (DRep c), the fourth x.

So, TEEEE means none of the components are present, TFEEE means only the reward-deposit pair is present, TEFEE means only the set of pointers is present, TEEFE means only the stake pool id is present. etc. TEEEF means only the voting delegatee id is present, and

The pattern UMElem will correctly use the optimal constructor.

Bundled Patterns

pattern UMElemStrictMaybe RDPairSet PtrStrictMaybe (KeyHash 'StakePool c) → StrictMaybe (DRep c) → UMElem c

A UMElem can be extracted and injected into the TEEEE ... TFFFF constructors.

Instances

Instances details
Crypto c ⇒ ToJSON (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Generic (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Associated Types

type Rep (UMElem c) ∷ TypeType Source #

Methods

fromUMElem c → Rep (UMElem c) x Source #

toRep (UMElem c) x → UMElem c Source #

Show (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

showsPrecIntUMElem c → ShowS Source #

showUMElem c → String Source #

showList ∷ [UMElem c] → ShowS Source #

Crypto c ⇒ DecShareCBOR (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Associated Types

type Share (UMElem c) Source #

Crypto c ⇒ EncCBOR (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

encCBORUMElem c → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (UMElem c) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [UMElem c] → Size Source #

NFData (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

rnfUMElem c → () Source #

Eq (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

(==)UMElem c → UMElem c → Bool Source #

(/=)UMElem c → UMElem c → Bool Source #

Ord (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

compareUMElem c → UMElem c → Ordering Source #

(<)UMElem c → UMElem c → Bool Source #

(<=)UMElem c → UMElem c → Bool Source #

(>)UMElem c → UMElem c → Bool Source #

(>=)UMElem c → UMElem c → Bool Source #

maxUMElem c → UMElem c → UMElem c Source #

minUMElem c → UMElem c → UMElem c Source #

NoThunks (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

type Rep (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

type Rep (UMElem c) = D1 ('MetaData "UMElem" "Cardano.Ledger.UMap" "cardano-ledger-core-1.12.0.0-inplace" 'False) ((((C1 ('MetaCons "TEEEE" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "TEEEF" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c)))) :+: (C1 ('MetaCons "TEEFE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))) :+: C1 ('MetaCons "TEEFF" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c))))) :+: ((C1 ('MetaCons "TEFEE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr))) :+: C1 ('MetaCons "TEFEF" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c)))) :+: (C1 ('MetaCons "TEFFE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))) :+: C1 ('MetaCons "TEFFF" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr)) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c))))))) :+: (((C1 ('MetaCons "TFEEE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair)) :+: C1 ('MetaCons "TFEEF" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c)))) :+: (C1 ('MetaCons "TFEFE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))) :+: C1 ('MetaCons "TFEFF" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c)))))) :+: ((C1 ('MetaCons "TFFEE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr))) :+: C1 ('MetaCons "TFFEF" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c))))) :+: (C1 ('MetaCons "TFFFE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)))) :+: C1 ('MetaCons "TFFFF" 'PrefixI 'False) ((S1 ('MetaSel ('NothingMaybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 RDPair) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set Ptr))) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c))))))))
type Share (UMElem c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

umElemRDPairUMElem c → Maybe RDPair Source #

Extract the reward-deposit pair if it is present. We can tell that the reward is present when Txxxx has an F in the first position

This is equivalent to the pattern (UMElem (SJust r) _ _ _) -> Just r

umElemRDActiveUMElem c → Maybe RDPair Source #

Extract a delegated reward-deposit pair if it is present. We can tell that the pair is present and active when Txxxx has an F in the 1st position (present) and 3rd position (delegated).

This is equivalent to the pattern (UMElem (SJust r) _ (SJust _) _) -> Just r

umElemDRepDelegatedRewardUMElem c → Maybe (CompactForm Coin, DRep c) Source #

Extract a DRep delegated reward if it is present. We can tell that the pair is present and active when Txxxx has an F in the 1st position (present) and 4rd position (DRep delegated).

This is equivalent to the pattern (UMElem (SJust r) _ _ (SJust d)) -> Just (r, d)

umElemDelegationsUMElem c → Maybe (RewardDelegation c) Source #

Extract rewards that are either delegated to a DRep or an SPO (or both). We can tell that the pair is present and active when Txxxx has F's in the 1st and either 3rd or 4th or both positions. If there are no rewards or deposits but the delegations still exist, then we return zero coin as reward.

umElemPtrsUMElem c → Maybe (Set Ptr) Source #

Extract the set of pointers if it is non-empty. We can tell that the reward is present when Txxxx has an F in the second position

This is equivalent to the pattern (UMElem _ p _ _) -> Just p

umElemSPoolUMElem c → Maybe (KeyHash 'StakePool c) Source #

Extract the stake delegatee pool id, if present. We can tell that the pool id is present when Txxxx has an F in the third position

This is equivalent to the pattern (UMElem _ _ (SJust s) _) -> Just s

umElemDRepUMElem c → Maybe (DRep c) Source #

Extract the voting delegatee id, if present. We can tell that the delegatee is present when Txxxx has an F in the fourth position

This is equivalent to the pattern (UMElem _ _ _ (SJust d)) -> Just d

umElemAsTupleUMElem c → (StrictMaybe RDPair, Set Ptr, StrictMaybe (KeyHash 'StakePool c), StrictMaybe (DRep c)) Source #

A n-Tuple view of the UMElem. We can view all of the constructors as an UMElem.

data UMap c Source #

A unified map represents 4 Maps with domain (Credential 'Staking c)

1) Map (Credential 'Staking c) RDPair -- (RDPair rewardCoin depositCoin) 2) Map (Credential 'Staking c) (Set Ptr) 3) Map (Credential 'Staking c) (StrictMaybe (KeyHash 'StakePool c)) 4) Map (Credential 'Staking c) (StrictMaybe (DRep c)) and one more map in the inverse direction with Ptr for keys and (Credential 'Staking c) for values.

Constructors

UMap 

Fields

Instances

Instances details
Crypto c ⇒ ToJSON (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Generic (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Associated Types

type Rep (UMap c) ∷ TypeType Source #

Methods

fromUMap c → Rep (UMap c) x Source #

toRep (UMap c) x → UMap c Source #

Show (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

showsPrecIntUMap c → ShowS Source #

showUMap c → String Source #

showList ∷ [UMap c] → ShowS Source #

Crypto c ⇒ DecShareCBOR (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Associated Types

type Share (UMap c) Source #

Crypto c ⇒ EncCBOR (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

encCBORUMap c → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (UMap c) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [UMap c] → Size Source #

NFData (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

rnfUMap c → () Source #

Eq (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

(==)UMap c → UMap c → Bool Source #

(/=)UMap c → UMap c → Bool Source #

NoThunks (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

type Rep (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

type Rep (UMap c) = D1 ('MetaData "UMap" "Cardano.Ledger.UMap" "cardano-ledger-core-1.12.0.0-inplace" 'False) (C1 ('MetaCons "UMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "umElems") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking c) (UMElem c))) :*: S1 ('MetaSel ('Just "umPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Ptr (Credential 'Staking c)))))
type Share (UMap c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

emptyUMap c Source #

Construct an empty UMap

umInvariantCredential 'Staking c → PtrUMap c → Bool Source #

It is worthwhile stating the invariant that holds on a Unified Map. The umPtrs and the ptrT field of the umElems are inverses.

StakeCredentials

data StakeCredentials c Source #

All maps unrolled. It is important to note that all fields are lazy, because conversion from UMap can be expensive, thus only fields that are forced will incur that conversion overhead.

Constructors

StakeCredentials 

Fields

Instances

Instances details
Generic (StakeCredentials c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Associated Types

type Rep (StakeCredentials c) ∷ TypeType Source #

Show (StakeCredentials c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

NFData (StakeCredentials c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

Methods

rnfStakeCredentials c → () Source #

Eq (StakeCredentials c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

NoThunks (StakeCredentials c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

type Rep (StakeCredentials c) Source # 
Instance details

Defined in Cardano.Ledger.UMap

UView and its components

data UView c k v where Source #

A UView lets one view a UMap in n different ways, one for each of the elements in a Unified Element UMElem (4) A (UView c key value) can be used like a (Map key value). It acts like a map, supporting efficient insert, delete, and lookup operations.

Constructors

RewDepUView ∷ !(UMap c) → UView c (Credential 'Staking c) RDPair 
PtrUView ∷ !(UMap c) → UView c Ptr (Credential 'Staking c) 
SPoolUView ∷ !(UMap c) → UView c (Credential 'Staking c) (KeyHash 'StakePool c) 
DRepUView ∷ !(UMap c) → UView c (Credential 'Staking c) (DRep c) 

Instances

Instances details
Foldable (UView c k) Source #

All Views are Foldable

Instance details

Defined in Cardano.Ledger.UMap

Methods

foldMonoid m ⇒ UView c k m → m Source #

foldMapMonoid m ⇒ (a → m) → UView c k a → m Source #

foldMap'Monoid m ⇒ (a → m) → UView c k a → m Source #

foldr ∷ (a → b → b) → b → UView c k a → b Source #

foldr' ∷ (a → b → b) → b → UView c k a → b Source #

foldl ∷ (b → a → b) → b → UView c k a → b Source #

foldl' ∷ (b → a → b) → b → UView c k a → b Source #

foldr1 ∷ (a → a → a) → UView c k a → a Source #

foldl1 ∷ (a → a → a) → UView c k a → a Source #

toListUView c k a → [a] Source #

nullUView c k a → Bool Source #

lengthUView c k a → Int Source #

elemEq a ⇒ a → UView c k a → Bool Source #

maximumOrd a ⇒ UView c k a → a Source #

minimumOrd a ⇒ UView c k a → a Source #

sumNum a ⇒ UView c k a → a Source #

productNum a ⇒ UView c k a → a Source #

rewDepUViewMap (Credential 'Staking c) (UMElem c) → Map Ptr (Credential 'Staking c) → UView c (Credential 'Staking c) RDPair Source #

Construct a RewDepUView from the two maps that make up a UMap

ptrUViewMap (Credential 'Staking c) (UMElem c) → Map Ptr (Credential 'Staking c) → UView c Ptr (Credential 'Staking c) Source #

Construct a PtrUView from the two maps that make up a UMap

sPoolUViewMap (Credential 'Staking c) (UMElem c) → Map Ptr (Credential 'Staking c) → UView c (Credential 'Staking c) (KeyHash 'StakePool c) Source #

Construct a SPoolUView from the two maps that make up a UMap

dRepUViewMap (Credential 'Staking c) (UMElem c) → Map Ptr (Credential 'Staking c) → UView c (Credential 'Staking c) (DRep c) Source #

Construct a DRepUView from the two maps that make up a UMap

unUViewUView c k v → UMap c Source #

Extract the underlying UMap from a UView

unUnifyToVMapUView c k v → VMap VB VB k v Source #

Materialize a real VMap (Vector Map) from a UView This is expensive, use it wisely (like maybe once per epoch boundary to make a SnapShot)

rdPairMapUMap c → Map (Credential 'Staking c) RDPair Source #

Extract a reward-deposit pairs Map from a UMap

rewardMapUMap c → Map (Credential 'Staking c) Coin Source #

Extract a rewards Map from a UMap

compactRewardMapUMap c → Map (Credential 'Staking c) (CompactForm Coin) Source #

Extract a compact rewards Map from a UMap

depositMapUMap c → Map (Credential 'Staking c) Coin Source #

Extract a deposits Map from a UMap

ptrMapUMap c → Map Ptr (Credential 'Staking c) Source #

Extract a pointers Map from a UMap

invPtrMapUMap c → Map (Credential 'Staking c) (Set Ptr) Source #

Extract a pointers Map from a UMap

sPoolMapUMap c → Map (Credential 'Staking c) (KeyHash 'StakePool c) Source #

Extract a stake pool delegations Map from a UMap

dRepMapUMap c → Map (Credential 'Staking c) (DRep c) Source #

Extract a delegated-representatives Map from a UMap

domRestrictedMapSet k → UView c k v → Map k v Source #

Extract a domain-restricted Map of a UMap. If `Set k` is small this should be efficient.

data family CompactForm a ∷ Type Source #

Instances

Instances details
FromJSON (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

ToJSON (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

ToJSON (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Monoid (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Semigroup (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Show (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Show (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

ToCBOR (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBORCompactForm CoinEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (CompactForm Coin) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [CompactForm Coin] → Size Source #

DecCBOR (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

DecCBOR (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

EncCBOR (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

EncCBOR (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

NFData (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnfCompactForm Coin → () Source #

NFData (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnfCompactForm DeltaCoin → () Source #

Eq (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Eq (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Ord (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Abelian (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Group (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

HeapWords (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

HeapWords (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

NoThunks (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

NoThunks (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Prim (CompactForm Coin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

Prim (CompactForm DeltaCoin) Source # 
Instance details

Defined in Cardano.Ledger.Coin

newtype CompactForm Coin Source # 
Instance details

Defined in Cardano.Ledger.Coin

newtype CompactForm DeltaCoin Source # 
Instance details

Defined in Cardano.Ledger.Coin

unifyMap (Credential 'Staking c) RDPairMap Ptr (Credential 'Staking c) → Map (Credential 'Staking c) (KeyHash 'StakePool c) → Map (Credential 'Staking c) (DRep c) → UMap c Source #

Create a UMap from 4 separate maps. NOTE: For use in tests only.

unUnifyUView c k v → Map k v Source #

Materialize a real Map from a View This is expensive, use it wisely (like maybe once per epoch boundary to make a SnapShot) See also domRestrictedMap, which domain-restricts before computing a view.

Set and Map operations on UViews

nullUViewUView c k v → Bool Source #

null for a UView, just like null

member ∷ k → UView c k v → Bool Source #

Membership check for a UView, just like member

Spec: eval (k ∈ dom (rewards dState)) eval (k ∈ dom (rewards ds))) eval (hk ∈ dom (rewards ds)) eval (hk ∉ dom (rewards ds))

notMember ∷ k → UView c k v → Bool Source #

Membership check for a UView, just like member

Spec: eval (k ∈ dom (rewards dState)) eval (k ∈ dom (rewards ds))) eval (hk ∈ dom (rewards ds)) eval (hk ∉ dom (rewards ds))

delete ∷ k → UView c k v → UMap c Source #

delete' ∷ k → UView c k v → UView c k v Source #

Delete a key and its value from the map-like UView, returning a version of the same UView.

In the case of a PtrUView we maintain the umInvariant and delete the pairs from both umElems as well as umPtrs of the UMap.

insertWith ∷ (v → v → v) → k → v → UView c k v → UMap c Source #

insertWith' ∷ (v → v → v) → k → v → UView c k v → UView c k v Source #

Insert with combination

If k exists as a key in the (map-like) UView:

  1. to keep the old value > insertWith' ( old new -> old) k v view
  2. to replace the old value with the new value > insertWith' ( old new -> new) k v view
  3. to combine the old and new values with summation > insertWith' ( old new -> old + new) k v view

If k does not exist as a key in the UView, the combining function is ignored, and the key k and the value v are inserted into the map-like UView > insertWith' ignoredCombiningFunction k v view

insert ∷ k → v → UView c k v → UMap c Source #

insert' ∷ k → v → UView c k v → UView c k v Source #

adjust ∷ (RDPairRDPair) → k → UView c k RDPairUMap c Source #

Adjust a UView, just like adjust. This is implemented only for reward-deposit pairs.

lookup ∷ k → UView c k v → Maybe v Source #

Lookup a UView, just like lookup.

domainUView c k v → Set k Source #

Get the domain of the Map-like UView

rangeUView c k v → Set v Source #

Get the range of the Map-like UView

(∪)UView c k v → (k, v) → UMap c Source #

Union with left preference. So if k, already exists, do nothing, if it doesn't exist insert it.

Spec: evalUnified (RewDepUView u1 ∪ singleton hk mempty) evalUnified (Ptrs u2 ∪ singleton ptr hk)

unionLUView c k v → (k, v) → UMap c Source #

Union with left preference. So if k, already exists, do nothing, if it doesn't exist insert it.

Spec: evalUnified (RewDepUView u1 ∪ singleton hk mempty) evalUnified (Ptrs u2 ∪ singleton ptr hk)

(⨃)UView c k v → Map k v → UMap c Source #

Union with right preference. So if k, already exists, then old v is overwritten with the new v.

Special rules apply for the RewDepUView, where only the rdReward field of the RDPair is overwritten, and the old rdDeposit value persists.

Note: In this case it is an invariant that the domain of the Map on the right side is a subset of the domain of the RewDepUView. See the single case in module Cardano.Ledger.Shelley.Rules.Delegs, in the dealing with Withdrawals's where it is used at this type.

Spec: evalUnified (delegations ds ⨃ singleton hk dpool) evalUnified (rewards' ⨃ wdrls_')

unionRUView c k v → Map k v → UMap c Source #

Union with right preference. So if k, already exists, then old v is overwritten with the new v.

Special rules apply for the RewDepUView, where only the rdReward field of the RDPair is overwritten, and the old rdDeposit value persists.

Note: In this case it is an invariant that the domain of the Map on the right side is a subset of the domain of the RewDepUView. See the single case in module Cardano.Ledger.Shelley.Rules.Delegs, in the dealing with Withdrawals's where it is used at this type.

Spec: evalUnified (delegations ds ⨃ singleton hk dpool) evalUnified (rewards' ⨃ wdrls_')

(∪+)UView c (Credential 'Staking c) RDPairMap (Credential 'Staking c) (CompactForm Coin) → UMap c Source #

Add the reward from the Map on the right side to the reward in the UView on the left. This is only implemented and is applicable to RewDepUViews.

We presume that the domain of the Map on the right, is a subset of the domain of the UView on the left.

Spec: evalUnified (rewards dState ∪+ registeredAggregated) evalUnified (rewards' ∪+ update) evalUnified (RewDepUView u0 ∪+ refunds)

unionRewAggUView c (Credential 'Staking c) RDPairMap (Credential 'Staking c) (CompactForm Coin) → UMap c Source #

Add the reward from the Map on the right side to the reward in the UView on the left. This is only implemented and is applicable to RewDepUViews.

We presume that the domain of the Map on the right, is a subset of the domain of the UView on the left.

Spec: evalUnified (rewards dState ∪+ registeredAggregated) evalUnified (rewards' ∪+ update) evalUnified (RewDepUView u0 ∪+ refunds)

unionKeyDepositsUView c k RDPairMap k (CompactForm Coin) → UMap c Source #

Add the deposit from the Map on the right side to the deposit in the UView on the left. This is only implemented and is applicable to RewDepUViews.

(⋪)Set k → UView c k v → UMap c Source #

Delete all keys in the given Set from the domain of the given map-like UView.

Spec: evalUnified (setSingleton hk ⋪ RewDepUView u0) evalUnified (setSingleton hk ⋪ SPoolUView u1)

domDeleteSet k → UView c k v → UMap c Source #

Delete all keys in the given Set from the domain of the given map-like UView.

Spec: evalUnified (setSingleton hk ⋪ RewDepUView u0) evalUnified (setSingleton hk ⋪ SPoolUView u1)

(⋫)UView c k v → Set v → UMap c Source #

Delete all elements in the given Set from the range of the given map-like UView. This is slow for SPoolUView, RewDepUView, and DReps UViews, better hope the sets are small

Spec: evalUnified (Ptrs u2 ⋫ setSingleton hk) evalUnified (SPoolUView u1 ⋫ retired)

rngDeleteUView c k v → Set v → UMap c Source #

Delete all elements in the given Set from the range of the given map-like UView. This is slow for SPoolUView, RewDepUView, and DReps UViews, better hope the sets are small

Spec: evalUnified (Ptrs u2 ⋫ setSingleton hk) evalUnified (SPoolUView u1 ⋫ retired)

(◁)UView c k v → Map k u → Map k u Source #

Domain restriction.

Spec: eval (dom rewards' ◁ iRReserves (_irwd ds) :: RewardAccounts (Crypto era)) eval (dom rewards' ◁ iRTreasury (_irwd ds) :: RewardAccounts (Crypto era))

domRestrictUView c k v → Map k u → Map k u Source #

Domain restriction.

Spec: eval (dom rewards' ◁ iRReserves (_irwd ds) :: RewardAccounts (Crypto era)) eval (dom rewards' ◁ iRTreasury (_irwd ds) :: RewardAccounts (Crypto era))

Derived functions

findWithDefault ∷ v → k → UView c k v → v Source #

Find the value associated with a key from a UView, return the default if the key is not there.

sizeUView c k v → Int Source #

A UView is a view, so the size of the view is NOT the same as the size of the underlying UMElem map.

domDeleteAllSet (Credential 'Staking c) → UMap c → UMap c Source #

Delete the stake credentials in the domain and all associated ranges from the UMap This can be expensive when there are many pointers associated with the credential.