HaskellForMaths-0.4.4: Combinatorics, group theory, commutative algebra, non-commutative algebra

Safe HaskellSafe-Infered

Math.Combinatorics.CombinatorialHopfAlgebra

Description

A module defining the following Combinatorial Hopf Algebras, together with coalgebra or Hopf algebra morphisms between them:

  • SSym, the Malvenuto-Reutnenauer Hopf algebra of permutations
  • YSym, the (dual of the) Loday-Ronco Hopf algebra of binary trees
  • QSym, the Hopf algebra of quasi-symmetric functions (having a basis indexed by compositions)
  • Sh, the Shuffle Hopf algebra

Synopsis

Documentation

newtype Shuffle a Source

A basis for the shuffle algebra. As a vector space, the shuffle algebra is identical to the tensor algebra. However, we consider a different algebra structure, based on the shuffle product. Together with the deconcatenation coproduct, this leads to a Hopf algebra structure.

Constructors

Sh [a] 

Instances

(Eq k, Num k, Ord a) => HopfAlgebra k (Shuffle a) 
(Eq k, Num k, Ord a) => Bialgebra k (Shuffle a) 
(Eq k, Num k, Ord a) => Coalgebra k (Shuffle a) 
(Eq k, Num k, Ord a) => Algebra k (Shuffle a) 
Eq a => Eq (Shuffle a) 
Ord a => Ord (Shuffle a) 
Show a => Show (Shuffle a) 

sh :: [a] -> Vect Q (Shuffle a)Source

Construct a basis element of the shuffle algebra

shuffles :: [a] -> [a] -> [[a]]Source

deconcatenations :: [a] -> [([a], [a])]Source

newtype SSymF Source

The fundamental basis for the Malvenuto-Reutenauer Hopf algebra of permutations, SSym.

Constructors

SSymF [Int] 

Instances

Eq SSymF 
Ord SSymF 
Show SSymF 
(Eq k, Num k) => HopfAlgebra k SSymF 
(Eq k, Num k) => Bialgebra k SSymF 
(Eq k, Num k) => Coalgebra k SSymF 
(Eq k, Num k) => Algebra k SSymF 

ssymF :: [Int] -> Vect Q SSymFSource

Construct a fundamental basis element in SSym. The list of ints must be a permutation of [1..n], eg [1,2], [3,4,2,1].

prop_Associative :: Eq t => (t -> t -> t) -> (t, t, t) -> BoolSource

flatten :: (Enum t, Num t, Ord a) => [a] -> [t]Source

newtype SSymM Source

An alternative "monomial" basis for the Malvenuto-Reutenauer Hopf algebra of permutations, SSym. This basis is related to the fundamental basis by Mobius inversion in the poset of permutations with the weak order.

Constructors

SSymM [Int] 

Instances

Eq SSymM 
Ord SSymM 
Show SSymM 
(Eq k, Num k) => HopfAlgebra k SSymM 
(Eq k, Num k) => Bialgebra k SSymM 
(Eq k, Num k) => Coalgebra k SSymM 
(Eq k, Num k) => Algebra k SSymM 

ssymM :: [Int] -> Vect Q SSymMSource

Construct a monomial basis element in SSym. The list of ints must be a permutation of [1..n], eg [1,2], [3,4,2,1].

inversions :: (Enum t, Num t, Ord a) => [a] -> [(t, t)]Source

weakOrder :: (Ord a1, Ord a) => [a] -> [a1] -> BoolSource

mu :: (Eq a, Num a1) => ([a], a -> a -> Bool) -> a -> a -> a1Source

toSSymF :: (Eq k, Num k) => Vect k SSymM -> Vect k SSymFSource

Convert an element of SSym represented in the monomial basis to the fundamental basis

toSSymM :: (Eq k, Num k) => Vect k SSymF -> Vect k SSymMSource

Convert an element of SSym represented in the fundamental basis to the monomial basis

data PBT a Source

A type for (rooted) planar binary trees. The basis elements of the Loday-Ronco Hopf algebra are indexed by these.

Although the trees are labelled, we're really only interested in the shapes of the trees, and hence in the type PBT (). The Algebra, Coalgebra and HopfAlgebra instances all ignore the labels. However, it is convenient to allow labels, as they can be useful for seeing what is going on, and they also make it possible to define various ways to create trees from lists of labels.

Constructors

T (PBT a) a (PBT a) 
E 

Instances

Functor PBT 
Eq a => Eq (PBT a) 
Ord a => Ord (PBT a) 
Show a => Show (PBT a) 

newtype YSymF a Source

The fundamental basis for (the dual of) the Loday-Ronco Hopf algebra of binary trees, YSym.

Constructors

YSymF (PBT a) 

Instances

Functor YSymF 
(Eq k, Num k, Ord a) => HopfAlgebra k (YSymF a) 
(Eq k, Num k, Ord a) => Bialgebra k (YSymF a) 
(Eq k, Num k, Ord a) => Coalgebra k (YSymF a) 
(Eq k, Num k, Ord a) => Algebra k (YSymF a) 
Eq a => Eq (YSymF a) 
Ord a => Ord (YSymF a) 
Show a => Show (YSymF a) 

ysymF :: PBT a -> Vect Q (YSymF a)Source

Construct the element of YSym in the fundamental basis indexed by the given tree

nodecount :: Num a => PBT t -> aSource

leafcount :: Num a => PBT t -> aSource

prefix :: PBT a -> [a]Source

shapeSignature :: Num t => PBT t1 -> [t]Source

lrCountTree :: Num a => PBT t -> PBT (a, a)Source

numbered :: Num a => PBT t -> PBT aSource

splits :: PBT a -> [(PBT a, PBT a)]Source

multisplits :: (Eq a, Num a) => a -> PBT a1 -> [[PBT a1]]Source

graft :: [PBT a] -> PBT a -> PBT aSource

newtype YSymM Source

An alternative monomial basis for (the dual of) the Loday-Ronco Hopf algebra of binary trees, YSym.

Constructors

YSymM (PBT ()) 

Instances

Eq YSymM 
Ord YSymM 
Show YSymM 
(Eq k, Num k) => HopfAlgebra k YSymM 
(Eq k, Num k) => Bialgebra k YSymM 
(Eq k, Num k) => Coalgebra k YSymM 
(Eq k, Num k) => Algebra k YSymM 

ysymM :: PBT () -> Vect Q YSymMSource

Construct the element of YSym in the monomial basis indexed by the given tree

trees :: (Enum t, Eq t, Num t) => t -> [PBT ()]Source

covers :: PBT a -> [PBT a]Source

The covering relation for the Tamari partial order on binary trees

tamariUpSet :: Ord a => PBT a -> [PBT a]Source

The up-set of a binary tree in the Tamari partial order

toYSymF :: (Eq k, Num k) => Vect k YSymM -> Vect k (YSymF ())Source

Convert an element of YSym represented in the monomial basis to the fundamental basis

toYSymM :: (Eq k, Num k) => Vect k (YSymF ()) -> Vect k YSymMSource

Convert an element of YSym represented in the fundamental basis to the monomial basis

compositions :: Int -> [[Int]]Source

List the compositions of an integer n. For example, the compositions of 4 are [[1,1,1,1],[1,1,2],[1,2,1],[1,3],[2,1,1],[2,2],[3,1],[4]]

quasiShuffles :: [Int] -> [Int] -> [[Int]]Source

newtype QSymM Source

A type for the monomial basis for the quasi-symmetric functions, indexed by compositions.

Constructors

QSymM [Int] 

Instances

Eq QSymM 
Ord QSymM 
Show QSymM 
(Eq k, Num k) => HopfAlgebra k QSymM 
(Eq k, Num k) => Bialgebra k QSymM 
(Eq k, Num k) => Coalgebra k QSymM 
(Eq k, Num k) => Algebra k QSymM 

qsymM :: [Int] -> Vect Q QSymMSource

Construct the element of QSym in the monomial basis indexed by the given composition

coarsenings :: Num a => [a] -> [[a]]Source

newtype QSymF Source

Constructors

QSymF [Int] 

Instances

Eq QSymF 
Ord QSymF 
Show QSymF 
(Eq k, Num k) => HopfAlgebra k QSymF 
(Eq k, Num k) => Bialgebra k QSymF 
(Eq k, Num k) => Coalgebra k QSymF 
(Eq k, Num k) => Algebra k QSymF 

qsymF :: [Int] -> Vect Q QSymFSource

Construct the element of QSym in the fundamental basis indexed by the given composition

toQSymF :: (Eq k, Num k) => Vect k QSymM -> Vect k QSymFSource

Convert an element of QSym represented in the monomial basis to the fundamental basis

toQSymM :: (Eq k, Num k) => Vect k QSymF -> Vect k QSymMSource

Convert an element of QSym represented in the fundamental basis to the monomial basis

xvars :: (Enum a, Num a, Show a) => a -> [GlexPoly Q [Char]]Source

quasiSymM :: (Integral b, Num a) => [a] -> [b] -> aSource

descendingTree :: Ord t => [t] -> PBT tSource

descendingTreeMap :: (Eq k, Num k) => Vect k SSymF -> Vect k (YSymF ())Source

A Hopf algebra morphism from SSymF to YSymF

minPerm :: Num a => PBT t -> [a]Source

maxPerm :: Num a => PBT t -> [a]Source

leftLeafCompositionMap :: (Eq k, Num k) => Vect k (YSymF a) -> Vect k QSymFSource

A Hopf algebra morphism from YSymF to QSymF

descents :: Ord b => [b] -> [Int]Source

descentMap :: (Eq k, Num k) => Vect k SSymF -> Vect k QSymFSource

A Hopf algebra morphism from SSymF to QSymF

under :: PBT a -> PBT a -> PBT aSource

ysymmToSh :: Functor f => f YSymM -> f (Shuffle (PBT ()))Source