species-0.1: Combinatorial species library

Math.Combinatorics.Species

Contents

Description

A DSL for describing combinatorial species and computing various properties. 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 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

The combinatorial species DSL

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).

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.

Methods

singleton :: sSource

The species X of singletons

set :: sSource

The species E of sets

cycle :: sSource

The species C of cyclical orderings (cycles/rings)

o :: s -> s -> sSource

Partitional composition

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. We include this as a special case, instead of just using ofSize (==k), since it can be more efficient: we get to turn infinite lists of coefficients into finite ones.

(.:) :: s -> s -> sSource

s1 .: s2 is the species which puts an s1 structure on the empty set and an s2 structure on anything else. Useful for getting recursively defined species off the ground.

Convenience methods

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).

x :: Species s => sSource

A synonym for singleton.

e :: Species s => sSource

A synonym for set.

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.

nonEmpty :: Species s => s -> sSource

Don't put a structure on the empty set.

Derived species

list :: Species s => sSource

The species L of linear orderings (lists): since lists are isomorphic to cycles with a hole, we may take L = C'.

lists :: Species s => sSource

A convenient synonym for list.

element :: Species s => sSource

Structures of the species eps of elements are just elements of the underlying set: eps = X * E.

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+ .

partition :: Species s => sSource

The species of set partitions is just the composition E o E+, that is, sets of nonempty sets.

permutation :: Species s => sSource

A permutation is a set of disjoint cycles: S = E o C.

subset :: Species s => sSource

The species p of subsets is given by p = E * E.

ballot :: Species s => sSource

The species Bal of ballots consists of linear orderings of nonempty sets: Bal = L o E+.

ksubset :: Species s => Integer -> sSource

Subsets of size exactly k, p[k] = E_k * E.

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. 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 :: SpeciesAlg -> [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. 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 SpeciesAlg 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, 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 whether it uses composition or differentiation, and using operations on cycle index series if it does, and (much faster) operations directly on ordinary generating functions otherwise.

generate :: SpeciesAlg -> [a] -> [Structure a]Source

We can generate structures from a SpeciesAlg (which is an instance of Species) only if we existentially quantify over the output type. However, we have guaranteed that the structures will be Showable. 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}}]

Of course, this is not the output we might hope for; octopi are cycles of lists, but above we are seeing the fact that lists are implemented as the derivative of cycles, so each list is represented by a cycle containing *. In a future version of this library I plan to implement a system for automatically converting between isomorphic structures during species generation.