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

A generic interface for some common functions. Using it we can write higher level algorithms and testing properties both for real and complex matrices.

In any case, the specific functions for particular base types can also be explicitly imported from Numeric.LinearAlgebra.LAPACK.

Synopsis
inv :: Field t => Matrix t -> Matrix t
pinv :: Field t => Matrix t -> Matrix t
pinvTol
det :: Field t => Matrix t -> t
rank :: Field t => Matrix t -> Int
rcond :: Field t => Matrix t -> Double
full :: Element t => (Matrix t -> (Matrix t, Vector Double, Matrix t)) -> Matrix t -> (Matrix t, Matrix Double, Matrix t)
economy :: Element t => (Matrix t -> (Matrix t, Vector Double, Matrix t)) -> Matrix t -> (Matrix t, Vector Double, Matrix t)
eigSH :: Field t => Matrix t -> (Vector Double, Matrix t)
chol :: Field t => Matrix t -> Matrix t
lu :: Field t => Matrix t -> (Matrix t, Matrix t, Matrix t, t)
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
class Normed t where
pnorm :: NormType -> t -> Double
data NormType
= Infinity
| PNorm1
| PNorm2
eps :: Double
i :: Complex Double
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)
class (Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t where
svd :: Matrix t -> (Matrix t, Vector Double, Matrix t)
linearSolve :: Matrix t -> Matrix t -> Matrix t
linearSolveSVD :: Matrix t -> Matrix t -> Matrix t
eig :: Matrix t -> (Vector (Complex Double), Matrix (Complex Double))
eigSH' :: Matrix t -> (Vector Double, Matrix t)
cholSH :: Matrix t -> Matrix t
qr :: Matrix t -> (Matrix t, Matrix t)
hess :: Matrix t -> (Matrix t, Matrix t)
schur :: Matrix t -> (Matrix t, Matrix t)
ctrans :: Matrix t -> Matrix t
Linear Systems
inv :: Field t => Matrix t -> Matrix tSource
Inverse of a square matrix using lapacks' dgesv and zgesv.
pinv :: Field t => Matrix t -> Matrix tSource
Pseudoinverse of a general matrix using lapack's dgelss or zgelss.
pinvTol
det :: Field t => Matrix t -> tSource
determinant of a square matrix, computed from the LU decomposition.
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 SVD.
Matrix factorizations
Singular value decomposition
full :: Element t => (Matrix t -> (Matrix t, Vector Double, Matrix 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) = full svd m then m == u <> d <> trans v.

economy :: Element t => (Matrix t -> (Matrix t, Vector Double, Matrix t)) -> Matrix t -> (Matrix t, Vector Double, Matrix t)Source

A version of svd which returns only the nonzero singular values and the corresponding rows and columns of the rotations.

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

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

Eigenvalues and Eigenvectors of a complex hermitian or real symmetric matrix using lapack's dsyev or zheev.

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

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

Cholesky factorization of a positive definite hermitian or symmetric matrix using lapack's dpotrf or zportrf.

If c = chol m then m == ctrans c <> c.

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

LU factorization of a general matrix using lapack's dgetrf or zgetrf.

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.

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
-> Matrix tinput matrix
-> [Vector t]list of unitary vectors spanning the nullspace
The nullspace of a matrix from its SVD decomposition.
nullVector :: Field t => Matrix t -> Vector tSource
The nullspace of a matrix, assumed to be one-dimensional, with default tolerance (shortcut for last . nullspacePrec 1).
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
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
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
class (Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t whereSource
Auxiliary typeclass used to define generic computations for both real and complex matrices.
Methods
svd :: Matrix t -> (Matrix t, Vector Double, Matrix t)Source
Singular value decomposition using lapack's dgesvd or zgesvd.
linearSolve :: Matrix t -> Matrix t -> Matrix tSource
Solution of a general linear system (for several right-hand sides) using lapacks' dgesv and zgesv. See also other versions of linearSolve in Numeric.LinearAlgebra.LAPACK.
linearSolveSVD :: Matrix t -> Matrix t -> Matrix tSource
eig :: Matrix t -> (Vector (Complex Double), Matrix (Complex Double))Source

Eigenvalues and eigenvectors of a general square matrix using lapack's dgeev or zgeev.

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

eigSH' :: Matrix t -> (Vector Double, Matrix t)Source
Similar to eigSH without checking that the input matrix is hermitian or symmetric.
cholSH :: Matrix t -> Matrix tSource
Similar to chol without checking that the input matrix is hermitian or symmetric.
qr :: Matrix t -> (Matrix t, Matrix t)Source

QR factorization using lapack's dgeqr2 or zgeqr2.

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

hess :: Matrix t -> (Matrix t, Matrix t)Source

Hessenberg factorization using lapack's dgehrd or zgehrd.

If (p,h) = hess m then m == p <> h <> ctrans p, where p is unitary and h is in upper Hessenberg form.

schur :: Matrix t -> (Matrix t, Matrix t)Source

Schur factorization using lapack's dgees or zgees.

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)

ctrans :: Matrix t -> Matrix tSource
Conjugate transpose.
show/hide Instances
Produced by Haddock version 2.4.2