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

Safe HaskellNone
LanguageHaskell2010

Eigen.SparseMatrix

Contents

Synopsis

Types

newtype SparseMatrix :: Nat -> Nat -> Type -> Type 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 :: ForeignPtr (CSparseMatrix a) -> SparseMatrix n m a 
Instances
(Elem a, Show a, KnownNat n, KnownNat m) => Show (SparseMatrix n m a) Source # 
Instance details

Defined in Eigen.SparseMatrix

Methods

showsPrec :: Int -> SparseMatrix n m a -> ShowS #

show :: SparseMatrix n m a -> String #

showList :: [SparseMatrix n m a] -> ShowS #

(Elem a, KnownNat n, KnownNat m) => Binary (SparseMatrix n m a) Source # 
Instance details

Defined in Eigen.SparseMatrix

Methods

put :: SparseMatrix n m a -> Put #

get :: Get (SparseMatrix n m a) #

putList :: [SparseMatrix n m a] -> Put #

type SparseMatrixXf n m = SparseMatrix n m Float Source #

Alias for single precision sparse matrix

type SparseMatrixXd n m = SparseMatrix n m Double Source #

Alias for double precision sparse matrix

type SparseMatrixXcf n m = SparseMatrix n m (Complex Float) Source #

Alias for single previsiom sparse matrix of complex numbers

type SparseMatrixXcd n m = SparseMatrix n m (Complex Double) Source #

Alias for double prevision sparse matrix of complex numbers

Matrix internal data

elems :: forall n m a. (Elem a, KnownNat n, KnownNat m) => SparseMatrix n m a -> Int Source #

Number of elements in the sparse matrix, including zeros

values :: Elem a => SparseMatrix n m a -> Vector a Source #

Get the coefficient values of the non-zeros.

innerIndices :: Elem a => SparseMatrix n m a -> Vector Int Source #

Get the row indices of the non-zeros.

outerStarts :: Elem a => SparseMatrix n m a -> Vector Int Source #

Gets for each column the index of the first non-zero in the previous two arrays.

innerNNZs :: Elem a => SparseMatrix n m a -> Maybe (Vector Int) Source #

Gets the number of non-zeros of each column. 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

Accessors

cols :: forall n m a. (Elem a, KnownNat n, KnownNat m) => SparseMatrix n m a -> Col m Source #

Number of colums in the sparse matrix

rows :: forall n m a. (Elem a, KnownNat n, KnownNat m) => SparseMatrix n m a -> Row n Source #

Number of rows in the sparse matrix

coeff :: forall n m r c a. (Elem a, KnownNat n, KnownNat m, KnownNat r, KnownNat c, r <= n, c <= m) => Row r -> Col c -> SparseMatrix n m a -> a Source #

Sparse matrix coefficient at the given row and column

(!) :: forall n m r c a. (Elem a, KnownNat n, KnownNat m, KnownNat r, KnownNat c, r <= n, c <= m) => SparseMatrix n m a -> (Row r, Col c) -> a Source #

Matrix coefficient at the given row and column

getRow :: forall n m r a. (Elem a, KnownNat n, KnownNat m, KnownNat r, r <= n, 1 <= n) => Row r -> SparseMatrix n m a -> SparseMatrix 1 m a Source #

Return a single row of the sparse matrix.

getCol :: forall n m c a. (Elem a, KnownNat n, KnownNat m, KnownNat c, c <= m, 1 <= m) => Col c -> SparseMatrix n m a -> SparseMatrix n 1 a Source #

Return a single column of the sparse matrix.

Matrix conversions

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

Construct a sparse matrix from a list of triples (row, val, col)

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

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

fromVector :: forall n m a. (Elem a, KnownNat n, KnownNat m) => Vector (CTriplet a) -> SparseMatrix n m a Source #

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

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

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

fromDenseList :: forall n m a. (Elem a, Eq a, KnownNat n, KnownNat m) => [[a]] -> Maybe (SparseMatrix n m a) Source #

Construct a sparsematrix from a two-dimensional list of values. If the dimensions of the list do not match that of the list, Nothing is returned. Zero values will be compressed.

toDenseList :: forall n m a. (Elem a, KnownNat n, KnownNat m) => SparseMatrix n m a -> [[a]] Source #

Convert a sparse matrix to a (n X m) dense list of values.

fromMatrix :: (Elem a, KnownNat n, KnownNat m) => Matrix n m a -> SparseMatrix n m a Source #

Construct a sparse matrix from a dense matrix. zero-elements will be compressed.

toMatrix :: (Elem a, KnownNat n, KnownNat m) => SparseMatrix n m a -> Matrix n m a Source #

Construct a dense matrix from a sparse matrix

Matrix properties

norm :: Elem a => SparseMatrix n m a -> 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 => SparseMatrix n m a -> 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 => SparseMatrix n m a -> 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 :: forall sr sc br bc n m a. (Elem a, KnownNat sr, KnownNat sc, KnownNat br, KnownNat bc, KnownNat n, KnownNat m) => (sr <= n, sc <= m, br <= n, bc <= m) => Row sr -> Col sc -> Row br -> Col bc -> SparseMatrix n m a -> SparseMatrix br bc a Source #

Extract a rectangular block from the sparse matrix, given a startRow, startCol, blockRows, blockCols

nonZeros :: Elem a => SparseMatrix n m a -> Int Source #

Number of non-zeros elements in the sparse matrix

innerSize :: Elem a => SparseMatrix n m a -> Int Source #

Minor dimension with respect to the storage order

outerSize :: Elem a => SparseMatrix n m a -> Int Source #

Major dimension with respect to the storage order

Basic matrix algebra

add :: Elem a => SparseMatrix n m a -> SparseMatrix n m a -> SparseMatrix n m a Source #

Add two sparse matrices by adding the corresponding entries together.

sub :: Elem a => SparseMatrix n m a -> SparseMatrix n m a -> SparseMatrix n m a Source #

Subtract two sparse matrices by subtracting the corresponding entries together.

mul :: Elem a => SparseMatrix p q a -> SparseMatrix q r a -> SparseMatrix p r a Source #

Matrix multiplication.

Matrix tranformations

pruned :: Elem a => a -> SparseMatrix n m a -> SparseMatrix n m a Source #

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

scale :: Elem a => a -> SparseMatrix n m a -> SparseMatrix n m a Source #

Multiply matrix on a given scalar

transpose :: Elem a => SparseMatrix n m a -> SparseMatrix m n a Source #

Transpose of the sparse matrix

adjoint :: Elem a => SparseMatrix n m a -> SparseMatrix m n a Source #

Adjoint of the sparse matrix

map :: (Elem a, Elem b, KnownNat n, KnownNat m) => (a -> b) -> SparseMatrix n m a -> SparseMatrix n m b Source #

Map a function over the SparseMatrix.

imap :: (Elem a, Elem b, KnownNat n, KnownNat m) => (Int -> Int -> a -> b) -> SparseMatrix n m a -> SparseMatrix n m b Source #

Map an indexed function over the SparseMatrix.

Matrix representation

compress :: Elem a => SparseMatrix n m a -> SparseMatrix n m a Source #

The matrix in the compressed format

uncompress :: Elem a => SparseMatrix n m a -> SparseMatrix n m a Source #

The matrix in the uncompressed format

compressed :: Elem a => SparseMatrix n m a -> Bool Source #

Is the matrix compressed?

Matrix serialisation

encode :: (Elem a, KnownNat n, KnownNat m) => SparseMatrix n m a -> ByteString Source #

Encode the sparse matrix as a lazy bytestring

decode :: (Elem a, KnownNat n, KnownNat m) => ByteString -> SparseMatrix n m a Source #

Decode the sparse matrix from a lazy bytestring

Mutable matrices

thaw :: (Elem a, PrimMonad p) => SparseMatrix n m a -> p (MSparseMatrix n m (PrimState p) a) Source #

Yield a mutable copy of the immutable matrix.

freeze :: (Elem a, PrimMonad p) => MSparseMatrix n m (PrimState p) a -> p (SparseMatrix n m a) Source #

Yield an immutable copy of the mutable matrix

unsafeThaw :: (Elem a, PrimMonad p) => SparseMatrix n m a -> p (MSparseMatrix n m (PrimState p) a) 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, PrimMonad p) => MSparseMatrix n m (PrimState p) a -> p (SparseMatrix n m a) Source #

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