bed-and-breakfast-0.4.1: Efficient Matrix operations in 100% Haskell.

Safe HaskellTrustworthy

Numeric.Matrix

Contents

Description

Efficient matrix operations in 100% pure Haskell.

This package uses miscellaneous implementations, depending on the type of its components. Typically unboxed arrays will perform best, while unboxed arrays give you certain features such as Rational or Complex components.

The following component types are supported by Matrix:

Int
Uses unboxed arrays internally. inv will always return Nothing.
Integer
Uses boxed arrays internally. inv will always return Nothing.
Double and Float
Uses unboxed arrays internally. All matrix operations will work as expected. Matrix Double will probably yield the best peformance.
Rational
Best choice if precision is what you aim for. Uses boxed arrays internally. All matrix operations will work as expected.
Complex
Experimental. Uses boxed arrays internally. The current implementation of inv requires an instance of Ord for the component type, therefor it is currently not possible to calculate the inverse of a complex matrix (on my to do list).

Synopsis

Documentation

data family Matrix e Source

Matrices are represented by a type which fits best the component type. For example a Matrix Double is represented by unboxed arrays, Matrix Integer by boxed arrays.

Data instances exist for Int, Float, Double, Integer, Ratio, and Complex. Certain types do have certain disadvantages, like for example you can not compute the inverse matrix of a Matrix Int.

Every matrix (regardless of the component type) has instances for Show, Read, Num, Fractional, Eq, Typeable, Binary, and NFData. This means that you can use arithmetic operations like +, *, and /, as well as functions like show, read, or typeOf.

Show (Matrix e)
Note that a Show instance for the component type e must exist.
Read (Matrix e)
You can read a matrix like so:
 read "1 0\n0 1\n" :: Matrix Double
Num (Matrix e)
+, -, *, negate, abs, signum, and fromInteger.

signum will compute the determinant and return the signum of it.

abs applies map abs on the matrix (that is, it applies abs on every component in the matrix and returns a new matrix without negative components).

fromInteger yields a 1-x-1-matrix.

Fractional (Matrix e)
Only available if there exists an instance Fractional e (the component type needs to have a Fractional instance, too). Note that while the Num operations are safe, recip and / will fail (with an error) if the involved matrix is not invertible or not a square matrix.
NFData (Matrix e)
Matrices have instances for NFData so that you can use a matrix in parallel computations using the Control.Monad.Par monad (see the monad-par package for details).
Typeable (Matrix e)
Allows you to use matrices as Dynamic values.
Binary (Matrix e)
Serialize and unserialize matrices using the binary package. See encode and decode.

class (Eq e, Num e) => MatrixElement e whereSource

Methods

matrix :: (Int, Int) -> ((Int, Int) -> e) -> Matrix eSource

Creates a matrix of the given size using a generator function for the value of each component.

select :: ((Int, Int) -> Bool) -> Matrix e -> [e]Source

Builds a list from a matrix for the indices for which the given predicate matches.

 trace == select (uncurry (==))

at :: Matrix e -> (Int, Int) -> eSource

Returns the component at the given position in the matrix. Note that indices start at one, not at zero.

row :: Int -> Matrix e -> [e]Source

Returns the row at the given index in the matrix. Note that indices start at one, not at zero.

col :: Int -> Matrix e -> [e]Source

Returns the row at the given index in the matrix. Note that indices start at one, not at zero.

dimensions :: Matrix e -> (Int, Int)Source

The dimensions of a given matrix.

numRows :: Matrix e -> IntSource

The number of rows in the given matrix.

numCols :: Matrix e -> IntSource

The number of columns in the given matrix.

fromList :: [[e]] -> Matrix eSource

Builds a matrix from a list of lists.

The innermost lists represent the rows. This function will create a m-n-matrix, where m is the number of rows, which is the minimum length of the row lists and n is the number of columns, i.e. the length of the outer list.

 fromList [[1,2,3],[2,1,3],[3,2,1]] :: Matrix Rational

toList :: Matrix e -> [[e]]Source

unit :: Int -> Matrix eSource

An identity square matrix of the given size.

>>> unit 4
1 0 0 0
0 1 0 0
0 0 1 0
0 0 0 1

zero :: Int -> Matrix eSource

A square matrix of the given size consisting of all zeros.

>>> zero 2
0 0
0 0

diag :: [e] -> Matrix eSource

A square matrix which trace is the given list, all other components set to zero.

>>> diag [1,4,7,9]
1 0 0 0
0 4 0 0
0 0 7 0
0 0 0 9

empty :: Matrix eSource

Check whether the matrix is the empty matrix.

 dimensions empty == (0, 0)

minus :: Matrix e -> Matrix e -> Matrix eSource

Subtract a matrix from another.

plus :: Matrix e -> Matrix e -> Matrix eSource

Add two matrices.

You may also use the Num instance for matrices, i.e. matrix1 + matrix2 will work, too.

times :: Matrix e -> Matrix e -> Matrix eSource

Multiply two matrices O(n^3).

You may also use the Num instance for matrices, i.e. matrix1 * matrix2 will work, too.

inv :: Matrix e -> Maybe (Matrix e)Source

Compute the inverse of a matrix. Returns Nothing if the matrix is not invertible.

det :: Matrix e -> eSource

Applies Bareiss multistep integer-preserving algorithm for finding the determinant of a matrix. Returns 0 if the matrix is not a square matrix.

transpose :: Matrix e -> Matrix eSource

Flip rows and columns.

 1 8 9                1 2 3
 2 1 8  --transpose-> 8 1 2
 3 2 1                9 8 1 

rank :: Matrix e -> eSource

Compute the rank of a matrix.

trace :: Matrix e -> [e]Source

minor :: MatrixElement e => Matrix e -> (Int, Int) -> eSource

cofactors :: MatrixElement e => Matrix e -> Matrix eSource

adjugate :: MatrixElement e => Matrix e -> Matrix eSource

minorMatrix :: MatrixElement e => Matrix e -> (Int, Int) -> Matrix eSource

map :: MatrixElement f => (e -> f) -> Matrix e -> Matrix fSource

Apply a function on every component in the matrix.

all :: (e -> Bool) -> Matrix e -> BoolSource

Apply a predicate on every component in the matrix and returns True iff all components satisfy it.

any :: (e -> Bool) -> Matrix e -> BoolSource

Apply a predicate on every component in the matrix and return True if one or more components satisfy it.

mapWithIndex :: MatrixElement f => ((Int, Int) -> e -> f) -> Matrix e -> Matrix fSource

allWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> BoolSource

anyWithIndex :: ((Int, Int) -> e -> Bool) -> Matrix e -> BoolSource

Matrix property and utility functions.

(<|>) :: MatrixElement e => Matrix e -> Matrix e -> Matrix eSource

Joins two matrices horizontally.

 1 2 3     1 0 0      1 2 3 1 0 0
 3 4 5 <|> 2 1 0  ->  3 4 5 2 1 0
 5 6 7     3 2 1      5 6 7 3 2 1

(<->) :: MatrixElement e => Matrix e -> Matrix e -> Matrix eSource

Joins two matrices vertically.

 1 2 3     1 0 0      1 2 3
 3 4 5 <-> 2 1 0  ->  3 4 5
 5 6 7     3 2 1      5 6 7
                      1 0 0
                      2 1 0
                      3 2 1

scale :: MatrixElement e => Matrix e -> e -> Matrix eSource

Scales a matrix by the given factor.

 scale s == map (*s)

Matrix properties

isUnit :: MatrixElement e => Matrix e -> BoolSource

Check whether the matrix is an identity matrix.

 1 0 0
 0 1 0
 0 0 1 (True)

isZero :: MatrixElement e => Matrix e -> BoolSource

Check whether the matrix consists of all zeros.

 isZero == all (== 0)

isDiagonal :: MatrixElement e => Matrix e -> BoolSource

Checks whether the matrix is a diagonal matrix.

 4 0 0 0
 0 7 0 0
 0 0 3 0
 0 0 0 9 (True)

isEmpty :: MatrixElement e => Matrix e -> BoolSource

Checks whether the matrix is empty.

 isEmpty m = numCols == 0 || numRows == 0

isSquare :: MatrixElement e => Matrix e -> BoolSource

Checks whether the matrix is a square matrix.

 isSquare == uncurry (==) . dimensions