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

Numeric.Matrix.LU

Synopsis

Documentation

class (KnownDim n, Ord t, Fractional t, PrimBytes t, KnownBackend t '[n, n]) => MatrixLU t (n :: Nat) where Source #

Methods

lu :: Matrix t n n -> LU t n Source #

Compute LU factorization with Partial Pivoting

Instances

Instances details
(KnownDim n, Ord t, Fractional t, PrimBytes t, KnownBackend t '[n, n]) => MatrixLU t n Source # 
Instance details

Defined in Numeric.Matrix.LU

Methods

lu :: Matrix t n n -> LU t n Source #

data LU (t :: Type) (n :: Nat) Source #

Result of LU factorization with Partial Pivoting \( PA = LU \).

Constructors

LU 

Fields

  • luLower :: Matrix t n n

    Unit lower triangular matrix \(L\). All elements on the diagonal of L equal 1. The rest of the elements satisfy \(|l_{ij}| \leq 1\).

  • luUpper :: Matrix t n n

    Upper triangular matrix \(U\)

  • luPerm :: Matrix t n n

    Row permutation matrix \(P\)

  • luPermDet :: Scalar t

    Sign of permutation luPermDet == det . luPerm; \(|P| = \pm 1\).

Instances

Instances details
(Eq (Matrix t n n), Eq t) => Eq (LU t n) Source # 
Instance details

Defined in Numeric.Matrix.LU

Methods

(==) :: LU t n -> LU t n -> Bool #

(/=) :: LU t n -> LU t n -> Bool #

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

Defined in Numeric.Matrix.LU

Methods

showsPrec :: Int -> LU t n -> ShowS #

show :: LU t n -> String #

showList :: [LU t n] -> ShowS #

luSolveR :: forall t (n :: Nat) (ds :: [Nat]). (MatrixLU t n, Dimensions ds) => LU t n -> DataFrame t (n :+ ds) -> DataFrame t (n :+ ds) Source #

Solve Ax = b problem given LU decomposition of A.

luSolveL :: forall t (n :: Nat) (ds :: [Nat]). (MatrixLU t n, Dimensions ds) => LU t n -> DataFrame t (ds +: n) -> DataFrame t (ds +: n) Source #

Solve xA = b problem given LU decomposition of A.

detViaLU :: forall (t :: Type) (n :: Nat). MatrixLU t n => Matrix t n n -> Scalar t Source #

Calculate determinant of a matrix via LU decomposition

inverseViaLU :: forall (t :: Type) (n :: Nat). MatrixLU t n => Matrix t n n -> Matrix t n n Source #

Calculate inverse of a matrix via LU decomposition