testing-feat-0.4: Functional Enumeration of Abstract Types

Safe HaskellNone

Test.Feat.Class

Contents

Description

Everything you need to construct an enumeration for an algebraic type. Just define each constructor using pure for nullary constructors and unary and funcurry for positive arity constructors, then combine the constructors with consts. Example:

  instance Enumerable a => Enumerable [a] where
    enumerate = consts [unary (funcurry (:)), pure []]

There's also a handy Template Haskell function for automatic derivation.

Synopsis

Documentation

class Typeable a => Enumerable a whereSource

A class of functionally enumerable types

Methods

enumerate :: Enumerate aSource

This is the interface for defining an instance. When combining enumerations use shared instead and when accessing the data of enumerations use optimal.

Instances

Enumerable Bool 
Enumerable Char

Contains only ASCII characters

Enumerable Double

Not injective

Enumerable Float

Not injective

Enumerable Int 
Enumerable Int8 
Enumerable Int16 
Enumerable Int32 
Enumerable Int64 
Enumerable Integer 
Enumerable Ordering 
Enumerable Word 
Enumerable Word8 
Enumerable Word16 
Enumerable Word32 
Enumerable Word64 
Enumerable () 
Enumerable Printable 
Enumerable Unicode 
(Typeable [a0], Enumerable a0) => Enumerable [a0] 
(Typeable (Ratio a), Infinite a, Enumerable a) => Enumerable (Ratio a)

Not injective

(Typeable (Maybe a0), Enumerable a0) => Enumerable (Maybe a0) 
(Typeable (NonZero a), Infinite a, Enumerable a) => Enumerable (NonZero a) 
(Typeable (Nat a), Infinite a) => Enumerable (Nat a) 
(Typeable (NonEmpty a), Enumerable a) => Enumerable (NonEmpty a) 
(Typeable (Either a0 b0), Enumerable a0, Enumerable b0) => Enumerable (Either a0 b0) 
(Typeable (a0, b0), Enumerable a0, Enumerable b0) => Enumerable (a0, b0) 
(Typeable (FreePair a b), Enumerable a, Enumerable b) => Enumerable (FreePair a b) 
(Typeable (a0, b0, c0), Enumerable a0, Enumerable b0, Enumerable c0) => Enumerable (a0, b0, c0) 
(Typeable (a0, b0, c0, d0), Enumerable a0, Enumerable b0, Enumerable c0, Enumerable d0) => Enumerable (a0, b0, c0, d0) 
(Typeable (a0, b0, c0, d0, e0), Enumerable a0, Enumerable b0, Enumerable c0, Enumerable d0, Enumerable e0) => Enumerable (a0, b0, c0, d0, e0) 
(Typeable (a0, b0, c0, d0, e0, f0), Enumerable a0, Enumerable b0, Enumerable c0, Enumerable d0, Enumerable e0, Enumerable f0) => Enumerable (a0, b0, c0, d0, e0, f0) 
(Typeable (a0, b0, c0, d0, e0, f0, g0), Enumerable a0, Enumerable b0, Enumerable c0, Enumerable d0, Enumerable e0, Enumerable f0, Enumerable g0) => Enumerable (a0, b0, c0, d0, e0, f0, g0) 

Building instances

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.

Accessing the enumerator of an instance

shared :: Enumerable a => Enumerate aSource

Version of enumerate that ensures that the enumeration is shared between all accesses. Should always be used when combining enumerations.

optimal :: Enumerable a => Enumerate aSource

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

Free pairs

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

Deriving instances with template Haskell

deriveEnumerable :: Name -> Q [Dec]Source

Derive an instance of Enumberable with Template Haskell. To derive an instance for Enumerable A, just put this as a top level declaration in your module (with the TemplateHaskell extension enabled):

   deriveEnumerable ''A

deriveEnumerable' :: ConstructorDeriv -> Q [Dec]Source

Derive an instance of Enumberable with Template Haskell, with rules for some specific constructors