Safe Haskell | None |
---|---|
Language | Haskell2010 |
Eigen.Solver.LA
Synopsis
- data Decomposition
- solve :: (KnownNat n, KnownNat m, KnownNat n1, KnownNat m1, Elem a) => Decomposition -> Matrix n m a -> Matrix n1 m1 a -> Matrix m 1 a
- relativeError :: (KnownNat n, KnownNat m, KnownNat n1, KnownNat m1, KnownNat n2, KnownNat m2, Elem a) => Matrix n m a -> Matrix n1 m1 a -> Matrix n2 m2 a -> a
- rank :: (KnownNat n, KnownNat m, Elem a) => Decomposition -> Matrix n m a -> Int
- kernel :: forall a n m. (Elem a, KnownNat n, KnownNat m) => Decomposition -> Matrix n m a -> Matrix n m a
- image :: forall a n m. (Elem a, KnownNat n, KnownNat m) => Decomposition -> Matrix n m a -> Matrix n m a
- linearRegression :: forall r. KnownNat r => Row r -> [[Double]] -> Maybe ([Double], Double)
Documentation
data Decomposition Source #
Decomposition Requirements on the matrix Speed Accuracy Rank Kernel Image PartialPivLU Invertible ++ + - - - FullPivLU None - +++ + + + HouseholderQR None ++ + - - - ColPivHouseholderQR None + ++ + - - FullPivHouseholderQR None - +++ + - - LLT Positive definite +++ + - - - LDLT Positive or negative semidefinite +++ ++ - - - JacobiSVD None - +++ + - -
The best way to do least squares solving for square matrices is with a SVD decomposition (JacobiSVD
)
Constructors
PartialPivLU | LU decomposition of a matrix with partial pivoting. |
FullPivLU | LU decomposition of a matrix with complete pivoting. |
HouseholderQR | Householder QR decomposition of a matrix. |
ColPivHouseholderQR | Householder rank-revealing QR decomposition of a matrix with column-pivoting. |
FullPivHouseholderQR | Householder rank-revealing QR decomposition of a matrix with full pivoting. |
LLT | Standard Cholesky decomposition (LL^T) of a matrix. |
LDLT | Robust Cholesky decomposition of a matrix with pivoting. |
JacobiSVD | Two-sided Jacobi SVD decomposition of a rectangular matrix. |
Instances
Enum Decomposition Source # | |
Defined in Eigen.Solver.LA Methods succ :: Decomposition -> Decomposition # pred :: Decomposition -> Decomposition # toEnum :: Int -> Decomposition # fromEnum :: Decomposition -> Int # enumFrom :: Decomposition -> [Decomposition] # enumFromThen :: Decomposition -> Decomposition -> [Decomposition] # enumFromTo :: Decomposition -> Decomposition -> [Decomposition] # enumFromThenTo :: Decomposition -> Decomposition -> Decomposition -> [Decomposition] # | |
Eq Decomposition Source # | |
Defined in Eigen.Solver.LA Methods (==) :: Decomposition -> Decomposition -> Bool # (/=) :: Decomposition -> Decomposition -> Bool # | |
Read Decomposition Source # | |
Defined in Eigen.Solver.LA Methods readsPrec :: Int -> ReadS Decomposition # readList :: ReadS [Decomposition] # | |
Show Decomposition Source # | |
Defined in Eigen.Solver.LA Methods showsPrec :: Int -> Decomposition -> ShowS # show :: Decomposition -> String # showList :: [Decomposition] -> ShowS # |
solve :: (KnownNat n, KnownNat m, KnownNat n1, KnownNat m1, Elem a) => Decomposition -> Matrix n m a -> Matrix n1 m1 a -> Matrix m 1 a Source #
- x = solve d a b
- finds a solution
x
ofax = b
equation using decompositiond
relativeError :: (KnownNat n, KnownNat m, KnownNat n1, KnownNat m1, KnownNat n2, KnownNat m2, Elem a) => Matrix n m a -> Matrix n1 m1 a -> Matrix n2 m2 a -> a Source #
- e = relativeError x a b
- computes
norm (ax - b) / norm b
wherenorm
is L2 norm
rank :: (KnownNat n, KnownNat m, Elem a) => Decomposition -> Matrix n m a -> Int Source #
The rank of the matrix.
kernel :: forall a n m. (Elem a, KnownNat n, KnownNat m) => Decomposition -> Matrix n m a -> Matrix n m a Source #
Return the matrix whose columns form a basis of the null-space of A
.
image :: forall a n m. (Elem a, KnownNat n, KnownNat m) => Decomposition -> Matrix n m a -> Matrix n m a Source #
Return a matrix whose columns form a basis of the column-space of A
.
linearRegression :: forall r. KnownNat r => Row r -> [[Double]] -> Maybe ([Double], Double) Source #
- (coeffs, error) = linearRegression points
- computes multiple linear regression
y = a1 x1 + a2 x2 + ... + an xn + b
usingColPivHouseholderQR
decomposition
- point format is
[y, x1..xn]
- coeffs format is
[b, a1..an]
- error is calculated using
relativeError
import Data.Eigen.LA main = print $ linearRegression (Row @5) [ [-4.32, 3.02, 6.89], [-3.79, 2.01, 5.39], [-4.01, 2.41, 6.01], [-3.86, 2.09, 5.55], [-4.10, 2.58, 6.32] ]
produces the following output
Just ([-2.3466569233817127,-0.2534897541434826,-0.1749653335680988],1.8905965120153139e-3)