| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Michelson.Test.Util
Contents
Description
Testing utility functions used by testing framework itself or intended to be used by test writers.
Synopsis
- leftToShowPanic :: (Show e, HasCallStack) => Either e a -> a
- leftToPrettyPanic :: (Buildable e, HasCallStack) => Either e a -> a
- failedTest :: (HasCallStack, MonadTest m) => Text -> m ()
- succeededTest :: MonadTest m => m ()
- eitherIsLeft :: (Show b, MonadTest m, HasCallStack) => Either a b -> m ()
- eitherIsRight :: (Show a, MonadTest m, HasCallStack) => Either a b -> m ()
- total :: (MonadTest m, NFData a, HasCallStack) => a -> m a
- meanTimeUpperBoundProp :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack) => Time unit -> (a -> b) -> a -> Property
- meanTimeUpperBoundPropNF :: (KnownDivRat unit Second, KnownUnitName unit, HasCallStack, NFData b) => Time unit -> (a -> b) -> a -> Property
- genEither :: MonadGen m => m a -> m b -> m (Either a b)
- genTuple2 :: MonadGen m => m a -> m b -> m (a, b)
- runGen :: HasCallStack => Size -> Word64 -> Gen a -> a
- roundtripTree :: forall x y err. (Show x, Show y, Show err, Typeable x, Eq x, Eq err) => Gen x -> (x -> y) -> (y -> Either err x) -> TestTree
- mcs :: RatioNat -> Time Microsecond
- ms :: RatioNat -> Time Millisecond
- sec :: RatioNat -> Time Second
- minute :: RatioNat -> Time Minute
- failedProp :: Text -> Property
- succeededProp :: Property
- qcIsLeft :: Show b => Either a b -> Property
- qcIsRight :: Show a => Either a b -> Property
- roundtripTest :: forall x y err. (Show x, Show err, Typeable x, Arbitrary x, Eq x, Eq err) => (x -> y) -> (y -> Either err x) -> TestTree
Documentation
leftToShowPanic :: (Show e, HasCallStack) => Either e a -> a Source #
leftToPrettyPanic :: (Buildable e, HasCallStack) => Either e a -> a Source #
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`.
total :: (MonadTest m, NFData a, HasCallStack) => a -> m a Source #
Checks that a value is total, i.e., doesn't crash when evaluated, by reducing it to its normal form.
Equivalent to QuickCheck's total.
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.
genEither :: MonadGen m => m a -> m b -> m (Either a b) Source #
Randomly selects one of the two generators.
genTuple2 :: MonadGen m => m a -> m b -> m (a, b) Source #
Generates an a and a b and wraps them in a tuple.
runGen :: HasCallStack => Size -> Word64 -> Gen a -> a Source #
Run the given generator deterministically, by fixing its size and seed.
roundtripTree :: forall x y err. (Show x, Show y, Show err, Typeable x, Eq x, Eq err) => Gen x -> (x -> y) -> (y -> Either err x) -> TestTree Source #
This TestTree contains a property based test for conversion from
some x to some y and back to x (it should successfully return
the initial x).
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 4242mcs
ms :: RatioNat -> Time Millisecond #
Creates Millisecond from given Natural.
>>>ms 4242ms
Deprecated
failedProp :: Text -> Property Source #
Deprecated: Use failedtest instead.
A Property that always fails with given message.
succeededProp :: Property Source #
Deprecated: Use succeededTest instead.
A Property that always succeeds.
qcIsLeft :: Show b => Either a b -> Property Source #
Deprecated: Use eitherIsLeft instead.
The Property holds on `Left a`.
qcIsRight :: Show a => Either a b -> Property Source #
Deprecated: Use eitherIsRight instead.
The Property holds on `Right b`.
roundtripTest :: forall x y err. (Show x, Show err, Typeable x, Arbitrary x, Eq x, Eq err) => (x -> y) -> (y -> Either err x) -> TestTree Source #
Deprecated: Use roundtripTree instead.
This TestTree contains a property based test for conversion from
some x to some y and back to x (it should successfully return
the initial x).