reflex-0.5.0.1: Higher-order Functional Reactive Programming

Safe HaskellNone
LanguageHaskell98

Data.FastMutableIntMap

Synopsis

Documentation

insert :: FastMutableIntMap a -> Int -> a -> IO () Source #

getFrozenAndClear :: FastMutableIntMap a -> IO (IntMap a) Source #

Make an immutable snapshot of the datastructure and clear it

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.

Constructors

PatchIntMap (IntMap (Maybe a)) 
Instances
Functor PatchIntMap Source # 
Instance details

Defined in Reflex.Patch.IntMap

Methods

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

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

Foldable PatchIntMap Source # 
Instance details

Defined in Reflex.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 Source # 
Instance details

Defined in Reflex.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) #

Semigroup (PatchIntMap v) Source #

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 Reflex.Patch.IntMap

Monoid (PatchIntMap a) Source # 
Instance details

Defined in Reflex.Patch.IntMap

Patch (PatchIntMap a) Source #

Apply the insertions or deletions to a given IntMap.

Instance details

Defined in Reflex.Patch.IntMap

Associated Types

type PatchTarget (PatchIntMap a) :: Type Source #

type PatchTarget (PatchIntMap a) Source # 
Instance details

Defined in Reflex.Patch.IntMap

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

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).

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 as inserted/updated by the given PatchIntMap a.

patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a Source #

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' Source #

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