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 (..))
4546import Cardano.Wallet.API.V1.Types (AccountIndex , Payment ,
4647 PaymentSource (.. ), V1 , WalletId (.. ))
4748import Cardano.Wallet.Client (ClientError (.. ), WalletClient (.. ))
48- import Pos.Core (Address (.. ), Coin ( .. ) )
49+ import Pos.Core (Address (.. ))
4950import Pos.Util.Mnemonic (Mnemonic )
51+ import Test.QuickCheck (Arbitrary (.. ), choose )
52+ import Test.QuickCheck.Arbitrary.Generic
5053
5154import Cardano.Faucet.Types.API
5255import Cardano.Faucet.Types.Recaptcha
@@ -104,16 +107,23 @@ cfgToPaymentSource (SourceWalletConfig wId aIdx _) = PaymentSource wId aIdx
104107-- 'paymentMean' + randomFloat(-1, 1) * 'paymentScale'
105108-- @
106109data PaymentDistribution = PaymentDistribution {
107- _mean :: Coin
108- , _scale :: Coin
109- }
110+ _mean :: Int
111+ , _scale :: Int
112+ } deriving ( Show )
110113
111114makeLenses ''PaymentDistribution
112115
113116instance 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
199209instance 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
216230data InitFaucetError =
0 commit comments