testing-feat-0.1: Functional enumeration for systematic and random testing

Safe HaskellSafe-Infered

Test.Feat

Contents

Synopsis

Documentation

data Enumerate a Source

A functional enumeration of type t is a partition of t into finite numbered sets called Parts. The number that identifies each part is called the cost of the values in that part.

Constructors

Enumerate 

Fields

card :: Part -> Index

Computes the cardinality of a given part.

select :: Part -> Index -> a

Selects a value from the enumeration For select e p i, i should be less than card e p

optimal :: Sharing Tag (Enumerate a)

A self-optimising function.

Instances

Functor Enumerate

Only use fmap with bijective functions (e.g. data constructors)

Typeable1 Enumerate 
Applicative Enumerate

* corresponds to product (as with lists)

Monoid (Enumerate a)

mappend = union

The type class

class Typeable a => Enumerable a whereSource

A class of functionally enumerable types

Methods

enumerate :: Enumerate aSource

This is the interface for defining an instance. Memoisation needs to be ensured e.g. using mempay but sharing is handled automatically by the default implementation of shared.

shared :: Enumerate aSource

Version of enumerate that ensures it is shared between all accessing functions. Should alwasy be used when combining enumerations. Should typically be left to default behaviour.

nullary :: a -> Constructor aSource

For nullary constructors such as True and [].

unary :: Enumerable a => (a -> b) -> Constructor bSource

For any non-nullary constructor. Apply funcurry until the type of the result is unary (i.e. n-1 times where n is the number of fields of the constructor).

funcurry :: (a -> b -> c) -> FreePair a b -> cSource

Uncurry a function (typically a constructor) to a function on free pairs.

consts :: [Constructor a] -> Enumerate aSource

Produces the enumeration of a type given the enumerators for each of its constructors. The result of unary should typically not be used directly in an instance even if it only has one constructor. So you should apply consts even in that case.

deriveEnumerable :: Name -> Q [Dec]Source

Derive an instance of Enumberable with Template Haskell.

newtype FreePair a b Source

A free pair constructor. The cost of constructing a free pair is equal to the sum of the costs of its components.

Constructors

Free 

Fields

free :: (a, b)
 

Instances

Accessing data

optimised :: Enumerable a => Enumerate aSource

An optimised version of enumerate. Used by all library functions that access enumerated values (but not by combining functions). Library functions should ensure that optimised is not reevaluated.

index :: Enumerate a -> Integer -> aSource

Mainly as a proof of concept we can use the isomorphism between natural numbers and (Part,Index) pairs to index into a type May not terminate for finite types. Might be slow the first time it is used with a specific enumeration because cardinalities need to be calculated. The computation complexity after cardinalities are computed is a polynomial of the size of the resulting value.

values :: Enumerable a => [(Integer, [a])]Source

All values of the enumeration by increasing cost (which is the number of constructors for most types). Also contains the cardinality of each list.

bounded :: Enumerable a => Integer -> [(Integer, [a])]Source

A version of vales that has a limited number of values in each inner list. If the list corresponds to a Part which is larger than the bound it evenly intersperses the values across the enumeration of the Part.

uniform :: Enumerable a => Int -> Gen aSource

Compatability with QuickCheck. Distribution is uniform generator over values bounded by the given size. Typical use: sized uniform.

ioAll :: Enumerable a => (a -> IO ()) -> IO ()Source

ioAll = ioFeat values

ioBounded :: Enumerable a => Integer -> (a -> IO ()) -> IO ()Source

ioBounded n = ioFeat (bounded n)