species-0.3.3: Computational combinatorial species

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

Math.Combinatorics.Species.Structures

Contents

Description

Types used for expressing generic structures when enumerating species.

Synopsis

Structure functors

Functors used in building up structures for species 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

data Unit a Source

The (constantly) unit functor.

Constructors

Unit 

Instances

newtype Const x a Source

The constant functor.

Constructors

Const x 

Instances

Functor (Const x) 
Typeable * a => Enumerable (Const a) 
Show x => Show (Const x a) 
Typeable (* -> * -> *) Const 
type StructTy (Const a) = Const a 

newtype Id a Source

The identity functor.

Constructors

Id a 

Instances

Functor Id 
Enumerable Id 
Show a => Show (Id a) 
Typeable (* -> *) Id 
type StructTy Id = Id 

data (f :+: g) a Source

Functor coproduct.

Constructors

Inl (f a) 
Inr (g a) 

Instances

(Functor f, Functor g) => Functor ((:+:) f g) 
(Enumerable f, Enumerable g) => Enumerable ((:+:) f g) 
Typeable ((* -> *) -> (* -> *) -> * -> *) (:+:) 
(Show (f a), Show (g a)) => Show ((:+:) f g a) 
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) 
(Enumerable f, Enumerable g) => Enumerable ((:*:) f g) 
Typeable ((* -> *) -> (* -> *) -> * -> *) (:*:) 
(Show (f a), Show (g a)) => Show ((:*:) f g a) 
type StructTy ((:*:) f g) = (:*:) (StructTy f) (StructTy g) 

data (f :.: g) a Source

Functor composition.

Constructors

Comp 

Fields

unComp :: f (g a)
 

Instances

(Functor f, Functor g) => Functor ((:.:) f g) 
(Enumerable f, Functor f, Enumerable g) => Enumerable ((:.:) f g) 
Typeable ((* -> *) -> (* -> *) -> * -> *) (:.:) 
Show (f (g a)) => Show ((:.:) f g a) 
type StructTy ((:.:) f g) = (:.:) (StructTy f) (StructTy g) 

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

getCycle :: [a]
 

Instances

Functor Cycle 
Enumerable Cycle 
Eq a => Eq (Cycle a) 
Show a => Show (Cycle a) 
Typeable (* -> *) Cycle 
type StructTy Cycle = Cycle 

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

getBracelet :: [a]
 

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

getSet :: [a]
 

Instances

Functor Set 
Enumerable Set 
Eq a => Eq (Set a) 
Show a => Show (Set a) 
Typeable (* -> *) Set 
type StructTy Set = Set 

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

data Mu f a Source

Higher-order fixpoint. Mu f a is morally isomorphic to f (Mu f) a, except that we actually need a level of indirection. In fact Mu f a is isomorphic to Interp f (Mu f) a; f is a code which is interpreted by the Interp type function.

Constructors

Mu 

Fields

unMu :: Interp f (Mu f) a
 

Instances

Typeable * f => Enumerable (Mu f) 
Typeable (* -> * -> *) Mu 
type StructTy (Mu f) = Mu f 

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.