git merging works
This commit is contained in:
		
							parent
							
								
									bc5d7a6915
								
							
						
					
					
						commit
						60a08808b9
					
				
							
								
								
									
										102
									
								
								Main.hs
									
									
									
									
									
								
							
							
						
						
									
										102
									
								
								Main.hs
									
									
									
									
									
								
							|  | @ -5,7 +5,10 @@ module Main where | ||||||
| import Control.Exception | import Control.Exception | ||||||
| import Control.Monad | import Control.Monad | ||||||
| import Data.Bool | import Data.Bool | ||||||
|  | import Data.Char | ||||||
| import Data.Foldable | import Data.Foldable | ||||||
|  | import Data.List | ||||||
|  | import Data.Traversable | ||||||
| import Opts | import Opts | ||||||
| import System.Exit | import System.Exit | ||||||
| import System.FilePath | import System.FilePath | ||||||
|  | @ -36,6 +39,59 @@ rundiff f1 f2 out = do | ||||||
|   unless (st `elem` [ExitSuccess, ExitFailure 1]) |   unless (st `elem` [ExitSuccess, ExitFailure 1]) | ||||||
|     $ error "diff failed for unknown reason (is GNU diffutils installed?)" |     $ error "diff failed for unknown reason (is GNU diffutils installed?)" | ||||||
| 
 | 
 | ||||||
|  | gitRepoRelRoot = do | ||||||
|  |   (path, st) <- | ||||||
|  |     withCreateProcess | ||||||
|  |       (proc "git" ["rev-parse", "--show-cdup"]) | ||||||
|  |         {std_in = NoStream, std_out = CreatePipe, std_err = Inherit} $ \_ (Just oh) _ p -> | ||||||
|  |       (,) <$> hGetContents' oh <*> waitForProcess p | ||||||
|  |   unless (st == ExitSuccess) $ error "git failed" | ||||||
|  |   let [p] = lines path | ||||||
|  |   pure p | ||||||
|  | 
 | ||||||
|  | gitUnmerged = do | ||||||
|  |   (paths, st) <- | ||||||
|  |     withCreateProcess | ||||||
|  |       (proc "git" ["status", "--porcelain=v1"]) | ||||||
|  |         {std_in = NoStream, std_out = CreatePipe, std_err = Inherit} $ \_ (Just oh) _ p -> | ||||||
|  |       (,) | ||||||
|  |         <$> (map (drop 3) . filter ("UU " `isPrefixOf`) . lines | ||||||
|  |                <$> hGetContents' oh) | ||||||
|  |         <*> waitForProcess p | ||||||
|  |   unless (st == ExitSuccess) $ error "git failed" | ||||||
|  |   pure paths | ||||||
|  | 
 | ||||||
|  | gitCheckoutMOY u my old your = do | ||||||
|  |   (paths, st) <- | ||||||
|  |     withCreateProcess | ||||||
|  |       (proc "git" ["ls-files", "--unmerged", "--", u]) | ||||||
|  |         {std_in = NoStream, std_out = CreatePipe, std_err = Inherit} $ \_ (Just oh) _ p -> | ||||||
|  |       (,) | ||||||
|  |         <$> (sortOn snd | ||||||
|  |                . map ((\[a, b] -> (a, b)) . take 2 . drop 1 . words) | ||||||
|  |                . lines | ||||||
|  |                <$> hGetContents' oh) | ||||||
|  |         <*> waitForProcess p | ||||||
|  |   unless (st == ExitSuccess) $ error "git failed" | ||||||
|  |   let co (hash, _) path = do | ||||||
|  |         st <- | ||||||
|  |           withCreateProcess | ||||||
|  |             (proc "git" ["cat-file", "blob", hash]) | ||||||
|  |               {std_in = NoStream, std_out = CreatePipe, std_err = Inherit} $ \_ (Just ho) _ p -> do | ||||||
|  |             hGetContents ho >>= writeFile path . Toks.split -- TODO cfg | ||||||
|  |             waitForProcess p | ||||||
|  |         unless (st == ExitSuccess) . error | ||||||
|  |           $ "failed checking out " ++ u ++ " from blob " ++ hash | ||||||
|  |   case paths of | ||||||
|  |     [(_, "1"), (_, "2"), (_, "3")] -> | ||||||
|  |       zipWithM co paths [old, my, your] >> pure () | ||||||
|  |     _ -> error $ "bad data from ls-files for unmerged " ++ u | ||||||
|  | 
 | ||||||
|  | gitAdd path = do | ||||||
|  |   traceM $ "adding " ++ path | ||||||
|  |   st <- rawSystem "git" ["add", "--", path] | ||||||
|  |   unless (st == ExitSuccess) $ error "git-add failed" | ||||||
|  | 
 | ||||||
| data Op | data Op | ||||||
|   = Del |   = Del | ||||||
|   | Keep |   | Keep | ||||||
|  | @ -125,6 +181,14 @@ resolve _ x = x | ||||||
| -- separate/overlapped conflict resolution -- e.g., what if someone wants to | -- separate/overlapped conflict resolution -- e.g., what if someone wants to | ||||||
| -- merge overlapping edits in text but separate edits in spaces? At this point | -- merge overlapping edits in text but separate edits in spaces? At this point | ||||||
| -- that might be ignorable. | -- that might be ignorable. | ||||||
|  | -- | ||||||
|  | -- Also, conflicts that are made out of an ignorable space change and a | ||||||
|  | -- mergeable non-space change now cause conflicts because the spaces are no | ||||||
|  | -- longer truly separable/alignable here. Ideally some part of the space | ||||||
|  | -- merging should be done at alignment (e.g., fake all spaces to cause them to | ||||||
|  | -- align well). Also it might be necessary to group space-tokens together | ||||||
|  | -- (newline and indent are now 2 space tokens, which won't ever merge with a | ||||||
|  | -- single space) | ||||||
| resolveSpace Config {..} c@(Conflict m o y) | resolveSpace Config {..} c@(Conflict m o y) | ||||||
|   | m == o && o == y = Ok o |   | m == o && o == y = Ok o | ||||||
|   | otherwise = |   | otherwise = | ||||||
|  | @ -140,21 +204,22 @@ resolveSpaces _ x = x | ||||||
| merge cfg@Config {..} ms ys = | merge cfg@Config {..} ms ys = | ||||||
|   regroup |   regroup | ||||||
|     . map (resolve cfg) |     . map (resolve cfg) | ||||||
|  |     . traceShowId | ||||||
|     . regroup |     . regroup | ||||||
|     . bool id (concatMap zeal) cfgZealous |     . bool id (concatMap zeal) cfgZealous | ||||||
|     . expand cfgContext |     . expand cfgContext | ||||||
|     . regroup |     . regroup | ||||||
|     $ align ms ys |     $ align ms ys | ||||||
| 
 | 
 | ||||||
| format :: Config -> [Merged] -> IO Bool | format :: Config -> Handle -> [Merged] -> IO Bool | ||||||
| format Config {..} = go False | format Config {..} h = go False | ||||||
|   where |   where | ||||||
|     go c [] = pure c |     go c [] = pure c | ||||||
|     go c (Ok x:xs) = do |     go c (Ok x:xs) = do | ||||||
|       putStr (Toks.glueToks x) |       hPutStr h (Toks.glueToks x) | ||||||
|       go c xs |       go c xs | ||||||
|     go c (Conflict m o y:xs) = do |     go c (Conflict m o y:xs) = do | ||||||
|       putStr |       hPutStr h | ||||||
|         $ mconcat |         $ mconcat | ||||||
|             [ cfgLabelStart |             [ cfgLabelStart | ||||||
|             , Toks.glueToks m |             , Toks.glueToks m | ||||||
|  | @ -174,11 +239,36 @@ runCmd CmdDiff3 {..} cfg = | ||||||
|       readFile path >>= writeFile tmp . Toks.split -- TODO cfg |       readFile path >>= writeFile tmp . Toks.split -- TODO cfg | ||||||
|     rundiff fOld fMy fdMy |     rundiff fOld fMy fdMy | ||||||
|     rundiff fOld fYour fdYour |     rundiff fOld fYour fdYour | ||||||
|     conflicted <- merge cfg <$> pdiff fdMy <*> pdiff fdYour >>= format cfg |     conflicted <- | ||||||
|  |       merge cfg <$> pdiff fdMy <*> pdiff fdYour >>= format cfg stdout | ||||||
|     if conflicted |     if conflicted | ||||||
|       then exitWith (ExitFailure 1) |       then exitWith (ExitFailure 1) | ||||||
|       else exitSuccess |       else exitSuccess | ||||||
| runCmd _ _ = error "not implemented yet" | runCmd CmdGitMerge {..} cfg = do | ||||||
|  |   relroot <- gitRepoRelRoot | ||||||
|  |   unmerged <- | ||||||
|  |     case gmFiles of | ||||||
|  |       Nothing -> map (relroot </>) <$> gitUnmerged | ||||||
|  |       Just fs -> pure fs | ||||||
|  |   conflicts <- | ||||||
|  |     for unmerged $ \u -> | ||||||
|  |       withSystemTempDirectory "werge-git" $ \workdir -> do | ||||||
|  |         let [fMy, fOld, fYour, fdMy, fdYour] = | ||||||
|  |               map (workdir </>) ["my", "old", "your", "mydiff", "yourdiff"] | ||||||
|  |         gitCheckoutMOY u fMy fOld fYour | ||||||
|  |         rundiff fOld fMy fdMy | ||||||
|  |         rundiff fOld fYour fdYour | ||||||
|  |         readFile u >>= writeFile (u ++ ".werge-backup") | ||||||
|  |         conflict <- | ||||||
|  |           withFile u WriteMode $ \h -> | ||||||
|  |             merge cfg <$> pdiff fdMy <*> pdiff fdYour >>= format cfg h | ||||||
|  |         traceShowM conflict | ||||||
|  |         traceShowM gmDoAdd | ||||||
|  |         unless conflict $ when gmDoAdd $ gitAdd u | ||||||
|  |         pure conflict | ||||||
|  |   if or conflicts | ||||||
|  |     then exitWith (ExitFailure 1) | ||||||
|  |     else exitSuccess | ||||||
| 
 | 
 | ||||||
| main :: IO () | main :: IO () | ||||||
| main = catch go bad | main = catch go bad | ||||||
|  |  | ||||||
							
								
								
									
										26
									
								
								Opts.hs
									
									
									
									
									
								
							
							
						
						
									
										26
									
								
								Opts.hs
									
									
									
									
									
								
							|  | @ -143,9 +143,9 @@ data Command | ||||||
|       , d3old :: FilePath |       , d3old :: FilePath | ||||||
|       , d3your :: FilePath |       , d3your :: FilePath | ||||||
|       } |       } | ||||||
|   | CmdGitMergetool |   | CmdGitMerge | ||||||
|       { gmtFiles :: Maybe [FilePath] |       { gmFiles :: Maybe [FilePath] | ||||||
|       , gmtDoAdd :: Bool |       , gmDoAdd :: Bool | ||||||
|       } |       } | ||||||
|   deriving (Show) |   deriving (Show) | ||||||
| 
 | 
 | ||||||
|  | @ -156,31 +156,33 @@ cmdDiff3 = do | ||||||
|     strArgument $ metavar "YOURFILE" <> help "version with other people's edits" |     strArgument $ metavar "YOURFILE" <> help "version with other people's edits" | ||||||
|   pure CmdDiff3 {..} |   pure CmdDiff3 {..} | ||||||
| 
 | 
 | ||||||
| cmdGitMergetool = do | cmdGitMerge = do | ||||||
|   gmtFiles <- |   gmFiles <- | ||||||
|     asum |     asum | ||||||
|       [ fmap Just . many |       [ fmap Just . some | ||||||
|           $ strArgument |           $ strArgument | ||||||
|           $ metavar "UNMERGED" |           $ metavar "UNMERGED" | ||||||
|               <> help "unmerged git file (can be specified repeatedly" |               <> help "unmerged git file (can be specified repeatedly)" | ||||||
|       , flag' |       , flag' | ||||||
|           Nothing |           Nothing | ||||||
|           (long "unmerged" |           (long "unmerged" | ||||||
|              <> short 'u' |              <> short 'u' | ||||||
|              <> help "process all files marked as unmerged by git") |              <> help "process all files marked as unmerged by git") | ||||||
|       ] |       ] | ||||||
|   gmtDoAdd <- |   gmDoAdd <- | ||||||
|     asum |     asum | ||||||
|       [ flag' |       [ flag' | ||||||
|           False |           True | ||||||
|           (long "add" |           (long "add" | ||||||
|              <> short 'a' |              <> short 'a' | ||||||
|              <> help "run `git add' for fully merged files") |              <> help "run `git add' for fully merged files") | ||||||
|       , flag' True (long "no-add" <> help "prevent running `git add'") |       , flag' False (long "no-add" <> help "prevent running `git add'") | ||||||
|       , pure False |       , pure False | ||||||
|       ] |       ] | ||||||
|   pure CmdGitMergetool {..} |   pure CmdGitMerge {..} | ||||||
| 
 | 
 | ||||||
|  | -- TODO have some option to output the (partially merged) my/old/your files so | ||||||
|  | -- that folks can continue with external program or so (such as meld) | ||||||
| cmd = | cmd = | ||||||
|   hsubparser |   hsubparser | ||||||
|     $ mconcat |     $ mconcat | ||||||
|  | @ -188,7 +190,7 @@ cmd = | ||||||
|             $ info cmdDiff3 |             $ info cmdDiff3 | ||||||
|             $ progDesc "diff3-style merge of changes" |             $ progDesc "diff3-style merge of changes" | ||||||
|         , command "git" |         , command "git" | ||||||
|             $ info cmdGitMergetool |             $ info cmdGitMerge | ||||||
|             $ progDesc "try to merge unmerged git tree" |             $ progDesc "try to merge unmerged git tree" | ||||||
|         ] |         ] | ||||||
| 
 | 
 | ||||||
|  |  | ||||||
		Loading…
	
		Reference in a new issue