-
Notifications
You must be signed in to change notification settings - Fork 629
[CO-324] Accounts per-field endpoints #3210
Changes from all commits
1e1c111
930c8c0
323d0fc
83c865e
File filter
Filter by extension
Conversations
Jump to
Diff view
Diff view
There are no files selected for viewing
| 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 []) | ||
| ] | ||
|
|
||
| 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 | ||
| Original file line number | Diff line number | Diff line change |
|---|---|---|
|
|
@@ -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 | ||
|
|
@@ -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" | ||
|
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more.
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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" | ||
|
|
||
| Original file line number | Diff line number | Diff line change |
|---|---|---|
|
|
@@ -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"] :> | ||
|
|
@@ -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 | ||
|
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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 😉
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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.
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more.
@parsonsmatt @KtorZ Isn't what Imho keeping
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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!
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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.
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more.
Indeed, but I think we should be fine in this case, as in the current implementation we simply call My main gripe was that, if we leave that Am I being mental? 😛
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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.
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more.
Aye, that is usually my experience -- that's why I have flagged this up 😉
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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) | ||
|
|
||
| ) | ||
| Original file line number | Diff line number | Diff line change |
|---|---|---|
|
|
@@ -26,6 +26,8 @@ handlers = | |
| :<|> listAccounts | ||
| :<|> newAccount | ||
| :<|> updateAccount | ||
| :<|> getAccountAddresses | ||
| :<|> getAccountBalance | ||
|
|
||
| deleteAccount | ||
| :: (V0.MonadWalletLogic ctx m) | ||
|
|
@@ -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 } | ||
|
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. is |
||
| 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 } | ||
| Original file line number | Diff line number | Diff line change |
|---|---|---|
|
|
@@ -654,6 +654,27 @@ curl -X GET \ | |
| $readAccounts | ||
| ``` | ||
|
|
||
| Partial Representations | ||
|
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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 | ||
| ------------------ | ||
|
|
@@ -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]) | ||
|
Contributor
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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 :)
Contributor
Author
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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. | ||
|
|
||

There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
love it