Skip to content

Commit

Permalink
Make internal Selection type monomorphic in the type of change.
Browse files Browse the repository at this point in the history
The original `Selection` type was polymorphic in the type of change
outputs. The intention behind this was to allow the wallet to reuse the
`Selection` type in different contexts, both before and after assigning
change outputs with addresses.

However, the internal coin selection library is not concerned with
assigning addresses to change outputs. Assigning change addresses is a
function of the wallet, rather than the coin selection library, and the
coin selection library should not have to be concerned with this detail.

Moreover, requiring the internal coin selection library's `Selection` type
to be polymorphic in the type of change outputs makes the internal
library functions and types more complicated than necessary.

This change forks the `Selection` type into two separate types:

  - A wallet-specific type,
    located in `Cardano.Wallet.CoinSelection`,
    where the type of `change` is kept polymorphic (as it currently is).

  - An internal type,
    located in `Cardano.Wallet.CoinSelection.Internal`,
    where the type of `change` is simply `TokenBundle`.

We also provide a pair of functions `selection{To,From}InternalSelection`
located in `Cardano.Wallet.CoinSelection` to handle conversion between these
two types.

The forking of this type into two will make it easier to make further
simplifications to the internal type, as we can restrict any breakage
to the `selection{To,From}InternalSelection` functions.
  • Loading branch information
jonathanknowles committed Feb 8, 2022
1 parent 8d22a6c commit 2d92cd9
Show file tree
Hide file tree
Showing 2 changed files with 110 additions and 30 deletions.
111 changes: 106 additions & 5 deletions lib/core/src/Cardano/Wallet/CoinSelection.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,17 +58,13 @@ module Cardano.Wallet.CoinSelection
where

import Cardano.Wallet.CoinSelection.Internal
( Selection
, SelectionCollateralRequirement (..)
( SelectionCollateralRequirement (..)
, SelectionConstraints (..)
, SelectionError (..)
, SelectionOf (..)
, SelectionOutputError (..)
, SelectionOutputSizeExceedsLimitError (..)
, SelectionOutputTokenQuantityExceedsLimitError (..)
, SelectionParams (..)
, performSelection
, selectionDelta
)
import Cardano.Wallet.CoinSelection.Internal.Balance
( BalanceInsufficientError (..)
Expand All @@ -86,21 +82,126 @@ import Cardano.Wallet.Primitive.Types.Coin
( Coin (..) )
import Cardano.Wallet.Primitive.Types.TokenBundle
( TokenBundle )
import Cardano.Wallet.Primitive.Types.TokenMap
( TokenMap )
import Cardano.Wallet.Primitive.Types.Tx
( TxIn, TxOut (..) )
import Control.Monad.Random.Class
( MonadRandom (..) )
import Control.Monad.Trans.Except
( ExceptT (..) )
import Data.Generics.Internal.VL.Lens
( over, view )
import Data.List.NonEmpty
( NonEmpty )
import Fmt
( Buildable (..), genericF )
import GHC.Generics
( Generic )
import GHC.Stack
( HasCallStack )

import Prelude

import qualified Cardano.Wallet.CoinSelection.Internal as Internal
import qualified Cardano.Wallet.Primitive.Types.TokenBundle as TokenBundle
import qualified Data.Foldable as F
import qualified Data.Set as Set

--------------------------------------------------------------------------------
-- Types
--------------------------------------------------------------------------------

-- | Represents a balanced selection.
--
data SelectionOf change = Selection
{ inputs
:: !(NonEmpty (TxIn, TxOut))
-- ^ Selected inputs.
, collateral
:: ![(TxIn, TxOut)]
-- ^ Selected collateral inputs.
, outputs
:: ![TxOut]
-- ^ User-specified outputs
, change
:: ![change]
-- ^ Generated change outputs.
, assetsToMint
:: !TokenMap
-- ^ Assets to mint.
, assetsToBurn
:: !TokenMap
-- ^ Assets to burn.
, extraCoinSource
:: !Coin
-- ^ An extra source of ada.
, extraCoinSink
:: !Coin
-- ^ An extra sink for ada.
}
deriving (Generic, Eq, Show)

-- | The default type of selection.
--
-- In this type of selection, change values do not have addresses assigned.
--
type Selection = SelectionOf TokenBundle

selectionFromInternalSelection
:: Internal.Selection
-> Selection
selectionFromInternalSelection Internal.Selection {..} =
Selection {..}

selectionToInternalSelection
:: (change -> TokenBundle)
-> SelectionOf change
-> Internal.Selection
selectionToInternalSelection getChangeBundle Selection {..} =
Internal.Selection
{ change = getChangeBundle <$> change
, ..
}

--------------------------------------------------------------------------------
-- Performing a selection
--------------------------------------------------------------------------------

-- | Performs a coin selection.
--
-- This function has the following responsibilities:
--
-- - selecting inputs from the UTxO set to pay for user-specified outputs;
-- - selecting inputs from the UTxO set to pay for collateral;
-- - producing change outputs to return excess value to the wallet;
-- - balancing a selection to pay for the transaction fee.
--
-- See 'Internal.performSelection' for more details.
--
performSelection
:: (HasCallStack, MonadRandom m)
=> SelectionConstraints
-> SelectionParams
-> ExceptT SelectionError m Selection
performSelection cs ps =
selectionFromInternalSelection <$> Internal.performSelection cs ps

--------------------------------------------------------------------------------
-- Selection deltas
--------------------------------------------------------------------------------

-- | Computes the ada surplus of a selection, assuming there is a surplus.
--
selectionDelta
:: (change -> Coin)
-- ^ A function to extract the coin value from a change value.
-> SelectionOf change
-> Coin
selectionDelta getChangeCoin
= Internal.selectionSurplusCoin
. selectionToInternalSelection (TokenBundle.fromCoin . getChangeCoin)

--------------------------------------------------------------------------------
-- Reporting
--------------------------------------------------------------------------------
Expand Down
29 changes: 4 additions & 25 deletions lib/core/src/Cardano/Wallet/CoinSelection/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,10 +20,9 @@ module Cardano.Wallet.CoinSelection.Internal
(
-- * Performing selections
performSelection
, Selection
, Selection (..)
, SelectionConstraints (..)
, SelectionError (..)
, SelectionOf (..)
, SelectionParams (..)

-- * Output preparation
Expand All @@ -41,11 +40,11 @@ module Cardano.Wallet.CoinSelection.Internal

-- * Selection deltas
, SelectionDelta (..)
, selectionDelta
, selectionDeltaAllAssets
, selectionDeltaCoin
, selectionHasValidSurplus
, selectionMinimumCost
, selectionSurplusCoin

-- * Selection collateral
, SelectionCollateralRequirement (..)
Expand Down Expand Up @@ -244,7 +243,7 @@ data SelectionError

-- | Represents a balanced selection.
--
data SelectionOf change = Selection
data Selection = Selection
{ inputs
:: !(NonEmpty (TxIn, TxOut))
-- ^ Selected inputs.
Expand All @@ -255,7 +254,7 @@ data SelectionOf change = Selection
:: ![TxOut]
-- ^ User-specified outputs
, change
:: ![change]
:: ![TokenBundle]
-- ^ Generated change outputs.
, assetsToMint
:: !TokenMap
Expand All @@ -272,12 +271,6 @@ data SelectionOf change = Selection
}
deriving (Generic, Eq, Show)

-- | The default type of selection.
--
-- In this type of selection, change values do not have addresses assigned.
--
type Selection = SelectionOf TokenBundle

-- | Provides a context for functions related to 'performSelection'.

type PerformSelection m a =
Expand Down Expand Up @@ -1187,20 +1180,6 @@ verifySelectionOutputTokenQuantityExceedsLimitError _cs _ps e =
-- Selection deltas
--------------------------------------------------------------------------------

-- | Computes the ada surplus of a selection, assuming there is a surplus.
--
-- This function is a convenient synonym for 'selectionSurplusCoin' that is
-- polymorphic over the type of change.
--
selectionDelta
:: (change -> Coin)
-- ^ A function to extract the coin value from a change value.
-> SelectionOf change
-> Coin
selectionDelta getChangeCoin selection
= selectionSurplusCoin
$ selection & over #change (fmap $ TokenBundle.fromCoin . getChangeCoin)

-- | Calculates the selection delta for all assets.
--
-- See 'SelectionDelta'.
Expand Down

0 comments on commit 2d92cd9

Please sign in to comment.