Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Property = Property {
- propertyConfig :: !PropertyConfig
- propertyTest :: PropertyT IO ()
- newtype PropertyT m a = PropertyT {
- unPropertyT :: TestT (GenT m) a
- newtype PropertyName = PropertyName {}
- data PropertyConfig = PropertyConfig {}
- newtype TestLimit = TestLimit Int
- newtype DiscardLimit = DiscardLimit Int
- newtype ShrinkLimit = ShrinkLimit Int
- newtype ShrinkRetries = ShrinkRetries Int
- withTests :: TestLimit -> Property -> Property
- withDiscards :: DiscardLimit -> Property -> Property
- withShrinks :: ShrinkLimit -> Property -> Property
- withRetries :: ShrinkRetries -> Property -> Property
- property :: HasCallStack => PropertyT IO () -> Property
- test :: Monad m => TestT m a -> PropertyT m a
- forAll :: (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a
- forAllT :: (Monad m, Show a, HasCallStack) => GenT m a -> PropertyT m a
- forAllWith :: (Monad m, HasCallStack) => (a -> String) -> Gen a -> PropertyT m a
- forAllWithT :: (Monad m, HasCallStack) => (a -> String) -> GenT m a -> PropertyT m a
- discard :: Monad m => PropertyT m a
- data Group = Group {
- groupName :: !GroupName
- groupProperties :: ![(PropertyName, Property)]
- newtype GroupName = GroupName {}
- class Monad m => MonadTest m where
- type Test = TestT Identity
- newtype TestT m a = TestT {}
- data Log
- data Failure = Failure (Maybe Span) String (Maybe Diff)
- data Diff = Diff {}
- annotate :: (MonadTest m, HasCallStack) => String -> m ()
- annotateShow :: (MonadTest m, Show a, HasCallStack) => a -> m ()
- footnote :: MonadTest m => String -> m ()
- footnoteShow :: (MonadTest m, Show a) => a -> m ()
- failure :: (MonadTest m, HasCallStack) => m a
- success :: MonadTest m => m ()
- assert :: (MonadTest m, HasCallStack) => Bool -> m ()
- (===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
- (/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
- eval :: (MonadTest m, HasCallStack) => a -> m a
- evalM :: (MonadTest m, MonadCatch m, HasCallStack) => m a -> m a
- evalIO :: (MonadTest m, MonadIO m, HasCallStack) => IO a -> m a
- evalEither :: (MonadTest m, Show x, HasCallStack) => Either x a -> m a
- evalExceptT :: (MonadTest m, Show x, HasCallStack) => ExceptT x m a -> m a
- defaultConfig :: PropertyConfig
- mapConfig :: (PropertyConfig -> PropertyConfig) -> Property -> Property
- failDiff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> b -> m ()
- failException :: (MonadTest m, HasCallStack) => SomeException -> m a
- failWith :: (MonadTest m, HasCallStack) => Maybe Diff -> String -> m a
- writeLog :: MonadTest m => Log -> m ()
- mkTest :: (Either Failure a, [Log]) -> Test a
- mkTestT :: m (Either Failure a, [Log]) -> TestT m a
- runTest :: Test a -> (Either Failure a, [Log])
- runTestT :: TestT m a -> m (Either Failure a, [Log])
Property
A property test, along with some configurable limits like how many times to run the test.
Property | |
|
newtype PropertyT m a Source #
The property monad transformer allows both the generation of test inputs and the assertion of expectations.
PropertyT | |
|
MonadTrans PropertyT Source # | |
Distributive PropertyT Source # | |
MonadBase b m => MonadBase b (PropertyT m) Source # | |
MonadState s m => MonadState s (PropertyT m) Source # | |
MonadReader r m => MonadReader r (PropertyT m) Source # | |
MonadError e m => MonadError e (PropertyT m) Source # | |
Monad m => Monad (PropertyT m) Source # | |
Functor m => Functor (PropertyT m) Source # | |
Monad m => Applicative (PropertyT m) Source # | |
MonadIO m => MonadIO (PropertyT m) Source # | |
MonadPlus m => Alternative (PropertyT m) Source # | |
MonadPlus m => MonadPlus (PropertyT m) Source # | |
MonadCatch m => MonadCatch (PropertyT m) Source # | |
MonadThrow m => MonadThrow (PropertyT m) Source # | |
PrimMonad m => PrimMonad (PropertyT m) Source # | |
Monad m => MonadTest (PropertyT m) Source # | |
MFunctor * PropertyT Source # | |
type Transformer t PropertyT m Source # | |
type PrimState (PropertyT m) Source # | |
newtype PropertyName Source #
The name of a property.
Can be constructed using OverloadedStrings
:
"apples" :: PropertyName
The number of successful tests that need to be run before a property test is considered successful.
Can be constructed using numeric literals:
200 :: TestLimit
newtype DiscardLimit Source #
The number of discards to allow before giving up.
Can be constructed using numeric literals:
10000 :: DiscardLimit
newtype ShrinkLimit Source #
The number of shrinks to try before giving up on shrinking.
Can be constructed using numeric literals:
1000 :: ShrinkLimit
newtype ShrinkRetries Source #
The number of times to re-run a test during shrinking. This is useful if you are testing something which fails non-deterministically and you want to increase the change of getting a good shrink.
If you are doing parallel state machine testing, you should probably set
shrink retries to something like 10
. This will mean that during
shrinking, a parallel test case requires 10 successful runs before it is
passes and we try a different shrink.
Can be constructed using numeric literals:
0 :: ShrinkRetries
withTests :: TestLimit -> Property -> Property Source #
Set the number of times a property should be executed before it is considered successful.
If you have a test that does not involve any generators and thus does not
need to run repeatedly, you can use withTests 1
to define a property that
will only be checked once.
withDiscards :: DiscardLimit -> Property -> Property Source #
Set the number of times a property is allowed to discard before the test runner gives up.
withShrinks :: ShrinkLimit -> Property -> Property Source #
Set the number of times a property is allowed to shrink before the test runner gives up and prints the counterexample.
withRetries :: ShrinkRetries -> Property -> Property Source #
Set the number of times a property will be executed for each shrink before
the test runner gives up and tries a different shrink. See ShrinkRetries
for more information.
property :: HasCallStack => PropertyT IO () -> Property Source #
Creates a property with the default configuration.
test :: Monad m => TestT m a -> PropertyT m a Source #
Lift a test in to a property.
Because both TestT
and PropertyT
have MonadTest
instances, this
function is not often required. It can however be useful for writing
functions directly in TestT
and thus gaining a MonadTransControl
instance at the expense of not being able to generate additional inputs
using forAll
.
One use case for this is writing tests which use ResourceT
:
property $ do n <- forAll $ Gen.int64 Range.linearBounded test . runResourceT $ do -- test with resource usage here
forAll :: (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a Source #
Generates a random input for the test by running the provided generator.
forAllT :: (Monad m, Show a, HasCallStack) => GenT m a -> PropertyT m a Source #
Generates a random input for the test by running the provided generator.
forAllWith :: (Monad m, HasCallStack) => (a -> String) -> Gen a -> PropertyT m a Source #
forAllWithT :: (Monad m, HasCallStack) => (a -> String) -> GenT m a -> PropertyT m a Source #
Group
A named collection of property tests.
Group | |
|
The name of a group of properties.
Can be constructed using OverloadedStrings
:
"fruit" :: GroupName
TestT
class Monad m => MonadTest m where Source #
MonadTest m => MonadTest (MaybeT m) Source # | |
MonadTest m => MonadTest (ResourceT m) Source # | |
Monad m => MonadTest (TestT m) Source # | |
Monad m => MonadTest (PropertyT m) Source # | |
MonadTest m => MonadTest (ExceptT x m) Source # | |
(MonadTest m, Monoid w) => MonadTest (WriterT w m) Source # | |
MonadTest m => MonadTest (StateT s m) Source # | |
MonadTest m => MonadTest (IdentityT * m) Source # | |
MonadTest m => MonadTest (StateT s m) Source # | |
(MonadTest m, Monoid w) => MonadTest (WriterT w m) Source # | |
MonadTest m => MonadTest (ReaderT * r m) Source # | |
MonadTest m => MonadTest (ContT * r m) Source # | |
(MonadTest m, Monoid w) => MonadTest (RWST r w s m) Source # | |
(MonadTest m, Monoid w) => MonadTest (RWST r w s m) Source # | |
A test monad transformer allows the assertion of expectations.
MonadTrans TestT Source # | |
MonadTransControl TestT Source # | |
Distributive TestT Source # | |
MonadBase b m => MonadBase b (TestT m) Source # | |
MonadBaseControl b m => MonadBaseControl b (TestT m) Source # | |
MonadState s m => MonadState s (TestT m) Source # | |
MonadReader r m => MonadReader r (TestT m) Source # | |
MonadError e m => MonadError e (TestT m) Source # | |
Monad m => Monad (TestT m) Source # | |
Functor m => Functor (TestT m) Source # | |
Monad m => Applicative (TestT m) Source # | |
MonadIO m => MonadIO (TestT m) Source # | |
MonadCatch m => MonadCatch (TestT m) Source # | |
MonadThrow m => MonadThrow (TestT m) Source # | |
PrimMonad m => PrimMonad (TestT m) Source # | |
MonadResource m => MonadResource (TestT m) Source # | |
Monad m => MonadTest (TestT m) Source # | |
MFunctor * TestT Source # | |
type StT TestT a Source # | |
type Transformer t TestT m Source # | |
type PrimState (TestT m) Source # | |
type StM (TestT m) a Source # | |
Log messages which are recorded during a test run.
Details on where and why a test failed.
The difference between some expected and actual value.
Diff | |
|
annotate :: (MonadTest m, HasCallStack) => String -> m () Source #
Annotates the source code with a message that might be useful for debugging a test failure.
annotateShow :: (MonadTest m, Show a, HasCallStack) => a -> m () Source #
Annotates the source code with a value that might be useful for debugging a test failure.
footnote :: MonadTest m => String -> m () Source #
Logs a message to be displayed as additional information in the footer of the failure report.
footnoteShow :: (MonadTest m, Show a) => a -> m () Source #
Logs a value to be displayed as additional information in the footer of the failure report.
failure :: (MonadTest m, HasCallStack) => m a Source #
Causes a test to fail.
assert :: (MonadTest m, HasCallStack) => Bool -> m () Source #
Fails the test if the condition provided is False
.
(===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 Source #
Fails the test if the two arguments provided are not equal.
(/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 Source #
Fails the test if the two arguments provided are equal.
eval :: (MonadTest m, HasCallStack) => a -> m a Source #
Fails the test if the value throws an exception when evaluated to weak head normal form (WHNF).
evalM :: (MonadTest m, MonadCatch m, HasCallStack) => m a -> m a Source #
Fails the test if the action throws an exception.
The benefit of using this over simply letting the exception bubble up is
that the location of the closest evalM
will be shown in the output.
evalEither :: (MonadTest m, Show x, HasCallStack) => Either x a -> m a Source #
evalExceptT :: (MonadTest m, Show x, HasCallStack) => ExceptT x m a -> m a Source #
Internal
These functions are exported in case you need them in a pinch, but are not part of the public API and may change at any time, even as part of a minor update.
defaultConfig :: PropertyConfig Source #
The default configuration for a property test.
mapConfig :: (PropertyConfig -> PropertyConfig) -> Property -> Property Source #
Map a config modification function over a property.
failDiff :: (MonadTest m, Show a, Show b, HasCallStack) => a -> b -> m () Source #
Fails with an error which shows the difference between two values.
failException :: (MonadTest m, HasCallStack) => SomeException -> m a Source #
Fails with an error which renders the type of an exception and its error message.
failWith :: (MonadTest m, HasCallStack) => Maybe Diff -> String -> m a Source #
Fail the test with an error message, useful for building other failure combinators.