size-based-0.1.0.0: Sized functors, for size-based enumerations

Safe HaskellNone
LanguageHaskell2010

Control.Enumerable

Contents

Description

This module provides the Enumerable class, which has a simple purpose: Provide any enumeration for any instance type. The prerequisite is that the enumeration data type is a sized functor (see Control.Sized) with the enumerated type as the type parameter. The general idea is that the size of a value is the number of constructor applications it contains.

Because Sized functors often rely of memoization, sharing is important. Since class dictionaries are not always shared, a mechanism is added that guarantees optimal sharing (it never creates two separate instance members for the same type). This is why the type of enumerate is Shared f a instead of simply f a. The technicalities of this memoization are not important, but it means there are two modes for accessing an enumeration: local and global. The former means sharing is guaranteed within this value, but subsequent calls to local may recreate dictionaries. The latter guarantees optimal sharing even between calls. It also means the enumeration will never be garbage collected, so use with care in programs that run for extended periods of time and contains many (especially non-regular) types.

Once a type has an instance, it can be enumerated in several ways (by instantiating global to different types). For instance global :: Count [Maybe Bool] would only count the number of lists of Maybe Bool of each size (using Control.Enumerable.Count). @global :: Values [Maybe Bool] would give the actual values for all sizes as lists. See FEAT for a more elaborate enumeration type that allows access to any value in the enumeration (given an index) in polynomial time, uniform selection from a given size etc.

Instances can be constructed in three ways:

1: Manually by passing datatype a list where each element is an application of the constructor functions c0, c1 etc, so a data type like Maybe would have enumerate = datatype [c0 Nothing, c1 Just]. This assumes all field types of all constructors are enumerable (recursive constructors work fine). The functions passed to cX do not have to be constructors, but should be injective functions (if they are not injective the enumeration will contain duplicates). So "smart constructors" can be used, for instance the Rational datatype is defined by an injection from the natural numbers.

2: Automatically with Template Haskell (deriveEnumerable). A top level declaration like deriveEnumerable ''Maybe would derive an instance for the Maybe data type.

3: Manually using the operations of a sized functor (see Control.Sized) to build a Shareable f a value, then apply share to it. To use other instances of Enumerable use access.

Synopsis

Documentation

class Typeable a => Enumerable a where Source #

Minimal complete definition

enumerate

Methods

enumerate :: (Typeable f, Sized f) => Shared f a Source #

Instances

Enumerable Bool Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Bool Source #

Enumerable Char Source #

ASCII characters

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Char Source #

Enumerable Double Source #

Not a proper injection

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Double Source #

Enumerable Float Source #

Not a proper injection

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Float Source #

Enumerable Int Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Int Source #

Enumerable Int8 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Int8 Source #

Enumerable Int16 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Int16 Source #

Enumerable Int32 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Int32 Source #

Enumerable Int64 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Int64 Source #

Enumerable Integer Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Integer Source #

Enumerable Ordering Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Ordering Source #

Enumerable Word Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Word Source #

Enumerable Word8 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Word8 Source #

Enumerable Word16 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Word16 Source #

Enumerable Word32 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Word32 Source #

Enumerable Word64 Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Word64 Source #

Enumerable () Source #

The unit constructor is free

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f () Source #

Enumerable Unicode Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Unicode Source #

Enumerable Printable Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f Printable Source #

Enumerable a => Enumerable [a] Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f [a] Source #

Enumerable a => Enumerable (Maybe a) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (Maybe a) Source #

Infinite a => Enumerable (Ratio a) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (Ratio a) Source #

Infinite integer => Enumerable (Nat integer) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (Nat integer) Source #

Enumerable a => Enumerable (NonEmpty a) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (NonEmpty a) Source #

(CoEnumerable a, Enumerable b) => Enumerable (a -> b) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (a -> b) Source #

(Enumerable a, Enumerable b) => Enumerable (Either a b) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (Either a b) Source #

(Enumerable a, Enumerable b) => Enumerable (a, b) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (a, b) Source #

(Enumerable a, Enumerable b, Enumerable c) => Enumerable (a, b, c) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (a, b, c) Source #

(Enumerable a, Enumerable b, Enumerable c, Enumerable d) => Enumerable (a, b, c, d) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (a, b, c, d) Source #

(Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e) => Enumerable (a, b, c, d, e) Source # 

Methods

enumerate :: (Typeable (* -> *) f, Sized f) => Shared f (a, b, c, d, e) Source #

Class based construction

datatype :: (Typeable a, Sized f, Typeable f) => [Shareable f a] -> Shared f a Source #

Builds an enumeration of a data type from a list of constructors (see c0-c7)

c0 :: Sized f => a -> Shareable f a Source #

Takes a constructor with arity 0 (a pure value)

c1 :: (Enumerable a, Sized f, Typeable f) => (a -> x) -> Shareable f x Source #

Takes a constructor of arity 1

c2 :: (Enumerable a, Enumerable b, Sized f, Typeable f) => (a -> b -> x) -> Shareable f x Source #

c3 :: (Enumerable a, Enumerable b, Enumerable c, Sized f, Typeable f) => (a -> b -> c -> x) -> Shareable f x Source #

c4 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Sized f, Typeable f) => (a -> b -> c -> d -> x) -> Shareable f x Source #

c5 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Sized f, Typeable f) => (a -> b -> c -> d -> e -> x) -> Shareable f x Source #

c6 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable g, Sized f, Typeable f) => (a -> b -> c -> d -> e -> g -> x) -> Shareable f x Source #

c7 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Enumerable g, Enumerable h, Sized f, Typeable f) => (a -> b -> c -> d -> e -> g -> h -> x) -> Shareable f x Source #

Access

global :: (Typeable f, Sized f, Enumerable a) => f a Source #

This is the primary way to access enumerations for usage. Guarantees global sharing of enumerations of the same type. Note that this means the enumerations are never garbage collected.

local :: (Typeable f, Sized f, Enumerable a) => f a Source #

Guarantees local sharing. All enumerations are shared inside each invokation of local, but may not be shared between them.

Automatic derivation

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

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

Non-class construction

access :: (Enumerable a, Sized f, Typeable f) => Shareable f a Source #

Used instead of enumerate when manually building instances.

share :: (Typeable * a, Typeable (* -> *) f) => Shareable f a -> Shared f a #

Share/memoize a class member of type f a.

data Shared f a :: (* -> *) -> * -> * #

data Shareable f a :: (* -> *) -> * -> * #

Instances

Functor f => Functor (Shareable f) 

Methods

fmap :: (a -> b) -> Shareable f a -> Shareable f b #

(<$) :: a -> Shareable f b -> Shareable f a #

Applicative f => Applicative (Shareable f) 

Methods

pure :: a -> Shareable f a #

(<*>) :: Shareable f (a -> b) -> Shareable f a -> Shareable f b #

(*>) :: Shareable f a -> Shareable f b -> Shareable f b #

(<*) :: Shareable f a -> Shareable f b -> Shareable f a #

Alternative f => Alternative (Shareable f) 

Methods

empty :: Shareable f a #

(<|>) :: Shareable f a -> Shareable f a -> Shareable f a #

some :: Shareable f a -> Shareable f [a] #

many :: Shareable f a -> Shareable f [a] #

class Typeable k a #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

Enumerating functions

function :: (Typeable a, Enumerable b, Sized f, Typeable f) => Shareable f (a -> b) -> Shared f (a -> b) Source #

Builds a suitable definition for coEnumerate given an pattern matching function for a data type (see source for examples).

class Typeable a => CoEnumerable a where Source #

Work in progress

Minimal complete definition

coEnumerate

Methods

coEnumerate :: (Enumerable b, Sized f, Typeable f) => Shared f (a -> b) Source #

Instances

CoEnumerable Bool Source # 

Methods

coEnumerate :: (Enumerable b, Sized f, Typeable (* -> *) f) => Shared f (Bool -> b) Source #

CoEnumerable a => CoEnumerable [a] Source # 

Methods

coEnumerate :: (Enumerable b, Sized f, Typeable (* -> *) f) => Shared f ([a] -> b) Source #

Other stuff (required for instances)

class (Typeable a, Integral a) => Infinite a Source #

A class of infinite precision integral types. Integer is the principal class member.

Instances

Orphan instances