| Maintainer | Roman Cheplyaka <roma@ro-che.info> |
|---|---|
| Safe Haskell | Trustworthy |
Test.SmallCheck.Series
Contents
Description
You need this module if you want to generate test values of your own types.
You'll typically need the following extensions:
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} SmallCheck itself defines data generators for all the data types used by the Prelude.
In order to generate values and functions of your own types, you need to make them instances of Serial (for values) and CoSerial (for functions). There are two main ways to do so: using Generics or writing the instances by hand.
- cons0 :: a -> Series m a
- cons1 :: Serial m a => (a -> b) -> Series m b
- cons2 :: (Serial m a, Serial m b) => (a -> b -> c) -> Series m c
- cons3 :: (Serial m a, Serial m b, Serial m c) => (a -> b -> c -> d) -> Series m d
- cons4 :: (Serial m a, Serial m b, Serial m c, Serial m d) => (a -> b -> c -> d -> e) -> Series m e
- newtypeCons :: Serial m a => (a -> b) -> Series m b
- alts0 :: Series m a -> Series m a
- alts1 :: CoSerial m a => Series m b -> Series m (a -> b)
- alts2 :: (CoSerial m a, CoSerial m b) => Series m c -> Series m (a -> b -> c)
- alts3 :: (CoSerial m a, CoSerial m b, CoSerial m c) => Series m d -> Series m (a -> b -> c -> d)
- alts4 :: (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) => Series m e -> Series m (a -> b -> c -> d -> e)
- newtypeAlts :: CoSerial m a => Series m b -> Series m (a -> b)
- type Depth = Int
- data Series m a
- class Monad m => Serial m a where
- class Monad m => CoSerial m a where
- newtype Positive a = Positive {
- getPositive :: a
- newtype NonNegative a = NonNegative {
- getNonNegative :: a
- newtype NonEmpty a = NonEmpty {
- getNonEmpty :: [a]
- (\/) :: Monad m => Series m a -> Series m a -> Series m a
- (><) :: Monad m => Series m a -> Series m b -> Series m (a, b)
- (<~>) :: Monad m => Series m (a -> b) -> Series m a -> Series m b
- (>>-) :: MonadLogic m => forall a b. m a -> (a -> m b) -> m b
- localDepth :: (Depth -> Depth) -> Series m a -> Series m a
- decDepth :: Series m a -> Series m a
- getDepth :: Series m Depth
- generate :: (Depth -> [a]) -> Series m a
- list :: Depth -> Series Identity a -> [a]
- listM :: Monad m => Depth -> Series m a -> m [a]
- fixDepth :: Series m a -> Series m (Series m a)
- decDepthChecked :: Series m a -> Series m a -> Series m a
- constM :: Monad m => m b -> m (a -> b)
Generic instances
The easiest way to create the necessary instances is to use GHC generics (available starting with GHC 7.2.1).
Here's a complete example:
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} {-# LANGUAGE DeriveGeneric #-} import Test.SmallCheck.Series import GHC.Generics data Tree a = Null | Fork (Tree a) a (Tree a) deriving Generic instance Serial m a => Serial m (Tree a) Here we enable the DeriveGeneric extension which allows to derive Generic instance for our data type. Then we declare that Tree a is an instance of Serial, but do not provide any definitions. This causes GHC to use the default definitions that use the Generic instance.
One minor limitation of generic instances is that there's currently no way to distinguish newtypes and datatypes. Thus, newtype constructors will also count as one level of depth.
Data Generators
Writing Serial instances for application-specific types is straightforward. You need to define a series generator, typically using consN family of generic combinators where N is constructor arity.
For example:
data Tree a = Null | Fork (Tree a) a (Tree a) instance Serial m a => Serial m (Tree a) where series = cons0 Null \/ cons3 Fork
For newtypes use newtypeCons instead of cons1. The difference is that cons1 is counts as one level of depth, while newtypeCons doesn't affect the depth.
newtype Light a = Light a instance Serial m a => Serial m (Light a) where series = newtypeCons Light
For data types with more than 4 fields define consN as
consN f = decDepth $ f <$> series <~> series <~> series <~> ... {- series repeated N times in total -} What does consN do, exactly?
consN has type (Serial t_1, ..., Serial t_N) => (t_1 -> ... -> t_N -> t) -> Series t.
consN f is a series which, for a given depth d > 0, produces values of the form
f x_1 ... x_N
where x_i ranges over all values of type t_i of depth up to d-1 (as defined by the series functions for t_i).
consN functions also ensure that x_i are enumerated in the breadth-first order. Thus, combinations of smaller depth come first (assuming the same is true for t_i).
If d <= 0, no values are produced.
cons4 :: (Serial m a, Serial m b, Serial m c, Serial m d) => (a -> b -> c -> d -> e) -> Series m eSource
newtypeCons :: Serial m a => (a -> b) -> Series m bSource
Same as cons1, but preserves the depth.
Function Generators
To generate functions of an application-specific argument type, make the type an instance of CoSerial.
Again there is a standard pattern, this time using the altsN combinators where again N is constructor arity. Here are Tree and Light instances:
instance CoSerial m a => CoSerial m (Tree a) where coseries rs = alts0 rs >>- \z -> alts3 rs >>- \f -> return $ \t -> case t of Null -> z Fork t1 x t2 -> f t1 x t2
instance CoSerial m a => CoSerial m (Light a) where coseries rs = newtypeAlts rs >>- \f -> return $ \l -> case l of Light x -> f x
For data types with more than 4 fields define altsN as
altsN rs = do rs <- fixDepth rs decDepthChecked (constM $ constM $ ... $ constM rs) (coseries $ coseries $ ... $ coseries rs) {- constM and coseries are repeated N times each -} What does altsN do, exactly?
altsN has type (Serial t_1, ..., Serial t_N) => Series t -> Series (t_1 -> ... -> t_N -> t).
altsN s is a series which, for a given depth d, produces functions of type
t_1 -> ... -> t_N -> t
If d <= 0, these are constant functions, one for each value produced by s.
If d > 0, these functions inspect each of their arguments up to the depth d-1 (as defined by the coseries functions for the corresponding types) and return values produced by s. The depth to which the values are enumerated does not depend on the depth of inspection.
alts3 :: (CoSerial m a, CoSerial m b, CoSerial m c) => Series m d -> Series m (a -> b -> c -> d)Source
alts4 :: (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) => Series m e -> Series m (a -> b -> c -> d -> e)Source
newtypeAlts :: CoSerial m a => Series m b -> Series m (a -> b)Source
Same as alts1, but preserves the depth.
Basic definitions
Maximum depth of generated test values.
For data values, it is the depth of nested constructor applications.
For functional values, it is both the depth of nested case analysis and the depth of results.
Series is a MonadLogic action that enumerates values of a certain type, up to some depth.
The depth bound is tracked in the SC monad and can be extracted using getDepth and changed using localDepth.
To manipulate series at the lowest level you can use its Monad, MonadPlus and MonadLogic instances. This module provides some higher-level combinators which simplify creating series.
A proper Series should be monotonic with respect to the depth — i.e. localDepth (+1) s should emit all the values that s emits (and possibly some more).
It is also desirable that values of smaller depth come before the values of greater depth.
Instances
| MonadTrans Series | |
| Monad (Series m) | |
| Functor (Series m) | |
| MonadPlus (Series m) | |
| Applicative (Series m) | |
| Alternative (Series m) | |
| Monad m => MonadLogic (Series m) |
class Monad m => Serial m a whereSource
Instances
| Monad m => Serial m Bool | |
| Monad m => Serial m Char | |
| Monad m => Serial m Double | |
| Monad m => Serial m Float | |
| Monad m => Serial m Integer | |
| Monad m => Serial m Int | |
| Monad m => Serial m () | |
| Serial m a => Serial m (NonEmpty a) | |
| (Num a, Ord a, Serial m a) => Serial m (NonNegative a) | |
| (Num a, Ord a, Serial m a) => Serial m (Positive a) | |
| Serial m a => Serial m [a] | |
| Serial m a => Serial m (Maybe a) | |
| (Integral i, Serial m i) => Serial m (Ratio i) | |
| (CoSerial m a, Serial m b) => Serial m (a -> b) | |
| (Serial m a, Serial m b) => Serial m (Either a b) | |
| (Serial m a, Serial m b) => Serial m (a, b) | |
| (Serial m a, Serial m b, Serial m c) => Serial m (a, b, c) | |
| (Serial m a, Serial m b, Serial m c, Serial m d) => Serial m (a, b, c, d) |
class Monad m => CoSerial m a whereSource
Methods
coseries :: Series m b -> Series m (a -> b)Source
A proper coseries implementation should pass the depth unchanged to its first argument. Doing otherwise will make enumeration of curried functions non-uniform in their arguments.
Instances
| Monad m => CoSerial m Bool | |
| Monad m => CoSerial m Char | |
| Monad m => CoSerial m Double | |
| Monad m => CoSerial m Float | |
| Monad m => CoSerial m Integer | |
| Monad m => CoSerial m Int | |
| Monad m => CoSerial m () | |
| CoSerial m a => CoSerial m [a] | |
| CoSerial m a => CoSerial m (Maybe a) | |
| (Integral i, CoSerial m i) => CoSerial m (Ratio i) | |
| (Serial m a, CoSerial m a, Serial m b, CoSerial m b) => CoSerial m (a -> b) | |
| (CoSerial m a, CoSerial m b) => CoSerial m (Either a b) | |
| (CoSerial m a, CoSerial m b) => CoSerial m (a, b) | |
| (CoSerial m a, CoSerial m b, CoSerial m c) => CoSerial m (a, b, c) | |
| (CoSerial m a, CoSerial m b, CoSerial m c, CoSerial m d) => CoSerial m (a, b, c, d) |
Convenient wrappers
Positive x: guarantees that x > 0.
Constructors
| Positive | |
Fields
| |
newtype NonNegative a Source
NonNegative x: guarantees that x >= 0.
Constructors
| NonNegative | |
Fields
| |
Instances
| (Num a, Ord a, Serial m a) => Serial m (NonNegative a) | |
| Enum a => Enum (NonNegative a) | |
| Eq a => Eq (NonNegative a) | |
| Integral a => Integral (NonNegative a) | |
| Num a => Num (NonNegative a) | |
| Ord a => Ord (NonNegative a) | |
| Real a => Real (NonNegative a) | |
| Show a => Show (NonNegative a) |
NonEmpty xs: guarantees that xs is not null
Constructors
| NonEmpty | |
Fields
| |
Other useful definitions
(>>-) :: MonadLogic m => forall a b. m a -> (a -> m b) -> m b
Fair conjunction. Similarly to the previous function, consider the distributivity law for MonadPlus:
(mplus a b) >>= k = (a >>= k) `mplus` (b >>= k)
If 'a >>= k' can backtrack arbitrarily many tmes, (b >>= k) may never be considered. (>>-) takes similar care to consider both branches of a disjunctive computation.
generate :: (Depth -> [a]) -> Series m aSource
A simple series specified by a function from depth to the list of values up to that depth.
fixDepth :: Series m a -> Series m (Series m a)Source
Fix the depth of a series at the current level. The resulting series will no longer depend on the "ambient" depth.
decDepthChecked :: Series m a -> Series m a -> Series m aSource
If the current depth is 0, evaluate the first argument. Otherwise, evaluate the second argument with decremented depth.