mirror of
https://github.com/github/semantic.git
synced 2024-12-26 00:12:29 +03:00
Parameterize SES by the cost function.
This commit is contained in:
parent
aabc5f62ee
commit
eeaa77812c
@ -36,7 +36,7 @@ run (Free (ByKey a b f)) = run $ f byKey where
|
||||
inserted = (Pure . Insert) <$> difference b a
|
||||
patched = intersectionWith interpret a b
|
||||
|
||||
run (Free (ByIndex a b f)) = run . f $ ses constructAndRun a b
|
||||
run (Free (ByIndex a b f)) = run . f $ ses constructAndRun cost a b
|
||||
|
||||
interpret :: Term a Info -> Term a Info -> Diff a
|
||||
interpret a b = maybeReplace $ constructAndRun a b where
|
||||
|
27
src/SES.hs
27
src/SES.hs
@ -1,4 +1,4 @@
|
||||
module SES (ses, Compare) where
|
||||
module SES where
|
||||
|
||||
import Patch
|
||||
import Diff
|
||||
@ -6,24 +6,23 @@ import Control.Monad.Free
|
||||
import Control.Comonad.Cofree
|
||||
|
||||
type Compare a = Term a Info -> Term a Info -> Maybe (Diff a)
|
||||
type Cost a = Diff a -> Integer
|
||||
|
||||
ses :: Compare a -> [Term a Info] -> [Term a Info] -> [Diff a]
|
||||
ses _ [] b = (Pure . Insert) <$> b
|
||||
ses _ a [] = (Pure . Delete) <$> a
|
||||
ses recur (a : as) (b : bs) = case recur a b of
|
||||
ses :: Compare a -> Cost a -> [Term a Info] -> [Term a Info] -> [Diff a]
|
||||
ses _ _ [] b = (Pure . Insert) <$> b
|
||||
ses _ _ a [] = (Pure . Delete) <$> a
|
||||
ses recur cost (a : as) (b : bs) = case recur a b of
|
||||
Just f | deleteCost < insertCost && deleteCost < copyCost -> delete
|
||||
| insertCost < copyCost -> insert
|
||||
| otherwise -> copy
|
||||
where
|
||||
copy = f : ses recur as bs
|
||||
copyCost = SES.cost copy
|
||||
copy = f : ses recur cost as bs
|
||||
copyCost = sumCost copy
|
||||
Nothing | deleteCost < insertCost -> delete
|
||||
| otherwise -> insert
|
||||
where
|
||||
delete = (Pure . Delete $ a) : ses recur as (b : bs)
|
||||
insert = (Pure . Insert $ b) : ses recur (a : as) bs
|
||||
deleteCost = SES.cost delete
|
||||
insertCost = SES.cost insert
|
||||
|
||||
cost :: [Diff a] -> Integer
|
||||
cost as = sum $ Diff.cost <$> as
|
||||
delete = (Pure . Delete $ a) : ses recur cost as (b : bs)
|
||||
insert = (Pure . Insert $ b) : ses recur cost (a : as) bs
|
||||
deleteCost = sumCost delete
|
||||
insertCost = sumCost insert
|
||||
sumCost a = sum $ cost <$> a
|
||||
|
Loading…
Reference in New Issue
Block a user