patch-0.0.2.0: Infrastructure for writing patches which act on other types.

Safe HaskellNone
LanguageHaskell98

Data.Patch.IntMap

Description

Module containing PatchIntMap, a Patch for IntMap which allows for insert/update or delete of associations.

Synopsis

Documentation

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 

Fields

Instances
Functor PatchIntMap Source # 
Instance details

Defined in Data.Patch.IntMap

Methods

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

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

Foldable PatchIntMap Source # 
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 Source # 
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 Source # 
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 Source # 
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 Source # 
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) Source # 
Instance details

Defined in Data.Patch.IntMap

Ord a => Ord (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Read a => Read (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Show a => Show (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

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

Monoid (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Wrapped (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Associated Types

type Unwrapped (PatchIntMap a) :: Type #

DecidablyEmpty (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

Patch (PatchIntMap a) Source #

Apply the insertions or deletions to a given IntMap.

Instance details

Defined in Data.Patch.IntMap

Associated Types

type PatchTarget (PatchIntMap a) :: Type Source #

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

Defined in Data.Patch.IntMap

type Unwrapped (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

type PatchTarget (PatchIntMap a) Source # 
Instance details

Defined in Data.Patch.IntMap

mapIntMapPatchWithKey :: (Int -> a -> b) -> PatchIntMap a -> PatchIntMap b Source #

Map a function Int -> a -> b over all as in the given PatchIntMap a (that is, all inserts/updates), producing a PatchIntMap b.

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

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.