sparse-lin-alg-0.4: Effective linear algebra on sparse matrices

Safe HaskellSafe-Infered

Math.LinearAlgebra.Sparse.Matrix

Contents

Synopsis

Sparse matrix datatype

type SMx α = SVec (SVec α)Source

Internal storage of matrix

data SparseMatrix α Source

Sparse matrix is indexed map of non-zero rows,

Constructors

SM 

Fields

dims :: (Int, Int)

real height and width of filled matrix

mx :: SMx α

IntMap (IntMap α) representing non-zero values

Instances

Functor SparseMatrix

fmap applies given function on all non-zero values

Eq α => Eq (SparseMatrix α) 
(Eq α, Num α) => Num (SparseMatrix α)

All Num work on sparse matrices the same way as on SparseVector (see documentation there)

(Show α, Eq α, Num α) => Show (SparseMatrix α)

Shows size and filled matrix (but without zeroes)

Monoid (SparseMatrix α)

mempty is just emptyMx

mappend is horisontal concatenation

Basic functions

height, width :: SparseMatrix α -> IntSource

Matrix real height and width

setSize :: Num α => (Int, Int) -> SparseMatrix α -> SparseMatrix αSource

Sets height and width of matrix

emptyMx :: SparseMatrix αSource

Matrix of zero size with no values

zeroMx :: Num α => (Int, Int) -> SparseMatrix αSource

Zero matrix of given size

isZeroMx, isNotZeroMx :: SparseMatrix α -> BoolSource

Checks if matrix has no non-zero values (i.e. is empty)

idMx :: (Num α, Eq α) => Int -> SparseMatrix αSource

Identity matrix of given size

Combining matrices

(//) :: SparseMatrix α -> SparseMatrix α -> SparseMatrix αSource

Vertical concatenation

hconcat, vconcat :: [SparseMatrix α] -> SparseMatrix αSource

Batch horisontal/vertical concatenation

sizedBlockMx :: Num α => (Int, Int) -> [[SparseMatrix α]] -> SparseMatrix αSource

Takes size of each block and matrix of sparse matrices and constructs sparse matrix from this blocks

sizedBlockSMx :: (Eq α, Num α) => (Int, Int) -> SparseMatrix (SparseMatrix α) -> SparseMatrix αSource

Fills sparse matrix of blocks and then applies sizedBlockMx

Addingdeleting rowcolumns

addRow :: Num α => SparseVector α -> Index -> SparseMatrix α -> SparseMatrix αSource

Adds row at given index, increasing matrix height by 1 and shifting indexes after it

addCol :: Num α => SparseVector α -> Index -> SparseMatrix α -> SparseMatrix αSource

Adds column at given index, increasing matrix width by 1 and shifting indexes after it

addZeroRow :: Num α => Index -> SparseMatrix α -> SparseMatrix αSource

Just adds zero row at given index

addZeroCol :: Num α => Index -> SparseMatrix α -> SparseMatrix αSource

Just adds zero column at given index

delRow :: Num α => Index -> SparseMatrix α -> SparseMatrix αSource

Deletes row at given index, decreasing matrix height by 1 and shifting indexes after it

delCol :: Num α => Index -> SparseMatrix α -> SparseMatrix αSource

Deletes column at given index, decreasing matrix width by 1 and shifting indexes after it

delRowCol :: Num α => Index -> Index -> SparseMatrix α -> SparseMatrix αSource

Deletes row and column at given indexes

separateMx :: Num α => (SparseVector α -> Bool) -> SparseMatrix α -> (SparseMatrix α, SparseMatrix α)Source

Separates matrix, using pedicate on rows and returns two matrices of the same size, one only with rows satisfying predicate, and another with the rest rows

Lookup/update

(#) :: Num α => SparseMatrix α -> (Index, Index) -> αSource

Looks up an element in the matrix (if not found, zero is returned)

row :: Num α => SparseMatrix α -> Index -> SparseVector αSource

Returns row of matrix at given index

col :: (Num α, Eq α) => SparseMatrix α -> Index -> SparseVector αSource

Returns column of matrix at given index

updRow :: Num α => (SparseVector α -> SparseVector α) -> Index -> SparseMatrix α -> SparseMatrix αSource

Updates values in row using given function

eraseRow :: Num α => Index -> SparseMatrix α -> SparseMatrix αSource

Fills row with zeroes (i.e. deletes it, but size of matrix doesn't change)

erase :: Num α => SparseMatrix α -> (Index, Index) -> SparseMatrix αSource

Erases matrix element at given index

ins :: (Num α, Eq α) => SparseMatrix α -> ((Index, Index), α) -> SparseMatrix αSource

Inserts new element to the sparse matrix (replaces old value)

findRowIndices :: (SparseVector α -> Bool) -> SparseMatrix α -> [Int]Source

Finds indices of rows, that satisfy given predicate. Searches from left to right (in ascending order of indices)

findRowIndicesR :: (SparseVector α -> Bool) -> SparseMatrix α -> [Int]Source

Finds indices of rows, that satisfy given predicate. Searches from right to left (in descending order of indices)

popRow :: Num α => Index -> SparseMatrix α -> (SparseVector α, SparseMatrix α)Source

Returns a row at given index and matrix without it

(|>) :: Num α => SparseVector α -> SparseMatrix α -> SparseMatrix αSource

Adds row to matrix at the top

(<|) :: Num α => SparseMatrix α -> SparseVector α -> SparseMatrix αSource

Adds row to matrix at the bottom

replaceRow :: Num α => SparseVector α -> Index -> SparseMatrix α -> SparseMatrix αSource

Replaces row at given index with given vector

exchangeRows :: Num α => Index -> Index -> SparseMatrix α -> SparseMatrix αSource

Exchanges positions of two rows

mapOnRows :: (SparseVector α -> SparseVector β) -> SparseMatrix α -> SparseMatrix βSource

Applies vector-function on matrix rows

To/from list

diagonalMx :: (Num α, Eq α) => [α] -> SparseMatrix αSource

Constructs square matrix with given elements on diagonal

mainDiag :: (Eq α, Num α) => SparseMatrix α -> SparseVector αSource

Collects main diagonal of matrix

fromRows :: Num α => [SparseVector α] -> SparseMatrix αSource

Constructs matrix from a list of rows

toAssocList :: (Num α, Eq α) => SparseMatrix α -> [((Index, Index), α)]Source

Converts sparse matrix to associative list, adding fake zero element, to save real size for inverse conversion

fromAssocListWithSize :: (Num α, Eq α) => (Int, Int) -> [((Index, Index), α)] -> SparseMatrix αSource

Converts associative list to sparse matrix, of given size

fromAssocList :: (Num α, Eq α) => [((Index, Index), α)] -> SparseMatrix αSource

Converts associative list to sparse matrix, using maximal index as matrix size

fillMx :: Num α => SparseMatrix α -> [[α]]Source

Converts sparse matrix to plain list-matrix with all zeroes restored

sparseMx :: (Num α, Eq α) => [[α]] -> SparseMatrix αSource

Converts plain list-matrix to sparse matrix, throwing out all zeroes

Transposition

trans :: (Num α, Eq α) => SparseMatrix α -> SparseMatrix αSource

Transposes matrix (rows become columns)

Multiplications

mulMV :: (Num α, Eq α) => SparseMatrix α -> SparseVector α -> SparseVector αSource

Matrix-by-vector multiplication

(×·) :: (Num α, Eq α) => SparseMatrix α -> SparseVector α -> SparseVector αSource

Unicode alias for mulMV

mulVM :: (Num α, Eq α) => SparseVector α -> SparseMatrix α -> SparseVector αSource

Vector-by-matrix multiplication

·× :: (Num α, Eq α) => SparseVector α -> SparseMatrix α -> SparseVector αSource

Unicode alias for mulVM

mul :: (Num α, Eq α) => SparseMatrix α -> SparseMatrix α -> SparseMatrix αSource

Sparse matrices multiplication

(×) :: (Num α, Eq α) => SparseMatrix α -> SparseMatrix α -> SparseMatrix αSource

Unicode alias for mul