leancheck-0.6.2: Cholesterol-free property-based testing

Copyright(c) 2015-2017 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Test.LeanCheck.Utils.Operators

Contents

Description

This module is part of LeanCheck, a simple enumerative property-based testing library.

Some operators for property-based testing.

Synopsis

Combining properties

(===) :: Eq b => (a -> b) -> (a -> b) -> a -> Bool infix 4 Source #

(====) :: Eq c => (a -> b -> c) -> (a -> b -> c) -> a -> b -> Bool infix 4 Source #

(&&&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool infixr 3 Source #

(&&&&) :: (a -> b -> Bool) -> (a -> b -> Bool) -> a -> b -> Bool infixr 3 Source #

(|||) :: (a -> Bool) -> (a -> Bool) -> a -> Bool infixr 2 Source #

(||||) :: (a -> b -> Bool) -> (a -> b -> Bool) -> a -> b -> Bool infixr 2 Source #

Properties of unary functions

idempotent :: Eq a => (a -> a) -> a -> Bool Source #

Is the given function idempotent? f (f x) == x

holds n $ idempotent abs
holds n $ idempotent sort
fails n $ idempotent negate

identity :: Eq a => (a -> a) -> a -> Bool Source #

Is the given function an identity? f x == x

holds n $ identity (+0)
holds n $ identity (sort :: [()])
holds n $ identity (not . not)

neverIdentity :: Eq a => (a -> a) -> a -> Bool Source #

Is the given function never an identity? f x /= x

holds n $ neverIdentity not
fails n $ neverIdentity negate   -- yes, fails: negate 0 == 0, hah!

Note: this is not the same as not being an identity.

Properties of operators (binary functions)

commutative :: Eq b => (a -> a -> b) -> a -> a -> Bool Source #

Is a given operator commutative? x + y = y + x

holds n $ commutative (+)
fails n $ commutative union  -- union [] [0,0] = [0]

associative :: Eq a => (a -> a -> a) -> a -> a -> a -> Bool Source #

Is a given operator associative? x + (y + z) = (x + y) + z

distributive :: Eq a => (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool Source #

Does the first operator, distributes over the second?

symmetric2 :: Eq b => (a -> a -> b) -> (a -> a -> b) -> a -> a -> Bool Source #

Are two operators flipped versions of each other?

holds n $ (<)  `symmetric2` (>)  -:> int
holds n $ (<=) `symmetric2` (>=) -:> int
fails n $ (<)  `symmetric2` (>=) -:> int
fails n $ (<=) `symmetric2` (>)  -:> int

Properties of relations (binary functions returning truth values)

transitive :: (a -> a -> Bool) -> a -> a -> a -> Bool Source #

Is a given relation transitive?

reflexive :: (a -> a -> Bool) -> a -> Bool Source #

An element is always related to itself.

irreflexive :: (a -> a -> Bool) -> a -> Bool Source #

An element is never related to itself.

symmetric :: (a -> a -> Bool) -> a -> a -> Bool Source #

Is a given relation symmetric? This is a type-restricted version of commutative.

asymmetric :: (a -> a -> Bool) -> a -> a -> Bool Source #

Is a given relation asymmetric? Not to be confused with "not symmetric" and "antissymetric".

antisymmetric :: Eq a => (a -> a -> Bool) -> a -> a -> Bool Source #

Is a given relation antisymmetric? Not to be confused with "not symmetric" and "assymetric".

Order relations

equivalence :: (a -> a -> Bool) -> a -> a -> a -> Bool Source #

partialOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool Source #

strictPartialOrder :: (a -> a -> Bool) -> a -> a -> a -> Bool Source #

totalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool Source #

strictTotalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool Source #

comparison :: (a -> a -> Ordering) -> a -> a -> a -> Bool Source #

Ternary comparison operators

(=$) :: Eq b => a -> (a -> b) -> a -> Bool infixl 4 Source #

Equal under, a ternary operator with the same fixity as ==.

x =$ f $= y  =  f x = f y
[1,2,3,4,5] =$  take 2    $= [1,2,4,8,16] -- > True
[1,2,3,4,5] =$  take 3    $= [1,2,4,8,16] -- > False
    [1,2,3] =$    sort    $= [3,2,1]      -- > True
         42 =$ (`mod` 10) $= 16842        -- > True
         42 =$ (`mod`  9) $= 16842        -- > False
        'a' =$  isLetter  $= 'b'          -- > True
        'a' =$  isLetter  $= '1'          -- > False

($=) :: (a -> Bool) -> a -> Bool infixl 4 Source #

See =$

(=|) :: Eq a => [a] -> Int -> [a] -> Bool infixl 4 Source #

Check if two lists are equal for n values. This operator has the same fixity of ==.

xs =| n |= ys  =  take n xs == take n ys
[1,2,3,4,5] =| 2 |= [1,2,4,8,16] -- > True
[1,2,3,4,5] =| 3 |= [1,2,4,8,16] -- > False

(|=) :: (a -> Bool) -> a -> Bool infixl 4 Source #

See =|

Properties for typeclass instances

okEq :: Eq a => a -> a -> a -> Bool Source #

okOrd :: Ord a => a -> a -> a -> Bool Source #

okEqOrd :: (Eq a, Ord a) => a -> a -> a -> Bool Source #