smartcheck-0.2.4: A smarter QuickCheck.

Safe HaskellSafe
LanguageHaskell2010

Test.SmartCheck

Contents

Description

Interface module.

Synopsis

Main SmartCheck interface.

smartCheck :: (SubTypes a, Generic a, ConNames (Rep a), Testable prop) => ScArgs -> (a -> prop) -> IO () Source #

Main interface function.

User-suppplied counterexample interface.

smartCheckInput :: forall a prop. (SubTypes a, Generic a, ConNames (Rep a), Testable prop, Read a) => ScArgs -> (a -> prop) -> IO () Source #

Run QuickCheck and get a result.

runQC :: forall a prop. (Show a, Arbitrary a, Testable prop) => Args -> (a -> prop) -> IO (Maybe a, a -> Property) Source #

Run QuickCheck, to get a counterexamples for each argument, including the one we want to focus on for SmartCheck, which is the first argument. That argument is never shrunk by QuickCheck, but others may be shrunk by QuickCheck. Returns the value (if it exists) and a Property (by applying the property method to the Testable value). In each iteration of runQC, non-SmartCheck arguments are not necessarily held constant

Arguments

Main type class based on Generics.

class (Arbitrary a, Show a, Typeable a) => SubTypes a where Source #

This class covers algebraic datatypes that can be transformed into Trees. subTypes is the main method, placing values into trees.

for a datatype with constructors A and C,

subTypes (A (C 0) 1)
[Node {rootLabel = C 0, subForest = []}]

Methods

subTypes :: a -> Forest SubT Source #

Turns algebraic data into a forest representation.

subTypes :: (Generic a, GST (Rep a)) => a -> Forest SubT Source #

Turns algebraic data into a forest representation.

baseType :: a -> Bool Source #

Base types (e.g., Int, Char) aren't analyzed.

replaceChild :: Typeable b => a -> Forest Subst -> b -> Maybe a Source #

Generically replace child i in m with value s. A total function: returns Nothing if you try to replace a child with an ill-typed child s. (Returns Just (the original data) if your index is out of bounds).

replaceChild :: (Generic a, GST (Rep a), Typeable b) => a -> Forest Subst -> b -> Maybe a Source #

Generically replace child i in m with value s. A total function: returns Nothing if you try to replace a child with an ill-typed child s. (Returns Just (the original data) if your index is out of bounds).

toConstr :: a -> String Source #

Get the string representation of the constructor.

toConstr :: (Generic a, GST (Rep a)) => a -> String Source #

Get the string representation of the constructor.

showForest :: a -> Forest String Source #

showForest generically shows a value while preserving its structure (in a Tree). Always returns either a singleton list containing the tree (a degenerate forest) or an empty list for baseTypes. An invariant is that the shape of the tree produced by showForest is the same as the one produced by subTypes.

showForest :: (Generic a, GST (Rep a)) => a -> Forest String Source #

showForest generically shows a value while preserving its structure (in a Tree). Always returns either a singleton list containing the tree (a degenerate forest) or an empty list for baseTypes. An invariant is that the shape of the tree produced by showForest is the same as the one produced by subTypes.

Instances

SubTypes Bool Source # 
SubTypes Char Source # 
SubTypes Double Source # 
SubTypes Float Source # 
SubTypes Int Source # 
SubTypes Int8 Source # 
SubTypes Int16 Source # 
SubTypes Int32 Source # 
SubTypes Int64 Source # 
SubTypes Integer Source # 
SubTypes Word Source # 
SubTypes Word8 Source # 
SubTypes Word16 Source # 
SubTypes Word32 Source # 
SubTypes Word64 Source # 
SubTypes () Source # 
(Arbitrary a, SubTypes a, Typeable * a) => SubTypes [a] Source # 

Methods

subTypes :: [a] -> Forest SubT Source #

baseType :: [a] -> Bool Source #

replaceChild :: Typeable * b => [a] -> Forest Subst -> b -> Maybe [a] Source #

toConstr :: [a] -> String Source #

showForest :: [a] -> Forest String Source #

(Arbitrary a, SubTypes a, Typeable * a) => SubTypes (Maybe a) Source # 
(Integral a, Arbitrary a, SubTypes a, Typeable * a) => SubTypes (Ratio a) Source # 
(RealFloat a, Arbitrary a, SubTypes a, Typeable * a) => SubTypes (Complex a) Source # 
(Arbitrary a, SubTypes a, Typeable * a, Arbitrary b, SubTypes b, Typeable * b) => SubTypes (Either a b) Source # 
(Arbitrary a, SubTypes a, Typeable * a, Arbitrary b, SubTypes b, Typeable * b) => SubTypes (a, b) Source # 

Methods

subTypes :: (a, b) -> Forest SubT Source #

baseType :: (a, b) -> Bool Source #

replaceChild :: Typeable * b => (a, b) -> Forest Subst -> b -> Maybe (a, b) Source #

toConstr :: (a, b) -> String Source #

showForest :: (a, b) -> Forest String Source #

(Arbitrary a, SubTypes a, Typeable * a, Arbitrary b, SubTypes b, Typeable * b, Arbitrary c, SubTypes c, Typeable * c) => SubTypes (a, b, c) Source # 

Methods

subTypes :: (a, b, c) -> Forest SubT Source #

baseType :: (a, b, c) -> Bool Source #

replaceChild :: Typeable * b => (a, b, c) -> Forest Subst -> b -> Maybe (a, b, c) Source #

toConstr :: (a, b, c) -> String Source #

showForest :: (a, b, c) -> Forest String Source #

(Arbitrary a, SubTypes a, Typeable * a, Arbitrary b, SubTypes b, Typeable * b, Arbitrary c, SubTypes c, Typeable * c, Arbitrary d, SubTypes d, Typeable * d) => SubTypes (a, b, c, d) Source # 

Methods

subTypes :: (a, b, c, d) -> Forest SubT Source #

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

replaceChild :: Typeable * b => (a, b, c, d) -> Forest Subst -> b -> Maybe (a, b, c, d) Source #

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

showForest :: (a, b, c, d) -> Forest String Source #

(Arbitrary a, SubTypes a, Typeable * a, Arbitrary b, SubTypes b, Typeable * b, Arbitrary c, SubTypes c, Typeable * c, Arbitrary d, SubTypes d, Typeable * d, Arbitrary e, SubTypes e, Typeable * e) => SubTypes (a, b, c, d, e) Source # 

Methods

subTypes :: (a, b, c, d, e) -> Forest SubT Source #

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

replaceChild :: Typeable * b => (a, b, c, d, e) -> Forest Subst -> b -> Maybe (a, b, c, d, e) Source #

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

showForest :: (a, b, c, d, e) -> Forest String Source #

For constructing new instances of SubTypes

gst :: GST f => f a -> Forest SubT Source #

grc :: (GST f, Typeable b) => f a -> Forest Subst -> b -> Maybe (f a) Source #

gtc :: GST f => f a -> String Source #

gsf :: GST f => f a -> Forest String Source #