Copyright | (c) Matt Hunzinger 2025 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | matt@hunzinger.me |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Data.SparseVector.Unboxed
Description
Synopsis
- newtype SparseVector a = SparseVector {
- unSparseVector :: Vector (Bool, a)
- empty :: Unbox a => SparseVector a
- insert :: Unbox a => Int -> a -> SparseVector a -> SparseVector a
- lookup :: Unbox a => Int -> SparseVector a -> Maybe a
- delete :: Unbox a => Int -> SparseVector a -> SparseVector a
- mapWithKey :: (Unbox a, Unbox b) => (Int -> a -> b) -> SparseVector a -> SparseVector b
- mapAccum :: (Unbox b, Unbox c) => (a -> b -> (a, c)) -> a -> SparseVector b -> (a, SparseVector c)
- svMap :: (Unbox a, Unbox b) => (a -> b) -> SparseVector a -> SparseVector b
- svFoldr :: Unbox a => (a -> b -> b) -> b -> SparseVector a -> b
- svFoldl :: Unbox a => (b -> a -> b) -> b -> SparseVector a -> b
- svLength :: Unbox a => SparseVector a -> Int
- svNull :: Unbox a => SparseVector a -> Bool
- intersection :: (Unbox a, Unbox b) => SparseVector a -> SparseVector b -> SparseVector a
- intersectionWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> SparseVector a -> SparseVector b -> SparseVector c
- intersectionWithKey :: (Unbox a, Unbox b, Unbox c) => (Int -> a -> b -> c) -> SparseVector a -> SparseVector b -> SparseVector c
- intersectionVec :: (Unbox a, Unbox b) => SparseVector a -> SparseVector b -> Vector a
- intersectionVecWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> SparseVector a -> SparseVector b -> Vector c
- intersectionVecWithKey :: (Unbox a, Unbox b, Unbox c) => (Int -> a -> b -> c) -> SparseVector a -> SparseVector b -> Vector c
- fromList :: Unbox a => [(Int, a)] -> SparseVector a
- toList :: Unbox a => SparseVector a -> [Maybe a]
- fromVector :: Unbox a => Vector a -> SparseVector a
- toVector :: Unbox a => SparseVector a -> Vector a
- freeze :: (PrimMonad m, Unbox a) => MSparseVector (PrimState m) a -> m (SparseVector a)
- unsafeFreeze :: (PrimMonad m, Unbox a) => MSparseVector (PrimState m) a -> m (SparseVector a)
- thaw :: (PrimMonad m, Unbox a) => SparseVector a -> m (MSparseVector (PrimState m) a)
- unsafeThaw :: (PrimMonad m, Unbox a) => SparseVector a -> m (MSparseVector (PrimState m) a)
Sparse vectors
newtype SparseVector a Source #
Sparse n-dimensional vector using unboxed vectors.
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.
The element type a
must have an Unbox
instance, and (Bool, a)
must also have an Unbox
instance.
Inserting elements at some dimension n
will grow the vector up to n
,
using (False, defaultVal)
to create empty cells.
Constructors
SparseVector | |
Fields
|
Instances
(Show a, Unbox a) => Show (SparseVector a) Source # | |
Defined in Data.SparseVector.Unboxed Methods showsPrec :: Int -> SparseVector a -> ShowS # show :: SparseVector a -> String # showList :: [SparseVector a] -> ShowS # | |
Unbox a => NFData (SparseVector a) Source # | |
Defined in Data.SparseVector.Unboxed Methods rnf :: SparseVector a -> () # | |
(Eq a, Unbox a) => Eq (SparseVector a) Source # | |
Defined in Data.SparseVector.Unboxed Methods (==) :: SparseVector a -> SparseVector a -> Bool # (/=) :: SparseVector a -> SparseVector a -> Bool # |
Construction
empty :: Unbox a => SparseVector a Source #
Empty sparse vector.
Operations
insert :: Unbox a => 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, undefined)
to create empty cells.
>>>
insert 0 'a' empty
SparseVector {unSparseVector = [(True, 'a')]}
>>>
insert 2 'b' empty
SparseVector {unSparseVector = [(False, undefined),(False, undefined),(True, 'b')]}
lookup :: Unbox a => Int -> SparseVector a -> Maybe a Source #
Lookup an element at a given index in a SparseVector
.
delete :: Unbox a => Int -> SparseVector a -> SparseVector a Source #
Delete an index from a SparseVector
, replacing its cell with (False, undefined)
.
mapWithKey :: (Unbox a, Unbox b) => (Int -> a -> b) -> SparseVector a -> SparseVector b Source #
mapAccum :: (Unbox b, Unbox c) => (a -> b -> (a, c)) -> a -> SparseVector b -> (a, SparseVector c) Source #
Functor-like operations (with Unbox constraints)
svMap :: (Unbox a, Unbox b) => (a -> b) -> SparseVector a -> SparseVector b Source #
Map a function over a SparseVector (requires Unbox constraints)
Foldable-like operations (with Unbox constraints)
svFoldr :: Unbox a => (a -> b -> b) -> b -> SparseVector a -> b Source #
Fold a SparseVector from the right (requires Unbox constraints)
svFoldl :: Unbox a => (b -> a -> b) -> b -> SparseVector a -> b Source #
Fold a SparseVector from the left (requires Unbox constraints)
svLength :: Unbox a => SparseVector a -> Int Source #
Get the number of actual elements (non-empty cells) in a SparseVector
svNull :: Unbox a => SparseVector a -> Bool Source #
Check if a SparseVector has no actual elements
Intersection
intersection :: (Unbox a, Unbox b) => SparseVector a -> SparseVector b -> SparseVector a Source #
intersectionWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> SparseVector a -> SparseVector b -> SparseVector c Source #
intersectionWithKey :: (Unbox a, Unbox b, Unbox c) => (Int -> a -> b -> c) -> SparseVector a -> SparseVector b -> SparseVector c Source #
intersectionVec :: (Unbox a, Unbox b) => SparseVector a -> SparseVector b -> Vector a Source #
intersectionVecWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> SparseVector a -> SparseVector b -> Vector c Source #
intersectionVecWithKey :: (Unbox a, Unbox b, Unbox c) => (Int -> a -> b -> c) -> SparseVector a -> SparseVector b -> Vector c Source #
Conversion
fromList :: Unbox a => [(Int, a)] -> SparseVector a Source #
toList :: Unbox a => SparseVector a -> [Maybe a] Source #
fromVector :: Unbox a => Vector a -> SparseVector a Source #
toVector :: Unbox a => SparseVector a -> Vector a Source #
Mutations
freeze :: (PrimMonad m, Unbox a) => MSparseVector (PrimState m) a -> m (SparseVector a) Source #
Freeze a MSparseVector
into a SparseVector
.
unsafeFreeze :: (PrimMonad m, Unbox a) => MSparseVector (PrimState m) a -> m (SparseVector a) Source #
Freeze a MSparseVector
into a SparseVector
.
thaw :: (PrimMonad m, Unbox a) => SparseVector a -> m (MSparseVector (PrimState m) a) Source #
Unfreeze a SparseVector
into a MSparseVector
.
unsafeThaw :: (PrimMonad m, Unbox a) => SparseVector a -> m (MSparseVector (PrimState m) a) Source #
Unfreeze a SparseVector
into a MSparseVector
.