combinat-0.2.10.0: Generate and manipulate various combinatorial objects.
Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Groups.Braid.NF

Description

Normal form of braids, take 1.

We implement the Adyan-Thurston-ElRifai-Morton solution to the word problem in braid groups.

Based on:

Synopsis

Normal form

data BraidNF (n :: Nat) Source #

A unique normal form for braids, called the left-greedy normal form. It looks like Delta^i*P, where Delta is the positive half-twist, i is an integer, and P is a positive word, which can be further decomposed into non-Delta permutation words; these words themselves are not unique, but the permutations they realize are unique.

This will solve the word problem relatively fast, though it is not the fastest known algorithm.

Constructors

BraidNF 

Fields

Instances

Instances details
Eq (BraidNF n) Source # 
Instance details

Defined in Math.Combinat.Groups.Braid.NF

Methods

(==) :: BraidNF n -> BraidNF n -> Bool #

(/=) :: BraidNF n -> BraidNF n -> Bool #

Ord (BraidNF n) Source # 
Instance details

Defined in Math.Combinat.Groups.Braid.NF

Methods

compare :: BraidNF n -> BraidNF n -> Ordering #

(<) :: BraidNF n -> BraidNF n -> Bool #

(<=) :: BraidNF n -> BraidNF n -> Bool #

(>) :: BraidNF n -> BraidNF n -> Bool #

(>=) :: BraidNF n -> BraidNF n -> Bool #

max :: BraidNF n -> BraidNF n -> BraidNF n #

min :: BraidNF n -> BraidNF n -> BraidNF n #

Show (BraidNF n) Source # 
Instance details

Defined in Math.Combinat.Groups.Braid.NF

Methods

showsPrec :: Int -> BraidNF n -> ShowS #

show :: BraidNF n -> String #

showList :: [BraidNF n] -> ShowS #

nfReprWord :: KnownNat n => BraidNF n -> Braid n Source #

A braid word representing the given normal form

braidNormalForm :: KnownNat n => Braid n -> BraidNF n Source #

Computes the normal form of a braid. We apply free reduction first, it should be faster that way.

braidNormalForm' :: KnownNat n => Braid n -> BraidNF n Source #

This function does not apply free reduction before computing the normal form

braidNormalFormNaive' :: KnownNat n => Braid n -> BraidNF n Source #

This one uses the naive inverse replacement method. Probably somewhat slower than braidNormalForm'.

Starting and finishing sets

permWordStartingSet :: Int -> [Int] -> [Int] Source #

The starting set of a positive braid P is the subset of [1..n-1] defined by

S(P) = [ i | P = sigma_i * Q , Q is positive ] = [ i | (sigma_i^-1 * P) is positive ] 

This function returns the starting set a positive word, assuming it is a permutation braid (see Lemma 2.4 in [2])

permWordFinishingSet :: Int -> [Int] -> [Int] Source #

The finishing set of a positive braid P is the subset of [1..n-1] defined by

F(P) = [ i | P = Q * sigma_i , Q is positive ] = [ i | (P * sigma_i^-1) is positive ] 

This function returns the finishing set, assuming the input is a permutation braid

permutationStartingSet :: Permutation -> [Int] Source #

This satisfies

permutationStartingSet p == permWordStartingSet n (_permutationBraid p)

permutationFinishingSet :: Permutation -> [Int] Source #

This satisfies

permutationFinishingSet p == permWordFinishingSet n (_permutationBraid p)