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

Commit 64092a7

Browse files
committed
[CO-424] Some cleanups in preparation for adding new functionalities.
* [CO-424] new module SetupTestEnv.hs. Exports the function setupClient :: CLIOptions -> IO (WalletClient IO, Manager) which has been in-lined in main :: IO () before. * [CO-424] Module Functions.hs has been renamed to RandomStateWalk.hs. * [CO-424] Cleanups in Main.hs : Definitions related to the random state walk move to RandomStateWalk.hs * [CO-424] Add a new CLI option --hspec-options to pass options to HSpec. This supersedes --match and --seed. Example : launch_integration_tests --hspec-options '--skip Address'
1 parent 9b8f3a0 commit 64092a7

11 files changed

+121
-142
lines changed

wallet-new/README.md

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -188,14 +188,17 @@ $ nix-build -A walletIntegrationTests --arg useStackBinaries true
188188
> test, you can pass the `--check` flag to force the test to run again. `--check`
189189
> is used to confirm that results from one test match the results again.
190190
191-
Wallet integration tests can be used also with seed/match options that behave like hspec test runner (and are passed to).
192-
--match PATTERN - behave exactly like Hspec's --match allowing to run only a subset of tests
193-
--seed SEED - enable passing an external, predictable seed to the test runner
194-
Example allowing the use of concrete seed and testing Address related tests only:
195-
191+
The wallet integration tests support --hspec-options to pass options to HSpec.
192+
This can be used to set a seed for the PRNG, only run a matching set of tests or to
193+
skip some tests.
194+
Examples:
196195
```
197196
$ nix-build -A walletIntegrationTests -o launch_integration_tests
198-
$ ./launch_integration_tests --match 'Address' --seed 47286650
197+
$ ./launch_integration_tests --hspec-options '--skip Address --seed 47286650'
198+
199+
$ nix-build -A walletIntegrationTests -o launch_integration_tests
200+
$ ./launch_integration_tests --hspec-options '--match Address --seed 47286650'
201+
199202
```
200203

201204

wallet-new/cardano-sl-wallet-new.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -363,12 +363,13 @@ executable wal-integr-test
363363
-O2
364364
other-modules: CLI
365365
Types
366-
Functions
367366
Error
368367
Util
369368
WalletSpecs
370369
AccountSpecs
371370
AddressSpecs
371+
RandomStateWalk
372+
SetupTestEnv
372373
TransactionSpecs
373374
QuickCheckSpecs
374375

wallet-new/integration/AccountSpecs.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@ import Cardano.Wallet.API.Indices (accessIx)
1010
import Cardano.Wallet.Client.Http
1111
import Control.Lens
1212
import qualified Data.Text as T
13-
import Functions (randomTest)
1413
import Pos.Core.Common (mkCoin)
1514
import Test.Hspec
1615
import Test.QuickCheck (arbitrary, shuffle)

wallet-new/integration/AddressSpecs.hs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,14 +7,11 @@ import Universum
77

88
import Cardano.Wallet.Client.Http
99
import Control.Lens
10-
import Functions (randomTest)
1110
import Test.Hspec
1211
import Test.QuickCheck.Monadic (run)
1312

14-
1513
import Util
1614

17-
1815
addressSpecs :: WalletRef -> WalletClient IO -> Spec
1916
addressSpecs wRef wc = do
2017
describe "Addresses" $ do

wallet-new/integration/CLI.hs

Lines changed: 13 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -3,17 +3,16 @@
33
-- | Functions for working with command-line options.
44

55
module CLI
6-
( CLOptions (..)
6+
( CLIOptions (..)
77
, getOptions
88
) where
99

10-
import Universum
11-
10+
import Data.String (words)
1211
import Options.Applicative
13-
12+
import Universum
1413

1514
-- | Parser for command-line options.
16-
optionsParser :: Parser CLOptions
15+
optionsParser :: Parser CLIOptions
1716
optionsParser = do
1817
tlsClientCertPath <- strOption $
1918
long "tls-client-cert"
@@ -44,24 +43,18 @@ optionsParser = do
4443
<> help "Server port"
4544
<> showDefault
4645

47-
testRunnerMatch <- optional . strOption $
48-
long "match"
49-
<> metavar "PATTERN"
50-
<> help "Only tests that match PATTERN will be run"
46+
hSpecOptions <- fmap Data.String.words $ strOption $
47+
long "hspec-options"
48+
<> metavar "OPTIONS"
49+
<> value ""
50+
<> help "extra options to pass to HSpec"
5151
<> showDefault
5252

53-
testRunnerSeed <- optional . option auto $
54-
long "seed"
55-
<> metavar "SEED"
56-
<> help "Seed for a test runner"
57-
<> showDefault
58-
59-
60-
pure CLOptions{..}
53+
pure CLIOptions{..}
6154

6255

6356
-- | Get command-line options.
64-
getOptions :: IO CLOptions
57+
getOptions :: IO CLIOptions
6558
getOptions = execParser programInfo
6659
where
6760
programInfo = info (helper <*> optionsParser) $
@@ -70,12 +63,11 @@ getOptions = execParser programInfo
7063

7164

7265
-- | The configuration for the application.
73-
data CLOptions = CLOptions
66+
data CLIOptions = CLIOptions
7467
{ tlsClientCertPath :: FilePath
7568
, tlsPrivKeyPath :: FilePath
7669
, tlsCACertPath :: FilePath
7770
, serverHost :: String
7871
, serverPort :: Int
79-
, testRunnerMatch :: Maybe String
80-
, testRunnerSeed :: Maybe Integer
72+
, hSpecOptions :: [String]
8173
} deriving (Show, Eq)

wallet-new/integration/Main.hs

Lines changed: 17 additions & 89 deletions
Original file line numberDiff line numberDiff line change
@@ -5,115 +5,43 @@ module Main where
55

66
import Universum
77

8-
import Cardano.Wallet.Client.Http
9-
import Data.Map (fromList)
10-
import Data.Traversable (for)
11-
import Data.X509.File (readSignedObject)
8+
import Cardano.Wallet.Client.Http (WalletClient)
129
import Network.HTTP.Client (Manager)
10+
import qualified QuickCheckSpecs as QuickCheck
1311
import System.Environment (withArgs)
14-
import System.IO (hSetEncoding, stdout, utf8)
15-
import Test.Hspec
12+
import Test.Hspec (Spec, hspec)
1613

1714
import AccountSpecs (accountSpecs)
1815
import AddressSpecs (addressSpecs)
19-
import CLI
20-
import Functions
16+
import CLI (CLIOptions (..), getOptions)
17+
import RandomStateWalk (randomStateWalkTest)
18+
import SetupTestEnv (setupClient)
19+
import System.IO (hSetEncoding, stdout, utf8)
2120
import TransactionSpecs (transactionSpecs)
22-
import Types
23-
import Util (WalletRef, newWalletRef)
21+
import Util (WalletRef, newWalletRef, printT)
2422
import WalletSpecs (walletSpecs)
2523

26-
import qualified Data.ByteString.Char8 as B8
27-
import qualified QuickCheckSpecs as QuickCheck
28-
29-
30-
-- | Here we want to run main when the (local) nodes
31-
-- have started.
24+
-- | Here we want to run main when the (local) nodes have started.
3225
main :: IO ()
3326
main = do
3427
hSetEncoding stdout utf8
35-
CLOptions {..} <- getOptions
36-
37-
-- TODO (akegalj): run server cluster in haskell, instead of using shell scripts
38-
-- serverThread <- async (runWalletServer options)
28+
options@CLIOptions {..} <- getOptions
3929

4030
printT "Starting the integration testing for wallet."
41-
42-
let serverId = (serverHost, B8.pack $ show serverPort)
43-
caChain <- readSignedObject tlsCACertPath
44-
clientCredentials <- orFail =<< credentialLoadX509 tlsClientCertPath tlsPrivKeyPath
45-
manager <- newManager $ mkHttpsManagerSettings serverId caChain clientCredentials
46-
47-
let baseUrl = BaseUrl Https serverHost serverPort mempty
48-
49-
let walletClient :: MonadIO m => WalletClient m
50-
walletClient = withThrottlingRetry
51-
. liftClient
52-
$ mkHttpClient baseUrl manager
53-
31+
(walletClient, manager) <- setupClient options
5432
-- Acquire the initial state for the deterministic tests
5533
wRef <- newWalletRef
5634

57-
-- NOTE Our own CLI options interfere with `hspec` which parse them for
58-
-- itself when executed, leading to a VERY unclear message:
59-
--
60-
-- cardano-integration-test: unrecognized option `--tls-ca-cert'
61-
-- Try `cardano-integration-test --help' for more information.
62-
--
63-
-- See also: https://github.com/hspec/hspec/issues/135
64-
65-
let optionsFromAbove = case (testRunnerMatch, testRunnerSeed) of
66-
(Nothing, Nothing) -> []
67-
(Nothing, Just seed) -> ["--seed", show seed]
68-
(Just match, Nothing) -> ["-m", match]
69-
(Just match, Just seed) -> ["-m", match, "--seed", show seed]
70-
71-
withArgs optionsFromAbove $ do
35+
-- main uses its own argument parsing.
36+
-- Don't use 'hspec $ do' it would cause strange error messages,
37+
-- because hspec would try to interpret the integration-test cmd arguments.
38+
withArgs hSpecOptions $ do
7239
printT "Starting deterministic tests."
73-
printT $ "match from options: " <> show testRunnerMatch
74-
printT $ "seed from options: " <> show testRunnerSeed
75-
40+
printT $ "HSpec options: " <> show hSpecOptions
7641
hspec $ deterministicTests wRef walletClient manager
7742

7843
printT $ "The 'runActionCheck' tests were disabled because they were highly un-reliable."
79-
when False $ do
80-
walletState <- initialWalletState walletClient
81-
82-
printT $ "Initial wallet state: " <> show walletState
83-
84-
-- some monadic fold or smth similar
85-
void $ runActionCheck
86-
walletClient
87-
walletState
88-
actionDistribution
89-
where
90-
orFail :: MonadFail m => Either String a -> m a
91-
orFail =
92-
either (fail . ("Error decoding X509 certificates: " <>)) return
93-
94-
actionDistribution :: ActionProbabilities
95-
actionDistribution =
96-
(PostWallet, Weight 2)
97-
:| (PostTransaction, Weight 5)
98-
: fmap (, Weight 1) [minBound .. maxBound]
99-
100-
initialWalletState :: WalletClient IO -> IO WalletState
101-
initialWalletState wc = do
102-
-- We will have single genesis wallet in intial state that was imported from launching script
103-
_wallets <- fromResp $ getWallets wc
104-
_accounts <- concat <$> for _wallets (fromResp . getAccounts wc . walId)
105-
-- Lets set all wallet passwords for initial wallets (genesis) to default (emptyPassphrase)
106-
let _lastAction = NoOp
107-
_walletsPass = fromList $ map ((, V1 mempty) . walId) _wallets
108-
_addresses = concatMap accAddresses _accounts
109-
-- TODO(akegalj): I am not sure does importing a genesis wallet (which we do prior launching integration tests) creates a transaction
110-
-- If it does, we should add this transaction to the list
111-
_transactions = mempty
112-
_actionsNum = 0
113-
_successActions = mempty
114-
return WalletState {..}
115-
where
116-
fromResp = (either throwM (pure . wrData) =<<)
44+
when False $ randomStateWalkTest walletClient
11745

11846
deterministicTests :: WalletRef -> WalletClient IO -> Manager -> Spec
11947
deterministicTests wref wc manager = do

wallet-new/integration/Functions.hs renamed to wallet-new/integration/RandomStateWalk.hs

Lines changed: 39 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,8 @@
77
{-# LANGUAGE TypeApplications #-}
88

99

10-
module Functions
11-
( runActionCheck
12-
, printT
13-
, randomTest
14-
) where
10+
module RandomStateWalk (randomStateWalkTest)
11+
where
1512

1613
import Universum hiding (init, throwM, uncons)
1714

@@ -23,16 +20,18 @@ import Data.Aeson.Diff (diff)
2320
import Data.Aeson.Encode.Pretty (encodePretty)
2421
import Data.Coerce (coerce)
2522
import Data.List (isInfixOf, nub, uncons, (!!), (\\))
23+
import Data.Map (fromList)
24+
import Data.Traversable (for)
25+
2626
import Servant.Client (GenResponse (..))
27-
import Test.Hspec (Spec, describe, expectationFailure, hspec,
28-
shouldBe, shouldContain)
27+
import Test.Hspec (describe, expectationFailure, hspec, shouldBe,
28+
shouldContain)
2929
import Test.Hspec.QuickCheck (prop)
3030
import Test.QuickCheck (arbitrary, choose, elements, frequency,
3131
quickCheck, suchThat, withMaxSuccess)
3232
import Test.QuickCheck.Monadic (PropertyM, monadic, monadicIO, pick,
3333
pre, run, stop)
34-
import Test.QuickCheck.Property (Property, Testable, ioProperty,
35-
rejected)
34+
import Test.QuickCheck.Property (Property, ioProperty, rejected)
3635
import Text.Show.Pretty (ppShow)
3736

3837
import Cardano.Wallet.API.Response (WalletResponse (..))
@@ -50,6 +49,13 @@ import Error (WalletTestError (..))
5049
import Types
5150
import Util
5251

52+
randomStateWalkTest :: WalletClient IO -> IO ()
53+
randomStateWalkTest walletClient = do
54+
printT "Starting the integration testing for wallet."
55+
walletState <- initialWalletState walletClient
56+
printT $ "Initial wallet state: " <> show walletState
57+
void $ runActionCheck walletClient walletState actionDistribution
58+
5359
newtype RefT s m a
5460
= RefT
5561
{ unRefT :: ReaderT (IORef s) m a
@@ -722,13 +728,33 @@ checkInvariant
722728
checkInvariant True _ = pure ()
723729
checkInvariant False walletTestErr = liftIO $ throwM walletTestErr
724730

731+
actionDistribution :: ActionProbabilities
732+
actionDistribution =
733+
(PostWallet, Weight 2)
734+
:| (PostTransaction, Weight 5)
735+
: fmap (, Weight 1) [minBound .. maxBound]
736+
737+
initialWalletState :: WalletClient IO -> IO WalletState
738+
initialWalletState wc = do
739+
-- We will have single genesis wallet in intial state that was imported from launching script
740+
_wallets <- fromResp $ getWallets wc
741+
_accounts <- concat <$> for _wallets (fromResp . getAccounts wc . walId)
742+
-- Lets set all wallet passwords for initial wallets (genesis) to default (emptyPassphrase)
743+
let _lastAction = NoOp
744+
_walletsPass = fromList $ map ((, V1 mempty) . walId) _wallets
745+
_addresses = concatMap accAddresses _accounts
746+
-- TODO(akegalj): I am not sure does importing a genesis wallet (which we do prior launching integration tests) creates a transaction
747+
-- If it does, we should add this transaction to the list
748+
_transactions = mempty
749+
_actionsNum = 0
750+
_successActions = mempty
751+
return WalletState {..}
752+
where
753+
fromResp = (either throwM (pure . wrData) =<<)
754+
725755
log :: MonadIO m => Text -> m ()
726756
log = putStrLn . mappend "[TEST-LOG] "
727757

728-
-- | Output for @Text@.
729-
printT :: Text -> IO ()
730-
printT = putStrLn
731-
732758
ppShowT :: Show a => a -> Text
733759
ppShowT = fromString . ppShow
734760

@@ -741,8 +767,3 @@ walletIdIsNotGenesis walletId = do
741767
mwallet <- (fmap fst . uncons) . filter ((walletId ==) . walId) <$> use wallets
742768
whenJust mwallet $ \wal ->
743769
pre (walName wal /= "Genesis wallet")
744-
745-
746-
randomTest :: (Testable a) => String -> Int -> PropertyM IO a -> Spec
747-
randomTest msg maxSuccesses =
748-
prop msg . withMaxSuccess maxSuccesses . monadicIO
Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
{-# LANGUAGE LambdaCase #-}
2+
module SetupTestEnv where
3+
import Universum
4+
5+
import Cardano.Wallet.Client.Http
6+
import CLI
7+
import qualified Data.ByteString.Char8 as B8
8+
import Data.X509.File (readSignedObject)
9+
import Network.HTTP.Client (Manager)
10+
11+
setupClient :: CLIOptions -> IO (WalletClient IO, Manager)
12+
setupClient CLIOptions {..} = do
13+
let serverId = (serverHost, B8.pack $ show serverPort)
14+
caChain <- readSignedObject tlsCACertPath
15+
clientCredentials <- credentialLoadX509 tlsClientCertPath tlsPrivKeyPath >>= \case
16+
Right a -> return a
17+
Left err -> fail $ "Error decoding X509 certificates: " <> err
18+
manager <- newManager $ mkHttpsManagerSettings serverId caChain clientCredentials
19+
20+
let
21+
baseUrl = BaseUrl Https serverHost serverPort mempty
22+
walletClient :: MonadIO m => WalletClient m
23+
walletClient = withThrottlingRetry
24+
. liftClient
25+
$ mkHttpClient baseUrl manager
26+
27+
return (walletClient, manager)
28+

wallet-new/integration/TransactionSpecs.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@ import Universum
77

88
import Cardano.Wallet.Client.Http
99
import Control.Lens
10-
import Functions (randomTest)
1110
import Test.Hspec
1211
import Test.QuickCheck.Monadic (PropertyM, run)
1312
import Text.Show.Pretty (ppShow)

0 commit comments

Comments
 (0)