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

Safe HaskellNone
LanguageHaskell98

Data.Eigen.Matrix

Contents

Synopsis

Matrix type

data Matrix Source

Matrix to be used in pure computations, uses column major memory layout

Constructors

Matrix 

Fields

m_rows :: Int
 
m_cols :: Int
 
m_vals :: Vector CDouble
 

Instances

Num Matrix

Nm instance for the matrix

Show Matrix

Pretty prints the matrix

valid :: Matrix -> Bool Source

Verify matrix dimensions and memory layout

Matrix conversions

fromList :: [[Double]] -> Matrix Source

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

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

Convert matrix to a list of rows

generate :: Int -> Int -> (Int -> Int -> Double) -> Matrix Source

Create matrix using generator function f :: row -> col -> val

Standard matrices and special cases

empty :: Matrix Source

Empty 0x0 matrix

null :: Matrix -> Bool Source

Is matrix empty?

square :: Matrix -> Bool Source

Is matrix square?

zero :: Int -> Int -> Matrix Source

Matrix where all coeff are 0

ones :: Int -> Int -> Matrix Source

Matrix where all coeff are 1

identity :: Int -> Matrix Source

Square matrix with 1 on main diagonal and 0 elsewhere

constant :: Int -> Int -> Double -> Matrix Source

Matrix where all coeffs are filled with given value

random :: Int -> Int -> IO Matrix Source

The random matrix of a given size

Accessing matrix data

cols :: Matrix -> Int Source

Number of columns for the matrix

rows :: Matrix -> Int Source

Number of rows for the matrix

(!) :: Matrix -> (Int, Int) -> Double Source

Matrix coefficient at specific row and col

coeff :: Int -> Int -> Matrix -> Double Source

Matrix coefficient at specific row and col

unsafeCoeff :: Int -> Int -> Matrix -> Double Source

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

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

List of coefficients for the given col

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

List of coefficients for the given row

block :: Int -> Int -> Int -> Int -> Matrix -> Matrix Source

Extract rectangular block from matrix defined by startRow startCol blockRows blockCols

topRows :: Int -> Matrix -> Matrix Source

Top n rows of matrix

bottomRows :: Int -> Matrix -> Matrix Source

Bottom n rows of matrix

leftCols :: Int -> Matrix -> Matrix Source

Left n columns of matrix

rightCols :: Int -> Matrix -> Matrix Source

Right n columns of matrix

Matrix properties

sum :: Matrix -> Double Source

The sum of all coefficients of the matrix

prod :: Matrix -> Double Source

The product of all coefficients of the matrix

mean :: Matrix -> Double Source

The mean of all coefficients of the matrix

minCoeff :: Matrix -> Double Source

The minimum of all coefficients of matrix

maxCoeff :: Matrix -> Double Source

The maximum of all coefficients of matrix

trace :: Matrix -> Double Source

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

norm :: Matrix -> Double 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 :: Matrix -> Double 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 :: Matrix -> Double 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 :: Matrix -> Double 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 :: Matrix -> Double Source

The determinant of the matrix

Boolean reductions

all :: (Double -> Bool) -> Matrix -> Bool Source

Returns true if all of the coefficients in a given matrix evaluate to true

any :: (Double -> Bool) -> Matrix -> Bool Source

Returns true if at least one of the coefficients in a given matrix evaluates to true

count :: (Double -> Bool) -> Matrix -> Int Source

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

Matrix operations

add :: Matrix -> Matrix -> Matrix Source

Adding two matrices by adding the corresponding entries together

sub :: Matrix -> Matrix -> Matrix Source

Return a + b

mul :: Matrix -> Matrix -> Matrix Source

Matrix multiplication

Matrix transformations

diagonal :: Matrix -> Matrix Source

Diagonal of the matrix

transpose :: Matrix -> Matrix Source

Transpose of the matrix

inverse :: Matrix -> Matrix 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 :: Matrix -> Matrix Source

Adjoint of the matrix

conjugate :: Matrix -> Matrix Source

Conjugate of the matrix

normalize :: Matrix -> Matrix Source

Nomalize the matrix by deviding it on its norm

modify :: (forall s. MMatrix s -> ST s ()) -> Matrix -> Matrix 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.

Mutable matrices

thaw :: PrimMonad m => Matrix -> m (MMatrix (PrimState m)) Source

Yield a mutable copy of the immutable matrix

freeze :: PrimMonad m => MMatrix (PrimState m) -> m Matrix Source

Yield an immutable copy of the mutable matrix

unsafeThaw :: PrimMonad m => Matrix -> m (MMatrix (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 :: PrimMonad m => MMatrix (PrimState m) -> m Matrix Source

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

unsafeWith :: Matrix -> (Ptr CDouble -> CInt -> CInt -> IO a) -> IO a Source

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