smallcheck-0.6.1: A property-based testing library

MaintainerRoman Cheplyaka <roma@ro-che.info>
Safe HaskellSafe-Infered

Test.SmallCheck.Series

Contents

Description

Generation of test data.

Synopsis

Basic definitions

type Depth = IntSource

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.

type Series a = Depth -> [a]Source

Series is a function from the depth to a finite list of values.

If s is a Series, s n is expected to yield values of depth up to n.

(In particular, series d is expected to be a subset of series (d+1).)

class Serial a whereSource

Methods

series :: Series aSource

coseries :: Series b -> Series (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

Serial Bool 
Serial Char 
Serial Double 
Serial Float 
Serial Int 
Serial Integer 
Serial () 
Serial a => Serial [a] 
Serial a => Serial (Maybe a) 
(Integral a, Serial a) => Serial (N a) 
(Serial a, Serial b) => Serial (a -> b) 
(Serial a, Serial b) => Serial (Either a b) 
(Serial a, Serial b) => Serial (a, b) 
(Serial a, Serial b, Serial c) => Serial (a, b, c) 
(Serial a, Serial b, Serial c, Serial d) => Serial (a, b, c, d) 

Data Generators

SmallCheck itself defines data generators for all the data types used by the Prelude.

Writing SmallCheck generators 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 a => Serial (Tree a) where
  series = cons0 Null \/ cons3 Fork

The default interpretation of depth for datatypes is the depth of nested construction: constructor functions, including those for newtypes, build results with depth one greater than their deepest argument. But this default can be over-ridden by composing a consN application with an application of depth, like this:

newtype Light a = Light a

instance Serial a => Serial (Light a) where
  series = cons1 Light . depth 0

The depth of Light x is just the depth of x.

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).

If d <= 0, no values are produced.

cons1 :: Serial a => (a -> b) -> Series bSource

cons2 :: (Serial a, Serial b) => (a -> b -> c) -> Series cSource

cons3 :: (Serial a, Serial b, Serial c) => (a -> b -> c -> d) -> Series dSource

cons4 :: (Serial a, Serial b, Serial c, Serial d) => (a -> b -> c -> d -> e) -> Series eSource

Function Generators

To generate functions of an application-specific argument type requires a second method coseries. Again there is a standard pattern, this time using the altsN combinators where again N is constructor arity. Here are Tree and Light instances:

coseries rs d = [ \t -> case t of
                        Null         -> z
                        Fork t1 x t2 -> f t1 x t2
                |  z <- alts0 rs d ,
                   f <- alts3 rs d ]

coseries rs d = [ \l -> case l of
                        Light x -> f x
                |  f <- (alts1 rs . depth 0) d ]

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 of s 0.

If d > 0, these functions inspect each of their arguments up to depth d-1 (as defined by the coseries functions for the corresponding types) and return values given by s d.

alts1 :: Serial a => Series b -> Series (a -> b)Source

alts2 :: (Serial a, Serial b) => Series c -> Series (a -> b -> c)Source

alts3 :: (Serial a, Serial b, Serial c) => Series d -> Series (a -> b -> c -> d)Source

alts4 :: (Serial a, Serial b, Serial c, Serial d) => Series e -> Series (a -> b -> c -> d -> e)Source

Automated Derivation of Generators

For small examples, Series instances are easy enough to define by hand, following the above patterns. But for programs with many or large data type definitions, automatic derivation using a tool such as "derive" is a better option. For example, the following command-line appends to Prog.hs the Series instances for all data types defined there.

$ derive Prog.hs -d Serial --append

Using GHC Generics

For GHC users starting from GHC 7.2.1 there's also an option to use GHC's Generics to get Serial instance for free.

Example:

{-# LANGUAGE DeriveGeneric #-}
import Test.SmallCheck
import GHC.Generics

data Tree a = Null | Fork (Tree a) a (Tree a)
    deriving Generic
instance Serial a => Serial (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.

Other useful definitions

(\/) :: Series a -> Series a -> Series aSource

Sum (union) of series

(><) :: Series a -> Series b -> Series (a, b)Source

Product of series

newtype N a Source

N is a wrapper for Integral types that causes only non-negative values to be generated. Generated functions of type N a -> b do not distinguish different negative values of a.

See also Nat and Natural.

Constructors

N a 

Instances

Eq a => Eq (N a) 
Ord a => Ord (N a) 
Show a => Show (N a) 
(Integral a, Serial a) => Serial (N a) 

type Nat = N IntSource

depth :: Depth -> Depth -> DepthSource

For customising the depth measure. Use with care!