species-0.3.2.4: Computational combinatorial species

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

Math.Combinatorics.Species.AST

Contents

Description

Various data structures representing reified combinatorial species expressions. See also Math.Combinatorics.Species.AST.Instances.

Synopsis

Basic species expression AST

data SpeciesAST where 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.

Instances

Eq SpeciesAST

Species expressions can be compared for structural equality. (Note that if s1 and s2 are isomorphic species we do not necessarily have s1 == s2.)

Note, however, that species containing an OfSize constructor will always compare as False with any other species, since we cannot decide function equality.

Ord SpeciesAST

An (arbitrary) Ord instance, so that we can put species expressions in canonical order when simplifying.

Show SpeciesAST

Display species expressions in a nice human-readable form. Note that we commit the unforgivable sin of omitting a corresponding Read instance. This will hopefully be remedied in a future version.

C SpeciesAST

Species expressions are differentiable.

C SpeciesAST

Species expressions form a ring. Well, sort of. Of course the ring laws actually only hold up to isomorphism of species, not up to structural equality.

C SpeciesAST

Species expressions are additive.

Species SpeciesAST

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

Typed, sized species expression AST

data TSpeciesAST s where 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.

Instances

Size annotations

data SizedSpeciesAST s where Source

Constructors

Sized :: Interval -> TSpeciesAST s -> SizedSpeciesAST s 

interval :: TSpeciesAST s -> Interval Source

Given a TSpeciesAST, compute (a conservative approximation of) the interval of label set sizes on which the species yields any structures.

annI :: TSpeciesAST s -> SizedSpeciesAST s Source

Annotate a TSpeciesAST with the interval of label set sizes for which it yields structures.

getI :: SizedSpeciesAST s -> Interval Source

Retrieve the interval annotation from a SizedSpeciesAST.

stripI :: SizedSpeciesAST s -> TSpeciesAST s Source

Strip the interval annotation from a SizedSpeciesAST.

Existentially wrapped AST

data ESpeciesAST where Source

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

Constructors

Wrap :: Typeable s => SizedSpeciesAST s -> ESpeciesAST 

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.

ASTFunctor class (codes for higher-order functors)

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.

Methods

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

Miscellaneous AST operations

needsCI :: SpeciesAST -> Bool Source

needsCI is a predicate which checks whether a species expression uses any of the operations which are not supported directly by ordinary generating functions (composition, differentiation, cartesian product, and functor composition), and hence need cycle index series.

substRec :: ASTFunctor f => f -> SpeciesAST -> SpeciesAST -> SpeciesAST Source

Substitute an expression for recursive occurrences.