2015-11-18 00:25:36 +03:00
|
|
|
module Diff where
|
|
|
|
|
2015-11-18 00:35:55 +03:00
|
|
|
import Syntax
|
2015-11-18 00:25:36 +03:00
|
|
|
import Data.Maybe
|
2015-11-18 00:44:27 +03:00
|
|
|
import Data.Map
|
2015-11-18 00:35:52 +03:00
|
|
|
import Control.Monad.Free
|
2015-11-18 01:06:07 +03:00
|
|
|
import Data.Fix
|
2015-11-18 01:07:36 +03:00
|
|
|
import Control.Comonad.Cofree
|
2015-11-18 00:25:36 +03:00
|
|
|
|
|
|
|
data Range = Range { start :: Int, end :: Int }
|
|
|
|
|
2015-11-18 01:17:20 +03:00
|
|
|
data Info = Info -- Range [String]
|
2015-11-18 00:25:36 +03:00
|
|
|
|
2015-11-18 01:17:55 +03:00
|
|
|
type Term a annotation = Cofree (Syntax a) annotation
|
2015-11-18 00:25:36 +03:00
|
|
|
data Patch a = Patch { old :: Maybe a, new :: Maybe a }
|
2015-11-18 01:17:55 +03:00
|
|
|
type Diff a = Free (Syntax a) (Patch (Term a Info))
|
2015-11-18 00:25:36 +03:00
|
|
|
|
2015-11-18 01:17:55 +03:00
|
|
|
(</>) :: Maybe (Term a Info) -> Maybe (Term a Info) -> Diff a
|
2015-11-18 02:09:42 +03:00
|
|
|
(</>) a b = Pure Patch { old = a, new = b }
|
2015-11-18 00:25:36 +03:00
|
|
|
|
2015-11-18 01:17:55 +03:00
|
|
|
a :: Term String Info
|
2015-11-18 02:06:24 +03:00
|
|
|
a = Info :< (Keyed $ fromList [
|
2015-11-18 02:09:42 +03:00
|
|
|
("hello", Info :< Indexed [ Info :< Leaf "hi" ]),
|
|
|
|
("goodbye", Info :< Leaf "goodbye") ])
|
2015-11-18 00:25:36 +03:00
|
|
|
|
2015-11-18 01:17:55 +03:00
|
|
|
b :: Term String Info
|
2015-11-18 02:06:24 +03:00
|
|
|
b = Info :< (Keyed $ fromList [
|
2015-11-18 02:09:42 +03:00
|
|
|
("hello", Info :< Indexed []),
|
|
|
|
("goodbye", Info :< Indexed []) ])
|
2015-11-18 00:25:36 +03:00
|
|
|
|
|
|
|
d :: Diff String
|
2015-11-18 00:44:27 +03:00
|
|
|
d = Free $ Keyed $ fromList [
|
2015-11-18 02:09:42 +03:00
|
|
|
("hello", Free $ Indexed [ Just (Info :< Leaf "hi") </> Nothing ]),
|
|
|
|
("goodbye", Just (Info :< Leaf "goodbye") </> Just (Info :< Indexed [])) ]
|
2015-11-18 00:25:36 +03:00
|
|
|
|
2015-11-18 02:14:57 +03:00
|
|
|
-- type Algorithm a = Free (Operation a)
|
2015-11-18 00:25:36 +03:00
|
|
|
|
|
|
|
cost :: Diff a -> Integer
|
|
|
|
cost f = iter c $ fmap g f where
|
|
|
|
c (Leaf _) = 0
|
2015-11-18 02:09:42 +03:00
|
|
|
c (Keyed xs) = sum $ snd <$> toList xs
|
2015-11-18 00:25:36 +03:00
|
|
|
c (Indexed xs) = sum xs
|
2015-11-18 00:46:23 +03:00
|
|
|
c (Fixed xs) = sum xs
|
2015-11-18 00:25:36 +03:00
|
|
|
g _ = 1
|
|
|
|
|
|
|
|
-- interpret :: Algorithm a b -> b
|
|
|
|
-- interpret (Pure b) = b
|
2015-11-18 00:40:19 +03:00
|
|
|
-- interpret (Free (Recur a b f)) = f $ Pure (Patch { old = Just (In a), new = Just (In b) })
|
2015-11-18 00:25:36 +03:00
|
|
|
|
2015-11-18 00:32:14 +03:00
|
|
|
type RangedTerm a = Cofree (Syntax a) Int
|
|
|
|
-- data Difff a f = Difff (Either (Patch (Term a)) (Syntax a f))
|
2015-11-18 00:25:36 +03:00
|
|
|
-- type RangedDiff a = Cofree (Difff a) Range
|
2015-11-18 00:32:14 +03:00
|
|
|
data AnnotatedSyntax a f = AnnotatedSyntax (Range, Syntax a f)
|
2015-11-18 01:17:55 +03:00
|
|
|
type RangedDiff a = Free (AnnotatedSyntax a) (Patch (Term a Info))
|