Safe Haskell | None |
---|---|
Language | Haskell2010 |
Testing contracts with HUnit and Tasty
Synopsis
- module Plutus.Contract.Trace
- newtype TracePredicateF a = TracePredicate (forall effs. Members TestEffects effs => FoldM (Eff effs) EmulatorEvent a)
- type TracePredicate = TracePredicateF Bool
- type ContractConstraints s = (Forall (Output s) Unconstrained1, Forall (Input s) Unconstrained1, AllUniqueLabels (Input s), AllUniqueLabels (Output s), Forall (Input s) FromJSON, Forall (Input s) ToJSON, Forall (Output s) FromJSON, Forall (Output s) ToJSON)
- not :: TracePredicate -> TracePredicate
- (.&&.) :: TracePredicate -> TracePredicate -> TracePredicate
- (.||.) :: TracePredicate -> TracePredicate -> TracePredicate
- w1 :: Wallet
- w2 :: Wallet
- w3 :: Wallet
- w4 :: Wallet
- w5 :: Wallet
- w6 :: Wallet
- w7 :: Wallet
- w8 :: Wallet
- w9 :: Wallet
- w10 :: Wallet
- endpointAvailable :: forall (l :: Symbol) w s e a. (KnownSymbol l, Monoid w) => Contract w s e a -> ContractInstanceTag -> TracePredicate
- assertDone :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (a -> Bool) -> String -> TracePredicate
- assertNotDone :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> String -> TracePredicate
- assertContractError :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (e -> Bool) -> String -> TracePredicate
- data Outcome e a
- assertOutcome :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (Outcome e a -> Bool) -> String -> TracePredicate
- assertInstanceLog :: ContractInstanceTag -> ([EmulatorTimeEvent ContractInstanceLog] -> Bool) -> TracePredicate
- assertNoFailedTransactions :: TracePredicate
- assertValidatedTransactionCount :: Int -> TracePredicate
- assertValidatedTransactionCountOfTotal :: Int -> Int -> TracePredicate
- assertFailedTransaction :: (CardanoTx -> ValidationError -> Bool) -> TracePredicate
- assertEvaluationError :: Text -> TracePredicate
- assertHooks :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> ([PABReq] -> Bool) -> String -> TracePredicate
- assertResponses :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> ([Response PABResp] -> Bool) -> String -> TracePredicate
- assertUserLog :: ([EmulatorTimeEvent UserThreadMsg] -> Bool) -> TracePredicate
- assertBlockchain :: ([Block] -> Bool) -> TracePredicate
- assertChainEvents :: ([ChainEvent] -> Bool) -> TracePredicate
- assertChainEvents' :: ([ChainEvent] -> String) -> ([ChainEvent] -> Bool) -> TracePredicate
- assertAccumState :: forall contract w s e a. (Monoid w, Show w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (w -> Bool) -> String -> TracePredicate
- data Shrinking
- assertResumableResult :: forall w s e a. (Monoid w, Show e, Show a, Show w) => Contract w s e a -> ContractInstanceTag -> Shrinking -> (ResumableResult w e PABResp PABReq a -> Bool) -> String -> TracePredicate
- assertUnbalancedTx :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> (UnbalancedTx -> Bool) -> String -> TracePredicate
- anyUnbalancedTx :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> TracePredicate
- assertEvents :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> ([PABResp] -> Bool) -> String -> TracePredicate
- walletFundsChangePlutus :: Wallet -> Value -> TracePredicate
- walletFundsChange :: Wallet -> Value -> TracePredicate
- walletFundsExactChange :: Wallet -> Value -> TracePredicate
- walletFundsAssetClassChange :: Wallet -> AssetId -> Integer -> TracePredicate
- walletPaidFees :: Wallet -> Lovelace -> TracePredicate
- waitingForSlot :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> Slot -> TracePredicate
- valueAtAddress :: CardanoAddress -> (Value -> Bool) -> TracePredicate
- plutusValueAtAddress :: CardanoAddress -> (Value -> Bool) -> TracePredicate
- dataAtAddress :: forall d. FromData d => CardanoAddress -> ([d] -> Bool) -> TracePredicate
- reasonable :: Validator -> Integer -> Assertion
- reasonable' :: (String -> IO ()) -> Validator -> Integer -> Assertion
- checkPredicate :: String -> TracePredicate -> EmulatorTrace () -> TestTree
- checkPredicateCoverage :: String -> CoverageRef -> TracePredicate -> EmulatorTrace () -> TestTree
- checkPredicateCoverageOptions :: CheckOptions -> String -> CoverageRef -> TracePredicate -> EmulatorTrace () -> TestTree
- checkPredicateOptions :: CheckOptions -> String -> TracePredicate -> EmulatorTrace () -> TestTree
- checkPredicateGen :: GeneratorModel -> TracePredicate -> EmulatorTrace () -> Property
- checkPredicateGenOptions :: CheckOptions -> GeneratorModel -> TracePredicate -> EmulatorTrace () -> Property
- checkPredicateInner :: forall m a. Monad m => CheckOptions -> TracePredicate -> EmulatorTrace a -> (String -> m ()) -> (Bool -> m ()) -> (CoverageData -> m ()) -> m (Either EmulatorErr a)
- checkPredicateInnerStream :: forall m a. Monad m => CheckOptions -> TracePredicate -> (forall effs. Stream (Of (LogMessage EmulatorEvent)) (Eff effs) (Either EmulatorErr a)) -> (String -> m ()) -> (Bool -> m ()) -> (CoverageData -> m ()) -> m (Either EmulatorErr a)
- checkEmulatorFails :: String -> CheckOptions -> TracePredicate -> EmulatorTrace () -> TestTree
- data CheckOptions = CheckOptions {
- _minLogLevel :: LogLevel
- _emulatorConfig :: EmulatorConfig
- defaultCheckOptions :: CheckOptions
- minLogLevel :: Lens' CheckOptions LogLevel
- emulatorConfig :: Lens' CheckOptions EmulatorConfig
- changeInitialWalletValue :: Wallet -> (Value -> Value) -> CheckOptions -> CheckOptions
- increaseTransactionLimits :: CheckOptions -> CheckOptions
- goldenPir :: FilePath -> CompiledCode a -> TestTree
Documentation
module Plutus.Contract.Trace
newtype TracePredicateF a Source #
TracePredicate (forall effs. Members TestEffects effs => FoldM (Eff effs) EmulatorEvent a) |
Instances
Functor TracePredicateF Source # | |
Defined in Plutus.Contract.Test fmap :: (a -> b) -> TracePredicateF a -> TracePredicateF b Source # (<$) :: a -> TracePredicateF b -> TracePredicateF a Source # | |
Applicative TracePredicateF Source # | |
Defined in Plutus.Contract.Test pure :: a -> TracePredicateF a Source # (<*>) :: TracePredicateF (a -> b) -> TracePredicateF a -> TracePredicateF b Source # liftA2 :: (a -> b -> c) -> TracePredicateF a -> TracePredicateF b -> TracePredicateF c Source # (*>) :: TracePredicateF a -> TracePredicateF b -> TracePredicateF b Source # (<*) :: TracePredicateF a -> TracePredicateF b -> TracePredicateF a Source # |
type TracePredicate = TracePredicateF Bool Source #
type ContractConstraints s = (Forall (Output s) Unconstrained1, Forall (Input s) Unconstrained1, AllUniqueLabels (Input s), AllUniqueLabels (Output s), Forall (Input s) FromJSON, Forall (Input s) ToJSON, Forall (Output s) FromJSON, Forall (Output s) ToJSON) Source #
not :: TracePredicate -> TracePredicate Source #
(.&&.) :: TracePredicate -> TracePredicate -> TracePredicate infixl 3 Source #
(.||.) :: TracePredicate -> TracePredicate -> TracePredicate infixl 2 Source #
Assertions
endpointAvailable :: forall (l :: Symbol) w s e a. (KnownSymbol l, Monoid w) => Contract w s e a -> ContractInstanceTag -> TracePredicate Source #
assertDone :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (a -> Bool) -> String -> TracePredicate Source #
A TracePredicate
checking that the wallet's contract instance finished
without errors.
assertNotDone :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> String -> TracePredicate Source #
A TracePredicate
checking that the wallet's contract instance is
waiting for input.
assertContractError :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (e -> Bool) -> String -> TracePredicate Source #
A TracePredicate
checking that the wallet's contract instance
failed with an error.
Done a | The contract finished without errors and produced a result |
NotDone | The contract is waiting for more input. |
Failed e | The contract failed with an error. |
assertOutcome :: forall contract w s e a. (Monoid w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (Outcome e a -> Bool) -> String -> TracePredicate Source #
assertInstanceLog :: ContractInstanceTag -> ([EmulatorTimeEvent ContractInstanceLog] -> Bool) -> TracePredicate Source #
assertNoFailedTransactions :: TracePredicate Source #
Assert that no transaction failed to validate.
assertValidatedTransactionCount :: Int -> TracePredicate Source #
Assert that n transactions validated, and no transaction failed to validate.
assertValidatedTransactionCountOfTotal :: Int -> Int -> TracePredicate Source #
Assert that n transactions validated, and the rest failed.
assertFailedTransaction :: (CardanoTx -> ValidationError -> Bool) -> TracePredicate Source #
Assert that at least one transaction failed to validate, and that all transactions that failed meet the predicate.
assertEvaluationError :: Text -> TracePredicate Source #
Assert that at least one transaction failed to validate with an EvaluationError containing the given text.
assertHooks :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> ([PABReq] -> Bool) -> String -> TracePredicate Source #
assertResponses :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> ([Response PABResp] -> Bool) -> String -> TracePredicate Source #
Make an assertion about the responses provided to the contract instance.
assertUserLog :: ([EmulatorTimeEvent UserThreadMsg] -> Bool) -> TracePredicate Source #
assertBlockchain :: ([Block] -> Bool) -> TracePredicate Source #
An assertion about the blockchain
assertChainEvents :: ([ChainEvent] -> Bool) -> TracePredicate Source #
An assertion about the chain events
assertChainEvents' :: ([ChainEvent] -> String) -> ([ChainEvent] -> Bool) -> TracePredicate Source #
An assertion about the chain events with a custom error message
assertAccumState :: forall contract w s e a. (Monoid w, Show w, IsContract contract) => contract w s e a -> ContractInstanceTag -> (w -> Bool) -> String -> TracePredicate Source #
Make an assertion about the accumulated state w
of
a contract instance.
Instances
Eq Shrinking Source # | |
Ord Shrinking Source # | |
Defined in Plutus.Contract.Test | |
Show Shrinking Source # | |
assertResumableResult :: forall w s e a. (Monoid w, Show e, Show a, Show w) => Contract w s e a -> ContractInstanceTag -> Shrinking -> (ResumableResult w e PABResp PABReq a -> Bool) -> String -> TracePredicate Source #
make an assertion about the ContractInstanceState
of a contract
instance
assertUnbalancedTx :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> (UnbalancedTx -> Bool) -> String -> TracePredicate Source #
anyUnbalancedTx :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> TracePredicate Source #
assertEvents :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> ([PABResp] -> Bool) -> String -> TracePredicate Source #
walletFundsChangePlutus :: Wallet -> Value -> TracePredicate Source #
Check that the funds in the wallet have changed by the given amount, exluding fees, using the Plutus Value
type.
walletFundsChange :: Wallet -> Value -> TracePredicate Source #
Check that the funds in the wallet have changed by the given amount, exluding fees.
walletFundsExactChange :: Wallet -> Value -> TracePredicate Source #
Check that the funds in the wallet have changed by the given amount, including fees.
walletFundsAssetClassChange :: Wallet -> AssetId -> Integer -> TracePredicate Source #
walletPaidFees :: Wallet -> Lovelace -> TracePredicate Source #
waitingForSlot :: forall w s e a. Monoid w => Contract w s e a -> ContractInstanceTag -> Slot -> TracePredicate Source #
valueAtAddress :: CardanoAddress -> (Value -> Bool) -> TracePredicate Source #
Check that the funds at an address meet some condition.
plutusValueAtAddress :: CardanoAddress -> (Value -> Bool) -> TracePredicate Source #
dataAtAddress :: forall d. FromData d => CardanoAddress -> ([d] -> Bool) -> TracePredicate Source #
reasonable :: Validator -> Integer -> Assertion Source #
Assert that the size of a Validator
is below
the maximum.
Checking predicates
:: String | Descriptive name of the test |
-> TracePredicate | The predicate to check |
-> EmulatorTrace () | |
-> TestTree |
Check if the emulator trace meets the condition
checkPredicateCoverage Source #
:: String | Descriptive name of the test |
-> CoverageRef | |
-> TracePredicate | The predicate to check |
-> EmulatorTrace () | |
-> TestTree |
checkPredicateCoverageOptions Source #
:: CheckOptions | Options to use |
-> String | Descriptive name of the test |
-> CoverageRef | |
-> TracePredicate | The predicate to check |
-> EmulatorTrace () | |
-> TestTree |
checkPredicateOptions Source #
:: CheckOptions | Options to use |
-> String | Descriptive name of the test |
-> TracePredicate | The predicate to check |
-> EmulatorTrace () | |
-> TestTree |
A version of checkPredicate
with configurable CheckOptions
checkPredicateGen :: GeneratorModel -> TracePredicate -> EmulatorTrace () -> Property Source #
Check if the emulator trace meets the condition, using the
GeneratorModel
to generate initial transactions for the blockchain
checkPredicateGenOptions :: CheckOptions -> GeneratorModel -> TracePredicate -> EmulatorTrace () -> Property Source #
A version of checkPredicateGen
with configurable CheckOptions
.
Note that the InitialChainState
in the EmulatorConfig
of the
CheckOptions
will be replaced with the mockchainInitialTxPool
generated
by the model.
:: forall m a. Monad m | |
=> CheckOptions | |
-> TracePredicate | |
-> EmulatorTrace a | |
-> (String -> m ()) | Print out debug information in case of test failures TODO: can we generalize Bool here? We need it to get extractPropertyResult to work |
-> (Bool -> m ()) | assert |
-> (CoverageData -> m ()) | |
-> m (Either EmulatorErr a) |
Evaluate a trace predicate on an emulator trace, printing out debug information and making assertions as we go.
checkPredicateInnerStream Source #
:: forall m a. Monad m | |
=> CheckOptions | |
-> TracePredicate | |
-> (forall effs. Stream (Of (LogMessage EmulatorEvent)) (Eff effs) (Either EmulatorErr a)) | |
-> (String -> m ()) | Print out debug information in case of test failures |
-> (Bool -> m ()) | assert |
-> (CoverageData -> m ()) | |
-> m (Either EmulatorErr a) |
:: String | Descriptive name of the test |
-> CheckOptions | |
-> TracePredicate | |
-> EmulatorTrace () | The trace that should fail |
-> TestTree |
Check if the emulator trace fails with the condition
data CheckOptions Source #
Options for running the
CheckOptions | |
|
minLogLevel :: Lens' CheckOptions LogLevel Source #
emulatorConfig :: Lens' CheckOptions EmulatorConfig Source #
changeInitialWalletValue :: Wallet -> (Value -> Value) -> CheckOptions -> CheckOptions Source #
Modify the value assigned to the given wallet in the initial distribution.
increaseTransactionLimits :: CheckOptions -> CheckOptions Source #
Set higher limits on transaction size and execution units.
This can be used to work around MaxTxSizeUTxO
and ExUnitsTooBigUTxO
errors.
Note that if you need this your Plutus script will probably not validate on Mainnet.