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

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

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

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)

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 # 

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 # 

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

Instances

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

Associated Types

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

Methods

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

type StructTy (Mu f) Source # 
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.