atlas-cardano-0.13.0: Application backend for Plutus smart contracts on Cardano
Copyright© 2018-2021 IOHK 2025 GYELD GMBH
LicenseApache-2.0
Safe HaskellSafe-Inferred
LanguageGHC2021

GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Description

Modified by: GeniusYield

Originally from: Cardano.CoinSelection.UTxOIndex.Internal.

Provides internal functions for the UTxOIndex type, which indexes a UTxO set by asset identifier.

The index makes it possible to efficiently compute the subset of a UTxO set containing a particular asset, or to select just a single UTxO containing a particular asset, without having to search linearly through the entire UTxO set.

See the documentation for UTxOIndex for more details.

Synopsis

Type

data UTxOIndex u #

A UTxO set that is indexed by asset identifier.

The index provides a mapping from assets to subsets of the UTxO set.

A UTxO appears in the set for a particular asset if and only if its associated value has a non-zero quantity of that asset.

The index makes it possible to efficiently compute the subset of a UTxO set containing a particular asset, or to select just a single UTxO containing a particular asset, without having to search linearly through the entire UTxO set.

The index also keeps track of the current UTxO balance of all assets, making it possible to efficiently look up the total quantity of a particular asset without having to sum across the entire UTxO set.

The UTxO index data structure has an invariant that can be checked with the checkInvariant function.

Instances

Instances details
Generic (UTxOIndex u) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Associated Types

type Rep (UTxOIndex u) ∷ TypeType #

Methods

fromUTxOIndex u → Rep (UTxOIndex u) x #

toRep (UTxOIndex u) x → UTxOIndex u #

Show u ⇒ Show (UTxOIndex u) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

showsPrecIntUTxOIndex u → ShowS #

showUTxOIndex u → String #

showList ∷ [UTxOIndex u] → ShowS #

Eq u ⇒ Eq (UTxOIndex u) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

(==)UTxOIndex u → UTxOIndex u → Bool #

(/=)UTxOIndex u → UTxOIndex u → Bool #

type Rep (UTxOIndex u) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

type Rep (UTxOIndex u) = D1 ('MetaData "UTxOIndex" "GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal" "atlas-cardano-0.13.0-inplace" 'False) (C1 ('MetaCons "UTxOIndex" 'PrefixI 'True) ((S1 ('MetaSel ('Just "indexAll") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MonoidMap GYAssetClass (Set u))) :*: S1 ('MetaSel ('Just "indexSingletons") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MonoidMap GYAssetClass (Set u)))) :*: (S1 ('MetaSel ('Just "indexPairs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MonoidMap GYAssetClass (Set u))) :*: (S1 ('MetaSel ('Just "balance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GYValue) :*: S1 ('MetaSel ('Just "universe") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map u GYValue))))))

Construction

emptyUTxOIndex u #

An index with no entries.

singletonOrd u ⇒ u → GYValueUTxOIndex u #

Creates a singleton index from the specified UTxO identifier and value.

fromSequence ∷ (Foldable f, Ord u) ⇒ f (u, GYValue) → UTxOIndex u #

Constructs an index from a sequence of entries.

Note that this operation is potentially expensive as it must construct an index from scratch, and therefore should only be used sparingly.

If the given sequence contains more than one mapping for the same UTxO identifier, the mapping that appears latest in the sequence will take precedence, and all others will be ignored.

fromMapOrd u ⇒ Map u GYValueUTxOIndex u #

Constructs an index from a map.

Note that this operation is potentially expensive as it must construct an index from scratch, and therefore should only be used sparingly.

Satisfies the following property:

fromMapfromSequence . toList

Deconstruction

toListUTxOIndex u → [(u, GYValue)] #

Converts an index to a list of its constituent entries.

Consider using fold if your goal is to consume all entries in the output.

toMapUTxOIndex u → Map u GYValue #

Converts an index into a map.

Consider using fold if your goal is to consume all entries in the output.

Folding

fold ∷ (a → u → GYValue → a) → a → UTxOIndex u → a #

Folds strictly over the constituent entries of an index.

Modification

insertOrd u ⇒ u → GYValueUTxOIndex u → UTxOIndex u #

Inserts an entry that maps the given UTxO identifier to the given value.

If the index has an existing value for the specified UTxO identifier, the value referred to by that identifier will be replaced with the specified value.

insertMany ∷ (Foldable f, Ord u) ⇒ f (u, GYValue) → UTxOIndex u → UTxOIndex u #

Inserts multiple entries into an index.

See insert.

delete ∷ ∀ u. Ord u ⇒ u → UTxOIndex u → UTxOIndex u #

Deletes the entry corresponding to the given UTxO identifier.

If the index has no existing entry for the specified identifier, the result of applying this function will be equivalent to the identity function.

deleteMany ∷ (Foldable f, Ord u) ⇒ f u → UTxOIndex u → UTxOIndex u #

Deletes multiple entries from an index.

See delete.

Filtering and partitioning

filterOrd u ⇒ (u → Bool) → UTxOIndex u → UTxOIndex u #

Filters an index.

partitionOrd u ⇒ (u → Bool) → UTxOIndex u → (UTxOIndex u, UTxOIndex u) #

Partitions an index.

Queries

assetsUTxOIndex u → Set GYAssetClass #

Returns the complete set of all assets contained in an index.

lookupOrd u ⇒ u → UTxOIndex u → Maybe GYValue #

Returns the value corresponding to the given UTxO identifier.

If the index has no such identifier, this function returns Nothing.

memberOrd u ⇒ u → UTxOIndex u → Bool #

Returns True if (and only if) the index has an entry for the given UTxO identifier.

nullUTxOIndex u → Bool #

Returns True if (and only if) the index is empty.

sizeUTxOIndex u → Int #

Returns the total number of UTxO entries held within the index.

Set operations

differenceOrd u ⇒ UTxOIndex u → UTxOIndex u → UTxOIndex u #

Creates a new index by subtracting the second index from the first.

This operation is fast if the intersection of the first and second indices is small relative to the size of the first index.

disjointOrd u ⇒ UTxOIndex u → UTxOIndex u → Bool #

Indicates whether a pair of UTxO indices are disjoint.

Selection

data SelectionFilter asset #

Specifies a filter for selecting UTxO entries.

Constructors

SelectSingleton asset

Matches UTxOs that contain only the given asset and no other assets.

SelectPairWith asset

Matches UTxOs that contain the given asset and exactly one other asset.

SelectAnyWith asset

Matches UTxOs that contain the given asset and any number of other assets.

SelectAny

Matches all UTxOs regardless of what assets they contain.

Instances

Instances details
Foldable SelectionFilter # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

foldMonoid m ⇒ SelectionFilter m → m #

foldMapMonoid m ⇒ (a → m) → SelectionFilter a → m #

foldMap'Monoid m ⇒ (a → m) → SelectionFilter a → m #

foldr ∷ (a → b → b) → b → SelectionFilter a → b #

foldr' ∷ (a → b → b) → b → SelectionFilter a → b #

foldl ∷ (b → a → b) → b → SelectionFilter a → b #

foldl' ∷ (b → a → b) → b → SelectionFilter a → b #

foldr1 ∷ (a → a → a) → SelectionFilter a → a #

foldl1 ∷ (a → a → a) → SelectionFilter a → a #

toListSelectionFilter a → [a] #

nullSelectionFilter a → Bool #

lengthSelectionFilter a → Int #

elemEq a ⇒ a → SelectionFilter a → Bool #

maximumOrd a ⇒ SelectionFilter a → a #

minimumOrd a ⇒ SelectionFilter a → a #

sumNum a ⇒ SelectionFilter a → a #

productNum a ⇒ SelectionFilter a → a #

Traversable SelectionFilter # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

traverseApplicative f ⇒ (a → f b) → SelectionFilter a → f (SelectionFilter b) #

sequenceAApplicative f ⇒ SelectionFilter (f a) → f (SelectionFilter a) #

mapMMonad m ⇒ (a → m b) → SelectionFilter a → m (SelectionFilter b) #

sequenceMonad m ⇒ SelectionFilter (m a) → m (SelectionFilter a) #

Functor SelectionFilter # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

fmap ∷ (a → b) → SelectionFilter a → SelectionFilter b #

(<$) ∷ a → SelectionFilter b → SelectionFilter a #

Show asset ⇒ Show (SelectionFilter asset) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

showsPrecIntSelectionFilter asset → ShowS #

showSelectionFilter asset → String #

showList ∷ [SelectionFilter asset] → ShowS #

Eq asset ⇒ Eq (SelectionFilter asset) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

(==)SelectionFilter asset → SelectionFilter asset → Bool #

(/=)SelectionFilter asset → SelectionFilter asset → Bool #

selectRandom ∷ ∀ m u. (MonadRandom m, Ord u) ⇒ UTxOIndex u → SelectionFilter GYAssetClass → m (Maybe ((u, GYValue), UTxOIndex u)) #

Selects an entry at random from the index according to the given filter.

Returns the selected entry and an updated index with the entry removed.

Returns Nothing if there were no matching entries.

selectRandomWithPriority #

Arguments

∷ (MonadRandom m, Ord u) 
UTxOIndex u 
NonEmpty (SelectionFilter GYAssetClass)

A list of selection filters to be traversed in descending order of priority, from left to right.

→ m (Maybe ((u, GYValue), UTxOIndex u)) 

Selects an entry at random from the index according to the given filters.

This function traverses the specified list of filters in descending order of priority, from left to right.

When considering a particular filter:

  • if the function is able to select a UTxO entry that matches, it terminates with that entry and an updated index with the entry removed.
  • if the function is not able to select a UTxO entry that matches, it traverses to the next filter available.

This function returns Nothing if (and only if) it traverses the entire list of filters without successfully selecting a UTxO entry.

Value categorization

data ValueCategory asset #

Represents different categories of value.

Instances

Instances details
Show asset ⇒ Show (ValueCategory asset) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

showsPrecIntValueCategory asset → ShowS #

showValueCategory asset → String #

showList ∷ [ValueCategory asset] → ShowS #

Eq asset ⇒ Eq (ValueCategory asset) # 
Instance details

Defined in GeniusYield.Transaction.CoinSelection.UTxOIndex.Internal

Methods

(==)ValueCategory asset → ValueCategory asset → Bool #

(/=)ValueCategory asset → ValueCategory asset → Bool #

categorizeValueGYValueValueCategory GYAssetClass #

Categorizes a value by how many assets it contains.

Utilities

selectRandomSetMemberMonadRandom m ⇒ Set a → m (Maybe a) #

Selects an element at random from the given set.

Returns Nothing if (and only if) the given set is empty.

Invariant

data InvariantStatus #

The result of checking the invariant with the checkInvariant function.

Constructors

InvariantHolds

Indicates a successful check of the invariant.

InvariantBalanceError BalanceError

Indicates that the cached balance value is incorrect.

InvariantIndexIncomplete

Indicates that the index is missing one or more entries.

InvariantIndexNonMinimal

Indicates that the index has one or more unnecessary entries.

InvariantIndexInconsistent

Indicates that the index sets are not consistent.

InvariantAssetsInconsistent

Indicates that the index and the cached balance value disagree about which assets are included.

checkInvariantOrd u ⇒ UTxOIndex u → InvariantStatus #

Checks whether or not the invariant holds.