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

Safe HaskellNone
LanguageHaskell2010

Data.Eigen.SparseMatrix

Contents

Synopsis

SparseMatrix type

data SparseMatrix a b where Source #

A versatible sparse matrix representation.

SparseMatrix is the main sparse matrix representation of Eigen's sparse module. It offers high performance and low memory usage. It implements a more versatile variant of the widely-used Compressed Column (or Row) Storage scheme.

It consists of four compact arrays:

  • values: stores the coefficient values of the non-zeros.
  • innerIndices: stores the row (resp. column) indices of the non-zeros.
  • outerStarts: stores for each column (resp. row) the index of the first non-zero in the previous two arrays.
  • innerNNZs: stores the number of non-zeros of each column (resp. row). The word inner refers to an inner vector that is a column for a column-major matrix, or a row for a row-major matrix. The word outer refers to the other direction.

This storage scheme is better explained on an example. The following matrix

0   3   0   0   0
22  0   0   0   17
7   5   0   1   0
0   0   0   0   0
0   0   14  0   8

and one of its possible sparse, column major representation:

values:         22  7   _   3   5   14  _   _   1   _   17  8
innerIndices:   1   2   _   0   2   4   _   _   2   _   1   4
outerStarts:    0   3   5   8   10  12
innerNNZs:      2   2   1   1   2

Currently the elements of a given inner vector are guaranteed to be always sorted by increasing inner indices. The "_" indicates available free space to quickly insert new elements. Assuming no reallocation is needed, the insertion of a random element is therefore in O(nnz_j) where nnz_j is the number of nonzeros of the respective inner vector. On the other hand, inserting elements with increasing inner indices in a given inner vector is much more efficient since this only requires to increase the respective innerNNZs entry that is a O(1) operation.

The case where no empty space is available is a special case, and is refered as the compressed mode. It corresponds to the widely used Compressed Column (or Row) Storage schemes (CCS or CRS). Any SparseMatrix can be turned to this form by calling the compress function. In this case, one can remark that the innerNNZs array is redundant with outerStarts because we the equality: InnerNNZs[j] = OuterStarts[j+1]-OuterStarts[j]. Therefore, in practice a call to compress frees this buffer.

The results of Eigen's operations always produces compressed sparse matrices. On the other hand, the insertion of a new element into a SparseMatrix converts this later to the uncompressed mode.

For more infomration please see Eigen documentation page.

Constructors

SparseMatrix :: Elem a b => !(ForeignPtr (CSparseMatrix a b)) -> SparseMatrix a b 
Instances
Elem a b => Num (SparseMatrix a b) Source #

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

Instance details

Defined in Data.Eigen.SparseMatrix

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

Pretty prints the sparse matrix

Instance details

Defined in Data.Eigen.SparseMatrix

Elem a b => Binary (SparseMatrix a b) Source # 
Instance details

Defined in Data.Eigen.SparseMatrix

Methods

put :: SparseMatrix a b -> Put #

get :: Get (SparseMatrix a b) #

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

type SparseMatrixXf = SparseMatrix Float CFloat Source #

Alias for single precision sparse matrix

type SparseMatrixXd = SparseMatrix Double CDouble Source #

Alias for double precision sparse matrix

type SparseMatrixXcf = SparseMatrix (Complex Float) (CComplex CFloat) Source #

Alias for single previsiom sparse matrix of complex numbers

type SparseMatrixXcd = SparseMatrix (Complex Double) (CComplex CDouble) Source #

Alias for double prevision sparse matrix of complex numbers

Matrix internal data

values :: Elem a b => SparseMatrix a b -> Vector b Source #

Stores the coefficient values of the non-zeros.

innerIndices :: Elem a b => SparseMatrix a b -> Vector CInt Source #

Stores the row (resp. column) indices of the non-zeros.

outerStarts :: Elem a b => SparseMatrix a b -> Vector CInt Source #

Stores for each column (resp. row) the index of the first non-zero in the previous two arrays.

innerNNZs :: Elem a b => SparseMatrix a b -> Maybe (Vector CInt) Source #

Stores the number of non-zeros of each column (resp. row). The word inner refers to an inner vector that is a column for a column-major matrix, or a row for a row-major matrix. The word outer refers to the other direction

Accessing matrix data

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

Number of columns for the sparse matrix

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

Number of rows for the sparse matrix

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

Matrix coefficient at given row and col

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

Matrix coefficient at given row and col

getRow :: Elem a b => Int -> SparseMatrix a b -> SparseMatrix a b Source #

Get a row of a sparse matrix.

getCol :: Elem a b => Int -> SparseMatrix a b -> SparseMatrix a b Source #

Get a column of a sparse matrix.

getRows :: Elem a b => SparseMatrix a b -> [SparseMatrix a b] Source #

Get all rows of a sparse matrix.

getCols :: Elem a b => SparseMatrix a b -> [SparseMatrix a b] Source #

Get all columns of a sparse matrix.

squareSubset :: Elem a b => [Int] -> SparseMatrix a b -> SparseMatrix a b Source #

Get a subset of a square matrix.

Matrix conversions

fromList :: Elem a b => Int -> Int -> [(Int, Int, a)] -> SparseMatrix a b Source #

Construct sparse matrix of given size from the list of triplets (row, col, val)

toList :: Elem a b => SparseMatrix a b -> [(Int, Int, a)] Source #

Convert sparse matrix to the list of triplets (row, col, val). Compressed elements will not be included

fromVector :: Elem a b => Int -> Int -> Vector (CTriplet b) -> SparseMatrix a b Source #

Construct sparse matrix of given size from the storable vector of triplets (row, col, val)

toVector :: Elem a b => SparseMatrix a b -> Vector (CTriplet b) Source #

Convert sparse matrix to the storable vector of triplets (row, col, val). Compressed elements will not be included

fromDenseList :: (Elem a b, Eq a) => [[a]] -> SparseMatrix a b Source #

Construct sparse matrix of two-dimensional list of values. Matrix dimensions will be detected automatically. Zero values will be compressed.

toDenseList :: Elem a b => SparseMatrix a b -> [[a]] Source #

Convert sparse matrix to (rows X cols) dense list of values

fromMatrix :: Elem a b => Matrix a b -> SparseMatrix a b Source #

Construct sparse matrix from dense matrix. Zero elements will be compressed

toMatrix :: Elem a b => SparseMatrix a b -> Matrix a b Source #

Construct dense matrix from sparse matrix

ones :: Int -> SparseMatrixXd Source #

Get the ones vector.

ident :: Int -> SparseMatrixXd Source #

Get the identity matrix.

diagCol :: Elem a b => Int -> SparseMatrix a b -> SparseMatrix a b Source #

Transform a column into a diagonal matrix.

diagRow :: Elem a b => Int -> SparseMatrix a b -> SparseMatrix a b Source #

Transform a row into a diagonal matrix.

fromRows :: Elem a b => [SparseMatrix a b] -> SparseMatrix a b Source #

Get a matrix from a list of rows.

fromCols :: Elem a b => [SparseMatrix a b] -> SparseMatrix a b Source #

Get a matrix from a list of cols.

Matrix properties

norm :: Elem a b => SparseMatrix 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 => SparseMatrix 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 => SparseMatrix 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.

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

Extract rectangular block from sparse matrix defined by startRow startCol blockRows blockCols

nonZeros :: Elem a b => SparseMatrix a b -> Int Source #

Number of non-zeros elements in the sparse matrix

innerSize :: Elem a b => SparseMatrix a b -> Int Source #

Minor dimension with respect to the storage order

outerSize :: Elem a b => SparseMatrix a b -> Int Source #

Major dimension with respect to the storage order

getColSums :: SparseMatrixXd -> SparseMatrixXd Source #

Get all column sums.

getSum :: SparseMatrixXd -> Double Source #

Get sum of matrix.

Basic matrix algebra

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

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

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

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

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

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

Matrix transformations

pruned :: Elem a b => a -> SparseMatrix a b -> SparseMatrix a b Source #

Suppresses all nonzeros which are much smaller than reference under the tolerence epsilon

scale :: Elem a b => a -> SparseMatrix a b -> SparseMatrix a b Source #

Multiply matrix on a given scalar

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

Transpose of the sparse matrix

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

Adjoint of the sparse matrix

_map :: Elem a b => (a -> a) -> SparseMatrix a b -> SparseMatrix a b Source #

Map over values of a sparse matrix.

_imap :: Elem a b => (Int -> Int -> a -> a) -> SparseMatrix a b -> SparseMatrix a b Source #

Map over values of a sparse matrix with indices.

Matrix representation

compress :: Elem a b => SparseMatrix a b -> SparseMatrix a b Source #

The matrix in the compressed format

uncompress :: Elem a b => SparseMatrix a b -> SparseMatrix a b Source #

The matrix in the uncompressed mode

compressed :: Elem a b => SparseMatrix a b -> Bool Source #

Is this in compressed form?

Matrix serialization

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

Encode the sparse matrix as a lazy byte string

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

Decode sparse matrix from the lazy byte string

Mutable matricies

thaw :: Elem a b => SparseMatrix a b -> IO (IOSparseMatrix a b) Source #

Yield a mutable copy of the immutable matrix

freeze :: Elem a b => IOSparseMatrix a b -> IO (SparseMatrix a b) Source #

Yield an immutable copy of the mutable matrix

unsafeThaw :: Elem a b => SparseMatrix a b -> IO (IOSparseMatrix a b) 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 => IOSparseMatrix a b -> IO (SparseMatrix a b) Source #

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