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

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

Sparse.Matrix.Internal.Heap

Description

Bootstrapped catenable non-empty pairing heaps as described in

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

Synopsis

Documentation

data Heap a Source

Bootstrapped _catenable_ non-empty pairing heaps

Constructors

Heap !Key a [Heap a] [Heap a] [Heap a] 

fby :: Heap a -> Heap a -> Heap aSource

Append two heaps where we know every key in the first occurs before every key in the second

>>> head $ singleton (Key 1 1) 1 `fby` singleton (Key 2 2) 2
(Key 1 1,1)

mix :: Heap a -> Heap a -> Heap aSource

Interleave two heaps making a new Heap

>>> head $ singleton (Key 1 1) 1 `mix` singleton (Key 2 2) 2
(Key 1 1,1)

singleton :: Key -> a -> Heap aSource

>>> singleton (Key 1 1) 1
Heap (Key 1 1) 1 [] [] []

head :: Heap a -> (Key, a)Source

>>> head $ singleton (Key 1 1) 1
(Key 1 1,1)

tail :: Heap a -> Maybe (Heap a)Source

>>> tail $ singleton (Key 1 1) 1
Nothing

fromList :: [(Key, a)] -> Heap aSource

Build a Heap from a jumbled up list of elements.

fromAscList :: [(Key, a)] -> Heap aSource

Build a Heap from an list of elements that must be in strictly ascending Morton order.

streamHeapWith :: Monad m => (a -> a -> a) -> Maybe (Heap a) -> Stream m (Key, a)Source

Convert a Heap into a Stream folding together values with identical keys using the supplied addition operator.

streamHeapWith0 :: Monad m => (a -> a -> Maybe a) -> Maybe (Heap a) -> Stream m (Key, a)Source

Convert a Heap into a Stream folding together values with identical keys using the supplied addition operator that is allowed to return a sparse 0, by returning Nothing.

timesSingleton :: (a -> b -> c) -> Stream Id (Key, a) -> Key -> b -> Maybe (Heap c)Source

This is an internal Heap fusion combinator used to multiply on the right by a singleton Key/value pair.

singletonTimes :: (a -> b -> c) -> Key -> a -> Stream Id (Key, b) -> Maybe (Heap c)Source

This is an internal Heap fusion combinator used to multiply on the right by a singleton Key/value pair.