species-0.2: Computational combinatorial speciesSource codeContentsIndex
Math.Combinatorics.Species.Class
Contents
The Species type class
Convenience methods
Derived operations
Derived species
Description
The Species type class, which defines a small DSL for describing combinatorial species. Other modules in this library provide specific instances which allow computing various properties of combinatorial species.
Synopsis
class C s => Species s where
singleton :: s
set :: s
cycle :: 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
subsets :: Species s => s
ksubsets :: Species s => Integer -> s
elements :: Species s => s
pointed :: Species s => s -> s
list :: Species s => s
lists :: Species 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
The Species type class
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).
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
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
subsets :: Species s => sSource
ksubsets :: Species s => Integer -> sSource
elements :: Species s => sSource
Derived operations
Some derived operations on species.
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
Some species that can be defined in terms of the primitive species operations.
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
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
Produced by Haddock version 2.6.0