matrices-0.5.0: native matrix based on vector

Safe HaskellNone
LanguageHaskell2010

Data.Matrix.Storable

Contents

Synopsis

Documentation

Accessors

length information

dim :: Context a => Matrix a -> (Int, Int) Source #

rows :: Context a => Matrix a -> Int Source #

cols :: Context a => Matrix a -> Int Source #

Indexing

unsafeIndex :: Context a => Matrix a -> (Int, Int) -> a Source #

(!) :: Context a => Matrix a -> (Int, Int) -> a Source #

takeRow :: Context a => Matrix a -> Int -> Vector a Source #

takeColumn :: Context a => Matrix a -> Int -> Vector a Source #

takeDiag :: Context a => Matrix a -> Vector a Source #

Construction

unsafeFromVector :: Context a => (Int, Int) -> Vector a -> Matrix a Source #

fromVector :: Context a => (Int, Int) -> Vector a -> Matrix a Source #

matrix :: Context a => Int -> [a] -> Matrix a Source #

O(m*n) Matrix construction

fromList :: Context a => (Int, Int) -> [a] -> Matrix a Source #

fromLists :: Context a => [[a]] -> Matrix a Source #

O(m*n) Create matrix from list of lists, it doesn't check if the list of list is a valid matrix

fromRows :: Context a => [Vector a] -> Matrix a Source #

O(m*n) Create matrix from rows

fromColumns :: Context a => [Vector a] -> Matrix a Source #

O(m*n) Create matrix from columns

empty :: Context a => Matrix a Source #

Conversions

flatten :: Context a => Matrix a -> Vector a Source #

toRows :: Context a => Matrix a -> [Vector a] Source #

O(m) Return the rows

toColumns :: Context a => Matrix a -> [Vector a] Source #

toList :: Context a => Matrix a -> [a] Source #

O(m*n) Create a list by concatenating rows

toLists :: Context a => Matrix a -> [[a]] Source #

O(m*n) List of lists

tr :: Context a => Matrix a -> Matrix a Source #

O(m*n) Matrix transpose

subMatrix Source #

Arguments

:: Context a 
=> (Int, Int)

upper left corner of the submatrix

-> (Int, Int)

bottom right corner of the submatrix

-> Matrix a 
-> Matrix a 

O(1) Extract sub matrix

ident :: (Context a, Num a) => Int -> Matrix a Source #

O(m*n) Create an identity matrix

diag Source #

Arguments

:: (Context a, Num a, Foldable t) 
=> t a

diagonal

-> Matrix a 

O(m*n) Create a square matrix with given diagonal, other entries default to 0

diagRect Source #

Arguments

:: (Context a, Foldable t) 
=> a

default value

-> (Int, Int) 
-> t a

diagonal

-> Matrix a 

O(m*n) Create a rectangular matrix with default values and given diagonal

fromBlocks Source #

Arguments

:: Context a 
=> a

default value

-> [[Matrix a]] 
-> Matrix a 

isSymmetric :: (Context a, Eq a) => Matrix a -> Bool Source #

force :: Context a => Matrix a -> Matrix a Source #

foldl :: Context b => (a -> b -> a) -> a -> Matrix b -> a Source #

Mapping

map :: (Context a, Context b) => (a -> b) -> Matrix a -> Matrix b Source #

imap :: (Context a, Context b) => ((Int, Int) -> a -> b) -> Matrix a -> Matrix b Source #

Monadic mapping

mapM :: (Context a, Context b, Monad m) => (a -> m b) -> Matrix a -> m (Matrix b) Source #

imapM :: (Context a, Context b, Monad m) => ((Int, Int) -> a -> m b) -> Matrix a -> m (Matrix b) Source #

O(m*n) Apply the monadic action to every element and its index, yielding a matrix of results.

mapM_ :: (Context a, Monad m) => (a -> m b) -> Matrix a -> m () Source #

imapM_ :: (Context a, Monad m) => ((Int, Int) -> a -> m b) -> Matrix a -> m () Source #

O(m*n) Apply the monadic action to every element and its index, ignoring the results.

forM :: (Context a, Context b, Monad m) => Matrix a -> (a -> m b) -> m (Matrix b) Source #

forM_ :: (Context a, Monad m) => Matrix a -> (a -> m b) -> m () Source #

Zipping

zipWith :: (Context a, Context b, Context c) => (a -> b -> c) -> Matrix a -> Matrix b -> Matrix c Source #

zipWith3 :: (Context a, Context b, Context c, Context d) => (a -> b -> c -> d) -> Matrix a -> Matrix b -> Matrix c -> Matrix d Source #

zipWith4 :: (Context a, Context b, Context c, Context d, Context e) => (a -> b -> c -> d -> e) -> Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e Source #

zipWith5 :: (Context a, Context b, Context c, Context d, Context e, Context f) => (a -> b -> c -> d -> e -> f) -> Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e -> Matrix f Source #

zipWith6 :: (Context a, Context b, Context c, Context d, Context e, Context f, Context g) => (a -> b -> c -> d -> e -> f -> g) -> Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e -> Matrix f -> Matrix g Source #

izipWith :: (Context a, Context b, Context c) => ((Int, Int) -> a -> b -> c) -> Matrix a -> Matrix b -> Matrix c Source #

izipWith3 :: (Context a, Context b, Context c, Context d) => ((Int, Int) -> a -> b -> c -> d) -> Matrix a -> Matrix b -> Matrix c -> Matrix d Source #

izipWith4 :: (Context a, Context b, Context c, Context d, Context e) => ((Int, Int) -> a -> b -> c -> d -> e) -> Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e Source #

izipWith5 :: (Context a, Context b, Context c, Context d, Context e, Context f) => ((Int, Int) -> a -> b -> c -> d -> e -> f) -> Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e -> Matrix f Source #

izipWith6 :: (Context a, Context b, Context c, Context d, Context e, Context f, Context g) => ((Int, Int) -> a -> b -> c -> d -> e -> f -> g) -> Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e -> Matrix f -> Matrix g Source #

zip :: (Context a, Context b, Context (a, b)) => Matrix a -> Matrix b -> Matrix (a, b) Source #

zip3 :: (Context a, Context b, Context c, Context (a, b, c)) => Matrix a -> Matrix b -> Matrix c -> Matrix (a, b, c) Source #

zip4 :: (Context a, Context b, Context c, Context d, Context (a, b, c, d)) => Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix (a, b, c, d) Source #

zip5 :: (Context a, Context b, Context c, Context d, Context e, Context (a, b, c, d, e)) => Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e -> Matrix (a, b, c, d, e) Source #

zip6 :: (Context a, Context b, Context c, Context d, Context e, Context f, Context (a, b, c, d, e, f)) => Matrix a -> Matrix b -> Matrix c -> Matrix d -> Matrix e -> Matrix f -> Matrix (a, b, c, d, e, f) Source #

Monadic Zipping

zipWithM :: (Context a, Context b, Context c, Monad m) => (a -> b -> m c) -> Matrix a -> Matrix b -> m (Matrix c) Source #

zipWithM_ :: (Context a, Context b, Monad m) => (a -> b -> m c) -> Matrix a -> Matrix b -> m () Source #

Unzipping

unzip :: (Context a, Context b, Context (a, b)) => Matrix (a, b) -> (Matrix a, Matrix b) Source #

unzip3 :: (Context a, Context b, Context c, Context (a, b, c)) => Matrix (a, b, c) -> (Matrix a, Matrix b, Matrix c) Source #

unzip4 :: (Context a, Context b, Context c, Context d, Context (a, b, c, d)) => Matrix (a, b, c, d) -> (Matrix a, Matrix b, Matrix c, Matrix d) Source #

unzip5 :: (Context a, Context b, Context c, Context d, Context e, Context (a, b, c, d, e)) => Matrix (a, b, c, d, e) -> (Matrix a, Matrix b, Matrix c, Matrix d, Matrix e) Source #

unzip6 :: (Context a, Context b, Context c, Context d, Context e, Context f, Context (a, b, c, d, e, f)) => Matrix (a, b, c, d, e, f) -> (Matrix a, Matrix b, Matrix c, Matrix d, Matrix e, Matrix f) Source #

generate :: Context a => (Int, Int) -> ((Int, Int) -> a) -> Matrix a Source #

Mutable matrix

thaw :: (Context a, PrimMonad s) => Matrix a -> s (MMatrix (PrimState s) a) Source #

unsafeThaw :: (Context a, PrimMonad s) => Matrix a -> s (MMatrix (PrimState s) a) Source #

freeze :: (Context a, PrimMonad s) => MMatrix (PrimState s) a -> s (Matrix a) Source #

unsafeFreeze :: (Context a, PrimMonad s) => MMatrix (PrimState s) a -> s (Matrix a) Source #

create :: Context a => (forall s. ST s (MMatrix s a)) -> Matrix a Source #