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

Math.Combinat.Groups.Braid

Description

Braids. See eg. https://en.wikipedia.org/wiki/Braid_group

Based on:

Note: This module GHC 7.8, since we use type-level naturals to parametrize the Braid type.

Synopsis

Artin generators

data BrGen Source #

A standard Artin generator of a braid: Sigma i represents twisting the neighbour strands i and (i+1), such that strand i goes under strand (i+1).

Note: The strands are numbered 1..n.

Constructors

Sigma !Int

i goes under (i+1)

SigmaInv !Int

i goes above (i+1)

Instances

Instances details
Eq BrGen Source # 
Instance details

Defined in Math.Combinat.Groups.Braid

Methods

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

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

Ord BrGen Source # 
Instance details

Defined in Math.Combinat.Groups.Braid

Methods

compare :: BrGen -> BrGen -> Ordering #

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

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

(>) :: BrGen -> BrGen -> Bool #

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

max :: BrGen -> BrGen -> BrGen #

min :: BrGen -> BrGen -> BrGen #

Show BrGen Source # 
Instance details

Defined in Math.Combinat.Groups.Braid

Methods

showsPrec :: Int -> BrGen -> ShowS #

show :: BrGen -> String #

showList :: [BrGen] -> ShowS #

brGenIdx :: BrGen -> Int Source #

The strand (more precisely, the first of the two strands) the generator twistes

invBrGen :: BrGen -> BrGen Source #

The inverse of a braid generator

The braid type

newtype Braid (n :: Nat) Source #

The braid group B_n on n strands. The number n is encoded as a type level natural in the type parameter.

Braids are represented as words in the standard generators and their inverses.

Constructors

Braid [BrGen] 

Instances

Instances details
Show (Braid n) Source # 
Instance details

Defined in Math.Combinat.Groups.Braid

Methods

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

show :: Braid n -> String #

showList :: [Braid n] -> ShowS #

KnownNat n => DrawASCII (Braid n) Source # 
Instance details

Defined in Math.Combinat.Groups.Braid

Methods

ascii :: Braid n -> ASCII Source #

numberOfStrands :: KnownNat n => Braid n -> Int Source #

The number of strands in the braid

data SomeBraid Source #

Sometimes we want to hide the type-level parameter n, for example when dynamically creating braids whose size is known only at runtime.

Constructors

forall n.KnownNat n => SomeBraid (Braid n) 

someBraid :: Int -> (forall (n :: Nat). KnownNat n => Braid n) -> SomeBraid Source #

withSomeBraid :: SomeBraid -> (forall n. KnownNat n => Braid n -> a) -> a Source #

mkBraid :: (forall n. KnownNat n => Braid n -> a) -> Int -> [BrGen] -> a Source #

withBraid :: Int -> (forall (n :: Nat). KnownNat n => Braid n) -> (forall (n :: Nat). KnownNat n => Braid n -> a) -> a Source #

extend :: n1 <= n2 => Braid n1 -> Braid n2 Source #

Embeds a smaller braid group into a bigger braid group

freeReduceBraidWord :: Braid n -> Braid n Source #

Apply "free reduction" to the word, that is, iteratively remove sigma_i sigma_i^-1 pairs. The resulting braid is clearly equivalent to the original.

Some specific braids

sigma :: KnownNat n => Int -> Braid (n :: Nat) Source #

The braid generator sigma_i as a braid

sigmaInv :: KnownNat n => Int -> Braid (n :: Nat) Source #

The braid generator sigma_i^(-1) as a braid

doubleSigma :: KnownNat n => Int -> Int -> Braid (n :: Nat) Source #

doubleSigma s t (for s<t)is the generator sigma_{s,t} in Birman-Ko-Lee's "new presentation". It twistes the strands s and t while going over all other strands. For t==s+1 we get back sigma s

positiveWord :: KnownNat n => [Int] -> Braid (n :: Nat) Source #

positiveWord [2,5,1] is shorthand for the word sigma_2*sigma_5*sigma_1.

halfTwist :: KnownNat n => Braid n Source #

The (positive) half-twist of all the braid strands, usually denoted by Delta.

_halfTwist :: Int -> [Int] Source #

The untyped version of halfTwist

tau :: KnownNat n => Braid n -> Braid n Source #

The inner automorphism defined by tau(X) = Delta^-1 X Delta, where Delta is the positive half-twist.

This sends each generator sigma_j to sigma_(n-j).

tauPerm :: Permutation -> Permutation Source #

The involution tau on permutations (permutation braids)

Group operations

identity :: Braid n Source #

The trivial braid

inverse :: Braid n -> Braid n Source #

The inverse of a braid. Note: we do not perform reduction here, as a word is reduced if and only if its inverse is reduced.

compose :: Braid n -> Braid n -> Braid n Source #

Composes two braids, doing free reduction on the result (that is, removing (sigma_k * sigma_k^-1) pairs@)

composeDontReduce :: Braid n -> Braid n -> Braid n Source #

Composes two braids without doing any reduction.

Braid permutations

isPureBraid :: KnownNat n => Braid n -> Bool Source #

A braid is pure if its permutation is trivial

braidPermutation :: KnownNat n => Braid n -> Permutation Source #

Returns the left-to-right permutation associated to the braid. We follow the strands from the left to the right (or from the top to the bottom), and return the permutation taking the left side to the right side.

This is compatible with right (standard) action of the permutations: permuteRight (braidPermutationRight b1) corresponds to the left-to-right permutation of the strands; also:

(braidPermutation b1) `multiply` (braidPermutation b2) == braidPermutation (b1 `compose` b2)

Writing the right numbering of the strands below the left numbering, we got the two-line notation of the permutation.

_braidPermutation :: Int -> [Int] -> Permutation Source #

This is an untyped version of braidPermutation

Permutation braids

isPositiveBraidWord :: KnownNat n => Braid n -> Bool Source #

A positive braid word contains only positive (Sigma) generators.

isPermutationBraid :: KnownNat n => Braid n -> Bool Source #

A permutation braid is a positive braid where any two strands cross at most one, and positively.

_isPermutationBraid :: Int -> [Int] -> Bool Source #

Untyped version of isPermutationBraid for positive words.

permutationBraid :: KnownNat n => Permutation -> Braid n Source #

For any permutation this functions returns a permutation braid realizing that permutation. Note that this is not unique, so we make an arbitrary choice (except for the permutation [n,n-1..1] reversing the order, in which case the result must be the half-twist braid).

The resulting braid word will have a length at most choose n 2 (and will have that length only for the permutation [n,n-1..1])

braidPermutationRight (permutationBraid perm) == perm
isPermutationBraid    (permutationBraid perm) == True

_permutationBraid' :: Permutation -> [[Int]] Source #

Returns the individual "phases" of the a permutation braid realizing the given permutation.

linkingMatrix :: KnownNat n => Braid n -> UArray (Int, Int) Int Source #

We compute the linking numbers between all pairs of strands:

linkingMatrix braid ! (i,j) == strandLinking braid i j 

_linkingMatrix :: Int -> [BrGen] -> UArray (Int, Int) Int Source #

Untyped version of linkingMatrix

strandLinking :: KnownNat n => Braid n -> Int -> Int -> Int Source #

The linking number between two strands numbered i and j (numbered such on the left side).

Growth

bronfmanH :: Int -> [Int] Source #

Bronfman's recursive formula for the reciprocial of the growth function of positive braids. It was already known (by Deligne) that these generating functions are reciprocials of polynomials; Bronfman [1] gave a recursive formula for them.

let count n l = length $ nub $ [ braidNormalForm w | w <- allPositiveBraidWords n l ]
let convertPoly (1:cs) = zip (map negate cs) [1..]
pseries' (convertPoly $ bronfmanH n) == expandBronfmanH n == [ count n l | l <- [0..] ] 
  • [1] Aaron Bronfman: Growth functions of a class of monoids. Preprint, 2001

bronfmanHsList :: [[Int]] Source #

An infinite list containing the Bronfman polynomials:

bronfmanH n = bronfmanHsList !! n

expandBronfmanH :: Int -> [Int] Source #

Expands the reciprocial of H(n) into an infinite power series, giving the growth function of the positive braids on n strands.

ASCII diagram

horizBraidASCII :: KnownNat n => Braid n -> ASCII Source #

Horizontal braid diagram, drawn from left to right, with strands numbered from the bottom to the top

horizBraidASCII' :: KnownNat n => Bool -> Braid n -> ASCII Source #

Horizontal braid diagram, drawn from left to right. The boolean flag indicates whether to flip the strands vertically (True means bottom-to-top, False means top-to-bottom)

List of all words

allPositiveBraidWords :: KnownNat n => Int -> [Braid n] Source #

All positive braid words of the given length

allBraidWords :: KnownNat n => Int -> [Braid n] Source #

All braid words of the given length

_allBraidWords :: Int -> Int -> [[BrGen]] Source #

Untyped version of allBraidWords

Random braids

randomBraidWord :: (RandomGen g, KnownNat n) => Int -> g -> (Braid n, g) Source #

Random braid word of the given length

randomPositiveBraidWord :: (RandomGen g, KnownNat n) => Int -> g -> (Braid n, g) Source #

Random positive braid word of the given length

randomPerturbBraidWord :: forall n g. (RandomGen g, KnownNat n) => Int -> Braid n -> g -> (Braid n, g) Source #

Given a braid word, we perturb it randomly m times using the braid relations, so that the resulting new braid word is equivalent to the original.

Useful for testing.

withRandomBraidWord Source #

Arguments

:: RandomGen g 
=> (forall n. KnownNat n => Braid n -> a) 
-> Int

number of strands

-> Int

length of the random word

-> g 
-> (a, g) 

This version of randomBraidWord may be convenient to avoid the type level stuff

withRandomPositiveBraidWord Source #

Arguments

:: RandomGen g 
=> (forall n. KnownNat n => Braid n -> a) 
-> Int

number of strands

-> Int

length of the random word

-> g 
-> (a, g) 

This version of randomPositiveBraidWord may be convenient to avoid the type level stuff

_randomBraidWord Source #

Arguments

:: RandomGen g 
=> Int

number of strands

-> Int

length of the random word

-> g 
-> ([BrGen], g) 

Untyped version of randomBraidWord

_randomPositiveBraidWord Source #

Arguments

:: RandomGen g 
=> Int

number of strands

-> Int

length of the random word

-> g 
-> ([BrGen], g) 

Untyped version of randomPositiveBraidWord