cleveland-0.3.1: Testing framework for Morley.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Cleveland.Michelson

Description

Module containing some utilities for testing Michelson contracts using Haskell testing frameworks. It's Morley testing EDSL. We focus on tasty and hedgehog because that's what we mostly use in our tests, but we also provide helpers for hspec, and defining helpers for other libraries (e. g. QuickCheck) shouldn't be hard. We don't provide helpers for other libraries to have less dependencies.

Synopsis

Importing a contract

testTreesWithContract :: (Each '[SingI] [cp, st], HasCallStack) => FilePath -> (Contract cp st -> IO [TestTree]) -> IO [TestTree] Source #

Import contract and use to create test trees. Both versions of contract are passed to the callback function (untyped and typed).

If contract's import fails, a tree with single failing test will be generated (so test tree will likely be generated unexceptionally, but a failing result will notify about problem).

testTreesWithUntypedContract :: HasCallStack => FilePath -> (Contract -> IO [TestTree]) -> IO [TestTree] Source #

Like testTreesWithContract but supplies only untyped contract.

testTreesWithTypedContract :: (Each '[SingI] [cp, st], HasCallStack) => FilePath -> (Contract cp st -> IO [TestTree]) -> IO [TestTree] Source #

Like testTreesWithContract but supplies only typed contract.

importContract :: forall (cp :: T) (st :: T). Each '[SingI :: T -> Constraint] '[cp, st] => FilePath -> IO (Contract cp st) #

importSomeContract :: FilePath -> IO SomeContract #

Unit testing

testContractCoversEntrypoints :: TestName -> Contract -> Map EpName Ty -> TestTree Source #

Assert the contract contains the entrypoints given in spec (with matching types). Ignores any additional entrypoints present in the contract.

Also tests if the same holds after Michelson and Micheline roundtrips of the contract.

testContractMatchesEntrypoints :: TestName -> Contract -> Map EpName Ty -> TestTree Source #

Assert the contract exactly matches the given entrypoints. Will report both missing and extraneous entrypoint names, and type mismatches.

Also tests if the same holds after Michelson and Micheline roundtrips of the contract.

General utilities

failedTest :: (HasCallStack, MonadTest m) => Text -> m () Source #

A Property that always fails with given message.

succeededTest :: MonadTest m => m () Source #

A Property that always succeeds.

eitherIsLeft :: (Show b, MonadTest m, HasCallStack) => Either a b -> m () Source #

The Property holds on `Left a`.

eitherIsRight :: (Show a, MonadTest m, HasCallStack) => Either a b -> m () Source #

The Property holds on `Right b`.

meanTimeUpperBoundProp :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack) => Time unit -> (a -> b) -> a -> Property Source #

Benchmarks the given function and checks that the mean time to evaluate to weak head normal form is under the given amount of time.

This test fails if the benchmark takes longer than 30 seconds to run.

meanTimeUpperBoundPropNF :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack, NFData b) => Time unit -> (a -> b) -> a -> Property Source #

Benchmarks the given function and checks that the mean time to evaluate to normal form is under the given amount of time.

This test aborts and fails if the benchmark takes longer than 120 seconds to run.

Re-exports

These functions from Time are re-exported here to make it convenient to call meanTimeUpperBoundProp and meanTimeUpperBoundPropNF.

mcs :: RatioNat -> Time Microsecond #

Creates Microsecond from given Natural.

>>> mcs 42
42mcs

ms :: RatioNat -> Time Millisecond #

Creates Millisecond from given Natural.

>>> ms 42
42ms

sec :: RatioNat -> Time Second #

Creates Second from given Natural.

>>> sec 42
42s

minute :: RatioNat -> Time Minute #

Creates Minute from given Natural.

>>> minute 42
42m

Autodoc testing

runDocTests :: (ContainsDoc code, HasCallStack) => [DocTest] -> code -> [TestTree] Source #

Finalize test suites.

testDocBasic :: [DocTest] Source #

Base properties which should comply for all documentations.

excludeDocTests :: [DocTest] -> [DocTest] -> [DocTest] Source #

Calling excludeDocTests tests toExclude returns all test suites from tests which are not present in toExclude.