{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Data.Patch
( module Data.Patch
, module X
) where
import Data.Patch.Class as X
import Data.Patch.DMap as X hiding (getDeletions)
import Data.Patch.DMapWithMove as X (PatchDMapWithMove, const2PatchDMapWithMoveWith, mapPatchDMapWithMove,
patchDMapWithMoveToPatchMapWithMoveWith,
traversePatchDMapWithMoveWithKey, unPatchDMapWithMove,
unsafePatchDMapWithMove, weakenPatchDMapWithMoveWith)
import Data.Patch.IntMap as X hiding (getDeletions)
import Data.Patch.Map as X
import Data.Patch.MapWithMove as X (PatchMapWithMove, patchMapWithMoveNewElements,
patchMapWithMoveNewElementsMap, unPatchMapWithMove,
unsafePatchMapWithMove)
import Data.Map.Monoidal (MonoidalMap)
import Data.Semigroup (Semigroup (..), (<>))
import GHC.Generics
import Data.Functor.Identity
import Data.Functor.Const
import Data.Proxy
import Control.Applicative
class (Semigroup q, Monoid q) => Group q where
negateG :: q -> q
(~~) :: q -> q -> q
r ~~ s = r <> negateG s
class Semigroup q => Additive q where
newtype AdditivePatch p = AdditivePatch { unAdditivePatch :: p }
instance Additive p => Patch (AdditivePatch p) where
type PatchTarget (AdditivePatch p) = p
apply (AdditivePatch p) q = Just $ p <> q
instance (Ord k, Group q) => Group (MonoidalMap k q) where
negateG = fmap negateG
instance (Ord k, Additive q) => Additive (MonoidalMap k q)
instance Group () where
negateG _ = ()
_ ~~ _ = ()
instance Additive ()
instance (Group a, Group b) => Group (a, b) where
negateG (a, b) = (negateG a, negateG b)
(a, b) ~~ (c, d) = (a ~~ c, b ~~ d)
instance (Additive a, Additive b) => Additive (a, b)
instance Group (f (g a)) => Group ((f :.: g) a) where
negateG (Comp1 xs) = Comp1 (negateG xs)
Comp1 xs ~~ Comp1 ys = Comp1 (xs ~~ ys)
instance Additive (f (g a)) => Additive ((f :.: g) a)
instance (Group (f a), Group (g a)) => Group ((f :*: g) a) where
negateG (a :*: b) = negateG a :*: negateG b
(a :*: b) ~~ (c :*: d) = (a ~~ c) :*: (b ~~ d)
instance (Additive (f a), Additive (g a)) => Additive ((f :*: g) a)
instance Group (Proxy x) where
negateG _ = Proxy
_ ~~ _ = Proxy
instance Additive (Proxy x)
deriving instance Group a => Group (Const a x)
instance Additive a => Additive (Const a x)
deriving instance Group a => Group (Identity a)
instance Additive a => Additive (Identity a)
instance Group b => Group (a -> b) where
negateG f = negateG . f
(~~) = liftA2 (~~)
instance Additive b => Additive (a -> b)