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

Commit 1453a90

Browse files
authored
Merge pull request #3443 from input-output-hk/bugfix/avoid-overflow-in-updateUTxO
[CBR-227] Avoid overflow in `updateUTxO`
2 parents a98100a + 1f41420 commit 1453a90

File tree

7 files changed

+35
-36
lines changed

7 files changed

+35
-36
lines changed

wallet-new/src/Cardano/Wallet/Kernel/DB/Spec.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -114,7 +114,8 @@ deriveSafeCopy 1 'base ''Checkpoint
114114
initCheckpoint :: Core.Utxo -> Checkpoint
115115
initCheckpoint utxo = Checkpoint {
116116
_checkpointUtxo = InDb utxo
117-
, _checkpointUtxoBalance = InDb $ Core.utxoBalance utxo
117+
, _checkpointUtxoBalance = InDb $ Core.unsafeIntegerToCoin $
118+
Core.utxoBalance utxo
118119
, _checkpointPending = Pending.empty
119120
, _checkpointForeign = Pending.empty
120121
, _checkpointBlockMeta = emptyBlockMeta

wallet-new/src/Cardano/Wallet/Kernel/DB/Spec/Read.hs

+7-5
Original file line numberDiff line numberDiff line change
@@ -55,10 +55,11 @@ cpAvailableBalance :: IsCheckpoint c => c -> Core.Coin
5555
cpAvailableBalance c =
5656
fromMaybe subCoinErr balance'
5757
where
58-
pendingIns = Pending.txIns (c ^. cpPending)
59-
spentUtxo = Core.utxoRestrictToInputs (c ^. cpUtxo) pendingIns
60-
balance' = Core.subCoin (c ^. cpUtxoBalance) (Core.utxoBalance spentUtxo)
61-
subCoinErr = error "cpAvailableBalance: spent more than available?"
58+
pendingIns = Pending.txIns (c ^. cpPending)
59+
spentUtxo = Core.utxoRestrictToInputs (c ^. cpUtxo) pendingIns
60+
spentBalance = Core.unsafeIntegerToCoin $ Core.utxoBalance spentUtxo
61+
balance' = Core.subCoin (c ^. cpUtxoBalance) spentBalance
62+
subCoinErr = error "cpAvailableBalance: spent more than available?"
6263

6364
-- | Change outputs
6465
--
@@ -78,7 +79,8 @@ cpTotalBalance ours c =
7879
Core.unsafeAddCoin availableBalance changeBalance
7980
where
8081
availableBalance = cpAvailableBalance c
81-
changeBalance = Core.utxoBalance (cpChange ours c)
82+
changeBalance = Core.unsafeIntegerToCoin $
83+
Core.utxoBalance (cpChange ours c)
8284

8385
-- | SlotId a transaction got confirmed in
8486
cpTxSlotId :: IsCheckpoint c => Core.TxId -> c -> Maybe Core.SlotId

wallet-new/src/Cardano/Wallet/Kernel/DB/Spec/Update.hs

+4-3
Original file line numberDiff line numberDiff line change
@@ -301,9 +301,10 @@ updateUtxo PrefilteredBlock{..} (utxo, balance) =
301301
utxoUnion = Map.union utxo pfbOutputs
302302
utxoMin = utxoUnion `Core.utxoRestrictToInputs` pfbInputs
303303
utxo' = utxoUnion `Core.utxoRemoveInputs` pfbInputs
304-
balance' = fromMaybe (error "updateUtxo: out-of-range impossible") $ do
305-
withNew <- Core.addCoin balance (Core.utxoBalance pfbOutputs)
306-
Core.subCoin withNew (Core.utxoBalance utxoMin)
304+
balance' = Core.unsafeIntegerToCoin $
305+
Core.coinToInteger balance
306+
+ Core.utxoBalance pfbOutputs
307+
- Core.utxoBalance utxoMin
307308

308309
-- | Update the pending transactions with the given prefiltered block
309310
--

wallet-new/src/Cardano/Wallet/Kernel/Transactions.hs

+5-2
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ import Formatting (bprint, build, sformat, (%))
3232
import qualified Formatting.Buildable
3333

3434
import Pos.Chain.Txp (Utxo)
35-
import Pos.Core (Address, Coin, unsafeSubCoin)
35+
import Pos.Core (Address, Coin, unsafeIntegerToCoin, unsafeSubCoin)
3636
import qualified Pos.Core as Core
3737
import Pos.Core.Txp (Tx (..), TxAux (..), TxId, TxIn (..), TxOut (..),
3838
TxOutAux (..))
@@ -342,10 +342,13 @@ estimateFees activeWallet@ActiveWallet{..} spendingPassword options accountId pa
342342
return $ Right
343343
$ sumOfInputs tx originalUtxo `unsafeSubCoin` sumOfOutputs tx
344344
where
345+
-- Unlike a block, a /single transaction/ cannot have inputs that sum to
346+
-- more than maxCoinVal
345347
sumOfInputs :: TxAux -> Utxo -> Coin
346348
sumOfInputs tx utxo =
347349
let inputs = Set.fromList $ toList . _txInputs . taTx $ tx
348-
in utxoBalance (utxo `utxoRestrictToInputs` inputs)
350+
in unsafeIntegerToCoin $
351+
utxoBalance (utxo `utxoRestrictToInputs` inputs)
349352

350353
sumOfOutputs :: TxAux -> Coin
351354
sumOfOutputs tx =

wallet-new/src/Cardano/Wallet/Kernel/Util/Core.hs

+9-12
Original file line numberDiff line numberDiff line change
@@ -54,19 +54,16 @@ getSomeTimestamp = Core.Timestamp $ fromMicroseconds 12340000
5454
UTxO
5555
-------------------------------------------------------------------------------}
5656

57-
-- | Computes the balance for this 'Utxo'. We use 'unsafeAddCoin' as
58-
-- as long as the 'maxCoinVal' stays within the 'Word64' 'maxBound', the
59-
-- circulating supply of coins is finite and as such we should never have
60-
-- to sum an 'Utxo' which would exceed the bounds.
61-
-- If it does, this is clearly a bug and we throw an 'ErrorCall' exception
62-
-- (crf. 'unsafeAddCoin' implementation).
63-
utxoBalance :: Core.Utxo -> Core.Coin
64-
utxoBalance = foldl' updateFn (Core.mkCoin 0) . Map.elems
57+
-- | Computes the balance for this UTxO
58+
--
59+
-- This returns an 'Integer' rather than a 'Coin' because the outputs of a
60+
-- block may sum to more than 'maxCoinVal' (if some outputs of the transactions
61+
-- in the block are used as inputs by other transactions in that block).
62+
utxoBalance :: Core.Utxo -> Integer
63+
utxoBalance = foldl' updateFn 0 . Map.elems
6564
where
66-
updateFn :: Core.Coin -> Core.TxOutAux -> Core.Coin
67-
updateFn acc txOutAux =
68-
fromMaybe (error "utxoBalance: overflow") $
69-
Core.addCoin acc (toCoin txOutAux)
65+
updateFn :: Integer -> Core.TxOutAux -> Integer
66+
updateFn acc txOut = acc + Core.coinToInteger (toCoin txOut)
7067

7168
-- | Restricts the 'Utxo' to only the selected set of inputs.
7269
utxoRestrictToInputs :: Core.Utxo -> Set Core.TxIn -> Core.Utxo

wallet-new/test/unit/Test/Spec/CoinSelection.hs

+5-5
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ import qualified Text.Tabl as Tabl
2525

2626
import Pos.Binary.Class (Bi (encode), toLazyByteString)
2727
import qualified Pos.Chain.Txp as Core
28-
import Pos.Core (Coeff (..), TxSizeLinear (..))
28+
import Pos.Core (Coeff (..), TxSizeLinear (..), unsafeIntegerToCoin)
2929
import qualified Pos.Core as Core
3030
import Pos.Core.Attributes (mkAttributes)
3131
import Pos.Crypto (SecretKey)
@@ -138,7 +138,7 @@ renderUtxoAndPayees utxo outputs =
138138
(sortedPayees $ toList outputs) <> footer
139139

140140
footer :: [Row]
141-
footer = ["Total", "Total"] : [[T.pack . show . Core.getCoin . utxoBalance $ utxo
141+
footer = ["Total", "Total"] : [[T.pack . show . utxoBalance $ utxo
142142
, T.pack . show . Core.getCoin . paymentAmount $ outputs
143143
]]
144144

@@ -186,9 +186,9 @@ renderTx payees utxo tx =
186186
in header : (subTable1 `mergeRows` subTable2) <> footer
187187

188188
footer :: [Row]
189-
footer = replicate 4 "Total" : [[T.pack . show . Core.getCoin . utxoBalance $ utxo
189+
footer = replicate 4 "Total" : [[T.pack . show . utxoBalance $ utxo
190190
, T.pack . show . Core.getCoin . paymentAmount $ payees
191-
, T.pack . show . Core.getCoin . utxoBalance $ pickedInputs
191+
, T.pack . show . utxoBalance $ pickedInputs
192192
, T.pack . show . Core.getCoin . paymentAmount $ txOutputs
193193
]]
194194

@@ -324,7 +324,7 @@ feeWasPayed SenderPaysFee originalUtxo originalOutputs tx =
324324
T.unpack (renderTx originalOutputs originalUtxo tx) <>
325325
"\n\n"
326326
)
327-
(< utxoBalance originalUtxo)
327+
(< unsafeIntegerToCoin (utxoBalance originalUtxo))
328328
(paymentAmount txOutputs)
329329
feeWasPayed ReceiverPaysFee _ originalOutputs tx =
330330
let txOutputs = Core._txOutputs . Core.taTx $ tx

wallet-new/test/unit/Test/Spec/CoinSelection/Generators.hs

+3-8
Original file line numberDiff line numberDiff line change
@@ -21,20 +21,15 @@ import Universum
2121
import qualified Data.List
2222
import qualified Data.Map as Map
2323
import Formatting (sformat)
24-
import Test.QuickCheck (Gen, arbitrary, choose, suchThat)
25-
2624
import qualified Formatting as F
25+
import Test.QuickCheck (Gen, arbitrary, choose, suchThat)
2726

2827
import qualified Pos.Chain.Txp as Core
29-
import Pos.Core ()
3028
import qualified Pos.Core as Core
31-
import Pos.Crypto ()
32-
33-
import Util.Buildable ()
3429

35-
import Cardano.Wallet.Kernel.CoinSelection ()
3630
import Cardano.Wallet.Kernel.Util.Core (paymentAmount, utxoBalance)
3731

32+
-- type class instances
3833
import Test.Pos.Core.Arbitrary ()
3934

4035
{-------------------------------------------------------------------------------
@@ -167,7 +162,7 @@ genUtxo o = do
167162
addr <- arbitraryAddress o
168163
let txOutAux = Core.TxOutAux (Core.TxOut addr coins)
169164
return $ Map.singleton txIn txOutAux
170-
fromStakeOptions o genValue utxoBalance
165+
fromStakeOptions o genValue (Core.unsafeIntegerToCoin . utxoBalance)
171166

172167
-- | Generate some Utxo with @at least@ the supplied amount of money.
173168
genFiddlyUtxo :: InitialBalance -> Gen Core.Utxo

0 commit comments

Comments
 (0)