matrix-sized-0.1.1: Haskell matrix library with interface to C++ linear algebra libraries.

Safe HaskellNone
LanguageHaskell2010

Data.Matrix.Static.LinearAlgebra

Contents

Synopsis

Documentation

class Arithmetic (mat1 :: MatrixKind) (mat2 :: MatrixKind) where Source #

Methods

(@@) :: (Numeric a, SingI n, SingI m, If (mat1 == mat2) mat1 Matrix ~ mat3) => mat1 n p Vector a -> mat2 p m Vector a -> mat3 n m Vector a infixr 8 Source #

Matrix multiplication between different types of matrices.

(%+%) :: (Numeric a, SingI n, SingI m, If (mat1 == mat2) mat1 Matrix ~ mat3) => mat1 n m Vector a -> mat2 n m Vector a -> mat3 n m Vector a infixr 8 Source #

Element-wise addition between different types of matrices.

(%-%) :: (Numeric a, SingI n, SingI m, If (mat1 == mat2) mat1 Matrix ~ mat3) => mat1 n m Vector a -> mat2 n m Vector a -> mat3 n m Vector a infixr 8 Source #

Element-wise substraction between different types of matrices.

(%*%) :: (Numeric a, SingI n, SingI m, If (mat1 == mat2) mat1 SparseMatrix ~ mat3) => mat1 n m Vector a -> mat2 n m Vector a -> mat3 n m Vector a infixr 8 Source #

Element-wise multiplication between different types of matrices.

Instances
Arithmetic Matrix Matrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

(@@) :: (Numeric a, SingI n, SingI m, If (Matrix == Matrix) Matrix Matrix ~ mat3) => Matrix n p Vector a -> Matrix p m Vector a -> mat3 n m Vector a Source #

(%+%) :: (Numeric a, SingI n, SingI m, If (Matrix == Matrix) Matrix Matrix ~ mat3) => Matrix n m Vector a -> Matrix n m Vector a -> mat3 n m Vector a Source #

(%-%) :: (Numeric a, SingI n, SingI m, If (Matrix == Matrix) Matrix Matrix ~ mat3) => Matrix n m Vector a -> Matrix n m Vector a -> mat3 n m Vector a Source #

(%*%) :: (Numeric a, SingI n, SingI m, If (Matrix == Matrix) Matrix SparseMatrix ~ mat3) => Matrix n m Vector a -> Matrix n m Vector a -> mat3 n m Vector a Source #

Arithmetic Matrix SparseMatrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

(@@) :: (Numeric a, SingI n, SingI m, If (Matrix == SparseMatrix) Matrix Matrix ~ mat3) => Matrix n p Vector a -> SparseMatrix p m Vector a -> mat3 n m Vector a Source #

(%+%) :: (Numeric a, SingI n, SingI m, If (Matrix == SparseMatrix) Matrix Matrix ~ mat3) => Matrix n m Vector a -> SparseMatrix n m Vector a -> mat3 n m Vector a Source #

(%-%) :: (Numeric a, SingI n, SingI m, If (Matrix == SparseMatrix) Matrix Matrix ~ mat3) => Matrix n m Vector a -> SparseMatrix n m Vector a -> mat3 n m Vector a Source #

(%*%) :: (Numeric a, SingI n, SingI m, If (Matrix == SparseMatrix) Matrix SparseMatrix ~ mat3) => Matrix n m Vector a -> SparseMatrix n m Vector a -> mat3 n m Vector a Source #

Arithmetic SparseMatrix Matrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

(@@) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == Matrix) SparseMatrix Matrix ~ mat3) => SparseMatrix n p Vector a -> Matrix p m Vector a -> mat3 n m Vector a Source #

(%+%) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == Matrix) SparseMatrix Matrix ~ mat3) => SparseMatrix n m Vector a -> Matrix n m Vector a -> mat3 n m Vector a Source #

(%-%) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == Matrix) SparseMatrix Matrix ~ mat3) => SparseMatrix n m Vector a -> Matrix n m Vector a -> mat3 n m Vector a Source #

(%*%) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == Matrix) SparseMatrix SparseMatrix ~ mat3) => SparseMatrix n m Vector a -> Matrix n m Vector a -> mat3 n m Vector a Source #

Arithmetic SparseMatrix SparseMatrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

(@@) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == SparseMatrix) SparseMatrix Matrix ~ mat3) => SparseMatrix n p Vector a -> SparseMatrix p m Vector a -> mat3 n m Vector a Source #

(%+%) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == SparseMatrix) SparseMatrix Matrix ~ mat3) => SparseMatrix n m Vector a -> SparseMatrix n m Vector a -> mat3 n m Vector a Source #

(%-%) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == SparseMatrix) SparseMatrix Matrix ~ mat3) => SparseMatrix n m Vector a -> SparseMatrix n m Vector a -> mat3 n m Vector a Source #

(%*%) :: (Numeric a, SingI n, SingI m, If (SparseMatrix == SparseMatrix) SparseMatrix SparseMatrix ~ mat3) => SparseMatrix n m Vector a -> SparseMatrix n m Vector a -> mat3 n m Vector a Source #

class Factorization mat where Source #

Methods

eigS :: (SingI k, SingI n, k <= (n - 2)) => Sing k -> mat n n Vector Double -> (Matrix k 1 (Complex Double), Matrix n k (Complex Double)) Source #

Eigenvalues (from largest to smallest) and eigenvectors (as columns) of a general square matrix.

eigSH :: (SingI k, SingI n, k <= (n - 1)) => Sing k -> mat n n Vector Double -> (Matrix k 1 Double, Matrix n k Double) Source #

Eigenvalues (from largest to smallest) and eigenvectors (as columns) of a symmetric square matrix.

cholesky :: (Numeric a, SingI n) => mat n n Vector a -> mat n n Vector a Source #

Cholesky decomposition

Instances
Factorization Matrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

eigS :: (SingI k, SingI n, k <= (n - 2)) => Sing k -> Matrix n n Vector Double -> (Matrix0 k 1 (Complex Double), Matrix0 n k (Complex Double)) Source #

eigSH :: (SingI k, SingI n, k <= (n - 1)) => Sing k -> Matrix n n Vector Double -> (Matrix0 k 1 Double, Matrix0 n k Double) Source #

cholesky :: (Numeric a, SingI n) => Matrix n n Vector a -> Matrix n n Vector a Source #

Factorization SparseMatrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

eigS :: (SingI k, SingI n, k <= (n - 2)) => Sing k -> SparseMatrix n n Vector Double -> (Matrix k 1 (Complex Double), Matrix n k (Complex Double)) Source #

eigSH :: (SingI k, SingI n, k <= (n - 1)) => Sing k -> SparseMatrix n n Vector Double -> (Matrix k 1 Double, Matrix n k Double) Source #

cholesky :: (Numeric a, SingI n) => SparseMatrix n n Vector a -> SparseMatrix n n Vector a Source #

class LinearAlgebra (mat :: MatrixKind) where Source #

Minimal complete definition

ident

Methods

ident :: (Numeric a, SingI n) => mat n n Vector a Source #

colSum :: (Numeric a, SingI n, Matrix mat Vector a) => mat m n Vector a -> Matrix 1 n a Source #

rowSum :: (Numeric a, SingI m, Matrix mat Vector a) => mat m n Vector a -> Matrix m 1 a Source #

Instances
LinearAlgebra Matrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

ident :: (Numeric a, SingI n) => Matrix n n Vector a Source #

colSum :: (Numeric a, SingI n, Matrix0 Matrix Vector a) => Matrix m n Vector a -> Matrix1 1 n a Source #

rowSum :: (Numeric a, SingI m, Matrix0 Matrix Vector a) => Matrix m n Vector a -> Matrix1 m 1 a Source #

LinearAlgebra SparseMatrix Source # 
Instance details

Defined in Data.Matrix.Static.LinearAlgebra

Methods

ident :: (Numeric a, SingI n) => SparseMatrix n n Vector a Source #

colSum :: (Numeric a, SingI n, Matrix SparseMatrix Vector a) => SparseMatrix m n Vector a -> Matrix 1 n a Source #

rowSum :: (Numeric a, SingI m, Matrix SparseMatrix Vector a) => SparseMatrix m n Vector a -> Matrix m 1 a Source #

Dense matrix operation

zeros :: (SingI m, SingI n) => Matrix m n Double Source #

ones :: (SingI m, SingI n) => Matrix m n Double Source #

inverse :: (SingI n, Numeric a) => Matrix n n a -> Matrix n n a Source #

The inverse of a dense matrix.

eig :: forall n. SingI n => Matrix n n Double -> (Matrix n 1 (Complex Double), Matrix n n (Complex Double)) Source #

Compute the full eigendecomposition for dense matrix.

svd :: forall n p a m. (Numeric (R a), Numeric a, SingI n, SingI p, SingI m, m ~ Min n p) => Matrix n p a -> (Matrix n m a, Matrix m 1 (R a), Matrix p m a) Source #

Compute the full singular value decomposition for dense matrix.

cond :: (Numeric a, Numeric (R a), Ord (R a), Fractional (R a), SingI n, SingI m, SingI (Min n m)) => Matrix n m a -> R a Source #

Condition number.