Safe Haskell | None |
---|---|
Language | Haskell2010 |
Normal form of braids, take 1.
We implement the Adyan-Thurston-ElRifai-Morton solution to the word problem in braid groups.
Based on:
- [1] Joan S. Birman, Tara E. Brendle: BRAIDS - A SURVEY https://www.math.columbia.edu/~jb/Handbook-21.pdf (chapter 5.1)
- [2] Elsayed A. Elrifai, Hugh R. Morton: Algorithms for positive braids
Synopsis
- data BraidNF (n :: Nat) = BraidNF {
- _nfDeltaExp :: !Int
- _nfPerms :: [Permutation]
- nfReprWord :: KnownNat n => BraidNF n -> Braid n
- braidNormalForm :: KnownNat n => Braid n -> BraidNF n
- braidNormalForm' :: KnownNat n => Braid n -> BraidNF n
- braidNormalFormNaive' :: KnownNat n => Braid n -> BraidNF n
- permWordStartingSet :: Int -> [Int] -> [Int]
- permWordFinishingSet :: Int -> [Int] -> [Int]
- permutationStartingSet :: Permutation -> [Int]
- permutationFinishingSet :: Permutation -> [Int]
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.
BraidNF | |
|
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)