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.Fee

Contents

Description

Provides functionality for adjusting coin selections in order to pay for transaction fees.

Synopsis

Fundamental Types

newtype Fee Source #

Represents a non-negative fee to be paid on a transaction.

Since: 1.0.0

Constructors

Fee 

Fields

Instances
Eq Fee Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Methods

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

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

Ord Fee Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Methods

compare :: Fee -> Fee -> Ordering #

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

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

(>) :: Fee -> Fee -> Bool #

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

max :: Fee -> Fee -> Fee #

min :: Fee -> Fee -> Fee #

Show Fee Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Methods

showsPrec :: Int -> Fee -> ShowS #

show :: Fee -> String #

showList :: [Fee] -> ShowS #

Generic Fee Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Associated Types

type Rep Fee :: Type -> Type #

Methods

from :: Fee -> Rep Fee x #

to :: Rep Fee x -> Fee #

Semigroup Fee Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Methods

(<>) :: Fee -> Fee -> Fee #

sconcat :: NonEmpty Fee -> Fee #

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

Monoid Fee Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Methods

mempty :: Fee #

mappend :: Fee -> Fee -> Fee #

mconcat :: [Fee] -> Fee #

type Rep Fee Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

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

newtype FeeEstimator i o Source #

Provides a function capable of estimating the transaction fee required for a given coin selection, according to the rules of a particular blockchain.

The fee estimate should be a function of the current memberships of the inputs, outputs, and change sets.

Depending on the rules of the blockchain under consideration, the fee estimate may take either (or both) of the following factors into account:

  • the number of entries in each set;
  • the coin value of each set member.

A fee estimate may differ from the final fee required for a selection, as fees are generally paid for by adjusting a given selection to make a new selection. See adjustForFee for more details of this process.

Since: 1.0.0

Constructors

FeeEstimator 

Fields

Instances
Generic (FeeEstimator i o) Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Associated Types

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

Methods

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

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

type Rep (FeeEstimator i o) Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

type Rep (FeeEstimator i o) = D1 (MetaData "FeeEstimator" "Cardano.CoinSelection.Fee" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" True) (C1 (MetaCons "FeeEstimator" PrefixI True) (S1 (MetaSel (Just "estimateFee") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CoinSelection i o -> Fee))))

Fee Adjustment

adjustForFee :: (Ord i, MonadRandom m) => FeeOptions i o -> CoinMap i -> CoinSelection i o -> ExceptT (FeeAdjustmentError i o) m (CoinSelection i o) Source #

Adjusts the given CoinSelection in order to pay for a transaction fee, required in order to publish the selection as a transaction on a blockchain.

Background

Implementations of CoinSelectionAlgorithm generally produce coin selections that are exactly balanced, satisfying the following equality:

>>> sumInputs s = sumOutputs s + sumChange s

In order to pay for a transaction fee, the above equality must be transformed into an inequality:

>>> sumInputs s > sumOutputs s + sumChange s

The difference between these two sides represents value to be paid by the originator of the transaction, in the form of a fee:

>>> sumInputs s = sumOutputs s + sumChange s + fee

The Adjustment Process

In order to generate a fee that is acceptable to the network, this function adjusts the change and inputs of the given CoinSelection, consulting the FeeEstimator as a guide for how much the current selection would cost to publish as a transaction on the network.

Methods of Adjustment

There are two methods of adjustment possible:

  1. The change set can be reduced, either by:

    a. completely removing a change value from the set; or by

    b. reducing a change value to a lower value.

  2. The inputs set can be augmented, by selecting additional inputs from the specified CoinMap argument.

Dealing with Dust Values

If, at any point, a change value is generated that is less than or equal to the DustThreshold, this function will eliminate that change value from the change set, redistributing the eliminated value over the remaining change values, ensuring that the total value of all change is preserved.

See coalesceDust for more details.

Termination

Since adjusting a selection can affect the fee estimate produced by estimateFee, the process of adjustment is an iterative process.

The termination post-condition depends on the choice of FeeBalancingPolicy:

  • If RequireBalancedFee is specified, this function terminates only when it has generated a CoinSelection s that satisfies the following property:

    >>> sumInputs s = sumOutputs s + sumChange s + estimateFee s
    
  • If RequireMinimalFee policy is specified, the above equality is relaxed to the following inequality:

    >>> sumInputs s ≥ sumOutputs s + sumChange s + estimateFee s
    

See FeeBalancingPolicy for more details.

Since: 1.0.0

data FeeOptions i o Source #

Provides options for fee adjustment.

Since: 1.0.0

Constructors

FeeOptions 

Fields

Instances
Generic (FeeOptions i o) Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Associated Types

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

Methods

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

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

type Rep (FeeOptions i o) Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

type Rep (FeeOptions i o) = D1 (MetaData "FeeOptions" "Cardano.CoinSelection.Fee" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" False) (C1 (MetaCons "FeeOptions" PrefixI True) (S1 (MetaSel (Just "feeEstimator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (FeeEstimator i o)) :*: (S1 (MetaSel (Just "dustThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DustThreshold) :*: S1 (MetaSel (Just "feeBalancingPolicy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FeeBalancingPolicy))))

data FeeBalancingPolicy Source #

A choice of fee balancing policies for use when adjusting a coin selection.

Background

A coin selection s is said to have a perfectly-balanced fee when it satisfies the following property:

>>> sumInputs s = sumOutputs s + sumChange s + estimateFee s

Conversely, a selection is said to have an unbalanced fee when it satisfies the following property:

>>> sumInputs s > sumOutputs s + sumChange s + estimateFee s

In other words, if a coin selection has an unbalanced fee, the effective fee is greater than the minimum fee actually required by the blockchain.

Balanced Fees vs Minimal Fees

Some blockchains require that fees are always perfectly-balanced.

However, for blockchains that allow unbalanced fees, it is sometimes possible to save money by generating a coin selection with an unbalanced fee. This may seem counterintuitive at first, but consider an individual change ouput c of value v. If the marginal fee f associated with c is greater than its value v, then we will save money by not including c within change.

There are two policy choices available for handling change values with marginal fees greater than their value:

  • For blockchains that allow transactions with unbalanced fees, specifying the RequireMinimalFee policy will allow money to be saved by excluding change outputs that have a marginal fee greater than their value.
  • For blockchains that do not allow transactions with unbalanced fees, specifying the RequireBalancedFee policy will always generate selections with fees that are perfectly-balanced, even if the resulting fees are higher than could be achieved by allowing unbalanced fees.

Constructors

RequireBalancedFee

Generate selections with fees that are perfectly balanced, with the trade-off of allowing slightly higher fees.

RequireMinimalFee

Generate selections with the lowest fees possible, with the trade-off of allowing slightly imbalanced fees.

Instances
Eq FeeBalancingPolicy Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Show FeeBalancingPolicy Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Generic FeeBalancingPolicy Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Associated Types

type Rep FeeBalancingPolicy :: Type -> Type #

type Rep FeeBalancingPolicy Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

type Rep FeeBalancingPolicy = D1 (MetaData "FeeBalancingPolicy" "Cardano.CoinSelection.Fee" "cardano-coin-selection-1.0.1-ArWDQ7GeNjh2nML9dPNIzs" False) (C1 (MetaCons "RequireBalancedFee" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RequireMinimalFee" PrefixI False) (U1 :: Type -> Type))

data FeeAdjustmentError i o Source #

Represents the set of possible failures that can occur when adjusting a CoinSelection with the adjustForFee function.

Constructors

CannotCoverFee Fee

Indicates that the given map of additional inputs was exhausted while attempting to select extra inputs to cover the required fee.

Records the shortfall (fs) between the required fee f and the total value s of currently-selected inputs.

CoinSelectionUnderfunded (CoinSelection i o)

Indicates that the given coin selection is underfunded: the total value of inputs is less than the total value of outputs, as calculated by the coinMapValue function.

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

Defined in Cardano.CoinSelection.Fee

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

Defined in Cardano.CoinSelection.Fee

Dust Processing

newtype DustThreshold Source #

Defines the maximum size of a dust coin.

Functions that accept a DustThreshold argument will generally exclude values that are less than or equal to this threshold from the change sets of generated selections, coalescing such coins together into larger coins that exceed the threshold.

Specifying a dust threshold of n causes all coins that are less than or equal to n to be treated as dust and coalesced together.

Specifying a dust threshold of 0 completely disables dust elimination with the exception of zero-valued coins, which will always be eliminated.

See coalesceDust.

Since: 1.0.0

Constructors

DustThreshold 
Instances
Eq DustThreshold Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Ord DustThreshold Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Show DustThreshold Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Generic DustThreshold Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

Associated Types

type Rep DustThreshold :: Type -> Type #

type Rep DustThreshold Source # 
Instance details

Defined in Cardano.CoinSelection.Fee

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

isDust :: DustThreshold -> Coin -> Bool Source #

Returns True if and only if the given Coin is a dust coin according to the given DustThreshold.

A coin is considered to be a dust coin if it is less than or equal to the threshold.

See DustThreshold.

coalesceDust :: DustThreshold -> NonEmpty Coin -> [Coin] Source #

From the given list of coins, remove dust coins with a value less than or equal to the given threshold value, redistributing their total value over the coins that remain.

This function satisfies the following properties:

>>> sum coins = sum (coalesceDust threshold coins)
>>> all (/= Coin 0) (coalesceDust threshold coins)