smartcheck-0.1: A smarter QuickCheck.

Safe HaskellNone

Test.SmartCheck

Contents

Description

Interface module.

Synopsis

Main interface function.

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

Main interface function.

Type of SmartCheck properties.

data ScProperty Source

Type for SmartCheck properties. Moral equivalent of QuickCheck's Property type.

Implication for SmartCheck properties.

(-->) :: Bool -> Bool -> ScPropertySource

Moral equivalent of QuickCheck's ==> operator.

Run QuickCheck and get a result.

runQCInit :: (Show a, Read a, Arbitrary a, ScProp prop, Testable prop) => Args -> (a -> prop) -> IO (Maybe a, a -> Property)Source

Run QuickCheck initially, to get counterexamples for each argument, includding the one we want to focus on for SmartCheck, plus a Property.

Arguments

Main type class based on Generics.

class (Arbitrary a, Show a, Typeable a) => SubTypes a whereSource

This class covers algebraic datatypes that can be transformed into Trees. subTypes is the main method, placing values into trees. For types that can't be put into a *structural* order (e.g., Int), we don't want SmartCheck to touch them, so that aren't placed in the tree (the baseType method tells subTypes which types have this property).

for a datatype with constructors A and C,

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

Methods

subTypes :: a -> Forest SubTSource

baseType :: a -> BoolSource

replaceChild :: Typeable b => a -> Forest Subst -> b -> Maybe aSource

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 -> StringSource

showForest :: a -> Forest StringSource

showForest generically shows a value while preserving its structure (in a Tree). You should always end up with either a singleton list containing the tree or an empty list for baseTypes. Also, it must be the case that for a value v,

null (subTypes v) iff null (showForest v) and if not . null (subTypes v), then subForest . head (showForest v) has the same structure as subTypes v.

We can't just return a Tree String or Maybe (Tree String). The reason is that in generically constructing the value, we have to deal with product types. There is no sane way to join them other than list-like concatenation (i.e., gsf (a :*: b) = gsf a ++ gsf b).

For constructing new instances of SubTypes

gst :: GST f => f a -> Forest SubTSource

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

gtc :: GST f => f a -> StringSource

gsf :: GST f => f a -> Forest StringSource

gsz :: GST f => f a -> IntSource