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

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Sparse.Matrix

Contents

Description

Sparse Matrices in Morton order

Synopsis

Sparse Matrices

data Mat v a Source

Constructors

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

Instances

(Functor f, Contravariant f, Vector v a) => Contains f (Mat v a) 
(Applicative f, Vector v a) => Ixed f (Mat v a) 
(Applicative f, Vector v a, Vector v b) => Each f (Mat v a) (Mat v b) a b 
Functor v => Functor (Mat v) 
Foldable v => Foldable (Mat v) 
Traversable v => Traversable (Mat v) 
Eq (v a) => Eq (Mat v a) 
(Vector v a, Num a, Eq0 a) => Num (Mat v a) 
Ord (v a) => Ord (Mat v a) 
(Vector v a, Read a) => Read (Mat v a) 
(Vector v a, Show a) => Show (Mat v a) 
NFData (v a) => NFData (Mat v a) 
(Vector v a, Num a, Eq0 a) => Eq0 (Mat v a) 

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 :: Vector v a => [(Key, a)] -> Mat v aSource

Build a sparse matrix.

singleton :: Vector v a => Key -> a -> Mat v aSource

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

transpose :: Vector v a => Mat v a -> Mat v aSource

Transpose a matrix

ident :: (Vector v a, Num a) => Int -> Mat v aSource

ident n makes an n x n identity matrix

>>> ident 4 :: Mat U.Vector Int
fromList [(Key 0 0,1),(Key 1 1,1),(Key 2 2,1),(Key 3 3,1)]

empty :: Vector v a => Mat v aSource

The empty matrix

>>> empty :: Mat U.Vector Int
fromList []

Consumption

size :: Mat v a -> IntSource

Count the number of non-zero entries in the matrix

>>> size (ident 4 :: Mat U.Vector Int)
4

null :: Mat v a -> BoolSource

>>> null (empty :: Mat U.Vector Int)
True

Distinguishable Zero

class Num a => Eq0 a whereSource

Methods

isZero :: a -> BoolSource

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 aSource

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 :: Vector v a => Mat v a -> Mat v a -> Mat v aSource

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) 
(Vector v a, Num a, Eq0 a) => Eq0 (Mat v a) 

Customization

addWith :: Vector v a => (a -> a -> a) -> Mat v a -> Mat v a -> Mat v aSource

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 :: Vector v a => (a -> a -> a) -> (Maybe (Heap a) -> Stream (Key, a)) -> Mat v a -> Mat v a -> Mat v aSource

Multiply two matrices using the specified multiplication and addition operation.

Lenses

_Mat :: Iso (Mat u a) (Mat v b) (Vector Vector u (Key, a)) (Vector Vector v (Key, b))Source

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

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

Access the keys of a matrix

values :: Lens (Mat u a) (Mat v b) (u a) (v b)Source

Access the keys of a matrix