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

Test.Falsify.Predicate

Description

Predicates

Intended for qualified import.

Synopsis

Documentation

data Predicate :: [Type] -> Type Source #

N-ary predicate

A predicate of type

Predicate '[Int, Bool, Char, ..]

is essentially a function Int -> Bool -> Char -> .. -> Bool, along with some metadata about that function that allows us to render it in a human readable way. In particular, we construct an Expr for the values that the predicate has been applied to.

Instances

Instances details
Monoid (Predicate a) Source # 
Instance details

Defined in Test.Falsify.Predicate

Semigroup (Predicate a) Source # 
Instance details

Defined in Test.Falsify.Predicate

Methods

(<>) :: Predicate a -> Predicate a -> Predicate a #

sconcat :: NonEmpty (Predicate a) -> Predicate a #

stimes :: Integral b => b -> Predicate a -> Predicate a #

Expressions

data Expr Source #

Simple expression language

The internal details of this type are (currently) not exposed.

Functions

data Fn a b Source #

Function (used for composition of a Predicate with a function)

fn :: Show b => (Var, a -> b) -> Fn a b Source #

Default constructor for a function

fnWith :: (Var, b -> String, a -> b) -> Fn a b Source #

Generalization of fn that does not depend on Show

transparent :: (a -> b) -> Fn a b Source #

Function that should not be visible in any rendered failure

Consider these two predicates:

p1, p2 :: Predicate '[Char, Char]
p1 = P.eq `P.on` (P.fn "ord"    ord)
p2 = P.eq `P.on` (P.transparent ord)

Both of these compare two characters on their codepoints (through ord), but they result in different failures. The first would give us something like

(ord x) /= (ord y)
x    : 'a'
y    : 'b'
ord x: 97
ord y: 98

whereas the second might give us something like

x /= y
x: 'a'
y: 'b'

which of these is more useful is of course application dependent.

Construction

unary Source #

Arguments

:: (a -> Bool)

The predicate proper

-> (Expr -> Err)

Error message, given Expr describing the input

-> Predicate '[a] 

Unary predicate

This is essentially a function a -> Bool; see Predicate for detailed discussion.

binary Source #

Arguments

:: (a -> b -> Bool)

The predicate proper

-> (Expr -> Expr -> Err)

Error message, given Expr describing inputs

-> Predicate [a, b] 

Binary predicate

This is essentially a function a -> b -> Bool; see Predicate for detailed discussion.

Auxiliary construction

satisfies :: (Var, a -> Bool) -> Predicate '[a] Source #

Specialization of unary for unary relations

relatedBy :: (Var, a -> b -> Bool) -> Predicate [a, b] Source #

Specialization of binary for relations

Combinators

dot :: Predicate (x ': xs) -> Fn y x -> Predicate (y ': xs) Source #

Function composition (analogue of (.))

split :: Predicate (x' ': (y' ': xs)) -> (Fn x x', Fn y y') -> Predicate (x ': (y ': xs)) Source #

Analogue of 'Control.Arrow.(***)'

on :: Predicate (x ': (x ': xs)) -> Fn y x -> Predicate (y ': (y ': xs)) Source #

Analogue of on

flip :: Predicate (x ': (y ': zs)) -> Predicate (y ': (x ': zs)) Source #

Analogue of flip

matchEither :: Predicate (a ': xs) -> Predicate (b ': xs) -> Predicate (Either a b ': xs) Source #

Match on the argument, and apply whichever predicate is applicable.

matchBool Source #

Arguments

:: Predicate xs

Predicate to evaluate if the condition is true

-> Predicate xs

Predicate to evaluate if the condition is false

-> Predicate (Bool ': xs) 

Conditional

This is a variation on choose that provides no evidence for which branch is taken.

Evaluation and partial evaluation

eval :: Predicate '[] -> Either Err () Source #

Evaluate fully applied predicate

(.$) :: Show x => Predicate (x ': xs) -> (Var, x) -> Predicate xs Source #

Infix version of at

Typical usage example:

assert $
     P.relatedBy ("equiv", equiv)
  .$ ("x", x)
  .$ ("y", y)

at Source #

Arguments

:: Predicate (x ': xs) 
-> (Var, String, x)

Rendered name, expression, and input proper

-> Predicate xs 

Generalization of (.$) that does not require a Show instance

Specific predicates

eq :: Eq a => Predicate [a, a] Source #

Equal

ne :: Eq a => Predicate [a, a] Source #

Not equal

lt :: Ord a => Predicate [a, a] Source #

(Strictly) less than

le :: Ord a => Predicate [a, a] Source #

Less than or equal to

gt :: Ord a => Predicate [a, a] Source #

(Strictly) greater than

ge :: Ord a => Predicate [a, a] Source #

Greater than or equal to

towards :: forall a. (Show a, Ord a, Num a) => a -> Predicate [a, a] Source #

Check that values get closed to the specified target

expect :: (Show a, Eq a) => a -> Predicate '[a] Source #

Specialization of eq, useful when expecting a specific value in a test

between :: (Show a, Ord a) => a -> a -> Predicate '[a] Source #

Check that lo <= x <= hi

even :: Integral a => Predicate '[a] Source #

Number is even

odd :: Integral a => Predicate '[a] Source #

Number is odd

elem :: Eq a => Predicate [[a], a] Source #

Membership check

pairwise :: forall a. Show a => Predicate [a, a] -> Predicate '[[a]] Source #

Apply predicate to every pair of consecutive elements in the list