QuickCheck-2.13.2: Automatic testing of Haskell programs

Safe HaskellSafe
LanguageHaskell98

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 b, you must have an instance Function a. If your type has a Show 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] instance for an example of the latter.

Synopsis

Documentation

data Fun a b Source #

Generation of random shrinkable, showable functions.

To generate random values of type Fun a b, you must have an instance Function a.

See also applyFun, and Fn with GHC >= 7.8.

Constructors

Fun (a :-> b, b, Shrunk) (a -> b) 
Instances
Functor (Fun a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

fmap :: (a0 -> b) -> Fun a a0 -> Fun a b #

(<$) :: a0 -> Fun a b -> Fun a a0 #

(Show a, Show b) => Show (Fun a b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

showsPrec :: Int -> Fun a b -> ShowS #

show :: Fun a b -> String #

showList :: [Fun a b] -> ShowS #

(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (Fun a b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

arbitrary :: Gen (Fun a b) Source #

shrink :: Fun a b -> [Fun a b] Source #

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"

apply :: Fun a b -> a -> b Source #

Alias to applyFun.

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.

data a :-> c Source #

The type of possibly partial concrete functions

Instances
Functor ((:->) a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

fmap :: (a0 -> b) -> (a :-> a0) -> a :-> b #

(<$) :: a0 -> (a :-> b) -> a :-> a0 #

(Show a, Show b) => Show (a :-> b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

showsPrec :: Int -> (a :-> b) -> ShowS #

show :: (a :-> b) -> String #

showList :: [a :-> b] -> ShowS #

(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (a :-> b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

arbitrary :: Gen (a :-> b) Source #

shrink :: (a :-> b) -> [a :-> b] Source #

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
Function Bool Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Bool -> b) -> Bool :-> b Source #

Function Char Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Char -> b) -> Char :-> b Source #

Function Double Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Double -> b) -> Double :-> b Source #

Function Float Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Float -> b) -> Float :-> b Source #

Function Int Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int -> b) -> Int :-> b Source #

Function Int8 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int8 -> b) -> Int8 :-> b Source #

Function Int16 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int16 -> b) -> Int16 :-> b Source #

Function Int32 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int32 -> b) -> Int32 :-> b Source #

Function Int64 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int64 -> b) -> Int64 :-> b Source #

Function Integer Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Integer -> b) -> Integer :-> b Source #

Function Ordering Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Ordering -> b) -> Ordering :-> b Source #

Function Word Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word -> b) -> Word :-> b Source #

Function Word8 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word8 -> b) -> Word8 :-> b Source #

Function Word16 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word16 -> b) -> Word16 :-> b Source #

Function Word32 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word32 -> b) -> Word32 :-> b Source #

Function Word64 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word64 -> b) -> Word64 :-> b Source #

Function () Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (() -> b) -> () :-> b Source #

Function All Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (All -> b) -> All :-> b Source #

Function Any Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Any -> b) -> Any :-> b Source #

Function IntSet Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (IntSet -> b) -> IntSet :-> b Source #

Function OrdC Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (OrdC -> b) -> OrdC :-> b Source #

Function OrdB Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (OrdB -> b) -> OrdB :-> b Source #

Function OrdA Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (OrdA -> b) -> OrdA :-> b Source #

Function C Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (C -> b) -> C :-> b Source #

Function B Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (B -> b) -> B :-> b Source #

Function A Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (A -> b) -> A :-> b Source #

Function a => Function [a] Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: ([a] -> b) -> [a] :-> b Source #

Function a => Function (Maybe a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Maybe a -> b) -> Maybe a :-> b Source #

(Integral a, Function a) => Function (Ratio a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Ratio a -> b) -> Ratio a :-> b Source #

(RealFloat a, Function a) => Function (Complex a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Complex a -> b) -> Complex a :-> b Source #

HasResolution a => Function (Fixed a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Fixed a -> b) -> Fixed a :-> b Source #

Function a => Function (Identity a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Identity a -> b) -> Identity a :-> b Source #

Function a => Function (First a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (First a -> b) -> First a :-> b Source #

Function a => Function (Last a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Last a -> b) -> Last a :-> b Source #

Function a => Function (Dual a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Dual a -> b) -> Dual a :-> b Source #

Function a => Function (Sum a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Sum a -> b) -> Sum a :-> b Source #

Function a => Function (Product a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Product a -> b) -> Product a :-> b Source #

Function a => Function (IntMap a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (IntMap a -> b) -> IntMap a :-> b Source #

Function a => Function (Seq a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Seq a -> b) -> Seq a :-> b Source #

(Ord a, Function a) => Function (Set a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Set a -> b) -> Set a :-> b Source #

(Function a, Function b) => Function (Either a b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Either a b -> b0) -> Either a b :-> b0 Source #

(Function a, Function b) => Function (a, b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b) -> b0) -> (a, b) :-> b0 Source #

(Ord a, Function a, Function b) => Function (Map a b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Map a b -> b0) -> Map a b :-> b0 Source #

(Function a, Function b, Function c) => Function (a, b, c) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b, c) -> b0) -> (a, b, c) :-> b0 Source #

Function a => Function (Const a b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Const a b -> b0) -> Const a b :-> b0 Source #

Function (f a) => Function (Alt f a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Alt f a -> b) -> Alt f a :-> b Source #

(Function a, Function b, Function c, Function d) => Function (a, b, c, d) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b, c, d) -> b0) -> (a, b, c, d) :-> b0 Source #

(Function a, Function b, Function c, Function d, Function e) => Function (a, b, c, d, e) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b, c, d, e) -> b0) -> (a, b, c, d, e) :-> b0 Source #

(Function a, Function b, Function c, Function d, Function e, Function f) => Function (a, b, c, d, e, f) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b, c, d, e, f) -> b0) -> (a, b, c, d, e, f) :-> b0 Source #

(Function a, Function b, Function c, Function d, Function e, Function f, Function g) => Function (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b, c, d, e, f, g) -> b0) -> (a, b, c, d, e, f, g) :-> b0 Source #

functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c Source #

The basic building block for Function instances. Provides a Function instance by mapping to and from a type that already has a Function instance.

functionShow :: (Show a, Read a) => (a -> c) -> a :-> c Source #

Provides a Function instance for types with Show and Read.

functionIntegral :: Integral a => (a -> b) -> a :-> b Source #

Provides a Function instance for types with Integral.

functionRealFrac :: RealFrac a => (a -> b) -> a :-> b Source #

Provides a Function instance for types with RealFrac.

functionBoundedEnum :: (Eq a, Bounded a, Enum a) => (a -> b) -> a :-> b Source #

Provides a Function instance for types with Bounded and Enum. Use only for small types (i.e. not integers): creates the list ['minBound'..'maxBound']!

functionVoid :: (forall b. void -> b) -> void :-> c Source #

Provides a Function instance for types isomorphic to Void.

An actual Function Void instance is defined in quickcheck-instances.

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"

pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c Source #

A modifier for testing binary functions.

prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool
prop_zipWith (Fn2 f) xs ys = zipWith f xs ys == [ f x y | (x, y) <- zip xs ys]

pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d Source #

A modifier for testing ternary functions.