Skip to content

Commit

Permalink
Merge pull request #365 from input-output-hk/piotr/cli_integration_tests
Browse files Browse the repository at this point in the history
Transaction tests via CLI
  • Loading branch information
piotr-iohk authored Jun 5, 2019
2 parents dca30dd + 07aac25 commit 626be50
Show file tree
Hide file tree
Showing 12 changed files with 548 additions and 87 deletions.
2 changes: 0 additions & 2 deletions cardano-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,7 @@ executable cardano-wallet
, cardano-wallet-core
, cardano-wallet-http-bridge
, docopt
, file-embed
, http-client
, regex-applicative
, servant-client
, servant-client-core
, servant-server
Expand Down
4 changes: 3 additions & 1 deletion exe/launcher/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Main where
import Prelude

import Cardano.CLI
( Port, help, parseArgWith )
( Port, help, parseArgWith, showVersion )
import Cardano.Launcher
( Command (Command)
, ProcessHasExited (ProcessHasExited)
Expand Down Expand Up @@ -59,6 +59,7 @@ in the directory.
Usage:
cardano-wallet-launcher [options]
cardano-wallet-launcher -h | --help
cardano-wallet-launcher --version

Options:
--network <STRING> testnet, staging, or mainnet [default: testnet]
Expand All @@ -71,6 +72,7 @@ main = do
args <- parseArgsOrExit cli =<< getArgs
when (args `isPresent` (longOption "help")) $ help cli
when (args `isPresent` (shortOption 'h')) $ help cli
when (args `isPresent` (longOption "version")) showVersion

network <- args `parseArg` longOption "network"
bridgePort <- args `parseArg` longOption "http-bridge-port"
Expand Down
21 changes: 2 additions & 19 deletions exe/wallet/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

Expand Down Expand Up @@ -35,6 +34,7 @@ import Cardano.CLI
, parseArgWith
, putErrLn
, setUtf8Encoding
, showVersion
)
import Cardano.Wallet
( newWalletLayer )
Expand All @@ -59,16 +59,12 @@ import Cardano.Wallet.Primitive.Mnemonic
( entropyToMnemonic, genEntropy, mnemonicToText )
import Cardano.Wallet.Primitive.Types
( DecodeAddress, EncodeAddress )
import Control.Applicative
( many )
import Control.Arrow
( second )
import Control.Monad
( when )
import Data.Aeson
( (.:) )
import Data.FileEmbed
( embedFile )
import Data.Function
( (&) )
import Data.Functor
Expand Down Expand Up @@ -109,8 +105,6 @@ import System.Exit
( exitFailure )
import System.IO
( BufferMode (NoBuffering), hSetBuffering, stderr, stdout )
import Text.Regex.Applicative
( anySym, few, match, string, sym )

import qualified Cardano.Wallet.Api.Server as Server
import qualified Cardano.Wallet.DB.MVar as MVar
Expand All @@ -119,7 +113,6 @@ import qualified Cardano.Wallet.HttpBridge.Transaction as HttpBridge
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Encode.Pretty as Aeson
import qualified Data.Aeson.Types as Aeson
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL8
import qualified Data.Text as T
Expand Down Expand Up @@ -267,17 +260,7 @@ exec execServer manager args
wId <- args `parseArg` argument "wallet-id"
runClient Aeson.encodePretty $ listAddresses (ApiT wId) Nothing

| args `isPresent` longOption "version" = do
let cabal = B8.unpack $(embedFile "cardano-wallet.cabal")
let re = few anySym
*> string "version:" *> many (sym ' ') *> few anySym
<* sym '\n' <* many anySym
case match re cabal of
Nothing -> do
putErrLn "Couldn't find program version!"
exitFailure
Just version -> do
TIO.putStrLn $ T.pack version
| args `isPresent` longOption "version" = showVersion

| otherwise =
exitWithUsage cli
Expand Down
3 changes: 3 additions & 0 deletions lib/cli/cardano-wallet-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -31,9 +31,12 @@ library
-Werror
build-depends:
base
, bytestring
, ansi-terminal
, docopt
, file-embed
, fmt
, regex-applicative
, text
, text-class
hs-source-dirs:
Expand Down
25 changes: 25 additions & 0 deletions lib/cli/src/Cardano/CLI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}

-- |
-- Copyright: © 2018-2019 IOHK
Expand Down Expand Up @@ -33,13 +34,20 @@ module Cardano.CLI
, hGetLine
, getSensitiveLine
, hGetSensitiveLine

-- * Show version
, showVersion
) where

import Prelude hiding
( getLine )

import Control.Applicative
( many )
import Control.Exception
( bracket )
import Data.FileEmbed
( embedFile )
import Data.Functor
( (<$) )
import qualified Data.List.NonEmpty as NE
Expand Down Expand Up @@ -88,7 +96,10 @@ import System.IO
, stdout
, utf8
)
import Text.Regex.Applicative
( anySym, few, match, string, sym )

import qualified Data.ByteString.Char8 as B8
import qualified Data.Text as T
import qualified Data.Text.IO as TIO

Expand Down Expand Up @@ -259,6 +270,20 @@ getSensitiveLine = hGetSensitiveLine (stdin, stderr)
Internals
-------------------------------------------------------------------------------}

showVersion :: IO ()
showVersion = do
let cabal = B8.unpack $(embedFile "../../cardano-wallet.cabal")
let re = few anySym
*> string "version:" *> many (sym ' ') *> few anySym
<* sym '\n' <* many anySym
case match re cabal of
Nothing -> do
putErrLn "Couldn't find program version!"
exitFailure
Just version -> do
TIO.putStrLn $ T.pack version
exitSuccess

withBuffering :: Handle -> BufferMode -> IO a -> IO a
withBuffering h buffering action = bracket aFirst aLast aBetween
where
Expand Down
51 changes: 47 additions & 4 deletions lib/http-bridge/test/integration/Test/Integration/Framework/DSL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,10 @@ module Test.Integration.Framework.DSL
, expectListSizeEqual
, expectResponseCode
, expectEventually
, expectEventually'
, expectValidJSON
, expectCliFieldBetween
, expectCliFieldEqual
, verify
, Headers(..)
, Payload(..)
Expand Down Expand Up @@ -184,6 +187,9 @@ import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import qualified Network.HTTP.Types.Status as HTTP

--
-- API response expectations
--

-- | Expect an errored response, without any further assumptions
expectError
Expand Down Expand Up @@ -306,25 +312,62 @@ expectEventually
expectEventually ctx getter target (_, res) = case res of
Left e -> wantedSuccessButError e
Right s -> loopUntilRestore (s ^. walletId)

where
loopUntilRestore :: (MonadIO m, MonadCatch m) => Text -> m ()
loopUntilRestore wid = do
r <- request @ApiWallet ctx ("GET", "v2/wallets/" <> wid) Default Empty
let target' = getFromResponse getter r
unless (target' >= target) $ loopUntilRestore wid

-- | Same as `expectEventually` but work directly on ApiWallet
-- , not response from the API
expectEventually'
:: (MonadIO m, MonadCatch m, MonadFail m, Ord a)
=> Context t
-> Lens' ApiWallet a
-> a
-> ApiWallet
-> m ()
expectEventually' ctx target value wallet = do
rb <- request @ApiWallet ctx (getWallet wallet) Default Empty
expectEventually ctx target value rb
--
-- CLI output expectations
--

-- | Expects a given string to be a valid JSON output corresponding to some
-- given data-type 'a'
-- given data-type 'a'. Returns this type if successful.
expectValidJSON
:: forall m a. (MonadFail m, FromJSON a)
=> Proxy a
-> String
-> m ()
-> m a
expectValidJSON _ str =
case Aeson.eitherDecode @a (BL8.pack str) of
Left e -> fail $ "expected valid JSON but failed decoding: " <> show e
Right _ -> return ()
Right a -> return a

expectCliFieldBetween
:: (MonadIO m, MonadFail m, Show a, Ord a)
=> Lens' s a
-> (a, a)
-> s
-> m ()
expectCliFieldBetween getter (aMin, aMax) s = case view getter s of
a | a < aMin -> fail $
"expected " <> show a <> " >= " <> show aMin
a | a > aMax -> fail $
"expected " <> show a <> " <= " <> show aMax
_ ->
return ()

expectCliFieldEqual
:: (MonadIO m, MonadFail m, Show a, Eq a)
=> Lens' s a
-> a
-> s
-> m ()
expectCliFieldEqual getter a out = (view getter out) `shouldBe` a

-- | Apply 'a' to all actions in sequence
verify :: (Monad m) => a -> [a -> m ()] -> m ()
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -40,13 +40,17 @@ module Test.Integration.Framework.TestData
, updatePassPayload

-- * Error messages
, errMsg403Fee
, errMsg403NotEnoughMoney
, errMsg403UTxO
, errMsg403WrongPass
, errMsg404NoEndpoint
, errMsg404NoRootKey
, errMsg404NoWallet
, errMsg405
, errMsg406
, errMsg415
, errMsg500
) where

import Prelude
Expand Down Expand Up @@ -204,6 +208,23 @@ updatePassPayload oldPass newPass = Json [json| {
---
--- Error messages
---
errMsg403Fee :: String
errMsg403Fee = "I'm unable to adjust the given transaction to cover the\
\ associated fee! In order to do so, I'd have to select one or\
\ more additional inputs, but I can't do that without increasing\
\ the size of the transaction beyond the acceptable limit."

errMsg403NotEnoughMoney :: Int -> Int -> String
errMsg403NotEnoughMoney has needs = "I can't process this payment because there's\
\ not enough UTxO available in the wallet. The total UTxO sums up to\
\ " ++ show has ++ " Lovelace, but I need " ++ show needs ++ " Lovelace\
\ (excluding fee amount) in order to proceed with the payment."

errMsg403UTxO :: String
errMsg403UTxO = "When creating new transactions, I'm not able to re-use the\
\ same UTxO for different outputs. Here, I only have 1\
\ available, but there are 2 outputs."

errMsg403WrongPass :: String
errMsg403WrongPass = "The given encryption passphrase doesn't match the one\
\ I use to encrypt the root private key of the given wallet"
Expand Down Expand Up @@ -238,3 +259,9 @@ errMsg415 = "I'm really sorry but I only understand 'application/json'. I need\
\ you to tell me what language you're speaking in order for me to understand\
\ your message. Please double-check your 'Content-Type' request header and\
\ make sure it's set to 'application/json'"

errMsg500 :: String
errMsg500 = "That's embarassing. It looks like I've created an invalid\
\ transaction that could not be parsed by the node. Here's an error\
\ message that may help with debugging: Transaction failed verification:\
\ output with no credited value"
Original file line number Diff line number Diff line change
Expand Up @@ -52,12 +52,16 @@ import Test.Integration.Framework.DSL
)
import Test.Integration.Framework.TestData
( arabicWalletName
, errMsg403Fee
, errMsg403NotEnoughMoney
, errMsg403UTxO
, errMsg403WrongPass
, errMsg404NoEndpoint
, errMsg404NoWallet
, errMsg405
, errMsg406
, errMsg415
, errMsg500
, falseWalletIds
, kanjiWalletName
, polishWalletName
Expand Down Expand Up @@ -252,10 +256,7 @@ spec = do
r <- request @(ApiTransaction t) ctx (postTx wSrc) Default payload
verify r
[ expectResponseCode HTTP.status403
, expectErrorMessage
"When creating new transactions, I'm not able to re-use the \
\same UTxO for different outputs. Here, I only have 1 \
\available, but there are 2 outputs."
, expectErrorMessage errMsg403UTxO
]

it "TRANS_CREATE_03 - 0 balance after transaction" $ \ctx -> do
Expand Down Expand Up @@ -319,11 +320,7 @@ spec = do
r <- request @(ApiTransaction t) ctx (postTx wSrc) Default payload
verify r
[ expectResponseCode HTTP.status403
, expectErrorMessage
"I'm unable to adjust the given transaction to cover the \
\associated fee! In order to do so, I'd have to select one or \
\more additional inputs, but I can't do that without increasing \
\the size of the transaction beyond the acceptable limit."
, expectErrorMessage errMsg403Fee
]

it "TRANS_CREATE_04 - Not enough money" $ \ctx -> do
Expand All @@ -345,11 +342,7 @@ spec = do
r <- request @(ApiTransaction t) ctx (postTx wSrc) Default payload
verify r
[ expectResponseCode HTTP.status403
, expectErrorMessage
"I can't process this payment because there's not enough \
\UTxO available in the wallet. The total UTxO sums up to \
\100000 Lovelace, but I need 1000000 Lovelace (excluding fee \
\amount) in order to proceed with the payment."
, expectErrorMessage (errMsg403NotEnoughMoney 100_000 1000_000)
]

it "TRANS_CREATE_04 - Wrong password" $ \ctx -> do
Expand Down Expand Up @@ -466,12 +459,7 @@ spec = do
[ ( "Quantity = 0"
, [json|{"quantity": 0, "unit": "lovelace"}|]
, [ expectResponseCode HTTP.status500
, expectErrorMessage "That's embarassing. It looks\
\ like I've created an invalid transaction that\
\ could not be parsed by the node. Here's an error\
\ message that may help with debugging:\
\ Transaction failed verification: output with no\
\ credited value" ]
, expectErrorMessage errMsg500 ] -- TODO change after #364
)
, ( "Quantity = 1.5"
, [json|{"quantity": 1.5, "unit": "lovelace"}|]
Expand Down
Loading

0 comments on commit 626be50

Please sign in to comment.