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

Safe HaskellSafe-Inferred

Math.LinearAlgebra.Sparse.Vector

Contents

Description

This module provides common funtions for manipulating sparse vectors

Synopsis

Sparse vector datatype

type SVec α = IntMap αSource

Type of internal vector storage

data SparseVector α Source

Sparse vector is just indexed map of non-zero values

Constructors

SV 

Fields

dim :: Int

real size of vector (with zeroes)

vec :: SVec α

IntMap storing non-zero values

Instances

Functor SparseVector

fmap applies given function on vector non-zero values

Foldable SparseVector

fold functions are applied to non-zero values

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

Num operators like (*), (+) and (-) work on sparse vectors like zipWith (…) works on lists, except size of result is maximum of arguments sizes.

signum, abs and negate work through fmap, so usual Num laws are satisfied (such as (signum v)*(abs v) == v.

fromInteger constructs a vector with single element (only fromInteger 0 = emptyVec). So,

>>> 3 + (sparseList [0,2,1])
sparseList [3,2,1]
(Show α, Eq α, Num α) => Show (SparseVector α)

Shows size and filled vector (but without zeroes)

Monoid (SparseVector α)

Monoid mappend operation works like concatenation of two vectors (indexes of second are shifted by length of first)

Examples:

>>> (sparseList [0,1,0,2]) <> (sparseList [3,0,4])
sparseList [0,1,0,2,3,0,4]
>>> 1 <> (sparseList [2,3])
sparseList [1,2,3]

Basic functions

setLength :: Int -> SparseVector α -> SparseVector αSource

Sets vector's size

emptyVec :: SparseVector αSource

Vector of zero size with no values

zeroVec :: Int -> SparseVector αSource

Vector of given size with no non-zero values

isZeroVec :: SparseVector α -> BoolSource

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

isNotZeroVec :: SparseVector α -> BoolSource

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

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

Vector of length 1 with given value

Filter

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

Splits vector using predicate and returns a pair with filtered values and re-enumereted second part (that doesn't satisfy predicate). For example:

>>> partitionVec (>0) (sparseList [0,1,-1,2,3,0,-4,5,-6,0,7])
( sparseList [0,1,0,2,3,0,0,5,0,0,7], sparseList [-1,-4,-6] )

Lookup/update

(!) :: Num α => SparseVector α -> Index -> αSource

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

eraseInVec :: Num α => SparseVector α -> Index -> SparseVector αSource

Deletes element of vector at given index (size of vector doesn't change)

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

Updates value at given index

Vectors combining

unionVecsWith :: (α -> α -> α) -> SparseVector α -> SparseVector α -> SparseVector αSource

Unions non-zero values of vectors and applies given function on intersection

intersectVecsWith :: (α -> α -> α) -> SparseVector α -> SparseVector α -> SparseVector αSource

Intersects non-zero values of vectors and applies given function on them

To/from list

fillVec :: Num α => SparseVector α -> [α]Source

Returns plain list with all zeroes restored

sparseList :: (Num α, Eq α) => [α] -> SparseVector αSource

Converts plain list to sparse vector, throwing out all zeroes

vecToAssocList :: (Num α, Eq α) => SparseVector α -> [(Index, α)]Source

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

vecFromAssocListWithSize :: (Num α, Eq α) => Int -> [(Index, α)] -> SparseVector αSource

Converts associative list to sparse vector, of given size

vecFromAssocList :: (Num α, Eq α) => [(Index, α)] -> SparseVector αSource

Converts associative list to sparse vector, using maximal index as it's size

Multiplications

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

Dot product of two sparse vectors

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

Unicode alias for dot