Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
defintion of free products over Oriented
symbols with exponents in a Number
.
Note On Oriented
structures the canonical injection inj
and projection
prj
are bijections between the valid
entities of Path
and
.
This is not true betwenn Product
N
Path
and
asProductForm
N
>>>
prj (P 3 :^ 2 :: ProductForm N Q) :: Path Q
Path () [3,3]
and
>>>
prj (P 3 :* P 3 :: ProductForm N Q) :: Path Q
Path () [3,3]
both map to the same Path
! But
>>>
let p = make (P 3) :: Product N Q in p * p == p ^ 2
True
Synopsis
- data Product r a
- prLength :: Product N a -> N
- prFactor :: Product N a -> N -> a
- prFactors :: Product N a -> [a]
- prwrd :: (Integral r, Oriented a) => Product r a -> Word r a
- nProduct :: (Hom Ort h, Multiplicative x) => h a x -> Product N a -> x
- zProduct :: (Hom Ort h, Cayleyan x) => h a x -> Product Z a -> x
- prdMapTotal :: (Singleton (Point y), Oriented y, Integral r) => (x -> y) -> Product r x -> Product r y
- prFromOp :: Product r (Op a) -> Product r a
- newtype Word r a = Word [(a, r)]
- fromWord :: Word r a -> [(a, r)]
- prfwrd :: Integral r => ProductForm r a -> Word r a
- wrdprf :: Semiring r => Point a -> Word r a -> ProductForm r a
- wrdPrfGroup :: (Eq a, Semiring r) => Word r a -> Rdc (Word r a)
- nFactorize :: N -> Word N N
- nFactorize' :: N -> N -> Word N N
- data ProductForm r a
- = One (Point a)
- | P a
- | (ProductForm r a) :^ r
- | (ProductForm r a) :* (ProductForm r a)
- prfLength :: Number r => ProductForm r a -> N
- prfDepth :: ProductForm r a -> N
- prfFactors :: ProductForm N a -> [a]
- nProductForm :: (Hom Ort h, Multiplicative x) => h a x -> ProductForm N a -> x
- zProductForm :: (Hom Ort h, Cayleyan x) => h a x -> ProductForm Z a -> x
- prfInverse :: Number r => ProductForm r a -> ProductForm r a
- prfFromOp :: ProductForm r (Op a) -> ProductForm r a
- prfMapTotal :: Singleton (Point y) => (x -> ProductForm r y) -> ProductForm r x -> ProductForm r y
- prfReduce :: (Oriented a, Integral r) => ProductForm r a -> ProductForm r a
- prfReduceWith :: (Oriented a, Integral r) => (Word r a -> Rdc (Word r a)) -> ProductForm r a -> ProductForm r a
- prfopr :: (x -> t -> x) -> x -> ProductForm N t -> x
- prfopr' :: N -> (x -> t -> x) -> x -> ProductForm N t -> x
- prfopl :: (t -> x -> x) -> ProductForm N t -> x -> x
- prfopl' :: N -> (t -> x -> x) -> ProductForm N t -> x -> x
Product
free product over Oriented
symbols in a
with exponents in a Integral
r
.
Definition A Product
p
is valid
if and only if its underlying
ProductForm
pf
is valid
and pf
is reduced, i.e. pf ==
.reduce
pf
Instances
prLength :: Product N a -> N Source #
number of primary factors where where all simple factors are expanded according to there exponent.
prFactor :: Product N a -> N -> a Source #
the n
-th primary factor where all simple factors are expanded according to there
exponent.
nProduct :: (Hom Ort h, Multiplicative x) => h a x -> Product N a -> x Source #
mapping a product with exponents in N
into a Multiplicative
structure
applying a homomorphism between Oriented
structures.
prdMapTotal :: (Singleton (Point y), Oriented y, Integral r) => (x -> y) -> Product r x -> Product r y Source #
mapping a product.
prFromOp :: Product r (Op a) -> Product r a Source #
from Op
symbols.
Property For every Oriented
structure a
and Integral
r
the resulting
map prFromOp
is a contravariant homomorphisms between Multiplicative
structures.
Word
list of symbols in a
together with an exponent in r
.
Word [(a, r)] |
prfwrd :: Integral r => ProductForm r a -> Word r a Source #
transforming a ProductForm
to its corresponding Word
.
wrdprf :: Semiring r => Point a -> Word r a -> ProductForm r a Source #
transforming a Word
to it corresponding ProductForm
.
wrdPrfGroup :: (Eq a, Semiring r) => Word r a -> Rdc (Word r a) Source #
reducing a Word
by adding the exponents of consecutive equal symbols and
eliminating symbols with zero exponents.
nFactorize :: N -> Word N N Source #
factorization of a natural number to powers of primes.
For 0
there will be thrown Undefined
.
factorization of a natural number to powers of primes smaller then the given bound.
For 0
there will be thrown Undefined
.
Form
data ProductForm r a Source #
form for a free product over Oriented
symbols in a
with exponents in r
.
Definition Let r
be a Number
. A ProductForm
pf
is valid
if and only if
is orientation
pfvalid
(see definition below) and all
its symbols x
- where
occurs in P
xpf
- are valid
.
The orientation
of pf
is defined according:
orientation pf = case pf of One p -> one p P a -> orientation a f :^ r -> orientation f ^ r where (^) = power f :* g -> orientation f * orientation g
Note Number
is required for -1
, 0
and 1
are not degenerated as in Z/2
or
Z/1
.
One (Point a) | |
P a | |
(ProductForm r a) :^ r infixl 9 | |
(ProductForm r a) :* (ProductForm r a) infixr 7 |
Instances
prfDepth :: ProductForm r a -> N Source #
depth.
prfFactors :: ProductForm N a -> [a] Source #
list of elementary factors.
nProductForm :: (Hom Ort h, Multiplicative x) => h a x -> ProductForm N a -> x Source #
mapping a product form with exponents in N
into a Multiplicative
structure
applying a homomorphism between Oriented
structures.
zProductForm :: (Hom Ort h, Cayleyan x) => h a x -> ProductForm Z a -> x Source #
prfInverse :: Number r => ProductForm r a -> ProductForm r a Source #
formal inverse
Let p
in
then:ProductForm
r a
Pre If p
contains a factor
then P
a
.minusOne
/=
Nothing
Post the formal inverse.
prfFromOp :: ProductForm r (Op a) -> ProductForm r a Source #
from Op
symbols.
prfMapTotal :: Singleton (Point y) => (x -> ProductForm r y) -> ProductForm r x -> ProductForm r y Source #
mapping a product form
Reduction
prfReduce :: (Oriented a, Integral r) => ProductForm r a -> ProductForm r a Source #
reducing a ProductForm
according to
.prfReduceWith
return
prfReduceWith :: (Oriented a, Integral r) => (Word r a -> Rdc (Word r a)) -> ProductForm r a -> ProductForm r a Source #
reduces a product form by the given reduction rules for words until no more reductions are applicable.
Operations
prfopr :: (x -> t -> x) -> x -> ProductForm N t -> x Source #
applicative operation from the right.
prfopl :: (t -> x -> x) -> ProductForm N t -> x -> x Source #
applicative operation from the left.