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.SparseSet.Unboxed
Description
Synopsis
- data SparseSet i a = SparseSet {
- dense :: !(Vector a)
- sparse :: !(SparseVector i)
- empty :: (Unbox a, Unbox i) => SparseSet i a
- insert :: (Integral i, Unbox a, Unbox i) => i -> a -> SparseSet i a -> SparseSet i a
- lookup :: (Integral i, Unbox a, Unbox i) => SparseSet i a -> i -> Maybe a
- delete :: (Integral i, Unbox a, Unbox i) => i -> SparseSet i a -> SparseSet i a
- intersection :: (Integral i, Unbox a, Unbox i) => SparseSet i a -> SparseSet i b -> SparseSet i a
- intersectionWith :: (Integral i, Unbox a, Unbox b, Unbox c, Unbox i) => (a -> b -> c) -> SparseSet i a -> SparseSet i b -> SparseSet i c
- intersectionVec :: (Integral i, Unbox a, Unbox i) => SparseSet i a -> SparseSet i b -> Vector a
- toList :: (Integral i, Unbox a, Unbox i) => SparseSet i a -> [Maybe a]
- freeze :: (PrimMonad m, Unbox a, Unbox i) => MSparseSet (PrimState m) i a -> m (SparseSet i a)
- unsafeFreeze :: (PrimMonad m, Unbox a, Unbox i) => MSparseSet (PrimState m) i a -> m (SparseSet i a)
- thaw :: (PrimMonad m, Unbox a, Unbox i) => SparseSet i a -> m (MSparseSet (PrimState m) i a)
- unsafeThaw :: (PrimMonad m, Unbox a, Unbox i) => SparseSet i a -> m (MSparseSet (PrimState m) i a)
Sparse sets
Constructors
SparseSet | |
Fields
|
Instances
Generic (SparseSet i a) Source # | |||||
Defined in Data.SparseSet.Unboxed Associated Types
| |||||
(Show a, Show i, Unbox a, Unbox i) => Show (SparseSet i a) Source # | |||||
Unbox i => NFData (SparseSet i a) Source # | |||||
Defined in Data.SparseSet.Unboxed | |||||
(Eq a, Eq i, Unbox a, Unbox i) => Eq (SparseSet i a) Source # | |||||
type Rep (SparseSet i a) Source # | |||||
Defined in Data.SparseSet.Unboxed type Rep (SparseSet i a) = D1 ('MetaData "SparseSet" "Data.SparseSet.Unboxed" "sparse-set-0.3.0-9e4aezLoPlHECzYnIPXBuf" 'False) (C1 ('MetaCons "SparseSet" 'PrefixI 'True) (S1 ('MetaSel ('Just "dense") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector a)) :*: S1 ('MetaSel ('Just "sparse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SparseVector i)))) |
Construction
Operations
Intersection
intersection :: (Integral i, Unbox a, Unbox i) => SparseSet i a -> SparseSet i b -> SparseSet i a Source #
intersectionWith :: (Integral i, Unbox a, Unbox b, Unbox c, Unbox i) => (a -> b -> c) -> SparseSet i a -> SparseSet i b -> SparseSet i c Source #
intersectionVec :: (Integral i, Unbox a, Unbox i) => SparseSet i a -> SparseSet i b -> Vector a Source #
Conversion
freeze :: (PrimMonad m, Unbox a, Unbox i) => MSparseSet (PrimState m) i a -> m (SparseSet i a) Source #
Freeze a MSparseSet
into a SparseSet
.
unsafeFreeze :: (PrimMonad m, Unbox a, Unbox i) => MSparseSet (PrimState m) i a -> m (SparseSet i a) Source #
thaw :: (PrimMonad m, Unbox a, Unbox i) => SparseSet i a -> m (MSparseSet (PrimState m) i a) Source #
Unfreeze a SparseSet
into a MSparseSet
.
unsafeThaw :: (PrimMonad m, Unbox a, Unbox i) => SparseSet i a -> m (MSparseSet (PrimState m) i a) Source #