easytensor-2.1.0.0: Pure, type-indexed haskell vector, matrix, and tensor library.

Safe HaskellNone
LanguageHaskell2010

Numeric.Matrix.SVD

Synopsis

Documentation

class RealFloatExtras t => MatrixSVD (t :: Type) (n :: Nat) (m :: Nat) where Source #

Methods

svd :: IterativeMethod => Matrix t n m -> SVD t n m Source #

Compute SVD factorization of a matrix

Instances
(RealFloatExtras t, KnownDim n, KnownDim m) => MatrixSVD t n m Source # 
Instance details

Defined in Numeric.Matrix.SVD

Methods

svd :: Matrix t n m -> SVD t n m Source #

(RealFloatExtras t, Quaternion t) => MatrixSVD t 3 3 Source # 
Instance details

Defined in Numeric.Matrix.SVD

Methods

svd :: Matrix t 3 3 -> SVD t 3 3 Source #

RealFloatExtras t => MatrixSVD t 2 2 Source # 
Instance details

Defined in Numeric.Matrix.SVD

Methods

svd :: Matrix t 2 2 -> SVD t 2 2 Source #

RealFloatExtras t => MatrixSVD t 1 1 Source # 
Instance details

Defined in Numeric.Matrix.SVD

Methods

svd :: Matrix t 1 1 -> SVD t 1 1 Source #

data SVD (t :: Type) (n :: Nat) (m :: Nat) Source #

Result of SVD factorization M = svdU %* asDiag svdS %* transpose svdV .

Invariants:

  • Singular values svdS are in non-increasing order and are non-negative.
  • svdU and svdV are orthogonal matrices
  • det svdU == 1

NB: SVD on wiki

Constructors

SVD 

Fields

Instances
(Eq (Matrix t n n), Eq (Matrix t m m), Eq (Vector t (Min n m))) => Eq (SVD t n m) Source # 
Instance details

Defined in Numeric.Matrix.SVD

Methods

(==) :: SVD t n m -> SVD t n m -> Bool #

(/=) :: SVD t n m -> SVD t n m -> Bool #

(Show t, PrimBytes t, KnownDim n, KnownDim m, KnownDim (Min n m)) => Show (SVD t n m) Source # 
Instance details

Defined in Numeric.Matrix.SVD

Methods

showsPrec :: Int -> SVD t n m -> ShowS #

show :: SVD t n m -> String #

showList :: [SVD t n m] -> ShowS #

svd1 :: (PrimBytes t, Num t, Eq t) => Matrix t 1 1 -> SVD t 1 1 Source #

Obvious dummy implementation of SVD for 1x1 matrices

svd3 :: forall t. (Quaternion t, RealFloatExtras t) => Matrix t 3 3 -> SVD t 3 3 Source #

Get SVD decomposition of a 3x3 matrix using svd3q function.

This function reorders the singular components under the hood to make sure s1 >= s2 >= s3 >= 0. Thus, it has some overhead on top of svd3q.

svd3q :: forall t. (Quaternion t, RealFloatExtras t) => Matrix t 3 3 -> (Quater t, Vector t 3, Quater t) Source #

Get SVD decomposition of a 3x3 matrix, with orthogonal matrices U and V represented as quaternions. Important: U and V are bound to be rotations at the expense of the last singular value being possibly negative.

This is an adoptation of a specialized 3x3 SVD algorithm described in "Computing the Singular Value Decomposition of 3x3 matrices with minimal branching and elementary floating point operations", by A. McAdams, A. Selle, R. Tamstorf, J. Teran, E. Sifakis.

http://pages.cs.wisc.edu/~sifakis/papers/SVD_TR1690.pdf