restructure diff3 a bit
This commit is contained in:
parent
23b62f6344
commit
e19a00b6d8
34
src/Diff3.hs
34
src/Diff3.hs
|
@ -1,15 +1,28 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
|
||||
module Diff3 where
|
||||
module Diff3
|
||||
( diff3Toks
|
||||
) where
|
||||
|
||||
import Diff
|
||||
import Merge
|
||||
import Types
|
||||
|
||||
diff3Toks :: MergeOpts -> TV -> TV -> TV -> Diff
|
||||
diff3Toks mo tMine tOrig tYour =
|
||||
conflict $ align (diffToks tOrig tMine) (diffToks tOrig tYour)
|
||||
stable :: (Origin, a) -> Bool
|
||||
stable (Stable, _) = True
|
||||
stable _ = False
|
||||
|
||||
applySplit :: (a -> Bool) -> ([a] -> [b]) -> ([a] -> [b]) -> [a] -> [b]
|
||||
applySplit cond f g xs = f (takeWhile cond xs) ++ g (dropWhile cond xs)
|
||||
|
||||
conflict :: MergeOpts -> [(Origin, (Op, Tok))] -> [(Op, Tok)]
|
||||
conflict mo = go
|
||||
where
|
||||
go [] = []
|
||||
go as@(a:_)
|
||||
| stable a = applySplit stable (map snd) go as
|
||||
| otherwise = applySplit (not . stable) (merge mo) go as
|
||||
|
||||
align :: Diff -> Diff -> [(Origin, (Op, Tok))]
|
||||
align ((Keep, a):as) ((Keep, _):bs) = (Stable, (Keep, a)) : align as bs
|
||||
align ((Add, a):as) ((Add, b):bs) =
|
||||
|
@ -28,12 +41,7 @@ diff3Toks mo tMine tOrig tYour =
|
|||
align as@((Add, _):_) [] = map (Mine, ) as
|
||||
align [] bs@((Add, _):_) = map (Your, ) bs
|
||||
align _ _ = error "Internal failure: diffstreams seem broken, cannot align"
|
||||
conflict :: [(Origin, (Op, Tok))] -> Diff
|
||||
conflict [] = []
|
||||
conflict as@(a:_)
|
||||
| stable a = applySplit stable (map snd) conflict as
|
||||
| otherwise = applySplit (not . stable) (merge mo) conflict as
|
||||
applySplit :: (a -> Bool) -> ([a] -> [b]) -> ([a] -> [b]) -> [a] -> [b]
|
||||
applySplit cond f g xs = f (takeWhile cond xs) ++ g (dropWhile cond xs)
|
||||
stable (Stable, _) = True
|
||||
stable _ = False
|
||||
|
||||
diff3Toks :: MergeOpts -> TV -> TV -> TV -> Diff
|
||||
diff3Toks mo tMine tOrig tYour =
|
||||
conflict mo $ align (diffToks tOrig tMine) (diffToks tOrig tYour)
|
||||
|
|
Loading…
Reference in a new issue