module Data.Aeson.Diff (
Patch(..),
Pointer,
Key(..),
Operation(..),
Config(..),
diff,
diff',
patch,
applyOperation,
) where
import Control.Applicative
import Control.Monad
import Control.Monad.Error.Class
import Data.Aeson
import Data.Aeson.Types (modifyFailure, typeMismatch)
import qualified Data.ByteString.Lazy.Char8 as BS
import Data.Foldable (foldlM)
import Data.Hashable
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.List (groupBy, intercalate)
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
import Data.Aeson.Patch
import Data.Aeson.Pointer
newtype Config = Config
{ configTstBeforeRem :: Bool
}
defaultConfig :: Config
defaultConfig = Config False
operationCost :: Operation -> Int
operationCost op =
case op of
Add{} -> valueSize (changeValue op)
Rem{} -> 1
Rep{} -> valueSize (changeValue op)
Mov{} -> 1
Cpy{} -> 1
Tst{} -> valueSize (changeValue op)
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
ins :: Config -> Pointer -> Value -> [Operation]
ins cfg p v = [Add p v]
del :: Config -> Pointer -> Value -> [Operation]
del Config{..} p v =
if configTstBeforeRem
then [Tst p v, Rem p]
else [Rem p]
rep :: Config -> Pointer -> Value -> [Operation]
rep Config{..} p v = [Rep p v]
diff
:: Value
-> Value
-> Patch
diff = diff' defaultConfig
diff'
:: Config
-> Value
-> Value
-> Patch
diff' cfg@Config{..} v v' = Patch (worker mempty v v')
where
check :: Monoid m => Bool -> m -> m
check b v = if b then mempty else v
worker :: Pointer -> Value -> Value -> [Operation]
worker p v1 v2 = case (v1, v2) of
(Null, Null) -> mempty
(Bool b1, Bool b2) -> check (b1 == b2) $ rep cfg p v2
(Number n1, Number n2) -> check (n1 == n2) $ rep cfg p v2
(String s1, String s2) -> check (s1 == s2) $ rep cfg p v2
(Array a1, Array a2) -> check (a1 == a2) $ workArray p a1 a2
(Object o1, Object o2) -> check (o1 == o2) $ workObject p o1 o2
_ -> rep cfg p v2
workObject :: Pointer -> Object -> Object -> [Operation]
workObject path o1 o2 =
let k1 = HM.keys o1
k2 = HM.keys o2
del_keys :: [Text]
del_keys = filter (not . (`elem` k2)) k1
deletions :: [Operation]
deletions = concatMap
(\k -> del cfg (Pointer [OKey k]) (fromJust $ HM.lookup k o1))
del_keys
ins_keys = filter (not . (`elem` k1)) k2
insertions :: [Operation]
insertions = concatMap
(\k -> ins cfg (Pointer [OKey k]) (fromJust $ HM.lookup k o2))
ins_keys
chg_keys = filter (`elem` k2) k1
changes :: [Operation]
changes = concatMap
(\k -> worker (Pointer [OKey k])
(fromJust $ HM.lookup k o1)
(fromJust $ HM.lookup k o2))
chg_keys
in modifyPointer (path <>) <$> (deletions <> insertions <> changes)
workArray :: Pointer -> Array -> Array -> [Operation]
workArray path ss tt = fmap (modifyPointer (path <>)) . snd . fmap concat $ leastChanges params ss tt
where
params :: Params Value [Operation] (Sum Int)
params = Params{..}
equivalent = (==)
delete i = del cfg (Pointer [AKey i])
insert i = ins cfg (Pointer [AKey i])
substitute i = worker (Pointer [AKey i])
cost = Sum . sum . fmap operationCost
positionOffset = sum . fmap adv . groupBy related
related :: Operation -> Operation -> Bool
related o1 o2 =
let p1 = pointerPath (changePointer o1)
p2 = pointerPath (changePointer o2)
in case (p1, p2) of
([i1], [i2]) -> False
(i1:_, i2:_) | i1 == i2 -> True
| otherwise -> False
adv :: [Operation] -> Int
adv [op]
| (length . pointerPath . changePointer $ op) == 1 = pos op
adv _ = 1
pos :: Operation -> Int
pos Rem{changePointer=Pointer path}
| length path == 1 = 0
| otherwise = 0
pos Add{changePointer=Pointer path}
| length path == 1 = 1
| otherwise = 0
pos Rep{changePointer=Pointer path}
| length path == 1 = 1
| otherwise = 0
pos Cpy{changePointer=Pointer path}
| length path == 1 = 1
| otherwise = 0
pos Mov{changePointer=Pointer path}
| length path == 1 = 1
| otherwise = 0
pos Tst{changePointer=Pointer path} = 0
patch
:: Patch
-> Value
-> Result Value
patch (Patch []) val = return val
patch (Patch ops) val = foldlM (flip applyOperation) val ops
applyOperation
:: Operation
-> Value
-> Result Value
applyOperation op json = case op of
Add path v' -> applyAdd path v' json
Rem path -> applyRem path json
Rep path v' -> applyRep path v' json
Tst path v -> applyTst path v json
Cpy path from -> applyCpy path from json
Mov path from -> do
v' <- get from json
applyRem from json >>= applyAdd path v'
applyAdd :: Pointer -> Value -> Value -> Result Value
applyAdd pointer = go pointer
where
go (Pointer []) val _ =
return val
go (Pointer [AKey i]) v' (Array v) =
let fn :: Maybe Value -> Result (Maybe Value)
fn _ = return (Just v')
in return (Array $ vInsert i v' v)
go (Pointer (AKey i : path)) v' (Array v) =
let fn :: Maybe Value -> Result (Maybe Value)
fn Nothing = cannot "insert" "array" i pointer
fn (Just d) = Just <$> go (Pointer path) v' d
in Array <$> vModify i fn v
go (Pointer [OKey n]) v' (Object m) =
return . Object $ HM.insert n v' m
go (Pointer (OKey n : path)) v' (Object o) =
let fn :: Maybe Value -> Result (Maybe Value)
fn Nothing = cannot "insert" "object" n pointer
fn (Just d) = Just <$> go (Pointer path) v' d
in Object <$> hmModify n fn o
go (Pointer (OKey n : path)) v' array@(Array v)
| n == "-" = go (Pointer (AKey (V.length v) : path)) v' array
go path _ v = pointerFailure path v
applyRem :: Pointer -> Value -> Result Value
applyRem from@(Pointer path) = go path
where
go [] _ = return Null
go [AKey i] d@(Array v) =
let fn :: Maybe Value -> Result (Maybe Value)
fn Nothing = cannot "delete" "array" i from
fn (Just v) = return Nothing
in Array <$> vModify i fn v
go (AKey i : path) (Array v) =
let fn :: Maybe Value -> Result (Maybe Value)
fn Nothing = cannot "traverse" "array" i from
fn (Just o) = Just <$> go path o
in Array <$> vModify i fn v
go [OKey n] (Object m) =
let fn :: Maybe Value -> Result (Maybe Value)
fn Nothing = cannot "delete" "object" n from
fn (Just _) = return Nothing
in Object <$> hmModify n fn m
go (OKey n : path) (Object m) =
let fn :: Maybe Value -> Result (Maybe Value)
fn Nothing = cannot "traverse" "object" n from
fn (Just o) = Just <$> go path o
in Object <$> hmModify n fn m
go (OKey n : path) array@(Array v)
| n == "-" = go (AKey (V.length v) : path) array
go path value = pointerFailure from value
applyRep :: Pointer -> Value -> Value -> Result Value
applyRep from v doc = applyRem from doc >>= applyAdd from v
applyMov :: Pointer -> Pointer -> Value -> Result Value
applyMov path from doc = do
v <- get from doc
applyRem from doc >>= applyAdd path v
applyCpy :: Pointer -> Pointer -> Value -> Result Value
applyCpy path from doc = do
v <- get from doc
applyAdd path v doc
applyTst :: Pointer -> Value -> Value -> Result Value
applyTst path v doc = do
v' <- get path doc
unless (v == v') (Error . T.unpack $ "Element at \"" <> formatPointer path <> "\" fails test.")
return doc
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 -> Result (Maybe a))
-> Vector a
-> Result (Vector a)
vModify i f v =
let a = v V.!? i
a' = f a
in case (a, a') of
(Nothing, Success Nothing ) -> return v
(Just _ , Success Nothing ) -> return (vDelete i v)
(Nothing, Success (Just n)) -> return (vInsert i n v)
(Just _ , Success (Just n)) -> return (V.update v (V.singleton (i, n)))
(_ , Error e ) -> Error e
hmModify
:: (Eq k, Hashable k)
=> k
-> (Maybe v -> Result (Maybe v))
-> HashMap k v
-> Result (HashMap k v)
hmModify k f m = case f (HM.lookup k m) of
Error e -> Error e
Success Nothing -> return $ HM.delete k m
Success (Just v) -> return $ HM.insert k v m
cannot
:: (Show ix)
=> String
-> String
-> ix
-> Pointer
-> Result a
cannot op ty ix p =
Error ("Cannot " <> op <> " missing " <> ty <> " member at index "
<> show ix <> " in pointer \"" <> T.unpack (formatPointer p) <> "\".")