fadno-braids-0.0.2: Braid representations in Haskell

Safe HaskellNone
LanguageHaskell2010

Fadno.Braids.Internal

Contents

Synopsis

Generators

data Gen a Source

Braid generator pairing position (absolute or relative) and polarity.

Constructors

Gen 

Fields

_gPos :: a
 
_gPol :: Polarity
 

Instances

Functor Gen Source 
Eq a => Eq (Gen a) Source 
Ord a => Ord (Gen a) Source 
Show a => Show (Gen a) Source 

gPos :: forall a a. Lens (Gen a) (Gen a) a a Source

gPol :: forall a. Lens' (Gen a) Polarity Source

data Polarity Source

Braid generator "power", as (i + 1) "over/under" i. O[ver] == power 1 (i + 1 "over" i) U[nder] = power -1 (i + 1 "under" i)

Constructors

U 
O 

power :: Integral a => Polarity -> a Source

Polarity to signum or "power" in literature.

complement :: Polarity -> Polarity Source

Flip polarity.

Representations

class (Integral b, Monoid (a b)) => Braid a b where Source

Braid representations.

Minimal complete definition

toGens, minIndex, maxIndex, invert

Methods

stepCount :: a b -> Int Source

Length, number of "steps"columnsartin generators.

strandCount :: a b -> b Source

N, braid group index, number of strandsrows"i"s.

toGens :: a b -> [[Gen b]] Source

Common format is a series of "steps" of absolute-indexed generators.

minIndex :: a b -> b Source

Minimum index (i) value

maxIndex :: a b -> b Source

Maximum index (i) value. Note this means values of (i+1) obtain, per generators.

invert :: a b -> a b Source

Invert indices

toArtin :: a b -> Artin b Source

convert to single-gen

toMultiGen :: a b -> MultiGen b Source

convert to multi-gen

Instances

newtype Artin a Source

Braid as "Artin generators" (one-at-a-time).

Constructors

Artin 

Fields

_aGens :: [Gen a]
 

aGens :: forall a a. Iso (Artin a) (Artin a) [Gen a] [Gen a] Source

newtype MultiGen a Source

Steps of many-at-a-time generators.

Constructors

MultiGen 

Fields

_mSteps :: [Step a]
 

data Step a Source

Braid "step" of many-at-a-time generators. Absolute-head-offset-tail structure disallows invalid adjacent generators. Example: 'Step (Gen 1 U) [Gen 0 O]' translates to [s1,s3^-1].

Constructors

Empty 
Step 

Fields

_sHead :: Gen a

Absolute-indexed "top" generator

_sOffsets :: [Gen Natural]

(offset + 2)-indexed tail generators.

Instances

Eq a => Eq (Step a) Source 
Show a => Show (Step a) Source 
Integral a => Monoid (Step a) Source 
Integral a => Ixed (Step a) Source 
type IxValue (Step a) = Polarity Source 
type Index (Step a) = a Source 

mSteps :: forall a a. Iso (MultiGen a) (MultiGen a) [Step a] [Step a] Source

insertWithS :: forall a. Integral a => (Polarity -> Polarity -> Polarity) -> Gen a -> Step a -> Step a Source

Insert a gen at absolute index into a Step. Ignores invalid indices, uses function with new, old value for update.

insertS :: Integral a => Gen a -> Step a -> Step a Source

Insert a gen at absolute index into a Step. Ignores invalid indices, overwrites on update.

lookupS :: Integral a => a -> Step a -> Maybe Polarity Source

Lookup by absolute index in a Step.

deleteS :: Integral a => a -> Step a -> Step a Source

Delete/clear a gen at absolute index.

stepGens :: Integral a => Iso' (Step a) [Gen a] Source

Iso for valid constructions.

stepToGens :: Integral a => Step a -> [Gen a] Source

translate Step to absolute-indexed gens.

gensToStep :: Integral a => [Gen a] -> Step a Source

translate absolute-indexed gens to Step. Drops invalid values.

data DimBraid b a Source

Braid with explicit dimensions (mainly for empty steps/strands)

Constructors

DimBraid 

Fields

_dBraid :: b a
 
_dSteps :: Int
 
_dStrands :: a
 

Instances

(Integral a, Braid b a) => Braid (DimBraid b) a Source 
(Eq a, Eq (b a)) => Eq (DimBraid b a) Source 
(Show a, Show (b a)) => Show (DimBraid b a) Source 
(Monoid (b a), Integral a) => Monoid (DimBraid b a) Source 

dim :: Braid b a => b a -> DimBraid b a Source

Make DimBraid using braid's dimensions.

dBraid :: forall b a b. Lens (DimBraid b a) (DimBraid b a) (b a) (b a) Source

dSteps :: forall b a. Lens' (DimBraid b a) Int Source

dStrands :: forall b a. Lens' (DimBraid b a) a Source

Strands, loops, weaves

type Weave a = (a, Polarity) Source

Instruction to send the value "over" or "under" to the next value in a Strand or Loop. Newtyping is undesirable, want to keep Pair instances.

class ToWeaves w a where Source

Extract a list of weaves.

Methods

toWeaves :: w -> [Weave a] Source

Instances

data Strand a Source

Concrete braid strand presentation as values delimited by polarities.

Constructors

Strand 

Fields

_sWeaves :: [Weave a]
 
_sLast :: a
 

strand :: (Integral a, Braid b a) => a -> b a -> Strand a Source

Extract a single strand from a braid.

strand' :: Integral a => a -> [[Gen a]] -> Strand a Source

Strand from gen matrix.

strands :: (Integral a, Braid b a) => b a -> [Strand a] Source

Extract all strands from a braid.

sWeaves :: forall a. Lens' (Strand a) [Weave a] Source

sLast :: forall a. Lens' (Strand a) a Source

newtype Loop a Source

Capture strands into a loop, where _sLast of one strand is the first value of the next. Foldable instance ignores "last" values of strands (since they will equal the next head).

Constructors

Loop 

Fields

_lStrands :: [Strand a]
 

toLoops :: (Eq a, Show a) => [Strand a] -> [Loop a] Source

Find loops in strands.

lStrands :: forall a a. Iso (Loop a) (Loop a) [Strand a] [Strand a] Source

Moves/isotopy

data Move b i Source

A la Reidemeister.

Constructors

Move (b i) (b i) 

Instances

Eq (b i) => Eq (Move b i) Source 
Show (b i) => Show (Move b i) Source 
Field2 (Move b i) (Move b i) (b i) (b i) Source 
Field1 (Move b i) (Move b i) (b i) (b i) Source 

inverse :: Move b i -> Move b i Source

Flip a move

moveH :: Braid a i => Move a i -> i Source

Move "height" or strand count

moveW :: Braid a i => Move a i -> Int Source

Move "width" or step count

data Loc a Source

Coordinate in braid.

Constructors

Loc 

Fields

_lx :: Int
 
_ly :: a
 

Instances

Eq a => Eq (Loc a) Source 
Ord a => Ord (Loc a) Source 
Show a => Show (Loc a) Source 
Field2 (Loc a) (Loc a) a a Source 
Field1 (Loc a) (Loc a) Int Int Source 

lx :: forall a. Lens' (Loc a) Int Source

ly :: forall a a. Lens (Loc a) (Loc a) a a Source