species-0.2.1: Computational combinatorial speciesSource codeContentsIndex
Math.Combinatorics.Species
Contents
The combinatorial species DSL
Convenience methods
Derived operations
Derived species
Computing with species
Generating species structures
Types used for generation
Species AST
Description

A DSL for describing and computing with combinatorial species. This module re-exports the most generally useful functionality; for more specialized functionality (for example, computing directly with cycle index series), see the various sub-modules.

Note that this library makes extensive use of the numeric-prelude library; to use it you will want to use -XNoImplicitPrelude, and import NumericPrelude and PreludeBase.

For a friendly introduction to combinatorial species in general and this library in particular, see my series of blog posts:

http://byorgey.wordpress.com/2009/07/24/introducing-math-combinatorics-species/

For a good reference (really, the only English-language reference!) on combinatorial species, see Bergeron, Labelle, and Leroux, "Combinatorial Species and Tree-Like Structures", Vol. 67 of the Encyclopedia of Mathematics and its Applications, Gian-Carlo Rota, ed., Cambridge University Press, 1998.

Synopsis
class C s => Species s where
singleton :: s
set :: s
cycle :: s
list :: s
subset :: s
ksubset :: Integer -> s
element :: s
o :: s -> s -> s
cartesian :: s -> s -> s
fcomp :: s -> s -> s
ofSize :: s -> (Integer -> Bool) -> s
ofSizeExactly :: s -> Integer -> s
nonEmpty :: s -> s
oneHole :: Species s => s -> s
madeOf :: Species s => s -> s -> s
(><) :: Species s => s -> s -> s
(@@) :: Species s => s -> s -> s
x :: Species s => s
sets :: Species s => s
cycles :: Species s => s
lists :: Species s => s
subsets :: Species s => s
ksubsets :: Species s => Integer -> s
elements :: Species s => s
pointed :: Species s => s -> s
octopus :: Species s => s
octopi :: Species s => s
partition :: Species s => s
partitions :: Species s => s
permutation :: Species s => s
permutations :: Species s => s
ballot :: Species s => s
ballots :: Species s => s
simpleGraph :: Species s => s
simpleGraphs :: Species s => s
directedGraph :: Species s => s
directedGraphs :: Species s => s
labelled :: EGF -> [Integer]
unlabelled :: SpeciesAST -> [Integer]
generate :: SpeciesAST -> [a] -> [Structure a]
generateTyped :: forall f a. (Typeable1 f, Typeable a) => SpeciesAST -> [a] -> [f a]
structureType :: SpeciesAST -> String
newtype Identity a = Identity a
newtype Const x a = Const x
newtype Sum f g a = Sum {
unSum :: Either (f a) (g a)
}
newtype Prod f g a = Prod {
unProd :: (f a, g a)
}
data Comp f g a = Comp {
unComp :: f (g a)
}
data Star a
= Star
| Original a
newtype Cycle a = Cycle {
getCycle :: [a]
}
newtype Set a = Set {
getSet :: [a]
}
data SpeciesTypedAST s where
N :: Integer -> SpeciesTypedAST Z
X :: SpeciesTypedAST X
E :: SpeciesTypedAST E
C :: SpeciesTypedAST C
L :: SpeciesTypedAST L
Subset :: SpeciesTypedAST Sub
KSubset :: Integer -> SpeciesTypedAST Sub
Elt :: SpeciesTypedAST Elt
:+: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :+: g)
:*: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :*: g)
:.: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :.: g)
:><: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :><: g)
:@: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :@: g)
Der :: ShowF (StructureF f) => SpeciesTypedAST f -> SpeciesTypedAST (Der f)
OfSize :: SpeciesTypedAST f -> (Integer -> Bool) -> SpeciesTypedAST f
OfSizeExactly :: SpeciesTypedAST f -> Integer -> SpeciesTypedAST f
NonEmpty :: SpeciesTypedAST f -> SpeciesTypedAST f
data SpeciesAST where
SA :: (ShowF (StructureF s), Typeable1 (StructureF s)) => SpeciesTypedAST s -> SpeciesAST
reify :: SpeciesAST -> SpeciesAST
reflect :: Species s => SpeciesAST -> s
The combinatorial species DSL
The combinatorial species DSL consists of the Species type class, which defines some primitive species and species operations. Expressions of type Species s => s can then be interpreted at various instance types in order to compute with species in various ways.
class C s => Species s whereSource

The Species type class. Note that the Differential constraint requires s to be a differentiable ring, which means that every instance must also implement instances for Algebra.Additive (the species 0 and species addition, i.e. disjoint sum), Algebra.Ring (the species 1 and species multiplication, i.e. partitional product), and Algebra.Differential (species differentiation, i.e. adjoining a distinguished element).

Minimal complete definition: singleton, set, cycle, o, cartesian, fcomp, ofSize.

Note that the o operation can be used infix to suggest common notation for composition, and also to be read as an abbreviation for "of", as in "top o' the mornin'": set `o` nonEmpty sets.

In this version of the library, Species has four instances: EGF (exponential generating functions, for counting labelled structures), GF (ordinary generating function, for counting unlabelled structures), CycleIndex (cycle index series, a generalization of both EGF and GF), and SpeciesAST (reified species expressions).

Methods
singleton :: sSource
The species X of singletons. X puts a singleton structure on an underlying set of size 1, and no structures on any other underlying sets.
set :: sSource
The species E of sets. E puts a singleton structure on any underlying set.
cycle :: sSource
The species C of cyclical orderings (cycles/rings).
list :: sSource
The species L of linear orderings (lists): since lists are isomorphic to cycles with a hole, we may take L = C' as the default implementation; list is included in the Species class so it can be special-cased for generation.
subset :: sSource
The species p of subsets is given by p = E * E. subset has a default implementation of set * set, but is included in the Species class so it can be overridden when generating structures: since subset is defined as set * set, the generation code by default generates a pair of the subset and its complement, but normally when thinking about subsets we only want to see the elements in the subset. To explicitly generate subset/complement pairs, you can use set * set directly.
ksubset :: Integer -> sSource
Subsets of size exactly k, p[k] = E_k * E. Included with a default definition in the Species class for the same reason as subset.
element :: sSource
Structures of the species e of elements are just elements of the underlying set: e = X * E. Included with default definition in Species class for the same reason as subset and ksubset.
o :: s -> s -> sSource
Partitional composition. To form all (F o G)-structures on the underlying set U, first form all set partitions of U; for each partition p, put an F-structure on the classes of p, and a separate G-structure on the elements in each class.
cartesian :: s -> s -> sSource
Cartisian product of two species. An (F x G)-structure consists of an F structure superimposed on a G structure over the same underlying set.
fcomp :: s -> s -> sSource
Functor composition of two species. An (F @@ G)-structure consists of an F-structure on the set of all G-structures.
ofSize :: s -> (Integer -> Bool) -> sSource
Only put a structure on underlying sets whose size satisfies the predicate.
ofSizeExactly :: s -> Integer -> sSource
Only put a structure on underlying sets of the given size. A default implementation of ofSize (==k) is provided, but this method is included in the Species class as a special case since it can be more efficient: we get to turn infinite lists of coefficients into finite ones.
nonEmpty :: s -> sSource
Don't put a structure on the empty set. The default definition uses ofSize; included in the Species class so it can be overriden in special cases (such as when reifying species expressions).
show/hide Instances
Convenience methods
Some synonyms are provided for convenience. In particular, gramatically it can often be convenient to have both the singular and plural versions of species, for example, set `o` nonEmpty sets.
oneHole :: Species s => s -> sSource
A convenient synonym for differentiation. F'-structures look like F-structures on a set formed by adjoining a distinguished "hole" element to the underlying set.
madeOf :: Species s => s -> s -> sSource
A synonym for o (partitional composition).
(><) :: Species s => s -> s -> sSource
A synonym for cartesian product.
(@@) :: Species s => s -> s -> sSource
A synonym for functor composition.
x :: Species s => sSource
A synonym for singleton.
sets :: Species s => sSource
cycles :: Species s => sSource
lists :: Species s => sSource
subsets :: Species s => sSource
ksubsets :: Species s => Integer -> sSource
elements :: Species s => sSource
Derived operations
pointed :: Species s => s -> sSource
Combinatorially, the operation of pointing picks out a distinguished element from an underlying set. It is equivalent to the operator x d/dx.
Derived species
octopus :: Species s => sSource
An octopus is a cyclic arrangement of lists, so called because the lists look like "tentacles" attached to the cyclic "body": Oct = C o E+ .
octopi :: Species s => sSource
partition :: Species s => sSource
The species of set partitions is just the composition E o E+, that is, sets of nonempty sets.
partitions :: Species s => sSource
permutation :: Species s => sSource
A permutation is a set of disjoint cycles: S = E o C.
permutations :: Species s => sSource
ballot :: Species s => sSource
The species Bal of ballots consists of linear orderings of nonempty sets: Bal = L o E+.
ballots :: Species s => sSource
simpleGraph :: Species s => sSource
Simple graphs (undirected, without loops). A simple graph is a subset of the set of all size-two subsets of the vertices: G = p @@ p_2.
simpleGraphs :: Species s => sSource
directedGraph :: Species s => sSource
A directed graph (with loops) is a subset of all pairs drawn (without replacement) from the set of vertices: D = p @@ (e >< e). It can also be thought of as the species of binary relations.
directedGraphs :: Species s => sSource
Computing with species
labelled :: EGF -> [Integer]Source

Extract the coefficients of an exponential generating function as a list of Integers. Since EGF is an instance of Species, the idea is that labelled can be applied directly to an expression of the Species DSL. In particular, labelled s !! n is the number of labelled s-structures on an underlying set of size n (note that labelled s is guaranteed to be an infinite list). For example:

 > take 10 $ labelled octopi
 [0,1,3,14,90,744,7560,91440,1285200,20603520]

gives the number of labelled octopi on 0, 1, 2, 3, ... 9 elements.

unlabelled :: SpeciesAST -> [Integer]Source

Extract the coefficients of an ordinary generating function as a list of Integers. In particular, unlabelled s !! n is the number of unlabelled s-structures on an underlying set of size n (unlabelled s is guaranteed to be infinite). For example:

 > take 10 $ unlabelled octopi
 [0,1,2,3,5,7,13,19,35,59]

gives the number of unlabelled octopi on 0, 1, 2, 3, ... 9 elements.

Actually, the above is something of a white lie, as you may have already realized by looking at the input type of unlabelled, which is SpeciesAST rather than the expected GF. The reason is that although products and sums of unlabelled species correspond to products and sums of ordinary generating functions, other operations such as composition and differentiation do not! In order to compute an ordinary generating function for a species defined in terms of composition and/or differentiation, we must compute the cycle index series for the species and then convert it to an ordinary generating function. So unlabelled actually works by first reifying the species to an AST and checking which operations are used in its definition, and then choosing to work with cycle index series or directly with (much faster) ordinary generating functions as appropriate.

Generating species structures
generate :: SpeciesAST -> [a] -> [Structure a]Source

generate s ls generates a complete list of all s-structures over the underlying set of labels ls. For example:

 > generate octopi ([1,2,3] :: [Int])
 [<<*,1,2,3>>,<<*,1,3,2>>,<<*,2,1,3>>,<<*,2,3,1>>,<<*,3,1,2>>,<<*,3,2,1>>,
  <<*,1,2>,<*,3>>,<<*,2,1>,<*,3>>,<<*,1,3>,<*,2>>,<<*,3,1>,<*,2>>,<<*,1>,
  <*,2,3>>,<<*,1>,<*,3,2>>,<<*,1>,<*,2>,<*,3>>,<<*,1>,<*,3>,<*,2>>]

 > generate subsets "abc"
 [{'a','b','c'},{'a','b'},{'a','c'},{'a'},{'b','c'},{'b'},{'c'},{}]
 > generate simpleGraphs ([1,2,3] :: [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, it must be existentially quantified! The output of generate can always be Shown, but not much else.

However! All is not lost. It's possible, by the magic of Data.Typeable, to yank the type information (kicking and screaming) back into the open, so that you can then manipulate the generated structures to your heart's content. To see how, consult structureType and generateTyped.

generateTyped :: forall f a. (Typeable1 f, Typeable a) => SpeciesAST -> [a] -> [f a]Source

generateTyped s ls generates a complete list of all s-structures over the underlying set of labels ls, where the type of the generated structures is known (structureType may be used to compute this type). For example:

 > structureType subsets
 "Set"
 > generateTyped subsets ([1,2,3] :: [Int]) :: [Set Int]
 [{1,2,3},{1,2},{1,3},{1},{2,3},{2},{3},{}]
 > map (sum . getSet) $ it
 [6,3,4,1,5,2,3,0]

Although the output from generate appears the same, trying to compute the subset sums fails spectacularly if we use generate instead of generateTyped:

 > generate subsets ([1..3] :: [Int])
 [{1,2,3},{1,2},{1,3},{1},{2,3},{2},{3},{}]
 > map (sum . getSet) $ it
 <interactive>:1:21:
     Couldn't match expected type `Set a'
            against inferred type `Math.Combinatorics.Species.Generate.Structure
                                     Int'
       Expected type: [Set a]
       Inferred type: [Math.Combinatorics.Species.Generate.Structure Int]
     In the second argument of `($)', namely `it'
     In the expression: map (sum . getSet) $ it

If we use the wrong type, we get a nice error message:

 > generateTyped octopi ([1..3] :: [Int]) :: [Set Int]
 *** Exception: structure type mismatch.
   Expected: Set Int
   Inferred: Comp Cycle (Comp Cycle Star) Int
structureType :: SpeciesAST -> StringSource

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 generateTyped by writing

 generateTyped s ls :: [T L]

where ls :: [L].

Types used for generation
Many of these functors are already defined elsewhere, in other packages; but to avoid a plethora of imports, inconsistent naming/instance schemes, etc., we just redefine them here.
newtype Identity a Source
The identity functor.
Constructors
Identity a
show/hide Instances
newtype Const x a Source
The constant functor.
Constructors
Const x
show/hide Instances
newtype Sum f g a Source
Functor coproduct.
Constructors
Sum
unSum :: Either (f a) (g a)
show/hide Instances
(Functor f, Functor g) => Functor (Sum f g)
(Typeable1 f, Typeable1 g) => Typeable1 (Sum f g)
(ShowF f, ShowF g) => ShowF (Sum f g)
(Show (f a), Show (g a)) => Show (Sum f g a)
newtype Prod f g a Source
Functor product.
Constructors
Prod
unProd :: (f a, g a)
show/hide Instances
(Functor f, Functor g) => Functor (Prod f g)
(Typeable1 f, Typeable1 g) => Typeable1 (Prod f g)
(ShowF f, ShowF g) => ShowF (Prod f g)
(Show (f a), Show (g a)) => Show (Prod f g a)
data Comp f g a Source
Functor composition.
Constructors
Comp
unComp :: f (g a)
show/hide Instances
(Functor f, Functor g) => Functor (Comp f g)
(Typeable1 f, Typeable1 g) => Typeable1 (Comp f g)
(ShowF f, ShowF g) => ShowF (Comp f g)
Show (f (g a)) => Show (Comp f g a)
data Star a Source
Star is isomorphic to Maybe, but with a more useful Show instance for our purposes. Used to implement species differentiation.
Constructors
Star
Original a
show/hide Instances
newtype Cycle a Source
Cycle structure. A value of type 'Cycle a' is implemented as '[a]', but thought of as a directed cycle.
Constructors
Cycle
getCycle :: [a]
show/hide Instances
newtype Set a Source
Set structure. A value of type 'Set a' is implemented as '[a]', but thought of as an unordered set.
Constructors
Set
getSet :: [a]
show/hide Instances
Species AST
Species can be converted to and from SpeciesAST via the functions reify and reflect.
data SpeciesTypedAST s whereSource

Reified combinatorial species. Note that SpeciesTypedAST has a phantom type parameter which also reflects the structure, so we can do case analysis on species at both the value and type level.

Of course, the non-uniform type parameter means that SpeciesTypedAST cannot be an instance of the Species class; for that purpose the existential wrapper SpeciesAST is provided.

Constructors
N :: Integer -> SpeciesTypedAST Z
X :: SpeciesTypedAST X
E :: SpeciesTypedAST E
C :: SpeciesTypedAST C
L :: SpeciesTypedAST L
Subset :: SpeciesTypedAST Sub
KSubset :: Integer -> SpeciesTypedAST Sub
Elt :: SpeciesTypedAST Elt
:+: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :+: g)
:*: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :*: g)
:.: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :.: g)
:><: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :><: g)
:@: :: (ShowF (StructureF f), ShowF (StructureF g)) => SpeciesTypedAST f -> SpeciesTypedAST g -> SpeciesTypedAST (f :@: g)
Der :: ShowF (StructureF f) => SpeciesTypedAST f -> SpeciesTypedAST (Der f)
OfSize :: SpeciesTypedAST f -> (Integer -> Bool) -> SpeciesTypedAST f
OfSizeExactly :: SpeciesTypedAST f -> Integer -> SpeciesTypedAST f
NonEmpty :: SpeciesTypedAST f -> SpeciesTypedAST f
show/hide Instances
data SpeciesAST whereSource
An existential wrapper to hide the phantom type parameter to SpeciesTypedAST, so we can make it an instance of Species.
Constructors
SA :: (ShowF (StructureF s), Typeable1 (StructureF s)) => SpeciesTypedAST s -> SpeciesAST
show/hide Instances
reify :: SpeciesAST -> SpeciesASTSource

Reify a species expression into an AST. Of course, this is just the identity function with a usefully restricted type. For example:

 > reify octopus
 C . L+
 > reify (ksubset 3)
 E3 * E
reflect :: Species s => SpeciesAST -> sSource
Reflect an AST back into any instance of the Species class.
Produced by Haddock version 2.6.0