tensor-0.1.1: A completely type-safe library for linear algebra

Safe HaskellSafe-Infered

Data.Tensor.LinearAlgebra

Synopsis

Documentation

class VectorSpace v whereSource

Methods

zero :: Num e => v eSource

(*.) :: Num e => e -> v e -> v eSource

(.+.) :: Num e => v e -> v e -> v eSource

Instances

class Cardinal n => Product n t1 t2 whereSource

A general form of product between two tensors, in which the last n dimensions of t1 are contracted with the first n dimensions of t2. The resulting tensor belongs to the space ProdSpace n t1 t2. MatrixProduct and TensorProduct below are particular cases where n is equal to 1 and 0 respectively.

Associated Types

type ProdSpace n t1 t2 Source

Methods

prod :: n -> t1 -> t2 -> ProdSpace n t1 t2Source

Instances

(Num e, Cardinal n, MultiIndex i, MultiIndex j, JoinList n i j) => Product n (Tensor i e) (Tensor j e) 

class MatrixProduct t1 t2 whereSource

It is the product of the last dimension of t1 with the first dimension of t2. In the case where t1 and t2 are matrices this coincide with the ordinary matrix product.

Associated Types

type MatrixProductSpace t1 t2 Source

Methods

(.*.) :: t1 -> t2 -> MatrixProductSpace t1 t2Source

Instances

Product (Succ Zero) t1 t2 => MatrixProduct t1 t2 

class TensorProduct t1 t2 whereSource

Tensor product of t1 and t2.

Associated Types

type t1 :⊗: t2 Source

Methods

(⊗) :: t1 -> t2 -> t1 :⊗: t2Source

Instances

Product C0 t1 t2 => TensorProduct t1 t2 

class DotProduct t whereSource

Methods

dot :: Num e => t e -> t e -> eSource

Instances

class (Tensor t, Index t ~ (i :|: (j :|: Nil))) => Matrix i j t whereSource

A matrix with i rows and j columns.

Methods

rowSwitch :: i -> i -> t -> tSource

Switch two rows.

rowMult :: (Num e, Elem t ~ e) => i -> Elem t -> t -> tSource

Multiply a row by a number.

rowAdd :: (Num e, Elem t ~ e) => i -> Elem t -> i -> t -> tSource

rowAdd i1 a i2 t adds a times the row i2 to the row i1 ot t.

colSwitch :: j -> j -> t -> tSource

Switch two columns.

colMult :: (Num e, Elem t ~ e) => j -> Elem t -> t -> tSource

Multiply a column by a number.

colAdd :: (Num e, Elem t ~ e) => j -> Elem t -> j -> t -> tSource

colAdd j1 a j2 t adds a times the column j2 to the column j1 ot t.

rowEchelonForm :: (Eq e, Fractional e, Elem t ~ e) => t -> tSource

Reduced row echelon form of the matrix.

Instances

(Bounded i, Ordinal i, Bounded j, Ordinal j) => Matrix i j (Tensor (:|: i (:|: j Nil)) e) 

class LinearSystem t1 t2 whereSource

Solves linear systems AX=B; t1 is the type of A, t2 is the type of B, and SolSpace t1 t2 is the type of the solution X.

Associated Types

type SolSpace t1 t2 Source

Methods

triangularSolve :: t1 -> t2 -> (t1, t2)Source

Performs row operations on the augmented matrix [t1,t2] until t1 is in reduced row echelon form, then slits the result.

parametricSolve :: t1 -> t2 -> Maybe (SolSpace t1 t2, [SolSpace t1 t2])Source

Returns Nothing if the system AX=B has no solution, otherwise returns a solution for the system and a list of basis vectors for the kernel of A.

Instances

(Eq e, Fractional e, Ordinal i, Ordinal j) => LinearSystem (Tensor (:|: i (:|: j Nil)) e) (Tensor (:|: i Nil) e) 
(Eq e, Fractional e, Ordinal i, Ordinal j, Ordinal k, Sum j k) => LinearSystem (Tensor (:|: i (:|: j Nil)) e) (Tensor (:|: i (:|: k Nil)) e) 

class SquareMatrix t whereSource

Methods

unit :: Num e => t eSource

Indentity matrix.

inverse :: (Eq e, Fractional e) => t e -> Maybe (t e)Source

Inverts, if the matrix is invertible, otherwise Nothing.

tr :: Num e => t e -> eSource

Trace of the matrix.

charPoly :: Num e => t e -> [e]Source

Computes the coefficient of the polynomial p(z)=det(A+zI) using the method of closed ordered walks (clow) illustrated in the paper of G. Rote http://page.mi.fu-berlin.de/rote/Papers/pdf/Division-free+algorithms.pdf. The number of operations for the whole process is O(n^4), where n is the number of rows of the matrix. The first coefficient is the known term and equals the determinant, while the last one is the coefficient of z^(n-1) and equals the trace. The coefficient of z^n equals 1 and is not included in the resulting list. The k-th coefficient is the sum of all principal minors of order n-k+1.

det :: Num e => t e -> eSource

Determinant of the matrix.

Instances

(Bounded i, Ordinal i, Sum i i) => SquareMatrix (Tensor (:|: i (:|: i Nil)))