sparse-vector-0.3.0: Sparse vector data structures
Copyright(c) Matt Hunzinger 2025
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainermatt@hunzinger.me
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.SparseVector.Strict

Description

 
Synopsis

Sparse vectors

newtype SparseVector a Source #

Sparse n-dimensional vector.

A sparse vector is defined as a Vector (Bool, a), where (Bool, a) is a cell for an element in the sparse vector. The Bool indicates whether the cell contains a valid element.

Inserting elements at some dimension n will grow the vector up to n, using (False, defaultVal) to create empty cells.

Constructors

SparseVector 

Fields

Instances

Instances details
Foldable SparseVector Source # 
Instance details

Defined in Data.SparseVector.Strict

Methods

fold :: Monoid m => SparseVector m -> m #

foldMap :: Monoid m => (a -> m) -> SparseVector a -> m #

foldMap' :: Monoid m => (a -> m) -> SparseVector a -> m #

foldr :: (a -> b -> b) -> b -> SparseVector a -> b #

foldr' :: (a -> b -> b) -> b -> SparseVector a -> b #

foldl :: (b -> a -> b) -> b -> SparseVector a -> b #

foldl' :: (b -> a -> b) -> b -> SparseVector a -> b #

foldr1 :: (a -> a -> a) -> SparseVector a -> a #

foldl1 :: (a -> a -> a) -> SparseVector a -> a #

toList :: SparseVector a -> [a] #

null :: SparseVector a -> Bool #

length :: SparseVector a -> Int #

elem :: Eq a => a -> SparseVector a -> Bool #

maximum :: Ord a => SparseVector a -> a #

minimum :: Ord a => SparseVector a -> a #

sum :: Num a => SparseVector a -> a #

product :: Num a => SparseVector a -> a #

Functor SparseVector Source # 
Instance details

Defined in Data.SparseVector.Strict

Methods

fmap :: (a -> b) -> SparseVector a -> SparseVector b #

(<$) :: a -> SparseVector b -> SparseVector a #

Show a => Show (SparseVector a) Source # 
Instance details

Defined in Data.SparseVector.Strict

NFData a => NFData (SparseVector a) Source # 
Instance details

Defined in Data.SparseVector.Strict

Methods

rnf :: SparseVector a -> () #

Eq a => Eq (SparseVector a) Source # 
Instance details

Defined in Data.SparseVector.Strict

Construction

empty :: SparseVector a Source #

Empty sparse vector (requires a default value for operations that need it).

emptyWith :: a -> SparseVector a Source #

Empty sparse vector with a default value.

Operations

insert :: Int -> a -> SparseVector a -> SparseVector a Source #

Insert an element at a given index into a SparseVector.

Inserting elements at some dimension n will grow the vector up to n, using (False, defaultVal) to create empty cells.

>>> insert 0 'a' 'x' empty
SparseVector {unSparseVector = [(True, 'a')]}
>>> insert 2 'b' 'x' empty
SparseVector {unSparseVector = [(False, 'x'), (False, 'x'), (True, 'b')]}

lookup :: Int -> SparseVector a -> Maybe a Source #

Lookup an element at a given index in a SparseVector.

delete :: Int -> SparseVector a -> SparseVector a Source #

Delete an index from a SparseVector, replacing its cell with (False, defaultVal).

mapWithKey :: (Int -> a -> b) -> SparseVector a -> SparseVector b Source #

mapAccum :: (a -> b -> (a, c)) -> a -> SparseVector b -> (a, SparseVector c) Source #

Intersection

intersectionVecWith :: (a -> b -> c) -> SparseVector a -> SparseVector b -> Vector c Source #

intersectionVecWithKey :: (Int -> a -> b -> c) -> SparseVector a -> SparseVector b -> Vector c Source #

Conversion

fromVector :: Vector a -> SparseVector a Source #

toVector :: SparseVector a -> Vector a Source #