{-# LANGUAGE ScopedTypeVariables #-}
module Data.TreeDiff.List (diffBy, Edit (..)) where
import Data.List.Compat (sortOn)
import qualified Data.MemoTrie as M
import qualified Data.Vector as V
data Edit a
= Ins a
| Del a
| Cpy a
| Swp a a
deriving Show
diffBy :: forall a. (a -> a -> Bool) -> [a] -> [a] -> [Edit a]
diffBy eq xs' ys' = reverse (snd (lcs (V.length xs) (V.length ys)))
where
xs = V.fromList xs'
ys = V.fromList ys'
lcs = M.memo2 impl
impl :: Int -> Int -> (Int, [Edit a])
impl 0 0 = (0, [])
impl 0 m = case lcs 0 (m-1) of
(w, edit) -> (w + 1, Ins (ys V.! (m - 1)) : edit)
impl n 0 = case lcs (n -1) 0 of
(w, edit) -> (w + 1, Del (xs V.! (n - 1)) : edit)
impl n m = head $ sortOn fst
[ edit
, bimap (+1) (Ins y :) (lcs n (m - 1))
, bimap (+1) (Del x :) (lcs (n - 1) m)
]
where
x = xs V.! (n - 1)
y = ys V.! (m - 1)
edit
| eq x y = bimap id (Cpy x :) (lcs (n - 1) (m - 1))
| otherwise = bimap (+1) (Swp x y :) (lcs (n -1 ) (m - 1))
bimap :: (a -> c) -> (b -> d) -> (a, b) -> (c, d)
bimap f g (x, y) = (f x, g y)