{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Patch.Map where
import Data.Patch.Class
import Control.Lens hiding (FunctorWithIndex, FoldableWithIndex, TraversableWithIndex)
#if !MIN_VERSION_lens(5,0,0)
import qualified Control.Lens as L
#endif
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
import Data.Monoid.DecidablyEmpty
import Data.Semigroup (Semigroup (..), stimesIdempotentMonoid)
import Data.Functor.WithIndex
import Data.Foldable.WithIndex
import Data.Traversable.WithIndex
newtype PatchMap k v = PatchMap { unPatchMap :: Map k (Maybe v) }
deriving ( Show, Read, Eq, Ord
, Foldable, Traversable
, DecidablyEmpty
)
deriving instance Functor (PatchMap k)
deriving instance Ord k => Monoid (PatchMap k v)
instance Ord k => Semigroup (PatchMap k v) where
PatchMap a <> PatchMap b = PatchMap $ a `mappend` b
stimes = stimesIdempotentMonoid
instance Ord k => Patch (PatchMap k v) where
type PatchTarget (PatchMap k v) = Map k v
{-# INLINABLE apply #-}
apply (PatchMap p) old = Just $! insertions `Map.union` (old `Map.difference` deletions)
where insertions = Map.mapMaybeWithKey (const id) p
deletions = Map.mapMaybeWithKey (const nothingToJust) p
nothingToJust = \case
Nothing -> Just ()
Just _ -> Nothing
makeWrapped ''PatchMap
instance FunctorWithIndex k (PatchMap k)
instance FoldableWithIndex k (PatchMap k)
instance TraversableWithIndex k (PatchMap k) where
itraverse = (_Wrapped .> itraversed <. traversed) . Indexed
#if !MIN_VERSION_lens(5,0,0)
instance L.FunctorWithIndex k (PatchMap k) where imap = Data.Functor.WithIndex.imap
instance L.FoldableWithIndex k (PatchMap k) where ifoldMap = Data.Foldable.WithIndex.ifoldMap
instance L.TraversableWithIndex k (PatchMap k) where itraverse = Data.Traversable.WithIndex.itraverse
#endif
patchMapNewElements :: PatchMap k v -> [v]
patchMapNewElements (PatchMap p) = catMaybes $ Map.elems p
patchMapNewElementsMap :: PatchMap k v -> Map k v
patchMapNewElementsMap (PatchMap p) = Map.mapMaybe id p