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

[CBR-371] unit tests for listing addresses #3563

Merged
merged 5 commits into from
Sep 17, 2018
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
8 changes: 4 additions & 4 deletions wallet-new/src/Cardano/Wallet/WalletLayer/Kernel/Addresses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,9 +71,9 @@ createAddress wallet
-- 1 2 .. 100
-- <deletion of an account happens, leaving a hole in the indices>
--
-- / /
-- +-----+-----+----------/---------------/-------------------+------+
-- | A1 | A2 | ... X \/ | A100 |
-- / /
-- +-----+-----+---------/--------------/---------------------+------+
-- | A1 | A2 | ... X X | A100 |
-- | | | \ \ | |
-- +-----+-----+----------\--------------\--------------------+------+
-- 1 2 .. 10 \ \ 30 .. 100
Expand Down Expand Up @@ -149,7 +149,7 @@ takeIndexed db n acc (currentIndex, (a:as))
new = map (toV1 a) . sortBy autoKey . IxSet.toList $ slice
in -- For the next iterations, the index will always be 0 as we
-- are hopping from one ixset to the other, collecting addresses.
takeIndexed db (n - IxSet.size slice) (new <> acc) (0, as)
takeIndexed db (n - IxSet.size slice) (acc <> new) (0, as)
where
toV1 :: HD.HdAccount -> Indexed HD.HdAddress -> V1.WalletAddress
toV1 hdAccount ixed = toAddress hdAccount (ixed ^. ixedIndexed)
Expand Down
180 changes: 179 additions & 1 deletion wallet-new/test/unit/Test/Spec/Addresses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ import Control.Monad.Except (runExceptT)
import Data.Acid (update)
import qualified Data.ByteString as B
import qualified Data.Map.Strict as M
import qualified Data.Set as S
import Formatting (build, sformat)
import Servant.Server

Expand All @@ -16,7 +17,7 @@ import Test.QuickCheck (arbitrary, choose, elements, withMaxSuccess,
(===))
import Test.QuickCheck.Monadic (PropertyM, monadicIO, pick)

import Pos.Core (Address)
import Pos.Core (Address, addrRoot)
import Pos.Crypto (EncryptedSecretKey, emptyPassphrase, firstHardened,
safeDeterministicKeyGen)

Expand All @@ -37,13 +38,15 @@ import Cardano.Wallet.Kernel.DB.HdWallet.Create (initHdRoot)
import Cardano.Wallet.Kernel.DB.HdWallet.Derivation
(HardeningMode (..), deriveIndex)
import Cardano.Wallet.Kernel.DB.InDb (InDb (..), fromDb)
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet
import Cardano.Wallet.Kernel.Internal (PassiveWallet, wallets)
import qualified Cardano.Wallet.Kernel.Keystore as Keystore
import qualified Cardano.Wallet.Kernel.Read as Kernel
import Cardano.Wallet.Kernel.Types (AccountId (..), WalletId (..))
import qualified Cardano.Wallet.Kernel.Wallets as Kernel
import Cardano.Wallet.WalletLayer (PassiveWalletLayer)
import qualified Cardano.Wallet.WalletLayer as WalletLayer
import qualified Cardano.Wallet.WalletLayer.Kernel.Accounts as Accounts
import qualified Cardano.Wallet.WalletLayer.Kernel.Addresses as Addresses
import qualified Cardano.Wallet.WalletLayer.Kernel.Conv as Kernel.Conv
import qualified Cardano.Wallet.WalletLayer.Kernel.Wallets as Wallets
Expand Down Expand Up @@ -123,6 +126,38 @@ prepareAddressFixture n = do
let SliceOf{..} = Addresses.getAddresses (RequestParams pp) db'
return . map AddressFixture $ paginatedSlice

prepareAddressesFixture
:: Int -- ^ Number of Accounts to create.
-> Int -- ^ Number of 'Address per account to create.
-> Fixture.GenPassiveWalletFixture (M.Map V1.AccountIndex [V1.WalletAddress])
prepareAddressesFixture acn adn = do
spendingPassword <- Fixture.genSpendingPassword
newWalletRq <- WalletLayer.CreateWallet <$> Wallets.genNewWalletRq spendingPassword
return $ \pw -> do
let newAcc (n :: Int) = (V1.NewAccount spendingPassword ("My Account " <> show n))
Right v1Wallet <- Wallets.createWallet pw newWalletRq
forM_ [1..acn] $ \n ->
Accounts.createAccount pw (V1.walId v1Wallet) (newAcc n)
-- Get all the available accounts
db <- Kernel.getWalletSnapshot pw
let Right accs = Accounts.getAccounts (V1.walId v1Wallet) db
let accounts = IxSet.toList accs
length accounts `shouldBe` (acn + 1)
Copy link
Contributor

Choose a reason for hiding this comment

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

I would recommend flipping the logic and doing something like:

prepareAddressFixture acn adn = 
    -- We recompute the values to account for the fact that creating a new wallet
    -- @always@ come with a fresh account, and this account always have a fresh address
    -- associated with it.
    let requestedAccounts = max 0 (acn - 1)
    let requestedAddresses = max 0 (adn - 1)

Then, you can use those two let bindings all over the place without having to worry about +1/-1 arithmetic, both in the fixtures and in the tests. Furthermore, you segregate the comment on why we do this exactly in one point in the code, without this assumption being scattered all over the place.

Copy link
Member Author

Choose a reason for hiding this comment

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

I'm not sure I understand what are the semantics of requestedAddresses. Some accounts will have requestedAddresses addresses, while the first account will have requestedAddresses+1. Also requestedAccounts should never be 0, as one account is created by default.

let insertAddresses :: V1.Account -> IO (V1.AccountIndex, [V1.WalletAddress])
insertAddresses acc = do
let accId = V1.accIndex acc
let newAddressRq = V1.NewAddress spendingPassword accId (V1.walId v1Wallet)
res <- replicateM adn (Addresses.createAddress pw newAddressRq)
case sequence res of
Left e -> error (show e)
Right addr -> return (accId, addr)
res <- mapM insertAddresses accounts
return $ M.fromList res

expectedNumber :: Int -> Int -> Int
expectedNumber acc adr = (acc + 1)*(adr + 1) - acc
Copy link
Contributor

Choose a reason for hiding this comment

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

I think if you bake the logic inside the fixture, you might be able to remove this.



withFixture :: ( Keystore.Keystore
-> PassiveWalletLayer IO
-> PassiveWallet
Expand All @@ -145,6 +180,18 @@ withAddressFixtures n =
Fixture.withPassiveWalletFixture $ do
prepareAddressFixture n

withAddressesFixtures :: Int -> Int ->
( Keystore.Keystore
-> PassiveWalletLayer IO
-> PassiveWallet
-> M.Map V1.AccountIndex [V1.WalletAddress]
-> IO a
)
-> PropertyM IO a
withAddressesFixtures n m =
Fixture.withPassiveWalletFixture $ do
prepareAddressesFixture n m

spec :: Spec
spec = describe "Addresses" $ do
describe "CreateAddress" $ do
Expand Down Expand Up @@ -348,6 +395,137 @@ spec = describe "Addresses" $ do
slice rNumOfPages rNumPerPage fixtureAddresses
pure (toBeCheckedAddresses === correctAddresses)

describe "Address listing with multiple Accounts (Servant)" $ do
prop "page 0, per page 0" $ withMaxSuccess 20 $ do
monadicIO $
withAddressesFixtures 4 4 $ \_ layer _ _ -> do
let pp = PaginationParams (Page 0) (PerPage 0)
res <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp)
case res of
Right wr | null (wrData wr) -> pure ()
_ -> fail ("Got " ++ show res)

prop "it yields the correct number of results" $ withMaxSuccess 20 $ do
monadicIO $
withAddressesFixtures 3 4 $ \_ layer _ _ -> do
let pp = PaginationParams (Page 1) (PerPage 40)
res <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp)
case res of
Right wr -> do
-- this takes into account that there is an initial account
-- and each account has an initial address (but not the initial
-- account thus the -1)
Copy link
Contributor

Choose a reason for hiding this comment

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

Yes, unfortunately if you create multiple accounts for the same wallet those won't come with an extra associated address. But ideally, if you can bake this inside the fixture creation, test logic should hopefully simplify 😉

Copy link
Member Author

Choose a reason for hiding this comment

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

I should delete this comment.

length (wrData wr) `shouldBe` expectedNumber 3 4
_ -> fail ("Got " ++ show res)

prop "is deterministic" $ withMaxSuccess 20 $ do
monadicIO $
withAddressesFixtures 3 8 $ \_ layer _ _ -> do
let (expectedTotal :: Int) = expectedNumber 3 8
let pp = PaginationParams (Page 1) (PerPage 40)
let pp1 = PaginationParams (Page 1) (PerPage (quot expectedTotal 3 + 1))
let pp2 = PaginationParams (Page 2) (PerPage (quot expectedTotal 3 + 1))
let pp3 = PaginationParams (Page 3) (PerPage (quot expectedTotal 3 + 1))
Copy link
Contributor

Choose a reason for hiding this comment

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

It's a bit dense for the reader to try to figure out why you do the quot expectedTotal dance, but hopefully we can simplify this one.

res <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp)
res' <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp)
res1 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp1)
res1' <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp1)
res2 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp2)
res2' <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp2)
res3 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp3)
res3' <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp3)
res `shouldBe` res'
res1 `shouldBe` res1'
res2 `shouldBe` res2'
res3 `shouldBe` res3'
Copy link
Contributor

Choose a reason for hiding this comment

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

Idea: considering is very error prone to go for this style of foo, foo', bar, bar', why don't you write something like this?

                        res <- runExceptT $ runHandler' $ do
                            r1 <- Handlers.listAddresses layer (RequestParams pp)
                            r2 <- Handlers.listAddresses layer (RequestParams pp)
                            pure (r1 === r2)
                        res1 <- runExceptT $ runHandler' $ do
                            r1 <- Handlers.listAddresses layer (RequestParams pp1)
                            r2 <- Handlers.listAddresses layer (RequestParams pp1)
                            pure (r1 === r2)
                       assert $ conjoin [res, res1]

Even better, I think you can simplify this even further by noticing how this is just iterating over [pp,pp1,pp2,pp3] but executing mechanical actions, so you can write something which runs a forM, calls internally replicateM 2 , yields a Property and conjoin everything at the end.


prop "yields the correct set of resutls" $ withMaxSuccess 20 $ do
monadicIO $
withAddressesFixtures 4 8 $ \_ layer _ _ -> do
let (expectedTotal :: Int) = expectedNumber 4 8
let pp = PaginationParams (Page 1) (PerPage 50)
let pp1 = PaginationParams (Page 1) (PerPage (quot expectedTotal 3 + 1))
let pp2 = PaginationParams (Page 2) (PerPage (quot expectedTotal 3 + 1))
let pp3 = PaginationParams (Page 3) (PerPage (quot expectedTotal 3 + 1))
res <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp)
res1 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp1)
res2 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp2)
res3 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp3)
case (res, res1, res2, res3) of
(Right wr, Right wr1, Right wr2, Right wr3) -> do
length (wrData wr) `shouldBe` expectedTotal
let con = wrData wr1 <> wrData wr2 <> wrData wr3
length con `shouldBe` expectedTotal
S.fromList con `shouldBe` S.fromList (wrData wr)
(addrRoot . V1.unV1 . V1.addrId <$> con)
`shouldBe` (addrRoot . V1.unV1 . V1.addrId <$> wrData wr)
_ -> fail ("Got " ++ show res)

prop "yields the correct ordered resutls when there is one account" $ withMaxSuccess 20 $ do
monadicIO $
withAddressesFixtures 0 15 $ \_ layer _ _ -> do
let (expectedTotal :: Int) = expectedNumber 0 15
let pp = PaginationParams (Page 1) (PerPage 50)
let pp1 = PaginationParams (Page 1) (PerPage (quot expectedTotal 3 + 1))
let pp2 = PaginationParams (Page 2) (PerPage (quot expectedTotal 3 + 1))
let pp3 = PaginationParams (Page 3) (PerPage (quot expectedTotal 3 + 1))
res <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp)
res1 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp1)
res2 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp2)
res3 <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp3)
case (res, res1, res2, res3) of
(Right wr, Right wr1, Right wr2, Right wr3) -> do
length (wrData wr) `shouldBe` expectedTotal
let con = wrData wr1 <> wrData wr2 <> wrData wr3
length con `shouldBe` expectedTotal
S.fromList con `shouldBe` S.fromList (wrData wr)
(addrRoot . V1.unV1 . V1.addrId <$> con)
`shouldBe` (addrRoot . V1.unV1 . V1.addrId <$> wrData wr)
_ -> fail ("Got " ++ show res)


prop "yields the correct ordered resutls" $ withMaxSuccess 20 $ do
monadicIO $ do
forM_ [(4,8), (6,6), (5,7)] $ \(acc,adr) ->
withAddressesFixtures acc adr $ \_ layer _ _ -> do
forM_ [2..10] $ \k -> do
let indexes = [1..k]
let (expectedTotal :: Int) = expectedNumber acc adr
let pagesParams = map (\i -> PaginationParams (Page i) (PerPage (quot expectedTotal k + 1)))
indexes
let pp = PaginationParams (Page 1) (PerPage 50)
res <- runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams pp)
eiResultsArray <- forM pagesParams $ \ppi -> runExceptT $ runHandler' $ do
Handlers.listAddresses layer (RequestParams ppi)
let resultsArray = sequence eiResultsArray
case (res, resultsArray) of
(Right wr, Right wrList) -> do
let con = mconcat $ map wrData wrList
length (wrData wr) `shouldBe` expectedTotal
length con `shouldBe` expectedTotal
S.fromList con `shouldBe` S.fromList (wrData wr)
(addrRoot . V1.unV1 . V1.addrId <$> con)
`shouldBe` (addrRoot . V1.unV1 . V1.addrId <$> wrData wr)
_ -> fail ("Got " ++ show res)
Copy link
Contributor

Choose a reason for hiding this comment

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

This is a minor thing, but these tests feels very imperative rather than declarative. I don't know what we can do about it, but I suspect we might come up with some combinators which factor away duplication and mechanical reshuffling of the data and leave the logic of the tests exposes. I guess what we aim is something like:

myTest = do
    -- Initialisation
    -- Execution
    -- Checking of properties

Which is exactly what your tests are also doing, but each of these steps takes a lot of lines of code and is hard to track down the spirit of the test 😉


describe "ValidateAddress" $ do
describe "Address validation (wallet layer)" $ do
Expand Down
2 changes: 1 addition & 1 deletion wallet-new/test/unit/WalletUnitTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,7 @@ _showContext = do

tests :: Spec
tests = parallel $ describe "Wallet unit tests" $ do
Test.Spec.Addresses.spec
DeltaCompressionSpecs.spec
Test.Spec.Kernel.spec
Test.Spec.GetTransactions.spec
Expand All @@ -80,7 +81,6 @@ tests = parallel $ describe "Wallet unit tests" $ do
txMetaStorageSpecs
Test.Spec.CoinSelection.spec
Test.Spec.Keystore.spec
Test.Spec.Addresses.spec
Test.Spec.Wallets.spec
Test.Spec.NewPayment.spec
Test.Spec.Accounts.spec