{-# LANGUAGE TypeFamilies #-}
module Reflex.Patch
( module Reflex.Patch
, module X
) where
import Reflex.Patch.Class as X
import Reflex.Patch.DMap as X hiding (getDeletions)
import Reflex.Patch.DMapWithMove as X (PatchDMapWithMove, const2PatchDMapWithMoveWith, mapPatchDMapWithMove,
patchDMapWithMoveToPatchMapWithMoveWith,
traversePatchDMapWithMoveWithKey, unPatchDMapWithMove,
unsafePatchDMapWithMove, weakenPatchDMapWithMoveWith)
import Reflex.Patch.IntMap as X hiding (getDeletions)
import Reflex.Patch.Map as X
import Reflex.Patch.MapWithMove as X (PatchMapWithMove, patchMapWithMoveNewElements,
patchMapWithMoveNewElementsMap, unPatchMapWithMove,
unsafePatchMapWithMove)
import Data.Map.Monoidal (MonoidalMap)
import Data.Semigroup (Semigroup (..), (<>))
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)