oalg-base-1.1.4.0: Algebraic structures on oriented entities and limits as a tool kit to solve algebraic problems.
Copyright(c) Erich Gut
LicenseBSD3
Maintainerzerich.gut@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

OAlg.Entity.Product.Definition

Description

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 Product N. This is not true betwenn Path and ProductForm N as

>>> 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

Product

data Product r a Source #

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

Instances details
(Oriented a, Integral r) => Embeddable a (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

inj :: a -> Product r a Source #

Foldable (Product N) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

fold :: Monoid m => Product N m -> m #

foldMap :: Monoid m => (a -> m) -> Product N a -> m #

foldMap' :: Monoid m => (a -> m) -> Product N a -> m #

foldr :: (a -> b -> b) -> b -> Product N a -> b #

foldr' :: (a -> b -> b) -> b -> Product N a -> b #

foldl :: (b -> a -> b) -> b -> Product N a -> b #

foldl' :: (b -> a -> b) -> b -> Product N a -> b #

foldr1 :: (a -> a -> a) -> Product N a -> a #

foldl1 :: (a -> a -> a) -> Product N a -> a #

toList :: Product N a -> [a] #

null :: Product N a -> Bool #

length :: Product N a -> Int #

elem :: Eq a => a -> Product N a -> Bool #

maximum :: Ord a => Product N a -> a #

minimum :: Ord a => Product N a -> a #

sum :: Num a => Product N a -> a #

product :: Num a => Product N a -> a #

Sequence (Product N) N a Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

graph :: p N -> Product N a -> Graph N a Source #

list :: p N -> Product N a -> [(a, N)] Source #

(??) :: Product N a -> N -> Maybe a Source #

(Oriented a, Integral r) => Embeddable (Path a) (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

inj :: Path a -> Product r a Source #

Oriented a => Projectible (Path a) (Product N a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

prj :: Product N a -> Path a Source #

(Oriented a, Entity r) => Show (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

showsPrec :: Int -> Product r a -> ShowS #

show :: Product r a -> String #

showList :: [Product r a] -> ShowS #

(Oriented a, Entity r) => Eq (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

(==) :: Product r a -> Product r a -> Bool #

(/=) :: Product r a -> Product r a -> Bool #

(Oriented a, OrdPoint a, Ord a, Ord r, Entity r) => Ord (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

compare :: Product r a -> Product r a -> Ordering #

(<) :: Product r a -> Product r a -> Bool #

(<=) :: Product r a -> Product r a -> Bool #

(>) :: Product r a -> Product r a -> Bool #

(>=) :: Product r a -> Product r a -> Bool #

max :: Product r a -> Product r a -> Product r a #

min :: Product r a -> Product r a -> Product r a #

(Oriented a, Integral r) => Constructable (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

make :: Form (Product r a) -> Product r a Source #

Exposable (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Associated Types

type Form (Product r a) Source #

Methods

form :: Product r a -> Form (Product r a) Source #

LengthN (Product N a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

lengthN :: Product N a -> N Source #

(Oriented a, Integral r) => Validable (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

valid :: Product r a -> Statement Source #

(Oriented a, Integral r) => Entity (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

(Oriented a, Integral r) => Exponential (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Associated Types

type Exponent (Product r a) Source #

Methods

(^) :: Product r a -> Exponent (Product r a) -> Product r a Source #

(Oriented a, Integral r, Ring r) => Cayleyan (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

(Oriented a, Integral r, Ring r) => Invertible (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

tryToInvert :: Product r a -> Solver (Product r a) Source #

invert :: Product r a -> Product r a Source #

isInvertible :: Product r a -> Bool Source #

zpower :: Product r a -> Z -> Product r a Source #

(Oriented a, Integral r) => Multiplicative (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

one :: Point (Product r a) -> Product r a Source #

(*) :: Product r a -> Product r a -> Product r a Source #

npower :: Product r a -> N -> Product r a Source #

(Oriented a, Integral r) => Oriented (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Associated Types

type Point (Product r a) Source #

Methods

orientation :: Product r a -> Orientation (Point (Product r a)) Source #

start :: Product r a -> Point (Product r a) Source #

end :: Product r a -> Point (Product r a) Source #

type Form (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

type Form (Product r a) = ProductForm r a
type Exponent (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

type Exponent (Product r a) = r
type Point (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

type Point (Product r a) = Point a

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.

prFactors :: Product N a -> [a] Source #

the list of primary factors.

prwrd :: (Integral r, Oriented a) => Product r a -> Word r a Source #

restriction of prfwrd.

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.

zProduct :: (Hom Ort h, Cayleyan x) => h a x -> Product Z a -> x Source #

mapping a product with exponents in Z into a Cayleyan 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

newtype Word r a Source #

list of symbols in a together with an exponent in r.

Constructors

Word [(a, r)] 

Instances

Instances details
(Show a, Show r) => Show (Word r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

showsPrec :: Int -> Word r a -> ShowS #

show :: Word r a -> String #

showList :: [Word r a] -> ShowS #

(Eq a, Eq r) => Eq (Word r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

(==) :: Word r a -> Word r a -> Bool #

(/=) :: Word r a -> Word r a -> Bool #

(Validable a, Validable r) => Validable (Word r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

valid :: Word r a -> Statement Source #

fromWord :: Word r a -> [(a, r)] Source #

the underlying list of a's with their exponent.

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.

Note the Point is needed for empty Words.

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.

nFactorize' Source #

Arguments

:: N

bound for the primes

-> N

a natural number

-> Word N N 

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 orientation pf is valid (see definition below) and all its symbols x - where P x occurs in pf - 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.

Constructors

One (Point a) 
P a 
(ProductForm r a) :^ r infixl 9 
(ProductForm r a) :* (ProductForm r a) infixr 7 

Instances

Instances details
Embeddable a (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

inj :: a -> ProductForm r a Source #

Foldable (ProductForm N) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

fold :: Monoid m => ProductForm N m -> m #

foldMap :: Monoid m => (a -> m) -> ProductForm N a -> m #

foldMap' :: Monoid m => (a -> m) -> ProductForm N a -> m #

foldr :: (a -> b -> b) -> b -> ProductForm N a -> b #

foldr' :: (a -> b -> b) -> b -> ProductForm N a -> b #

foldl :: (b -> a -> b) -> b -> ProductForm N a -> b #

foldl' :: (b -> a -> b) -> b -> ProductForm N a -> b #

foldr1 :: (a -> a -> a) -> ProductForm N a -> a #

foldl1 :: (a -> a -> a) -> ProductForm N a -> a #

toList :: ProductForm N a -> [a] #

null :: ProductForm N a -> Bool #

length :: ProductForm N a -> Int #

elem :: Eq a => a -> ProductForm N a -> Bool #

maximum :: Ord a => ProductForm N a -> a #

minimum :: Ord a => ProductForm N a -> a #

sum :: Num a => ProductForm N a -> a #

product :: Num a => ProductForm N a -> a #

Sequence (ProductForm N) N x Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

graph :: p N -> ProductForm N x -> Graph N x Source #

list :: p N -> ProductForm N x -> [(x, N)] Source #

(??) :: ProductForm N x -> N -> Maybe x Source #

Embeddable (GLT x) (ProductForm N (Transformation x)) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Embeddable (Path a) (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

inj :: Path a -> ProductForm r a Source #

Oriented a => Projectible (Path a) (ProductForm N a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

prj :: ProductForm N a -> Path a Source #

(Oriented a, Entity r) => Show (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

showsPrec :: Int -> ProductForm r a -> ShowS #

show :: ProductForm r a -> String #

showList :: [ProductForm r a] -> ShowS #

(Oriented a, Entity r) => Eq (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

(==) :: ProductForm r a -> ProductForm r a -> Bool #

(/=) :: ProductForm r a -> ProductForm r a -> Bool #

(Oriented a, Entity r, Ord a, OrdPoint a, Ord r) => Ord (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

compare :: ProductForm r a -> ProductForm r a -> Ordering #

(<) :: ProductForm r a -> ProductForm r a -> Bool #

(<=) :: ProductForm r a -> ProductForm r a -> Bool #

(>) :: ProductForm r a -> ProductForm r a -> Bool #

(>=) :: ProductForm r a -> ProductForm r a -> Bool #

max :: ProductForm r a -> ProductForm r a -> ProductForm r a #

min :: ProductForm r a -> ProductForm r a -> ProductForm r a #

LengthN (ProductForm N a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

lengthN :: ProductForm N a -> N Source #

(Oriented a, Integral r) => Reducible (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

reduce :: ProductForm r a -> ProductForm r a Source #

(Oriented a, Number r) => Validable (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

(Oriented a, Number r) => Entity (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

(Oriented a, Number r) => Oriented (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Associated Types

type Point (ProductForm r a) Source #

Integral r => Embeddable (ProductForm N a) (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

inj :: ProductForm N a -> ProductForm r a Source #

Integral r => Projectible (ProductForm N a) (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Methods

prj :: ProductForm r a -> ProductForm N a Source #

type Point (ProductForm r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

type Point (ProductForm r a) = Point a

prfLength :: Number r => ProductForm r a -> N Source #

length.

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 #

mapping a product form with exponents in Z into a Cayleyan structure applying a homomorphism between Oriented structures.

prfInverse :: Number r => ProductForm r a -> ProductForm r a Source #

formal inverse

Let p in ProductForm r a then:

Pre If p contains a factor P a then 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.

prfopr' :: N -> (x -> t -> x) -> x -> ProductForm N t -> x Source #

partially strict version of prfopr, i.e. every n-th application will be reduced to head normal form.

Let x' = prfopr' n op x p.

Pre 0 < n.

Post x' == prfopr op x p.

prfopl :: (t -> x -> x) -> ProductForm N t -> x -> x Source #

applicative operation from the left.

prfopl' :: N -> (t -> x -> x) -> ProductForm N t -> x -> x Source #

partially strict version of prfopl, i.e. every n-th application will be reduced to head normal form.

Let x' = prfopl' n op p x.

Pre 0 < n.

Post x' == prfopl op p x.