eigen-1.0.0: Haskel binding for Eigen library

Safe HaskellNone

Data.Eigen.Matrix

Contents

Synopsis

Matrix type

data Matrix Source

constant Matrix class to be used in pure computations, uses the same column major memory layout as Eigen MatrixXd

Constructors

Matrix 

Fields

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

Instances

Num Matrix

only the following functions are defined for Num instance: (*), (+), (-)

Show Matrix

pretty prints the matrix

Matrix conversions

fromList :: [[Double]] -> MatrixSource

construct matrix from a list of rows, column count is detected as maximum row length

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

converts matrix to a list of its rows

Standard matrices and special cases

empty :: MatrixSource

empty 0x0 matrix

zero :: Int -> Int -> MatrixSource

matrix where all coeff are 0

ones :: Int -> Int -> MatrixSource

matrix where all coeff are 1

identity :: Int -> MatrixSource

square matrix with 1 on main diagonal and 0 elsewhere

constant :: Int -> Int -> Double -> MatrixSource

matrix where all coeffs are filled with given value

Accessing matrix data

cols :: Matrix -> IntSource

number of columns for the matrix

rows :: Matrix -> IntSource

number of rows for the matrix

coeff :: Int -> Int -> Matrix -> DoubleSource

matrix coefficient at specific row and col

minCoeff :: Matrix -> DoubleSource

the minimum of all coefficients of matrix

maxCoeff :: Matrix -> DoubleSource

the maximum of all coefficients of matrix

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 -> MatrixSource

extract rectangular block from matrix defined by startRow startCol blockRows blockCols

topRows :: Int -> Matrix -> MatrixSource

top n rows of matrix

bottomRows :: Int -> Matrix -> MatrixSource

bottom n rows of matrix

leftCols :: Int -> Matrix -> MatrixSource

left n columns of matrix

rightCols :: Int -> Matrix -> MatrixSource

right n columns of matrix

Matrix properties

norm :: Matrix -> DoubleSource

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 -> DoubleSource

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.

determinant :: Matrix -> DoubleSource

the determinant of the matrix

Matrix transformations

inverse :: Matrix -> MatrixSource

inverse of the matrix

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

adjoint :: Matrix -> MatrixSource

adjoint of the matrix

transpose :: Matrix -> MatrixSource

transpose of the matrix

normalize :: Matrix -> MatrixSource

nomalize the matrix by deviding it on its norm

Mutable operations

freeze :: MMatrix -> IO MatrixSource

create a snapshot of mutable matrix

thaw :: Matrix -> IO MMatrixSource

create mutable copy of the matrix

modify :: (MMatrix -> IO ()) -> Matrix -> MatrixSource

apply mutable operation to the mutable copy of the matrix and snapshot of this copy

with :: Matrix -> (Ptr C_MatrixXd -> IO a) -> IO aSource

apply foreign operation to the mutable copy of the matrix and operation result