| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Test.QuickCheck.Function
Description
Generation of random shrinkable, showable functions. See the paper "Shrinking and showing functions" by Koen Claessen.
Note: most of the contents of this module are re-exported by Test.QuickCheck. You probably do not need to import it directly.
Example of use:
>>>:{>>>let prop :: Fun String Integer -> Bool>>>prop (Fun _ f) = f "monkey" == f "banana" || f "banana" == f "elephant">>>:}>>>quickCheck prop*** Failed! Falsified (after 3 tests and 134 shrinks): {"elephant"->1, "monkey"->1, _->0}
To generate random values of type Fun a bFunction aShow instance, you can use functionShow to write the instance; otherwise,
 use functionMap to give a bijection between your type and a type that is already an instance of Function.
 See the Function [a]
Synopsis
- data Fun a b = Fun (a :-> b, b, Shrunk) (a -> b)
- applyFun :: Fun a b -> a -> b
- apply :: Fun a b -> a -> b
- applyFun2 :: Fun (a, b) c -> a -> b -> c
- applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d
- data a :-> c
- class Function a where
- functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c
- functionShow :: (Show a, Read a) => (a -> c) -> a :-> c
- functionIntegral :: Integral a => (a -> b) -> a :-> b
- functionRealFrac :: RealFrac a => (a -> b) -> a :-> b
- functionBoundedEnum :: (Eq a, Bounded a, Enum a) => (a -> b) -> a :-> b
- pattern Fn :: (a -> b) -> Fun a b
- pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c
- pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d
Documentation
Generation of random shrinkable, showable functions.
To generate random values of type Fun a bFunction a
applyFun :: Fun a b -> a -> b Source #
Extracts the value of a function.
Fn is the pattern equivalent of this function.
prop :: Fun String Integer -> Bool
prop f = applyFun f "banana" == applyFun f "monkey"
      || applyFun f "banana" == applyFun f "elephant"applyFun2 :: Fun (a, b) c -> a -> b -> c Source #
Extracts the value of a binary function.
Fn2 is the pattern equivalent of this function.
prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool prop_zipWith f xs ys = zipWith (applyFun2 f) xs ys == [ applyFun2 f x y | (x, y) <- zip xs ys]
applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d Source #
Extracts the value of a ternary function. Fn3 is the
 pattern equivalent of this function.
The type of possibly partial concrete functions
class Function a where Source #
The class Function a is used for random generation of showable
 functions of type a -> b.
There is a default implementation for function, which you can use
 if your type has structural equality. Otherwise, you can normally
 use functionMap or functionShow.
Minimal complete definition
Nothing
Methods
function :: (a -> b) -> a :-> b Source #
function :: (Generic a, GFunction (Rep a)) => (a -> b) -> a :-> b Source #
Instances
functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c Source #
functionIntegral :: Integral a => (a -> b) -> a :-> b Source #
functionRealFrac :: RealFrac a => (a -> b) -> a :-> b Source #
pattern Fn :: (a -> b) -> Fun a b Source #
A modifier for testing functions.
prop :: Fun String Integer -> Bool
prop (Fn f) = f "banana" == f "monkey"
           || f "banana" == f "elephant"