{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Patch.MapWithMove where
import Data.Patch.Class
import Control.Arrow
import Control.Lens hiding (from, to)
import Control.Monad.Trans.State
import Data.Foldable
import Data.Function
import Data.List
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
import Data.Semigroup (Semigroup (..), (<>))
import qualified Data.Set as Set
import Data.These (These(..))
import Data.Tuple
newtype PatchMapWithMove k v = PatchMapWithMove
{
unPatchMapWithMove :: Map k (NodeInfo k v)
}
deriving ( Show, Read, Eq, Ord
, Functor, Foldable, Traversable
)
data NodeInfo k v = NodeInfo
{ _nodeInfo_from :: !(From k v)
, _nodeInfo_to :: !(To k)
}
deriving (Show, Read, Eq, Ord, Functor, Foldable, Traversable)
data From k v
= From_Insert v
| From_Delete
| From_Move !k
deriving (Show, Read, Eq, Ord, Functor, Foldable, Traversable)
type To = Maybe
makeWrapped ''PatchMapWithMove
instance FunctorWithIndex k (PatchMapWithMove k)
instance FoldableWithIndex k (PatchMapWithMove k)
instance TraversableWithIndex k (PatchMapWithMove k) where
itraverse = itraversed . Indexed
itraversed = _Wrapped .> itraversed <. traversed
patchMapWithMove :: Ord k => Map k (NodeInfo k v) -> Maybe (PatchMapWithMove k v)
patchMapWithMove m = if valid then Just $ PatchMapWithMove m else Nothing
where valid = forwardLinks == backwardLinks
forwardLinks = Map.mapMaybe _nodeInfo_to m
backwardLinks = Map.fromList $ catMaybes $ flip fmap (Map.toList m) $ \(to, v) ->
case _nodeInfo_from v of
From_Move from -> Just (from, to)
_ -> Nothing
patchMapWithMoveInsertAll :: Map k v -> PatchMapWithMove k v
patchMapWithMoveInsertAll m = PatchMapWithMove $ flip fmap m $ \v -> NodeInfo
{ _nodeInfo_from = From_Insert v
, _nodeInfo_to = Nothing
}
insertMapKey :: k -> v -> PatchMapWithMove k v
insertMapKey k v = PatchMapWithMove . Map.singleton k $ NodeInfo (From_Insert v) Nothing
moveMapKey :: Ord k => k -> k -> PatchMapWithMove k v
moveMapKey src dst
| src == dst = mempty
| otherwise =
PatchMapWithMove $ Map.fromList
[ (dst, NodeInfo (From_Move src) Nothing)
, (src, NodeInfo From_Delete (Just dst))
]
swapMapKey :: Ord k => k -> k -> PatchMapWithMove k v
swapMapKey src dst
| src == dst = mempty
| otherwise =
PatchMapWithMove $ Map.fromList
[ (dst, NodeInfo (From_Move src) (Just src))
, (src, NodeInfo (From_Move dst) (Just dst))
]
deleteMapKey :: k -> PatchMapWithMove k v
deleteMapKey k = PatchMapWithMove . Map.singleton k $ NodeInfo From_Delete Nothing
unsafePatchMapWithMove :: Map k (NodeInfo k v) -> PatchMapWithMove k v
unsafePatchMapWithMove = PatchMapWithMove
instance Ord k => Patch (PatchMapWithMove k v) where
type PatchTarget (PatchMapWithMove k v) = Map k v
apply (PatchMapWithMove p) old = Just $! insertions `Map.union` (old `Map.difference` deletions)
where insertions = flip Map.mapMaybeWithKey p $ \_ ni -> case _nodeInfo_from ni of
From_Insert v -> Just v
From_Move k -> Map.lookup k old
From_Delete -> Nothing
deletions = flip Map.mapMaybeWithKey p $ \_ ni -> case _nodeInfo_from ni of
From_Delete -> Just ()
_ -> Nothing
patchMapWithMoveNewElements :: PatchMapWithMove k v -> [v]
patchMapWithMoveNewElements = Map.elems . patchMapWithMoveNewElementsMap
patchMapWithMoveNewElementsMap :: PatchMapWithMove k v -> Map k v
patchMapWithMoveNewElementsMap (PatchMapWithMove p) = Map.mapMaybe f p
where f ni = case _nodeInfo_from ni of
From_Insert v -> Just v
From_Move _ -> Nothing
From_Delete -> Nothing
patchThatSortsMapWith :: Ord k => (v -> v -> Ordering) -> Map k v -> PatchMapWithMove k v
patchThatSortsMapWith cmp m = PatchMapWithMove $ Map.fromList $ catMaybes $ zipWith g unsorted sorted
where unsorted = Map.toList m
sorted = sortBy (cmp `on` snd) unsorted
f (to, _) (from, _) = if to == from then Nothing else
Just (from, to)
reverseMapping = Map.fromList $ catMaybes $ zipWith f unsorted sorted
g (to, _) (from, _) = if to == from then Nothing else
let Just movingTo = Map.lookup to reverseMapping
in Just (to, NodeInfo (From_Move from) $ Just movingTo)
patchThatChangesAndSortsMapWith :: forall k v. (Ord k, Ord v) => (v -> v -> Ordering) -> Map k v -> Map k v -> PatchMapWithMove k v
patchThatChangesAndSortsMapWith cmp oldByIndex newByIndexUnsorted = patchThatChangesMap oldByIndex newByIndex
where newList = Map.toList newByIndexUnsorted
newByIndex = Map.fromList $ zip (fst <$> newList) $ sortBy cmp $ snd <$> newList
patchThatChangesMap :: (Ord k, Ord v) => Map k v -> Map k v -> PatchMapWithMove k v
patchThatChangesMap oldByIndex newByIndex = patch
where oldByValue = Map.fromListWith Set.union $ swap . first Set.singleton <$> Map.toList oldByIndex
(insertsAndMoves, unusedValuesByValue) = flip runState oldByValue $ do
let f k v = do
remainingValues <- get
let putRemainingKeys remainingKeys = put $ if Set.null remainingKeys
then Map.delete v remainingValues
else Map.insert v remainingKeys remainingValues
case Map.lookup v remainingValues of
Nothing -> return $ NodeInfo (From_Insert v) $ Just undefined
Just fromKs ->
if k `Set.member` fromKs
then do
putRemainingKeys $ Set.delete k fromKs
return $ NodeInfo (From_Move k) $ Just undefined
else do
(fromK, remainingKeys) <- return . fromJust $ Set.minView fromKs
putRemainingKeys remainingKeys
return $ NodeInfo (From_Move fromK) $ Just undefined
Map.traverseWithKey f newByIndex
unusedOldKeys = fold unusedValuesByValue
pointlessMove k = \case
From_Move k' | k == k' -> True
_ -> False
keyWasMoved k = if k `Map.member` oldByIndex && not (k `Set.member` unusedOldKeys)
then Just undefined
else Nothing
patch = unsafePatchMapWithMove $ Map.filterWithKey (\k -> not . pointlessMove k . _nodeInfo_from) $ Map.mergeWithKey (\k a _ -> Just $ nodeInfoSetTo (keyWasMoved k) a) (Map.mapWithKey $ \k -> nodeInfoSetTo $ keyWasMoved k) (Map.mapWithKey $ \k _ -> NodeInfo From_Delete $ keyWasMoved k) insertsAndMoves oldByIndex
nodeInfoMapFrom :: (From k v -> From k v) -> NodeInfo k v -> NodeInfo k v
nodeInfoMapFrom f ni = ni { _nodeInfo_from = f $ _nodeInfo_from ni }
nodeInfoMapMFrom :: Functor f => (From k v -> f (From k v)) -> NodeInfo k v -> f (NodeInfo k v)
nodeInfoMapMFrom f ni = fmap (\result -> ni { _nodeInfo_from = result }) $ f $ _nodeInfo_from ni
nodeInfoSetTo :: To k -> NodeInfo k v -> NodeInfo k v
nodeInfoSetTo to ni = ni { _nodeInfo_to = to }
data Fixup k v
= Fixup_Delete
| Fixup_Update (These (From k v) (To k))
instance Ord k => Semigroup (PatchMapWithMove k v) where
PatchMapWithMove ma <> PatchMapWithMove mb = PatchMapWithMove m
where
connections = Map.toList $ Map.intersectionWithKey (\_ a b -> (_nodeInfo_to a, _nodeInfo_from b)) ma mb
h :: (k, (Maybe k, From k v)) -> [(k, Fixup k v)]
h (_, (mToAfter, editBefore)) = case (mToAfter, editBefore) of
(Just toAfter, From_Move fromBefore)
| fromBefore == toAfter
-> [(toAfter, Fixup_Delete)]
| otherwise
-> [ (toAfter, Fixup_Update (This editBefore))
, (fromBefore, Fixup_Update (That mToAfter))
]
(Nothing, From_Move fromBefore) -> [(fromBefore, Fixup_Update (That mToAfter))]
(Just toAfter, _) -> [(toAfter, Fixup_Update (This editBefore))]
(Nothing, _) -> []
mergeFixups _ Fixup_Delete Fixup_Delete = Fixup_Delete
mergeFixups _ (Fixup_Update a) (Fixup_Update b)
| This x <- a, That y <- b
= Fixup_Update $ These x y
| That y <- a, This x <- b
= Fixup_Update $ These x y
mergeFixups _ _ _ = error "PatchMapWithMove: incompatible fixups"
fixups = Map.fromListWithKey mergeFixups $ concatMap h connections
combineNodeInfos _ nia nib = NodeInfo
{ _nodeInfo_from = _nodeInfo_from nia
, _nodeInfo_to = _nodeInfo_to nib
}
applyFixup _ ni = \case
Fixup_Delete -> Nothing
Fixup_Update u -> Just $ NodeInfo
{ _nodeInfo_from = fromMaybe (_nodeInfo_from ni) $ getHere u
, _nodeInfo_to = fromMaybe (_nodeInfo_to ni) $ getThere u
}
m = Map.differenceWithKey applyFixup (Map.unionWithKey combineNodeInfos ma mb) fixups
getHere :: These a b -> Maybe a
getHere = \case
This a -> Just a
These a _ -> Just a
That _ -> Nothing
getThere :: These a b -> Maybe b
getThere = \case
This _ -> Nothing
These _ b -> Just b
That b -> Just b
instance Ord k => Monoid (PatchMapWithMove k v) where
mempty = PatchMapWithMove mempty
mappend = (<>)