QuickCheck-2.9.2: Automatic testing of Haskell programs

Safe HaskellNone
LanguageHaskell98

Test.QuickCheck.Function

Description

Generation of random shrinkable, showable functions. See the paper "Shrinking and showing functions" by Koen Claessen.

Example of use:

>>> :{
>>> let prop :: Fun String Integer -> Bool
>>> prop (Fun _ f) = f "monkey" == f "banana" || f "banana" == f "elephant"
>>> :}
>>> quickCheck prop
*** Failed! Falsifiable (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 #

Constructors

Fun (a :-> b, b, Bool) (a -> b) 

Instances

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

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 # 

Methods

arbitrary :: Gen (Fun a b) Source #

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

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

data a :-> c Source #

The type of possibly partial concrete functions

Instances

Functor ((:->) a) Source # 

Methods

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

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

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

Methods

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

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

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

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

Methods

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

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

class Function a where Source #

Methods

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

function :: (Generic a, GFunction (Rep a)) => (a -> b) -> a :-> b Source #

Instances

Function Bool Source # 

Methods

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

Function Char Source # 

Methods

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

Function Double Source # 

Methods

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

Function Float Source # 

Methods

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

Function Int Source # 

Methods

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

Function Int8 Source # 

Methods

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

Function Int16 Source # 

Methods

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

Function Int32 Source # 

Methods

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

Function Int64 Source # 

Methods

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

Function Integer Source # 

Methods

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

Function Ordering Source # 

Methods

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

Function Word8 Source # 

Methods

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

Function Word16 Source # 

Methods

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

Function Word32 Source # 

Methods

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

Function Word64 Source # 

Methods

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

Function () Source # 

Methods

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

Function Natural Source # 

Methods

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

Function IntSet Source # 

Methods

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

Function OrdC Source # 

Methods

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

Function OrdB Source # 

Methods

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

Function OrdA Source # 

Methods

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

Function C Source # 

Methods

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

Function B Source # 

Methods

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

Function A Source # 

Methods

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

Function a => Function [a] Source # 

Methods

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

Function a => Function (Maybe a) Source # 

Methods

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

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

Methods

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

Function a => Function (NonEmpty a) Source # 

Methods

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

HasResolution a => Function (Fixed a) Source # 

Methods

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

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

Methods

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

Function a => Function (Seq a) Source # 

Methods

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

Function a => Function (IntMap a) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

function :: ((a, b, c, d, e, f, g) -> b) -> (a, b, c, d, e, f, g) :-> b 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']!

pattern Fn :: forall t t1. (t -> t1) -> Fun t t1 Source #

A pattern for matching against the function only:

prop :: Fun String Integer -> Bool
prop (Fn f) = f "banana" == f "monkey"
           || f "banana" == f "elephant"