cardano-coin-selection-1.0.1: Algorithms for coin selection and fee balancing.

Copyright© 2018-2020 IOHK
LicenseApache-2.0
Safe HaskellNone
LanguageHaskell2010

Cardano.CoinSelection

Contents

Description

Provides general functions and types relating to coin selection.

The CoinSelection type represents a coin selection, the basis for a transaction in a UTxO-based blockchain.

The CoinSelectionAlgorithm type provides a common interface to algorithms that generate coin selections.

For a guide to algorithms provided by this library, see the Cardano.CoinSelection.Algorithm module.

To adjust coin selections in order to pay for transaction fees, see the Cardano.CoinSelection.Fee module.

Synopsis

Coin Selections

data CoinSelection i o Source #

A coin selection is the basis for a transaction.

It consists of a selection of inputs, outputs, and change.

The inputs and outputs fields are both maps of unique keys to associated Coin values, where:

  • Each key-value pair in the inputs map corresponds to an unspent output from a previous transaction (also known as a UTxO). The key is a unique reference to that output, and the value is the amount of unspent value associated with it.
  • Each key-value pair in the outputs map corresponds to a payment. The key is a unique reference to a payment recipient, and the value is the amount of money to pay to that recipient.

The change field is a set of coins to be returned to the originator of the transaction.

The CoinSelectionAlgorithm type provides a common interface for generating coin selections.

Since: 1.0.0

Constructors

CoinSelection 

Fields

Instances
(Eq i, Eq o) => Eq (CoinSelection i o) Source # 
Instance details

Defined in Cardano.CoinSelection

Methods

(==) :: CoinSelection i o -> CoinSelection i o -> Bool #

(/=) :: CoinSelection i o -> CoinSelection i o -> Bool #

(Show i, Show o) => Show (CoinSelection i o) Source # 
Instance details

Defined in Cardano.CoinSelection

Generic (CoinSelection i o) Source # 
Instance details

Defined in Cardano.CoinSelection

Associated Types

type Rep (CoinSelection i o) :: Type -> Type #

Methods

from :: CoinSelection i o -> Rep (CoinSelection i o) x #

to :: Rep (CoinSelection i o) x -> CoinSelection i o #

(Ord i, Ord o) => Semigroup (CoinSelection i o) Source # 
Instance details

Defined in Cardano.CoinSelection

(Ord i, Ord o) => Monoid (CoinSelection i o) Source # 
Instance details

Defined in Cardano.CoinSelection

type Rep (CoinSelection i o) Source # 
Instance details

Defined in Cardano.CoinSelection

type Rep (CoinSelection i o) = D1 (MetaData "CoinSelection" "Cardano.CoinSelection" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" False) (C1 (MetaCons "CoinSelection" PrefixI True) (S1 (MetaSel (Just "inputs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CoinMap i)) :*: (S1 (MetaSel (Just "outputs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CoinMap o)) :*: S1 (MetaSel (Just "change") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Coin]))))

sumInputs :: CoinSelection i o -> Coin Source #

Calculate the total sum of all inputs for the given CoinSelection.

Since: 1.0.0

sumOutputs :: CoinSelection i o -> Coin Source #

Calculate the total sum of all outputs for the given CoinSelection.

Since: 1.0.0

sumChange :: CoinSelection i o -> Coin Source #

Calculate the total sum of all change for the given CoinSelection.

Since: 1.0.0

Coin Selection Algorithms

newtype CoinSelectionAlgorithm i o m Source #

Provides a common interface for coin selection algorithms.

The function selectCoins, when applied to the given CoinSelectionParameters object (with available inputs and requested outputs), will generate a CoinSelectionResult (with remaining inputs and a coin selection).

For implementations provided by this library, see Cardano.CoinSelection.Algorithm.

Since: 1.0.0

data CoinSelectionParameters i o Source #

The complete set of parameters required for a CoinSelectionAlgorithm.

The inputsAvailable and outputsRequested fields are both maps of unique keys to associated Coin values, where:

  • Each key-value pair in the inputsAvailable map corresponds to an unspent output from a previous transaction that is available for selection as an input by the coin selection algorithm. The key is a unique reference to that output, and the value is the amount of unspent value associated with it.
  • Each key-value pair in the outputsRequested map corresponds to a payment whose value is to be paid for by the coin selection algorithm. The key is a unique reference to a payment recipient, and the value is the amount of money to pay to that recipient.

A coin selection algorithm will select a subset of inputs from inputsAvailable in order to pay for all the outputs in outputsRequested, where:

The number of inputs that can selected is limited by limit.

The total value of inputsAvailable must be greater than or equal to the total value of outputsRequested, as given by the coinMapValue function.

Since: 1.0.0

Constructors

CoinSelectionParameters 

Fields

Instances
Generic (CoinSelectionParameters i o) Source # 
Instance details

Defined in Cardano.CoinSelection

Associated Types

type Rep (CoinSelectionParameters i o) :: Type -> Type #

type Rep (CoinSelectionParameters i o) Source # 
Instance details

Defined in Cardano.CoinSelection

type Rep (CoinSelectionParameters i o) = D1 (MetaData "CoinSelectionParameters" "Cardano.CoinSelection" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" False) (C1 (MetaCons "CoinSelectionParameters" PrefixI True) (S1 (MetaSel (Just "inputsAvailable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CoinMap i)) :*: (S1 (MetaSel (Just "outputsRequested") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CoinMap o)) :*: S1 (MetaSel (Just "limit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CoinSelectionLimit))))

data CoinSelectionResult i o Source #

Represents the result of running a coin selection algorithm.

See CoinSelectionAlgorithm.

Since: 1.0.0

Constructors

CoinSelectionResult 

Fields

Instances
(Eq i, Eq o) => Eq (CoinSelectionResult i o) Source # 
Instance details

Defined in Cardano.CoinSelection

(Show i, Show o) => Show (CoinSelectionResult i o) Source # 
Instance details

Defined in Cardano.CoinSelection

newtype CoinSelectionLimit Source #

Defines an inclusive upper bound on the number of inputs that a CoinSelectionAlgorithm is allowed to select.

Since: 1.0.0

Constructors

CoinSelectionLimit 

Fields

Instances
Generic CoinSelectionLimit Source # 
Instance details

Defined in Cardano.CoinSelection

Associated Types

type Rep CoinSelectionLimit :: Type -> Type #

type Rep CoinSelectionLimit Source # 
Instance details

Defined in Cardano.CoinSelection

type Rep CoinSelectionLimit = D1 (MetaData "CoinSelectionLimit" "Cardano.CoinSelection" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" True) (C1 (MetaCons "CoinSelectionLimit" PrefixI True) (S1 (MetaSel (Just "calculateLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Word16 -> Word16))))

Coins

data Coin Source #

Represents a non-negative integral amount of currency.

Use coinFromNatural to create a coin from a natural number.

Use coinToNatural to convert a coin into a natural number.

Since: 1.0.0

Instances
Eq Coin Source # 
Instance details

Defined in Internal.Coin

Methods

(==) :: Coin -> Coin -> Bool #

(/=) :: Coin -> Coin -> Bool #

Ord Coin Source # 
Instance details

Defined in Internal.Coin

Methods

compare :: Coin -> Coin -> Ordering #

(<) :: Coin -> Coin -> Bool #

(<=) :: Coin -> Coin -> Bool #

(>) :: Coin -> Coin -> Bool #

(>=) :: Coin -> Coin -> Bool #

max :: Coin -> Coin -> Coin #

min :: Coin -> Coin -> Coin #

Show Coin Source # 
Instance details

Defined in Internal.Coin

Methods

showsPrec :: Int -> Coin -> ShowS #

show :: Coin -> String #

showList :: [Coin] -> ShowS #

Generic Coin Source # 
Instance details

Defined in Internal.Coin

Associated Types

type Rep Coin :: Type -> Type #

Methods

from :: Coin -> Rep Coin x #

to :: Rep Coin x -> Coin #

Semigroup Coin Source # 
Instance details

Defined in Internal.Coin

Methods

(<>) :: Coin -> Coin -> Coin #

sconcat :: NonEmpty Coin -> Coin #

stimes :: Integral b => b -> Coin -> Coin #

Monoid Coin Source # 
Instance details

Defined in Internal.Coin

Methods

mempty :: Coin #

mappend :: Coin -> Coin -> Coin #

mconcat :: [Coin] -> Coin #

type Rep Coin Source # 
Instance details

Defined in Internal.Coin

type Rep Coin = D1 (MetaData "Coin" "Internal.Coin" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" True) (C1 (MetaCons "Coin" PrefixI True) (S1 (MetaSel (Just "unCoin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))

coinFromNatural :: Natural -> Coin Source #

Creates a coin from a natural number.

Since: 1.0.0

coinToNatural :: Coin -> Natural Source #

Converts the given coin into a natural number.

Since: 1.0.0

Coin Maps

newtype CoinMap a Source #

A mapping from unique keys to associated Coin values.

A CoinMap can be used to represent:

  • a UTxO set, where each key within the map refers to an unspent output from a previous transaction.
  • a set of inputs to a CoinSelection, where each input is an entry selected from a UTxO set by a CoinSelectionAlgorithm.
  • a set of outputs for a CoinSelection, where each key within the map refers to the address of a payment recipient.

A CoinMap can be constructed with the coinMapFromList function.

The total value of a CoinMap is given by the coinMapValue function.

Since: 1.0.0

Constructors

CoinMap 

Fields

Instances
Foldable CoinMap Source # 
Instance details

Defined in Cardano.CoinSelection

Methods

fold :: Monoid m => CoinMap m -> m #

foldMap :: Monoid m => (a -> m) -> CoinMap a -> m #

foldr :: (a -> b -> b) -> b -> CoinMap a -> b #

foldr' :: (a -> b -> b) -> b -> CoinMap a -> b #

foldl :: (b -> a -> b) -> b -> CoinMap a -> b #

foldl' :: (b -> a -> b) -> b -> CoinMap a -> b #

foldr1 :: (a -> a -> a) -> CoinMap a -> a #

foldl1 :: (a -> a -> a) -> CoinMap a -> a #

toList :: CoinMap a -> [a] #

null :: CoinMap a -> Bool #

length :: CoinMap a -> Int #

elem :: Eq a => a -> CoinMap a -> Bool #

maximum :: Ord a => CoinMap a -> a #

minimum :: Ord a => CoinMap a -> a #

sum :: Num a => CoinMap a -> a #

product :: Num a => CoinMap a -> a #

Eq a => Eq (CoinMap a) Source # 
Instance details

Defined in Cardano.CoinSelection

Methods

(==) :: CoinMap a -> CoinMap a -> Bool #

(/=) :: CoinMap a -> CoinMap a -> Bool #

Show a => Show (CoinMap a) Source # 
Instance details

Defined in Cardano.CoinSelection

Methods

showsPrec :: Int -> CoinMap a -> ShowS #

show :: CoinMap a -> String #

showList :: [CoinMap a] -> ShowS #

Generic (CoinMap a) Source # 
Instance details

Defined in Cardano.CoinSelection

Associated Types

type Rep (CoinMap a) :: Type -> Type #

Methods

from :: CoinMap a -> Rep (CoinMap a) x #

to :: Rep (CoinMap a) x -> CoinMap a #

Ord a => Semigroup (CoinMap a) Source # 
Instance details

Defined in Cardano.CoinSelection

Methods

(<>) :: CoinMap a -> CoinMap a -> CoinMap a #

sconcat :: NonEmpty (CoinMap a) -> CoinMap a #

stimes :: Integral b => b -> CoinMap a -> CoinMap a #

Ord a => Monoid (CoinMap a) Source # 
Instance details

Defined in Cardano.CoinSelection

Methods

mempty :: CoinMap a #

mappend :: CoinMap a -> CoinMap a -> CoinMap a #

mconcat :: [CoinMap a] -> CoinMap a #

type Rep (CoinMap a) Source # 
Instance details

Defined in Cardano.CoinSelection

type Rep (CoinMap a) = D1 (MetaData "CoinMap" "Cardano.CoinSelection" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" True) (C1 (MetaCons "CoinMap" PrefixI True) (S1 (MetaSel (Just "unCoinMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map a Coin))))

data CoinMapEntry a Source #

An entry for a CoinMap.

Since: 1.0.0

Constructors

CoinMapEntry 

Fields

  • entryKey :: a

    The unique key associated with this entry.

  • entryValue :: Coin

    The coin value associated with this entry.

Instances
Eq a => Eq (CoinMapEntry a) Source # 
Instance details

Defined in Cardano.CoinSelection

Ord a => Ord (CoinMapEntry a) Source # 
Instance details

Defined in Cardano.CoinSelection

Show a => Show (CoinMapEntry a) Source # 
Instance details

Defined in Cardano.CoinSelection

Generic (CoinMapEntry a) Source # 
Instance details

Defined in Cardano.CoinSelection

Associated Types

type Rep (CoinMapEntry a) :: Type -> Type #

Methods

from :: CoinMapEntry a -> Rep (CoinMapEntry a) x #

to :: Rep (CoinMapEntry a) x -> CoinMapEntry a #

type Rep (CoinMapEntry a) Source # 
Instance details

Defined in Cardano.CoinSelection

type Rep (CoinMapEntry a) = D1 (MetaData "CoinMapEntry" "Cardano.CoinSelection" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" False) (C1 (MetaCons "CoinMapEntry" PrefixI True) (S1 (MetaSel (Just "entryKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "entryValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Coin)))

coinMapFromList :: Ord a => [CoinMapEntry a] -> CoinMap a Source #

Constructs a CoinMap from a list of entries.

See CoinMapEntry.

Since: 1.0.0

coinMapToList :: CoinMap a -> [CoinMapEntry a] Source #

Converts a CoinMap to a list of entries.

See CoinMapEntry.

Since: 1.0.0

coinMapValue :: CoinMap a -> Coin Source #

Calculates the total coin value associated with a CoinMap.

Since: 1.0.0

Coin Selection Errors

data InputValueInsufficientError Source #

Indicates that the total value of inputsAvailable is less than the total value of outputsRequested, making it impossible to cover all payments, regardless of which algorithm is chosen.

Since: 1.0.0

data InputCountInsufficientError Source #

Indicates that the total count of entries in inputsAvailable is fewer than required by the algorithm. The number required depends on the particular algorithm implementation.

Since: 1.0.0

Constructors

InputCountInsufficientError 

Fields

newtype InputLimitExceededError Source #

Indicates that the coin selection algorithm is unable to cover the total value of outputsRequested without exceeding the maximum number of inputs defined by limit.

See calculateLimit.

Since: 1.0.0

data InputsExhaustedError Source #

Indicates that all available entries in inputsAvailable were depleted before all the payments in outputsRequested could be paid for.

This condition can occur even if the total value of inputsAvailable is greater than or equal to the total value of outputsRequested, due to differences in the way that algorithms select inputs.

Since: 1.0.0

Constructors

InputsExhaustedError