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

Safe HaskellNone
LanguageHaskell2010

Eigen.Matrix.Mutable

Contents

Synopsis

Types

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

A mutable matrix. See Matrix for details about matrix layout.

Constructors

MMatrix :: Vec (n * m) s a -> MMatrix n m s a 

type MMatrixXf n m s = MMatrix n m s Float Source #

Alias for single precision mutable matrix

type MMatrixXd n m s = MMatrix n m s Double Source #

Alias for double precision mutable matrix

type MMatrixXcf n m s = MMatrix n m s (Complex Float) Source #

Alias for single precision mutable matrix of complex numbers

type MMatrixXcd n m s = MMatrix n m s (Complex Double) Source #

Alias for double precision mutable matrix of complex numbers

type IOMatrix n m a = MMatrix n m RealWorld a Source #

A mutable matrix where the state token is specialised to RealWorld.

type STMatrix n m s a = MMatrix n m s a Source #

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

Construction

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

Create a mutable matrix of the given size and fill it with 0 as an initial value.

replicate :: forall n m p a. (PrimMonad p, Elem a, KnownNat n, KnownNat m) => a -> p (MMatrix n m (PrimState p) a) Source #

Create a mutable matrix of the given size and fill it with an initial value.

Indexing

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

Yield the element at the given position.

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

Replace the element at the given position.

Modification

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

Set all elements of the matrix to a given value.

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

Copy a matrix.

Modification with Pointers

unsafeWith :: forall n m a b. (KnownNat n, KnownNat m, Elem a) => IOMatrix n m a -> (Ptr (C a) -> CInt -> CInt -> IO b) -> IO b Source #

Pass a pointer to the matrix's data to the IO action. Modifying dat through the pointer is unsafe if the matrix could have been frozen before the modification.

Conversion to Vectors

vals :: MMatrix n m s a -> MVector s (C a) Source #

Return a mutable storable MVector of the corresponding C types to one's mutable matrix.

fromVector :: Elem a => MVector s (C a) -> MMatrix n m s a Source #

Create a mutable matrix from a mutable storable MVector.