merging merges
This commit is contained in:
		
							parent
							
								
									8f4f4434b6
								
							
						
					
					
						commit
						114a333982
					
				|  | @ -46,6 +46,7 @@ executable adiff | ||||||
|   other-modules: Diff, |   other-modules: Diff, | ||||||
|                  Diff3, |                  Diff3, | ||||||
|                  Format, |                  Format, | ||||||
|  |                  Hunks, | ||||||
|                  Merge, |                  Merge, | ||||||
|                  Patch, |                  Patch, | ||||||
|                  Redfa, |                  Redfa, | ||||||
|  |  | ||||||
							
								
								
									
										31
									
								
								src/Diff.hs
									
									
									
									
									
								
							
							
						
						
									
										31
									
								
								src/Diff.hs
									
									
									
									
									
								
							|  | @ -1,8 +1,5 @@ | ||||||
| module Diff | module Diff | ||||||
|   ( Tok |   ( diffToks | ||||||
|   , Op |  | ||||||
|   , diffToks |  | ||||||
|   , hunks |  | ||||||
|   ) where |   ) where | ||||||
| 
 | 
 | ||||||
| import Control.Monad | import Control.Monad | ||||||
|  | @ -259,29 +256,3 @@ diffToks' de@DiffEnv {deS = s, deE = e, deA = a, deB = b, deTrans = trans} = | ||||||
|       | otherwise = |       | otherwise = | ||||||
|         diffToks' de {deE = mid, deVE = vecEmid, deB = opt} ++ |         diffToks' de {deE = mid, deVE = vecEmid, deB = opt} ++ | ||||||
|         diffToks' de {deS = mid, deVS = vecSmid, deA = opt} |         diffToks' de {deS = mid, deVS = vecSmid, deA = opt} | ||||||
| 
 |  | ||||||
| hunks :: Int -> Diff -> [Hunk] |  | ||||||
| hunks ctxt d = |  | ||||||
|   map (stripNums . map snd) . |  | ||||||
|   filter (not . null) . split fst . zip remove . addNums $ |  | ||||||
|   d |  | ||||||
|   where |  | ||||||
|     edit (Keep, _) = 0 |  | ||||||
|     edit _ = 1 |  | ||||||
|     edits :: [Int] |  | ||||||
|     edits = tail $ scanl (+) 0 (map edit d) |  | ||||||
|     padEnd _ [] = [] |  | ||||||
|     padEnd i [a] = replicate i a |  | ||||||
|     padEnd i (x:xs) = x : padEnd i xs |  | ||||||
|     remove = |  | ||||||
|       drop ctxt $ |  | ||||||
|       zipWith (<=) (padEnd ctxt edits) (replicate (1 + 2 * ctxt) 0 ++ edits) |  | ||||||
|     addNums = snd . mapAccumL countTok (0, 0) |  | ||||||
|     stripNums = (,) <$> fst . head <*> map snd |  | ||||||
|     countTok x@(i, j) d@(op, _) = |  | ||||||
|       (,) |  | ||||||
|         (case op of |  | ||||||
|            Remove -> (i + 1, j) |  | ||||||
|            Keep -> (i + 1, j + 1) |  | ||||||
|            Add -> (i, j + 1)) |  | ||||||
|         (x, d) |  | ||||||
|  |  | ||||||
							
								
								
									
										53
									
								
								src/Diff3.hs
									
									
									
									
									
								
							
							
						
						
									
										53
									
								
								src/Diff3.hs
									
									
									
									
									
								
							|  | @ -1,7 +1,54 @@ | ||||||
| 
 |  | ||||||
| module Diff3 where | module Diff3 where | ||||||
| 
 | 
 | ||||||
|  | import Diff | ||||||
| import Types | import Types | ||||||
| 
 | 
 | ||||||
| diff3Toks :: BS -> BS -> BS -> TV -> TV -> TV -> a | data Origin | ||||||
| diff3Toks = undefined |   = Stable | ||||||
|  |   | Mine | ||||||
|  |   | Your | ||||||
|  |   deriving (Show, Eq) | ||||||
|  | 
 | ||||||
|  | --diff3Toks :: TV -> TV -> TV -> Diff | ||||||
|  | diff3Toks tMine tOrig tYour = | ||||||
|  |   conflict $ align (diffToks tOrig tMine) (diffToks tOrig tYour) | ||||||
|  |   where | ||||||
|  |     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) = | ||||||
|  |       (Mine, (Add, a)) : (Your, (Add, b)) : align as bs | ||||||
|  |     align ((Remove, a):as) ((Remove, b):bs) = | ||||||
|  |       (Mine, (Remove, a)) : (Your, (Remove, b)) : align as bs | ||||||
|  |     align ((Add, a):as) bs@((Keep, _):_) = (Mine, (Add, a)) : align as bs | ||||||
|  |     align as@((Keep, _):_) ((Add, b):bs) = (Your, (Add, b)) : align as bs | ||||||
|  |     align ((Remove, a):as) ((Keep, b):bs) = | ||||||
|  |       (Mine, (Remove, a)) : (Your, (Keep, b)) : align as bs | ||||||
|  |     align ((Keep, a):as) ((Remove, b):bs) = | ||||||
|  |       (Mine, (Keep, a)) : (Your, (Remove, b)) : align as bs | ||||||
|  |     align ((Add, a):as) bs@((Remove, _):_) = (Mine, (Add, a)) : align as bs | ||||||
|  |     align as@((Remove, _):_) ((Add, b):bs) = (Your, (Add, b)) : align as bs | ||||||
|  |     align [] [] = [] | ||||||
|  |     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 | ||||||
|  |       | unstable a = applySplit unstable merge conflict as | ||||||
|  |     applySplit :: (a -> Bool) -> ([a] -> [b]) -> ([a] -> [b]) -> [a] -> [b] | ||||||
|  |     applySplit cond f g xs = f (takeWhile cond xs) ++ g (dropWhile cond xs) | ||||||
|  |     merge :: [(Origin, (Op,Tok))] -> Diff | ||||||
|  |     merge cs = | ||||||
|  |       let mys = map (\a -> map snd $ filter ((== a) . fst) cs) [Mine, Your] | ||||||
|  |           [tokOrigsMine, tokOrigsYour] = | ||||||
|  |             map (map snd.filter ((/= Add) . fst)) mys | ||||||
|  |           [tokMine, tokYour] = map (map snd.filter ((/= Remove) . fst)) mys | ||||||
|  |        in if tokOrigsMine /= tokOrigsYour | ||||||
|  |             then error "Internal failure: merge origins differ" | ||||||
|  |             else map ((,) MineChanged) tokMine ++ | ||||||
|  |                  map ((,) Original) tokOrigsMine ++ | ||||||
|  |                  map ((,) YourChanged) tokYour | ||||||
|  |     stable (Stable, _) = True | ||||||
|  |     stable _ = False | ||||||
|  |     unstable = not . stable | ||||||
|  |  | ||||||
|  | @ -24,14 +24,15 @@ pprHunk ((i, j), toks) = B.concat ((pprHunkHdr i j <> lineSep) : map pprDiff1 to | ||||||
| pprDiff1 (op, (tok, s)) = | pprDiff1 (op, (tok, s)) = | ||||||
|   fromString pfx <> escNewlines s <> lineSep |   fromString pfx <> escNewlines s <> lineSep | ||||||
|   where |   where | ||||||
|     pfx = |     pfx = opc:tc:[] | ||||||
|       case (op, tok) of |     opc = case op of | ||||||
|         (Add, True) -> "+|" |       Add -> '+' | ||||||
|         (Remove, True) -> "-|" |       Keep -> ' ' | ||||||
|         (Keep, True) -> " |" |       Remove -> '-' | ||||||
|         (Add, False) -> "+." |       MineChanged -> '<' | ||||||
|         (Remove, False) -> "-." |       Original -> '=' | ||||||
|         (Keep, False) -> " ." |       YourChanged -> '>' | ||||||
|  |     tc = if tok then '|' else '.' | ||||||
| 
 | 
 | ||||||
| escNewlines = BL.toStrict . BB.toLazyByteString . escNewlines' | escNewlines = BL.toStrict . BB.toLazyByteString . escNewlines' | ||||||
| 
 | 
 | ||||||
|  |  | ||||||
							
								
								
									
										33
									
								
								src/Hunks.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										33
									
								
								src/Hunks.hs
									
									
									
									
									
										Normal file
									
								
							|  | @ -0,0 +1,33 @@ | ||||||
|  | module Hunks where | ||||||
|  | 
 | ||||||
|  | import Data.List.Extra | ||||||
|  | import Types | ||||||
|  | 
 | ||||||
|  | hunks :: Int -> Diff -> [Hunk] | ||||||
|  | hunks ctxt d = | ||||||
|  |   map (stripNums . map snd) . | ||||||
|  |   filter (not . null) . split fst . zip remove . addNums $ | ||||||
|  |   d | ||||||
|  |   where | ||||||
|  |     edit (Keep, _) = 0 | ||||||
|  |     edit _ = 1 | ||||||
|  |     edits :: [Int] | ||||||
|  |     edits = tail $ scanl (+) 0 (map edit d) | ||||||
|  |     padEnd _ [] = [] | ||||||
|  |     padEnd i [a] = a : replicate i a | ||||||
|  |     padEnd i (x:xs) = x : padEnd i xs | ||||||
|  |     remove = | ||||||
|  |       drop ctxt $ | ||||||
|  |       zipWith (<=) (padEnd ctxt edits) (replicate (1 + 2 * ctxt) 0 ++ edits) | ||||||
|  |     addNums = snd . mapAccumL countTok (0, 0) | ||||||
|  |     stripNums = (,) <$> fst . head <*> map snd | ||||||
|  |     countTok x@(i, j) d@(op, _) = | ||||||
|  |       (,) | ||||||
|  |         (case op of | ||||||
|  |            Remove -> (i + 1, j) | ||||||
|  |            Keep -> (i + 1, j + 1) | ||||||
|  |            Add -> (i, j + 1) | ||||||
|  |            MineChanged -> (i, j) | ||||||
|  |            Original -> (i + 1, j + 1) | ||||||
|  |            YourChanged -> (i, j)) | ||||||
|  |         (x, d) | ||||||
							
								
								
									
										33
									
								
								src/Main.hs
									
									
									
									
									
								
							
							
						
						
									
										33
									
								
								src/Main.hs
									
									
									
									
									
								
							|  | @ -1,11 +1,15 @@ | ||||||
| module Main where | module Main where | ||||||
| 
 | 
 | ||||||
| import qualified Data.ByteString as B | import qualified Data.ByteString as B | ||||||
|  | import qualified Data.ByteString.Builder as BB | ||||||
| import qualified Data.ByteString.Char8 as B8 | import qualified Data.ByteString.Char8 as B8 | ||||||
| import Data.ByteString.UTF8 (fromString) | import Data.ByteString.UTF8 (fromString) | ||||||
| import qualified Data.Vector as V | import qualified Data.Vector as V | ||||||
| import Format | import System.IO (stdout) | ||||||
| import Diff | import Diff | ||||||
|  | import Diff3 | ||||||
|  | import Format | ||||||
|  | import Hunks | ||||||
| import Merge | import Merge | ||||||
| import Options.Applicative | import Options.Applicative | ||||||
| import Redfa | import Redfa | ||||||
|  | @ -34,7 +38,8 @@ data ADiffCommandOpts | ||||||
|       , patchMergeOpts :: MergeOpts |       , patchMergeOpts :: MergeOpts | ||||||
|       } |       } | ||||||
|   | CmdDiff3 |   | CmdDiff3 | ||||||
|       { diff3Mine :: String |       { context :: Int | ||||||
|  |       , diff3Mine :: String | ||||||
|       , diff3Old :: String |       , diff3Old :: String | ||||||
|       , diff3Yours :: String |       , diff3Yours :: String | ||||||
|       , diff3MergeOpts :: MergeOpts |       , diff3MergeOpts :: MergeOpts | ||||||
|  | @ -77,7 +82,14 @@ patchCmdOptions = | ||||||
|   mergeOption True |   mergeOption True | ||||||
| 
 | 
 | ||||||
| diff3CmdOptions = | diff3CmdOptions = | ||||||
|   CmdDiff3 <$> strArgument (metavar "MYFILE") <*> |   CmdDiff3 <$> | ||||||
|  |   option | ||||||
|  |     auto | ||||||
|  |     (metavar "CONTEXT" <> | ||||||
|  |      short 'C' <> | ||||||
|  |      long "context" <> | ||||||
|  |      value 5 <> help "How many tokens around the change to include in the patch") <*> | ||||||
|  |   strArgument (metavar "MYFILE") <*> | ||||||
|   strArgument (metavar "OLDFILE") <*> |   strArgument (metavar "OLDFILE") <*> | ||||||
|   strArgument (metavar "YOURFILE") <*> |   strArgument (metavar "YOURFILE") <*> | ||||||
|   mergeOption False |   mergeOption False | ||||||
|  | @ -113,6 +125,17 @@ main = | ||||||
|              data2 <- mmapFileByteString f2 Nothing |              data2 <- mmapFileByteString f2 Nothing | ||||||
|              toks1 <- V.fromList <$> redfaTokenize redfa data1 |              toks1 <- V.fromList <$> redfaTokenize redfa data1 | ||||||
|              toks2 <- V.fromList <$> redfaTokenize redfa data2 |              toks2 <- V.fromList <$> redfaTokenize redfa data2 | ||||||
|              let hs = hunks (max 0 ctxt) $ diffToks toks1 toks2 |              B8.putStr $ pprHunks $ hunks (max 0 ctxt) $ diffToks toks1 toks2 | ||||||
|              B8.putStr $ pprHunks hs |  | ||||||
|            CmdPatch {} -> putStrLn "not supported yet" |            CmdPatch {} -> putStrLn "not supported yet" | ||||||
|  |            CmdDiff3 ctxt f1 f2 f3 mo -> do | ||||||
|  |              [toksMine, toksOld, toksYour] <- | ||||||
|  |                map V.fromList <$> | ||||||
|  |                traverse | ||||||
|  |                  ((>>= redfaTokenize redfa) . flip mmapFileByteString Nothing) | ||||||
|  |                  [f1, f2, f3] | ||||||
|  |              let d3 = diff3Toks toksMine toksOld toksYour | ||||||
|  |              if mergeDoMerge mo | ||||||
|  |                then BB.hPutBuilder stdout $ fmtMerged mo d3 | ||||||
|  |                else B8.putStr $ | ||||||
|  |                     pprHunks $ | ||||||
|  |                     hunks (max 0 ctxt) $ diff3Toks toksMine toksOld toksYour | ||||||
|  |  | ||||||
							
								
								
									
										127
									
								
								src/Merge.hs
									
									
									
									
									
								
							
							
						
						
									
										127
									
								
								src/Merge.hs
									
									
									
									
									
								
							|  | @ -1,9 +1,12 @@ | ||||||
|  | {-# LANGUAGE OverloadedStrings #-} | ||||||
| module Merge | module Merge | ||||||
|   ( MergeOpts |   ( MergeOpts(..) | ||||||
|   , mergeOption |   , mergeOption | ||||||
|  |   , fmtMerged | ||||||
|   ) where |   ) where | ||||||
| 
 | 
 | ||||||
| import qualified Data.ByteString as B | import qualified Data.ByteString as B | ||||||
|  | import qualified Data.ByteString.Builder as BB | ||||||
| import Data.String | import Data.String | ||||||
| import Options.Applicative | import Options.Applicative | ||||||
| import Types | import Types | ||||||
|  | @ -16,52 +19,86 @@ data MergeOpts = | ||||||
|     , mergeCStartStr :: BS |     , mergeCStartStr :: BS | ||||||
|     , mergeMineSepStr :: BS |     , mergeMineSepStr :: BS | ||||||
|     , mergeYourSepStr :: BS |     , mergeYourSepStr :: BS | ||||||
|     , mergeEndStr :: BS |     , mergeCEndStr :: BS | ||||||
|     } |     } | ||||||
|   deriving (Show) |   deriving (Show) | ||||||
| 
 | 
 | ||||||
| marker = fromString . replicate 7 | marker = fromString . replicate 7 | ||||||
| 
 | 
 | ||||||
| mergeOption forPatch = | mergeOption forPatch = addLBR <$> ((,) <$> switch (short 'a' <> long "add-linebreak" <> help "Automatically add a line break after conflict markers") <*> mo) | ||||||
|   MergeOpts <$> |   where | ||||||
|   switch |    mo = MergeOpts <$> | ||||||
|     (short 'm' <> |     switch | ||||||
|      long "merge" <> |       (short 'm' <> | ||||||
|      help |        long "merge" <> | ||||||
|        (if forPatch |        help | ||||||
|           then "Merge using conflict markers instead of printing the rejected hunks" |          (if forPatch | ||||||
|           else "Output the merged file instead of the patch")) <*> |             then "Merge using conflict markers instead of printing the rejected hunks" | ||||||
|   switch |             else "Output the merged file instead of the patch")) <*> | ||||||
|     (short 'w' <> |     switch | ||||||
|      long "whitespace" <> |       (short 'w' <> | ||||||
|      help |        long "whitespace" <> | ||||||
|        ((if forPatch |        help | ||||||
|            then "Force rejecting a thunk" |          ((if forPatch | ||||||
|            else "Force a merge conflict") ++ |              then "Force rejecting a thunk" | ||||||
|         " on whitespace mismatch")) <*> |              else "Force a merge conflict") ++ | ||||||
|   switch |           " on whitespace mismatch")) <*> | ||||||
|     (short 'k' <> |     switch | ||||||
|      long "keep-whitespace" <> |       (short 'k' <> | ||||||
|      help |        long "keep-whitespace" <> | ||||||
|        ("On whitespace mismatch, default to the version from " ++ |        help | ||||||
|         (if forPatch |          ("On whitespace mismatch, default to the version from " ++ | ||||||
|            then "original file" |           (if forPatch | ||||||
|            else "MYFILE") ++ |              then "original file" | ||||||
|         " instead of the one from " ++ |              else "MYFILE") ++ | ||||||
|         (if forPatch |           " instead of the one from " ++ | ||||||
|            then "patch" |           (if forPatch | ||||||
|            else "YOURFILE"))) <*> |              then "patch" | ||||||
|   strOption |              else "YOURFILE"))) <*> | ||||||
|     (long "merge-start" <> |     strOption | ||||||
|      value (marker '<') <> help "Marker for the beginning of a conflict") <*> |       (long "merge-start" <> | ||||||
|   strOption |        value (marker '<') <> help "Marker for the beginning of a conflict") <*> | ||||||
|     (long "merge-mine" <> |     strOption | ||||||
|      value (marker '|') <> |       (long "merge-mine" <> | ||||||
|      help "Marker that separates `mine' from `original' part of the conflict") <*> |        value (marker '|') <> | ||||||
|   strOption |        help "Marker that separates `mine' from `original' part of the conflict") <*> | ||||||
|     (long "merge-your" <> |     strOption | ||||||
|      value (marker '=') <> |       (long "merge-your" <> | ||||||
|      help "Marker that separates `original' from `your' part of the conflict") <*> |        value (marker '=') <> | ||||||
|   strOption |        help "Marker that separates `original' from `your' part of the conflict") <*> | ||||||
|     (long "merge-end" <> |     strOption | ||||||
|      value (marker '>') <> help "Marker for the end of a conflict") |       (long "merge-end" <> | ||||||
|  |        value (marker '>') <> help "Marker for the end of a conflict") | ||||||
|  |    addLBR (False,x)=x | ||||||
|  |    addLBR (True,x)=x{ | ||||||
|  |     mergeCStartStr=mergeCStartStr x <> "\n", | ||||||
|  |     mergeMineSepStr=mergeMineSepStr x <> "\n", | ||||||
|  |     mergeYourSepStr=mergeYourSepStr x <> "\n", | ||||||
|  |     mergeCEndStr=mergeCEndStr x <> "\n"} | ||||||
|  | 
 | ||||||
|  | {- This kinda relies on reasonable ordering within the conflicts in the Diff -} | ||||||
|  | fmtMerged :: MergeOpts -> Diff -> BB.Builder | ||||||
|  | fmtMerged mo = go Keep | ||||||
|  |   where | ||||||
|  |     go op [] | ||||||
|  |       | conflictOp op = bb $ mergeCEndStr mo | ||||||
|  |       | otherwise = mempty | ||||||
|  |     go last l@((op, (_, tok)):xs) | ||||||
|  |       | conflictOp last && not (conflictOp op) = | ||||||
|  |         bb (mergeCEndStr mo) <> go Keep l | ||||||
|  |       | not (conflictOp last) && conflictOp op = | ||||||
|  |         bb (mergeCStartStr mo) <> go MineChanged l | ||||||
|  |       | last /= op && conflictOp op = | ||||||
|  |         (case op of | ||||||
|  |            MineChanged -> bb $ mergeCStartStr mo | ||||||
|  |            Original -> bb $ mergeMineSepStr mo | ||||||
|  |            YourChanged -> bb $ mergeYourSepStr mo) <> | ||||||
|  |         go op l | ||||||
|  |       | otherwise = bb tok <> go op xs | ||||||
|  |     conflictOp o = | ||||||
|  |       case o of | ||||||
|  |         Keep -> False | ||||||
|  |         Add -> False | ||||||
|  |         Remove -> False | ||||||
|  |         _ -> True | ||||||
|  |     bb = BB.byteString | ||||||
|  |  | ||||||
|  | @ -15,11 +15,9 @@ import Data.Monoid | ||||||
| import qualified Data.Vector as V | import qualified Data.Vector as V | ||||||
| import Options.Applicative | import Options.Applicative | ||||||
| import Text.Regex.TDFA | import Text.Regex.TDFA | ||||||
| import Diff | import Types | ||||||
| import Substr | import Substr | ||||||
| 
 | 
 | ||||||
| type BS = B.ByteString |  | ||||||
| 
 |  | ||||||
| data RedfaOption | data RedfaOption | ||||||
|   = RedfaOptionRules [BS] |   = RedfaOptionRules [BS] | ||||||
|   | RedfaOptionFile String |   | RedfaOptionFile String | ||||||
|  |  | ||||||
|  | @ -17,4 +17,7 @@ data Op | ||||||
|   = Remove |   = Remove | ||||||
|   | Keep |   | Keep | ||||||
|   | Add |   | Add | ||||||
|  |   | MineChanged | ||||||
|  |   | Original | ||||||
|  |   | YourChanged | ||||||
|   deriving (Show, Eq) |   deriving (Show, Eq) | ||||||
|  |  | ||||||
		Loading…
	
		Reference in a new issue