@@ -12,24 +12,25 @@ import qualified Test.Spec.Wallets as Wallets
1212
1313import Formatting (build , formatToString , (%) )
1414
15- import Cardano.Wallet.Kernel.Accounts (CreateAccountError (.. ))
16- import qualified Cardano.Wallet.Kernel.DB.HdWallet as Kernel
17- import qualified Cardano.Wallet.Kernel.Internal as Internal
18- import qualified Cardano.Wallet.Kernel.Keystore as Keystore
19- import Cardano.Wallet.WalletLayer (PassiveWalletLayer )
20- import qualified Cardano.Wallet.WalletLayer as WalletLayer
21-
2215import qualified Cardano.Wallet.API.Request as API
2316import qualified Cardano.Wallet.API.Request.Pagination as API
2417import qualified Cardano.Wallet.API.Response as API
2518import Cardano.Wallet.API.V1.Handlers.Accounts as Handlers
2619import Cardano.Wallet.API.V1.Types (V1 (.. ))
2720import qualified Cardano.Wallet.API.V1.Types as V1
21+ import Cardano.Wallet.Kernel.Accounts (CreateAccountError (.. ))
22+ import qualified Cardano.Wallet.Kernel.DB.HdWallet as Kernel
2823import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet
24+ import qualified Cardano.Wallet.Kernel.Internal as Internal
25+ import qualified Cardano.Wallet.Kernel.Keystore as Keystore
26+ import Cardano.Wallet.WalletLayer (PassiveWalletLayer )
27+ import qualified Cardano.Wallet.WalletLayer as WalletLayer
2928import qualified Cardano.Wallet.WalletLayer.Kernel.Wallets as Wallets
3029import Control.Monad.Except (runExceptT )
3130import Servant.Server
3231
32+ import Pos.Core.Common (mkCoin )
33+
3334import Test.Spec.Fixture (GenPassiveWalletFixture ,
3435 genSpendingPassword , withLayer , withPassiveWalletFixture )
3536import Util.Buildable (ShowThroughBuild (.. ))
@@ -367,3 +368,186 @@ spec = describe "Accounts" $ do
367368 case res of
368369 Left e -> fail (show e)
369370 Right wr -> (length $ API. wrData wr) `shouldBe` 5
371+
372+
373+ describe " GetAccountAddresses" $ do
374+
375+ prop " fails if the account doesn't exists" $ withMaxSuccess 50 $ do
376+ monadicIO $ do
377+ withFixture $ \ _ layer _ Fixture {.. } -> do
378+ let params = API. RequestParams (API. PaginationParams (API. Page 1 ) (API. PerPage 10 ))
379+ let filters = API. NoFilters
380+ res <- WalletLayer. getAccountAddresses layer
381+ (V1. walId fixtureV1Wallet)
382+ (V1. unsafeMkAccountIndex 2147483648 )
383+ params
384+ filters
385+ case res of
386+ Left (WalletLayer. GetAccountError (V1 (Kernel. UnknownHdAccount _))) ->
387+ return ()
388+ Left unexpectedErr ->
389+ fail $ " expecting different failure than " <> show unexpectedErr
390+ Right _ ->
391+ let errMsg = " expecting account not to be retrieved, but it was. random WalletId "
392+ % build
393+ % " , V1.Wallet "
394+ in fail $ formatToString errMsg (V1. walId fixtureV1Wallet)
395+
396+
397+ prop " applied to each newly created accounts gives addresses as obtained from GetAccounts" $ withMaxSuccess 25 $ do
398+ monadicIO $ do
399+ withFixture $ \ _ layer _ Fixture {.. } -> do
400+ -- We create 4 accounts, plus one is created automatically
401+ -- by the 'createWallet' endpoint, for a total of 5.
402+ forM_ [1 .. 4 ] $ \ (_i :: Int ) ->
403+ WalletLayer. createAccount layer (V1. walId fixtureV1Wallet)
404+ fixtureNewAccountRq
405+ accounts <- WalletLayer. getAccounts layer (V1. walId fixtureV1Wallet)
406+ let accountIndices =
407+ case accounts of
408+ Left _ -> []
409+ Right accs -> map V1. accIndex $ IxSet. toList accs
410+ let params = API. RequestParams (API. PaginationParams (API. Page 1 ) (API. PerPage 10 ))
411+ let filters = API. NoFilters
412+ partialAddresses <- forM accountIndices $ \ (ind :: V1. AccountIndex ) ->
413+ WalletLayer. getAccountAddresses layer (V1. walId fixtureV1Wallet) ind params filters
414+ case accounts of
415+ Right accs -> (map V1. accAddresses $ IxSet. toList accs)
416+ `shouldBe`
417+ (map (\ (Right addr) -> API. wrData addr) partialAddresses)
418+ Left err -> fail (show err)
419+
420+
421+ prop " and this also works when called from Servant" $ withMaxSuccess 25 $ do
422+ monadicIO $ do
423+ withFixture $ \ _ layer _ Fixture {.. } -> do
424+ let create = Handlers. newAccount layer (V1. walId fixtureV1Wallet) fixtureNewAccountRq
425+ -- We create 4 accounts, plus one is created automatically
426+ -- by the 'createWallet' endpoint, for a total of 5.
427+ forM_ [1 .. 4 ] $ \ (_i :: Int ) -> runExceptT . runHandler' $ create
428+ let params = API. RequestParams (API. PaginationParams (API. Page 1 ) (API. PerPage 10 ))
429+ let fetchForAccounts = Handlers. listAccounts layer (V1. walId fixtureV1Wallet) params
430+ accounts <- runExceptT . runHandler' $ fetchForAccounts
431+ let accountIndices =
432+ case accounts of
433+ Left _ -> []
434+ Right accs -> map V1. accIndex $ API. wrData accs
435+ let reqParams = API. RequestParams (API. PaginationParams (API. Page 1 ) (API. PerPage 10 ))
436+ let filters = API. NoFilters
437+ let fetchForAccountAddresses ind =
438+ Handlers. getAccountAddresses layer (V1. walId fixtureV1Wallet)
439+ ind reqParams filters
440+ partialAddresses <- forM accountIndices $ \ (ind :: V1. AccountIndex ) ->
441+ runExceptT . runHandler' $ fetchForAccountAddresses ind
442+ case accounts of
443+ Right accs -> (map V1. accAddresses $ API. wrData accs)
444+ `shouldBe`
445+ (map (\ (Right bal) -> (V1. acaAddresses . API. wrData) bal) partialAddresses)
446+ Left err -> fail (show err)
447+
448+
449+ prop " applied to accounts that were just updated via address creation is the same as obtained from GetAccounts" $ withMaxSuccess 25 $ do
450+ monadicIO $ do
451+ withFixture $ \ _ layer _ Fixture {.. } -> do
452+ -- We create 4 accounts, plus one is created automatically
453+ -- by the 'createWallet' endpoint, for a total of 5.
454+ forM_ [1 .. 4 ] $ \ (_i :: Int ) ->
455+ WalletLayer. createAccount layer (V1. walId fixtureV1Wallet)
456+ fixtureNewAccountRq
457+ accountsBefore <- WalletLayer. getAccounts layer (V1. walId fixtureV1Wallet)
458+ let accountIndices =
459+ case accountsBefore of
460+ Left _ -> []
461+ Right accs -> map V1. accIndex $ IxSet. toList accs
462+ forM_ accountIndices $ \ (accIdx :: V1. AccountIndex ) ->
463+ WalletLayer. createAddress layer (V1. NewAddress Nothing accIdx (V1. walId fixtureV1Wallet))
464+ accountsUpdated <- WalletLayer. getAccounts layer (V1. walId fixtureV1Wallet)
465+ let params = API. RequestParams (API. PaginationParams (API. Page 1 ) (API. PerPage 10 ))
466+ let filters = API. NoFilters
467+ partialAddresses <- forM accountIndices $ \ (ind :: V1. AccountIndex ) ->
468+ WalletLayer. getAccountAddresses layer (V1. walId fixtureV1Wallet) ind params filters
469+ case accountsUpdated of
470+ Right accs -> (map V1. accAddresses $ IxSet. toList accs)
471+ `shouldBe`
472+ (map (\ (Right addr) -> API. wrData addr) partialAddresses)
473+ Left err -> fail (show err)
474+
475+
476+ describe " GetAccountBalance" $ do
477+
478+ prop " gives zero balance for newly created account" $ withMaxSuccess 25 $ do
479+ monadicIO $ do
480+ withFixture $ \ _ layer _ Fixture {.. } -> do
481+ let zero = V1 (mkCoin 0 )
482+ (Right V1. Account {.. }) <-
483+ WalletLayer. createAccount layer (V1. walId fixtureV1Wallet)
484+ fixtureNewAccountRq
485+ res <- WalletLayer. getAccountBalance layer (V1. walId fixtureV1Wallet)
486+ accIndex
487+ case res of
488+ Left e -> fail (show e)
489+ Right balance -> balance `shouldBe` V1. AccountBalance zero
490+
491+ prop " fails if the account doesn't exists" $ withMaxSuccess 50 $ do
492+ monadicIO $ do
493+ withFixture $ \ _ layer _ Fixture {.. } -> do
494+ res <- WalletLayer. getAccountBalance layer
495+ (V1. walId fixtureV1Wallet)
496+ (V1. unsafeMkAccountIndex 2147483648 )
497+ case res of
498+ Left (WalletLayer. GetAccountError (V1 (Kernel. UnknownHdAccount _))) ->
499+ return ()
500+ Left unexpectedErr ->
501+ fail $ " expecting different failure than " <> show unexpectedErr
502+ Right _ ->
503+ let errMsg = " expecting account not to be retrieved, but it was. random WalletId "
504+ % build
505+ % " , V1.Wallet "
506+ in fail $ formatToString errMsg (V1. walId fixtureV1Wallet)
507+
508+
509+
510+ prop " applied to each newly created account gives balances as obtained from GetAccounts" $ withMaxSuccess 25 $ do
511+ monadicIO $ do
512+ withFixture $ \ _ layer _ Fixture {.. } -> do
513+ -- We create 4 accounts, plus one is created automatically
514+ -- by the 'createWallet' endpoint, for a total of 5.
515+ forM_ [1 .. 4 ] $ \ (_i :: Int ) ->
516+ WalletLayer. createAccount layer (V1. walId fixtureV1Wallet)
517+ fixtureNewAccountRq
518+ accounts <- WalletLayer. getAccounts layer (V1. walId fixtureV1Wallet)
519+ let accountIndices =
520+ case accounts of
521+ Left _ -> []
522+ Right accs -> map V1. accIndex $ IxSet. toList accs
523+ partialBalances <- forM accountIndices $ \ (ind :: V1. AccountIndex ) ->
524+ WalletLayer. getAccountBalance layer (V1. walId fixtureV1Wallet) ind
525+ case (accounts, length partialBalances /= 5 ) of
526+ (Right accs, False ) -> (map (V1. AccountBalance . V1. accAmount) $ IxSet. toList accs)
527+ `shouldBe`
528+ (map (\ (Right bal) -> bal) partialBalances)
529+ _ -> fail " expecting to get 5 balances from partial getters"
530+
531+
532+ prop " and this also works when called from Servant" $ withMaxSuccess 25 $ do
533+ monadicIO $ do
534+ withFixture $ \ _ layer _ Fixture {.. } -> do
535+ let create = Handlers. newAccount layer (V1. walId fixtureV1Wallet) fixtureNewAccountRq
536+ -- We create 4 accounts, plus one is created automatically
537+ -- by the 'createWallet' endpoint, for a total of 5.
538+ forM_ [1 .. 4 ] $ \ (_i :: Int ) -> runExceptT . runHandler' $ create
539+ let params = API. RequestParams (API. PaginationParams (API. Page 1 ) (API. PerPage 10 ))
540+ let fetchForAccounts = Handlers. listAccounts layer (V1. walId fixtureV1Wallet) params
541+ accounts <- runExceptT . runHandler' $ fetchForAccounts
542+ let accountIndices =
543+ case accounts of
544+ Left _ -> []
545+ Right accs -> map V1. accIndex $ API. wrData accs
546+ let fetchForAccountBalance = Handlers. getAccountBalance layer (V1. walId fixtureV1Wallet)
547+ partialBalances <- forM accountIndices $ \ (ind :: V1. AccountIndex ) ->
548+ runExceptT . runHandler' $ fetchForAccountBalance ind
549+ case (accounts, length partialBalances /= 5 ) of
550+ (Right accs, False ) -> (map (V1. AccountBalance . V1. accAmount) $ API. wrData accs)
551+ `shouldBe`
552+ (map (\ (Right bal) -> API. wrData bal) partialBalances)
553+ _ -> fail " expecting to get 5 balances from partial getters"
0 commit comments