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.Matrix.GeneralLinearGroup

Description

general linear group GL and elementary transformations over a Galoisian structure.

Synopsis

Transformation

data Transformation x where Source #

elementary linear transformation over a Distributive structure x.

Property Let f be in Transformation x then holds:

  1. If f matches Permute r c p then holds:

    1. h <= It n where (_,h) = span nProxy p and n = lengthN c.
    2. r == c <* p.
  2. If f matches Scale d k s then holds:

    1. k < lengthN d.
    2. s is an endo at d ? k.
    3. s is valid.
  3. If f matches Shear d k l g then holds:

    1. k < lengthN d and l < lengthN d.
    2. k < l.
    3. g is valid.

Note Shear d k l (GL2 s t u v) represents the square matrix m of dimension d where m k k == s, m k l == t, m l k == u, m l l == v and for all i, j not in [k,l] holds: If i /= j then m i j is zero else m i i is one.

Constructors

Permute :: Distributive x => Dim x (Point x) -> Dim x (Point x) -> Permutation N -> Transformation x 
Scale :: Distributive x => Dim x (Point x) -> N -> Inv x -> Transformation x 
Shear :: Galoisian x => Dim x (Point x) -> N -> N -> GL2 x -> Transformation x 

GL

type GL x = Inv (Matrix x) Source #

general linear groupoid of matrices.

data GL2 x Source #

the general linear group of 2x2 matrices for a Galoisian structure x.

Property Let GL2 s t u v be in GL2 x for a Galoisian structure x, then holds: s*v - u*t is invertible.

Example Let g = GL2 3 5 4 7 :: GL2 Z:

>>> invert g
 GL2 7 -5 -4 3
>>> g * invert g
GL2 1 0 0 1

which is the one in GL2 Z.

Note

GL2 (s t u v) represents the 2x2-matrix

   [s t]
   [u v]

and is obtained by GL2GL.

Constructors

GL2 x x x x 

Instances

Instances details
Show x => Show (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

showsPrec :: Int -> GL2 x -> ShowS #

show :: GL2 x -> String #

showList :: [GL2 x] -> ShowS #

Eq x => Eq (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

(==) :: GL2 x -> GL2 x -> Bool #

(/=) :: GL2 x -> GL2 x -> Bool #

Ord x => Ord (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

compare :: GL2 x -> GL2 x -> Ordering #

(<) :: GL2 x -> GL2 x -> Bool #

(<=) :: GL2 x -> GL2 x -> Bool #

(>) :: GL2 x -> GL2 x -> Bool #

(>=) :: GL2 x -> GL2 x -> Bool #

max :: GL2 x -> GL2 x -> GL2 x #

min :: GL2 x -> GL2 x -> GL2 x #

(Galoisian x, TransposableDistributive x) => Transposable (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

transpose :: GL2 x -> GL2 x Source #

Galoisian x => Validable (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

valid :: GL2 x -> Statement Source #

Galoisian x => Entity (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Galoisian x => Exponential (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Exponent (GL2 x) Source #

Methods

(^) :: GL2 x -> Exponent (GL2 x) -> GL2 x Source #

Galoisian x => Cayleyan (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Galoisian x => Invertible (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

tryToInvert :: GL2 x -> Solver (GL2 x) Source #

invert :: GL2 x -> GL2 x Source #

isInvertible :: GL2 x -> Bool Source #

zpower :: GL2 x -> Z -> GL2 x Source #

Galoisian x => Multiplicative (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

one :: Point (GL2 x) -> GL2 x Source #

(*) :: GL2 x -> GL2 x -> GL2 x Source #

npower :: GL2 x -> N -> GL2 x Source #

(Galoisian x, TransposableDistributive x) => TransposableMultiplicative (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Galoisian x => Oriented (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Point (GL2 x) Source #

Methods

orientation :: GL2 x -> Orientation (Point (GL2 x)) Source #

start :: GL2 x -> Point (GL2 x) Source #

end :: GL2 x -> Point (GL2 x) Source #

Galoisian x => Total (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

(Galoisian x, TransposableDistributive x) => TransposableOriented (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type Exponent (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type Exponent (GL2 x) = Z
type Point (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type Point (GL2 x) = Point x

GLT

data GLT x Source #

quotient groupoid of the free groupoid of Transformation (see FTGLT) given by the relations:

Property Let g be in GLT, then holds:

  1. For all exponents z in form g holds: 0 < z.

Example Let d = dim [()] ^ 10 :: Dim' Z, a = permuteFT d d (swap 2 8), b = permuteFT d d (swap 2 3) and c = permuteFT d d (swap 2 3 * swap 2 8) then:

>>> a * b == c
False

but in GLT holds: let a' = amap FTGLT a, b' = amap FTGLT b and c' = amap FTGLT c in

>>> a' * b' == c'
True

and

>>> amap GLTGL (a' * b') == amap GLTGL a' * amap GLTGL b'
True

Note: As a consequence of the property (1.), GLT can be canonically embedded via prj . form - in to ProductForm N (Transformation x).

Instances

Instances details
Oriented x => Show (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

showsPrec :: Int -> GLT x -> ShowS #

show :: GLT x -> String #

showList :: [GLT x] -> ShowS #

Oriented x => Eq (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

(==) :: GLT x -> GLT x -> Bool #

(/=) :: GLT x -> GLT x -> Bool #

Oriented x => Constructable (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

make :: Form (GLT x) -> GLT x Source #

Exposable (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Form (GLT x) Source #

Methods

form :: GLT x -> Form (GLT x) Source #

Oriented x => Validable (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

valid :: GLT x -> Statement Source #

Oriented x => Entity (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Oriented x => Exponential (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Exponent (GLT x) Source #

Methods

(^) :: GLT x -> Exponent (GLT x) -> GLT x Source #

Oriented x => Cayleyan (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Oriented x => Invertible (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

tryToInvert :: GLT x -> Solver (GLT x) Source #

invert :: GLT x -> GLT x Source #

isInvertible :: GLT x -> Bool Source #

zpower :: GLT x -> Z -> GLT x Source #

Oriented x => Multiplicative (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

one :: Point (GLT x) -> GLT x Source #

(*) :: GLT x -> GLT x -> GLT x Source #

npower :: GLT x -> N -> GLT x Source #

Oriented x => Oriented (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Point (GLT x) Source #

Methods

orientation :: GLT x -> Orientation (Point (GLT x)) Source #

start :: GLT x -> Point (GLT x) Source #

end :: GLT x -> Point (GLT x) Source #

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

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type Form (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type Form (GLT x) = GLTForm x
type Exponent (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type Exponent (GLT x) = Z
type Point (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type Point (GLT x) = Dim x (Point x)

permute :: Distributive x => Dim' x -> Dim' x -> Permutation N -> GLT x Source #

permutation of the given dimensions.

Property Let r, c be in Dim' x and p in Permutation N for a Distributive structure x, then holds: If Permute r c p is valid then permute r c p is valid.

Example Let t = permute r c p with Permute r c p is valid then its associated matrix (see GLTGL) has the orientation c :> r and the form

           k         l
  [1                          ]
  [  .                        ]
  [    .                      ]
  [     1                     ]
  [                 1         ] k
  [         1                 ]
  [           .               ]
  [             .             ]
  [               1           ]
  [       1                   ] l
  [                    1      ]
  [                      .    ]
  [                        .  ]
  [                          1]

Note r dose not have to be equal to c, but from r == c <* p follows that both have the same length.

permuteFT :: Distributive x => Dim' x -> Dim' x -> Permutation N -> FT x Source #

the induce element in the free groupoid of transformations.

scale :: Distributive x => Dim' x -> N -> Inv x -> GLT x Source #

scaling.

Property Let d be in Dim' x, k in N and s in Inv x, then holds: If Scale d k s is valid then scale d k s is valid.

Example Let t = scale d k s with Scale d k s is valid then its associated matrix (see GLTGL) is an endo with dimension d and has the form

          k         
  [1               ]
  [  .             ]
  [    .           ]
  [     1          ]
  [      s'        ] k
  [         1      ]
  [           .    ]
  [             .  ]
  [               1]

where s' = (inj :: Inv x -> x) s.

shear :: Galoisian x => Dim' x -> N -> N -> GL2 x -> GLT x Source #

shearing.

Property Let d be in Dim' x, k, l in N and g in GL2 x then holds: If Shear d k l g is valid then shear d k l g is valid.

Example Let t = shear d k l g where Shear d k l g is valid then its associated matrix (see GLTGL) is an endo with dimension d and has the form

           k         l
  [1                          ]
  [  .                        ]
  [    .                      ]
  [     1                     ]
  [       s         t         ] k
  [         1                 ]
  [           .               ]
  [             .             ]
  [               1           ]
  [       u         v         ] l
  [                    1      ]
  [                      .    ]
  [                        .  ]
  [                          1]

rdcGLTForm :: Oriented x => GLTForm x -> GLTForm x Source #

reduces a GLTForm x to its normal form.

Property Let f be in GLTForm x for a Oriented structure x, then holds:

  1. rdcGLTForm (rdcGLTForm f) == rdcGLTForm f.
  2. For all exponents z in rdcGLTForm f holds: 0 < z.

gltfTrsp :: TransposableDistributive r => GLTForm r -> GLTForm r Source #

transposition of a product of elementary transformation.

FT

type FT x = Product Z (Transformation x) Source #

the free groupoid of Transformations.

Homomorphism

Ort

data TrApp x y where Source #

Oriented homomorphisms.

Constructors

TrFT :: Oriented x => TrApp (Transformation x) (FT x) 
TrGL :: Distributive x => TrApp (Transformation x) (GL x) 
TrGLT :: Oriented x => TrApp (Transformation x) (GLT x) 

Instances

Instances details
Applicative TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

amap :: TrApp a b -> a -> b Source #

EmbeddableMorphismTyp TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Morphism TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type ObjectClass TrApp Source #

Eq2 TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

eq2 :: TrApp x y -> TrApp x y -> Bool Source #

Show2 TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

show2 :: TrApp a b -> String Source #

Validable2 TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

valid2 :: TrApp x y -> Statement Source #

Entity2 TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

HomOriented TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

pmap :: TrApp a b -> Point a -> Point b Source #

EmbeddableMorphism TrApp Typ Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

EmbeddableMorphism TrApp Ort Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Show (TrApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

showsPrec :: Int -> TrApp x y -> ShowS #

show :: TrApp x y -> String #

showList :: [TrApp x y] -> ShowS #

Eq (TrApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

(==) :: TrApp x y -> TrApp x y -> Bool #

(/=) :: TrApp x y -> TrApp x y -> Bool #

Validable (TrApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

valid :: TrApp x y -> Statement Source #

(Typeable x, Typeable y) => Entity (TrApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type ObjectClass TrApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

trGLT :: Oriented x => Transformation x -> GLT x Source #

the induced element of the groupoid GLT.

Mlt

data GLApp x y where Source #

Multiplicative homomorphisms.

Constructors

FTGL :: Distributive x => GLApp (FT x) (GL x) 
FTGLT :: Oriented x => GLApp (FT x) (GLT x) 
GLTGL :: Distributive x => GLApp (GLT x) (GL x) 
GL2GL :: Galoisian x => GLApp (GL2 x) (GL x) 

Instances

Instances details
Applicative GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

amap :: GLApp a b -> a -> b Source #

EmbeddableMorphismTyp GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Morphism GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type ObjectClass GLApp Source #

Eq2 GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

eq2 :: GLApp x y -> GLApp x y -> Bool Source #

Show2 GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

show2 :: GLApp a b -> String Source #

Validable2 GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

valid2 :: GLApp x y -> Statement Source #

Entity2 GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

HomMultiplicative GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

HomOriented GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

pmap :: GLApp a b -> Point a -> Point b Source #

EmbeddableMorphism GLApp Typ Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

EmbeddableMorphism GLApp Mlt Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

EmbeddableMorphism GLApp Ort Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Show (GLApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

showsPrec :: Int -> GLApp x y -> ShowS #

show :: GLApp x y -> String #

showList :: [GLApp x y] -> ShowS #

Eq (GLApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

(==) :: GLApp x y -> GLApp x y -> Bool #

(/=) :: GLApp x y -> GLApp x y -> Bool #

Validable (GLApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Methods

valid :: GLApp x y -> Statement Source #

(Typeable x, Typeable y) => Entity (GLApp x y) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

type ObjectClass GLApp Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup