static-tensor-0.1.0.0: Tensors of statically known size

Copyright(C) 2017 Alexey Vagarenko
LicenseBSD-style (see LICENSE)
MaintainerAlexey Vagarenko (vagarenko@gmail.com)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Matrix.Static

Contents

Description

 

Synopsis

Matrix

type Matrix m n e = Tensor '[m, n] e Source #

Matrix with m rows, n columns

type MatrixConstructor m n e = TensorConstructor '[m, n] e Source #

Type of matrix data constructor.

type IsMatrix m n e = IsTensor '[m, n] e Source #

Matrix constraint.

Matrix construction

matrix :: forall m n e. IsMatrix m n e => MatrixConstructor m n e Source #

Alias for a conrete matrix data constructor.

identity Source #

Arguments

:: (IsMatrix m m e, Generate '[m, m] e ([Nat] -> Constraint) (IdentityWrk e), Num e) 
=> Matrix m m e 

Identity matrix of size m*m

type Identity m e = (IsMatrix m m e, Generate '[m, m] e ([Nat] -> Constraint) (IdentityWrk e), Num e) Source #

Constraints for identity function.

Matrix elements

Rows

row Source #

Arguments

:: forall (r :: Nat) (m :: Nat) (n :: Nat). Row r m n e 
=> Lens' (Matrix m n e) (Vector n e) 

Lens for the row number r of the matrix mxn.

>>> matrix @2 @2 @Float 0 1 2 3 ^. row @0
Tensor'2 [0.0,1.0]
>>> set (row @1) (vector @2 @Float 20 30) (matrix @2 @2 @Float 0 1 2 3)
Tensor'2'2 [[0.0,1.0],[20.0,30.0]]

type Row (r :: Nat) (m :: Nat) (n :: Nat) e = (SubtensorCtx '[r] '[m, n] e, r <= (m - 1), NormalizeDims '[n] ~ '[n]) Source #

Constraints for row function.

getRowElems Source #

Arguments

:: forall (r :: Nat) (m :: Nat) (n :: Nat). GetRowElems r m n e 
=> Matrix m n e 
-> [e] 

List of elements of the row number r of the matrix mxn.

>>> getRowElems @0 (matrix @2 @2 @Float 0 1 2 3)
[0.0,1.0]

type GetRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = GetSubtensorElems '[r] '[m, n] e Source #

Constraints for getRowElems function.

setRowElems Source #

Arguments

:: forall (r :: Nat) (m :: Nat) (n :: Nat). SetRowElems r m n e 
=> Matrix m n e

The matrix.

-> [e]

New row elements.

-> Maybe (Matrix m n e) 

Put elements of the list into row number r. The list must have enough elements.

>>> setRowElems @1 (matrix @2 @2 @Float 0 1 2 3) [20, 30]
Just Tensor'2'2 [[0.0,1.0],[20.0,30.0]]
>>> setRowElems @1 (matrix @2 @2 @Float 0 1 2 3) [20]
Nothing

type SetRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = SetSubtensorElems '[r] '[m, n] e Source #

Constraints for setRowElems function.

mapRowElems Source #

Arguments

:: forall (r :: Nat) (m :: Nat) (n :: Nat). MapRowElems r m n e 
=> Matrix m n e

The matrix.

-> (e -> e)

The mapping function.

-> Matrix m n e 

Apply a function to all elements of the row number r.

>>> mapRowElems @1 (matrix @2 @2 @Float 0 1 2 3) (* 100)
Tensor'2'2 [[0.0,1.0],[200.0,300.0]]

type MapRowElems (r :: Nat) (m :: Nat) (n :: Nat) e = MapSubtensorElems '[r] '[m, n] e Source #

Constraints for mapRowElems function.

Columns

col Source #

Arguments

:: forall (c :: Nat) (m :: Nat) (n :: Nat). Col c m n e 
=> Lens' (Matrix m n e) (Vector m e) 

Lens for the column number c of the matrix mxn.

>>> matrix @2 @2 @Float 0 1 2 3 ^. col @0
Tensor'2 [0.0,2.0]
>>> set (col @1) (vector @2 @Float 10 30) (matrix @2 @2 @Float 0 1 2 3)
Tensor'2'2 [[0.0,10.0],[2.0,30.0]]

type Col (c :: Nat) (m :: Nat) (n :: Nat) e = (Slice '[0, c] '[m, 1] '[m, n] e, NormalizeDims '[m, 1] ~ '[m]) Source #

Constraints for col function.

getColElems Source #

Arguments

:: forall (c :: Nat) (m :: Nat) (n :: Nat). GetColElems c m n e 
=> Matrix m n e 
-> [e] 

List of elements of the column number c of the matrix mxn.

>>> getColElems @0 (matrix @2 @2 @Float 0 1 2 3)
[0.0,2.0]

type GetColElems (c :: Nat) (m :: Nat) (n :: Nat) e = GetSliceElems '[0, c] '[m, 1] '[m, n] e Source #

Constraints for getColElems function.

setColElems Source #

Arguments

:: forall (c :: Nat) (m :: Nat) (n :: Nat). SetColElems c m n e 
=> Matrix m n e

The matrix.

-> [e]

New column elements.

-> Maybe (Matrix m n e) 

Put elements of the list into column number r. The list must have enough elements.

>>> setColElems @1 (matrix @2 @2 @Float 0 1 2 3) [10, 30]
Just Tensor'2'2 [[0.0,10.0],[2.0,30.0]]
>>> setColElems @1 (matrix @2 @2 @Float 0 1 2 3) [10]
Nothing

type SetColElems (c :: Nat) (m :: Nat) (n :: Nat) e = SetSliceElems '[0, c] '[m, 1] '[m, n] e Source #

Constraints for setColElems function.

mapColElems Source #

Arguments

:: forall (c :: Nat) (m :: Nat) (n :: Nat). MapColElems c m n e 
=> Matrix m n e 
-> (e -> e) 
-> Matrix m n e 

Apply a function to all elements of the column number c.

>>> mapColElems @1 (matrix @2 @2 @Float 0 1 2 3) (* 100)
Tensor'2'2 [[0.0,100.0],[2.0,300.0]]

type MapColElems (c :: Nat) (m :: Nat) (n :: Nat) e = MapSliceElems '[0, c] '[m, 1] '[m, n] e Source #

Constraints for mapColElems function.

Matrix multiplication

type family MatrixMultDims (dims0 :: [Nat]) (dims1 :: [Nat]) :: [Nat] where ... Source #

Shape of the result of matrix multiplication.

Equations

MatrixMultDims '[m, n] '[n, o] = '[m, o] 
MatrixMultDims '[n] '[n, o] = '[o] 
MatrixMultDims '[m, n] '[n] = '[m] 
MatrixMultDims a b = TypeError ((((Text "Matrices of shapes " :<>: ShowType a) :<>: Text " and ") :<>: ShowType b) :<>: Text " are incompatible for multiplication.") 

class MatrixMult (dims0 :: [Nat]) (dims1 :: [Nat]) e where Source #

Matrix multiplication.

Minimal complete definition

mult

Methods

mult Source #

Arguments

:: (IsTensor dims0 e, IsTensor dims1 e, IsTensor (MatrixMultDims dims0 dims1) e) 
=> Tensor dims0 e 
-> Tensor dims1 e 
-> Tensor (MatrixMultDims dims0 dims1) e 

Multiply two matrices, or matrix and vector. Matrices (or matrix and vector) must have compatible dimensions.

Instances

(Num e, Generate (MatrixMultDims ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ((:) Nat o ([] Nat)))) e ((~>) [Nat] Constraint) (MultMatMatGoSym4 m n o e)) => MatrixMult ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ((:) Nat o ([] Nat))) e Source #

Multiply two matrices.

Methods

mult :: Tensor ((Nat ': m) ((Nat ': n) [Nat])) e -> Tensor ((Nat ': n) ((Nat ': o) [Nat])) e -> Tensor (MatrixMultDims ((Nat ': m) ((Nat ': n) [Nat])) ((Nat ': n) ((Nat ': o) [Nat]))) e Source #

(Num e, Generate (MatrixMultDims ((:) Nat n ([] Nat)) ((:) Nat n ((:) Nat o ([] Nat)))) e ((~>) [Nat] Constraint) (MultVecMatGoSym4 m n o e)) => MatrixMult ((:) Nat n ([] Nat)) ((:) Nat n ((:) Nat o ([] Nat))) e Source #

Multiply vector and matrix.

Methods

mult :: Tensor ((Nat ': n) [Nat]) e -> Tensor ((Nat ': n) ((Nat ': o) [Nat])) e -> Tensor (MatrixMultDims ((Nat ': n) [Nat]) ((Nat ': n) ((Nat ': o) [Nat]))) e Source #

(Num e, Generate (MatrixMultDims ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ([] Nat))) e ((~>) [Nat] Constraint) (MultMatVecGoSym4 m n o e)) => MatrixMult ((:) Nat m ((:) Nat n ([] Nat))) ((:) Nat n ([] Nat)) e Source #

Multiply matrix and vector.

Methods

mult :: Tensor ((Nat ': m) ((Nat ': n) [Nat])) e -> Tensor ((Nat ': n) [Nat]) e -> Tensor (MatrixMultDims ((Nat ': m) ((Nat ': n) [Nat])) ((Nat ': n) [Nat])) e Source #

Matrix operations

transpose Source #

Arguments

:: Transpose m n e 
=> Matrix m n e 
-> Matrix n m e 

Transpose a matrix.

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this function. Expect it to be slower than most of the functions in the package.

type Transpose m n e = (IsMatrix m n e, IsMatrix n m e, Generate '[n, m] e ([Nat] ~> Constraint) (TransposeGoSym3 m n e)) Source #

Constraints for transpose function.

minorMatrix Source #

Arguments

:: forall (i :: Nat) (j :: Nat) (n :: Nat). Generate [n - 1, n - 1] e ([Nat] ~> Constraint) (MinorMatrixGoSym4 i j n e) 
=> Matrix n n e 
-> Matrix (n - 1) (n - 1) e 

Minor matrix is a matrix made by deleting i-th row and j-th column from given square matrix.

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this function. Expect it to be slower than most of the functions in the package.

type MinorMatrix (i :: Nat) (j :: Nat) (n :: Nat) e = Generate [n - 1, n - 1] e ([Nat] ~> Constraint) (MinorMatrixGoSym4 i j n e) Source #

Constraint for minorMatrix function.

class Determinant (n :: Nat) e where Source #

Determinant of a matrix.

Minimal complete definition

determinant

Methods

determinant :: Num e => Matrix n n e -> e Source #

Instances

(Num e, IsMatrix n n e, DemoteWith Nat ((~>) Nat Constraint) (DeterminantGoSym2 n e) (NatsFromTo 0 ((-) n 1)), Sum n e) => Determinant n e Source #

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this method. Expect it to be slower than most of the functions in the package.

Methods

determinant :: Matrix n n e -> e Source #

(Num e, IsMatrix 2 2 e) => Determinant 2 e Source # 

Methods

determinant :: Matrix 2 2 e -> e Source #

(Num e, IsMatrix 3 3 e) => Determinant 3 e Source # 

Methods

determinant :: Matrix 3 3 e -> e Source #

minor Source #

Arguments

:: forall (i :: Nat) (j :: Nat) (n :: Nat). Minor i j n e 
=> Matrix n n e 
-> e 

Minor is the determinant of minor matrix.

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this function. Expect it to be slower than most of the functions in the package.

type Minor (i :: Nat) (j :: Nat) (n :: Nat) e = (MinorMatrix i j n e, Determinant (n - 1) e, Num e) Source #

Constraint for minor function.

cofactor Source #

Arguments

:: forall (i :: Nat) (j :: Nat) (n :: Nat). Cofactor i j n e 
=> Matrix n n e 
-> e 

cofactor @i @j is the minor @i @j multiplied by (-1) ^ (i + j).

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this function. Expect it to be slower than most of the functions in the package.

type Cofactor (i :: Nat) (j :: Nat) (n :: Nat) e = (Minor i j n e, Sign (i + j)) Source #

Constraint for cofactor function.

cofactorMatrix Source #

Arguments

:: forall (n :: Nat). CofactorMatrix n e 
=> Matrix n n e 
-> Matrix n n e 

The matrix formed by all of the cofactors of given square matrix.

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this function. Expect it to be slower than most of the functions in the package.

type CofactorMatrix (n :: Nat) e = Generate [n, n] e ([Nat] ~> Constraint) (CofactorMatrixGoSym2 n e) Source #

Constraint for cofactorMatrix function.

adjugateMatrix Source #

Arguments

:: forall (n :: Nat). AdjugateMatrix n e 
=> Matrix n n e 
-> Matrix n n e 

Adjugate matrix of given square matrix is the transpose of its cofactor matrix.

adjugateMatrix = transpose . cofactorMatrix

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this function. Expect it to be slower than most of the functions in the package.

type AdjugateMatrix (n :: Nat) e = (CofactorMatrix n e, Transpose n n e) Source #

Constraint for adjugateMatrix function.

inverse Source #

Arguments

:: forall (n :: Nat). Inverse n e 
=> Matrix n n e 
-> Matrix n n e 

Inverse of the matrix.

Note: at the moment(GHC-8.2.1) the compiler generates suboptimal core for this function. Expect it to be slower than most of the functions in the package.

type Inverse (n :: Nat) e = (AdjugateMatrix n e, Determinant n e, Fractional e, Scale '[n, n] e) Source #

Constraint for inverse function.

Generating matrix instances

genMatrixInstance Source #

Arguments

:: Int

Number of rows.

-> Int

Number of columns.

-> Name

Type of elements.

-> Q [Dec] 

Generate instance of a matrix.