easytensor-2.1.1.0: Pure, type-indexed haskell vector, matrix, and tensor library.
Safe HaskellNone
LanguageHaskell2010

Numeric.Matrix.QR

Synopsis

Documentation

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

Result of QR factorization \( A = QR \).

Constructors

QR 

Fields

  • qrQ :: Matrix t n n

    Orthogonal matrix \( Q \)

  • qrQDet :: Scalar t

    A shortcut for evaluating a determinant of \( |Q| = \pm 1 \)

  • qrR :: Matrix t n m

    Upper-triangular matrix \( R \)

Instances

Instances details
(Eq t, PrimBytes t, KnownDim n, KnownDim m) => Eq (QR t n m) Source # 
Instance details

Defined in Numeric.Matrix.QR

Methods

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

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

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

Defined in Numeric.Matrix.QR

Methods

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

show :: QR t n m -> String #

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

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

Result of LQ factorization \( A = LQ \).

Constructors

LQ 

Fields

  • lqL :: Matrix t n m

    Lower-triangular matrix \( L \)

  • lqQ :: Matrix t m m

    Orthogonal matrix \( Q \)

  • lqQDet :: Scalar t

    A shortcut for evaluating a determinant of \( |Q| = \pm 1 \)

Instances

Instances details
(Eq t, PrimBytes t, KnownDim n, KnownDim m) => Eq (LQ t n m) Source # 
Instance details

Defined in Numeric.Matrix.QR

Methods

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

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

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

Defined in Numeric.Matrix.QR

Methods

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

show :: LQ t n m -> String #

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

class (PrimBytes t, Ord t, Epsilon t, KnownDim n, KnownDim m) => MatrixQR t (n :: Nat) (m :: Nat) where Source #

Methods

qr :: Matrix t n m -> QR t n m Source #

Compute QR factorization

lq :: Matrix t n m -> LQ t n m Source #

Compute LQ factorization

Instances

Instances details
(PrimBytes t, Ord t, Epsilon t, KnownDim n, KnownDim m) => MatrixQR t n m Source # 
Instance details

Defined in Numeric.Matrix.QR

Methods

qr :: Matrix t n m -> QR t n m Source #

lq :: Matrix t n m -> LQ t n m Source #

detViaQR :: forall t n. MatrixQR t n n => Matrix t n n -> Scalar t Source #

Calculate determinant of a matrix via QR decomposition

inverseViaQR :: forall t n. MatrixQR t n n => Matrix t n n -> Matrix t n n Source #

Calculate inverse of a matrix via QR decomposition

qrSolveR :: forall t (n :: Nat) (m :: Nat) (ds :: [Nat]). (MatrixQR t n m, Dimensions ds) => Matrix t n m -> DataFrame t (n :+ ds) -> DataFrame t (m :+ ds) Source #

Compute a QR or LQ decomposition of matrix \( A : n \times m \), and solve a system of linear equations \( Ax = b \).

If \( n >= m \) QR decomposition is used; if \( n > m \) this function solves linear least squares problem. If \( n < m \) (underdetermined system) LQ decomposition is used to yield a minimum norm solution.

qrSolveL :: forall t (n :: Nat) (m :: Nat) (ds :: [Nat]). (MatrixQR t n m, Dimensions ds) => Matrix t n m -> DataFrame t (ds +: m) -> DataFrame t (ds +: n) Source #

Compute a QR or LQ decomposition of matrix \( A : n \times m \), and solve a system of linear equations \( xA = b \).

If \( n <= m \) LQ decomposition is used; if \( n < m \) this function solves linear least squares problem. If \( n > m \) (underdetermined system) QR decomposition is used to yield a minimum norm solution.