lapack-0.5.1.1: Numerical Linear Algebra using LAPACK
Safe HaskellSafe-Inferred
LanguageHaskell98

Numeric.LAPACK.Matrix.Square

Synopsis

Documentation

type Square sh = SquareMeas Shape sh sh Source #

size :: Square sh a -> sh Source #

mapSize :: (sh0 -> sh1) -> Square sh0 a -> Square sh1 a Source #

toFull :: (Measured meas vert, Measured meas horiz) => Square sh a -> Full meas vert horiz sh sh a Source #

toGeneral :: Square sh a -> General sh sh a Source #

fromFull :: (Measure meas, C vert, C horiz, Eq sh) => Full meas vert horiz sh sh a -> Square sh a Source #

liberalFromFull :: (Measure meas, C vert, C horiz, C height, C width) => Full meas vert horiz height width a -> LiberalSquare height width a Source #

fromScalar :: Storable a => a -> Square () a Source #

toScalar :: Storable a => Square () a -> a Source #

fromList :: (C sh, Storable a) => sh -> [a] -> Square sh a Source #

transpose :: Square sh a -> Square sh a Source #

adjoint :: (C sh, Floating a) => Square sh a -> Square sh a Source #

conjugate transpose

identity :: (C sh, Floating a) => sh -> Square sh a Source #

identityFrom :: (C sh, Floating a) => Square sh a -> Square sh 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 #

diagonal :: (C sh, Floating a) => Vector sh a -> Square sh a Source #

takeDiagonal :: (C sh, Floating a) => Square sh a -> Vector sh a Source #

trace :: (C sh, Floating a) => Square sh a -> a Source #

stack :: (Measure meas, C vert, C horiz, C sizeA, Eq sizeA, C sizeB, Eq sizeB, Floating a) => Square sizeA a -> Full meas vert horiz sizeA sizeB a -> Full meas horiz vert sizeB sizeA a -> Square sizeB a -> Square (sizeA ::+ sizeB) a Source #

(|=|) :: (Measure meas, C vert, C horiz, C sizeA, Eq sizeA, C sizeB, Eq sizeB, Floating a) => (Square sizeA a, Full meas vert horiz sizeA sizeB a) -> (Full meas horiz vert sizeB sizeA a, Square sizeB a) -> Square (sizeA ::+ sizeB) a infix 3 Source #

split :: (C sizeA, C sizeB, Floating a) => Square (sizeA ::+ sizeB) a -> (Square sizeA a, General sizeA sizeB a, General sizeB sizeA a, Square sizeB a) Source #

takeTopLeft :: (C sizeA, C sizeB, Floating a) => Square (sizeA ::+ sizeB) a -> Square sizeA a Source #

takeBottomRight :: (C sizeA, C sizeB, Floating a) => Square (sizeA ::+ sizeB) a -> Square sizeB a Source #

multiply :: (C sh, Eq sh, Floating a) => Square sh a -> Square sh a -> Square sh a Source #

square :: (C sh, Floating a) => Square sh a -> Square sh a Source #

power :: (C sh, Floating a) => Integer -> Square sh a -> Square sh a 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 :: (Measure meas, C vert, C horiz, C sh, Eq sh, C nrhs, Floating a) => Square sh a -> Full meas vert horiz sh nrhs a -> Full meas vert horiz sh nrhs a Source #

inverse :: (Measure meas, C height, C width, Floating a) => SquareMeas meas height width a -> SquareMeas meas width height a Source #

determinant :: (C sh, Floating a) => Square sh a -> a Source #

schur :: (Permutable sh, Floating a) => Square sh a -> (Square sh a, QuasiUpper 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 :: (Permutable sh, Real a, Complex a ~ ac) => Square sh ac -> (Square sh ac, Upper sh ac) Source #

eigensystem :: (Permutable 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:

type ComplexOf x = Complex (RealOf x) #