diff --git a/lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs b/lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs index 3a196e24fa8..a211fb0b66c 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs @@ -310,16 +310,21 @@ _estimateMaxNumberOfInputs -> Word8 -- ^ Number of outputs in transaction -> Word8 -_estimateMaxNumberOfInputs networkId (Quantity maxSize) md nOuts = - findMax minBound +_estimateMaxNumberOfInputs networkId txMaxSize md nOuts = + findLargestUntil ((> maxSize) . txSizeGivenInputs) 0 where - findMax :: Word8 -> Word8 - findMax inf - | inf == maxBound = 0 - | isTooBig (inf + 1) = inf - | otherwise = findMax (inf + 1) - - isTooBig nInps = size > fromIntegral maxSize + -- | Find the largest amount of inputs that doesn't make the tx too big. + -- Tries in sequence from 0 and upward (up to 255, but smaller than 50 in + -- practice because of the max transaction size). + findLargestUntil :: (Word8 -> Bool) -> Word8 -> Word8 + findLargestUntil isTxTooLarge inf + | inf == maxBound = maxBound + | isTxTooLarge (inf + 1) = inf + | otherwise = findLargestUntil isTxTooLarge (inf + 1) + + maxSize = fromIntegral (getQuantity txMaxSize) + + txSizeGivenInputs nInps = size where size = computeTxSize networkId (txWitnessTagFor @k) md Nothing sel sel = dummyCoinSel (fromIntegral nInps) (fromIntegral nOuts) diff --git a/lib/shelley/test/unit/Cardano/Wallet/Shelley/TransactionSpec.hs b/lib/shelley/test/unit/Cardano/Wallet/Shelley/TransactionSpec.hs index b06a6c8cc3e..814b3dbe68e 100644 --- a/lib/shelley/test/unit/Cardano/Wallet/Shelley/TransactionSpec.hs +++ b/lib/shelley/test/unit/Cardano/Wallet/Shelley/TransactionSpec.hs @@ -2,6 +2,7 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -198,15 +199,20 @@ spec = do res `shouldBe` Right (FeeEstimation 165413 165413) +newtype GivenNumOutputs = GivenNumOutputs Word8 deriving Num +newtype ExpectedNumInputs = ExpectedNumInputs Word8 deriving Num + +-- | Set of tests related to `estimateMaxNumberOfInputs` from the transaction +-- layer. estimateMaxInputsTests :: forall k. (TxWitnessTagFor k, Typeable k) => Cardano.NetworkId - -> [(Word8, Word8)] + -> [(GivenNumOutputs, ExpectedNumInputs)] -> SpecWith () estimateMaxInputsTests net cases = do let k = show $ typeRep (Proxy @k) describe ("estimateMaxNumberOfInputs for "<>k<>" on "<>show net) $ do - forM_ cases $ \(nOuts, nInps) -> do + forM_ cases $ \(GivenNumOutputs nOuts, ExpectedNumInputs nInps) -> do let (o,i) = (show nOuts, show nInps) it ("order of magnitude, nOuts = " <> o <> " → nInps = " <> i) $ _estimateMaxNumberOfInputs @k net (Quantity 4096) Nothing nOuts