fadno-braids-0.0.5: 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

Instances

Functor Gen Source # 

Methods

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

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

Eq a => Eq (Gen a) Source # 

Methods

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

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

Ord a => Ord (Gen a) Source # 

Methods

compare :: Gen a -> Gen a -> Ordering #

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

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

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

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

max :: Gen a -> Gen a -> Gen a #

min :: Gen a -> Gen a -> Gen a #

Show a => Show (Gen a) Source # 

Methods

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

show :: Gen a -> String #

showList :: [Gen a] -> ShowS #

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 a, Monoid (br a)) => Braid br a where Source #

Braid representations.

Minimal complete definition

toGens, minIndex, maxIndex, invert

Methods

stepCount :: br a -> Int Source #

Length, number of "steps"columnsartin generators.

strandCount :: br a -> a Source #

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

toGens :: br a -> [[Gen a]] Source #

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

minIndex :: br a -> a Source #

Minimum index (i) value

maxIndex :: br a -> a Source #

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

invert :: br a -> br a Source #

Invert indices

toArtin :: br a -> Artin a Source #

convert to single-gen

toMultiGen :: br a -> MultiGen a Source #

convert to multi-gen

newtype Artin a Source #

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

Constructors

Artin 

Fields

Instances

Functor Artin Source # 

Methods

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

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

Foldable Artin Source # 

Methods

fold :: Monoid m => Artin m -> m #

foldMap :: Monoid m => (a -> m) -> Artin a -> m #

foldr :: (a -> b -> b) -> b -> Artin a -> b #

foldr' :: (a -> b -> b) -> b -> Artin a -> b #

foldl :: (b -> a -> b) -> b -> Artin a -> b #

foldl' :: (b -> a -> b) -> b -> Artin a -> b #

foldr1 :: (a -> a -> a) -> Artin a -> a #

foldl1 :: (a -> a -> a) -> Artin a -> a #

toList :: Artin a -> [a] #

null :: Artin a -> Bool #

length :: Artin a -> Int #

elem :: Eq a => a -> Artin a -> Bool #

maximum :: Ord a => Artin a -> a #

minimum :: Ord a => Artin a -> a #

sum :: Num a => Artin a -> a #

product :: Num a => Artin a -> a #

Integral a => Braid Artin a Source # 
Eq a => Eq (Artin a) Source # 

Methods

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

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

Show a => Show (Artin a) Source # 

Methods

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

show :: Artin a -> String #

showList :: [Artin a] -> ShowS #

Monoid (Artin a) Source # 

Methods

mempty :: Artin a #

mappend :: Artin a -> Artin a -> Artin a #

mconcat :: [Artin a] -> Artin 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

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

Instances

Eq a => Eq (Step a) Source # 

Methods

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

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

Show a => Show (Step a) Source # 

Methods

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

show :: Step a -> String #

showList :: [Step a] -> ShowS #

Integral a => Monoid (Step a) Source # 

Methods

mempty :: Step a #

mappend :: Step a -> Step a -> Step a #

mconcat :: [Step a] -> Step a #

Integral a => Ixed (Step a) Source # 

Methods

ix :: Index (Step a) -> Traversal' (Step a) (IxValue (Step a)) #

type IxValue (Step a) Source # 
type IxValue (Step a) = Polarity
type Index (Step a) Source # 
type Index (Step a) = a

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

Instances

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

Methods

(==) :: DimBraid b a -> DimBraid b a -> Bool #

(/=) :: DimBraid b a -> DimBraid b a -> Bool #

(Show a, Show (b a)) => Show (DimBraid b a) Source # 

Methods

showsPrec :: Int -> DimBraid b a -> ShowS #

show :: DimBraid b a -> String #

showList :: [DimBraid b a] -> ShowS #

(Monoid (b a), Integral a) => Monoid (DimBraid b a) Source # 

Methods

mempty :: DimBraid b a #

mappend :: DimBraid b a -> DimBraid b a -> DimBraid b a #

mconcat :: [DimBraid b a] -> DimBraid b a #

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.

Minimal complete definition

toWeaves

Methods

toWeaves :: w -> [Weave a] Source #

Instances

ToWeaves [Weave a] a Source # 

Methods

toWeaves :: [Weave a] -> [Weave a] Source #

ToWeaves (Strand a) a Source # 

Methods

toWeaves :: Strand a -> [Weave a] Source #

ToWeaves (Loop a) a Source # 

Methods

toWeaves :: Loop a -> [Weave a] Source #

data Strand a Source #

Concrete braid strand presentation as values delimited by polarities.

Constructors

Strand 

Fields

Instances

Functor Strand Source # 

Methods

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

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

Foldable Strand Source # 

Methods

fold :: Monoid m => Strand m -> m #

foldMap :: Monoid m => (a -> m) -> Strand a -> m #

foldr :: (a -> b -> b) -> b -> Strand a -> b #

foldr' :: (a -> b -> b) -> b -> Strand a -> b #

foldl :: (b -> a -> b) -> b -> Strand a -> b #

foldl' :: (b -> a -> b) -> b -> Strand a -> b #

foldr1 :: (a -> a -> a) -> Strand a -> a #

foldl1 :: (a -> a -> a) -> Strand a -> a #

toList :: Strand a -> [a] #

null :: Strand a -> Bool #

length :: Strand a -> Int #

elem :: Eq a => a -> Strand a -> Bool #

maximum :: Ord a => Strand a -> a #

minimum :: Ord a => Strand a -> a #

sum :: Num a => Strand a -> a #

product :: Num a => Strand a -> a #

Traversable Strand Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Strand a -> f (Strand b) #

sequenceA :: Applicative f => Strand (f a) -> f (Strand a) #

mapM :: Monad m => (a -> m b) -> Strand a -> m (Strand b) #

sequence :: Monad m => Strand (m a) -> m (Strand a) #

Eq a => Eq (Strand a) Source # 

Methods

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

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

Show a => Show (Strand a) Source # 

Methods

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

show :: Strand a -> String #

showList :: [Strand a] -> ShowS #

ToWeaves (Strand a) a Source # 

Methods

toWeaves :: Strand a -> [Weave a] Source #

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

Instances

Functor Loop Source # 

Methods

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

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

Foldable Loop Source # 

Methods

fold :: Monoid m => Loop m -> m #

foldMap :: Monoid m => (a -> m) -> Loop a -> m #

foldr :: (a -> b -> b) -> b -> Loop a -> b #

foldr' :: (a -> b -> b) -> b -> Loop a -> b #

foldl :: (b -> a -> b) -> b -> Loop a -> b #

foldl' :: (b -> a -> b) -> b -> Loop a -> b #

foldr1 :: (a -> a -> a) -> Loop a -> a #

foldl1 :: (a -> a -> a) -> Loop a -> a #

toList :: Loop a -> [a] #

null :: Loop a -> Bool #

length :: Loop a -> Int #

elem :: Eq a => a -> Loop a -> Bool #

maximum :: Ord a => Loop a -> a #

minimum :: Ord a => Loop a -> a #

sum :: Num a => Loop a -> a #

product :: Num a => Loop a -> a #

Eq a => Eq (Loop a) Source # 

Methods

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

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

Show a => Show (Loop a) Source # 

Methods

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

show :: Loop a -> String #

showList :: [Loop a] -> ShowS #

Monoid (Loop a) Source # 

Methods

mempty :: Loop a #

mappend :: Loop a -> Loop a -> Loop a #

mconcat :: [Loop a] -> Loop a #

ToWeaves (Loop a) a Source # 

Methods

toWeaves :: Loop a -> [Weave a] Source #

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 # 

Methods

(==) :: Move b i -> Move b i -> Bool #

(/=) :: Move b i -> Move b i -> Bool #

Show (b i) => Show (Move b i) Source # 

Methods

showsPrec :: Int -> Move b i -> ShowS #

show :: Move b i -> String #

showList :: [Move b i] -> ShowS #

Field2 (Move b i) (Move b i) (b i) (b i) Source # 

Methods

_2 :: Lens (Move b i) (Move b i) (b i) (b i) #

Field1 (Move b i) (Move b i) (b i) (b i) Source # 

Methods

_1 :: Lens (Move b i) (Move b i) (b i) (b i) #

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

Instances

Eq a => Eq (Loc a) Source # 

Methods

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

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

Ord a => Ord (Loc a) Source # 

Methods

compare :: Loc a -> Loc a -> Ordering #

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

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

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

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

max :: Loc a -> Loc a -> Loc a #

min :: Loc a -> Loc a -> Loc a #

Show a => Show (Loc a) Source # 

Methods

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

show :: Loc a -> String #

showList :: [Loc a] -> ShowS #

Field2 (Loc a) (Loc a) a a Source # 

Methods

_2 :: Lens (Loc a) (Loc a) a a #

Field1 (Loc a) (Loc a) Int Int Source # 

Methods

_1 :: Lens (Loc a) (Loc a) Int Int #

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

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