Skip to content
This repository was archived by the owner on Aug 18, 2020. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions wallet-new/cardano-sl-wallet-new.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -307,6 +307,7 @@ executable wal-integr-test
Error
Util
WalletSpecs
AccountSpecs
AddressSpecs
TransactionSpecs
QuickCheckSpecs
Expand Down
57 changes: 57 additions & 0 deletions wallet-new/integration/AccountSpecs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,57 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}

module AccountSpecs (accountSpecs) where

import Universum

import Cardano.Wallet.API.Indices (accessIx)
import Cardano.Wallet.Client.Http
import Control.Lens
import Pos.Core.Common (mkCoin)
import Test.Hspec
import Util

import qualified Pos.Core as Core
import qualified Prelude


accountSpecs :: WalletRef -> WalletClient IO -> Spec
accountSpecs _ wc =
describe "Accounts" $ do
it "can retrieve only an accounts balance" $ do
let zero = V1 (mkCoin 0)
(Wallet{..}, Account{..}) <- randomAccount wc
eresp <- getAccountBalance wc walId accIndex

partialAccount <- wrData <$> eresp `shouldPrism` _Right
partialAccount `shouldBe` AccountBalance zero

it "can retrieve only an account's addresses" $ do
pair@(Wallet{..}, Account{..}) <- randomAccount wc
addresses <- createAddresses wc 10 pair
let addr = Prelude.head addresses
let tests =
[ PaginationTest (Just 1) (Just 5) NoFilters NoSorts
(expectNAddresses 5)
, PaginationTest (Just 1) (Just 5) (filterByAddress addr) NoSorts
(expectExactlyAddresses [addr])
, PaginationTest (Just 2) (Just 5) (filterByAddress addr) NoSorts
(expectExactlyAddresses [])
]
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

love it


forM_ tests $ \PaginationTest{..} -> do
eresp <- getAccountAddresses wc walId accIndex page perPage filters sorts
expectations . acaAddresses . wrData =<< eresp `shouldPrism` _Right
where
filterByAddress :: WalletAddress -> FilterOperations WalletAddress
filterByAddress addr =
FilterOp (FilterByIndex $ accessIx @_ @(V1 Core.Address) addr) NoFilters

expectNAddresses :: Int -> [WalletAddress] -> IO ()
expectNAddresses n addrs =
length addrs `shouldBe` n

expectExactlyAddresses :: [WalletAddress] -> [WalletAddress] -> IO ()
expectExactlyAddresses as bs =
sort as `shouldBe` sort bs
19 changes: 11 additions & 8 deletions wallet-new/integration/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ module Main where
import Universum

import Cardano.Wallet.Client.Http
import qualified Data.ByteString.Char8 as B8
import Data.Map (fromList)
import Data.Traversable (for)
import Data.X509.File (readSignedObject)
Expand All @@ -15,20 +14,23 @@ import System.Environment (withArgs)
import System.IO (hSetEncoding, stdout, utf8)
import Test.Hspec

import AccountSpecs (accountSpecs)
import AddressSpecs (addressSpecs)
import CLI
import Functions
import qualified QuickCheckSpecs as QuickCheck
import TransactionSpecs (transactionSpecs)
import Types
import Util (WalletRef, newWalletRef)
import WalletSpecs (walletSpecs)

import qualified Data.ByteString.Char8 as B8
import qualified QuickCheckSpecs as QuickCheck


-- | Here we want to run main when the (local) nodes
-- have started.
main :: IO ()
main = do

hSetEncoding stdout utf8
CLOptions {..} <- getOptions

Expand All @@ -53,9 +55,9 @@ main = do

-- some monadic fold or smth similar
_ <- runActionCheck
walletClient
walletState
actionDistribution
walletClient
walletState
actionDistribution

-- Acquire the initial state for the deterministic tests
wRef <- newWalletRef
Expand All @@ -75,7 +77,7 @@ main = do
either (fail . ("Error decoding X509 certificates: " <>)) return

actionDistribution :: ActionProbabilities
actionDistribution = do
actionDistribution =
(PostWallet, Weight 2)
:| (PostTransaction, Weight 5)
: fmap (\x -> (x, Weight 1)) [minBound .. maxBound]
Expand All @@ -94,12 +96,13 @@ initialWalletState wc = do
_transactions = mempty
_actionsNum = 0
_successActions = mempty
pure $ WalletState {..}
return WalletState {..}
where
fromResp = (either throwM (pure . wrData) =<<)

deterministicTests :: WalletRef -> WalletClient IO -> Manager -> Spec
deterministicTests wref wc manager = do
accountSpecs wref wc
addressSpecs wref wc
walletSpecs wref wc
transactionSpecs wref wc
Expand Down
23 changes: 23 additions & 0 deletions wallet-new/integration/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,14 @@ import Test.QuickCheck (arbitrary, generate)

type WalletRef = MVar Wallet

data PaginationTest a = PaginationTest
{ page :: Maybe Page
, perPage :: Maybe PerPage
, filters :: FilterOperations a
, sorts :: SortOperations a
, expectations :: [a] -> IO ()
}

randomWallet :: WalletOperation -> IO NewWallet
randomWallet walletOp =
generate $
Expand All @@ -29,6 +37,12 @@ randomCreateWallet = randomWallet CreateWallet
randomRestoreWallet :: IO NewWallet
randomRestoreWallet = randomWallet RestoreWallet

randomAccount :: WalletClient IO -> IO (Wallet, Account)
randomAccount wc = do
newWallet <- randomWallet CreateWallet
wallet@Wallet{..} <- createWalletCheck wc newWallet
(\(account, _) -> (wallet, account)) <$> firstAccountAndId wc wallet

createWalletCheck :: WalletClient IO -> NewWallet -> IO Wallet
createWalletCheck wc newWallet = do
result <- fmap wrData <$> postWallet wc newWallet
Expand All @@ -47,6 +61,15 @@ firstAccountAndId wc wallet = do

pure (toAcct, toAddr)

createAddress :: WalletClient IO -> (Wallet, Account) -> IO WalletAddress
createAddress wc (Wallet{..}, Account{..}) = do
eresp <- postAddress wc (NewAddress Nothing accIndex walId)
wrData <$> eresp `shouldPrism` _Right

createAddresses :: WalletClient IO -> Int -> (Wallet, Account) -> IO [WalletAddress]
createAddresses wc n src =
replicateM n (createAddress wc src)

newWalletRef :: IO WalletRef
newWalletRef = newEmptyMVar

Expand Down
6 changes: 5 additions & 1 deletion wallet-new/src/Cardano/Wallet/API/Indices.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,10 @@ instance ToIndex Transaction (V1 Core.Timestamp) where
toIndex _ = fmap V1 . Core.parseTimestamp
accessIx Transaction{..} = txCreationTime

instance ToIndex WalletAddress (V1 Core.Address) where
toIndex _ = fmap V1 . either (const Nothing) Just . Core.decodeTextAddress
accessIx WalletAddress{..} = addrId

-- | A type family mapping a resource 'a' to all its indices.
type family IndicesOf a :: [*] where
IndicesOf Wallet = WalletIxs
Expand Down Expand Up @@ -117,7 +121,7 @@ type family IndexToQueryParam resource ix where
IndexToQueryParam Wallet WalletId = "id"
IndexToQueryParam Wallet (V1 Core.Timestamp) = "created_at"

IndexToQueryParam WalletAddress (V1 Core.Address) = "id"
IndexToQueryParam WalletAddress (V1 Core.Address) = "address"
Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

NOTE: Wasn't used before, so there's no breaking change here. I believe address makes more sense even though it filters on the id field of an address. As a reminder, we represent addresses as follows:

image

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

man, that does feel really weird. i agree that this is an improvement, but this is confusing.


IndexToQueryParam Transaction (V1 Core.TxId) = "id"
IndexToQueryParam Transaction (V1 Core.Timestamp) = "created_at"
Expand Down
15 changes: 15 additions & 0 deletions wallet-new/src/Cardano/Wallet/API/V1/Accounts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,14 @@ module Cardano.Wallet.API.V1.Accounts where

import Servant

import Cardano.Wallet.API.Request
import Cardano.Wallet.API.Response
import Cardano.Wallet.API.Types
import Cardano.Wallet.API.V1.Parameters
import Cardano.Wallet.API.V1.Types

import qualified Pos.Core as Core


type API
= Tags '["Accounts"] :>
Expand All @@ -31,4 +34,16 @@ type API
:> Summary "Update an Account for the given Wallet."
:> ReqBody '[ValidJSON] (Update Account)
:> Put '[ValidJSON] (WalletResponse Account)
:<|> "wallets" :> CaptureWalletId :> "accounts"
:> CaptureAccountId :> "addresses"
:> Summary "Retrieve only account's addressees."
:> WalletRequestParams
:> FilterBy '[V1 Core.Address] WalletAddress
:> SortBy '[V1 Core.Address] WalletAddress
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Does sorting on address really make sense? They are just a bunch of base58-encoded strings after all, so I'm wondering whether or not we should allow sorting, as it buys virtually nothing 😉

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It allows pagination based on an indexed part of the datatype, which makes for super efficient querying.

Copy link
Contributor

@adinapoli-iohk adinapoli-iohk Jul 16, 2018

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It allows pagination based on an indexed part of the datatype, which makes for super efficient querying.

@parsonsmatt @KtorZ Isn't what FilterBy buys you already? Unless I am mistaken, note that the type-level sorting & filtering has no effect on the (already-defined) IxSet indices. Once those are defined (as in instance Indexable ...) which one you use for filter & sort (or the lack thereof) really doesn't undermine querying efficiency 😉

Imho keeping SortBy here is a mistake, as it would encourage exchanges to sort by addresses, which is an operation terribly wasteful, as there is no meaningful ordering for addresses, as the lexicographical order doesn't really help here. My 2 cents anyway, very happy to be proved wrong! 😀

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

In a way, pagination without ordering doesn't make much sense to me, does it? Do we even have guarantees with the acid-state db that we will yield the same elements from two successive get queries? Or is it completely non-deterministic on non-indexed items?

Though, I'd rather follow your intuition on that @adinapoli-iohk. Note that the PR has been merged in a feature-branch and not yet to develop, so there's still time to do some minor adjusments!

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Haven't followed the details here but I agree that for pagination it is important to have an indexed attribute available to sort on. Not sure how much control we need to give the user over this, since as @adinapoli-iohk points out, sorting on base58 strings isn't particularly meaningful. Moreover, in the new wallet we clearly distinguish between the primary key and the rest of the data structure and don't require Ord instances for the whole type; in this case, the natural way to sort by "address" would be to sort on its key (which is basically just the pair of integers telling it how that address is derived from the root). So I think it's important that "sort by address" doesn't necessarily mean "sort lexicographically", but rather "give me some kind of pagination I can depend on" -- so that we are free to switch over the sorting to the primary key once we move to the new wallet, rather than being forced to still support this lexicographical sort.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

In a way, pagination without ordering doesn't make much sense to me, does it?

Indeed, but I think we should be fine in this case, as in the current implementation we simply call IxSet.toList which, AFAIK, uses descending ordering, which is a reasonable default, I believe.

My main gripe was that, if we leave that SortBy as-it-is, we are really exposing sort_by=address[DES|ASC] to the API, which means exchanges could enforce an explicit sorting on the addresses, which, considering the amount of addresses an exchanges has, I would prefer to not pay the explicit price, if possible 😀

Am I being mental? 😛

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I usually say: If users can do something, eventually they will. I wonder if we shouldn't indeed remove that sorting for now, until we have something more meaningful we can actually sort on.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

If users can do something, eventually they will.

Aye, that is usually my experience -- that's why I have flagged this up 😉

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

NOTE: Sorting was removed on the main story branch

:> Get '[ValidJSON] (WalletResponse AccountAddresses)
:<|> "wallets" :> CaptureWalletId :> "accounts"
:> CaptureAccountId :> "amount"
:> Summary "Retrieve only account's balance."
:> Get '[ValidJSON] (WalletResponse AccountBalance)

)
24 changes: 24 additions & 0 deletions wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Accounts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,8 @@ handlers =
:<|> listAccounts
:<|> newAccount
:<|> updateAccount
:<|> getAccountAddresses
:<|> getAccountBalance

deleteAccount
:: (V0.MonadWalletLogic ctx m)
Expand Down Expand Up @@ -68,3 +70,25 @@ updateAccount wId accIdx accUpdate = do
accMeta <- migrate accUpdate
cAccount <- V0.updateAccount newAccId accMeta
single <$> (migrate cAccount)

getAccountAddresses
:: (V0.MonadWalletLogic ctx m)
=> WalletId
-> AccountIndex
-> RequestParams
-> FilterOperations WalletAddress
-> SortOperations WalletAddress
-> m (WalletResponse AccountAddresses)
getAccountAddresses wId accIdx pagination filters sorts = do
resp <- respondWith pagination filters sorts (getAddresses <$> getAccount wId accIdx)
return resp { wrData = AccountAddresses . wrData $ resp }
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

is WalletResponse a functor/foldable? it totally should be!

where
getAddresses =
IxSet.fromList . accAddresses . wrData

getAccountBalance
:: (V0.MonadWalletLogic ctx m)
=> WalletId -> AccountIndex -> m (WalletResponse AccountBalance)
getAccountBalance wId accIdx = do
resp <- getAccount wId accIdx
return resp { wrData = AccountBalance . accAmount . wrData $ resp }
39 changes: 31 additions & 8 deletions wallet-new/src/Cardano/Wallet/API/V1/Swagger.hs
Original file line number Diff line number Diff line change
Expand Up @@ -654,6 +654,27 @@ curl -X GET \
$readAccounts
```

Partial Representations
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Good lad for adding documentation! 😻

-----------------------

The previous endpoint gives you a list of full representations. However, in some cases, it might be interesting to retrieve only a partial representation of an account (e.g. only the balance). There are two extra endpoints one could use to either fetch a given account's balance, and another to retrieve the list of addresses associated to a specific account.

[`GET /api/v1/wallets/{{walletId}}/accounts/{{accountId}}/addresses`](#tag/Accounts%2Fpaths%2F~1api~1v1~1wallets~1%7BwalletId%7D~1accounts~1%7BaccountId%7D~1addresses%2Fget)

```json
$readAccountAddresses
```

Note that this endpoint is paginated and allow basic filtering and sorting on
addresses. Similarly, you can retrieve only the account balance with:

[`GET /api/v1/wallets/{{walletId}}/accounts/{{accountId}}/amount`](#tag/Accounts%2Fpaths%2F~1api~1v1~1wallets~1%7BwalletId%7D~1accounts~1%7BaccountId%7D~1amount%2Fget)


```json
$readAccountBalance
```


Managing Addresses
------------------
Expand Down Expand Up @@ -771,14 +792,16 @@ Make sure to carefully read the section about [Pagination](#section/Pagination)
leverage the API capabilities.
|]
where
createAccount = decodeUtf8 $ encodePretty $ genExample @(WalletResponse Account)
createAddress = decodeUtf8 $ encodePretty $ genExample @(WalletResponse WalletAddress)
createWallet = decodeUtf8 $ encodePretty $ genExample @(WalletResponse Wallet)
readAccounts = decodeUtf8 $ encodePretty $ genExample @(WalletResponse [Account])
readAddresses = decodeUtf8 $ encodePretty $ genExample @(WalletResponse [Address])
readFees = decodeUtf8 $ encodePretty $ genExample @(WalletResponse EstimatedFees)
readNodeInfo = decodeUtf8 $ encodePretty $ genExample @(WalletResponse NodeInfo)
readTransactions = decodeUtf8 $ encodePretty $ genExample @(WalletResponse [Transaction])
createAccount = decodeUtf8 $ encodePretty $ genExample @(WalletResponse Account)
createAddress = decodeUtf8 $ encodePretty $ genExample @(WalletResponse WalletAddress)
createWallet = decodeUtf8 $ encodePretty $ genExample @(WalletResponse Wallet)
readAccounts = decodeUtf8 $ encodePretty $ genExample @(WalletResponse [Account])
readAccountBalance = decodeUtf8 $ encodePretty $ genExample @(WalletResponse AccountBalance)
readAccountAddresses = decodeUtf8 $ encodePretty $ genExample @(WalletResponse AccountAddresses)
readAddresses = decodeUtf8 $ encodePretty $ genExample @(WalletResponse [Address])
readFees = decodeUtf8 $ encodePretty $ genExample @(WalletResponse EstimatedFees)
readNodeInfo = decodeUtf8 $ encodePretty $ genExample @(WalletResponse NodeInfo)
readTransactions = decodeUtf8 $ encodePretty $ genExample @(WalletResponse [Transaction])
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

rather than large whitespace changes like this i would prefer an indentation to make the start point equal for each line. minor quibble :)

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

And I do agree with you!



-- | Provide an alternative UI (ReDoc) for rendering Swagger documentation.
Expand Down
2 changes: 2 additions & 0 deletions wallet-new/src/Cardano/Wallet/API/V1/Swagger/Example.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,8 @@ instance Example (V1 (Mnemonic 12)) where
instance Example Address
instance Example Metadata
instance Example AccountIndex
instance Example AccountBalance
instance Example AccountAddresses
instance Example WalletId
instance Example AssuranceLevel
instance Example SyncPercentage
Expand Down
Loading