module Data.Aeson.Diff (
Patch(..),
Path,
Key(..),
Operation(..),
diff,
patch,
applyOperation,
formatPatch,
) where
import Control.Applicative
import Control.Monad
import Control.Monad.Error.Class
import Data.Aeson
import Data.Hashable
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.Maybe
import Data.Monoid
import Data.Scientific
import Data.Text (Text)
import qualified Data.Text as T
import Data.Vector (Vector)
import qualified Data.Vector as V
import Data.Vector.Distance
data Patch = Patch
{ patchOperations :: [Operation] }
deriving (Eq)
instance Show Patch where
show = T.unpack . formatPatch
instance Monoid Patch where
mempty = Patch []
mappend (Patch p1) (Patch p2) = Patch $ p1 <> p2
instance ToJSON Patch where
toJSON (Patch ops) = object [ "patch" .= ops ]
instance FromJSON Patch where
parseJSON (Object v) = Patch <$> v .: "patch"
parseJSON _ = fail "Patch must be a JSON object."
instance ToJSON Operation where
toJSON (Ins p v) = object
[ ("change", "insert")
, "path" .= p
, "value" .= v
]
toJSON (Del p v) = object
[ ("change", "delete")
, "path" .= p
, "value" .= v
]
instance FromJSON Operation where
parseJSON (Object v)
= (fixed v "change" (String "insert") *>
(Ins <$> v .: "path" <*> v .: "value"))
<> (fixed v "change" (String "delete") *>
(Del <$> v .: "path" <*> v .: "value"))
where
fixed o n val = do
v' <- o .: n
unless (v' == val) . fail . T.unpack $ "Cannot find " <> n <> "."
return v'
parseJSON _ = fail "Operation must be a JSON object."
data Operation
= Ins { changePath :: Path, changeValue :: Value }
| Del { changePath :: Path, changeValue :: Value }
deriving (Eq, Show)
type Path = [Key]
data Key
= OKey Text
| AKey Int
deriving (Eq, Ord, Show)
instance ToJSON Key where
toJSON (OKey t) = String t
toJSON (AKey a) = Number . fromInteger . toInteger $ a
instance FromJSON Key where
parseJSON (String t) = return $ OKey t
parseJSON (Number n) =
case toBoundedInteger n of
Nothing -> fail "A numeric key must be a positive whole number."
Just n' -> return $ AKey n'
parseJSON _ = fail "A key element must be a number or a string."
modifyPath :: (Path -> Path) -> Operation -> Operation
modifyPath path op = op { changePath = path (changePath op) }
ins :: Path -> Value -> Patch
ins p v = Patch [Ins p v]
del :: Path -> Value -> Patch
del p v = Patch [Del p v]
ch :: Path -> Value -> Value -> Patch
ch p v1 v2 = del p v1 <> ins p v2
diff
:: Value
-> Value
-> Patch
diff = worker []
where
check :: Monoid m => Bool -> m -> m
check b v = if b then mempty else v
worker :: Path -> Value -> Value -> Patch
worker p v1 v2 = case (v1, v2) of
(Null, Null) -> mempty
(Bool b1, Bool b2) -> check (b1 == b2) $ ch p v1 v2
(Number n1, Number n2) -> check (n1 == n2) $ ch p v1 v2
(String s1, String s2) -> check (s1 == s2) $ ch p v1 v2
(Array a1, Array a2) -> check (a1 == a2) $ workArray p a1 a2
(Object o1, Object o2) -> check (o1 == o2) $ workObject p o1 o2
_ -> del p v1 <> ins p v2
workObject :: Path -> Object -> Object -> Patch
workObject p o1 o2 =
let k1 = HM.keys o1
k2 = HM.keys o2
del_keys = filter (not . (`elem` k2)) k1
deletions = Patch $ fmap
(\k -> Del (p <> [OKey k]) . fromJust $ HM.lookup k o1)
del_keys
ins_keys = filter (not . (`elem` k1)) k2
insertions = Patch $ fmap
(\k -> Ins (p <> [OKey k]) . fromJust $ HM.lookup k o2)
ins_keys
chg_keys = filter (`elem` k2) k1
changes = fmap
(\k -> worker (p <> [OKey k])
(fromJust $ HM.lookup k o1)
(fromJust $ HM.lookup k o2))
chg_keys
in deletions <> insertions <> mconcat changes
workArray :: Path -> Array -> Array -> Patch
workArray path ss tt = Patch . snd . fmap concat $ leastChanges params ss tt
where
params :: Params Value [Operation] (Sum Int)
params = Params{..}
equivalent = (==)
delete i v = [Del (path <> [AKey i]) v]
insert i v = [Ins (path <> [AKey i]) v]
substitute i v v' =
let p = path <> [AKey i]
Patch ops = diff v v'
in fmap (modifyPath (p <>)) ops
cost = Sum . sum . fmap (valueSize . changeValue)
positionOffset = sum . fmap pos
pos Del{} = 0
pos Ins{} = 1
patch
:: Patch
-> Value
-> Value
patch (Patch []) val = val
patch (Patch ops) val = foldl (flip applyOperation) val ops
applyOperation
:: Operation
-> Value
-> Value
applyOperation op j = case op of
Ins path v' -> insert path v' j
Del path v' -> delete path v' j
where
insert :: Path -> Value -> Value -> Value
insert [] v' _ = v'
insert [AKey i] v' (Array v) = Array $ vInsert i v' v
insert [OKey n] v' (Object m) = Object $ HM.insert n v' m
insert (AKey i : path) v' (Array v) = Array $ vModify i
(Just . insert path v' . fromMaybe (Array mempty)) v
insert (OKey n : path) v' (Object m) = Object $ hmModify n
(Just . insert path v' . fromMaybe (Object mempty)) m
insert (AKey _ : path) v' v = Array $ V.singleton (insert path v' v)
insert (OKey n : path) v' v = Object $ HM.singleton n (insert path v' v)
delete :: Path -> Value -> Value -> Value
delete [AKey i] _v' (Array v) = Array $ vDelete i v
delete [OKey n] _v' (Object m) = Object $ HM.delete n m
delete (AKey i : rest) v' (Array v) = Array $ vModify i
(fmap (delete rest v')) v
delete (OKey n : rest) v' (Object m) = Object $ hmModify n
(fmap (delete rest v')) m
delete _ _v' v = v
formatPatch
:: Patch
-> Text
formatPatch (Patch ops) = T.unlines $ fmap formatOp ops
where
formatKey (OKey t) = "." <> t
formatKey (AKey i) = "[" <> (T.pack . show $ i) <> "]"
formatPath :: [Key] -> Text
formatPath p = "@" <> (T.concat . fmap formatKey $ p)
formatOp :: Operation -> Text
formatValue :: Value -> Text
formatValue v = case v of
String t -> t
Number s -> T.pack . show $ s
Bool b -> T.pack . show $ b
Null -> "Null"
_ -> ":-("
formatOp (Ins k v) = formatPath k <> "\n" <> "+" <> formatValue v
formatOp (Del k v) = formatPath k <> "\n" <> "-" <> formatValue v
parsePatch :: Text -> Either Text Patch
parsePatch _t = throwError "Cannot parse"
valueSize :: Value -> Int
valueSize val = case val of
Object o -> sum . fmap valueSize . HM.elems $ o
Array a -> V.sum $ V.map valueSize a
_ -> 1
vDelete :: Int -> Vector a -> Vector a
vDelete i v =
let l = V.length v
in V.slice 0 i v <> V.slice (i + 1) (l i 1) v
vInsert :: Int -> a -> Vector a -> Vector a
vInsert i a v
| i <= 0 = V.cons a v
| V.length v <= i = V.snoc v a
| otherwise = V.slice 0 i v
<> V.singleton a
<> V.slice i (V.length v i) v
vModify :: Int -> (Maybe a -> Maybe a) -> Vector a -> Vector a
vModify i f v =
let a = v V.!? i
a' = f a
in case (a, a') of
(Nothing, Nothing) -> v
(Just _, Nothing) -> vDelete i v
(Nothing, Just n ) -> vInsert i n v
(Just _, Just n ) -> V.update v (V.singleton (i, n))
hmModify
:: (Eq k, Hashable k)
=> k
-> (Maybe v -> Maybe v)
-> HashMap k v
-> HashMap k v
hmModify k f m = case f (HM.lookup k m) of
Nothing -> HM.delete k m
Just v -> HM.insert k v m