Copyright | (c) Colin Runciman et al. |
---|---|
License | BSD3 |
Maintainer | Roman Cheplyaka <roma@ro-che.info> |
Safe Haskell | Safe |
Language | Haskell2010 |
This module exports the main pieces of SmallCheck functionality.
To generate test cases for your own types, refer to Test.SmallCheck.Series.
For pointers to other sources of information about SmallCheck, please refer to the README at https://github.com/Bodigrim/smallcheck/blob/master/README.md
Synopsis
- forAll :: Testable m a => a -> Property m
- exists :: Testable m a => a -> Property m
- existsUnique :: Testable m a => a -> Property m
- over :: (Show a, Testable m b) => Series m a -> (a -> b) -> Property m
- monadic :: Testable m a => m a -> Property m
- (==>) :: (Testable m c, Testable m a) => c -> a -> Property m
- changeDepth :: Testable m a => (Depth -> Depth) -> a -> Property m
- changeDepth1 :: (Show a, Serial m a, Testable m b) => (Depth -> Depth) -> (a -> b) -> Property m
- type Depth = Int
- smallCheck :: Testable IO a => Depth -> a -> IO ()
- class Monad m => Testable m a where
- data Property m
- type Reason = String
Constructing tests
The simplest kind of test is a function (possibly of many
arguments) returning Bool
. The function arguments are interpreted
as being universally, existentially or uniquely quantified, depending
on the quantification context.
The default quantification context is universal (forAll
).
forAll
, exists
and existsUnique
functions set the quantification
context for function arguments. Depending on the quantification
context, the test \x y -> p x y
may be equivalent to:
- \( \forall x, y\colon p\, x \, y \) (
forAll
), - \( \exists x, y\colon p\, x \, y \) (
exists
), - \( \exists! x, y\colon p\, x \, y \) (
existsUnique
).
The quantification context affects all the variables immediately
following the quantification operator, also extending past over
,
changeDepth
and changeDepth1
functions.
However, it doesn't extend past other functions, like monadic
, and
doesn't affect the operands of ==>
. Such functions start a fresh
default quantification context.
Examples
\x y -> p x y
means \( \forall x, y\colon p\, x \, y \).
means \( \exists x, y\colon p\, x \, y \).exists
$ \x y -> p x y
means \( \exists x\colon \forall y\colon p \, x \, y \).exists
$ \x ->forAll
$ \y -> p x y
means \( \exists! x, y\colon p\, x \, y \).existsUnique
$ \x y -> p x y
means \( \exists! x, y \colon y \in s \wedge p \, x \, y \).existsUnique
$ \x ->over
s $ \y -> p x y
means \( \exists! x \colon \forall y \colon [p \, x \, y] \).existsUnique
$ \x ->monadic
$ \y -> p x y
means \( \exists! x \colon \exists! y \colon p \, x \, y \).existsUnique
$ \x ->existsUnique
$ \y -> p x y
means \( \exists x \colon (\forall y\colon p\, y) \implies (\forall z\colon q\, z) \).exists
$ \x -> (\y -> p y)==>
(\z -> q z)
forAll :: Testable m a => a -> Property m Source #
Set the universal quantification context.
Since: 1.0
exists :: Testable m a => a -> Property m Source #
Set the existential quantification context.
Since: 1.0
existsUnique :: Testable m a => a -> Property m Source #
Set the uniqueness quantification context.
Bear in mind that \( \exists! x, y\colon p\, x \, y \) is not the same as \( \exists! x \colon \exists! y \colon p \, x \, y \).
For example, \( \exists! x \colon \exists! y \colon |x| = |y| \) is true (it holds only when \(x=y=0\)), but \( \exists! x, y \colon |x| = |y| \) is false (there are many such pairs).
As is customary in mathematics,
is equivalent to
existsUnique
$ \x y -> p x y
and not to
existsUnique
$ \(x, y) -> p x y
(the latter, of course, may be explicitly written when desired).existsUnique
$ \x -> existsUnique
$ \y -> p x y
That is, all the variables affected by the same uniqueness context are quantified simultaneously as a tuple.
Since: 1.0
over :: (Show a, Testable m b) => Series m a -> (a -> b) -> Property m Source #
makes over
s $ \x -> p xx
range over the Series
s
(by
default, all variables range over the series
for their types).
Note that, unlike the quantification operators, this affects only the variable following the operator and not subsequent variables.
over
does not affect the quantification context.
Since: 1.0
changeDepth :: Testable m a => (Depth -> Depth) -> a -> Property m Source #
Run property with a modified depth. Affects all quantified variables in the property.
Since: 1.0
changeDepth1 :: (Show a, Serial m a, Testable m b) => (Depth -> Depth) -> (a -> b) -> Property m Source #
Quantify the function's argument over its series
, but adjust the
depth. This doesn't affect any subsequent variables.
Since: 1.0
Running tests
smallCheck
is a simple way to run a test.
As an alternative, consider using a testing framework.
The packages http://hackage.haskell.org/package/tasty-smallcheck and http://hackage.haskell.org/package/hspec-smallcheck provide integration with Tasty and HSpec, two popular testing frameworks.
They allow to organize SmallCheck properties into a test suite (possibly together with HUnit or QuickCheck tests) and provide other useful features.
For more ways to run the tests, see Test.SmallCheck.Drivers.
Maximum depth of generated test values.
For data values, it is the depth of nested constructor applications.
For functional values, it is both the depth of nested case analysis and the depth of results.
Since: 0.6
smallCheck :: Testable IO a => Depth -> a -> IO () Source #
A simple driver that runs the test in the IO
monad and prints the
results.
Since: 1.0
Main types and classes
class Monad m => Testable m a where Source #
Class of tests that can be run in a monad. For pure tests, it is
recommended to keep their types polymorphic in m
rather than
specialising it to Identity
.
Since: 1.0
Instances
Monad m => Testable m Bool Source # | |
(Monad m, m ~ n) => Testable n (Property m) Source # | |
Monad m => Testable m (Either Reason Reason) Source # | Works like the
Since: 1.1 |
(Serial m a, Show a, Testable m b) => Testable m (a -> b) Source # | |
Defined in Test.SmallCheck.Property |
The type of properties over the monad m
.
Since: 1.0