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

Safe HaskellNone
LanguageHaskell98

Data.Eigen.SparseMatrix

Contents

Synopsis

SparseMatrix type

SparseMatrix aliases follows Eigen naming convention

data SparseMatrix a b where Source

A versatible sparse matrix representation.

This class implements a more versatile variants of the common compressed row/column storage format. Each colmun's (resp. row) non zeros are stored as a pair of value with associated row (resp. colmiun) index. All the non zeros are stored in a single large buffer. Unlike the compressed format, there might be extra space inbetween the nonzeros of two successive colmuns (resp. rows) such that insertion of new non-zero can be done with limited memory reallocation and copies.

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.

A call to the function compress turns the matrix into the standard compressed format compatible with many library.

Implementation deails of SparseMatrix are intentionally hidden behind ForeignPtr bacause Eigen doesn't provide mapping over plain data for sparse matricies.

For more infomration please see Eigen documentation page: http://eigen.tuxfamily.org/dox/classEigen_1_1SparseMatrix.html

Constructors

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

Instances

Elem a b => Num (SparseMatrix a b) Source

Shortcuts for basic matrix math

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

Pretty prints the sparse matrix

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

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

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

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

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

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

Turns the matrix into the compressed format

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

not exposed currently

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

not exposed currently

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

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

Matrix serialization

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

Encode the sparse matrix as a lazy byte string

decode :: forall a b. Elem a b => ByteString -> SparseMatrix a b Source

Decode sparse matrix from the lazy byte string