Skip to content

Commit

Permalink
unit-test the newly introduced 'proportionallyTo'
Browse files Browse the repository at this point in the history
Getting this one wrong would be quite bad :s
  • Loading branch information
KtorZ committed Jul 6, 2020
1 parent 12b28f7 commit 547b130
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 19 deletions.
22 changes: 22 additions & 0 deletions lib/core/src/Cardano/Wallet/Primitive/CoinSelection.hs
Expand Up @@ -20,6 +20,7 @@ module Cardano.Wallet.Primitive.CoinSelection
, outputBalance
, changeBalance
, feeBalance
, proportionallyTo
, ErrCoinSelection (..)
, CoinSelectionOptions (..)
) where
Expand All @@ -30,6 +31,8 @@ import Cardano.Wallet.Primitive.Types
( Coin (..), TxIn, TxOut (..) )
import Data.List
( foldl' )
import Data.Ratio
( Ratio, denominator, numerator )
import Data.Word
( Word64, Word8 )
import Fmt
Expand Down Expand Up @@ -123,6 +126,25 @@ addTxOut total = addCoin total . coin
addCoin :: Integral a => a -> Coin -> a
addCoin total c = total + (fromIntegral (getCoin c))

-- | Compute the fraction of the first input to match the given ratio, rounded
-- down.
--
-- /invariant:/ The ratio mustn't be greater than 1 without risk to overflow.
--
-- >>> 10 `proportionallyTo` 1%1
-- 10
--
-- >>> 10 `proportionallyTo` 1%2
-- 5
--
-- >>> 10 `proportionallyTo` 1%3
-- 3
proportionallyTo :: Integral a => a -> Ratio a -> a
proportionallyTo n r
| r > 1 = error "proportionallyTo: ratio is greater than 1!"
| otherwise = fromIntegral $
toInteger n * toInteger (numerator r) `div` toInteger (denominator r)

data ErrCoinSelection e
= ErrNotEnoughMoney Word64 Word64
-- ^ UTxO exhausted during input selection
Expand Down
25 changes: 7 additions & 18 deletions lib/core/src/Cardano/Wallet/Primitive/CoinSelection/Random.hs
Expand Up @@ -18,7 +18,11 @@ module Cardano.Wallet.Primitive.CoinSelection.Random
import Prelude

import Cardano.Wallet.Primitive.CoinSelection
( CoinSelection (..), CoinSelectionOptions (..), ErrCoinSelection (..) )
( CoinSelection (..)
, CoinSelectionOptions (..)
, ErrCoinSelection (..)
, proportionallyTo
)
import Cardano.Wallet.Primitive.CoinSelection.LargestFirst
( largestFirst )
import Cardano.Wallet.Primitive.Types
Expand Down Expand Up @@ -51,10 +55,10 @@ import Data.Ord
( comparing )
import Data.Quantity
( Quantity (..) )
import Data.Ratio
( Ratio, denominator, numerator, (%) )
import Data.Word
( Word64 )
import Data.Ratio
( (%) )

import qualified Data.List as L
import qualified Data.List.NonEmpty as NE
Expand Down Expand Up @@ -278,18 +282,3 @@ mkChange (TxOut _ (Coin out)) inps =
[]
c ->
[ Coin c ]

-- | Compute the fraction of the first input to match the given ratio, rounded
-- down.
--
-- >>> 10 `proportionallyTo` 1%1
-- 10
--
-- >>> 10 `proportionallyTo` 1%2
-- 5
--
-- >>> 10 `proportionallyTo` 1%3
-- 3
proportionallyTo :: Integral a => a -> Ratio a -> a
proportionallyTo n r = fromIntegral $
toInteger n * toInteger (numerator r) `div` toInteger (denominator r)
29 changes: 28 additions & 1 deletion lib/core/test/unit/Cardano/Wallet/Primitive/CoinSelectionSpec.hs
Expand Up @@ -28,7 +28,11 @@ import Prelude
import Cardano.Wallet.Api.Server
( assignMigrationAddresses )
import Cardano.Wallet.Primitive.CoinSelection
( CoinSelection (..), CoinSelectionOptions (..), ErrCoinSelection (..) )
( CoinSelection (..)
, CoinSelectionOptions (..)
, ErrCoinSelection (..)
, proportionallyTo
)
import Cardano.Wallet.Primitive.Types
( Address (..)
, Coin (..)
Expand All @@ -47,6 +51,8 @@ import Data.Maybe
( catMaybes )
import Data.Quantity
( Quantity (..) )
import Data.Ratio
( Ratio, (%) )
import Data.Vector.Shuffle
( shuffle )
import Data.Word
Expand All @@ -65,13 +71,15 @@ import Test.QuickCheck
, applyArbitrary2
, checkCoverageWith
, choose
, conjoin
, counterexample
, cover
, elements
, generate
, scale
, vector
, (===)
, (==>)
)
import Test.QuickCheck.Monadic
( monadicIO )
Expand Down Expand Up @@ -101,6 +109,16 @@ spec = do
prop "All inputs are used" prop_allInputsAreUsed
prop "All inputs are used per transaction" prop_allInputsAreUsedPerTx
prop "Addresses are recycled fairly" prop_fairAddressesRecycled

describe "proportionallyTo" $ do
prop "proportionallyTo behaves as expected" prop_proportionallyTo
it "10 `proportionallyTo` 1%1 == 10" $
(10 `proportionallyTo` (1%1)) `shouldBe` (10 :: Integer)
it "10 `proportionallyTo` 1%2 == 5" $
(10 `proportionallyTo` (1%2)) `shouldBe` (5 :: Integer)
it "10 `proportionallyTo` 1%3 == 3" $
(10 `proportionallyTo` (1%3)) `shouldBe` (3 :: Integer)

where
lowerConfidence :: Confidence
lowerConfidence = Confidence (10^(6 :: Integer)) 0.75
Expand All @@ -109,6 +127,15 @@ spec = do
Properties
-------------------------------------------------------------------------------}

prop_proportionallyTo
:: Word8
-> Ratio Word8
-> Property
prop_proportionallyTo n r = conjoin
[ r <= 1 ==> n `proportionallyTo` r <= n
, n `proportionallyTo` 1 === n
]

prop_utxoToListOrderDeterministic
:: UTxO
-> Property
Expand Down

0 comments on commit 547b130

Please sign in to comment.