Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data FastMutableIntMap a
- new :: IntMap a -> IO (FastMutableIntMap a)
- newEmpty :: IO (FastMutableIntMap a)
- insert :: FastMutableIntMap a -> Int -> a -> IO ()
- isEmpty :: FastMutableIntMap a -> IO Bool
- getFrozenAndClear :: FastMutableIntMap a -> IO (IntMap a)
- size :: FastMutableIntMap a -> IO Int
- applyPatch :: FastMutableIntMap a -> PatchIntMap a -> IO (IntMap a)
- newtype PatchIntMap a = PatchIntMap (IntMap (Maybe a))
- traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
- lookup :: FastMutableIntMap a -> Int -> IO (Maybe a)
- forIntersectionWithImmutable_ :: MonadIO m => FastMutableIntMap a -> IntMap b -> (a -> b -> m ()) -> m ()
- for_ :: MonadIO m => FastMutableIntMap a -> (a -> m ()) -> m ()
- patchIntMapNewElements :: PatchIntMap a -> [a]
- patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a
- getDeletions :: PatchIntMap v -> IntMap v' -> IntMap v'
Documentation
data FastMutableIntMap a Source #
newEmpty :: IO (FastMutableIntMap a) Source #
getFrozenAndClear :: FastMutableIntMap a -> IO (IntMap a) Source #
Make an immutable snapshot of the datastructure and clear it
applyPatch :: FastMutableIntMap a -> PatchIntMap a -> IO (IntMap a) Source #
newtype PatchIntMap a Source #
Patch
for IntMap
which represents insertion or deletion of keys in the mapping.
Internally represented by 'IntMap (Maybe a)', where Just
means insert/update
and Nothing
means delete.
PatchIntMap (IntMap (Maybe a)) |
Instances
traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b) Source #
Map an effectful function Int -> a -> f b
over all a
s in the given
(that is, all inserts/updates), producing a PatchIntMap
af (PatchIntMap b)
.
forIntersectionWithImmutable_ :: MonadIO m => FastMutableIntMap a -> IntMap b -> (a -> b -> m ()) -> m () Source #
for_ :: MonadIO m => FastMutableIntMap a -> (a -> m ()) -> m () Source #
patchIntMapNewElements :: PatchIntMap a -> [a] Source #
Extract all a
s inserted/updated by the given
.PatchIntMap
a
patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a Source #
Convert the given
into an PatchIntMap
a
with all
the inserts/updates in the given patch.IntMap
a
getDeletions :: PatchIntMap v -> IntMap v' -> IntMap v' Source #
Subset the given
to contain only the keys that would be
deleted by the given IntMap
a
.PatchIntMap
a