species-0.1: Combinatorial species library

Math.Combinatorics.Species.Types

Contents

Description

Some common types used by the species library.

Synopsis

Lazy multiplication

newtype LazyRing a Source

If T is an instance of Ring, then LazyRing T is isomorphic to T but with a lazy multiplication: 0 * undefined = undefined * 0 = 0.

Constructors

LR 

Fields

unLR :: a
 

Instances

Eq a => Eq (LazyRing a) 
Ord a => Ord (LazyRing a) 
Show a => Show (LazyRing a) 
HasLub (LazyRing a) 
(Eq a, C a) => C (LazyRing a) 
C a => C (LazyRing a) 
(Eq a, C a) => C (LazyRing a) 
C a => C (LazyRing a) 

Series types

newtype EGF Source

Exponential generating functions, for counting labelled species.

Constructors

EGF (T LazyQ) 

Instances

liftEGF2 :: (T LazyQ -> T LazyQ -> T LazyQ) -> EGF -> EGF -> EGFSource

newtype GF Source

Ordinary generating functions, for counting unlabelled species.

Constructors

GF (T Integer) 

Instances

liftGF2 :: (T Integer -> T Integer -> T Integer) -> GF -> GF -> GFSource

newtype CycleIndex Source

Cycle index series.

Constructors

CI (T Rational) 

filterCoeffs :: C a => (Integer -> Bool) -> [a] -> [a]Source

Filter the coefficients of a series according to a predicate.

selectIndex :: (C a, Eq a) => Integer -> [a] -> [a]Source

Set every coefficient of a series to 0 except the selected index. Truncate any trailing zeroes.

Higher-order Show

class Functor f => ShowF f whereSource

When generating species, we build up a functor representing structures of that species; in order to display generated structures, we need to know that applying the computed functor to a Showable type will also yield something Showable.

Methods

showF :: Show a => f a -> StringSource

Instances

ShowF [] 
ShowF Star 
ShowF Cycle 
ShowF Identity 
Show x => ShowF (Const x) 
(ShowF f, ShowF g) => ShowF (Comp f g) 
(ShowF f, ShowF g) => ShowF (Prod f g) 
(ShowF f, ShowF g) => ShowF (Sum f g) 

newtype RawString Source

RawString is like String, but with a Show instance that doesn't add quotes or do any escaping. This is a (somewhat silly) hack needed to implement a ShowF instance for Comp.

Constructors

RawString String 

Instances

Structure functors

Functors used in building up structures for species generation.

newtype Const x a Source

The constant functor.

Constructors

Const x 

Instances

Functor (Const x) 
Show x => ShowF (Const x) 
Show x => Show (Const x a) 

newtype Identity a Source

The identity functor.

Constructors

Identity a 

newtype Sum f g a Source

Functor coproduct.

Constructors

Sum 

Fields

unSum :: Either (f a) (g a)
 

Instances

(Functor f, Functor g) => Functor (Sum f g) 
(ShowF f, ShowF g) => ShowF (Sum f g) 
(Show (f a), Show (g a)) => Show (Sum f g a) 

newtype Prod f g a Source

Functor product.

Constructors

Prod 

Fields

unProd :: (f a, g a)
 

Instances

(Functor f, Functor g) => Functor (Prod f g) 
(ShowF f, ShowF g) => ShowF (Prod f g) 
(Show (f a), Show (g a)) => Show (Prod f g a) 

data Comp f g a Source

Functor composition.

Constructors

Comp 

Fields

unComp :: f (g a)
 

Instances

(Functor f, Functor g) => Functor (Comp f g) 
(ShowF f, ShowF g) => ShowF (Comp f g) 
Show (f (g a)) => Show (Comp f g a) 

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 [a] 

Instances

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

Type-level species

Some constructor-less data types used as indices to SpeciesAlgT to reflect the species structure at the type level. This is the point at which we wish we were doing this in a dependently typed language.

data Z Source

data S n Source

data X Source

data f :+: g Source

data f :*: g Source

data f :.: g Source

data Der f Source

data E Source

data C Source

type family StructureF t :: * -> *Source

StructureF is a type function which maps type-level species descriptions to structure functors. That is, a structure of the species with type-level representation s, on the underlying set a, has type StructureF s a.