falsify-0.2.0: Property-based testing with internal integrated shrinking
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Falsify.Property

Description

Properties

Intended for unqualified import.

Most users will probably use Test.Tasty.Falsify instead of this module.

Synopsis

Documentation

data Property' e a Source #

Property

A Property is a generator that can fail and keeps a track of some information about the test run.

In most cases, you will probably want to use Property instead, which fixes e at String.

Instances

Instances details
MonadFail (Property' String) Source # 
Instance details

Defined in Test.Falsify.Internal.Property

Methods

fail :: String -> Property' String a #

Applicative (Property' e) Source # 
Instance details

Defined in Test.Falsify.Internal.Property

Methods

pure :: a -> Property' e a #

(<*>) :: Property' e (a -> b) -> Property' e a -> Property' e b #

liftA2 :: (a -> b -> c) -> Property' e a -> Property' e b -> Property' e c #

(*>) :: Property' e a -> Property' e b -> Property' e b #

(<*) :: Property' e a -> Property' e b -> Property' e a #

Functor (Property' e) Source # 
Instance details

Defined in Test.Falsify.Internal.Property

Methods

fmap :: (a -> b) -> Property' e a -> Property' e b #

(<$) :: a -> Property' e b -> Property' e a #

Monad (Property' e) Source # 
Instance details

Defined in Test.Falsify.Internal.Property

Methods

(>>=) :: Property' e a -> (a -> Property' e b) -> Property' e b #

(>>) :: Property' e a -> Property' e b -> Property' e b #

return :: a -> Property' e a #

type Property = Property' String Source #

Property that uses strings as errors

Run generators

gen :: (HasCallStack, Show a) => Gen a -> Property' e a Source #

Generate value and add it to the log

genWith :: HasCallStack => (a -> Maybe String) -> Gen a -> Property' e a Source #

Generalization of gen that doesn't depend on a Show instance

No log entry is added if Nothing.

Property features

testFailed :: e -> Property' e a Source #

Test failure

assert :: Predicate '[] -> Property' String () Source #

Fail the test if the predicate does not hold

info :: String -> Property' e () Source #

Log some additional information about the test

This will be shown in verbose mode.

discard :: Property' e a Source #

Discard this test

label :: String -> [String] -> Property' e () Source #

Variation on collect that does not rely on Show

See collect for detailed discussion.

collect :: Show a => String -> [a] -> Property' e () Source #

Label this test

See also label, which does not rely on Show.

Motivation

Labelling is instrumental in understanding the distribution of test data. For example, consider testing a binary tree type, and we want to test some properties of an insert operation (example from "How to specify it!" by John Hughes):

prop_insert_insert :: Property ()
prop_insert_insert = do
  tree     <- gen $ ..
  (k1, v1) <- gen $ ..
  (k2, v2) <- gen $ ..
  assert $ .. (insert k1 v1 $ insert k2 v2 $ tree) ..

We might want to know in what percentage of tests k1 == k2:

collect "sameKey" [k1 == k2]

When we do, falsify will report in which percentage of tests the key are the same, and in which percentage of tests they are not.

Labels with multiple values

In general, a particular label can have multiple values in any given test run. Given a test of n test runs, for each value v reported, falsify will report what percentage of the n runs are labelled with v. That means that these percentages may not add up to 100%; indeed, if we had

collect "sameKey" [True]
..
collect "sameKey" [False]

or, equivalently,

collect "sameKey" [True, False]

then every test would have been reported as labelled with True (100%) as well as with False@ (also 100%). Of course, if we do (like above)

collect "sameKey" [k1 == k2]

each test will be labelled with either True or False, and the percentages will add up to 100%.

Difference from QuickCheck

Since you can call collect anywhere in a property, it is natural that the same label can have multiple values in any given test run. In this regard, collect is closer to QuickCheck's tabulate. However, the statistics of tabulate can be difficult to interpret; QuickCheck reports the frequency of a value as a percentage of the total number of values collected; the frequency reported by falsify here is always in terms of number of test runs, like collect does in QuickCheck. We therefore opted to use the name collect rather than tabulate.

Testing shrinking

testShrinking :: forall e. Show e => Predicate [e, e] -> Property' e () -> Property' String () Source #

Test shrinking of a property

A property is normally only shrunk when it fails. We do the same here: if the property succeeds, we discard the test and try again.

If the given property itself discards immediately, then this generator will discard also; otherwise, only shrink steps are considered that do not lead to a discard.

testMinimum :: forall e. Show e => Predicate '[e] -> Property' e () -> Property' String () Source #

Test the minimum error thrown by the property

If the given property passes, we will discard this test (in that case, there is nothing to test); this test is also discarded if the given property discards.

NOTE: When testing a particular generator, you might still want to test with some particular property in mind. Otherwise, the minimum value will always simply be the value that the generator produces when given the Minimal sample tree.

Testing generators

testGen :: forall a. Show a => Predicate '[a] -> Gen a -> Property' String () Source #

Test output of the generator

testShrinkingOfGen :: Show a => Predicate [a, a] -> Gen a -> Property' String () Source #

Test shrinking of a generator

We check any shrink step that the generator can make (independent of any property).