species-0.4.0.1: Computational combinatorial species

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

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 where Source #

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.

Minimal complete definition

singleton, set, cycle, bracelet, o, (><), (@@), ofSize

Methods

singleton :: s Source #

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 :: s Source #

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

cycle :: s Source #

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

bracelet :: s Source #

The species of bracelets (i.e. cycles that can also be flipped).

linOrd :: s Source #

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 :: s Source #

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 -> s Source #

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 :: s Source #

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 -> s Source #

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 -> s Source #

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 -> s Source #

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) -> s Source #

Only put a structure on underlying sets whose size satisfies the predicate.

ofSizeExactly :: s -> Integer -> s Source #

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 -> s Source #

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 -> s Source #

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

omega :: s Source #

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.

Convenience methods

oneHole :: Species s => s -> s Source #

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 => s Source #

A synonym for singleton.

Plurals and synonyms

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.

sets :: Species s => s Source #

necklace :: Species s => s Source #

A synonym for cycle.

necklaces :: Species s => s Source #

A synonym for cycle.

bag :: Species s => s Source #

bags :: Species s => s Source #

Derived operations

Some derived operations on species.

pointed :: Species s => s -> s Source #

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 => s Source #

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.

octopi :: Species s => s Source #

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 => s Source #

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

partitions :: Species s => s Source #

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

permutation :: Species s => s Source #

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

permutations :: Species s => s Source #

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

ballot :: Species s => s Source #

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

ballots :: Species s => s Source #

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

simpleGraph :: Species s => s Source #

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

simpleGraphs :: Species s => s Source #

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 => s Source #

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.

directedGraphs :: Species s => s Source #

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.