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

Safe HaskellNone
LanguageHaskell98

Data.Eigen.SparseMatrix.Mutable

Contents

Synopsis

Mutable SparseMatrix

data IOSparseMatrix a b where Source

Mutable version of sparse matrix. See SparseMatrix for details about matrix layout.

Constructors

IOSparseMatrix :: Elem a b => !(ForeignPtr (CSparseMatrix a b)) -> IOSparseMatrix a b 

type IOSparseMatrixXf = IOSparseMatrix Float CFloat Source

Alias for single precision mutable matrix

type IOSparseMatrixXd = IOSparseMatrix Double CDouble Source

Alias for double precision mutable matrix

type IOSparseMatrixXcf = IOSparseMatrix (Complex Float) (CComplex CFloat) Source

Alias for single previsiom mutable matrix of complex numbers

type IOSparseMatrixXcd = IOSparseMatrix (Complex Double) (CComplex CDouble) Source

Alias for double prevision mutable matrix of complex numbers

new :: Elem a b => Int -> Int -> IO (IOSparseMatrix a b) Source

Creates new matrix with the given size rows x cols

reserve :: Elem a b => IOSparseMatrix a b -> Int -> IO () Source

Preallocates space for non zeros. The matrix must be in compressed mode.

Matrix properties

rows :: Elem a b => IOSparseMatrix a b -> IO Int Source

Returns the number of rows of the matrix

cols :: Elem a b => IOSparseMatrix a b -> IO Int Source

Returns the number of columns of the matrix

innerSize :: Elem a b => IOSparseMatrix a b -> IO Int Source

Returns the number of rows (resp. columns) of the matrix if the storage order column major (resp. row major)

outerSize :: Elem a b => IOSparseMatrix a b -> IO Int Source

Returns the number of columns (resp. rows) of the matrix if the storage order column major (resp. row major)

nonZeros :: Elem a b => IOSparseMatrix a b -> IO Int Source

The number of non zero coefficients

Matrix compression

compressed :: Elem a b => IOSparseMatrix a b -> IO Bool Source

Returns whether this matrix is in compressed form.

compress :: Elem a b => IOSparseMatrix a b -> IO () Source

Turns the matrix into the compressed format.

uncompress :: Elem a b => IOSparseMatrix a b -> IO () Source

Turns the matrix into the uncompressed mode.

Accessing matrix data

read :: Elem a b => IOSparseMatrix a b -> Int -> Int -> IO a Source

Reads the value of the matrix at position i, j. This function returns Scalar(0) if the element is an explicit zero.

write :: Elem a b => IOSparseMatrix a b -> Int -> Int -> a -> IO () Source

Writes the value of the matrix at position i, j. This function turns the matrix into a non compressed form if that was not the case.

This is a O(log(nnz_j)) operation (binary search) plus the cost of element insertion if the element does not already exist.

Cost of element insertion is sorted insertion in O(1) if the elements of each inner vector are inserted in increasing inner index order, and in O(nnz_j) for a random insertion.

setZero :: Elem a b => IOSparseMatrix a b -> IO () Source

Removes all non zeros but keep allocated memory

setIdentity :: Elem a b => IOSparseMatrix a b -> IO () Source

Sets the matrix to the identity matrix

Changing matrix shape

resize :: Elem a b => IOSparseMatrix a b -> Int -> Int -> IO () Source

Resizes the matrix to a rows x cols matrix and initializes it to zero.

conservativeResize :: Elem a b => IOSparseMatrix a b -> Int -> Int -> IO () Source

Resizes the matrix to a rows x cols matrix leaving old values untouched.