Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newtype RowTrafo a = RowTrafo (GLT a)
- crTrafoRows :: Transformation x -> Col N (Row N x) -> Col N (Row N x)
- newtype ColTrafo x = ColTrafo (GLT x)
- crTrafoCols :: Col N (Row N x) -> Transformation x -> Col N (Row N x)
- data DiagonalForm k = DiagonalForm [k] (RowTrafo k) (ColTrafo k)
- dgfMatrix :: Distributive k => DiagonalForm k -> Matrix k
- newtype DiagonalFormStrictPositive k = DiagonalFormStrictPositive (DiagonalForm k)
Row Trafo
GLT
as row transformations.
Instances
Oriented a => Show (RowTrafo a) Source # | |
Oriented a => Eq (RowTrafo a) Source # | |
Oriented a => Validable (RowTrafo a) Source # | |
Oriented a => Entity (RowTrafo a) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
Oriented a => Exponential (RowTrafo a) Source # | |
Oriented a => Cayleyan (RowTrafo a) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
Oriented a => Invertible (RowTrafo a) Source # | |
Oriented a => Multiplicative (RowTrafo a) Source # | |
Oriented a => Oriented (RowTrafo a) Source # | |
Oriented x => Opl (RowTrafo x) (Matrix x) Source # | |
Distributive x => OrientedOpl (RowTrafo x) (Matrix x) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
type Exponent (RowTrafo a) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
type Point (RowTrafo a) Source # | |
Defined in OAlg.Entity.Matrix.Transformation |
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
GLT
as a column transformation.
Instances
Oriented x => Show (ColTrafo x) Source # | |
Oriented x => Eq (ColTrafo x) Source # | |
Oriented x => Validable (ColTrafo x) Source # | |
Oriented x => Entity (ColTrafo x) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
Oriented x => Exponential (ColTrafo x) Source # | |
Oriented x => Cayleyan (ColTrafo x) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
Oriented x => Invertible (ColTrafo x) Source # | |
Oriented x => Multiplicative (ColTrafo x) Source # | |
Oriented x => Oriented (ColTrafo x) Source # | |
Oriented x => Opr (ColTrafo x) (Matrix x) Source # | |
Distributive x => OrientedOpr (ColTrafo x) (Matrix x) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
type Exponent (ColTrafo x) Source # | |
Defined in OAlg.Entity.Matrix.Transformation | |
type Point (ColTrafo x) Source # | |
Defined in OAlg.Entity.Matrix.Transformation |
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
be in DiagonalForm
ds rt ct
, then holds:DiagonalForm
k
DiagonalForm [k] (RowTrafo k) (ColTrafo k) |
Instances
Oriented k => Show (DiagonalForm k) Source # | |
Defined in OAlg.Entity.Matrix.Transformation showsPrec :: Int -> DiagonalForm k -> ShowS # show :: DiagonalForm k -> String # showList :: [DiagonalForm k] -> ShowS # | |
Oriented k => Eq (DiagonalForm k) Source # | |
Defined in OAlg.Entity.Matrix.Transformation (==) :: DiagonalForm k -> DiagonalForm k -> Bool # (/=) :: DiagonalForm k -> DiagonalForm k -> Bool # | |
Distributive k => Validable (DiagonalForm k) Source # | |
Defined in OAlg.Entity.Matrix.Transformation valid :: DiagonalForm k -> Statement Source # | |
Distributive k => Entity (DiagonalForm k) Source # | |
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.
newtype DiagonalFormStrictPositive k Source #
predicate for diagonal forms with strict positive entries.
Property Let
be in
DiagonalFormStrictPositive
(DiagonalForm
ds _ _)
, then holds: DiagonalForm
k0
for all <
dd
in ds
.
Instances
Oriented k => Show (DiagonalFormStrictPositive k) Source # | |
Defined in OAlg.Entity.Matrix.Transformation showsPrec :: Int -> DiagonalFormStrictPositive k -> ShowS # show :: DiagonalFormStrictPositive k -> String # showList :: [DiagonalFormStrictPositive k] -> ShowS # | |
Oriented k => Eq (DiagonalFormStrictPositive k) Source # | |
Defined in OAlg.Entity.Matrix.Transformation (==) :: DiagonalFormStrictPositive k -> DiagonalFormStrictPositive k -> Bool # (/=) :: DiagonalFormStrictPositive k -> DiagonalFormStrictPositive k -> Bool # | |
Number k => Validable (DiagonalFormStrictPositive k) Source # | |
Defined in OAlg.Entity.Matrix.Transformation valid :: DiagonalFormStrictPositive k -> Statement Source # | |
Number k => Entity (DiagonalFormStrictPositive k) Source # | |
Defined in OAlg.Entity.Matrix.Transformation |