Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- type Square sh = ArrayMatrix (Square sh)
- size :: Square sh a -> sh
- mapSize :: (sh0 -> sh1) -> Square sh0 a -> Square sh1 a
- toFull :: (C vert, C horiz) => Square sh a -> Full vert horiz sh sh a
- toGeneral :: Square sh a -> General sh sh a
- fromGeneral :: Eq sh => General sh sh a -> Square sh a
- fromScalar :: Storable a => a -> Square () a
- toScalar :: Storable a => Square () a -> a
- fromList :: (C sh, Storable a) => sh -> [a] -> Square sh a
- autoFromList :: Storable a => [a] -> Square ShapeInt a
- transpose :: Square sh a -> Square sh a
- adjoint :: (C sh, Floating a) => Square sh a -> Square sh a
- identity :: (C sh, Floating a) => sh -> Square sh a
- identityFrom :: (C sh, Floating a) => Square sh a -> Square sh a
- identityFromWidth :: (C height, C width, Floating a) => General height width a -> Square width a
- identityFromHeight :: (C height, C width, Floating a) => General height width a -> Square height a
- diagonal :: (C sh, Floating a) => Vector sh a -> Square sh a
- takeDiagonal :: (C sh, Floating a) => Square sh a -> Vector sh a
- trace :: (C sh, Floating a) => Square sh a -> a
- stack :: (C vert, C horiz, C sizeA, Eq sizeA, C sizeB, Eq sizeB, Floating a) => Square sizeA a -> Full vert horiz sizeA sizeB a -> Full horiz vert sizeB sizeA a -> Square sizeB a -> Square (sizeA :+: sizeB) a
- (|=|) :: (C vert, C horiz, C sizeA, Eq sizeA, C sizeB, Eq sizeB, Floating a) => (Square sizeA a, Full vert horiz sizeA sizeB a) -> (Full horiz vert sizeB sizeA a, Square sizeB a) -> Square (sizeA :+: sizeB) a
- multiply :: (C sh, Eq sh, Floating a) => Square sh a -> Square sh a -> Square sh a
- square :: (C sh, Floating a) => Square sh a -> Square sh a
- power :: (C sh, Floating a) => Integer -> Square sh a -> Square sh a
- congruence :: (C height, Eq height, C width, Floating a) => Square height a -> General height width a -> Square width a
- congruenceAdjoint :: (C height, C width, Eq width, Floating a) => General height width a -> Square width a -> Square height a
- solve :: (C vert, C horiz, C sh, Eq sh, C nrhs, Floating a) => Square sh a -> Full vert horiz sh nrhs a -> Full vert horiz sh nrhs a
- inverse :: (C sh, Floating a) => Square sh a -> Square sh a
- determinant :: (C sh, Floating a) => Square sh a -> a
- eigenvalues :: (C sh, Floating a) => Square sh a -> Vector sh (ComplexOf a)
- schur :: (C sh, Floating a) => Square sh a -> (Square sh a, Square sh a)
- schurComplex :: (C sh, Real a, Complex a ~ ac) => Square sh ac -> (Square sh ac, Upper sh ac)
- eigensystem :: (C sh, Floating a, ComplexOf a ~ ac) => Square sh a -> (Square sh ac, Vector sh ac, Square sh ac)
- type ComplexOf x = Complex (RealOf x)
Documentation
type Square sh = ArrayMatrix (Square sh) Source #
fromScalar :: Storable a => a -> Square () a Source #
identityFromWidth :: (C height, C width, Floating a) => General height width a -> Square width a Source #
identityFromHeight :: (C height, C width, Floating a) => General height width a -> Square height a Source #
stack :: (C vert, C horiz, C sizeA, Eq sizeA, C sizeB, Eq sizeB, Floating a) => Square sizeA a -> Full vert horiz sizeA sizeB a -> Full horiz vert sizeB sizeA a -> Square sizeB a -> Square (sizeA :+: sizeB) a Source #
(|=|) :: (C vert, C horiz, C sizeA, Eq sizeA, C sizeB, Eq sizeB, Floating a) => (Square sizeA a, Full vert horiz sizeA sizeB a) -> (Full horiz vert sizeB sizeA a, Square sizeB a) -> Square (sizeA :+: sizeB) a infix 3 Source #
congruence :: (C height, Eq height, C width, Floating a) => Square height a -> General height width a -> Square width a Source #
congruence B A = A^H * B * A
The meaning and order of matrix factors of these functions is consistent:
congruenceAdjoint :: (C height, C width, Eq width, Floating a) => General height width a -> Square width a -> Square height a Source #
congruenceAdjoint A B = A * B * A^H
solve :: (C vert, C horiz, C sh, Eq sh, C nrhs, Floating a) => Square sh a -> Full vert horiz sh nrhs a -> Full vert horiz sh nrhs a Source #
schur :: (C sh, Floating a) => Square sh a -> (Square sh a, Square sh a) Source #
If (q,r) = schur a
, then a = q <> r <> adjoint q
,
where q
is unitary (orthogonal)
and r
is a right-upper triangular matrix for complex a
and a 1x1-or-2x2-block upper triangular matrix for real a
.
With takeDiagonal r
you get all eigenvalues of a
if a
is complex
and the real parts of the eigenvalues if a
is real.
Complex conjugated eigenvalues of a real matrix a
are encoded as 2x2 blocks along the diagonal.
The meaning and order of matrix factors of these functions is consistent:
schurComplex :: (C sh, Real a, Complex a ~ ac) => Square sh ac -> (Square sh ac, Upper sh ac) Source #
eigensystem :: (C sh, Floating a, ComplexOf a ~ ac) => Square sh a -> (Square sh ac, Vector sh ac, Square sh ac) Source #
(vr,d,vlAdj) = eigensystem a
Counterintuitively, vr
contains the right eigenvectors as columns
and vlAdj
contains the left conjugated eigenvectors as rows.
The idea is to provide a decomposition of a
.
If a
is diagonalizable, then vr
and vlAdj
are almost inverse to each other.
More precisely, vlAdj <> vr
is a diagonal matrix,
but not necessarily an identity matrix.
This is because all eigenvectors are normalized to Euclidean norm 1.
With the following scaling, the decomposition becomes perfect:
let scal = takeDiagonal $ vlAdj <> vr a == vr #*\ Vector.divide d scal ##*# vlAdj
If a
is non-diagonalizable
then some columns of vr
and corresponding rows of vlAdj
are left zero
and the above property does not hold.
The meaning and order of result matrices of these functions is consistent: