Skip to content
This repository was archived by the owner on Aug 18, 2020. It is now read-only.

Commit 0e61a0c

Browse files
Merge pull request #3730 from input-output-hk/adinapoli/always-sort-outputs-coin-selection
Always sort payees by amount
2 parents 09de855 + 2fde8ce commit 0e61a0c

File tree

2 files changed

+20
-15
lines changed

2 files changed

+20
-15
lines changed

src/Cardano/Wallet/Kernel/CoinSelection/FromGeneric.hs

+19-2
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
{-# LANGUAGE RankNTypes #-}
1+
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE ViewPatterns #-}
23
{-# OPTIONS_GHC -fno-warn-orphans #-}
34

45
module Cardano.Wallet.Kernel.CoinSelection.FromGeneric (
@@ -211,7 +212,23 @@ runCoinSelT :: forall m. Monad m
211212
=> NonEmpty (Output (Dom utxo))
212213
-> CoinSelT utxo CoinSelHardErr m [CoinSelResult (Dom utxo)])
213214
-> CoinSelPolicy Core.Utxo m CoinSelFinalResult
214-
runCoinSelT opts pickUtxo policy request utxo = do
215+
runCoinSelT opts pickUtxo policy (NE.sortBy (flip (comparing outVal)) -> request) utxo = do
216+
-- NOTE: we sort the payees by output value, to maximise our chances of succees.
217+
-- In particular, let's consider a scenario where:
218+
--
219+
-- 1. We have a payment request with two outputs, one smaller and one
220+
-- larger (but both relatively large)
221+
-- 2. Random selection tries to cover the smaller one first, fail because
222+
-- it exceeds the maximum number of inputs, fall back on largest first,
223+
-- which will pick the n largest outputs, and then traverse from from
224+
-- small to large to cover the payment.
225+
-- 3. It then tries to deal with the larger output, and fail because in
226+
-- step (2) we picked an output we needed due to only consider the n
227+
-- largest outputs (rather than sorting the entire UTxO,
228+
-- which would be much too expensive).
229+
--
230+
-- Therefore, just always considering them in order from large to small
231+
-- is probably a good idea.
215232
mSelection <- unwrapCoinSelT policy' utxo
216233
case mSelection of
217234
Left err -> return (Left err)

test/unit/Test/Spec/CoinSelection.hs

+1-13
Original file line numberDiff line numberDiff line change
@@ -495,16 +495,7 @@ payRestrictInputsTo :: Word64
495495
payRestrictInputsTo maxInputs genU genP feeFunction adjustOptions bal amount policy =
496496
withDefConfiguration $ \genesisConfig -> do
497497
utxo <- genU bal
498-
-- Sort the payees by amount, so that biggest entries comes first. This
499-
-- is to mitigate some pathological generator's corner cases in
500-
-- @largestFirst@ where the selection would pick the largest to cover
501-
-- the smallest inputs, not having enough Utxo to cover the rest. We do
502-
-- this here in the tests and not by modifying the coin selection code
503-
-- because we never run @largestFirst@ in production; in @random@ we
504-
-- merely piggyback on the @atLeast@ function (a low-level API used
505-
--for @largestFirst') but the @random@ policy doesn't require outputs
506-
-- to be sorted, and doing so every time would be a waste of CPU cycles.
507-
payee <- sortByAmount <$> genP utxo amount
498+
payee <- genP utxo amount
508499
key <- arbitrary
509500
let options = adjustOptions (newOptions feeFunction)
510501
res <- policy options
@@ -521,9 +512,6 @@ payRestrictInputsTo maxInputs genU genP feeFunction adjustOptions bal amount pol
521512
outputs
522513
change
523514
return (utxo, payee, bimap STB identity txAux)
524-
where
525-
sortByAmount :: NonEmpty Core.TxOut -> NonEmpty Core.TxOut
526-
sortByAmount = NE.sort
527515

528516
pay :: (InitialBalance -> Gen Core.Utxo)
529517
-> (Core.Utxo -> Pay -> Gen (NonEmpty Core.TxOut))

0 commit comments

Comments
 (0)