{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Patch.IntMap where
import Control.Lens hiding  (FunctorWithIndex, FoldableWithIndex, TraversableWithIndex)
#if !MIN_VERSION_lens(5,0,0)
import qualified Control.Lens as L
#endif
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as IntMap
import Data.Maybe
import Data.Monoid.DecidablyEmpty
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup (Semigroup (..))
#endif
import Data.Patch.Class
import Data.Functor.WithIndex
import Data.Foldable.WithIndex
import Data.Traversable.WithIndex
newtype PatchIntMap a = PatchIntMap { forall a. PatchIntMap a -> IntMap (Maybe a)
unPatchIntMap :: IntMap (Maybe a) }
  deriving ( Int -> PatchIntMap a -> ShowS
[PatchIntMap a] -> ShowS
PatchIntMap a -> String
(Int -> PatchIntMap a -> ShowS)
-> (PatchIntMap a -> String)
-> ([PatchIntMap a] -> ShowS)
-> Show (PatchIntMap a)
forall a. Show a => Int -> PatchIntMap a -> ShowS
forall a. Show a => [PatchIntMap a] -> ShowS
forall a. Show a => PatchIntMap a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> PatchIntMap a -> ShowS
showsPrec :: Int -> PatchIntMap a -> ShowS
$cshow :: forall a. Show a => PatchIntMap a -> String
show :: PatchIntMap a -> String
$cshowList :: forall a. Show a => [PatchIntMap a] -> ShowS
showList :: [PatchIntMap a] -> ShowS
Show, ReadPrec [PatchIntMap a]
ReadPrec (PatchIntMap a)
Int -> ReadS (PatchIntMap a)
ReadS [PatchIntMap a]
(Int -> ReadS (PatchIntMap a))
-> ReadS [PatchIntMap a]
-> ReadPrec (PatchIntMap a)
-> ReadPrec [PatchIntMap a]
-> Read (PatchIntMap a)
forall a. Read a => ReadPrec [PatchIntMap a]
forall a. Read a => ReadPrec (PatchIntMap a)
forall a. Read a => Int -> ReadS (PatchIntMap a)
forall a. Read a => ReadS [PatchIntMap a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (PatchIntMap a)
readsPrec :: Int -> ReadS (PatchIntMap a)
$creadList :: forall a. Read a => ReadS [PatchIntMap a]
readList :: ReadS [PatchIntMap a]
$creadPrec :: forall a. Read a => ReadPrec (PatchIntMap a)
readPrec :: ReadPrec (PatchIntMap a)
$creadListPrec :: forall a. Read a => ReadPrec [PatchIntMap a]
readListPrec :: ReadPrec [PatchIntMap a]
Read, PatchIntMap a -> PatchIntMap a -> Bool
(PatchIntMap a -> PatchIntMap a -> Bool)
-> (PatchIntMap a -> PatchIntMap a -> Bool) -> Eq (PatchIntMap a)
forall a. Eq a => PatchIntMap a -> PatchIntMap a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => PatchIntMap a -> PatchIntMap a -> Bool
== :: PatchIntMap a -> PatchIntMap a -> Bool
$c/= :: forall a. Eq a => PatchIntMap a -> PatchIntMap a -> Bool
/= :: PatchIntMap a -> PatchIntMap a -> Bool
Eq, Eq (PatchIntMap a)
Eq (PatchIntMap a) =>
(PatchIntMap a -> PatchIntMap a -> Ordering)
-> (PatchIntMap a -> PatchIntMap a -> Bool)
-> (PatchIntMap a -> PatchIntMap a -> Bool)
-> (PatchIntMap a -> PatchIntMap a -> Bool)
-> (PatchIntMap a -> PatchIntMap a -> Bool)
-> (PatchIntMap a -> PatchIntMap a -> PatchIntMap a)
-> (PatchIntMap a -> PatchIntMap a -> PatchIntMap a)
-> Ord (PatchIntMap a)
PatchIntMap a -> PatchIntMap a -> Bool
PatchIntMap a -> PatchIntMap a -> Ordering
PatchIntMap a -> PatchIntMap a -> PatchIntMap a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (PatchIntMap a)
forall a. Ord a => PatchIntMap a -> PatchIntMap a -> Bool
forall a. Ord a => PatchIntMap a -> PatchIntMap a -> Ordering
forall a. Ord a => PatchIntMap a -> PatchIntMap a -> PatchIntMap a
$ccompare :: forall a. Ord a => PatchIntMap a -> PatchIntMap a -> Ordering
compare :: PatchIntMap a -> PatchIntMap a -> Ordering
$c< :: forall a. Ord a => PatchIntMap a -> PatchIntMap a -> Bool
< :: PatchIntMap a -> PatchIntMap a -> Bool
$c<= :: forall a. Ord a => PatchIntMap a -> PatchIntMap a -> Bool
<= :: PatchIntMap a -> PatchIntMap a -> Bool
$c> :: forall a. Ord a => PatchIntMap a -> PatchIntMap a -> Bool
> :: PatchIntMap a -> PatchIntMap a -> Bool
$c>= :: forall a. Ord a => PatchIntMap a -> PatchIntMap a -> Bool
>= :: PatchIntMap a -> PatchIntMap a -> Bool
$cmax :: forall a. Ord a => PatchIntMap a -> PatchIntMap a -> PatchIntMap a
max :: PatchIntMap a -> PatchIntMap a -> PatchIntMap a
$cmin :: forall a. Ord a => PatchIntMap a -> PatchIntMap a -> PatchIntMap a
min :: PatchIntMap a -> PatchIntMap a -> PatchIntMap a
Ord
           , (forall a b. (a -> b) -> PatchIntMap a -> PatchIntMap b)
-> (forall a b. a -> PatchIntMap b -> PatchIntMap a)
-> Functor PatchIntMap
forall a b. a -> PatchIntMap b -> PatchIntMap a
forall a b. (a -> b) -> PatchIntMap a -> PatchIntMap b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> PatchIntMap a -> PatchIntMap b
fmap :: forall a b. (a -> b) -> PatchIntMap a -> PatchIntMap b
$c<$ :: forall a b. a -> PatchIntMap b -> PatchIntMap a
<$ :: forall a b. a -> PatchIntMap b -> PatchIntMap a
Functor, (forall m. Monoid m => PatchIntMap m -> m)
-> (forall m a. Monoid m => (a -> m) -> PatchIntMap a -> m)
-> (forall m a. Monoid m => (a -> m) -> PatchIntMap a -> m)
-> (forall a b. (a -> b -> b) -> b -> PatchIntMap a -> b)
-> (forall a b. (a -> b -> b) -> b -> PatchIntMap a -> b)
-> (forall b a. (b -> a -> b) -> b -> PatchIntMap a -> b)
-> (forall b a. (b -> a -> b) -> b -> PatchIntMap a -> b)
-> (forall a. (a -> a -> a) -> PatchIntMap a -> a)
-> (forall a. (a -> a -> a) -> PatchIntMap a -> a)
-> (forall a. PatchIntMap a -> [a])
-> (forall a. PatchIntMap a -> Bool)
-> (forall a. PatchIntMap a -> Int)
-> (forall a. Eq a => a -> PatchIntMap a -> Bool)
-> (forall a. Ord a => PatchIntMap a -> a)
-> (forall a. Ord a => PatchIntMap a -> a)
-> (forall a. Num a => PatchIntMap a -> a)
-> (forall a. Num a => PatchIntMap a -> a)
-> Foldable PatchIntMap
forall a. Eq a => a -> PatchIntMap a -> Bool
forall a. Num a => PatchIntMap a -> a
forall a. Ord a => PatchIntMap a -> a
forall m. Monoid m => PatchIntMap m -> m
forall a. PatchIntMap a -> Bool
forall a. PatchIntMap a -> Int
forall a. PatchIntMap a -> [a]
forall a. (a -> a -> a) -> PatchIntMap a -> a
forall m a. Monoid m => (a -> m) -> PatchIntMap a -> m
forall b a. (b -> a -> b) -> b -> PatchIntMap a -> b
forall a b. (a -> b -> b) -> b -> PatchIntMap a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => PatchIntMap m -> m
fold :: forall m. Monoid m => PatchIntMap m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> PatchIntMap a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> PatchIntMap a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> PatchIntMap a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> PatchIntMap a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> PatchIntMap a -> b
foldr :: forall a b. (a -> b -> b) -> b -> PatchIntMap a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> PatchIntMap a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> PatchIntMap a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> PatchIntMap a -> b
foldl :: forall b a. (b -> a -> b) -> b -> PatchIntMap a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> PatchIntMap a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> PatchIntMap a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> PatchIntMap a -> a
foldr1 :: forall a. (a -> a -> a) -> PatchIntMap a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> PatchIntMap a -> a
foldl1 :: forall a. (a -> a -> a) -> PatchIntMap a -> a
$ctoList :: forall a. PatchIntMap a -> [a]
toList :: forall a. PatchIntMap a -> [a]
$cnull :: forall a. PatchIntMap a -> Bool
null :: forall a. PatchIntMap a -> Bool
$clength :: forall a. PatchIntMap a -> Int
length :: forall a. PatchIntMap a -> Int
$celem :: forall a. Eq a => a -> PatchIntMap a -> Bool
elem :: forall a. Eq a => a -> PatchIntMap a -> Bool
$cmaximum :: forall a. Ord a => PatchIntMap a -> a
maximum :: forall a. Ord a => PatchIntMap a -> a
$cminimum :: forall a. Ord a => PatchIntMap a -> a
minimum :: forall a. Ord a => PatchIntMap a -> a
$csum :: forall a. Num a => PatchIntMap a -> a
sum :: forall a. Num a => PatchIntMap a -> a
$cproduct :: forall a. Num a => PatchIntMap a -> a
product :: forall a. Num a => PatchIntMap a -> a
Foldable, Functor PatchIntMap
Foldable PatchIntMap
(Functor PatchIntMap, Foldable PatchIntMap) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> PatchIntMap a -> f (PatchIntMap b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    PatchIntMap (f a) -> f (PatchIntMap a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> PatchIntMap a -> m (PatchIntMap b))
-> (forall (m :: * -> *) a.
    Monad m =>
    PatchIntMap (m a) -> m (PatchIntMap a))
-> Traversable PatchIntMap
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
PatchIntMap (m a) -> m (PatchIntMap a)
forall (f :: * -> *) a.
Applicative f =>
PatchIntMap (f a) -> f (PatchIntMap a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> PatchIntMap a -> m (PatchIntMap b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
PatchIntMap (f a) -> f (PatchIntMap a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
PatchIntMap (f a) -> f (PatchIntMap a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> PatchIntMap a -> m (PatchIntMap b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> PatchIntMap a -> m (PatchIntMap b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
PatchIntMap (m a) -> m (PatchIntMap a)
sequence :: forall (m :: * -> *) a.
Monad m =>
PatchIntMap (m a) -> m (PatchIntMap a)
Traversable
           , Semigroup (PatchIntMap a)
PatchIntMap a
Semigroup (PatchIntMap a) =>
PatchIntMap a
-> (PatchIntMap a -> PatchIntMap a -> PatchIntMap a)
-> ([PatchIntMap a] -> PatchIntMap a)
-> Monoid (PatchIntMap a)
[PatchIntMap a] -> PatchIntMap a
PatchIntMap a -> PatchIntMap a -> PatchIntMap a
forall a. Semigroup (PatchIntMap a)
forall a. PatchIntMap a
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. [PatchIntMap a] -> PatchIntMap a
forall a. PatchIntMap a -> PatchIntMap a -> PatchIntMap a
$cmempty :: forall a. PatchIntMap a
mempty :: PatchIntMap a
$cmappend :: forall a. PatchIntMap a -> PatchIntMap a -> PatchIntMap a
mappend :: PatchIntMap a -> PatchIntMap a -> PatchIntMap a
$cmconcat :: forall a. [PatchIntMap a] -> PatchIntMap a
mconcat :: [PatchIntMap a] -> PatchIntMap a
Monoid, Monoid (PatchIntMap a)
Monoid (PatchIntMap a) =>
(PatchIntMap a -> Bool) -> DecidablyEmpty (PatchIntMap a)
PatchIntMap a -> Bool
forall a. Monoid (PatchIntMap a)
forall a. Monoid a => (a -> Bool) -> DecidablyEmpty a
forall a. PatchIntMap a -> Bool
$cisEmpty :: forall a. PatchIntMap a -> Bool
isEmpty :: PatchIntMap a -> Bool
DecidablyEmpty
           )
deriving instance Semigroup (PatchIntMap v)
makeWrapped ''PatchIntMap
instance Patch (PatchIntMap a) where
  type PatchTarget (PatchIntMap a) = IntMap a
  apply :: PatchIntMap a
-> PatchTarget (PatchIntMap a)
-> Maybe (PatchTarget (PatchIntMap a))
apply (PatchIntMap IntMap (Maybe a)
p) PatchTarget (PatchIntMap a)
v = if IntMap (Maybe a) -> Bool
forall a. IntMap a -> Bool
IntMap.null IntMap (Maybe a)
p then Maybe (IntMap a)
Maybe (PatchTarget (PatchIntMap a))
forall a. Maybe a
Nothing else PatchTarget (PatchIntMap a) -> Maybe (PatchTarget (PatchIntMap a))
forall a. a -> Maybe a
Just (PatchTarget (PatchIntMap a)
 -> Maybe (PatchTarget (PatchIntMap a)))
-> PatchTarget (PatchIntMap a)
-> Maybe (PatchTarget (PatchIntMap a))
forall a b. (a -> b) -> a -> b
$
    let removes :: IntMap (Maybe a)
removes = (Maybe a -> Bool) -> IntMap (Maybe a) -> IntMap (Maybe a)
forall a. (a -> Bool) -> IntMap a -> IntMap a
IntMap.filter Maybe a -> Bool
forall a. Maybe a -> Bool
isNothing IntMap (Maybe a)
p
        adds :: IntMap a
adds = (Maybe a -> Maybe a) -> IntMap (Maybe a) -> IntMap a
forall a b. (a -> Maybe b) -> IntMap a -> IntMap b
IntMap.mapMaybe Maybe a -> Maybe a
forall a. a -> a
id IntMap (Maybe a)
p
    in IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
IntMap.union IntMap a
adds (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
PatchTarget (PatchIntMap a)
v IntMap a -> IntMap (Maybe a) -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
`IntMap.difference` IntMap (Maybe a)
removes
instance FunctorWithIndex Int PatchIntMap
instance FoldableWithIndex Int PatchIntMap
instance TraversableWithIndex Int PatchIntMap where
  itraverse :: forall (f :: * -> *) a b.
Applicative f =>
(Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
itraverse = ((IntMap (Maybe a) -> f (IntMap (Maybe b)))
-> PatchIntMap a -> f (PatchIntMap b)
(Unwrapped (PatchIntMap a) -> f (Unwrapped (PatchIntMap b)))
-> PatchIntMap a -> f (PatchIntMap b)
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso
  (PatchIntMap a)
  (PatchIntMap b)
  (Unwrapped (PatchIntMap a))
  (Unwrapped (PatchIntMap b))
_Wrapped ((IntMap (Maybe a) -> f (IntMap (Maybe b)))
 -> PatchIntMap a -> f (PatchIntMap b))
-> (Indexed Int a (f b)
    -> IntMap (Maybe a) -> f (IntMap (Maybe b)))
-> Indexed Int a (f b)
-> PatchIntMap a
-> f (PatchIntMap b)
forall st r kab. (st -> r) -> (kab -> st) -> kab -> r
.> Indexed Int (Maybe a) (f (Maybe b))
-> IntMap (Maybe a) -> f (IntMap (Maybe b))
forall i (t :: * -> *) a b.
TraversableWithIndex i t =>
IndexedTraversal i (t a) (t b) a b
IndexedTraversal
  Int (IntMap (Maybe a)) (IntMap (Maybe b)) (Maybe a) (Maybe b)
itraversed (Indexed Int (Maybe a) (f (Maybe b))
 -> IntMap (Maybe a) -> f (IntMap (Maybe b)))
-> ((a -> f b) -> Maybe a -> f (Maybe b))
-> Indexed Int a (f b)
-> IntMap (Maybe a)
-> f (IntMap (Maybe b))
forall i (p :: * -> * -> *) s t r a b.
Indexable i p =>
(Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r
<. (a -> f b) -> Maybe a -> f (Maybe b)
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
IndexedTraversal Int (Maybe a) (Maybe b) a b
traversed) (Indexed Int a (f b) -> PatchIntMap a -> f (PatchIntMap b))
-> ((Int -> a -> f b) -> Indexed Int a (f b))
-> (Int -> a -> f b)
-> PatchIntMap a
-> f (PatchIntMap b)
forall st r kab. (st -> r) -> (kab -> st) -> kab -> r
. (Int -> a -> f b) -> Indexed Int a (f b)
forall i a b. (i -> a -> b) -> Indexed i a b
Indexed
#if !MIN_VERSION_lens(5,0,0)
instance L.FunctorWithIndex     Int PatchIntMap where imap = Data.Functor.WithIndex.imap
instance L.FoldableWithIndex    Int PatchIntMap where ifoldMap = Data.Foldable.WithIndex.ifoldMap
instance L.TraversableWithIndex Int PatchIntMap where itraverse = Data.Traversable.WithIndex.itraverse
#endif
mapIntMapPatchWithKey :: (Int -> a -> b) -> PatchIntMap a -> PatchIntMap b
mapIntMapPatchWithKey :: forall a b. (Int -> a -> b) -> PatchIntMap a -> PatchIntMap b
mapIntMapPatchWithKey Int -> a -> b
f (PatchIntMap IntMap (Maybe a)
m) = IntMap (Maybe b) -> PatchIntMap b
forall a. IntMap (Maybe a) -> PatchIntMap a
PatchIntMap (IntMap (Maybe b) -> PatchIntMap b)
-> IntMap (Maybe b) -> PatchIntMap b
forall a b. (a -> b) -> a -> b
$ (Int -> Maybe a -> Maybe b) -> IntMap (Maybe a) -> IntMap (Maybe b)
forall a b. (Int -> a -> b) -> IntMap a -> IntMap b
IntMap.mapWithKey (\ Int
k Maybe a
mv -> Int -> a -> b
f Int
k (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a
mv) IntMap (Maybe a)
m
traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
traverseIntMapPatchWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
traverseIntMapPatchWithKey Int -> a -> f b
f (PatchIntMap IntMap (Maybe a)
m) = IntMap (Maybe b) -> PatchIntMap b
forall a. IntMap (Maybe a) -> PatchIntMap a
PatchIntMap (IntMap (Maybe b) -> PatchIntMap b)
-> f (IntMap (Maybe b)) -> f (PatchIntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int -> Maybe a -> f (Maybe b))
-> IntMap (Maybe a) -> f (IntMap (Maybe b))
forall (t :: * -> *) a b.
Applicative t =>
(Int -> a -> t b) -> IntMap a -> t (IntMap b)
IntMap.traverseWithKey ((a -> f b) -> Maybe a -> f (Maybe b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse ((a -> f b) -> Maybe a -> f (Maybe b))
-> (Int -> a -> f b) -> Int -> Maybe a -> f (Maybe b)
forall st r kab. (st -> r) -> (kab -> st) -> kab -> r
. Int -> a -> f b
f) IntMap (Maybe a)
m
patchIntMapNewElements :: PatchIntMap a -> [a]
patchIntMapNewElements :: forall a. PatchIntMap a -> [a]
patchIntMapNewElements (PatchIntMap IntMap (Maybe a)
m) = [Maybe a] -> [a]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe a] -> [a]) -> [Maybe a] -> [a]
forall a b. (a -> b) -> a -> b
$ IntMap (Maybe a) -> [Maybe a]
forall a. IntMap a -> [a]
IntMap.elems IntMap (Maybe a)
m
patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a
patchIntMapNewElementsMap :: forall a. PatchIntMap a -> IntMap a
patchIntMapNewElementsMap (PatchIntMap IntMap (Maybe a)
m) = (Maybe a -> Maybe a) -> IntMap (Maybe a) -> IntMap a
forall a b. (a -> Maybe b) -> IntMap a -> IntMap b
IntMap.mapMaybe Maybe a -> Maybe a
forall a. a -> a
id IntMap (Maybe a)
m
getDeletions :: PatchIntMap v -> IntMap v' -> IntMap v'
getDeletions :: forall v v'. PatchIntMap v -> IntMap v' -> IntMap v'
getDeletions (PatchIntMap IntMap (Maybe v)
m) IntMap v'
v = IntMap v' -> IntMap (Maybe v) -> IntMap v'
forall a b. IntMap a -> IntMap b -> IntMap a
IntMap.intersection IntMap v'
v IntMap (Maybe v)
m