combinat-0.2.9.0: Generate and manipulate various combinatorial objects.

Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Groups.Thompson.F

Contents

Description

Thompson's group F.

See eg. https://en.wikipedia.org/wiki/Thompson_groups

Based mainly on James Michael Belk's PhD thesis "THOMPSON'S GROUP F"; see http://www.math.u-psud.fr/~breuilla/Belk.pdf

Synopsis

Tree diagrams

data TDiag Source #

A tree diagram, consisting of two binary trees with the same number of leaves, representing an element of the group F.

Constructors

TDiag 

Fields

  • _width :: !Int

    the width is the number of leaves, minus 1, of both diagrams

  • _domain :: !T

    the top diagram correspond to the domain

  • _range :: !T

    the bottom diagram corresponds to the range

Instances
Eq TDiag Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

(==) :: TDiag -> TDiag -> Bool #

(/=) :: TDiag -> TDiag -> Bool #

Ord TDiag Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

compare :: TDiag -> TDiag -> Ordering #

(<) :: TDiag -> TDiag -> Bool #

(<=) :: TDiag -> TDiag -> Bool #

(>) :: TDiag -> TDiag -> Bool #

(>=) :: TDiag -> TDiag -> Bool #

max :: TDiag -> TDiag -> TDiag #

min :: TDiag -> TDiag -> TDiag #

Show TDiag Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

showsPrec :: Int -> TDiag -> ShowS #

show :: TDiag -> String #

showList :: [TDiag] -> ShowS #

HasWidth TDiag Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

width :: TDiag -> Int Source #

DrawASCII TDiag Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

ascii :: TDiag -> ASCII Source #

mkTDiag :: T -> T -> TDiag Source #

Creates a tree diagram from two trees

mkTDiagDontReduce :: T -> T -> TDiag Source #

Creates a tree diagram, but does not reduce it.

x0 :: TDiag Source #

The generator x0

x1 :: TDiag Source #

The generator x1

xk :: Int -> TDiag Source #

The generators x0, x1, x2 ...

identity :: TDiag Source #

The identity element in the group F

positive :: T -> TDiag Source #

A positive diagram is a diagram whose bottom tree (the range) is a right vine.

inverse :: TDiag -> TDiag Source #

Swaps the top and bottom of a tree diagram. This is the inverse in the group F. (Note: we don't do reduction here, as this operation keeps the reducedness)

equivalent :: TDiag -> TDiag -> Bool Source #

Decides whether two (possibly unreduced) tree diagrams represents the same group element in F.

Reduction of tree diagrams

reduce :: TDiag -> TDiag Source #

Reduces a diagram. The result is a normal form of an element in the group F.

treeCaretList :: T -> [Int] Source #

List of carets at the bottom of the tree, indexed by their left edge position

removeCarets :: [Int] -> T -> T Source #

Remove the carets with the given indices (throws an error if there is no caret at the given index)

Composition of tree diagrams

compose :: TDiag -> TDiag -> TDiag Source #

If diag1 corresponds to the PL function f, and diag2 to g, then compose diag1 diag2 will correspond to (g.f) (note that the order is opposite than normal function composition!)

This is the multiplication in the group F.

composeDontReduce :: TDiag -> TDiag -> TDiag Source #

Compose two tree diagrams without reducing the result

extensionToCommonTree :: T -> T -> ([T], [T]) Source #

Given two binary trees, we return a pair of list of subtrees which, grafted the to leaves of the first (resp. the second) tree, results in the same extended tree.

Subdivions

subdivision1 :: T -> [Rational] Source #

Returns the list of dyadic subdivision points

subdivision2 :: T -> [(Rational, Rational)] Source #

Returns the list of dyadic intervals

Binary trees

data Tree a Source #

A (strict) binary tree with labelled leaves (but unlabelled nodes)

Constructors

Branch !(Tree a) !(Tree a) 
Leaf !a 
Instances
Functor Tree Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

fmap :: (a -> b) -> Tree a -> Tree b #

(<$) :: a -> Tree b -> Tree a #

DrawASCII T Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

ascii :: T -> ASCII Source #

Eq a => Eq (Tree a) Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

(==) :: Tree a -> Tree a -> Bool #

(/=) :: Tree a -> Tree a -> Bool #

Ord a => Ord (Tree a) Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

compare :: Tree a -> Tree a -> Ordering #

(<) :: Tree a -> Tree a -> Bool #

(<=) :: Tree a -> Tree a -> Bool #

(>) :: Tree a -> Tree a -> Bool #

(>=) :: Tree a -> Tree a -> Bool #

max :: Tree a -> Tree a -> Tree a #

min :: Tree a -> Tree a -> Tree a #

Show a => Show (Tree a) Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

HasNumberOfLeaves (Tree a) Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

numberOfLeaves :: Tree a -> Int Source #

HasWidth (Tree a) Source # 
Instance details

Defined in Math.Combinat.Groups.Thompson.F

Methods

width :: Tree a -> Int Source #

graft :: Tree (Tree a) -> Tree a Source #

The monadic join operation of binary trees

listGraft :: [Tree a] -> Tree b -> Tree a Source #

A list version of graft

type T = Tree () Source #

A completely unlabelled binary tree

branch :: T -> T -> T Source #

treeWidth :: Tree a -> Int Source #

The width of the tree is the number of leaves minus 1.

enumerate_ :: Tree a -> Tree Int Source #

Enumerates the leaves a tree, starting from 0

enumerate :: Tree a -> (Int, Tree Int) Source #

Enumerates the leaves a tree, and also returns the number of leaves

rightVine :: Int -> T Source #

"Right vine" of the given width

leftVine :: Int -> T Source #

"Left vine" of the given width

flipTree :: Tree a -> Tree a Source #

Flips each node of a binary tree

Conversion to/from BinTree

toBinTree :: Tree a -> BinTree a Source #

Tree and BinTree are the same type, except that Tree is strict.

TODO: maybe unify these two types? Until that, you can convert between the two with these functions if necessary.

Pattern synonyms

pattern Lf :: Tree () Source #

pattern Br :: forall a. Tree a -> Tree a -> Tree a Source #

pattern Ct :: Tree () Source #

pattern X0 :: TDiag Source #

pattern X1 :: TDiag Source #

ASCII

asciiT :: T -> ASCII Source #

Draws a binary tree, with all leaves at the same (bottom) row

asciiT' :: Bool -> T -> ASCII Source #

Draws a binary tree; when the boolean flag is True, we draw upside down

asciiTLabels :: T -> ASCII Source #

Draws a binary tree, with all leaves at the same (bottom) row, and labelling the leaves starting with 0 (continuing with letters after 9)

asciiTLabels' :: Bool -> T -> ASCII Source #

When the flag is true, we draw upside down

asciiTDiag :: TDiag -> ASCII Source #

Draws a tree diagram