Safe Haskell | None |
---|
Functions for constructing and analysing signatures.
- class Signature a where
- data Sig = Sig {}
- maxDepth :: Sig -> Int
- maxSize :: Sig -> Int
- updateDepth :: Int -> Sig -> Sig
- updateSize :: Int -> Sig -> Sig
- minTests :: Sig -> Int
- maxQuickCheckSize :: Sig -> Int
- data Used = Used Witness [Symbol]
- uses :: Sig -> Witness -> Used
- data Summary = Summary {
- summaryFunctions :: [Symbol]
- summaryBackground :: [Symbol]
- summaryVariables :: [Symbol]
- summaryObserved :: [TypeRep]
- summaryUninhabited :: [Used]
- summaryNoVars :: [TypeRep]
- summaryUntestable :: [TypeRep]
- summaryDepth :: Maybe Int
- summarySize :: Maybe Int
- summaryTests :: Maybe Int
- summaryQuickCheckSize :: Maybe Int
- sigToHaskell :: Signature a => a -> String
- summarise :: Sig -> Summary
- data Observer a = forall b . Ord b => Observer (PGen (a -> b))
- observe :: Typeable a => a -> Sig -> Observer a
- emptySig :: Sig
- constantSig :: Typeable a => Constant a -> Sig
- variableSig :: forall a. Typeable a => [Variable a] -> Sig
- totalSig :: forall a. Typeable a => Gen a -> Sig
- partialSig :: forall a. Typeable a => Gen a -> Sig
- observerSig :: forall a. Typeable a => Observer a -> Sig
- typeSig :: Typeable a => a -> Sig
- ordSig :: Typeable a => Observer a -> Sig
- withDepth :: Int -> Sig
- withSize :: Int -> Sig
- withTests :: Int -> Sig
- withQuickCheckSize :: Int -> Sig
- without :: Signature a => a -> [String] -> Sig
- undefinedSig :: forall a. Typeable a => String -> a -> Sig
- primCon0 :: forall a. Typeable a => Int -> String -> a -> Sig
- primCon1 :: forall a b. (Typeable a, Typeable b) => Int -> String -> (a -> b) -> Sig
- primCon2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => Int -> String -> (a -> b -> c) -> Sig
- primCon3 :: forall a b c d. (Typeable a, Typeable b, Typeable c, Typeable d) => Int -> String -> (a -> b -> c -> d) -> Sig
- primCon4 :: forall a b c d e. (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Int -> String -> (a -> b -> c -> d -> e) -> Sig
- 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) -> Sig
- blind0 :: forall a. Typeable a => String -> a -> Sig
- blind1 :: forall a b. (Typeable a, Typeable b) => String -> (a -> b) -> Sig
- blind2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => String -> (a -> b -> c) -> Sig
- blind3 :: forall a b c d. (Typeable a, Typeable b, Typeable c, Typeable d) => String -> (a -> b -> c -> d) -> Sig
- blind4 :: forall a b c d e. (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => String -> (a -> b -> c -> d -> e) -> Sig
- 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) -> Sig
- ord :: (Ord a, Typeable a) => a -> Sig
- observing :: Observer a -> a -> Observer a
- background :: Signature a => a -> Sig
- primVars0 :: forall a. Typeable a => Int -> [(String, PGen a)] -> Sig
- primVars1 :: forall a b. (Typeable a, Typeable b) => Int -> [(String, PGen (a -> b))] -> Sig
- primVars2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => Int -> [(String, PGen (a -> b -> c))] -> Sig
- gvars :: forall a. Typeable a => [String] -> Gen a -> Sig
- gvars0 :: forall a. Typeable a => [String] -> Gen a -> Sig
- gvars1 :: forall a b. (Typeable a, Typeable b) => [String] -> Gen (a -> b) -> Sig
- gvars2 :: forall a b c. (Typeable a, Typeable b, Typeable c) => [String] -> Gen (a -> b -> c) -> Sig
- gvars' :: forall a. Typeable a => [(String, Gen a)] -> Sig
- vars :: forall a. (Arbitrary a, Typeable a) => [String] -> a -> Sig
- vars0 :: forall a. (Arbitrary a, Typeable a) => [String] -> a -> Sig
- vars1 :: forall a b. (CoArbitrary a, Typeable a, Arbitrary b, Typeable b) => [String] -> (a -> b) -> Sig
- vars2 :: forall a b c. (CoArbitrary a, Typeable a, CoArbitrary b, Typeable b, Arbitrary c, Typeable c) => [String] -> (a -> b -> c) -> Sig
- con :: (Ord a, Typeable a) => String -> a -> Sig
- fun0 :: (Ord a, Typeable a) => String -> a -> Sig
- fun1 :: (Typeable a, Typeable b, Ord b) => String -> (a -> b) -> Sig
- fun2 :: (Typeable a, Typeable b, Typeable c, Ord c) => String -> (a -> b -> c) -> Sig
- fun3 :: (Typeable a, Typeable b, Typeable c, Typeable d, Ord d) => String -> (a -> b -> c -> d) -> Sig
- fun4 :: (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Ord e) => String -> (a -> b -> c -> d -> e) -> Sig
- fun5 :: (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, Ord f) => String -> (a -> b -> c -> d -> e -> f) -> Sig
- observer1 :: (Typeable a, Typeable b, Ord b) => (a -> b) -> Sig
- observer2 :: (Arbitrary a, Typeable a, Typeable b, Typeable c, Ord c) => (a -> b -> c) -> Sig
- observer3 :: (Arbitrary a, Arbitrary b, Typeable a, Typeable b, Typeable c, Typeable d, Ord d) => (a -> b -> c -> d) -> Sig
- observer4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Ord e) => (a -> b -> c -> d -> e) -> Sig
- testable :: Typeable a => Sig -> a -> Bool
- constantApplications :: forall a. Typeable a => Sig -> Constant a -> [Witness]
- constantArgs :: forall a. Typeable a => Sig -> Constant a -> [Witness]
- constantRes :: forall a. Typeable a => Sig -> Constant a -> Witness
- saturatedTypes :: Sig -> [Witness]
- inhabitedTypes :: Sig -> [Witness]
- argumentTypes :: Sig -> [Witness]
- variableTypes :: Sig -> [Witness]
- witnessArrow :: Typeable a => Sig -> a -> Maybe (Witness, Witness)
- lhsWitnesses :: Typeable a => Sig -> a -> [Witness]
- findWitness :: Sig -> TypeRep -> Witness
- lookupWitness :: Sig -> TypeRep -> Maybe Witness
- disambiguate :: Sig -> [Symbol] -> Symbol -> Symbol
- constantSymbols :: Sig -> [Symbol]
- symbols :: Sig -> [Symbol]
- variableSymbols :: Sig -> [Symbol]
Documentation
The class of things that can be used as a signature.
A signature.
updateDepth :: Int -> Sig -> SigSource
updateSize :: Int -> Sig -> SigSource
maxQuickCheckSize :: Sig -> IntSource
Summary | |
|
sigToHaskell :: Signature a => a -> StringSource
constantSig :: Typeable a => Constant a -> SigSource
variableSig :: forall a. Typeable a => [Variable a] -> SigSource
partialSig :: forall a. Typeable a => Gen a -> SigSource
observerSig :: forall a. Typeable a => Observer a -> SigSource
If withDepth n
is in your signature,
QuickSpec will consider terms of up to depth n
(the default is 3).
If withSize n
is in your signature,
QuickSpec will consider terms of up to size n
(the default is 100).
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
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
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.
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.
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)
.
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
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.
saturatedTypes :: Sig -> [Witness]Source
inhabitedTypes :: Sig -> [Witness]Source
argumentTypes :: Sig -> [Witness]Source
variableTypes :: Sig -> [Witness]Source
lhsWitnesses :: Typeable a => Sig -> a -> [Witness]Source
findWitness :: Sig -> TypeRep -> WitnessSource
constantSymbols :: Sig -> [Symbol]Source
variableSymbols :: Sig -> [Symbol]Source