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

Commit 166665c

Browse files
committed
[CO-347] Change computeUtxoStatistics API to take [Utxo]
This is more semantically correct and type-safe than taking a raw list of 'Word64'. This way, we also get documentation for free simply by looking at the function signature and also makes calls for callers simpler (provided they have a list of available utxos, but why would they call the function if they hadn't? :) )
1 parent a360004 commit 166665c

File tree

3 files changed

+34
-21
lines changed

3 files changed

+34
-21
lines changed

wallet-new/integration/TransactionSpecs.hs

+13-2
Original file line numberDiff line numberDiff line change
@@ -8,13 +8,17 @@ import Universum
88
import Cardano.Wallet.API.V1.Errors hiding (describe)
99
import Cardano.Wallet.Client.Http
1010
import Control.Lens
11-
import qualified Pos.Core as Core
1211
import Test.Hspec
1312

1413
import Control.Concurrent (threadDelay)
1514
import Text.Show.Pretty (ppShow)
1615
import Util
1716

17+
import qualified Data.Map.Strict as Map
18+
import qualified Pos.Core as Core
19+
import qualified Pos.Core.Txp as Txp
20+
21+
1822
{-# ANN module ("HLint: ignore Reduce duplication" :: Text) #-}
1923

2024
log :: MonadIO m => Text -> m ()
@@ -216,7 +220,14 @@ transactionSpecs wRef wc =
216220
void $ postTransaction wc (payment 1)
217221
threadDelay 120000000
218222

223+
let txIn = Txp.TxInUnknown 0 "test"
224+
let txOut = Txp.TxOutAux Txp.TxOut
225+
{ Txp.txOutAddress = unV1 (addrId toAddr)
226+
, Txp.txOutValue = Core.mkCoin 1
227+
}
228+
let utxos = [Map.fromList [(txIn, txOut)]]
229+
219230
eresp <- getUtxoStatistics wc (walId wallet)
220231
utxoStatistics <- fmap wrData eresp `shouldPrism` _Right
221-
let utxoStatisticsExpected = computeUtxoStatistics log10 [1]
232+
let utxoStatisticsExpected = computeUtxoStatistics log10 utxos
222233
utxoStatistics `shouldBe` utxoStatisticsExpected

wallet-new/src/Cardano/Wallet/API/V1/Handlers/Wallets.hs

+6-15
Original file line numberDiff line numberDiff line change
@@ -2,22 +2,18 @@ module Cardano.Wallet.API.V1.Handlers.Wallets where
22

33
import Universum
44

5+
import Servant
6+
57
import Cardano.Wallet.API.Request
68
import Cardano.Wallet.API.Response
79
import Cardano.Wallet.API.V1.Types as V1
8-
import qualified Cardano.Wallet.API.V1.Wallets as Wallets
9-
1010
import Cardano.Wallet.WalletLayer (PassiveWalletLayer (..))
11-
import qualified Cardano.Wallet.WalletLayer.Types as WalletLayer
1211

12+
import qualified Cardano.Wallet.API.V1.Wallets as Wallets
1313
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as KernelIxSet
14+
import qualified Cardano.Wallet.WalletLayer.Types as WalletLayer
1415
import qualified Data.IxSet.Typed as IxSet
15-
import Pos.Chain.Txp (Utxo)
16-
import Pos.Core.Common (Coin (..))
17-
import Pos.Core.Txp (TxOut (..), TxOutAux (..))
1816

19-
import qualified Data.Map.Strict as M (elems)
20-
import Servant
2117

2218
-- | All the @Servant@ handlers for wallet-specific operations.
2319
handlers :: PassiveWalletLayer IO -> ServerT Wallets.API Handler
@@ -110,10 +106,5 @@ getUtxoStatistics pwl wid = do
110106
res <- liftIO $ WalletLayer.getUtxos pwl wid
111107
case res of
112108
Left e -> throwM e
113-
Right w -> do
114-
let extractValue :: TxOutAux -> Word64
115-
extractValue = getCoin . txOutValue . toaOut
116-
let utxosCoinValuesForAllAccounts :: [(Account, Utxo)] -> [Word64]
117-
utxosCoinValuesForAllAccounts =
118-
concatMap (\pair -> map extractValue (M.elems $ snd pair) )
119-
return $ single (V1.computeUtxoStatistics V1.log10 $ utxosCoinValuesForAllAccounts w)
109+
Right w ->
110+
return $ single $ V1.computeUtxoStatistics V1.log10 (map snd w)

wallet-new/src/Cardano/Wallet/Types/UtxoStatistics.hs

+15-4
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,9 @@ import Test.QuickCheck (Arbitrary (..), arbitrary, choose, elements,
3434
infiniteListOf, shuffle)
3535

3636
import Cardano.Wallet.API.V1.Swagger.Example (Example)
37+
import Pos.Chain.Txp (Utxo)
38+
import Pos.Core.Common (Coin (..))
39+
import Pos.Core.Txp (TxOut (..), TxOutAux (..))
3740
import Pos.Infra.Util.LogSafe (BuildableSafeGen (..),
3841
deriveSafeBuildable)
3942

@@ -184,11 +187,19 @@ log10 = Log10
184187
{-# INLINE log10 #-}
185188

186189
-- | Compute UtxoStatistics from a bunch of UTXOs
187-
computeUtxoStatistics :: BoundType -> [Word64] -> UtxoStatistics
188-
computeUtxoStatistics btype = L.fold $ UtxoStatistics
189-
<$> foldBuckets (generateBounds btype)
190-
<*> L.sum
190+
computeUtxoStatistics :: BoundType -> [Utxo] -> UtxoStatistics
191+
computeUtxoStatistics btype =
192+
L.fold foldStatistics . concatMap getCoins
191193
where
194+
getCoins :: Utxo -> [Word64]
195+
getCoins =
196+
map (getCoin . txOutValue . toaOut) . Map.elems
197+
198+
foldStatistics :: L.Fold Word64 UtxoStatistics
199+
foldStatistics = UtxoStatistics
200+
<$> foldBuckets (generateBounds btype)
201+
<*> L.sum
202+
192203
foldBuckets :: NonEmpty Word64 -> L.Fold Word64 [HistogramBar]
193204
foldBuckets bounds =
194205
let

0 commit comments

Comments
 (0)