tasty-smallcheck-0.8.2: SmallCheck support for the Tasty test framework.
Safe HaskellNone
LanguageHaskell2010

Test.Tasty.SmallCheck

Description

This module allows to use SmallCheck properties in tasty.

Synopsis

Documentation

testProperty :: Testable IO a => TestName -> a -> TestTree Source #

Create a Test for a SmallCheck Testable property

newtype SmallCheckDepth Source #

The "depth" parameter for SmallCheck

Constructors

SmallCheckDepth Int 

Instances

Instances details
Enum SmallCheckDepth Source # 
Instance details

Defined in Test.Tasty.SmallCheck

Eq SmallCheckDepth Source # 
Instance details

Defined in Test.Tasty.SmallCheck

Integral SmallCheckDepth Source # 
Instance details

Defined in Test.Tasty.SmallCheck

Num SmallCheckDepth Source # 
Instance details

Defined in Test.Tasty.SmallCheck

Ord SmallCheckDepth Source # 
Instance details

Defined in Test.Tasty.SmallCheck

Real SmallCheckDepth Source # 
Instance details

Defined in Test.Tasty.SmallCheck

IsOption SmallCheckDepth Source # 
Instance details

Defined in Test.Tasty.SmallCheck

changeDepth1 :: forall a (m :: Type -> Type) b. (Show a, Serial m a, Testable m b) => (Depth -> Depth) -> (a -> b) -> Property m #

Quantify the function's argument over its series, but adjust the depth. This doesn't affect any subsequent variables.

changeDepth :: forall (m :: Type -> Type) a. Testable m a => (Depth -> Depth) -> a -> Property m #

Run property with a modified depth. Affects all quantified variables in the property.

(==>) :: forall (m :: Type -> Type) c a. (Testable m c, Testable m a) => c -> a -> Property m infixr 0 #

The ==> operator can be used to express a restricting condition under which a property should hold. It corresponds to implication in the classical logic.

Note that ==> resets the quantification context for its operands to the default (universal).

existsUnique :: forall (m :: Type -> Type) a. Testable m a => a -> Property m #

Set the uniqueness quantification context.

Bear in mind that ∃! (x, y): p x y is not the same as ∃! x: ∃! y: p x y.

For example, ∃! x: ∃! y: |x| = |y| is true (it holds only when x=0), but ∃! (x,y): |x| = |y| is false (there are many such pairs).

As is customary in mathematics, existsUnique $ \x y -> p x y is equivalent to existsUnique $ \(x,y) -> p x y and not to existsUnique $ \x -> existsUnique $ \y -> p x y (the latter, of course, may be explicitly written when desired).

That is, all the variables affected by the same uniqueness context are quantified simultaneously as a tuple.

exists :: forall (m :: Type -> Type) a. Testable m a => a -> Property m #

Set the existential quantification context

forAll :: forall (m :: Type -> Type) a. Testable m a => a -> Property m #

Set the universal quantification context

monadic :: Testable m a => m a -> Property m #

Execute a monadic test

over :: forall a (m :: Type -> Type) b. (Show a, Testable m b) => Series m a -> (a -> b) -> Property m #

over s $ \x -> p x makes x 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.

data Property (m :: Type -> Type) #

The type of properties over the monad m

Instances

Instances details
(Monad m, m ~ n) => Testable n (Property m) 
Instance details

Defined in Test.SmallCheck.Property

Methods

test :: Property m -> Property n #

IsTest (Property IO) Source # 
Instance details

Defined in Test.Tasty.SmallCheck

class Monad m => Testable (m :: Type -> Type) a where #

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.

Methods

test :: a -> Property m #

Instances

Instances details
Monad m => Testable m Bool 
Instance details

Defined in Test.SmallCheck.Property

Methods

test :: Bool -> Property m #

(Monad m, m ~ n) => Testable n (Property m) 
Instance details

Defined in Test.SmallCheck.Property

Methods

test :: Property m -> Property n #

Monad m => Testable m (Either Reason Reason)

Works like the Bool instance, but includes an explanation of the result.

Left and Right correspond to test failure and success respectively.

Instance details

Defined in Test.SmallCheck.Property

(Serial m a, Show a, Testable m b) => Testable m (a -> b) 
Instance details

Defined in Test.SmallCheck.Property

Methods

test :: (a -> b) -> Property m #

type Depth = Int #

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.

type Reason = String #

An explanation for the test outcome

Orphan instances

IsTest (Property IO) Source # 
Instance details