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

Commit 8741c9d

Browse files
author
Ben Ford
committed
[DEVOPS-834] Get test suite running
1 parent 1c2ae37 commit 8741c9d

File tree

8 files changed

+111
-21
lines changed

8 files changed

+111
-21
lines changed

faucet/cardano-sl-faucet.cabal

Lines changed: 13 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ library
3535
, ekg-statsd
3636
, exceptions
3737
, filepath
38+
, generic-arbitrary
3839
, http-api-data
3940
, http-client
4041
, http-client-tls
@@ -106,15 +107,22 @@ executable faucet
106107
, warp
107108
default-language: Haskell2010
108109

109-
test-suite cardano-sl-faucet-test
110+
test-suite faucet-test
110111
type: exitcode-stdio-1.0
111112
main-is: Spec.hs
112113
hs-source-dirs:
113114
test
114115
ghc-options: -threaded -rtsopts -with-rtsopts=-N
115116
build-depends:
116-
base
117-
, cardano-sl-faucet
118-
, cardano-sl-wallet
119-
, QuickCheck
117+
base
118+
, aeson
119+
, bytestring
120+
, cardano-sl-faucet
121+
, cardano-sl-core
122+
, cardano-sl-wallet
123+
, cardano-sl-wallet-new
124+
, hspec
125+
, QuickCheck
126+
, mtl
127+
, time
120128
default-language: Haskell2010

faucet/src/Cardano/Faucet/Types/API.hs

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ import Data.Swagger
3131
import Data.Text (Text)
3232
import Data.Typeable (Typeable)
3333
import GHC.Generics (Generic)
34+
import Test.QuickCheck.Arbitrary.Generic
3435
import Web.FormUrlEncoded
3536

3637
import Cardano.Wallet.API.V1.Types (Transaction, V1 (..))
@@ -39,21 +40,25 @@ import Pos.Core (Address (..), Coin (..))
3940

4041
--------------------------------------------------------------------------------
4142
-- | The "g-recaptcha-response" field
42-
newtype GCaptchaResponse = GCaptchaResponse Text deriving (Show)
43+
newtype GCaptchaResponse = GCaptchaResponse Text deriving (Eq, Show, Generic)
4344

4445
makeWrapped ''GCaptchaResponse
4546

4647
instance IsString GCaptchaResponse where
4748
fromString = GCaptchaResponse . fromString
4849

50+
instance Arbitrary GCaptchaResponse where
51+
arbitrary = genericArbitrary
52+
shrink = genericShrink
53+
4954
--------------------------------------------------------------------------------
5055
-- | A request to withdraw ADA from the faucet wallet
5156
data WithdrawalRequest = WithdrawalRequest {
5257
-- | The address to send the ADA to
5358
_wAddress :: !(V1 Address)
5459
-- | The "g-recaptcha-response" field sent by the form
5560
, _gRecaptchaResponse :: !GCaptchaResponse
56-
} deriving (Show, Typeable, Generic)
61+
} deriving (Eq, Show, Typeable, Generic)
5762

5863
makeLenses ''WithdrawalRequest
5964

@@ -83,6 +88,10 @@ instance ToJSON WithdrawalRequest where
8388
, "g-recaptcha-response" .= (g ^. _Wrapped)]
8489

8590

91+
instance Arbitrary WithdrawalRequest where
92+
arbitrary = genericArbitrary
93+
shrink = genericShrink
94+
8695
--------------------------------------------------------------------------------
8796
data WithdrawalQFull = WithdrawalQFull deriving (Show, Generic, Exception)
8897

faucet/src/Cardano/Faucet/Types/Config.hs

Lines changed: 21 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE ConstraintKinds #-}
22
{-# LANGUAGE DataKinds #-}
3+
{-# LANGUAGE DeriveAnyClass #-}
34
{-# LANGUAGE DeriveGeneric #-}
45
{-# LANGUAGE DuplicateRecordFields #-}
56
{-# LANGUAGE FlexibleInstances #-}
@@ -45,8 +46,10 @@ import System.Remote.Monitoring.Statsd (StatsdOptions (..))
4546
import Cardano.Wallet.API.V1.Types (AccountIndex, Payment,
4647
PaymentSource (..), V1, WalletId (..))
4748
import Cardano.Wallet.Client (ClientError (..), WalletClient (..))
48-
import Pos.Core (Address (..), Coin (..))
49+
import Pos.Core (Address (..))
4950
import Pos.Util.Mnemonic (Mnemonic)
51+
import Test.QuickCheck (Arbitrary(..), choose)
52+
import Test.QuickCheck.Arbitrary.Generic
5053

5154
import Cardano.Faucet.Types.API
5255
import Cardano.Faucet.Types.Recaptcha
@@ -104,16 +107,23 @@ cfgToPaymentSource (SourceWalletConfig wId aIdx _) = PaymentSource wId aIdx
104107
-- 'paymentMean' + randomFloat(-1, 1) * 'paymentScale'
105108
-- @
106109
data PaymentDistribution = PaymentDistribution {
107-
_mean :: Coin
108-
, _scale :: Coin
109-
}
110+
_mean :: Int
111+
, _scale :: Int
112+
} deriving (Show)
110113

111114
makeLenses ''PaymentDistribution
112115

113116
instance FromJSON PaymentDistribution where
114117
parseJSON = withObject "PaymentDistibution" $ \v -> PaymentDistribution
115-
<$> (Coin <$> v .: "mean")
116-
<*> (Coin <$> v .: "scale")
118+
<$> (v .: "mean")
119+
<*> (v .: "scale")
120+
121+
instance Arbitrary PaymentDistribution where
122+
arbitrary = do
123+
m <- choose (1000, 10000)
124+
s <- choose (0, m)
125+
return $ PaymentDistribution m s
126+
117127

118128
--------------------------------------------------------------------------------
119129
-- | Config for the wallet used by the faucet as a source of ADA
@@ -194,7 +204,7 @@ data CreatedWallet = CreatedWallet {
194204
, _createdAcctIdx :: AccountIndex
195205
-- | Sending address within the account in the created wallet
196206
, _createdAddress :: Address
197-
} deriving (Show, Generic)
207+
} deriving (Eq, Show, Generic)
198208

199209
instance ToJSON CreatedWallet where
200210
toJSON (CreatedWallet wId phrase acctIdx addr) =
@@ -211,6 +221,10 @@ instance FromJSON CreatedWallet where
211221
<*> v .: "account-index"
212222
<*> v .: "address"
213223

224+
instance Arbitrary CreatedWallet where
225+
arbitrary = genericArbitrary
226+
shrink = genericShrink
227+
214228
--------------------------------------------------------------------------------
215229
-- | Sum type for possible errors encountered at faucet startup time
216230
data InitFaucetError =

faucet/src/Cardano/Faucet/Types/Recaptcha.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ data CaptchaResponse = CaptchaResponse {
5858
, _hostname :: Maybe Text
5959
-- | Any errors present
6060
, _errorCodes :: [Text]
61-
} deriving (Show)
61+
} deriving (Eq, Show)
6262

6363
makeLenses ''CaptchaResponse
6464

faucet/src/Cardano/WalletClient.hs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
{-# OPTIONS_GHC -Wall #-}
77
module Cardano.WalletClient (
88
withdraw
9+
, randomAmount
910
) where
1011

1112
import Cardano.Wallet.API.V1.Types (Payment (..), V1 (..))
@@ -22,18 +23,18 @@ import qualified Data.ByteArray as BA
2223
import Data.ByteString (ByteString)
2324
import Data.List.NonEmpty (NonEmpty (..))
2425
import Data.Text.Strict.Lens (utf8)
25-
import Pos.Core (Address (..), Coin (..), getCoin)
26+
import Pos.Core (Address (..), Coin (..))
2627
import Pos.Crypto.Signing (PassPhrase)
2728
import System.Random
2829
import System.Wlog (logError, logInfo, withSublogger)
2930

3031
import Cardano.Faucet.Types
3132

3233
-- | Computes the amount of ADA (units in lovelace) to send in 'withdraw'
33-
randomAmount :: (MonadIO m) => PaymentDistribution -> m (V1 Coin)
34-
randomAmount (PaymentDistribution (getCoin -> amt) (getCoin -> var))= do
34+
randomAmount :: (MonadIO m) => PaymentDistribution -> m Int
35+
randomAmount (PaymentDistribution amt var)= do
3536
(f :: Float) <- liftIO $ randomRIO ((-1), 1)
36-
return $ V1 $ Coin $ round $ ((fromIntegral amt) + ((fromIntegral var) * f))
37+
return $ round $ ((fromIntegral amt) + ((fromIntegral var) * f))
3738

3839
-- | Client function for the handler for the @/withdraw@ action
3940
--
@@ -43,7 +44,8 @@ withdraw :: (MonadFaucet c m) => V1 Address -> m (Either WithdrawalQFull Withdra
4344
withdraw addr = withSublogger "WalletClient.withdraw" $ do
4445
paymentSource <- view (feSourceWallet . to cfgToPaymentSource)
4546
spendingPassword <- view (feSourceWallet . srcSpendingPassword)
46-
coin <- randomAmount =<< view (feFaucetConfig . fcPaymentDistribution)
47+
coin <- V1 . Coin . fromIntegral
48+
<$> (randomAmount =<< view (feFaucetConfig . fcPaymentDistribution))
4749
q <- view feWithdrawalQ
4850
let paymentDist = (V1.PaymentDistribution addr coin :| [])
4951
sp = spendingPassword <&> view (re utf8 . to hashPwd . to V1)

faucet/test/Spec.hs

Lines changed: 48 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,49 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
{-# OPTIONS_GHC -Wall #-}
3+
module Main where
4+
5+
import Control.Monad.IO.Class (liftIO)
6+
import Data.Aeson
7+
import qualified Data.ByteString.Lazy as BSL
8+
import Data.Time.Clock (UTCTime)
9+
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
10+
import Test.Hspec
11+
import Test.QuickCheck
12+
import Test.QuickCheck.Monadic
13+
14+
import Cardano.Faucet.Types
15+
import Cardano.Faucet.Types.Recaptcha
16+
import Cardano.WalletClient
17+
118
main :: IO ()
2-
main = putStrLn "Test suite not yet implemented"
19+
main = hspec $ do
20+
describe "randomAmount" $ do
21+
it "should be within PaymentDistribution" $ do
22+
property $ prop_randomAmount
23+
24+
describe "Aeson encode and decode" $ do
25+
it "CreatedWallet" $ property (prop_aeson_id :: CreatedWallet -> Bool)
26+
it "WithdrawalRequest" $ property (prop_aeson_id :: WithdrawalRequest -> Bool)
27+
it "CaptchaResponse decode" $ captchaDecode
28+
29+
prop_randomAmount :: PaymentDistribution -> Property
30+
prop_randomAmount pd = monadicIO $ do
31+
c <- run (liftIO $ randomAmount pd)
32+
assert (between pd c)
33+
where
34+
between (PaymentDistribution m s) c = c <= m + s
35+
&& c >= m - s
36+
37+
prop_aeson_id :: (Arbitrary a, ToJSON a, FromJSON a, Eq a) => a -> Bool
38+
prop_aeson_id a = Just a == (decode $ encode a)
39+
40+
41+
t :: UTCTime
42+
t = posixSecondsToUTCTime 1527811200
43+
44+
getJSON :: FromJSON a => FilePath -> IO (Either String a)
45+
getJSON f = eitherDecode <$> BSL.readFile f
46+
47+
captchaDecode :: Expectation
48+
captchaDecode = do
49+
getJSON "test/captcha-resp-ok.json" `shouldReturn` Right (CaptchaResponse True (Just t) (Just "test") [])

faucet/test/captcha-resp-err.json

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
{
2+
"success": false,
3+
"error-codes": ["error"]
4+
}

faucet/test/captcha-resp-ok.json

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
{
2+
"success": true,
3+
"challenge_ts": "2018-06-01T00:00:00Z",
4+
"hostname": "test",
5+
"error-codes": []
6+
}

0 commit comments

Comments
 (0)