species-0.4: Computational combinatorial species

Safe HaskellNone
LanguageHaskell2010

Math.Combinatorics.Species

Contents

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:

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

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

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

sets :: Species s => s Source #

Derived operations

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

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.

Counting species structures

 

labeled :: 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 labeled can be applied directly to an expression of the species DSL. In particular, labeled s !! n is the number of labeled s-structures on an underlying set of size n (note that labeled s is guaranteed to be an infinite list). For example:

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

gives the number of labeled octopi on 0, 1, 2, 3, ... 9 labels.

labelled :: EGF -> [Integer] Source #

A synonym for labeled, since both spellings are acceptable and it's annoying to have to remember which is correct.

unlabeled :: SpeciesAST -> [Integer] Source #

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

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

gives the number of unlabeled 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 unlabeled, which is SpeciesAST rather than the expected GF. The reason is that although products and sums of unlabeled 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 unlabeled 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.

unlabelled :: SpeciesAST -> [Integer] Source #

A synonym for unlabeled, since both spellings are acceptable.

Enumerating species structures

 

class Typeable (StructTy f) => Enumerable f where Source #

The Enumerable class allows you to enumerate structures of any type, by declaring an instance of Enumerable. The Enumerable instance requires you to declare a standard structure type (see Math.Combinatorics.Species.Structures) associated with your type, and a mapping iso from the standard type to your custom one. Instances are provided for all the standard structure types so you can enumerate species without having to provide your own custom data type as the target of the enumeration if you don't want to.

You should only rarely have to explicitly make an instance of Enumerable yourself; Template Haskell code to derive instances for you is provided in Math.Combinatorics.Species.TH.

Minimal complete definition

iso

Associated Types

type StructTy f :: * -> * Source #

The standard structure type (see Math.Combinatorics.Species.Structures) that will map into f.

Methods

iso :: StructTy f a -> f a Source #

The mapping from StructTy f to f.

Instances

Enumerable [] Source # 

Associated Types

type StructTy ([] :: * -> *) :: * -> * Source #

Methods

iso :: StructTy [] a -> [a] Source #

Enumerable Maybe Source # 

Associated Types

type StructTy (Maybe :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Maybe a -> Maybe a Source #

Enumerable Star Source # 

Associated Types

type StructTy (Star :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Star a -> Star a Source #

Enumerable Set Source # 

Associated Types

type StructTy (Set :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Set a -> Set a Source #

Enumerable Bracelet Source # 

Associated Types

type StructTy (Bracelet :: * -> *) :: * -> * Source #

Enumerable Cycle Source # 

Associated Types

type StructTy (Cycle :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Cycle a -> Cycle a Source #

Enumerable Id Source # 

Associated Types

type StructTy (Id :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Id a -> Id a Source #

Enumerable Unit Source # 

Associated Types

type StructTy (Unit :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Unit a -> Unit a Source #

Enumerable Void Source # 

Associated Types

type StructTy (Void :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Void a -> Void a Source #

Typeable * f => Enumerable (Mu f) Source # 

Associated Types

type StructTy (Mu f :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (Mu f) a -> Mu f a Source #

Typeable * a => Enumerable (Const a) Source # 

Associated Types

type StructTy (Const a :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (Const a) a -> Const a a Source #

(Enumerable f, Functor f, Enumerable g) => Enumerable ((:.:) f g) Source # 

Associated Types

type StructTy ((:.:) f g :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (f :.: g) a -> (f :.: g) a Source #

(Enumerable f, Enumerable g) => Enumerable ((:*:) f g) Source # 

Associated Types

type StructTy ((:*:) f g :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (f :*: g) a -> (f :*: g) a Source #

(Enumerable f, Enumerable g) => Enumerable ((:+:) f g) Source # 

Associated Types

type StructTy ((:+:) f g :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (f :+: g) a -> (f :+: g) a Source #

structureType :: ESpeciesAST -> String Source #

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 enumerate and friends by writing

enumerate s ls :: [T a]

where ls :: [a].

For example,

> structureType octopus
"Comp Cycle []"
> enumerate octopus [1,2,3] :: [Comp Cycle [] Int]
[<[3,2,1]>,<[3,1,2]>,<[2,3,1]>,<[2,1,3]>,<[1,3,2]>
,<[1,2,3]>,<[1],[3,2]>,<[1],[2,3]>,<[3,1],[2]>
,<[1,3],[2]>,<[2,1],[3]>,<[1,2],[3]>,<[2],[1],[3]>
,<[1],[2],[3]>]

Note, however, that providing a type annotation on enumerate in this way is usually only necessary at the ghci prompt; when used in the context of a larger program the type of a call to enumerate can often be inferred.

enumerate :: (Enumerable f, Typeable a, Eq a) => SpeciesAST -> [a] -> [f a] Source #

enumerate s ls computes a complete list of distinct s-structures over the underlying multiset of labels ls. For example:

> enumerate octopi [1,2,3] :: [Comp Cycle [] Int]
[<[3,2,1]>,<[3,1,2]>,<[2,3,1]>,<[2,1,3]>,<[1,3,2]>,<[1,2,3]>,
 <[1],[3,2]>,<[1],[2,3]>,<[3,1],[2]>,<[1,3],[2]>,<[2,1],[3]>,
 <[1,2],[3]>,<[2],[1],[3]>,<[1],[2],[3]>]

> enumerate octopi [1,1,2] :: [Comp Cycle [] Int]
[<[2,1,1]>,<[1,2,1]>,<[1,1,2]>,<[2,1],[1]>,<[1,2],[1]>,
 <[1,1],[2]>,<[1],[1],[2]>]

> enumerate subsets "abc" :: [Set Int]
[{'a','b','c'},{'a','b'},{'a','c'},{'a'},{'b','c'},{'b'},{'c'},{}]

> enumerate simpleGraphs [1,2,3] :: [Comp Set Set 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, they must be cast (using the magic of Data.Typeable) out of an existential wrapper; this is why type annotations are required in all the examples above. Of course, if a call to enumerate is used in the context of some larger program, a type annotation will probably not be needed, due to the magic of type inference.

For help in knowing what type annotation you can give when enumerating the structures of a particular species at the ghci prompt, see the structureType function. To be able to use your own custom data type in an enumeration, just make your data type an instance of the Enumerable type class; this can be done for you automatically by Math.Combinatorics.Species.TH.

If an invalid type annotation is given, enumerate will call error with a helpful error message. This should not be much of an issue in practice, since usually enumerate will be used at a specific type; it's hard to imagine a usage of enumerate which will sometimes work and sometimes fail. However, those who like their functions total can use extractStructure to make a version of enumerate (or the other variants) with a return type of [Either String (f a)] (which will return an annoying ton of duplicate error messages) or Either String [f a] (which has the unfortunate property of being much less lazy than the current versions, since it must compute the entire list before deciding whether to return Left or Right).

For slight variants on enumerate, see enumerateL, enumerateU, and enumerateM.

enumerateL :: (Enumerable f, Typeable a) => SpeciesAST -> [a] -> [f a] Source #

Labeled enumeration: given a species expression and a list of labels (which are assumed to be distinct), compute the list of all structures built from the given labels. If the type given for the enumeration does not match the species expression (via an Enumerable instance), call error with an error message explaining the mismatch. This is slightly more efficient than enumerate for lists of labels which are known to be distinct, since it doesn't have to waste time checking for duplicates. (However, it probably doesn't really make much difference, since the time to do the actual enumeration will usually dwarf the time to process the list of labels anyway.)

For example:

> enumerateL ballots [1,2,3] :: [Comp [] Set Int]
[[{1,2,3}],[{2,3},{1}],[{1},{2,3}],[{2},{1,3}],[{1,3},{2}],[{3},{1,2}]
,[{1,2},{3}],[{3},{2},{1}],[{3},{1},{2}],[{2},{3},{1}],[{2},{1},{3}]
,[{1},{3},{2}],[{1},{2},{3}]]

enumerateU :: Enumerable f => SpeciesAST -> Int -> [f ()] Source #

Unlabeled enumeration: given a species expression and an integer indicating the number of labels to use, compute the list of all unlabeled structures of the given size. If the type given for the enumeration does not match the species expression, call error with an error message explaining the mismatch.

Note that enumerateU s n is equivalent to enumerate s (replicate n ()).

For example:

> enumerateU octopi 4 :: [Comp Cycle [] ()]
[<[(),(),(),()]>,<[(),()],[(),()]>,<[(),(),()],[()]>
,<[(),()],[()],[()]>,<[()],[()],[()],[()]>]

enumerateM :: (Enumerable f, Typeable a) => SpeciesAST -> Multiset a -> [f a] Source #

General enumeration: given a species expression and a multiset of labels, compute the list of all distinct structures built from the given labels. If the type given for the enumeration does not match the species expression, call error with a message explaining the mismatch.

enumerateAll :: Enumerable f => SpeciesAST -> [f Int] Source #

Lazily enumerate all labeled structures, using [1..] as the labels.

For example:

> take 10 $ enumerateAll ballots :: [Comp [] Set Int]
[[],[{1}],[{1,2}],[{2},{1}],[{1},{2}],[{1,2,3}],[{2,3},{1}]
,[{1},{2,3}],[{2},{1,3}],[{1,3},{2}]]

enumerateAllU :: Enumerable f => SpeciesAST -> [f ()] Source #

Lazily enumerate all unlabeled structures.

For example:

> take 10 $ enumerateAllU octopi :: [Comp Cycle [] ()]
[<[()]>,<[(),()]>,<[()],[()]>,<[(),(),()]>,<[(),()],[()]>
,<[()],[()],[()]>,<[(),(),(),()]>,<[(),()],[(),()]>
,<[(),(),()],[()]>,<[(),()],[()],[()]>]

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.

data Void a Source #

The (constantly) void functor.

Instances

Functor Void Source # 

Methods

fmap :: (a -> b) -> Void a -> Void b #

(<$) :: a -> Void b -> Void a #

Enumerable Void Source # 

Associated Types

type StructTy (Void :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Void a -> Void a Source #

Show (Void a) Source # 

Methods

showsPrec :: Int -> Void a -> ShowS #

show :: Void a -> String #

showList :: [Void a] -> ShowS #

type StructTy Void Source # 

data Unit a Source #

The (constantly) unit functor.

Constructors

Unit 

Instances

Functor Unit Source # 

Methods

fmap :: (a -> b) -> Unit a -> Unit b #

(<$) :: a -> Unit b -> Unit a #

Enumerable Unit Source # 

Associated Types

type StructTy (Unit :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Unit a -> Unit a Source #

Show (Unit a) Source # 

Methods

showsPrec :: Int -> Unit a -> ShowS #

show :: Unit a -> String #

showList :: [Unit a] -> ShowS #

type StructTy Unit Source # 

newtype Id a Source #

The identity functor.

Constructors

Id a 

Instances

Functor Id Source # 

Methods

fmap :: (a -> b) -> Id a -> Id b #

(<$) :: a -> Id b -> Id a #

Enumerable Id Source # 

Associated Types

type StructTy (Id :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Id a -> Id a Source #

Show a => Show (Id a) Source # 

Methods

showsPrec :: Int -> Id a -> ShowS #

show :: Id a -> String #

showList :: [Id a] -> ShowS #

type StructTy Id Source # 
type StructTy Id = Id

newtype Const x a Source #

The constant functor.

Constructors

Const x 

Instances

Functor (Const x) Source # 

Methods

fmap :: (a -> b) -> Const x a -> Const x b #

(<$) :: a -> Const x b -> Const x a #

Typeable * a => Enumerable (Const a) Source # 

Associated Types

type StructTy (Const a :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (Const a) a -> Const a a Source #

Show x => Show (Const x a) Source # 

Methods

showsPrec :: Int -> Const x a -> ShowS #

show :: Const x a -> String #

showList :: [Const x a] -> ShowS #

type StructTy (Const a) Source # 
type StructTy (Const a) = Const a

data (f :+: g) a Source #

Functor coproduct.

Constructors

Inl (f a) 
Inr (g a) 

Instances

(Functor f, Functor g) => Functor ((:+:) f g) Source # 

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b #

(<$) :: a -> (f :+: g) b -> (f :+: g) a #

(Enumerable f, Enumerable g) => Enumerable ((:+:) f g) Source # 

Associated Types

type StructTy ((:+:) f g :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (f :+: g) a -> (f :+: g) a Source #

(Show (f a), Show (g a)) => Show ((:+:) f g a) Source # 

Methods

showsPrec :: Int -> (f :+: g) a -> ShowS #

show :: (f :+: g) a -> String #

showList :: [(f :+: g) a] -> ShowS #

type StructTy ((:+:) f g) Source # 
type StructTy ((:+:) f g) = (:+:) (StructTy f) (StructTy g)

data (f :*: g) a Source #

Functor product.

Constructors

(f a) :*: (g a) 

Instances

(Functor f, Functor g) => Functor ((:*:) f g) Source # 

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b #

(<$) :: a -> (f :*: g) b -> (f :*: g) a #

(Enumerable f, Enumerable g) => Enumerable ((:*:) f g) Source # 

Associated Types

type StructTy ((:*:) f g :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (f :*: g) a -> (f :*: g) a Source #

(Show (f a), Show (g a)) => Show ((:*:) f g a) Source # 

Methods

showsPrec :: Int -> (f :*: g) a -> ShowS #

show :: (f :*: g) a -> String #

showList :: [(f :*: g) a] -> ShowS #

type StructTy ((:*:) f g) Source # 
type StructTy ((:*:) f g) = (:*:) (StructTy f) (StructTy g)

data (f :.: g) a Source #

Functor composition.

Constructors

Comp 

Fields

Instances

(Functor f, Functor g) => Functor ((:.:) f g) Source # 

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b #

(<$) :: a -> (f :.: g) b -> (f :.: g) a #

(Enumerable f, Functor f, Enumerable g) => Enumerable ((:.:) f g) Source # 

Associated Types

type StructTy ((:.:) f g :: * -> *) :: * -> * Source #

Methods

iso :: StructTy (f :.: g) a -> (f :.: g) a Source #

Show (f (g a)) => Show ((:.:) f g a) Source # 

Methods

showsPrec :: Int -> (f :.: g) a -> ShowS #

show :: (f :.: g) a -> String #

showList :: [(f :.: g) a] -> ShowS #

type StructTy ((:.:) f g) Source # 
type StructTy ((:.:) f g) = (:.:) (StructTy f) (StructTy g)

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 

Instances

Functor Star Source # 

Methods

fmap :: (a -> b) -> Star a -> Star b #

(<$) :: a -> Star b -> Star a #

Enumerable Star Source # 

Associated Types

type StructTy (Star :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Star a -> Star a Source #

Show a => Show (Star a) Source # 

Methods

showsPrec :: Int -> Star a -> ShowS #

show :: Star a -> String #

showList :: [Star a] -> ShowS #

type StructTy Star Source # 

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 

Fields

Instances

Functor Cycle Source # 

Methods

fmap :: (a -> b) -> Cycle a -> Cycle b #

(<$) :: a -> Cycle b -> Cycle a #

Enumerable Cycle Source # 

Associated Types

type StructTy (Cycle :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Cycle a -> Cycle a Source #

Eq a => Eq (Cycle a) Source # 

Methods

(==) :: Cycle a -> Cycle a -> Bool #

(/=) :: Cycle a -> Cycle a -> Bool #

Show a => Show (Cycle a) Source # 

Methods

showsPrec :: Int -> Cycle a -> ShowS #

show :: Cycle a -> String #

showList :: [Cycle a] -> ShowS #

type StructTy Cycle Source # 

newtype Bracelet a Source #

Bracelet structure. A value of type Bracelet a is implemented as [a], but thought of as an undirected cycle (i.e. equivalent up to rotations as well as flips/reversals).

Constructors

Bracelet 

Fields

Instances

Functor Bracelet Source # 

Methods

fmap :: (a -> b) -> Bracelet a -> Bracelet b #

(<$) :: a -> Bracelet b -> Bracelet a #

Enumerable Bracelet Source # 

Associated Types

type StructTy (Bracelet :: * -> *) :: * -> * Source #

Eq a => Eq (Bracelet a) Source # 

Methods

(==) :: Bracelet a -> Bracelet a -> Bool #

(/=) :: Bracelet a -> Bracelet a -> Bool #

Show a => Show (Bracelet a) Source # 

Methods

showsPrec :: Int -> Bracelet a -> ShowS #

show :: Bracelet a -> String #

showList :: [Bracelet a] -> ShowS #

type StructTy Bracelet Source # 

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 

Fields

Instances

Functor Set Source # 

Methods

fmap :: (a -> b) -> Set a -> Set b #

(<$) :: a -> Set b -> Set a #

Enumerable Set Source # 

Associated Types

type StructTy (Set :: * -> *) :: * -> * Source #

Methods

iso :: StructTy Set a -> Set a Source #

Eq a => Eq (Set a) Source # 

Methods

(==) :: Set a -> Set a -> Bool #

(/=) :: Set a -> Set a -> Bool #

Show a => Show (Set a) Source # 

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

type StructTy Set Source # 

Species AST

Species expressions can be reified into one of several AST types.

data SpeciesAST Source #

A basic, untyped AST type for species expressions, for easily doing things like analysis, simplification, deriving isomorphisms, and so on. Converting between SpeciesAST and the typed variant ESpeciesAST can be done with annotate and erase.

reify :: SpeciesAST -> SpeciesAST Source #

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

> reify octopus
C . TL+
> reify (ksubset 3)
E3 * TE

reflect :: Species s => SpeciesAST -> s Source #

Reflect an AST back into any instance of the Species class.

data TSpeciesAST s Source #

A variant of SpeciesAST with a phantom type parameter which also reflects the structure, so we can write quasi-dependently-typed functions over species, in particular for species enumeration.

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

TSpeciesAST is defined via mutual recursion with SizedSpeciesAST, which pairs a TSpeciesAST with an interval annotation indicating (a conservative approximation of) the label set sizes for which the species actually yields any structures; this information makes enumeration faster and also prevents it from getting stuck in infinite recursion in some cases. A value of SizedSpeciesAST is thus an annotated species expression tree with interval annotations at every node.

data ESpeciesAST Source #

An existential wrapper to hide the phantom type parameter to SizedSpeciesAST, so we can make it an instance of Species.

wrap :: Typeable s => TSpeciesAST s -> ESpeciesAST Source #

Construct an ESpeciesAST from a TSpeciesAST by adding an appropriate interval annotation and hiding the type.

unwrap :: Typeable s => ESpeciesAST -> TSpeciesAST s Source #

Unwrap an existential wrapper to get out a typed AST. You can get out any type you like as long as it is the right one.

CAUTION: Don't try this at home!

erase :: ESpeciesAST -> SpeciesAST Source #

Erase the type and interval information from an existentially wrapped species AST.

erase' :: TSpeciesAST f -> SpeciesAST Source #

Erase the type and interval information from a typed species AST.

annotate :: SpeciesAST -> ESpeciesAST Source #

Reconstruct the type and interval annotations on a species AST.

Species simplification

simplify :: SpeciesAST -> SpeciesAST Source #

Given a species expression s, return a species expression in normal form which represents a species isomorphic to s.

sumOfProducts :: SpeciesAST -> [[SpeciesAST]] Source #

Simplify a species and decompose it into a sum of products.

Recursive species

Tools for dealing with recursive species.

class (Typeable f, Show f, Typeable (Interp f (Mu f))) => ASTFunctor f where Source #

ASTFunctor is a type class for codes which can be interpreted (via the Interp type family) as higher-order functors over species expressions. The apply method allows such codes to be applied to a species AST. The indirection is needed to implement recursive species.

Minimal complete definition

apply

Methods

apply :: Typeable g => f -> TSpeciesAST g -> TSpeciesAST (Interp f g) Source #

type family Interp f (self :: * -> *) :: * -> * Source #

Interpretation type function for codes for higher-order type constructors, used as arguments to the higher-order fixpoint Mu.

newtonRaphsonRec :: (ASTFunctor f, Species s) => f -> Integer -> Maybe s Source #

newtonRaphsonRec f k tries to compute the recursive species represented by the code f up to order at least k, using Newton-Raphson iteration. Returns Nothing if f cannot be written in the form f = X*R(f) for some species R.

newtonRaphson :: Species s => s -> Integer -> s Source #

Given a species r and a desired accuracy k, newtonRaphson r k computes a species which has contact at least k with the species t = x * (r `o` t).