{-# 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 { unPatchIntMap :: IntMap (Maybe a) }
deriving ( Show, Read, Eq, Ord
, Functor, Foldable, Traversable
, Monoid, DecidablyEmpty
)
deriving instance Semigroup (PatchIntMap v)
makeWrapped ''PatchIntMap
instance Patch (PatchIntMap a) where
type PatchTarget (PatchIntMap a) = IntMap a
apply (PatchIntMap p) v = if IntMap.null p then Nothing else Just $
let removes = IntMap.filter isNothing p
adds = IntMap.mapMaybe id p
in IntMap.union adds $ v `IntMap.difference` removes
instance FunctorWithIndex Int PatchIntMap
instance FoldableWithIndex Int PatchIntMap
instance TraversableWithIndex Int PatchIntMap where
itraverse = (_Wrapped .> itraversed <. traversed) . 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 f (PatchIntMap m) = PatchIntMap $ IntMap.mapWithKey (\ k mv -> f k <$> mv) m
traverseIntMapPatchWithKey :: Applicative f => (Int -> a -> f b) -> PatchIntMap a -> f (PatchIntMap b)
traverseIntMapPatchWithKey f (PatchIntMap m) = PatchIntMap <$> IntMap.traverseWithKey (traverse . f) m
patchIntMapNewElements :: PatchIntMap a -> [a]
patchIntMapNewElements (PatchIntMap m) = catMaybes $ IntMap.elems m
patchIntMapNewElementsMap :: PatchIntMap a -> IntMap a
patchIntMapNewElementsMap (PatchIntMap m) = IntMap.mapMaybe id m
getDeletions :: PatchIntMap v -> IntMap v' -> IntMap v'
getDeletions (PatchIntMap m) v = IntMap.intersection v m