species-0.3.4.2: Computational combinatorial species

Copyright(c) Brent Yorgey 2010
LicenseBSD-style (see LICENSE)
Maintainerbyorgey@cis.upenn.edu
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Math.Combinatorics.Species.Enumerate

Contents

Description

Enumeration (i.e. exhaustive generation of structures) of both labeled and unlabeled species.

Synopsis

Enumeration methods

enumerate :: (Enumerable f, Typeable a, Eq a) => SpeciesAST -> [a] -> [f a] Source

enumerate s ls computes a complete list of distinct s-structures over the underlying multiset of labels ls. For example:

> enumerate octopi [1,2,3] :: [Comp Cycle [] Int]
[<[3,2,1]>,<[3,1,2]>,<[2,3,1]>,<[2,1,3]>,<[1,3,2]>,<[1,2,3]>,
 <[1],[3,2]>,<[1],[2,3]>,<[3,1],[2]>,<[1,3],[2]>,<[2,1],[3]>,
 <[1,2],[3]>,<[2],[1],[3]>,<[1],[2],[3]>]

> enumerate octopi [1,1,2] :: [Comp Cycle [] Int]
[<[2,1,1]>,<[1,2,1]>,<[1,1,2]>,<[2,1],[1]>,<[1,2],[1]>,
 <[1,1],[2]>,<[1],[1],[2]>]

> enumerate subsets "abc" :: [Set Int]
[{'a','b','c'},{'a','b'},{'a','c'},{'a'},{'b','c'},{'b'},{'c'},{}]

> enumerate simpleGraphs [1,2,3] :: [Comp Set Set Int]
[{{1,2},{1,3},{2,3}},{{1,2},{1,3}},{{1,2},{2,3}},{{1,2}},{{1,3},{2,3}},
 {{1,3}},{{2,3}},{}]

There is one caveat: since the type of the generated structures is different for each species, they must be cast (using the magic of Data.Typeable) out of an existential wrapper; this is why type annotations are required in all the examples above. Of course, if a call to enumerate is used in the context of some larger program, a type annotation will probably not be needed, due to the magic of type inference.

For help in knowing what type annotation you can give when enumerating the structures of a particular species at the ghci prompt, see the structureType function. To be able to use your own custom data type in an enumeration, just make your data type an instance of the Enumerable type class; this can be done for you automatically by Math.Combinatorics.Species.TH.

If an invalid type annotation is given, enumerate will call error with a helpful error message. This should not be much of an issue in practice, since usually enumerate will be used at a specific type; it's hard to imagine a usage of enumerate which will sometimes work and sometimes fail. However, those who like their functions total can use extractStructure to make a version of enumerate (or the other variants) with a return type of [Either String (f a)] (which will return an annoying ton of duplicate error messages) or Either String [f a] (which has the unfortunate property of being much less lazy than the current versions, since it must compute the entire list before deciding whether to return Left or Right).

For slight variants on enumerate, see enumerateL, enumerateU, and enumerateM.

enumerateL :: (Enumerable f, Typeable a) => SpeciesAST -> [a] -> [f a] Source

Labeled enumeration: given a species expression and a list of labels (which are assumed to be distinct), compute the list of all structures built from the given labels. If the type given for the enumeration does not match the species expression (via an Enumerable instance), call error with an error message explaining the mismatch. This is slightly more efficient than enumerate for lists of labels which are known to be distinct, since it doesn't have to waste time checking for duplicates. (However, it probably doesn't really make much difference, since the time to do the actual enumeration will usually dwarf the time to process the list of labels anyway.)

For example:

> enumerateL ballots [1,2,3] :: [Comp [] Set Int]
[[{1,2,3}],[{2,3},{1}],[{1},{2,3}],[{2},{1,3}],[{1,3},{2}],[{3},{1,2}]
,[{1,2},{3}],[{3},{2},{1}],[{3},{1},{2}],[{2},{3},{1}],[{2},{1},{3}]
,[{1},{3},{2}],[{1},{2},{3}]]

enumerateU :: Enumerable f => SpeciesAST -> Int -> [f ()] Source

Unlabeled enumeration: given a species expression and an integer indicating the number of labels to use, compute the list of all unlabeled structures of the given size. If the type given for the enumeration does not match the species expression, call error with an error message explaining the mismatch.

Note that enumerateU s n is equivalent to enumerate s (replicate n ()).

For example:

> enumerateU octopi 4 :: [Comp Cycle [] ()]
[<[(),(),(),()]>,<[(),()],[(),()]>,<[(),(),()],[()]>
,<[(),()],[()],[()]>,<[()],[()],[()],[()]>]

enumerateM :: (Enumerable f, Typeable a) => SpeciesAST -> Multiset a -> [f a] Source

General enumeration: given a species expression and a multiset of labels, compute the list of all distinct structures built from the given labels. If the type given for the enumeration does not match the species expression, call error with a message explaining the mismatch.

enumerateAll :: Enumerable f => SpeciesAST -> [f Int] Source

Lazily enumerate all labeled structures, using [1..] as the labels.

For example:

> take 10 $ enumerateAll ballots :: [Comp [] Set Int]
[[],[{1}],[{1,2}],[{2},{1}],[{1},{2}],[{1,2,3}],[{2,3},{1}]
,[{1},{2,3}],[{2},{1,3}],[{1,3},{2}]]

enumerateAllU :: Enumerable f => SpeciesAST -> [f ()] Source

Lazily enumerate all unlabeled structures.

For example:

> take 10 $ enumerateAllU octopi :: [Comp Cycle [] ()]
[<[()]>,<[(),()]>,<[()],[()]>,<[(),(),()]>,<[(),()],[()]>
,<[()],[()],[()]>,<[(),(),(),()]>,<[(),()],[(),()]>
,<[(),(),()],[()]>,<[(),()],[()],[()]>]

Tools for dealing with structure types

class Typeable (StructTy f) => Enumerable f where Source

The Enumerable class allows you to enumerate structures of any type, by declaring an instance of Enumerable. The Enumerable instance requires you to declare a standard structure type (see Math.Combinatorics.Species.Structures) associated with your type, and a mapping iso from the standard type to your custom one. Instances are provided for all the standard structure types so you can enumerate species without having to provide your own custom data type as the target of the enumeration if you don't want to.

You should only rarely have to explicitly make an instance of Enumerable yourself; Template Haskell code to derive instances for you is provided in Math.Combinatorics.Species.TH.

Associated Types

type StructTy f :: * -> * Source

The standard structure type (see Math.Combinatorics.Species.Structures) that will map into f.

Methods

iso :: StructTy f a -> f a Source

The mapping from StructTy f to f.

data Structure a where Source

An existential wrapper for structures, hiding the structure functor and ensuring that it is Typeable.

Constructors

Structure :: Typeable f => f a -> Structure a 

extractStructure :: forall f a. (Enumerable f, Typeable a) => Structure a -> Either String (f a) Source

Extract the contents from a Structure wrapper, if we know the type, and map it into an isomorphic type. If the type doesn't match, return a helpful error message instead.

unsafeExtractStructure :: (Enumerable f, Typeable a) => Structure a -> f a Source

A version of extractStructure which calls error with the message in the case of a type mismatch, instead of returning an Either.

structureType :: ESpeciesAST -> String Source

structureType s returns a String representation of the functor type which represents the structure of the species s. In particular, if structureType s prints "T", then you can safely use enumerate and friends by writing

enumerate s ls :: [T a]

where ls :: [a].

For example,

> structureType octopus
"Comp Cycle []"
> enumerate octopus [1,2,3] :: [Comp Cycle [] Int]
[<[3,2,1]>,<[3,1,2]>,<[2,3,1]>,<[2,1,3]>,<[1,3,2]>
,<[1,2,3]>,<[1],[3,2]>,<[1],[2,3]>,<[3,1],[2]>
,<[1,3],[2]>,<[2,1],[3]>,<[1,2],[3]>,<[2],[1],[3]>
,<[1],[2],[3]>]

Note, however, that providing a type annotation on enumerate in this way is usually only necessary at the ghci prompt; when used in the context of a larger program the type of a call to enumerate can often be inferred.

showStructureType :: TypeRep -> String Source

Show a TypeRep while stripping off qualifier portions of TyCon names. This is essentially copied and pasted from the Data.Typeable source, with a number of cases taken out that we don't care about (special cases for (->), tuples, etc.).

Where all the work actually happens

enumerate' :: TSpeciesAST s -> Multiset a -> [s a] Source

Given an AST describing a species, with a phantom type parameter representing the structure of the species, and an underlying multiset of elements, compute a list of all possible structures built over the underlying multiset. (Of course, it would be really nice to have a real dependently-typed language for this!)

Unfortunately, TSpeciesAST cannot be made an instance of Species, so if we want to be able to enumerate structures given an expression of the Species DSL as input, the output must be existentially quantified; see enumerateE.

Generating structures over base elements from a multiset unifies labeled and unlabeled generation into one framework. To enumerate labeled structures, use a multiset where each element occurs exactly once; to enumerate unlabeled structures, use a multiset with the desired number of copies of a single element. To do labeled generation we could get away without the generality of multisets, but to do unlabeled generation we need the full generality anyway.

enumerate' does all the actual work, but is not meant to be used directly; use one of the specialized enumerateXX methods.

enumerateE :: ESpeciesAST -> Multiset a -> [Structure a] Source

enumerateE is a variant of enumerate' which takes an (existentially quantified) typed AST and returns a list of existentially quantified structures. This is also not meant to be used directly. Instead, you should use one of the other enumerateX methods.