reflex-0.6.4.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell2010

Data.FastMutableIntMap

Description

 
Synopsis

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

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.

Constructors

PatchIntMap 

Fields

Instances
Functor PatchIntMap 
Instance details

Defined in Data.Patch.IntMap

Methods

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

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

Foldable PatchIntMap 
Instance details

Defined in Data.Patch.IntMap

Methods

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

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

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

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

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

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

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

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

toList :: PatchIntMap a -> [a] #

null :: PatchIntMap a -> Bool #

length :: PatchIntMap a -> Int #

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

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

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

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

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

Traversable PatchIntMap 
Instance details

Defined in Data.Patch.IntMap

Methods

traverse :: Applicative f => (a -> f b) -> PatchIntMap a -> f (PatchIntMap b) #

sequenceA :: Applicative f => PatchIntMap (f a) -> f (PatchIntMap a) #

mapM :: Monad m => (a -> m b) -> PatchIntMap a -> m (PatchIntMap b) #

sequence :: Monad m => PatchIntMap (m a) -> m (PatchIntMap a) #

FunctorWithIndex Int PatchIntMap 
Instance details

Defined in Data.Patch.IntMap

Methods

imap :: (Int -> a -> b) -> PatchIntMap a -> PatchIntMap b #

imapped :: IndexedSetter Int (PatchIntMap a) (PatchIntMap b) a b #

FoldableWithIndex Int PatchIntMap 
Instance details

Defined in Data.Patch.IntMap

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> PatchIntMap a -> m #

ifolded :: IndexedFold Int (PatchIntMap a) a #

ifoldr :: (Int -> a -> b -> b) -> b -> PatchIntMap a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> PatchIntMap a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> PatchIntMap a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> PatchIntMap a -> b #

TraversableWithIndex Int PatchIntMap 
Instance details

Defined in Data.Patch.IntMap

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b) #

itraversed :: IndexedTraversal Int (PatchIntMap a) (PatchIntMap b) a b #

Eq a => Eq (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

Ord a => Ord (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

Read a => Read (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

Show a => Show (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

Semigroup (PatchIntMap v)

a <> b will apply the changes of b and then apply the changes of a. If the same key is modified by both patches, the one on the left will take precedence.

Instance details

Defined in Data.Patch.IntMap

Monoid (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

Wrapped (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

Associated Types

type Unwrapped (PatchIntMap a) :: Type #

Patch (PatchIntMap a)

Apply the insertions or deletions to a given IntMap.

Instance details

Defined in Data.Patch.IntMap

Associated Types

type PatchTarget (PatchIntMap a) :: Type #

DecidablyEmpty (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

Methods

isEmpty :: PatchIntMap a -> Bool #

PatchIntMap a1 ~ t => Rewrapped (PatchIntMap a2) t 
Instance details

Defined in Data.Patch.IntMap

type Unwrapped (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

type PatchTarget (PatchIntMap a) 
Instance details

Defined in Data.Patch.IntMap

traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b) #

Map an effectful function Int -> a -> f b over all as in the given PatchIntMap a (that is, all inserts/updates), producing a f (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 as inserted/updated by the given PatchIntMap a.

patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a #

Convert the given PatchIntMap a into an IntMap a with all the inserts/updates in the given patch.

getDeletions :: PatchIntMap v -> IntMap v' -> IntMap v' #

Subset the given IntMap a to contain only the keys that would be deleted by the given PatchIntMap a.