quickspec-2: Equational laws for free!

Safe HaskellNone
LanguageHaskell98

QuickSpec

Contents

Description

The main QuickSpec module. Everything you need to run QuickSpec lives here.

To run QuickSpec, you need to tell it which functions to test. We call the list of functions the signature. Here is an example signature, which tells QuickSpec to test the ++, reverse and [] functions:

sig = [
  con "++"      ((++) :: [A] -> [A] -> [A]),
  con "reverse" (reverse :: [A] -> [A]),
  con "[]"      ([] :: [A]) ]

The con function, used above, adds a function to the signature, given its name and its value. When declaring polymorphic functions in the signature, we use the types A to E to represent type variables. Having defined this signature, we can say quickSpec sig to test it and see the discovered equations.

If you want to test functions over your own datatypes, those types need to implement Arbitrary and Ord (if the Ord instance is a problem, see Observe). You must also declare those instances to QuickSpec, by including them in the signature. For monomorphic types you can do this using monoType:

data T = ...
main = quickSpec [
  ...,
  `monoType` (Proxy :: Proxy T)]

You can only declare monomorphic types with monoType. If you want to test your own polymorphic types, you must explicitly declare Arbitrary and Ord instances using the inst function.

You can also use QuickSpec to find conditional equations. To do so, you need to include some predicates in the signature. These are functions returning Bool which can appear as conditions in other equations. Declaring a predicate works just like declaring a function, except that you declare it using predicate instead of con.

You can also put certain options in the signature. The most useful is withMaxTermSize, which you can use to tell QuickSpec to generate larger equations.

The examples directory contains many examples. Here are some interesting ones:

  • Arith.hs: a simple arithmetic example. Demonstrates basic use of QuickSpec.
  • Lists.hs: list functions. Demonstrates testing polymorphic functions.
  • Sorted.hs: sorting. Demonstrates finding conditional equations.
  • IntSet.hs: a few functions from Data.IntSet. Demonstrates testing user-defined datatypes and finding conditional equations.
  • PrettyPrinting.hs: pretty printing combinators. Demonstrates testing user-defined datatypes and using observational equality.
  • Parsing.hs: parser combinators. Demonstrates testing polymorphic datatypes and using observational equality.

You can also find some larger case studies in our paper, <http://www.cse.chalmers.se/~nicsma/papers/quickspec2.pdf Quick specifications for the busy programmer>.

Synopsis

Running QuickSpec

quickSpec :: Signature sig => sig -> IO () Source #

Run QuickSpec. See the documentation at the top of this file.

data Sig Source #

A signature.

Instances

Monoid Sig Source # 

Methods

mempty :: Sig #

mappend :: Sig -> Sig -> Sig #

mconcat :: [Sig] -> Sig #

Signature Sig Source # 

Methods

toSig :: Sig -> Sig Source #

class Signature sig where Source #

A class of things that can be used as a QuickSpec signature.

Minimal complete definition

toSig

Methods

toSig :: sig -> Sig Source #

Convert the thing to a signature.

Instances

Signature Sig Source # 

Methods

toSig :: Sig -> Sig Source #

Signature sig => Signature [sig] Source # 

Methods

toSig :: [sig] -> Sig Source #

Declaring functions and predicates

con :: Typeable a => String -> a -> Sig Source #

Declare a constant with a given name and value. If the constant you want to use is polymorphic, you can use the types A, B, C, D, E to monomorphise it, for example:

constant "reverse" (reverse :: [A] -> [A])

QuickSpec will then understand that the constant is really polymorphic.

predicate :: (Predicateable a, Typeable a, Typeable (TestCase a)) => String -> a -> Sig Source #

Declare a predicate with a given name and value. The predicate should be a function which returns Bool. It will appear in equations just like any other constant, but will also be allowed to appear as a condition.

For example:

sig = [
  con "delete" (delete :: Int -> [Int] -> [Int]),
  con "insert" (insert :: Int -> [Int] -> [Int]),
  predicate "member" (member :: Int -> [Int] -> Bool) ]

Type variables for polymorphic functions

data A Source #

data B Source #

data C Source #

data D Source #

data E Source #

Declaring types

monoType :: forall proxy a. (Ord a, Arbitrary a, Typeable a) => proxy a -> Sig Source #

Declare a new monomorphic type. The type must implement Ord and Arbitrary.

vars :: forall proxy a. Typeable a => [String] -> proxy a -> Sig Source #

Customize how variables of a particular type are named.

monoTypeWithVars :: forall proxy a. (Ord a, Arbitrary a, Typeable a) => [String] -> proxy a -> Sig Source #

Declare a new monomorphic type, saying how you want variables of that type to be named.

inst :: (Typeable c1, Typeable c2) => (c1 :- c2) -> Sig Source #

Declare a typeclass instance. QuickSpec needs to have an Ord and Arbitrary instance for each type you want it to test.

For example, if you are testing Map k v, you will need to add the following two declarations to your signature:

inst (Sub Dict :: (Ord A, Ord B) :- Ord (Map A B))
inst (Sub Dict :: (Arbitrary A, Arbitrary B) :- Arbitrary (Map A B))

class (Arbitrary test, Ord outcome) => Observe test outcome a | a -> test outcome where Source #

A typeclass for types which support observational equality, typically used for types that have no Ord instance.

An instance Observe test outcome a declares that values of type a can be tested for equality by random testing. You supply a function observe :: test -> outcome -> a. Then, two values x and y are considered equal, if for many random values of type test, observe test x == observe test y.

For an example of using observational equality, see PrettyPrinting.hs.

You must use inst to add the Observe instance to your signature. Note that monoType requires an Ord instance, so this even applies for monomorphic types. Don't forget to add the Arbitrary instance too in that case.

Methods

observe :: test -> a -> outcome Source #

Make an observation on a value. Should satisfy the following law: if x /= y, then there exists a value of test such that observe test x /= observe test y.

observe :: (test ~ (), outcome ~ a) => test -> a -> outcome Source #

Make an observation on a value. Should satisfy the following law: if x /= y, then there exists a value of test such that observe test x /= observe test y.

Instances

(Arbitrary a, Observe test outcome b) => Observe (a, test) outcome (a -> b) Source # 

Methods

observe :: (a, test) -> (a -> b) -> outcome Source #

Exploring functions in series

background :: Signature sig => sig -> Sig Source #

Declare some functions as being background functions. These are functions which are not interesting on their own, but which may appear in interesting laws with non-background functions. Declaring background functions may improve the laws you get out.

Here is an example, which tests ++ and length, giving 0 and + as background functions:

main = quickSpec [
  con "++" ((++) :: [A] -> [A] -> [A]),
  con "length" (length :: [A] -> Int),

  background [
    con "0" (0 :: Int),
    con "+" ((+) :: Int -> Int -> Int) ] ]

series :: Signature sig => [sig] -> Sig Source #

Run QuickCheck on a series of signatures. Tests the functions in the first signature, then adds the functions in the second signature, then adds the functions in the third signature, and so on.

This can be useful when you have a core API you want to test first, and a larger API you want to test later. The laws for the core API will be printed separately from the laws for the larger API.

Here is an example which first tests 0 and + and then adds ++ and length:

main = quickSpec [sig1, sig2]
  where
    sig1 = [
      con "0" (0 :: Int),
      con "+" ((+) :: Int -> Int -> Int) ]
    sig2 = [
      con "++" ((++) :: [A] -> [A] -> [A]),
      con "length" (length :: [A] -> Int) ]

Customising QuickSpec

withMaxTermSize :: Int -> Sig Source #

Set the maximum size of terms to explore (default: 7).

withMaxTests :: Int -> Sig Source #

Set how many times to test each discovered law (default: 1000).

withMaxTestSize :: Int -> Sig Source #

Set the maximum value for QuickCheck's size parameter when generating test data (default: 20).

defaultTo :: Typeable a => proxy a -> Sig Source #

Set which type polymorphic terms are tested at.

withPruningDepth :: Int -> Sig Source #

Set how hard QuickSpec tries to filter out redundant equations (default: no limit).

If you experience long pauses when running QuickSpec, try setting this number to 2 or 3.

withPruningTermSize :: Int -> Sig Source #

Set the maximum term size QuickSpec will reason about when it filters out redundant equations (default: same as maximum term size).

If you get laws you believe are redundant, try increasing this number to 1 or 2 more than the maximum term size.

withFixedSeed :: Int -> Sig Source #

Set the random number seed used for test case generation. Useful if you want repeatable results.

Re-exported functionality

class Typeable k (a :: k) #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

newtype a :- b :: Constraint -> Constraint -> * infixr 9 #

This is the type of entailment.

a :- b is read as a "entails" b.

With this we can actually build a category for Constraint resolution.

e.g.

Because Eq a is a superclass of Ord a, we can show that Ord a entails Eq a.

Because instance Ord a => Ord [a] exists, we can show that Ord a entails Ord [a] as well.

This relationship is captured in the :- entailment type here.

Since p :- p and entailment composes, :- forms the arrows of a Category of constraints. However, Category only became sufficiently general to support this instance in GHC 7.8, so prior to 7.8 this instance is unavailable.

But due to the coherence of instance resolution in Haskell, this Category has some very interesting properties. Notably, in the absence of IncoherentInstances, this category is "thin", which is to say that between any two objects (constraints) there is at most one distinguishable arrow.

This means that for instance, even though there are two ways to derive Ord a :- Eq [a], the answers from these two paths _must_ by construction be equal. This is a property that Haskell offers that is pretty much unique in the space of languages with things they call "type classes".

What are the two ways?

Well, we can go from Ord a :- Eq a via the superclass relationship, and then from Eq a :- Eq [a] via the instance, or we can go from Ord a :- Ord [a] via the instance then from Ord [a] :- Eq [a] through the superclass relationship and this diagram by definition must "commute".

Diagrammatically,

                   Ord a
               ins /     \ cls
                  v       v
            Ord [a]     Eq a
               cls \     / ins
                    v   v
                   Eq [a]

This safety net ensures that pretty much anything you can write with this library is sensible and can't break any assumptions on the behalf of library authors.

Constructors

Sub (a -> Dict b) 

Instances

Category Constraint (:-)

Possible since GHC 7.8, when Category was made polykinded.

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

() :=> (Eq ((:-) a b)) 

Methods

ins :: () :- Eq (a :- b) #

() :=> (Ord ((:-) a b)) 

Methods

ins :: () :- Ord (a :- b) #

() :=> (Show ((:-) a b)) 

Methods

ins :: () :- Show (a :- b) #

Eq ((:-) a b)

Assumes IncoherentInstances doesn't exist.

Methods

(==) :: (a :- b) -> (a :- b) -> Bool #

(/=) :: (a :- b) -> (a :- b) -> Bool #

(Typeable Constraint p, Typeable Constraint q, p, q) => Data ((:-) p q) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> (p :- q) -> c (p :- q) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (p :- q) #

toConstr :: (p :- q) -> Constr #

dataTypeOf :: (p :- q) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (p :- q)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (p :- q)) #

gmapT :: (forall b. Data b => b -> b) -> (p :- q) -> p :- q #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r #

gmapQ :: (forall d. Data d => d -> u) -> (p :- q) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> (p :- q) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) #

Ord ((:-) a b)

Assumes IncoherentInstances doesn't exist.

Methods

compare :: (a :- b) -> (a :- b) -> Ordering #

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

(<=) :: (a :- b) -> (a :- b) -> Bool #

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

(>=) :: (a :- b) -> (a :- b) -> Bool #

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

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

Show ((:-) a b) 

Methods

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

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

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

a => NFData ((:-) a b) 

Methods

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

data Dict a :: Constraint -> * where #

Values of type Dict p capture a dictionary for a constraint of type p.

e.g.

Dict :: Dict (Eq Int)

captures a dictionary that proves we have an:

instance Eq 'Int

Pattern matching on the Dict constructor will bring this instance into scope.

Constructors

Dict :: Dict a 

Instances

a :=> (Read (Dict a)) 

Methods

ins :: a :- Read (Dict a) #

a :=> (Monoid (Dict a)) 

Methods

ins :: a :- Monoid (Dict a) #

a :=> (Enum (Dict a)) 

Methods

ins :: a :- Enum (Dict a) #

a :=> (Bounded (Dict a)) 

Methods

ins :: a :- Bounded (Dict a) #

() :=> (Eq (Dict a)) 

Methods

ins :: () :- Eq (Dict a) #

() :=> (Ord (Dict a)) 

Methods

ins :: () :- Ord (Dict a) #

() :=> (Show (Dict a)) 

Methods

ins :: () :- Show (Dict a) #

() :=> (Semigroup (Dict a)) 

Methods

ins :: () :- Semigroup (Dict a) #

a => Bounded (Dict a) 

Methods

minBound :: Dict a #

maxBound :: Dict a #

a => Enum (Dict a) 

Methods

succ :: Dict a -> Dict a #

pred :: Dict a -> Dict a #

toEnum :: Int -> Dict a #

fromEnum :: Dict a -> Int #

enumFrom :: Dict a -> [Dict a] #

enumFromThen :: Dict a -> Dict a -> [Dict a] #

enumFromTo :: Dict a -> Dict a -> [Dict a] #

enumFromThenTo :: Dict a -> Dict a -> Dict a -> [Dict a] #

Eq (Dict a) 

Methods

(==) :: Dict a -> Dict a -> Bool #

(/=) :: Dict a -> Dict a -> Bool #

(Typeable Constraint p, p) => Data (Dict p) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dict p -> c (Dict p) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dict p) #

toConstr :: Dict p -> Constr #

dataTypeOf :: Dict p -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Dict p)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dict p)) #

gmapT :: (forall b. Data b => b -> b) -> Dict p -> Dict p #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dict p -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dict p -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

Ord (Dict a) 

Methods

compare :: Dict a -> Dict a -> Ordering #

(<) :: Dict a -> Dict a -> Bool #

(<=) :: Dict a -> Dict a -> Bool #

(>) :: Dict a -> Dict a -> Bool #

(>=) :: Dict a -> Dict a -> Bool #

max :: Dict a -> Dict a -> Dict a #

min :: Dict a -> Dict a -> Dict a #

a => Read (Dict a) 
Show (Dict a) 

Methods

showsPrec :: Int -> Dict a -> ShowS #

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

Semigroup (Dict a) 

Methods

(<>) :: Dict a -> Dict a -> Dict a #

sconcat :: NonEmpty (Dict a) -> Dict a #

stimes :: Integral b => b -> Dict a -> Dict a #

a => Monoid (Dict a) 

Methods

mempty :: Dict a #

mappend :: Dict a -> Dict a -> Dict a #

mconcat :: [Dict a] -> Dict a #

NFData (Dict c) 

Methods

rnf :: Dict c -> () #

data Proxy k (t :: k) :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Generic1 k (Proxy k) 

Associated Types

type Rep1 (Proxy k) (f :: Proxy k -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Proxy k) f a #

to1 :: Rep1 (Proxy k) f a -> f a #

Monad (Proxy *)

Since: 4.7.0.0

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *)

Since: 4.7.0.0

Methods

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

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

Applicative (Proxy *)

Since: 4.7.0.0

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

liftA2 :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Foldable (Proxy *)

Since: 4.7.0.0

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Traversable (Proxy *)

Since: 4.7.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Proxy * a -> f (Proxy * b) #

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) #

mapM :: Monad m => (a -> m b) -> Proxy * a -> m (Proxy * b) #

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) #

Eq1 (Proxy *)

Since: 4.9.0.0

Methods

liftEq :: (a -> b -> Bool) -> Proxy * a -> Proxy * b -> Bool #

Ord1 (Proxy *)

Since: 4.9.0.0

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy * a -> Proxy * b -> Ordering #

Read1 (Proxy *)

Since: 4.9.0.0

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy * a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy * a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy * a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy * a] #

Show1 (Proxy *)

Since: 4.9.0.0

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy * a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy * a] -> ShowS #

Alternative (Proxy *)

Since: 4.9.0.0

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadPlus (Proxy *)

Since: 4.9.0.0

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Bounded (Proxy k t) 

Methods

minBound :: Proxy k t #

maxBound :: Proxy k t #

Enum (Proxy k s)

Since: 4.7.0.0

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s)

Since: 4.7.0.0

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Ord (Proxy k s)

Since: 4.7.0.0

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Read (Proxy k s)

Since: 4.7.0.0

Show (Proxy k s)

Since: 4.7.0.0

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s)

Since: 4.7.0.0

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Semigroup (Proxy k s)

Since: 4.9.0.0

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Monoid (Proxy k s)

Since: 4.7.0.0

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

type Rep1 k (Proxy k) 
type Rep1 k (Proxy k) = D1 k (MetaData "Proxy" "Data.Proxy" "base" False) (C1 k (MetaCons "Proxy" PrefixI False) (U1 k))
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 * (MetaData "Proxy" "Data.Proxy" "base" False) (C1 * (MetaCons "Proxy" PrefixI False) (U1 *))

class Arbitrary a #

Random generation and shrinking of values.

QuickCheck provides Arbitrary instances for most types in base, except those which incur extra dependencies. For a wider range of Arbitrary instances see the quickcheck-instances package.

Minimal complete definition

arbitrary

Instances

Arbitrary Bool 

Methods

arbitrary :: Gen Bool #

shrink :: Bool -> [Bool] #

Arbitrary Char 

Methods

arbitrary :: Gen Char #

shrink :: Char -> [Char] #

Arbitrary Double 
Arbitrary Float 

Methods

arbitrary :: Gen Float #

shrink :: Float -> [Float] #

Arbitrary Int 

Methods

arbitrary :: Gen Int #

shrink :: Int -> [Int] #

Arbitrary Int8 

Methods

arbitrary :: Gen Int8 #

shrink :: Int8 -> [Int8] #

Arbitrary Int16 

Methods

arbitrary :: Gen Int16 #

shrink :: Int16 -> [Int16] #

Arbitrary Int32 

Methods

arbitrary :: Gen Int32 #

shrink :: Int32 -> [Int32] #

Arbitrary Int64 

Methods

arbitrary :: Gen Int64 #

shrink :: Int64 -> [Int64] #

Arbitrary Integer 
Arbitrary Ordering 
Arbitrary Word 

Methods

arbitrary :: Gen Word #

shrink :: Word -> [Word] #

Arbitrary Word8 

Methods

arbitrary :: Gen Word8 #

shrink :: Word8 -> [Word8] #

Arbitrary Word16 
Arbitrary Word32 
Arbitrary Word64 
Arbitrary () 

Methods

arbitrary :: Gen () #

shrink :: () -> [()] #

Arbitrary Version

Generates Version with non-empty non-negative versionBranch, and empty versionTags

Arbitrary QCGen 

Methods

arbitrary :: Gen QCGen #

shrink :: QCGen -> [QCGen] #

Arbitrary ExitCode 
Arbitrary All 

Methods

arbitrary :: Gen All #

shrink :: All -> [All] #

Arbitrary Any 

Methods

arbitrary :: Gen Any #

shrink :: Any -> [Any] #

Arbitrary CChar 

Methods

arbitrary :: Gen CChar #

shrink :: CChar -> [CChar] #

Arbitrary CSChar 
Arbitrary CUChar 
Arbitrary CShort 
Arbitrary CUShort 
Arbitrary CInt 

Methods

arbitrary :: Gen CInt #

shrink :: CInt -> [CInt] #

Arbitrary CUInt 

Methods

arbitrary :: Gen CUInt #

shrink :: CUInt -> [CUInt] #

Arbitrary CLong 

Methods

arbitrary :: Gen CLong #

shrink :: CLong -> [CLong] #

Arbitrary CULong 
Arbitrary CLLong 
Arbitrary CULLong 
Arbitrary CFloat 
Arbitrary CDouble 
Arbitrary CPtrdiff 
Arbitrary CSize 

Methods

arbitrary :: Gen CSize #

shrink :: CSize -> [CSize] #

Arbitrary CWchar 
Arbitrary CSigAtomic 
Arbitrary CClock 
Arbitrary CTime 

Methods

arbitrary :: Gen CTime #

shrink :: CTime -> [CTime] #

Arbitrary CUSeconds 
Arbitrary CSUSeconds 
Arbitrary CIntPtr 
Arbitrary CUIntPtr 
Arbitrary CIntMax 
Arbitrary CUIntMax 
Arbitrary IntSet 
Arbitrary a => Arbitrary [a] 

Methods

arbitrary :: Gen [a] #

shrink :: [a] -> [[a]] #

Arbitrary a => Arbitrary (Maybe a) 

Methods

arbitrary :: Gen (Maybe a) #

shrink :: Maybe a -> [Maybe a] #

Integral a => Arbitrary (Ratio a) 

Methods

arbitrary :: Gen (Ratio a) #

shrink :: Ratio a -> [Ratio a] #

(Ord a, Num a, Real a, Enum a) => Arbitrary (Bounds a) 

Methods

arbitrary :: Gen (Bounds a) #

shrink :: Bounds a -> [Bounds a] #

(RealFloat a, Arbitrary a) => Arbitrary (Complex a) 

Methods

arbitrary :: Gen (Complex a) #

shrink :: Complex a -> [Complex a] #

HasResolution a => Arbitrary (Fixed a) 

Methods

arbitrary :: Gen (Fixed a) #

shrink :: Fixed a -> [Fixed a] #

Arbitrary a => Arbitrary (ZipList a) 

Methods

arbitrary :: Gen (ZipList a) #

shrink :: ZipList a -> [ZipList a] #

Arbitrary a => Arbitrary (Identity a) 

Methods

arbitrary :: Gen (Identity a) #

shrink :: Identity a -> [Identity a] #

Arbitrary a => Arbitrary (Dual a) 

Methods

arbitrary :: Gen (Dual a) #

shrink :: Dual a -> [Dual a] #

(Arbitrary a, CoArbitrary a) => Arbitrary (Endo a) 

Methods

arbitrary :: Gen (Endo a) #

shrink :: Endo a -> [Endo a] #

Arbitrary a => Arbitrary (Sum a) 

Methods

arbitrary :: Gen (Sum a) #

shrink :: Sum a -> [Sum a] #

Arbitrary a => Arbitrary (Product a) 

Methods

arbitrary :: Gen (Product a) #

shrink :: Product a -> [Product a] #

Arbitrary a => Arbitrary (First a) 

Methods

arbitrary :: Gen (First a) #

shrink :: First a -> [First a] #

Arbitrary a => Arbitrary (Last a) 

Methods

arbitrary :: Gen (Last a) #

shrink :: Last a -> [Last a] #

Arbitrary a => Arbitrary (IntMap a) 

Methods

arbitrary :: Gen (IntMap a) #

shrink :: IntMap a -> [IntMap a] #

Arbitrary a => Arbitrary (Seq a) 

Methods

arbitrary :: Gen (Seq a) #

shrink :: Seq a -> [Seq a] #

(Ord a, Arbitrary a) => Arbitrary (Set a) 

Methods

arbitrary :: Gen (Set a) #

shrink :: Set a -> [Set a] #

(CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) 

Methods

arbitrary :: Gen (a -> b) #

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

(Arbitrary a, Arbitrary b) => Arbitrary (Either a b) 

Methods

arbitrary :: Gen (Either a b) #

shrink :: Either a b -> [Either a b] #

(Arbitrary a, Arbitrary b) => Arbitrary (a, b) 

Methods

arbitrary :: Gen (a, b) #

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

Arbitrary (m a) => Arbitrary (WrappedMonad m a) 

Methods

arbitrary :: Gen (WrappedMonad m a) #

shrink :: WrappedMonad m a -> [WrappedMonad m a] #

(Ord k, Arbitrary k, Arbitrary v) => Arbitrary (Map k v) 

Methods

arbitrary :: Gen (Map k v) #

shrink :: Map k v -> [Map k v] #

(Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) 

Methods

arbitrary :: Gen (a, b, c) #

shrink :: (a, b, c) -> [(a, b, c)] #

Arbitrary (a b c) => Arbitrary (WrappedArrow a b c) 

Methods

arbitrary :: Gen (WrappedArrow a b c) #

shrink :: WrappedArrow a b c -> [WrappedArrow a b c] #

Arbitrary a => Arbitrary (Const k a b) 

Methods

arbitrary :: Gen (Const k a b) #

shrink :: Const k a b -> [Const k a b] #

Arbitrary (f a) => Arbitrary (Alt k f a) 

Methods

arbitrary :: Gen (Alt k f a) #

shrink :: Alt k f a -> [Alt k f a] #

Arbitrary a => Arbitrary (Constant k a b) 

Methods

arbitrary :: Gen (Constant k a b) #

shrink :: Constant k a b -> [Constant k a b] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) 

Methods

arbitrary :: Gen (a, b, c, d) #

shrink :: (a, b, c, d) -> [(a, b, c, d)] #

(Arbitrary1 f, Arbitrary1 g, Arbitrary a) => Arbitrary (Product * f g a) 

Methods

arbitrary :: Gen (Product * f g a) #

shrink :: Product * f g a -> [Product * f g a] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e) => Arbitrary (a, b, c, d, e) 

Methods

arbitrary :: Gen (a, b, c, d, e) #

shrink :: (a, b, c, d, e) -> [(a, b, c, d, e)] #

(Arbitrary1 f, Arbitrary1 g, Arbitrary a) => Arbitrary (Compose * * f g a) 

Methods

arbitrary :: Gen (Compose * * f g a) #

shrink :: Compose * * f g a -> [Compose * * f g a] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f) => Arbitrary (a, b, c, d, e, f) 

Methods

arbitrary :: Gen (a, b, c, d, e, f) #

shrink :: (a, b, c, d, e, f) -> [(a, b, c, d, e, f)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g) => Arbitrary (a, b, c, d, e, f, g) 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g) #

shrink :: (a, b, c, d, e, f, g) -> [(a, b, c, d, e, f, g)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h) => Arbitrary (a, b, c, d, e, f, g, h) 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h) #

shrink :: (a, b, c, d, e, f, g, h) -> [(a, b, c, d, e, f, g, h)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i) => Arbitrary (a, b, c, d, e, f, g, h, i) 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h, i) #

shrink :: (a, b, c, d, e, f, g, h, i) -> [(a, b, c, d, e, f, g, h, i)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j) => Arbitrary (a, b, c, d, e, f, g, h, i, j) 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h, i, j) #

shrink :: (a, b, c, d, e, f, g, h, i, j) -> [(a, b, c, d, e, f, g, h, i, j)] #