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

Safe HaskellNone
LanguageHaskell98

Data.Eigen.Matrix.Mutable

Contents

Synopsis

Documentation

data MMatrix a b s Source

Mutable matrix. You can modify elements

Constructors

MMatrix 

Fields

mm_rows :: Int
 
mm_cols :: Int
 
mm_vals :: MVector s b
 

type MMatrixXf = MMatrix Float CFloat Source

Alias for single precision mutable matrix

type MMatrixXd = MMatrix Double CDouble Source

Alias for double precision mutable matrix

type MMatrixXcf = MMatrix (Complex Float) (CComplex CFloat) Source

Alias for single previsiom mutable matrix of complex numbers

type MMatrixXcd = MMatrix (Complex Double) (CComplex CDouble) Source

Alias for double prevision mutable matrix of complex numbers

type STMatrix a b s = MMatrix a b s Source

Construction

new :: (PrimMonad m, Elem a b) => Int -> Int -> m (MMatrix a b (PrimState m)) Source

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

replicate :: (PrimMonad m, Elem a b) => Int -> Int -> a -> m (MMatrix a b (PrimState m)) Source

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

Consistency check

valid :: Elem a b => MMatrix a b s -> Bool Source

Verify matrix dimensions and memory layout

Accessing individual elements

read :: (PrimMonad m, Elem a b) => MMatrix a b (PrimState m) -> Int -> Int -> m a Source

Yield the element at the given position.

write :: (PrimMonad m, Elem a b) => MMatrix a b (PrimState m) -> Int -> Int -> a -> m () Source

Replace the element at the given position.

unsafeRead :: (PrimMonad m, Elem a b) => MMatrix a b (PrimState m) -> Int -> Int -> m a Source

Yield the element at the given position. No bounds checks are performed.

unsafeWrite :: (PrimMonad m, Elem a b) => MMatrix a b (PrimState m) -> Int -> Int -> a -> m () Source

Replace the element at the given position. No bounds checks are performed.

Modifying matrices

set :: (PrimMonad m, Elem a b) => MMatrix a b (PrimState m) -> a -> m () Source

Set all elements of the matrix to the given value

copy :: (PrimMonad m, Elem a b) => MMatrix a b (PrimState m) -> MMatrix a b (PrimState m) -> m () Source

Copy a matrix. The two matrices must have the same size and may not overlap.

unsafeCopy :: (PrimMonad m, Elem a b) => MMatrix a b (PrimState m) -> MMatrix a b (PrimState m) -> m () Source

Copy a matrix. The two matrices must have the same size and may not overlap however no bounds check performaned to it may SEGFAULT for incorrect input.

Raw pointers

unsafeWith :: Elem a b => IOMatrix a b -> (Ptr b -> CInt -> CInt -> IO c) -> IO c Source

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