Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 {
- unPatchIntMap :: 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'
- toList :: FastMutableIntMap a -> IO [(Int, a)]
Documentation
data FastMutableIntMap a Source #
A FastMutableIntMap
holds a map of values of type a
and allows low-overhead modifications via IO.
Operations on FastMutableIntMap
run in IO.
new :: IntMap a -> IO (FastMutableIntMap a) Source #
Create a new FastMutableIntMap
out of an IntMap
newEmpty :: IO (FastMutableIntMap a) Source #
Create a new empty FastMutableIntMap
insert :: FastMutableIntMap a -> Int -> a -> IO () Source #
Insert an element into a FastMutableIntMap
at the given key
isEmpty :: FastMutableIntMap a -> IO Bool Source #
Checks whether a FastMutableIntMap
is empty
getFrozenAndClear :: FastMutableIntMap a -> IO (IntMap a) Source #
Make an immutable snapshot of the datastructure and clear it
size :: FastMutableIntMap a -> IO Int Source #
Retrieves the size of a FastMutableIntMap
applyPatch :: FastMutableIntMap a -> PatchIntMap a -> IO (IntMap a) Source #
Updates the value of a FastMutableIntMap
with the given patch (see IntMap
),
and returns an IntMap
with the modified keys and values.
newtype PatchIntMap a #
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 | |
|
Instances
traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b) #
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)
.
lookup :: FastMutableIntMap a -> Int -> IO (Maybe a) Source #
Attempt to lookup an element by key in a FastMutableIntMap
forIntersectionWithImmutable_ :: MonadIO m => FastMutableIntMap a -> IntMap b -> (a -> b -> m ()) -> m () Source #
Runs the provided action over the intersection of a FastMutableIntMap
and an IntMap
for_ :: MonadIO m => FastMutableIntMap a -> (a -> m ()) -> m () Source #
Runs the provided action over the values of a FastMutableIntMap
patchIntMapNewElements :: PatchIntMap a -> [a] #
Extract all a
s inserted/updated by the given
.PatchIntMap
a
patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a #
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' #
Subset the given
to contain only the keys that would be
deleted by the given IntMap
a
.PatchIntMap
a