quickspec-0.9.5: Equational laws for free

Safe HaskellNone

Test.QuickSpec.Signature

Description

Functions for constructing and analysing signatures.

Synopsis

Documentation

class Signature a whereSource

The class of things that can be used as a signature.

Methods

signature :: a -> SigSource

Instances

data Used Source

Constructors

Used Witness [Symbol] 

Instances

data Observer a Source

Constructors

forall b . Ord b => Observer (PGen (a -> b)) 

variableSig :: forall a. Typeable a => [Variable a] -> SigSource

totalSig :: forall a. Typeable a => Gen a -> SigSource

partialSig :: forall a. Typeable a => Gen a -> SigSource

observerSig :: forall a. Typeable a => Observer a -> SigSource

withDepth :: Int -> SigSource

If withDepth n is in your signature, QuickSpec will consider terms of up to depth n (the default is 3).

withSize :: Int -> SigSource

If withSize n is in your signature, QuickSpec will consider terms of up to size n (the default is 100).

withTests :: Int -> SigSource

If withTests n is in your signature, QuickSpec will run at least n tests (the default is 500).

withQuickCheckSize :: Int -> SigSource

If withQuickCheckSize n is in your signature, QuickSpec will generate test data of up to size n (the default is 20).

without :: Signature a => a -> [String] -> SigSource

sig `without` xs will remove the functions in xs from the signature sig. Useful when you want to use prelude but exclude some functions. Example: prelude (undefined :: A) `without` ["head", "tail"].

undefinedSig :: forall a. Typeable a => String -> a -> SigSource

primCon0 :: forall a. Typeable a => Int -> String -> a -> SigSource

primCon1 :: forall a b. (Typeable a, Typeable b) => Int -> String -> (a -> b) -> SigSource

primCon2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => Int -> String -> (a -> b -> c) -> SigSource

primCon3 :: forall a b c d. (Typeable a, Typeable b, Typeable c, Typeable d) => Int -> String -> (a -> b -> c -> d) -> SigSource

primCon4 :: forall a b c d e. (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Int -> String -> (a -> b -> c -> d -> e) -> SigSource

primCon5 :: forall a b c d e f. (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => Int -> String -> (a -> b -> c -> d -> e -> f) -> SigSource

blind0 :: forall a. Typeable a => String -> a -> SigSource

A constant.

blind1 :: forall a b. (Typeable a, Typeable b) => String -> (a -> b) -> SigSource

A unary function.

blind2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => String -> (a -> b -> c) -> SigSource

A binary function.

blind3 :: forall a b c d. (Typeable a, Typeable b, Typeable c, Typeable d) => String -> (a -> b -> c -> d) -> SigSource

A ternary function.

blind4 :: forall a b c d e. (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => String -> (a -> b -> c -> d -> e) -> SigSource

A function of arity 4.

blind5 :: forall a b c d e f. (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f) => String -> (a -> b -> c -> d -> e -> f) -> SigSource

A function of arity 5.

ord :: (Ord a, Typeable a) => a -> SigSource

background :: Signature a => a -> SigSource

Mark all the functions in a signature as background functions.

QuickSpec will only print a law if it contains at least one non-background function.

The functions in e.g. prelude are declared as background functions.

primVars0 :: forall a. Typeable a => Int -> [String] -> PGen a -> SigSource

primVars1 :: forall a b. (Typeable a, Typeable b) => Int -> [String] -> PGen (a -> b) -> SigSource

primVars2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => Int -> [String] -> PGen (a -> b -> c) -> SigSource

gvars :: forall a. Typeable a => [String] -> Gen a -> SigSource

Similar to vars, but takes a generator as a parameter.

gvars xs (arbitrary :: Gen a) is the same as vars xs (undefined :: a).

gvars0 :: forall a. Typeable a => [String] -> Gen a -> SigSource

Similar to vars, but takes a generator as a parameter.

gvars xs (arbitrary :: Gen a) is the same as vars xs (undefined :: a).

gvars1 :: forall a b. (Typeable a, Typeable b) => [String] -> Gen (a -> b) -> SigSource

gvars2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => [String] -> Gen (a -> b -> c) -> SigSource

vars :: forall a. (Arbitrary a, Typeable a) => [String] -> a -> SigSource

Declare a set of variables of a particular type.

For example, vars ["x","y","z"] (undefined :: Int) defines three variables, x, y and z, of type Int.

vars0 :: forall a. (Arbitrary a, Typeable a) => [String] -> a -> SigSource

Declare a set of variables of a particular type.

For example, vars ["x","y","z"] (undefined :: Int) defines three variables, x, y and z, of type Int.

vars1 :: forall a b. (CoArbitrary a, Typeable a, Arbitrary b, Typeable b) => [String] -> (a -> b) -> SigSource

vars2 :: forall a b c. (CoArbitrary a, Typeable a, CoArbitrary b, Typeable b, Arbitrary c, Typeable c) => [String] -> (a -> b -> c) -> SigSource

con :: (Ord a, Typeable a) => String -> a -> SigSource

A constant. The same as fun0.

fun0 :: (Ord a, Typeable a) => String -> a -> SigSource

A constant. The same as con.

fun1 :: (Typeable a, Typeable b, Ord b) => String -> (a -> b) -> SigSource

A unary function.

fun2 :: (Typeable a, Typeable b, Typeable c, Ord c) => String -> (a -> b -> c) -> SigSource

A binary function.

fun3 :: (Typeable a, Typeable b, Typeable c, Typeable d, Ord d) => String -> (a -> b -> c -> d) -> SigSource

A ternary function.

fun4 :: (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Ord e) => String -> (a -> b -> c -> d -> e) -> SigSource

A function of four arguments.

fun5 :: (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, Ord f) => String -> (a -> b -> c -> d -> e -> f) -> SigSource

A function of five arguments.

observer1 :: (Typeable a, Typeable b, Ord b) => (a -> b) -> SigSource

An observation function of arity 1.

observer2 :: (Arbitrary a, Typeable a, Typeable b, Typeable c, Ord c) => (a -> b -> c) -> SigSource

An observation function of arity 2.

observer3 :: (Arbitrary a, Arbitrary b, Typeable a, Typeable b, Typeable c, Typeable d, Ord d) => (a -> b -> c -> d) -> SigSource

An observation function of arity 3.

observer4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Ord e) => (a -> b -> c -> d -> e) -> SigSource

An observation function of arity 4.

constantArgs :: forall a. Typeable a => Sig -> Constant a -> [Witness]Source

constantRes :: forall a. Typeable a => Sig -> Constant a -> WitnessSource