hmatrix-static-0.3: hmatrix with vector and matrix sizes encoded in typesSource codeContentsIndex
Numeric.LinearAlgebra.Static.Algorithms
Portabilityportable
Stabilityexperimental
MaintainerReiner Pope <reiner.pope@gmail.com>
Contents
Type hints
Multiplication
Concatenating
Solving / inverting
Determinant / rank / condition number
Eigensystems
Factorisations
SVD
QR
Cholesky
Hessenberg
Schur
LU
Matrix functions
Nullspace
Norms
Misc
Description
Common operations.
Synopsis
matT :: Matrix s t -> a
vecT :: Vector s t -> a
doubleT :: a s Double -> x
complexT :: a s (Complex Double) -> x
class Mul a b where
type MulResult a b :: * -> *
(<>) :: Field t => a t -> b t -> MulResult a b t
(<.>) :: Field t => Vector n t -> Vector n t -> t
(<->) :: (JoinableV a b, Element t) => a t -> b t -> Matrix (JoinShapeV a b) t
(<|>) :: (JoinableH a b, Element t) => a t -> b t -> Matrix (JoinShapeH a b) t
(<\>) :: Field t => Matrix (m, n) t -> Vector m t -> Vector n t
linearSolve :: Field t => Matrix (m, m) t -> Matrix (m, n) t -> Matrix (m, n) t
inv :: Field t => Matrix (m, m) t -> Matrix (m, m) t
pinv :: Field t => Matrix (m, n) t -> Matrix (n, m) t
det :: Field t => Matrix (m, m) t -> t
rank :: Field t => Matrix (m, n) t -> Int
rcond :: Field t => Matrix (m, n) t -> Double
eig :: Field t => Matrix (m, m) t -> (Vector m (Complex Double), Matrix (m, m) (Complex Double))
eigSH :: Field t => Matrix (m, m) t -> (Vector m Double, Matrix (m, m) t)
svd :: Field t => Matrix (m, n) t -> (Matrix (m, m) t, Vector (Min m n) Double, Matrix (n, n) t)
fullSVD :: Field t => Matrix mn t -> (Matrix (m, m) t, Matrix (m, n) Double, Matrix (n, n) t)
economySVDU :: Field t => Matrix (m, n) t -> (Matrix (m, Unknown) t, Vector Unknown Double, Matrix (n, Unknown) t)
qr :: Field t => Matrix (m, n) t -> (Matrix (m, m) t, Matrix (m, n) t)
chol :: Field t => Matrix (m, m) t -> Matrix (m, m) t
hess :: Field t => Matrix (m, m) t -> (Matrix (m, m) t, Matrix (m, m) t)
schur :: Field t => Matrix (m, m) t -> (Matrix (m, m) t, Matrix (m, m) t)
lu :: Field t => Matrix (m, n) t -> (Matrix (m, Min m n) t, Matrix (Min m n, n) t, Matrix (m, m) t, t)
luPacked :: Field t => Matrix (m, n) t -> (Matrix (m, n) t, [Int])
luSolve :: Field t => (Matrix (m, n) t, [Int]) -> Matrix (m, p) t -> Matrix (n, p) t
expm :: Field t => Matrix (m, m) t -> Matrix (m, m) t
sqrtm :: Field t => Matrix (m, m) t -> Matrix (m, m) t
matFunc :: Field t => (Complex Double -> Complex Double) -> Matrix (m, m) t -> Matrix (m, m) (Complex Double)
nullspacePrec :: Field t => Double -> Matrix (m, n) t -> [Vector n t]
nullVector :: Field t => Matrix (m, n) t -> Vector n t
pnorm
NormType (Infinity, PNorm1, PNorm2)
ctrans :: Field t => Matrix (m, n) t -> Matrix (n, m) t
eps :: Double
i :: Complex Double
outer :: Field t => Vector m t -> Vector n t -> Matrix (m, n) t
kronecker :: Field t => Matrix (m, n) t -> Matrix (p, q) t -> Matrix (m :*: p, n :*: q) t
Type hints
matT :: Matrix s t -> aSource
vecT :: Vector s t -> aSource
doubleT :: a s Double -> xSource
complexT :: a s (Complex Double) -> xSource
Multiplication
class Mul a b whereSource
Associated Types
type MulResult a b :: * -> *Source
Methods
(<>) :: Field t => a t -> b t -> MulResult a b tSource
Overloaded matrix-matrix, matrix-vector, or vector-matrix product. The instances have type equalities to improve the quality of type inference.
show/hide Instances
n ~ n' => Mul (Matrix ((,) m n)) (Vector n')
n ~ n' => Mul (Matrix ((,) m n)) (Vector n')
n ~ n' => Mul (Matrix ((,) m n)) (Matrix ((,) n' p))
m ~ m' => Mul (Vector m) (Matrix ((,) m' n))
m ~ m' => Mul (Vector m) (Matrix ((,) m' n))
(<.>) :: Field t => Vector n t -> Vector n t -> tSource
Dot product
Concatenating
(<->) :: (JoinableV a b, Element t) => a t -> b t -> Matrix (JoinShapeV a b) tSource
Overloaded matrix-matrix, matrix-vector, vector-matrix, or vector-vector vertical concatenation. The instances have type equalities to improve the quality of type inference.
(<|>) :: (JoinableH a b, Element t) => a t -> b t -> Matrix (JoinShapeH a b) tSource
Overloaded matrix-matrix, matrix-vector, vector-matrix, or vector-vector horizontal concatenation. The instances have type equalities to improve the quality of type inference.
Solving / inverting
(<\>) :: Field t => Matrix (m, n) t -> Vector m t -> Vector n tSource
Least squares solution of a linear equation.
linearSolve :: Field t => Matrix (m, m) t -> Matrix (m, n) t -> Matrix (m, n) tSource
inv :: Field t => Matrix (m, m) t -> Matrix (m, m) tSource
pinv :: Field t => Matrix (m, n) t -> Matrix (n, m) tSource
Determinant / rank / condition number
det :: Field t => Matrix (m, m) t -> tSource
rank :: Field t => Matrix (m, n) t -> IntSource
rcond :: Field t => Matrix (m, n) t -> DoubleSource
Eigensystems
eig :: Field t => Matrix (m, m) t -> (Vector m (Complex Double), Matrix (m, m) (Complex Double))Source
eigSH :: Field t => Matrix (m, m) t -> (Vector m Double, Matrix (m, m) t)Source
Factorisations
SVD
svd :: Field t => Matrix (m, n) t -> (Matrix (m, m) t, Vector (Min m n) Double, Matrix (n, n) t)Source
fullSVD :: Field t => Matrix mn t -> (Matrix (m, m) t, Matrix (m, n) Double, Matrix (n, n) t)Source
economySVDU :: Field t => Matrix (m, n) t -> (Matrix (m, Unknown) t, Vector Unknown Double, Matrix (n, Unknown) t)Source
QR
qr :: Field t => Matrix (m, n) t -> (Matrix (m, m) t, Matrix (m, n) t)Source
Cholesky
chol :: Field t => Matrix (m, m) t -> Matrix (m, m) tSource
Hessenberg
hess :: Field t => Matrix (m, m) t -> (Matrix (m, m) t, Matrix (m, m) t)Source
Schur
schur :: Field t => Matrix (m, m) t -> (Matrix (m, m) t, Matrix (m, m) t)Source
LU
lu :: Field t => Matrix (m, n) t -> (Matrix (m, Min m n) t, Matrix (Min m n, n) t, Matrix (m, m) t, t)Source
luPacked :: Field t => Matrix (m, n) t -> (Matrix (m, n) t, [Int])Source
luSolve :: Field t => (Matrix (m, n) t, [Int]) -> Matrix (m, p) t -> Matrix (n, p) tSource
Matrix functions
expm :: Field t => Matrix (m, m) t -> Matrix (m, m) tSource
sqrtm :: Field t => Matrix (m, m) t -> Matrix (m, m) tSource
matFunc :: Field t => (Complex Double -> Complex Double) -> Matrix (m, m) t -> Matrix (m, m) (Complex Double)Source
Nullspace
nullspacePrec :: Field t => Double -> Matrix (m, n) t -> [Vector n t]Source
nullVector :: Field t => Matrix (m, n) t -> Vector n tSource
Norms
pnorm
NormType (Infinity, PNorm1, PNorm2)
Misc
ctrans :: Field t => Matrix (m, n) t -> Matrix (n, m) tSource
eps :: DoubleSource
i :: Complex DoubleSource
outer :: Field t => Vector m t -> Vector n t -> Matrix (m, n) tSource
kronecker :: Field t => Matrix (m, n) t -> Matrix (p, q) t -> Matrix (m :*: p, n :*: q) tSource
Produced by Haddock version 2.4.2