jalla-0.2.0.1: Higher level functions for linear algebra. Wraps BLAS and LAPACKE.

Safe HaskellNone
LanguageHaskell98

Numeric.Jalla.Matrix

Contents

Description

This is the matrix module of Jalla.

Synopsis

Classes

Matrices

class (Field1 e, Indexable (mat e) IndexPair e) => GMatrix mat e where Source

Generic matrix interface.

Minimal complete definition

Nothing

Methods

shape :: mat e -> Shape Source

rowCount :: mat e -> Index Source

colCount :: mat e -> Index Source

Instances

class (Storable e, BlasOps e, GMatrix mat e) => CMatrix mat e where Source

Interface for matrices with underlying contiguous C array storage. These matrices can be used with BLAS and LAPACK functions.

Associated Types

type CMatrixVector mat e :: * Source

This is an associated vector type that can be used with mat e.

type CMatrixVectorS mat e :: * Source

The same, but a vector type with a type that is the associated scalar of e.

Methods

matrixAlloc :: Shape -> IO (mat e) Source

withCMatrix :: mat e -> (Ptr e -> IO a) -> IO a Source

lda :: mat e -> Index Source

order :: mat e -> Order Source

matrixForeignPtr :: mat e -> ForeignPtr e Source

Instances

shapeTrans :: Transpose -> Shape -> Shape Source

Shape of a matrix with given transposedness and shape.

Matrix/Matrix Operations

class (Field1 e, BlasOps e, GMatrix mat e, CMatrix mat e) => MatrixMatrix mat e where Source

Minimal complete definition

Nothing

Methods

(##) :: mat e -> mat e -> mat e infixl 7 Source

(##!) :: (mat e, Transpose) -> (mat e, Transpose) -> mat e infixl 7 Source

(##+) :: mat e -> mat e -> mat e infixl 6 Source

(##-) :: mat e -> mat e -> mat e infixl 6 Source

Instances

Matrix/Vector Operations

class (CMatrix mat e, CVector vec e) => MatrixVector mat vec e where Source

Methods

(#|) :: mat e -> vec e -> vec e infixl 7 Source

(|#) :: vec e -> mat e -> vec e infixl 7 Source

Matrix/Scalar Operations

class (Storable e, CMatrix mat e) => MatrixScalar mat e where Source

Matrix operations with a scalar. The nomenclature is to be read Matrix - Scalar - [operation name], where # stands for matrix, . stands for scalar.

Minimal complete definition

Nothing

Methods

(#.*) :: mat e -> e -> mat e infixl 7 Source

(#./) :: mat e -> e -> mat e infixl 7 Source

(#.+) :: mat e -> e -> mat e infixl 6 Source

(#.-) :: mat e -> e -> mat e infixl 6 Source

Indexable

Data types

data Matrix e Source

This is the instance of CMatrix that Jalla provides. If you don't have another CMatrix instance, Matrix is the one you will want to use.

Instances

(Num e, Field1 e, BlasOps e) => CMatrix Matrix e Source 
BlasOps e => MatrixMatrix Matrix e Source 
(Num e, Field1 e, BlasOps e) => GMatrix Matrix e Source 
(BlasOps e, Eq e) => Eq (Matrix e) Source 
(BlasOps e, Num e, Fractional e) => Floating (Matrix e) Source

An instance of Matrix for Floating, for convenience. Some of these don't make much sense in some situations, but having the trigonometric functions and the like around can be pretty handy. The functions work element-wise.

(BlasOps e, Num e, Fractional e) => Fractional (Matrix e) Source 
(BlasOps e, Num e) => Num (Matrix e) Source

Num instance for a Matrix. The operations are all element-wise. There may be the occasional error by wrongly assuming that (*) returns the matrix product, which it doesn't. This instance is basically only provided to get the + and - operators. Note that this will not work with sum, since that assumes it can start with a "0".

(BlasOps e, Show e) => Show (Matrix e) Source 
BlasOps e => Indexable (Matrix e) IndexPair e Source 
type CMatrixVector Matrix e = Vector e Source 
type CMatrixVectorS Matrix e = Vector (FieldScalar e) Source 

data Order Source

Constructors

RowMajor 
ColumnMajor 

data RefVector e Source

A construct to enable us to reference rows and columns in matrices, thereby saving some cost on copying and memory allocation. The referenced matrix will not be garbage collected (if I understand ForeignPtr right) before one of the RefVectors referencing it.

Construction, Conversion, Manipulation

Manipulation Monad and Functions

data MMM s mat e a Source

Matrix modification monad. This is used for creating and modifying matrices efficiently.

Instances

Monad (MMM s mat e) Source 
Functor (MMM s mat e) Source 
Applicative (MMM s mat e) Source 
(BlasOps e, CMatrix mat e) => IMM (MMM s mat e) IndexPair (mat e) e Source 

createMatrix Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> Shape

(Rows, Columns)

-> MMM s mat e a

Modification action

-> mat e

Return value: The newly created matrix.

Create a new matrix of given size and run the given modification action on it; then return The new matrix.

modifyMatrix :: (BlasOps e, CMatrix mat e) => mat e -> Transpose -> MMM s mat e a -> mat e Source

Modify the given matrix using the given modification action; return the modified matrix.

setDiag Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> Index

Number of the diagonal. 0 Means the main diagonal, negative values mean lower diagonals, positive values mean upper diagonals.

-> [e]

The values of the diagonal. Only as many values as fit in the diagonal are used.

-> MMM s mat e ()

Returns the action that sets the diagonal.

Sets the diagonal with given index to the given values. Operates on the matrix that is currently under modification.

setRow Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> Index

Number of the row to set

-> [e]

List of elements to set

-> MMM s mat e () 

Set a row in the current matrix to a list of elements.

setColumn Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> Index

Number of the column to set

-> [e]

List of elements to set

-> MMM s mat e () 

Set a column in the current matrix to a list of elements.

setBlock Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> IndexPair

Position in the current matrix where to put the block

-> mat e

Matrix to put at the given position

-> MMM s mat e () 

Set the block starting at a given index to the given CMatrix.

fillBlock Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> IndexPair

Start of the range.

-> IndexPair

End of the range (inclusive).

-> e

Element to fill the range with.

-> MMM s mat e () 

Fill a range with a given element.

scaleRow Source

Arguments

:: CMatrix mat e 
=> e

Number to scale with.

-> Index

Row index. If out of range, an exception is raised.

-> MMM s mat e () 

Scales (multiplies) the given row of the matrix under construction by a scalar.

scaleColumn :: CMatrix mat e => e -> Index -> MMM s mat e () Source

Scales (multiplies) the given column of the matrix under construction by a scalar.

refRow :: CMatrix mat e => Index -> MMM s mat e (RefVector e) Source

Reference a row in the matrix under construction. See also row.

refColumn :: CMatrix mat e => Index -> MMM s mat e (RefVector e) Source

Reference a column in the matrix under construction. See also column.

Maps over CMatrix

matrixMap Source

Arguments

:: (Storable e1, Storable e2, CMatrix mat1 e1, CMatrix mat2 e2) 
=> (e1 -> e2)

Function f to map.

-> mat1 e1

Input matrix A.

-> mat2 e2

Return matrix B. B_ij = f A_ij.

Map over a CMatrix. Applies the given function to each element in the matrix and returns the resulting matrix.

matrixBinMap Source

Arguments

:: (Storable e1, Storable e2, Storable e3, CMatrix mat1 e1, CMatrix mat2 e2, CMatrix mat3 e3) 
=> (e1 -> e2 -> e3)

Function f to map.

-> mat1 e1

First input matrix A.

-> mat2 e2

Second input matrix B.

-> mat3 e3

Return matrix C. C_ij = f A_ij B_ij.

Map a binary function over two CMatrixs.

Conversions To And From Lists

matrixList :: GMatrix mat e => Order -> mat e -> [e] Source

Create a list of elements, in the given order, from the given matrix.

matrixLists :: GMatrix mat e => mat e -> [[e]] Source

Create a list of lists of elements from a matrix, representing the rows of the matrix.

listMatrix Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> Shape

Shape of the matrix

-> [e]

List of elements, row-major order

-> mat e

If the number of elements in the list matches the number needed for the given shape exactly, returns a Just Matrix; otherwise, returns Nothing.

Create a matrix from a list of elements, stored in row-major.

matrixAssocs :: (BlasOps e, CMatrix mat e) => Order -> mat e -> [(IndexPair, e)] Source

Get association list of indices and elements for the given CMatrix.

gmatrixAssocs :: GMatrix mat e => mat e -> [(IndexPair, e)] Source

Get association list of indices and elements for the given GMatrix.

Copying Rows and Columns

row :: (CMatrix mat e, CVector vec e) => mat e -> Index -> vec e Source

Get a column or row from a matrix.

column :: (CMatrix mat e, CVector vec e) => mat e -> Index -> vec e Source

Get a column or row from a matrix.

rows :: (CMatrix mat e, CVector vec e) => mat e -> [vec e] Source

Get all rows or columns from a matrix.

columns :: (CMatrix mat e, CVector vec e) => mat e -> [vec e] Source

Get all rows or columns from a matrix.

Functions From IMM Can Be Used

Printing Matrices

prettyPrintMatrix :: GMatrix mat e => mat e -> [String] Source

prettyPrintMatrixIO :: GMatrix mat e => mat e -> IO () Source

CMatrix Linear Algebra Functions

Solving Linear Systems

solveLinearSystem Source

Arguments

:: (BlasOps e, LapackeOps e se, CMatrix mat e) 
=> mat e

The matrix A

-> mat e

The matrix B, the right-hand sides.

-> mat e

The solutions X, one in each column.

Solves a system AX = B with LAPACKs xgesv procedure. Returns a matrix with the solutions in its columns.

Inversion

invert :: (BlasOps e, LapackeOps e se, CMatrix mat e) => mat e -> Maybe (mat e) Source

Invert. Implemented with LAPACK's getrf and getri, that is probably more efficient than using solveLinearSystem.

pseudoInverse :: (BlasOps e, se ~ FieldScalar e, BlasOps se, Real se, LapackeOps e se, MatrixMatrix mat e, CMatrix mat e) => mat e -> mat e Source

Compute the pseudo-inverse with the help of a SVD.

Norms

frobNorm :: (BlasOps e, CMatrix mat e) => mat e -> e Source

Compute the Frobenius norm of a matrix.

Special Matrices And Operations

idMatrix :: (BlasOps e, CMatrix mat e) => Index -> mat e Source

Returns the square identity matrix with given row number.

matrixMultDiag Source

Arguments

:: BlasOps e 
=> CMatrix mat e 
=> (mat e, Transpose)

Matrix A and information on whether to use it transposed or not.

-> [e]

Diagonals of a matrix S

-> mat e

A * S or A^T * S.

Multiply a matrix with a diagonal matrix, given only as a list of diagonal entries. This uses references instead of copied vectors, to work more memory efficient with large matrices.

SVD

svd Source

Arguments

:: (BlasOps e, se ~ FieldScalar e, BlasOps se, LapackeOps e se, CMatrix mat e) 
=> mat e

The matrix A

-> (SVDU, SVDVT)

Choice of extent to which to compute U and V^T.

-> SVD mat e

Returns the SVD.

Compute the singular value decomposition U * S * V^T = A of a matrix A. U and V are (m,m) and (n,n) unitary matrices, and S is a (m,n) matrix with nonzero elements only on the main diagonal. These are the singular values.

The extent to which U and V^T are computed can be chosen by SVDU and SVDVT arguments. SVDU or SVDVT SVDFull return the full (m,m) or (n,n) matrices. For SVDU SVDThin, only the first min(m,n) columns of U are computed. For SVDVT SVDThin, only the first min(m,n) rows of V^T are computed. For SVDNone, the respective matrix will not be returned.

Note that V^T is indeed returned in its transposed form.

data SVD mat e Source

Description of the result of a singular value decomposition with svd.

Constructors

SVD 

Fields

svdU :: Maybe (mat e)

The left, unitary matrix U. Nothing if the SVDU SVDNone was selected.

svdVT :: Maybe (mat e)

The right singular vectors, VT (transposed, so the vectors are in the rows). Nothing if SVDVT SVDNone was selected.

svdS :: [FieldScalar e]

The singular values, s.

data SVDOpt Source

SVD options for the output.

Constructors

SVDFull

Selects the output to be fully computed. For U, that means m x m, for VT it means n x n.

SVDThin

Selects Thin SVD. U: (m, min (m,n)), VT: (n, min (m,n))

SVDNone

Deselects the output.

data SVDU Source

SVD option for the U output.

Constructors

SVDU SVDOpt 

Instances

data SVDVT Source

SVD option for the VT output.

Constructors

SVDVT SVDOpt 

Generating and Checking Indices

inMatrixRange :: (BlasOps e, GMatrix mat e) => mat e -> IndexPair -> Bool Source

diagIndices Source

Arguments

:: Shape

The shape of the matrix (rows,columns)

-> Index

The index of the diagonal -- 0: main diagonal; lower diagonals;0: upper diagonals

-> [IndexPair]

Index list. Empty if there is no such diagonal.

Generate indices of a diagonal in a matrix of given shape.

Low Level IO Matrix Functions

matrixElem :: (Num e, BlasOps e, CMatrix mat e) => mat e -> IndexPair -> IO e Source

matrixMult Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> e

Factor alpha

-> Transpose

Transposition of matrix A

-> mat e

Matrix A

-> Transpose

Transposition of Matrix B

-> mat e

Matrix B

-> IO (mat e) 

Matrix multiplication. Computes alpha * A(^T) * B(^T).

Unsafe manipulations.

unsafeMatrixSetElem Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> mat e

Matrix to be modified.

-> IndexPair

Index of the element to set

-> e

Element to set

-> IO () 

Sets an element in place, therefore this is unsafe. Range check is done, and an error is raised if the given index is out of bounds.

unsafeMatrixMult Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> e

Factor alpha

-> Transpose

Transposition of matrix A

-> mat e

Matrix A

-> Transpose

Transposition of Matrix B

-> mat e

Matrix B

-> e

Factor beta

-> mat e

Matrix C -- This is changed in place and must be of the correct size! The size is not checked!

-> IO () 

Unsafe matrix multiplication. The result is accumulated in the last matrix argument; this function is unsafe because the memory of the last argument is changed in place. This can be used for accumulating many operations in a monad, maybe? Computes C <- alpha * A(^T) * B(^T) + beta * C

unsafeMatrixFill Source

Arguments

:: (Num e, BlasOps e, CMatrix mat e) 
=> mat e

Matrix to fill.

-> e

Value to fill with

-> IO () 

Fill the matrix in place, therefore this is unsafe.

unsafeMatrixCopy Source

Arguments

:: (BlasOps e, CMatrix mat e) 
=> mat e

Source A to copy from.

-> Transpose

If Trans, copies A^T to B, otherwise copies A.

-> mat e

Destination B. Must have the right dimensions.

-> IO () 

Copies a matrix into the storage of another matrix, in-place and therefore unsafe Uses the BLAS copy routine from BlasOps. NOTE: This uses BLAS copy, i.e. the LDA must be either m or n, where (m,n) is the shape of the matrix.

unsafeSolveLinearSystem Source

Arguments

:: (BlasOps e, LapackeOps e se, CMatrix mat e) 
=> mat e

Matrix A

-> mat e

Matrix B, holds the result after the method returned.

-> IO () 

Solve a system AX = B with LAPACKs xgesv procedure. Replaces A with a LU decomposition and B with the solution.

unsafeSVD Source

Arguments

:: (BlasOps e, LapackeOps e se, CVector vec se, CMatrix mat e) 
=> mat e

The matrix to diagonalise.

-> (SVDU, SVDVT)

Options for the SVD.

-> vec se

The CVector for holding the singular values.

-> mat e

U

-> mat e

VT

-> IO Int

The return value of gesvd.

Uses the LAPACKE function gesvd internally to compute the singular value decomposition. The arguments are used as storage, so this is really unsafe. Only used internally.

unsafeMatrixMap :: (Storable e1, Storable e2, CMatrix mat1 e1, CMatrix mat2 e2) => (e1 -> e2) -> mat1 e1 -> mat2 e2 -> IO () Source

unsafeMatrixBinMap :: (Storable e1, Storable e2, Storable e3, CMatrix mat1 e1, CMatrix mat2 e2, CMatrix mat3 e3) => (e1 -> e2 -> e3) -> mat1 e1 -> mat2 e2 -> mat3 e3 -> IO () Source

withCMatrixRow :: Storable e => CMatrix mat e => mat e -> Index -> (RefVector e -> IO a) -> IO a Source

Run an IO action on a row of a matrix, without copying the vector.

withCMatrixColumn :: Storable e => CMatrix mat e => mat e -> Index -> (RefVector e -> IO a) -> IO a Source

Run an IO action on a column of a matrix, without copying the vector.

Re-exported

data Complex a :: * -> *

Complex numbers are an algebraic type.

For a complex number z, abs z is a number with the magnitude of z, but oriented in the positive real direction, whereas signum z has the phase of z, but unit magnitude.

Instances