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

Commit 7387048

Browse files
committed
Merge branch 'CO-347' into Squad1/CO-325/api-v1-improvements
2 parents 6b43c7a + 89775cb commit 7387048

File tree

16 files changed

+503
-25
lines changed

16 files changed

+503
-25
lines changed

wallet-new/cardano-sl-wallet-new.cabal

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -129,6 +129,7 @@ library
129129
Cardano.Wallet.Server.CLI
130130
Cardano.Wallet.Server.Plugins
131131
Cardano.Wallet.TypeLits
132+
Cardano.Wallet.Types.UtxoStatistics
132133
Cardano.Wallet.Client
133134
Cardano.Wallet.Client.Http
134135

@@ -176,7 +177,6 @@ library
176177
, cardano-sl-node-ipc
177178
, cardano-sl-util
178179
, cardano-sl-wallet
179-
, cardano-sl-wallet-test
180180
, cereal
181181
, conduit
182182
, connection
@@ -195,6 +195,7 @@ library
195195
, http-client-tls
196196
, http-types
197197
, ixset-typed
198+
, foldl
198199
, lens
199200
, log-warper
200201
, memory
@@ -505,7 +506,6 @@ test-suite wallet-unit-tests
505506
, data-default
506507
, formatting
507508
, hspec
508-
, ixset-typed
509509
, lens
510510
, log-warper
511511
, mtl
@@ -643,7 +643,6 @@ benchmark cardano-sl-wallet-new-bench
643643
, bytestring
644644
, cardano-sl-client
645645
, cardano-sl-core
646-
, cardano-sl-db
647646
, cardano-sl-wallet
648647
, cassava
649648
, connection

wallet-new/integration/TransactionSpecs.hs

Lines changed: 45 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,9 +11,12 @@ import Control.Lens
1111
import Test.Hspec
1212
import Text.Show.Pretty (ppShow)
1313

14+
import Util
15+
16+
import qualified Data.Map.Strict as Map
1417
import qualified Pos.Core as Core
18+
import qualified Pos.Core.Txp as Txp
1519

16-
import Util
1720

1821
{-# ANN module ("HLint: ignore Reduce duplication" :: Text) #-}
1922

@@ -24,7 +27,7 @@ ppShowT :: Show a => a -> Text
2427
ppShowT = fromString . ppShow
2528

2629
transactionSpecs :: WalletRef -> WalletClient IO -> Spec
27-
transactionSpecs wRef wc = do
30+
transactionSpecs wRef wc =
2831
describe "Transactions" $ do
2932
it "posted transactions appear in the index" $ do
3033
genesis <- genesisWallet wc
@@ -187,3 +190,43 @@ transactionSpecs wRef wc = do
187190
etxn <- postTransaction wc payment
188191

189192
void $ etxn `shouldPrism` _Left
193+
194+
xit "posted transactions gives rise to nonempty Utxo histogram" $ do
195+
genesis <- genesisWallet wc
196+
(fromAcct, _) <- firstAccountAndId wc genesis
197+
198+
wallet <- sampleWallet wRef wc
199+
(_, toAddr) <- firstAccountAndId wc wallet
200+
201+
let payment val = Payment
202+
{ pmtSource = PaymentSource
203+
{ psWalletId = walId genesis
204+
, psAccountIndex = accIndex fromAcct
205+
}
206+
, pmtDestinations = pure PaymentDistribution
207+
{ pdAddress = addrId toAddr
208+
, pdAmount = V1 (Core.mkCoin val)
209+
}
210+
, pmtGroupingPolicy = Nothing
211+
, pmtSpendingPassword = Nothing
212+
}
213+
214+
eresp0 <- getUtxoStatistics wc (walId wallet)
215+
utxoStatistics0 <- fmap wrData eresp0 `shouldPrism` _Right
216+
let utxoStatistics0Expected = computeUtxoStatistics log10 []
217+
utxoStatistics0 `shouldBe` utxoStatistics0Expected
218+
219+
void $ postTransaction wc (payment 1)
220+
threadDelay 120000000
221+
222+
let txIn = Txp.TxInUnknown 0 "test"
223+
let txOut = Txp.TxOutAux Txp.TxOut
224+
{ Txp.txOutAddress = unV1 (addrId toAddr)
225+
, Txp.txOutValue = Core.mkCoin 1
226+
}
227+
let utxos = [Map.fromList [(txIn, txOut)]]
228+
229+
eresp <- getUtxoStatistics wc (walId wallet)
230+
utxoStatistics <- fmap wrData eresp `shouldPrism` _Right
231+
let utxoStatisticsExpected = computeUtxoStatistics log10 utxos
232+
utxoStatistics `shouldBe` utxoStatisticsExpected

wallet-new/integration/WalletSpecs.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ import Util
1313

1414

1515
walletSpecs :: WalletRef -> WalletClient IO -> Spec
16-
walletSpecs _ wc = do
16+
walletSpecs _ wc =
1717
describe "Wallets" $ do
1818
it "Creating a wallet makes it available." $ do
1919
newWallet <- randomWallet CreateWallet
@@ -51,6 +51,15 @@ walletSpecs _ wc = do
5151
}
5252

5353
eresp `shouldPrism_` _Right
54+
55+
it "creating wallet gives rise to an empty Utxo histogram" $ do
56+
newWallet <- randomWallet CreateWallet
57+
wallet <- createWalletCheck wc newWallet
58+
59+
eresp <- getUtxoStatistics wc (walId wallet)
60+
utxoStatistics <- fmap wrData eresp `shouldPrism` _Right
61+
let utxoStatisticsExpected = computeUtxoStatistics log10 []
62+
utxoStatistics `shouldBe` utxoStatisticsExpected
5463
where
5564
testWalletAlreadyExists action = do
5665
newWallet1 <- randomWallet action

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

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,17 +2,17 @@ module Cardano.Wallet.API.V1.Handlers.Wallets where
22

33
import Universum
44

5-
import Pos.Core (Coin)
5+
import Servant
66

77
import Cardano.Wallet.API.Request
88
import Cardano.Wallet.API.Response
99
import Cardano.Wallet.API.V1.Types as V1
1010
import qualified Cardano.Wallet.API.V1.Wallets as Wallets
11-
1211
import Cardano.Wallet.WalletLayer (PassiveWalletLayer)
1312
import qualified Cardano.Wallet.WalletLayer as WalletLayer
1413

15-
import Servant
14+
import Pos.Core.Common (Coin (..))
15+
1616

1717
-- | All the @Servant@ handlers for wallet-specific operations.
1818
handlers :: PassiveWalletLayer IO -> ServerT Wallets.API Handler
@@ -22,6 +22,7 @@ handlers pwl = newWallet pwl
2222
:<|> deleteWallet pwl
2323
:<|> getWallet pwl
2424
:<|> updateWallet pwl
25+
:<|> getUtxoStatistics pwl
2526
:<|> checkExternalWallet pwl
2627
:<|> newExternalWallet pwl
2728
:<|> deleteExternalWallet pwl
@@ -96,6 +97,17 @@ updateWallet pwl wid walletUpdateRequest = do
9697
Left e -> throwM e
9798
Right w -> return $ single w
9899

100+
getUtxoStatistics
101+
:: PassiveWalletLayer IO
102+
-> WalletId
103+
-> Handler (WalletResponse UtxoStatistics)
104+
getUtxoStatistics pwl wid = do
105+
res <- liftIO $ WalletLayer.getUtxos pwl wid
106+
case res of
107+
Left e -> throwM e
108+
Right w ->
109+
return $ single $ V1.computeUtxoStatistics V1.log10 (map snd w)
110+
99111
checkExternalWallet :: PassiveWalletLayer IO
100112
-> PublicKeyAsBase58
101113
-> Handler (WalletResponse WalletAndTxHistory)

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

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ import Pos.Wallet.Web.Methods.Logic (MonadWalletLogic,
3030
import Pos.Wallet.Web.Tracking.Types (SyncQueue)
3131
import Servant
3232

33+
3334
-- | All the @Servant@ handlers for wallet-specific operations.
3435
handlers :: HasConfigurations
3536
=> ServerT Wallets.API MonadV1
@@ -39,11 +40,11 @@ handlers = newWallet
3940
:<|> deleteWallet
4041
:<|> getWallet
4142
:<|> updateWallet
43+
:<|> getUtxoStatistics
4244
:<|> checkExternalWallet
4345
:<|> newExternalWallet
4446
:<|> deleteExternalWallet
4547

46-
4748
-- | Pure function which returns whether or not the underlying node is
4849
-- \"synced enough\" to allow wallet creation/restoration. The notion of
4950
-- \"synced enough\" is quite vague and if made too stringent could prevent
@@ -183,6 +184,15 @@ updateWallet wid WalletUpdate{..} = do
183184
ws' <- V0.askWalletSnapshot
184185
addWalletInfo ws' updated
185186

187+
-- | Gets Utxo statistics for a wallet.
188+
-- | Stub, not calling data layer.
189+
getUtxoStatistics
190+
:: (MonadWalletLogic ctx m)
191+
=> WalletId
192+
-> m (WalletResponse UtxoStatistics)
193+
getUtxoStatistics _ = do
194+
return $ single (V1.computeUtxoStatistics V1.log10 [])
195+
186196
-- | Check if external wallet is presented in node's wallet db.
187197
checkExternalWallet
188198
:: -- ( V0.MonadWalletLogic ctx m

wallet-new/src/Cardano/Wallet/API/V1/Swagger.hs

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -857,6 +857,24 @@ curl -X GET 'https://127.0.0.1:8090/api/v1/transactions?wallet_id=Ae2tdPwU...3AV
857857
--cert ./scripts/tls-files/client.pem
858858
```
859859

860+
861+
Getting Utxo statistics
862+
---------------------------------
863+
864+
You can get Utxo statistics of a given wallet using
865+
[`GET /api/v1/wallets/{{walletId}}/statistics/utxos`](#tag/Accounts%2Fpaths%2F~1api~1v1~1wallets~1{walletId}~1statistics~1utxos%2Fget)
866+
```
867+
curl -X GET \
868+
https://127.0.0.1:8090/api/v1/wallets/Ae2tdPwUPE...8V3AVTnqGZ/statistics/utxos \
869+
-H 'Accept: application/json;charset=utf-8' \
870+
--cacert ./scripts/tls-files/ca.crt \
871+
--cert ./scripts/tls-files/client.pem
872+
```
873+
874+
```json
875+
$readUtxoStatistics
876+
```
877+
860878
Make sure to carefully read the section about [Pagination](#section/Pagination) to fully
861879
leverage the API capabilities.
862880
|]
@@ -871,7 +889,7 @@ leverage the API capabilities.
871889
readFees = decodeUtf8 $ encodePretty $ genExample @(WalletResponse EstimatedFees)
872890
readNodeInfo = decodeUtf8 $ encodePretty $ genExample @(WalletResponse NodeInfo)
873891
readTransactions = decodeUtf8 $ encodePretty $ genExample @(WalletResponse [Transaction])
874-
892+
readUtxoStatistics = decodeUtf8 $ encodePretty $ genExample @(WalletResponse UtxoStatistics)
875893

876894
-- | Provide an alternative UI (ReDoc) for rendering Swagger documentation.
877895
swaggerSchemaUIServer

wallet-new/src/Cardano/Wallet/API/V1/Types.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -122,6 +122,8 @@ module Cardano.Wallet.API.V1.Types (
122122
, WalletError(..)
123123
, toServantError
124124
, toHttpErrorStatus
125+
126+
, module Cardano.Wallet.Types.UtxoStatistics
125127
) where
126128

127129
import qualified Prelude
@@ -177,7 +179,9 @@ import Cardano.Wallet.API.V1.Generic (jsendErrorGenericParseJSON,
177179
import Cardano.Wallet.API.V1.Swagger.Example (Example, example,
178180
genExample)
179181
import Cardano.Wallet.Orphans.Aeson ()
182+
import Cardano.Wallet.Types.UtxoStatistics
180183
import Cardano.Wallet.Util (showApiUtcTime)
184+
181185
import qualified Pos.Binary.Class as Bi
182186
import qualified Pos.Client.Txp.Util as Core
183187
import Pos.Core (addressF)

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

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,9 @@ type API = Tags '["Wallets"] :>
3737
:> Summary "Update the Wallet identified by the given walletId."
3838
:> ReqBody '[ValidJSON] (Update Wallet)
3939
:> Put '[ValidJSON] (WalletResponse Wallet)
40+
:<|> "wallets" :> CaptureWalletId :> "statistics" :> "utxos"
41+
:> Summary "Returns Utxo statistics for the Wallet identified by the given walletId."
42+
:> Get '[ValidJSON] (WalletResponse UtxoStatistics)
4043
:<|> "external-wallets"
4144
:> Capture "rootPK" PublicKeyAsBase58
4245
:> Summary "Check if this external wallet is presented in the node."

wallet-new/src/Cardano/Wallet/Client.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -89,6 +89,8 @@ data WalletClient m
8989
:: WalletId -> Resp m Wallet
9090
, updateWallet
9191
:: WalletId -> Update Wallet -> Resp m Wallet
92+
, getUtxoStatistics
93+
:: WalletId -> Resp m UtxoStatistics
9294
, postCheckExternalWallet
9395
:: PublicKeyAsBase58 -> Resp m WalletAndTxHistory
9496
, postExternalWallet
@@ -218,6 +220,8 @@ hoistClient phi wc = WalletClient
218220
phi . getWallet wc
219221
, updateWallet =
220222
\x -> phi . updateWallet wc x
223+
, getUtxoStatistics =
224+
phi . getUtxoStatistics wc
221225
, postCheckExternalWallet =
222226
phi . postCheckExternalWallet wc
223227
, postExternalWallet =

wallet-new/src/Cardano/Wallet/Client/Http.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -105,6 +105,8 @@ mkHttpClient baseUrl manager = WalletClient
105105
= run . getWalletR
106106
, updateWallet
107107
= \x -> run . updateWalletR x
108+
, getUtxoStatistics
109+
= run . getUtxoStatisticsR
108110
, postCheckExternalWallet
109111
= run . postCheckExternalWalletR
110112
, postExternalWallet
@@ -171,6 +173,7 @@ mkHttpClient baseUrl manager = WalletClient
171173
:<|> deleteWalletR
172174
:<|> getWalletR
173175
:<|> updateWalletR
176+
:<|> getUtxoStatisticsR
174177
:<|> postCheckExternalWalletR
175178
:<|> postExternalWalletR
176179
:<|> deleteExternalWalletR

0 commit comments

Comments
 (0)