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

Description

elementary matrix transformations, i.e. operations of GLT on Matrix.

Synopsis

Row Trafo

newtype RowTrafo a Source #

GLT as row transformations.

Constructors

RowTrafo (GLT a) 

Instances

Instances details
Oriented a => Show (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Methods

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

show :: RowTrafo a -> String #

showList :: [RowTrafo a] -> ShowS #

Oriented a => Eq (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Methods

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

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

Oriented a => Validable (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Oriented a => Entity (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Oriented a => Exponential (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Exponent (RowTrafo a) Source #

Methods

(^) :: RowTrafo a -> Exponent (RowTrafo a) -> RowTrafo a Source #

Oriented a => Cayleyan (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Oriented a => Invertible (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Oriented a => Multiplicative (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Oriented a => Oriented (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Point (RowTrafo a) Source #

Oriented x => Opl (RowTrafo x) (Matrix x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Methods

(*>) :: RowTrafo x -> Matrix x -> Matrix x Source #

Distributive x => OrientedOpl (RowTrafo x) (Matrix x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

type Exponent (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

type Exponent (RowTrafo a) = Z
type Point (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

type Point (RowTrafo a) = Dim a (Point a)

crTrafoRows :: Transformation x -> Col N (Row N x) -> Col N (Row N x) Source #

applying a transformation as a row transformation on a column of rows.

Col Trafo

newtype ColTrafo x Source #

GLT as a column transformation.

Constructors

ColTrafo (GLT x) 

Instances

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

Defined in OAlg.Entity.Matrix.Transformation

Methods

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

show :: ColTrafo x -> String #

showList :: [ColTrafo x] -> ShowS #

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

Defined in OAlg.Entity.Matrix.Transformation

Methods

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

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

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

Defined in OAlg.Entity.Matrix.Transformation

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

Defined in OAlg.Entity.Matrix.Transformation

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

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Exponent (ColTrafo x) Source #

Methods

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

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

Defined in OAlg.Entity.Matrix.Transformation

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

Defined in OAlg.Entity.Matrix.Transformation

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

Defined in OAlg.Entity.Matrix.Transformation

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

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Point (ColTrafo x) Source #

Oriented x => Opr (ColTrafo x) (Matrix x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Methods

(<*) :: Matrix x -> ColTrafo x -> Matrix x Source #

Distributive x => OrientedOpr (ColTrafo x) (Matrix x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

type Exponent (ColTrafo x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

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

Defined in OAlg.Entity.Matrix.Transformation

type Point (ColTrafo x) = Dim x (Point x)

crTrafoCols :: Col N (Row N x) -> Transformation x -> Col N (Row N x) Source #

applying a transformation as a column transformation on a column of rows.

Diagonal Form

data DiagonalForm k Source #

the result of transforming a matrix into a diagonal form.

Property Let DiagonalForm ds rt ct be in DiagonalForm k, then holds:

  1. n <= lengthN (start rt) and n <= lengthN (end ct) where n = lengthN ds.
  2. For all d in ds holds: not (isZero d).

Constructors

DiagonalForm [k] (RowTrafo k) (ColTrafo k) 

Instances

Instances details
Oriented k => Show (DiagonalForm k) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Oriented k => Eq (DiagonalForm k) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Distributive k => Validable (DiagonalForm k) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Distributive k => Entity (DiagonalForm k) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

dgfMatrix :: Distributive k => DiagonalForm k -> Matrix k Source #

the resulting matrix by applying on the diagonal matrix the inverse of the given transformations.