eigen-2.1.7: Eigen C++ library (linear algebra: matrices, sparse matrices, vectors, numerical solvers).

Safe HaskellNone
LanguageHaskell98

Data.Eigen.Matrix

Contents

Synopsis

Matrix type

Matrix aliases follows Eigen naming convention

data Matrix a b where Source #

Matrix to be used in pure computations, uses column major memory layout, features copy-free FFI with C++ Eigen library.

Constructors

Matrix :: Elem a b => !Int -> !Int -> !(Vector b) -> Matrix a b 

Instances

Elem a b => Num (Matrix a b) Source #

Basic matrix math exposed through Num instance: (*), (+), (-), fromInteger, signum, abs, negate

Methods

(+) :: Matrix a b -> Matrix a b -> Matrix a b #

(-) :: Matrix a b -> Matrix a b -> Matrix a b #

(*) :: Matrix a b -> Matrix a b -> Matrix a b #

negate :: Matrix a b -> Matrix a b #

abs :: Matrix a b -> Matrix a b #

signum :: Matrix a b -> Matrix a b #

fromInteger :: Integer -> Matrix a b #

(Elem a b, Show a) => Show (Matrix a b) Source #

Pretty prints the matrix

Methods

showsPrec :: Int -> Matrix a b -> ShowS #

show :: Matrix a b -> String #

showList :: [Matrix a b] -> ShowS #

Elem a b => Binary (Matrix a b) Source #

Matrix binary serialization

Methods

put :: Matrix a b -> Put #

get :: Get (Matrix a b) #

putList :: [Matrix a b] -> Put #

type MatrixXf = Matrix Float CFloat Source #

Alias for single precision matrix

type MatrixXd = Matrix Double CDouble Source #

Alias for double precision matrix

type MatrixXcf = Matrix (Complex Float) (CComplex CFloat) Source #

Alias for single previsiom matrix of complex numbers

type MatrixXcd = Matrix (Complex Double) (CComplex CDouble) Source #

Alias for double prevision matrix of complex numbers

class (Num a, Cast a b, Cast b a, Storable b, Code b) => Elem a b | a -> b Source #

data CComplex a Source #

Complex number for FFI with the same memory layout as std::complex<T>

Instances

valid :: Elem a b => Matrix a b -> Bool Source #

Verify matrix dimensions and memory layout

Matrix conversions

fromList :: Elem a b => [[a]] -> Matrix a b Source #

Construct matrix from a list of rows, column count is detected as maximum row length. Missing values are filled with 0

toList :: Elem a b => Matrix a b -> [[a]] Source #

Convert matrix to a list of rows

fromFlatList :: Elem a b => Int -> Int -> [a] -> Matrix a b Source #

Build matrix of given dimensions and values from given list split on rows. Invalid list length results in error.

toFlatList :: Elem a b => Matrix a b -> [a] Source #

Convert matrix to a list by concatenating rows

generate :: Elem a b => Int -> Int -> (Int -> Int -> a) -> Matrix a b Source #

generate rows cols (λ row col -> val)

Create matrix using generator function λ row col -> val

Standard matrices and special cases

empty :: Elem a b => Matrix a b Source #

Empty 0x0 matrix

null :: Elem a b => Matrix a b -> Bool Source #

Is matrix empty?

square :: Elem a b => Matrix a b -> Bool Source #

Is matrix square?

zero :: Elem a b => Int -> Int -> Matrix a b Source #

Matrix where all coeff are 0

ones :: Elem a b => Int -> Int -> Matrix a b Source #

Matrix where all coeff are 1

identity :: Elem a b => Int -> Int -> Matrix a b Source #

The identity matrix (not necessarily square).

constant :: Elem a b => Int -> Int -> a -> Matrix a b Source #

Matrix where all coeffs are filled with given value

random :: Elem a b => Int -> Int -> IO (Matrix a b) Source #

The random matrix of a given size

Accessing matrix data

cols :: Elem a b => Matrix a b -> Int Source #

Number of columns for the matrix

rows :: Elem a b => Matrix a b -> Int Source #

Number of rows for the matrix

dims :: Elem a b => Matrix a b -> (Int, Int) Source #

Mtrix size as (rows, cols) pair

(!) :: Elem a b => Matrix a b -> (Int, Int) -> a Source #

Matrix coefficient at specific row and col

coeff :: Elem a b => Int -> Int -> Matrix a b -> a Source #

Matrix coefficient at specific row and col

unsafeCoeff :: Elem a b => Int -> Int -> Matrix a b -> a Source #

Unsafe version of coeff function. No bounds check performed so SEGFAULT possible

col :: Elem a b => Int -> Matrix a b -> [a] Source #

List of coefficients for the given col

row :: Elem a b => Int -> Matrix a b -> [a] Source #

List of coefficients for the given row

block :: Elem a b => Int -> Int -> Int -> Int -> Matrix a b -> Matrix a b Source #

Extract rectangular block from matrix defined by startRow startCol blockRows blockCols

topRows :: Elem a b => Int -> Matrix a b -> Matrix a b Source #

Top N rows of matrix

bottomRows :: Elem a b => Int -> Matrix a b -> Matrix a b Source #

Bottom N rows of matrix

leftCols :: Elem a b => Int -> Matrix a b -> Matrix a b Source #

Left N columns of matrix

rightCols :: Elem a b => Int -> Matrix a b -> Matrix a b Source #

Right N columns of matrix

Matrix properties

sum :: Elem a b => Matrix a b -> a Source #

The sum of all coefficients of the matrix

prod :: Elem a b => Matrix a b -> a Source #

The product of all coefficients of the matrix

mean :: Elem a b => Matrix a b -> a Source #

The mean of all coefficients of the matrix

minCoeff :: (Elem a b, Ord a) => Matrix a b -> a Source #

The minimum coefficient of the matrix

maxCoeff :: (Elem a b, Ord a) => Matrix a b -> a Source #

The maximum coefficient of the matrix

trace :: Elem a b => Matrix a b -> a Source #

The trace of a matrix is the sum of the diagonal coefficients and can also be computed as sum (diagonal m)

norm :: Elem a b => Matrix a b -> a Source #

For vectors, the l2 norm, and for matrices the Frobenius norm. In both cases, it consists in the square root of the sum of the square of all the matrix entries. For vectors, this is also equals to the square root of the dot product of this with itself.

squaredNorm :: Elem a b => Matrix a b -> a Source #

For vectors, the squared l2 norm, and for matrices the Frobenius norm. In both cases, it consists in the sum of the square of all the matrix entries. For vectors, this is also equals to the dot product of this with itself.

blueNorm :: Elem a b => Matrix a b -> a Source #

The l2 norm of the matrix using the Blue's algorithm. A Portable Fortran Program to Find the Euclidean Norm of a Vector, ACM TOMS, Vol 4, Issue 1, 1978.

hypotNorm :: Elem a b => Matrix a b -> a Source #

The l2 norm of the matrix avoiding undeflow and overflow. This version use a concatenation of hypot calls, and it is very slow.

determinant :: Elem a b => Matrix a b -> a Source #

The determinant of the matrix

Generic reductions

fold :: Elem a b => (c -> a -> c) -> c -> Matrix a b -> c Source #

Reduce matrix using user provided function applied to each element.

fold' :: Elem a b => (c -> a -> c) -> c -> Matrix a b -> c Source #

Reduce matrix using user provided function applied to each element. This is strict version of fold

ifold :: Elem a b => (Int -> Int -> c -> a -> c) -> c -> Matrix a b -> c Source #

Reduce matrix using user provided function applied to each element and it's index

ifold' :: Elem a b => (Int -> Int -> c -> a -> c) -> c -> Matrix a b -> c Source #

Reduce matrix using user provided function applied to each element and it's index. This is strict version of ifold

fold1 :: Elem a b => (a -> a -> a) -> Matrix a b -> a Source #

Reduce matrix using user provided function applied to each element.

fold1' :: Elem a b => (a -> a -> a) -> Matrix a b -> a Source #

Reduce matrix using user provided function applied to each element. This is strict version of fold

Boolean reductions

all :: Elem a b => (a -> Bool) -> Matrix a b -> Bool Source #

Applied to a predicate and a matrix, all determines if all elements of the matrix satisfies the predicate

any :: Elem a b => (a -> Bool) -> Matrix a b -> Bool Source #

Applied to a predicate and a matrix, any determines if any element of the matrix satisfies the predicate

count :: Elem a b => (a -> Bool) -> Matrix a b -> Int Source #

Returns the number of coefficients in a given matrix that evaluate to true

Basic matrix algebra

add :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b Source #

Adding two matrices by adding the corresponding entries together. You can use (+) function as well.

sub :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b Source #

Subtracting two matrices by subtracting the corresponding entries together. You can use (-) function as well.

mul :: Elem a b => Matrix a b -> Matrix a b -> Matrix a b Source #

Matrix multiplication. You can use (*) function as well.

Mapping over elements

map :: Elem a b => (a -> a) -> Matrix a b -> Matrix a b Source #

Apply a given function to each element of the matrix.

Here is an example how to implement scalar matrix multiplication:

>>> let a = fromList [[1,2],[3,4]] :: MatrixXf
>>> a
Matrix 2x2
1.0 2.0
3.0 4.0
>>> map (*10) a
Matrix 2x2
10.0    20.0
30.0    40.0

imap :: Elem a b => (Int -> Int -> a -> a) -> Matrix a b -> Matrix a b Source #

Apply a given function to each element of the matrix.

Here is an example how upper triangular matrix can be implemented:

>>> let a = fromList [[1,2,3],[4,5,6],[7,8,9]] :: MatrixXf
>>> a
Matrix 3x3
1.0 2.0 3.0
4.0 5.0 6.0
7.0 8.0 9.0
>>> imap (\row col val -> if row <= col then val else 0) a
Matrix 3x3
1.0 2.0 3.0
0.0 5.0 6.0
0.0 0.0 9.0

filter :: Elem a b => (a -> Bool) -> Matrix a b -> Matrix a b Source #

Filter elements in the matrix. Filtered elements will be replaced by 0

ifilter :: Elem a b => (Int -> Int -> a -> Bool) -> Matrix a b -> Matrix a b Source #

Filter elements in the matrix. Filtered elements will be replaced by 0

Matrix transformations

diagonal :: Elem a b => Matrix a b -> Matrix a b Source #

Diagonal of the matrix

transpose :: Elem a b => Matrix a b -> Matrix a b Source #

Transpose of the matrix

inverse :: Elem a b => Matrix a b -> Matrix a b Source #

Inverse of the matrix

For small fixed sizes up to 4x4, this method uses cofactors. In the general case, this method uses PartialPivLU decomposition

adjoint :: Elem a b => Matrix a b -> Matrix a b Source #

Adjoint of the matrix

conjugate :: Elem a b => Matrix a b -> Matrix a b Source #

Conjugate of the matrix

normalize :: Elem a b => Matrix a b -> Matrix a b Source #

Nomalize the matrix by deviding it on its norm

modify :: Elem a b => (forall s. MMatrix a b s -> ST s ()) -> Matrix a b -> Matrix a b Source #

Apply a destructive operation to a matrix. The operation will be performed in place if it is safe to do so and will modify a copy of the matrix otherwise.

convert :: (Elem a b, Elem c d) => (a -> c) -> Matrix a b -> Matrix c d Source #

Convert matrix to different type using user provided element converter

data TriangularMode Source #

Constructors

Lower

View matrix as a lower triangular matrix.

Upper

View matrix as an upper triangular matrix.

StrictlyLower

View matrix as a lower triangular matrix with zeros on the diagonal.

StrictlyUpper

View matrix as an upper triangular matrix with zeros on the diagonal.

UnitLower

View matrix as a lower triangular matrix with ones on the diagonal.

UnitUpper

View matrix as an upper triangular matrix with ones on the diagonal.

triangularView :: Elem a b => TriangularMode -> Matrix a b -> Matrix a b Source #

Triangular view extracted from the current matrix

lowerTriangle :: Elem a b => Matrix a b -> Matrix a b Source #

Lower trinagle of the matrix. Shortcut for triangularView Lower

upperTriangle :: Elem a b => Matrix a b -> Matrix a b Source #

Upper trinagle of the matrix. Shortcut for triangularView Upper

Matrix serialization

encode :: Elem a b => Matrix a b -> ByteString Source #

Encode the matrix as a lazy byte string

decode :: Elem a b => ByteString -> Matrix a b Source #

Decode matrix from the lazy byte string

Mutable matrices

thaw :: Elem a b => PrimMonad m => Matrix a b -> m (MMatrix a b (PrimState m)) Source #

Yield a mutable copy of the immutable matrix

freeze :: Elem a b => PrimMonad m => MMatrix a b (PrimState m) -> m (Matrix a b) Source #

Yield an immutable copy of the mutable matrix

unsafeThaw :: Elem a b => PrimMonad m => Matrix a b -> m (MMatrix a b (PrimState m)) Source #

Unsafely convert an immutable matrix to a mutable one without copying. The immutable matrix may not be used after this operation.

unsafeFreeze :: Elem a b => PrimMonad m => MMatrix a b (PrimState m) -> m (Matrix a b) Source #

Unsafe convert a mutable matrix to an immutable one without copying. The mutable matrix may not be used after this operation.

Raw pointers

unsafeWith :: Elem a b => Matrix a b -> (Ptr b -> CInt -> CInt -> IO c) -> IO c Source #

Pass a pointer to the matrix's data to the IO action. The data may not be modified through the pointer.