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

Commit

Permalink
[CBR-371] test fail
Browse files Browse the repository at this point in the history
  • Loading branch information
kderme committed Sep 9, 2018
1 parent ff671bb commit f271f03
Show file tree
Hide file tree
Showing 2 changed files with 97 additions and 4 deletions.
95 changes: 94 additions & 1 deletion wallet-new/test/unit/Test/Spec/Addresses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ import Universum
import Control.Monad.Except (runExceptT)
import Data.Acid (update)
import qualified Data.ByteString as B
-- import qualified Data.List as L
import qualified Data.Map.Strict as M
import Formatting (build, sformat)
import Servant.Server
Expand All @@ -15,7 +16,7 @@ import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (arbitrary, choose, withMaxSuccess)
import Test.QuickCheck.Monadic (PropertyM, monadicIO, pick)

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

import Cardano.Wallet.API.Request (RequestParams (..))
Expand Down Expand Up @@ -105,6 +106,35 @@ prepareAddressFixture n = do
Left e -> error (show e)
Right addr -> return (map AddressFixture addr)

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) (WalletLayer.CreateHdAccountRandomIndex $ 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)
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


withFixture :: ( Keystore.Keystore
-> PassiveWalletLayer IO
-> PassiveWallet
Expand All @@ -127,9 +157,72 @@ 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
describe "Address listing with multiple Accounts (Servant)" $ do


prop "page 1, 2 pages" $ withMaxSuccess 20 $ do
monadicIO $
withAddressesFixtures 3 8 $ \_ layer _ _ -> do
let (expectedTotal :: Int) = (3 + 1)*(8 + 1) -1
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))
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
length (wrData wr1) + length (wrData wr2) + length (wrData wr3) `shouldBe` expectedTotal
(addrRoot . V1.unV1 . V1.addrId <$> wrData wr1 <> wrData wr2 <> wrData wr3)
`shouldBe` (addrRoot . V1.unV1 . V1.addrId <$> wrData wr) -- (addrRoot . V1.unV1 . V1.addrId <$> concat (M.elems mp))
-- (addrRoot . V1.unV1 . V1.addrId <$> wrData wr1 <> wrData wr2) `shouldSatisfy`
-- (L.isSubsequenceOf (addrRoot . V1.unV1 . V1.addrId <$> concat (M.elems mp)))
_ -> fail ("Got " ++ show res)

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 "page 1, per page 40" $ 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
length (wrData wr) `shouldBe` ((3 + 1)*(4 + 1) - 1)
_ -> fail ("Got " ++ show res)


describe "Address creation (wallet layer)" $ do
prop "works as expected in the happy path scenario" $ withMaxSuccess 200 $
monadicIO $ do
Expand Down
6 changes: 3 additions & 3 deletions wallet-new/test/unit/WalletUnitTest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Main (main) where
import Universum

import Formatting (build, sformat)
import Test.Hspec (Spec, describe, hspec, parallel)
import Test.Hspec (Spec, describe, hspec)

import InputSelection.Evaluation (evalUsingGenData, evalUsingReplay)
import InputSelection.Evaluation.Options (Command (..), evalCommand,
Expand Down Expand Up @@ -69,7 +69,8 @@ _showContext = do
-------------------------------------------------------------------------------}

tests :: Spec
tests = parallel $ describe "Wallet unit tests" $ do
tests = 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

0 comments on commit f271f03

Please sign in to comment.