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

Safe HaskellNone
LanguageHaskell2010

Eigen.SparseMatrix.Mutable

Contents

Synopsis

Mutable SparseMatrix

newtype MSparseMatrix :: Nat -> Nat -> Type -> Type -> Type where Source #

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

Constructors

MSparseMatrix :: ForeignPtr (CSparseMatrix a) -> MSparseMatrix n m s a 

type IOSparseMatrix n m a = MSparseMatrix n m RealWorld a Source #

A sparse matrix where the state token is specialised to ReadWorld.

type STSparseMatrix n m s a = MSparseMatrix n m s a Source #

This type does not differ from MSparseMatrix, but might be desirable for readability.

new :: forall m n p a. (Elem a, KnownNat n, KnownNat m, PrimMonad p) => p (MSparseMatrix n m (PrimState p) a) Source #

Create a new sparse matrix with the given size rows x cols.

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

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

SparseMatrix properties

rows :: forall n m s a. (Elem a, KnownNat n, KnownNat m) => MSparseMatrix n m s a -> Int Source #

Returns the number of rows of the matrix.

cols :: forall n m s a. (Elem a, KnownNat n, KnownNat m) => MSparseMatrix n m s a -> Int Source #

Returns the number of columns of the matrix.

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

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

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

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

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

Returns the number of nonzero coefficients.

SparseMatrix compression

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

Returns whether or not the matrix is in compressed form.

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

Turns the matrix into compressed format.

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

Decompresses the matrix.

Accessing SparseMatrix data

read :: forall n m r c p a. (Elem a, PrimMonad p, KnownNat n, KnownNat m, KnownNat r, KnownNat c, r <= n, c <= m) => Row r -> Col c -> MSparseMatrix n m (PrimState p) a -> p a Source #

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

write :: forall n m r c p a. (Elem a, PrimMonad p, KnownNat n, KnownNat m, KnownNat r, KnownNat c, r <= n, c <= m) => MSparseMatrix n m (PrimState p) a -> Row r -> Col c -> a -> p () 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, PrimMonad p) => MSparseMatrix n m (PrimState p) a -> p () Source #

Remove all non zeros, but keep allocated memory.

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

Sets the matrix to the identity matrix.