species-0.3.1: Computational combinatorial species

Stabilityexperimental
Maintainerbyorgey@cis.upenn.edu

Math.Combinatorics.Species.Class

Contents

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

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.

Methods

singleton :: sSource

The species X of singletons. Puts a singleton structure on an underlying label set of size 1, and no structures on any other underlying label sets. x is also provided as a synonym.

set :: sSource

The species E of sets. Puts a singleton structure on any underlying label set.

cycle :: sSource

The species C of cyclical orderings (cycles/rings).

linOrd :: sSource

The species L of linear orderings (lists). Since linear orderings are isomorphic to cyclic orderings with a hole, we may take linOrd = oneHole cycle as the default implementation; linOrd is included in the Species class so it can be special-cased for enumeration.

subset :: sSource

The species p of subsets is given by subset = set * set. subset is included in the Species class so it can be overridden when enumerating structures: by default the enumeration code would generate 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 enumerate subset/complement pairs, you can use set * set directly.

ksubset :: Integer -> sSource

Subsets of size exactly k, ksubset k = (set `ofSizeExactly` k) * set. 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, element = singleton * set. Included with a 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 label 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.

(><) :: s -> s -> sSource

Cartisian product of two species. An (f >< g)-structure consists of an f-structure superimposed on a g-structure over the same underlying set.

(@@) :: 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).

rec :: ASTFunctor f => f -> sSource

'rec f' is the least fixpoint of (the interpretation of) the higher-order species constructor f.

omega :: sSource

Omega is the pseudo-species which only puts a structure on infinite label sets. Of course this is not really a species, but it is sometimes a convenient fiction to use Omega to stand in for recursive occurrences of a species.

Instances

Species CycleIndex

An interpretation of species expressions as cycle index series. For the definition of the CycleIndex type, see Math.Combinatorics.Species.Types.

Species GF 
Species EGF 
Species ESpeciesAST 
Species SpeciesAST

Species expressions are an instance of the Species class, so we can use the Species class DSL to build species expression ASTs.

Convenience methods

oneHole :: Species s => s -> sSource

A convenient synonym for differentiation. oneHole f-structures look like f-structures on a set formed by adjoining a distinguished "hole" element to the underlying set.

x :: Species s => sSource

A synonym for singleton.

Plurals

It can be grammatically convenient to define plural versions of species as synonyms for the singular versions. For example, we can use set `o` nonEmpty sets instead of set `o` nonEmpty set.

Derived operations

Some derived operations on species.

pointed :: Species s => s -> sSource

Intuitively, the operation of pointing picks out a distinguished element from an underlying set. It is equivalent to the operator x d/dx: pointed s = singleton * differentiate s.

Derived species

Some species that can be defined in terms of the primitive species operations.

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": octopus = cycle `o` nonEmpty linOrds.

partition :: Species s => sSource

The species of set partitions is just the composition set `o` nonEmpty sets.

permutation :: Species s => sSource

A permutation is a set of disjoint cycles: permutation = set `o` cycles.

ballot :: Species s => sSource

The species of ballots consists of linear orderings of nonempty sets: ballot = linOrd `o` nonEmpty sets.

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: simpleGraph = subset @@ (ksubset 2).

directedGraph :: Species s => sSource

A directed graph (with loops) is a subset of all pairs drawn (with replacement) from the set of vertices: subset @@ (element >< element). It can also be thought of as the species of binary relations.