hmatrix-0.9.3.0: Linear algebra and numerical computationSource codeContentsIndex
Numeric.LinearAlgebra.Algorithms
Portabilityuses ffi
Stabilityprovisional
MaintainerAlberto Ruiz (aruiz at um dot es)
Contents
Supported types
Products
Linear Systems
Matrix factorizations
Singular value decomposition
Eigensystems
QR
Cholesky
Hessenberg
Schur
LU
Matrix functions
Nullspace
Norms
Misc
Util
Description

Generic interface for the most common functions. Using it we can write higher level algorithms and testing properties for both real and complex matrices.

Specific functions for particular base types can also be explicitly imported from Numeric.LinearAlgebra.LAPACK.

Synopsis
class (Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t
multiply :: Field t => Matrix t -> Matrix t -> Matrix t
dot :: Field t => Vector t -> Vector t -> t
outer :: Field t => Vector t -> Vector t -> Matrix t
kronecker :: Field t => Matrix t -> Matrix t -> Matrix t
linearSolve :: Field t => Matrix t -> Matrix t -> Matrix t
luSolve :: Field t => (Matrix t, [Int]) -> Matrix t -> Matrix t
cholSolve :: Field t => Matrix t -> Matrix t -> Matrix t
linearSolveLS :: Field t => Matrix t -> Matrix t -> Matrix t
linearSolveSVD :: Field t => Matrix t -> Matrix t -> Matrix t
inv :: Field t => Matrix t -> Matrix t
pinv :: Field t => Matrix t -> Matrix t
det :: Field t => Matrix t -> t
rank :: Field t => Matrix t -> Int
rcond :: Field t => Matrix t -> Double
svd :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)
fullSVD :: Field t => Matrix t -> (Matrix t, Matrix Double, Matrix t)
thinSVD :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)
compactSVD :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)
singularValues :: Field t => Matrix t -> Vector Double
leftSV :: Field t => Matrix t -> (Matrix t, Vector Double)
rightSV :: Field t => Matrix t -> (Vector Double, Matrix t)
eig :: Field t => Matrix t -> (Vector (Complex Double), Matrix (Complex Double))
eigSH :: Field t => Matrix t -> (Vector Double, Matrix t)
eigSH' :: Field t => Matrix t -> (Vector Double, Matrix t)
eigenvalues :: Field t => Matrix t -> Vector (Complex Double)
eigenvaluesSH :: Field t => Matrix t -> Vector Double
eigenvaluesSH' :: Field t => Matrix t -> Vector Double
qr :: Field t => Matrix t -> (Matrix t, Matrix t)
rq :: Field t => Matrix t -> (Matrix t, Matrix t)
chol :: Field t => Matrix t -> Matrix t
cholSH :: Field t => Matrix t -> Matrix t
mbCholSH :: Field t => Matrix t -> Maybe (Matrix t)
hess :: Field t => Matrix t -> (Matrix t, Matrix t)
schur :: Field t => Matrix t -> (Matrix t, Matrix t)
lu :: Field t => Matrix t -> (Matrix t, Matrix t, Matrix t, t)
luPacked :: Field t => Matrix t -> (Matrix t, [Int])
expm :: Field t => Matrix t -> Matrix t
sqrtm :: Field t => Matrix t -> Matrix t
matFunc :: Field t => (Complex Double -> Complex Double) -> Matrix t -> Matrix (Complex Double)
nullspacePrec :: Field t => Double -> Matrix t -> [Vector t]
nullVector :: Field t => Matrix t -> Vector t
nullspaceSVD :: Field t => Either Double Int -> Matrix t -> (Vector Double, Matrix t) -> [Vector t]
class Normed t where
pnorm :: NormType -> t -> Double
data NormType
= Infinity
| PNorm1
| PNorm2
ctrans :: Field t => Matrix t -> Matrix t
eps :: Double
i :: Complex Double
class Container c e => Linear c e where
scalar :: e -> c e
scale :: e -> c e -> c e
scaleRecip :: e -> c e -> c e
addConstant :: e -> c e -> c e
add :: c e -> c e -> c e
sub :: c e -> c e -> c e
mul :: c e -> c e -> c e
divide :: c e -> c e -> c e
equal :: c e -> c e -> Bool
haussholder :: Field a => a -> Vector a -> Matrix a
unpackQR :: Field t => (Matrix t, Vector t) -> (Matrix t, Matrix t)
unpackHess :: Field t => (Matrix t -> (Matrix t, Vector t)) -> Matrix t -> (Matrix t, Matrix t)
pinvTol :: Double -> Matrix Double -> Matrix Double
ranksv :: Double -> Int -> [Double] -> Int
full :: Element t3 => (Matrix t -> (t1, Vector t3, t2)) -> Matrix t -> (t1, Matrix t3, t2)
economy :: (Element t2, Element t1, Element t) => (Matrix t -> (Matrix t1, Vector Double, Matrix t2)) -> Matrix t -> (Matrix t1, Vector Double, Matrix t2)
Supported types
class (Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t Source
Auxiliary typeclass used to define generic computations for both real and complex matrices.
show/hide Instances
Products
multiply :: Field t => Matrix t -> Matrix t -> Matrix tSource
Matrix product.
dot :: Field t => Vector t -> Vector t -> tSource
Euclidean inner product.
outer :: Field t => Vector t -> Vector t -> Matrix tSource

Outer product of two vectors.

> fromList [1,2,3] `outer` fromList [5,2,3]
(3><3)
 [  5.0, 2.0, 3.0
 , 10.0, 4.0, 6.0
 , 15.0, 6.0, 9.0 ]
kronecker :: Field t => Matrix t -> Matrix t -> Matrix tSource

Kronecker product of two matrices.

m1=(2><3)
 [ 1.0,  2.0, 0.0
 , 0.0, -1.0, 3.0 ]
m2=(4><3)
 [  1.0,  2.0,  3.0
 ,  4.0,  5.0,  6.0
 ,  7.0,  8.0,  9.0
 , 10.0, 11.0, 12.0 ]
> kronecker m1 m2
(8><9)
 [  1.0,  2.0,  3.0,   2.0,   4.0,   6.0,  0.0,  0.0,  0.0
 ,  4.0,  5.0,  6.0,   8.0,  10.0,  12.0,  0.0,  0.0,  0.0
 ,  7.0,  8.0,  9.0,  14.0,  16.0,  18.0,  0.0,  0.0,  0.0
 , 10.0, 11.0, 12.0,  20.0,  22.0,  24.0,  0.0,  0.0,  0.0
 ,  0.0,  0.0,  0.0,  -1.0,  -2.0,  -3.0,  3.0,  6.0,  9.0
 ,  0.0,  0.0,  0.0,  -4.0,  -5.0,  -6.0, 12.0, 15.0, 18.0
 ,  0.0,  0.0,  0.0,  -7.0,  -8.0,  -9.0, 21.0, 24.0, 27.0
 ,  0.0,  0.0,  0.0, -10.0, -11.0, -12.0, 30.0, 33.0, 36.0 ]
Linear Systems
linearSolve :: Field t => Matrix t -> Matrix t -> Matrix tSource
Solve a linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition. For underconstrained or overconstrained systems use linearSolveLS or linearSolveSVD. It is similar to luSolve . luPacked, but linearSolve raises an error if called on a singular system.
luSolve :: Field t => (Matrix t, [Int]) -> Matrix t -> Matrix tSource
Solution of a linear system (for several right hand sides) from the precomputed LU factorization obtained by luPacked.
cholSolve :: Field t => Matrix t -> Matrix t -> Matrix tSource
Solve a symmetric or Hermitian positive definite linear system using a precomputed Cholesky decomposition obtained by chol.
linearSolveLS :: Field t => Matrix t -> Matrix t -> Matrix tSource
Least squared error solution of an overconstrained linear system, or the minimum norm solution of an underconstrained system. For rank-deficient systems use linearSolveSVD.
linearSolveSVD :: Field t => Matrix t -> Matrix t -> Matrix tSource
Minimum norm solution of a general linear least squares problem Ax=B using the SVD. Admits rank-deficient systems but it is slower than linearSolveLS. The effective rank of A is determined by treating as zero those singular valures which are less than eps times the largest singular value.
inv :: Field t => Matrix t -> Matrix tSource
Inverse of a square matrix.
pinv :: Field t => Matrix t -> Matrix tSource
Pseudoinverse of a general matrix.
det :: Field t => Matrix t -> tSource
Determinant of a square matrix.
rank :: Field t => Matrix t -> IntSource
Number of linearly independent rows or columns.
rcond :: Field t => Matrix t -> DoubleSource
Reciprocal of the 2-norm condition number of a matrix, computed from the singular values.
Matrix factorizations
Singular value decomposition
svd :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)Source
Full singular value decomposition.
fullSVD :: Field t => Matrix t -> (Matrix t, Matrix Double, Matrix t)Source

A version of svd which returns an appropriate diagonal matrix with the singular values.

If (u,d,v) = fullSVD m then m == u <> d <> trans v.

thinSVD :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)Source

A version of svd which returns only the min (rows m) (cols m) singular vectors of m.

If (u,s,v) = thinSVD m then m == u <> diag s <> trans v.

compactSVD :: Field t => Matrix t -> (Matrix t, Vector Double, Matrix t)Source
Similar to thinSVD, returning only the nonzero singular values and the corresponding singular vectors.
singularValues :: Field t => Matrix t -> Vector DoubleSource
Singular values only.
leftSV :: Field t => Matrix t -> (Matrix t, Vector Double)Source
Singular values and all right singular vectors.
rightSV :: Field t => Matrix t -> (Vector Double, Matrix t)Source
Singular values and all right singular vectors.
Eigensystems
eig :: Field t => Matrix t -> (Vector (Complex Double), Matrix (Complex Double))Source

Eigenvalues and eigenvectors of a general square matrix.

If (s,v) = eig m then m <> v == v <> diag s

eigSH :: Field t => Matrix t -> (Vector Double, Matrix t)Source

Eigenvalues and Eigenvectors of a complex hermitian or real symmetric matrix.

If (s,v) = eigSH m then m == v <> diag s <> ctrans v

eigSH' :: Field t => Matrix t -> (Vector Double, Matrix t)Source
Similar to eigSH without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.
eigenvalues :: Field t => Matrix t -> Vector (Complex Double)Source
Eigenvalues of a general square matrix.
eigenvaluesSH :: Field t => Matrix t -> Vector DoubleSource
Eigenvalues of a complex hermitian or real symmetric matrix.
eigenvaluesSH' :: Field t => Matrix t -> Vector DoubleSource
Similar to eigenvaluesSH without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.
QR
qr :: Field t => Matrix t -> (Matrix t, Matrix t)Source

QR factorization.

If (q,r) = qr m then m == q <> r, where q is unitary and r is upper triangular.

rq :: Field t => Matrix t -> (Matrix t, Matrix t)Source

RQ factorization.

If (r,q) = rq m then m == r <> q, where q is unitary and r is upper triangular.

Cholesky
chol :: Field t => Matrix t -> Matrix tSource

Cholesky factorization of a positive definite hermitian or symmetric matrix.

If c = chol m then c is upper triangular and m == ctrans c <> c.

cholSH :: Field t => Matrix t -> Matrix tSource
Similar to chol, without checking that the input matrix is hermitian or symmetric. It works with the upper triangular part.
mbCholSH :: Field t => Matrix t -> Maybe (Matrix t)Source
Similar to cholSH, but instead of an error (e.g., caused by a matrix not positive definite) it returns Nothing.
Hessenberg
hess :: Field t => Matrix t -> (Matrix t, Matrix t)Source

Hessenberg factorization.

If (p,h) = hess m then m == p <> h <> ctrans p, where p is unitary and h is in upper Hessenberg form (it has zero entries below the first subdiagonal).

Schur
schur :: Field t => Matrix t -> (Matrix t, Matrix t)Source

Schur factorization.

If (u,s) = schur m then m == u <> s <> ctrans u, where u is unitary and s is a Shur matrix. A complex Schur matrix is upper triangular. A real Schur matrix is upper triangular in 2x2 blocks.

"Anything that the Jordan decomposition can do, the Schur decomposition can do better!" (Van Loan)

LU
lu :: Field t => Matrix t -> (Matrix t, Matrix t, Matrix t, t)Source

Explicit LU factorization of a general matrix.

If (l,u,p,s) = lu m then m == p <> l <> u, where l is lower triangular, u is upper triangular, p is a permutation matrix and s is the signature of the permutation.

luPacked :: Field t => Matrix t -> (Matrix t, [Int])Source
Obtains the LU decomposition of a matrix in a compact data structure suitable for luSolve.
Matrix functions
expm :: Field t => Matrix t -> Matrix tSource
Matrix exponential. It uses a direct translation of Algorithm 11.3.1 in Golub & Van Loan, based on a scaled Pade approximation.
sqrtm :: Field t => Matrix t -> Matrix tSource

Matrix square root. Currently it uses a simple iterative algorithm described in Wikipedia. It only works with invertible matrices that have a real solution. For diagonalizable matrices you can try matFunc sqrt.

m = (2><2) [4,9
           ,0,4] :: Matrix Double
>sqrtm m
(2><2)
 [ 2.0, 2.25
 , 0.0,  2.0 ]
matFunc :: Field t => (Complex Double -> Complex Double) -> Matrix t -> Matrix (Complex Double)Source

Generic matrix functions for diagonalizable matrices. For instance:

logm = matFunc log
Nullspace
nullspacePrecSource
:: Field t
=> Doublerelative tolerance in eps units (e.g., use 3 to get 3*eps)
-> Matrix tinput matrix
-> [Vector t]list of unitary vectors spanning the nullspace
The nullspace of a matrix. See also nullspaceSVD.
nullVector :: Field t => Matrix t -> Vector tSource
The nullspace of a matrix, assumed to be one-dimensional, with machine precision.
nullspaceSVDSource
:: Field t
=> Either Double IntLeft "numeric" zero (eg. 1*eps), or Right "theoretical" matrix rank.
-> Matrix tinput matrix m
-> (Vector Double, Matrix t)rightSV of m
-> [Vector t]list of unitary vectors spanning the nullspace
The nullspace of a matrix from its SVD decomposition.
Norms
class Normed t whereSource

Objects which have a p-norm. Using it you can define convenient shortcuts:

norm2 x = pnorm PNorm2 x
frobenius m = norm2 . flatten $ m
Methods
pnorm :: NormType -> t -> DoubleSource
show/hide Instances
data NormType Source
Constructors
Infinity
PNorm1
PNorm2
Misc
ctrans :: Field t => Matrix t -> Matrix tSource
Generic conjugate transpose.
eps :: DoubleSource
The machine precision of a Double: eps = 2.22044604925031e-16 (the value used by GNU-Octave).
i :: Complex DoubleSource
The imaginary unit: i = 0.0 :+ 1.0
class Container c e => Linear c e whereSource
Basic element-by-element functions.
Methods
scalar :: e -> c eSource
create a structure with a single element
scale :: e -> c e -> c eSource
scaleRecip :: e -> c e -> c eSource

scale the element by element reciprocal of the object:

scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]
addConstant :: e -> c e -> c eSource
add :: c e -> c e -> c eSource
sub :: c e -> c e -> c eSource
mul :: c e -> c e -> c eSource
element by element multiplication
divide :: c e -> c e -> c eSource
element by element division
equal :: c e -> c e -> BoolSource
show/hide Instances
Util
haussholder :: Field a => a -> Vector a -> Matrix aSource
unpackQR :: Field t => (Matrix t, Vector t) -> (Matrix t, Matrix t)Source
unpackHess :: Field t => (Matrix t -> (Matrix t, Vector t)) -> Matrix t -> (Matrix t, Matrix t)Source
pinvTol :: Double -> Matrix Double -> Matrix DoubleSource
ranksvSource
:: Doublenumeric zero (e.g. 1*eps)
-> Intmaximum dimension of the matrix
-> [Double]singular values
-> Intrank of m
Numeric rank of a matrix from its singular values.
full :: Element t3 => (Matrix t -> (t1, Vector t3, t2)) -> Matrix t -> (t1, Matrix t3, t2)Source
economy :: (Element t2, Element t1, Element t) => (Matrix t -> (Matrix t1, Vector Double, Matrix t2)) -> Matrix t -> (Matrix t1, Vector Double, Matrix t2)Source
Produced by Haddock version 2.6.1