Copyright | (c) 2015-2018 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | None |
Language | Haskell2010 |
This module is part of LeanCheck, a simple enumerative property-based testing library.
Some operators for property-based testing.
Synopsis
- (===) :: Eq b => (a -> b) -> (a -> b) -> a -> Bool
- (====) :: Eq c => (a -> b -> c) -> (a -> b -> c) -> a -> b -> Bool
- (&&&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
- (&&&&) :: (a -> b -> Bool) -> (a -> b -> Bool) -> a -> b -> Bool
- (|||) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
- (||||) :: (a -> b -> Bool) -> (a -> b -> Bool) -> a -> b -> Bool
- idempotent :: Eq a => (a -> a) -> a -> Bool
- identity :: Eq a => (a -> a) -> a -> Bool
- neverIdentity :: Eq a => (a -> a) -> a -> Bool
- commutative :: Eq b => (a -> a -> b) -> a -> a -> Bool
- associative :: Eq a => (a -> a -> a) -> a -> a -> a -> Bool
- distributive :: Eq a => (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool
- symmetric2 :: Eq b => (a -> a -> b) -> (a -> a -> b) -> a -> a -> Bool
- transitive :: (a -> a -> Bool) -> a -> a -> a -> Bool
- reflexive :: (a -> a -> Bool) -> a -> Bool
- irreflexive :: (a -> a -> Bool) -> a -> Bool
- symmetric :: (a -> a -> Bool) -> a -> a -> Bool
- asymmetric :: (a -> a -> Bool) -> a -> a -> Bool
- antisymmetric :: Eq a => (a -> a -> Bool) -> a -> a -> Bool
- equivalence :: (a -> a -> Bool) -> a -> a -> a -> Bool
- partialOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool
- strictPartialOrder :: (a -> a -> Bool) -> a -> a -> a -> Bool
- totalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool
- strictTotalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool
- comparison :: (a -> a -> Ordering) -> a -> a -> a -> Bool
- (=$) :: Eq b => a -> (a -> b) -> a -> Bool
- ($=) :: (a -> Bool) -> a -> Bool
- (=|) :: Eq a => [a] -> Int -> [a] -> Bool
- (|=) :: (a -> Bool) -> a -> Bool
- okEq :: Eq a => a -> a -> a -> Bool
- okOrd :: Ord a => a -> a -> a -> Bool
- okEqOrd :: (Eq a, Ord a) => a -> a -> a -> Bool
- okNum :: (Eq a, Num a) => a -> a -> a -> Bool
Combining properties
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?
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 #
Is the given binary relation an equivalence? Is the given relation reflexive, symmetric and transitive?
> check (equivalence (==) :: Int -> Int -> Int -> Bool) +++ OK, passed 200 tests. > check (equivalence (<=) :: Int -> Int -> Int -> Bool) *** Failed! Falsifiable (after 3 tests): 0 1 0
Or, using Test.LeanCheck.Utils.TypeBinding:
> check $ equivalence (<=) -:> int *** Failed! Falsifiable (after 3 tests): 0 1 0
partialOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool Source #
Is the given binary relation a partial order? Is the given relation reflexive, antisymmetric and transitive?
strictPartialOrder :: (a -> a -> Bool) -> a -> a -> a -> Bool Source #
Is the given binary relation a strict partial order? Is the given relation irreflexive, asymmetric and transitive?
totalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool Source #
Is the given binary relation a total order?
strictTotalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool Source #
Is the given binary relation a strict total order?
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
(=|) :: 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