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

Copyright(c) Artem Chirkin
LicenseBSD3
Maintainerchirkin@arch.ethz.ch
Safe HaskellNone
LanguageHaskell2010

Numeric.Matrix

Contents

Description

 
Synopsis

Documentation

class MatrixTranspose t (n :: k) (m :: k) where Source #

Minimal complete definition

transpose

Methods

transpose :: Matrix t n m -> Matrix t m n Source #

Transpose Mat

Instances
MatrixTranspose (t :: Type) (xn :: XNat) (xm :: XNat) Source # 
Instance details

Defined in Numeric.Matrix

Methods

transpose :: Matrix t xn xm -> Matrix t xm xn Source #

(KnownDim n, KnownDim m, PrimArray t (Matrix t n m), PrimArray t (Matrix t m n)) => MatrixTranspose (t :: *) (n :: Nat) (m :: Nat) Source # 
Instance details

Defined in Numeric.Matrix

Methods

transpose :: Matrix t n m -> Matrix t m n Source #

class SquareMatrix t (n :: Nat) where Source #

Minimal complete definition

eye, diag, trace

Methods

eye :: Matrix t n n Source #

Mat with 1 on diagonal and 0 elsewhere

diag :: Scalar t -> Matrix t n n Source #

Put the same value on the Mat diagonal, 0 otherwise

trace :: Matrix t n n -> Scalar t Source #

Sum of diagonal elements

Instances
(KnownDim n, PrimArray t (Matrix t n n), Num t) => SquareMatrix t n Source # 
Instance details

Defined in Numeric.Matrix

Methods

eye :: Matrix t n n Source #

diag :: Scalar t -> Matrix t n n Source #

trace :: Matrix t n n -> Scalar t Source #

class MatrixDeterminant t (n :: Nat) where Source #

Minimal complete definition

det

Methods

det :: Matrix t n n -> Scalar t Source #

Determinant of Mat

Instances
(KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n)) => MatrixDeterminant t n Source # 
Instance details

Defined in Numeric.Matrix

Methods

det :: Matrix t n n -> Scalar t Source #

class MatrixInverse t (n :: Nat) where Source #

Minimal complete definition

inverse

Methods

inverse :: Matrix t n n -> Matrix t n n Source #

Matrix inverse

Instances
(KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n), PrimArray t (Vector t n), PrimBytes (Vector t n), PrimBytes (Matrix t n n)) => MatrixInverse (t :: *) n Source # 
Instance details

Defined in Numeric.Matrix

Methods

inverse :: Matrix t n n -> Matrix t n n Source #

class MatrixLU t (n :: Nat) where Source #

Minimal complete definition

lu

Methods

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

Compute LU factorization with Partial Pivoting

Instances
(KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n)) => MatrixLU t n Source # 
Instance details

Defined in Numeric.Matrix

Methods

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

data LUFact t n Source #

Result of LU factorization with Partial Pivoting PA = LU .

Constructors

LUFact 

Fields

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

Defined in Numeric.Matrix.Class

Methods

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

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

(Show (Matrix t n n), Show t) => Show (LUFact t n) Source # 
Instance details

Defined in Numeric.Matrix.Class

Methods

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

show :: LUFact t n -> String #

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

type Matrix (t :: l) (n :: k) (m :: k) = DataFrame t '[n, m] Source #

Alias for DataFrames of rank 2

mat22 :: (PrimBytes (Vector (t :: Type) 2), PrimBytes (Matrix t 2 2)) => Vector t 2 -> Vector t 2 -> Matrix t 2 2 Source #

Compose a 2x2D matrix

mat33 :: (PrimBytes (t :: Type), PrimBytes (Vector t 3), PrimBytes (Matrix t 3 3)) => Vector t 3 -> Vector t 3 -> Vector t 3 -> Matrix t 3 3 Source #

Compose a 3x3D matrix

mat44 :: forall (t :: Type). (PrimBytes t, PrimBytes (Vector t (4 :: Nat)), PrimBytes (Matrix t (4 :: Nat) (4 :: Nat))) => Vector t (4 :: Nat) -> Vector t (4 :: Nat) -> Vector t (4 :: Nat) -> Vector t (4 :: Nat) -> Matrix t (4 :: Nat) (4 :: Nat) Source #

Compose a 4x4D matrix

(%*) :: (ConcatList as bs (as ++ bs), Contraction t as bs asbs, KnownDim m, PrimArray t (DataFrame t (as +: m)), PrimArray t (DataFrame t (m :+ bs)), PrimArray t (DataFrame t (as ++ bs))) => DataFrame t (as +: m) -> DataFrame t (m :+ bs) -> DataFrame t (as ++ bs) infixl 7 Source #

Tensor contraction. In particular: 1. matrix-matrix product 2. matrix-vector or vector-matrix product 3. dot product of two vectors.

pivotMat :: forall (t :: Type) (n :: k). (KnownDim n, PrimArray t (Matrix t n n), Ord t, Num t) => Matrix t n n -> (Matrix t n n, Matrix t n n, Scalar t) Source #

Permute rows that the largest magnitude elements in columns are on diagonals.

Invariants of result matrix: * forall j >= i: |M[i,i]| >= M[j,i] * if M[i,i] == 0 then forall j >= i: |M[i+1,i+1]| >= M[j,i+1]

luSolve :: forall (t :: Type) (n :: Nat). (KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n), PrimArray t (Vector t n)) => LUFact t n -> Vector t n -> Vector t n Source #

Solve Ax = b problem given LU decomposition of A.

Orphan instances

(KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n)) => MatrixLU t n Source # 
Instance details

Methods

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

(KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n)) => MatrixDeterminant t n Source # 
Instance details

Methods

det :: Matrix t n n -> Scalar t Source #

(KnownDim n, PrimArray t (Matrix t n n), Num t) => SquareMatrix t n Source # 
Instance details

Methods

eye :: Matrix t n n Source #

diag :: Scalar t -> Matrix t n n Source #

trace :: Matrix t n n -> Scalar t Source #

MatrixTranspose (t :: Type) (xn :: XNat) (xm :: XNat) Source # 
Instance details

Methods

transpose :: Matrix t xn xm -> Matrix t xm xn Source #

(KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n), PrimArray t (Vector t n), PrimBytes (Vector t n), PrimBytes (Matrix t n n)) => MatrixInverse (t :: *) n Source # 
Instance details

Methods

inverse :: Matrix t n n -> Matrix t n n Source #

(KnownDim n, KnownDim m, PrimArray t (Matrix t n m), PrimArray t (Matrix t m n)) => MatrixTranspose (t :: *) (n :: Nat) (m :: Nat) Source # 
Instance details

Methods

transpose :: Matrix t n m -> Matrix t m n Source #