spe-0.5: Combinatorial species lite

MaintainerAnders Claesson <anders.claesson@gmail.com>
Safe HaskellSafe-Inferred

Math.Spe

Contents

Description

License : BSD-3

Species lite

Synopsis

The species type synonym

type Spe a c = [a] -> [c]Source

A combinatorial species is an endofunctor on the category of finite sets and bijections. We approximate this by a function as defined.

Constructions

(.+.) :: Spe a b -> Spe a c -> Spe a (Either b c)Source

Species addition.

assemble :: [Spe a c] -> Spe a cSource

The sum of a list of species of the same type.

(.*.) :: Spe a b -> Spe a c -> Spe a (b, c)Source

Species multiplication.

(<*.) :: Spe a b -> Spe a c -> Spe a (b, c)Source

Ordinal L-species multiplication. Give that the underlying set is sorted , elements in the left factor will be smaller than those in the right factor.

prod :: [Spe a b] -> Spe a [b]Source

The product of a list of species.

ordinalProd :: [Spe a b] -> Spe a [b]Source

The ordinal product of a list of L-species.

(.^) :: Spe a b -> Int -> Spe a [b]Source

The power F^k for species F.

(<^) :: Spe a b -> Int -> Spe a [b]Source

The ordinal power F^k for L-species F.

compose :: Spe [a] b -> Spe a c -> Spe a (b, [c])Source

The composition F(G) of two species F and G.

o :: Spe [a] b -> Spe a c -> Spe a (b, [c])Source

This is just a synonym for compose. It is usually used infix.

kDiff :: Int -> Spe (Maybe a) b -> Spe a bSource

The derivative d^k/dX^k F of a species F.

diff :: Spe (Maybe a) b -> Spe a bSource

The first derivative.

ofSize :: Spe a c -> Int -> Spe a cSource

f ofSize n is like f on n element sets, but empty otherwise.

nonEmpty :: Spe a c -> Spe a cSource

No structure on the empty set, but otherwise the same.

Specific species

set :: Spe a [a]Source

The species of sets.

one :: Spe a ()Source

The species characteristic of the empty set; the identity with respect to species multiplication.

x :: Spe a aSource

The singleton species.

kBal :: Int -> Spe a [[a]]Source

The species of ballots with k blocks

bal :: Spe a [[a]]Source

The species of ballots.

par :: Spe a [[a]]Source

The species of set partitions.

kList :: Int -> Spe a [a]Source

The species of lists (linear orders) with k elements.

list :: Spe a [a]Source

The species of lists (linear orders)

cyc :: Spe a [a]Source

The species of cycles.

perm :: Spe a [[a]]Source

The species of permutations, where a permutation is a set of cycles.

kSubset :: Int -> Spe a ([a], [a])Source

The species of k element subsets.

subset :: Spe a [a]Source

The species of subsets.