Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Tasty.Falsify
Description
Support for falsify
in the tasty
framework
As is customary, this also re-exports parts of the falsify
API, but not
modules such as Test.Falsify.Range that are intended to be imported
qualified.
Synopsis
- testProperty :: TestName -> Property' String () -> TestTree
- data TestOptions = TestOptions {}
- data Verbose
- data ExpectFailure
- testPropertyWith :: TestOptions -> TestName -> Property' String () -> TestTree
- module Test.Falsify.Property
- data Gen a
- pattern Fn :: (a -> b) -> Fun a b
- pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c
- pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d
Test property
testProperty :: TestName -> Property' String () -> TestTree Source #
Generalization of testPropertyWith
using default options
Configure test behaviour
data TestOptions Source #
Constructors
TestOptions | |
Fields
|
Instances
Default TestOptions Source # | |
Defined in Test.Falsify.Internal.Driver.Tasty Methods def :: TestOptions # |
Verbose output
Note that if a test fails (and we were not expecting failure) we show the logs independent of verbosity.
Constructors
Verbose | |
NotVerbose |
Instances
IsOption Verbose Source # | |
Defined in Test.Falsify.Internal.Driver.Tasty Methods defaultValue :: Verbose # parseValue :: String -> Maybe Verbose # optionName :: Tagged Verbose String # optionHelp :: Tagged Verbose String # showDefaultValue :: Verbose -> Maybe String # |
data ExpectFailure Source #
Do we expect the property to fail?
If ExpectFailure
, the test will fail if the property does not fail.
Note that if we expect failure for a property, then we can stop at the first
failed test; the number of tests to run for the property becomes a maximum
rather than a goal.
Constructors
ExpectFailure | |
DontExpectFailure |
testPropertyWith :: TestOptions -> TestName -> Property' String () -> TestTree Source #
Re-exports
module Test.Falsify.Property
Generators
Generator of a random value
Generators can be combined through their Functor
, Applicative
and Monad
interfaces. The primitive generator is prim
, but most users will probably
want to construct their generators using the predefined from
Test.Falsify.Generator as building blocks.
Generators support "internal integrated shrinking". Shrinking is
integrated in the sense of Hedgehog, meaning that we don't write a separate
shrinker at all, but the shrink behaviour is implied by the generator. For
example, if you have a generator genList
for a list of numbers, then
filter even <$> genList
will only generate even numbers, and that property is automatically preserved during shrinking. Shrinking is internal in the sense of Hypothesis, meaning that unlike in Hedgehog, shrinking works correctly even in the context of monadic bind. For example, if you do
do n <- genListLength replicateM n someOtherGen
then we can shrink n
and the results from someOtherGen
in any order (that
said, users may prefer to use the dedicated
list
generator for this purpose, which
improves on this in a few ways).
NOTE: Gen
is NOT an instance of Alternative
; this would not be
compatible with the generation of infinite data structures. For the same
reason, we do not have a monad transformer version of Gen either.
Functions
pattern Fn :: (a -> b) -> Fun a b Source #
Pattern synonym useful when generating functions of one argument