Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
.
- class Typeable a => Enumerable a where
- datatype :: (Typeable a, Sized f, Typeable f) => [Shareable f a] -> Shared f a
- c0 :: Sized f => a -> Shareable f a
- c1 :: (Enumerable a, Sized f, Typeable f) => (a -> x) -> Shareable f x
- c2 :: (Enumerable a, Enumerable b, Sized f, Typeable f) => (a -> b -> x) -> Shareable f x
- c3 :: (Enumerable a, Enumerable b, Enumerable c, Sized f, Typeable f) => (a -> b -> c -> x) -> Shareable f x
- c4 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Sized f, Typeable f) => (a -> b -> c -> d -> x) -> Shareable f x
- c5 :: (Enumerable a, Enumerable b, Enumerable c, Enumerable d, Enumerable e, Sized f, Typeable f) => (a -> b -> c -> d -> e -> x) -> Shareable f x
- 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
- 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
- global :: (Typeable f, Sized f, Enumerable a) => f a
- local :: (Typeable f, Sized f, Enumerable a) => f a
- deriveEnumerable :: Name -> Q [Dec]
- dAll :: Name -> ConstructorDeriv
- dExcluding :: Name -> ConstructorDeriv -> ConstructorDeriv
- dExcept :: Name -> ExpQ -> ConstructorDeriv -> ConstructorDeriv
- type ConstructorDeriv = (Name, [(Name, ExpQ)])
- deriveEnumerable' :: ConstructorDeriv -> Q [Dec]
- access :: (Enumerable a, Sized f, Typeable f) => Shareable f a
- share :: (Typeable * a, Typeable (* -> *) f) => Shareable f a -> Shared f a
- data Shared (f :: * -> *) a :: (* -> *) -> * -> *
- data Shareable (f :: * -> *) a :: (* -> *) -> * -> *
- class Typeable k (a :: k)
- module Control.Sized
- function :: (Typeable a, Enumerable b, Sized f, Typeable f) => Shareable f (a -> b) -> Shared f (a -> b)
- class Typeable a => CoEnumerable a where
- class (Typeable a, Integral a) => Infinite a
Documentation
class Typeable a => Enumerable a where 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)
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
dAll :: Name -> ConstructorDeriv Source #
dExcluding :: Name -> ConstructorDeriv -> ConstructorDeriv Source #
dExcept :: Name -> ExpQ -> ConstructorDeriv -> ConstructorDeriv Source #
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
.
The class Typeable
allows a concrete representation of a type to
be calculated.
typeRep#
module Control.Sized
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
coEnumerate :: (Enumerable b, Sized f, Typeable f) => Shared f (a -> b) Source #
CoEnumerable Bool Source # | |
CoEnumerable a => CoEnumerable [a] 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.