sparse-0.9.2: A playground of sparse linear algebra primitives using Morton ordering

Copyright(C) 2013 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Sparse.Matrix

Contents

Description

Sparse Matrices in Morton order

The design of this library is described in the series "Revisiting Matrix Multiplication" on FP Complete's School of Haskell.

https://www.fpcomplete.com/user/edwardk/revisiting-matrix-multiplication/

Synopsis

Sparse Matrices

data Mat a Source

Constructors

Mat !Int !(Vector Word) !(Vector Word) !(Array a) 

Instances

(Arrayed a, Eq (Array a)) => Eq (Mat a) 
(Arrayed a, Eq0 a) => Num (Mat a) 
(Arrayed a, Ord (Array a)) => Ord (Mat a) 
(Arrayed a, Read a) => Read (Mat a) 
(Arrayed a, Show a) => Show (Mat a) 
NFData (Array a) => NFData (Mat a) 
Arrayed a => Ixed (Mat a) 
Arrayed a => Arrayed (Mat a) 
(Arrayed a, Eq0 a) => Eq0 (Mat a) 
(Arrayed a, (~) * a b) => Each (Mat a) (Mat b) a b 
type Index (Mat a) = Key 
type IxValue (Mat a) = a 
type Arr (Mat a) = Vector 

Keys

data Key Source

Key i j logically orders the keys as if the bits of the keys i and j were interleaved. This is equivalent to storing the keys in "Morton Order".

>>> Key 100 200 ^. _1
100
>>> Key 100 200 ^. _2
200

Constructors

Key !Word !Word 

Construction

fromList :: Arrayed a => [(Key, a)] -> Mat a Source

Build a sparse matrix.

singleton :: Arrayed a => Key -> a -> Mat a Source

singleton makes a matrix with a singleton value at a given location

transpose :: Arrayed a => Mat a -> Mat a Source

Transpose a matrix

ident :: (Arrayed a, Num a) => Int -> Mat a Source

ident n makes an n x n identity matrix

>>> ident 4
fromList [(Key 0 0,1),(Key 1 1,1),(Key 2 2,1),(Key 3 3,1)]

empty :: Arrayed a => Mat a Source

The empty matrix

>>> empty :: Mat Int
fromList []

Consumption

size :: Mat a -> Int Source

Count the number of non-zero entries in the matrix

>>> size (ident 4)
4

null :: Mat a -> Bool Source

>>> null (empty :: Mat Int)
True

Distinguishable Zero

class (Arrayed a, Num a) => Eq0 a where Source

Minimal complete definition

Nothing

Methods

isZero :: a -> Bool Source

Return whether or not the element is 0.

It may be okay to never return True, but you won't be able to thin spurious zeroes introduced into your matrix.

nonZero :: (x -> y -> a) -> x -> y -> Maybe a Source

Remove results that are equal to zero from a simpler function.

When used with addWith or multiplyWith's additive argument this can help retain the sparsity of the matrix.

addMats :: Mat a -> Mat a -> Mat a Source

Add two matrices. By default this assumes isZero can possibly return True after an addition. For some ring-like structures, this doesn't hold. There you can use:

addMats = addWith (+)

By default this will use

addMats = addWith0 $ nonZero (+)

addHeap :: Maybe (Heap a) -> Stream (Key, a) Source

Convert from a Heap to a Stream.

If addition of non-zero valus in your ring-like structure cannot yield zero, then you can use

addHeap = streamHeapWith (+)

instead of the default definition:

addHeap = streamHeapWith0 $ nonZero (+)

Instances

Eq0 Double 
Eq0 Float 
Eq0 Int 
Eq0 Integer 
Eq0 Word 
(RealFloat a, Eq0 a) => Eq0 (Complex a) 
(Arrayed a, Eq0 a) => Eq0 (Mat a) 

Customization

addWith :: Arrayed a => (a -> a -> a) -> Mat a -> Mat a -> Mat a Source

Merge two matrices where the indices coincide into a new matrix. This provides for generalized addition, but where the summation of two non-zero entries is necessarily non-zero.

multiplyWith :: Arrayed a => (a -> a -> a) -> (Maybe (Heap a) -> Stream (Key, a)) -> Mat a -> Mat a -> Mat a Source

Multiply two matrices using the specified multiplication and addition operation.

Storage

Lenses

_Mat :: Arrayed a => Iso' (Mat a) (Vector Vector (Arr a) (Key, a)) Source

bundle up the matrix in a form suitable for vector-algorithms

keys :: Lens' (Mat a) (Vector Key) Source

Access the keys of the non-zero entries of our matrix

values :: Lens (Mat a) (Mat b) (Array a) (Array b) Source

Access the values of the non-zero entries of our matrix