allow for union merges between a tree and the content in the index
This is needed for robust handling of the git-annex branch. Since changes are staged to its index as git-annex runs, and committed at the end, it's possible that git-annex is interrupted, and leaves a dirty index. When it next runs, it needs to be able to merge the git-annex branch as necessary, without losing the existing changes in the index. Note that this assumes that the git-annex branch is only modified by git-annex. Any changes to it will be lost when git-annex updates the branch. I don't see a good, inexpensive way to find changes in the git-annex branch that arn't in the index, and union merging the git-annex branch into the index every time would likewise be expensive.
This commit is contained in:
parent
5e0adb2637
commit
7a693394f4
3 changed files with 70 additions and 43 deletions
31
Branch.hs
31
Branch.hs
|
@ -12,12 +12,13 @@ module Branch (
|
||||||
commit
|
commit
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Monad (unless)
|
import Control.Monad (unless, liftM)
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Data.String.Utils
|
import Data.String.Utils
|
||||||
import System.Cmd.Utils
|
import System.Cmd.Utils
|
||||||
|
import Data.Maybe
|
||||||
|
|
||||||
import qualified GitRepo as Git
|
import qualified GitRepo as Git
|
||||||
import qualified GitUnionMerge
|
import qualified GitUnionMerge
|
||||||
|
@ -72,14 +73,18 @@ update = do
|
||||||
updated <- Annex.getState Annex.updated
|
updated <- Annex.getState Annex.updated
|
||||||
unless updated $ withIndex $ do
|
unless updated $ withIndex $ do
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
refs <- liftIO $ Git.pipeRead g [Param "show-ref", Param name]
|
r <- liftIO $ Git.pipeRead g [Param "show-ref", Param name]
|
||||||
mapM_ updateRef $ map (last . words) (lines refs)
|
let refs = map (last . words) (lines r)
|
||||||
|
updated <- catMaybes `liftM` mapM updateRef refs
|
||||||
|
unless (null updated) $ liftIO $
|
||||||
|
GitUnionMerge.commit g "update" fullname
|
||||||
|
(fullname:updated)
|
||||||
Annex.changeState $ \s -> s { Annex.updated = True }
|
Annex.changeState $ \s -> s { Annex.updated = True }
|
||||||
|
|
||||||
{- Ensures that a given ref has been merged into the local git-annex branch. -}
|
{- Ensures that a given ref has been merged into the index. -}
|
||||||
updateRef :: String -> Annex ()
|
updateRef :: String -> Annex (Maybe String)
|
||||||
updateRef ref
|
updateRef ref
|
||||||
| ref == fullname = return ()
|
| ref == fullname = return Nothing
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
diffs <- liftIO $ Git.pipeRead g [
|
diffs <- liftIO $ Git.pipeRead g [
|
||||||
|
@ -87,9 +92,15 @@ updateRef ref
|
||||||
Param (name++".."++ref),
|
Param (name++".."++ref),
|
||||||
Params "--oneline -n1"
|
Params "--oneline -n1"
|
||||||
]
|
]
|
||||||
unless (null diffs) $ do
|
if (null diffs)
|
||||||
showSideAction $ "merging " ++ ref ++ " into " ++ name ++ "..."
|
then return Nothing
|
||||||
liftIO $ unionMerge g fullname ref fullname True
|
else do
|
||||||
|
showSideAction $ "merging " ++ ref ++ " into " ++ name ++ "..."
|
||||||
|
-- By passing only one ref, it is actually
|
||||||
|
-- merged into the index, preserving any
|
||||||
|
-- changes that may already be staged.
|
||||||
|
liftIO $ GitUnionMerge.merge g [ref]
|
||||||
|
return $ Just ref
|
||||||
|
|
||||||
{- Stages the content of a file into the branch's index. -}
|
{- Stages the content of a file into the branch's index. -}
|
||||||
change :: FilePath -> String -> Annex ()
|
change :: FilePath -> String -> Annex ()
|
||||||
|
@ -104,7 +115,7 @@ change file content = do
|
||||||
commit :: String -> Annex ()
|
commit :: String -> Annex ()
|
||||||
commit message = withIndex $ do
|
commit message = withIndex $ do
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
liftIO $ GitUnionMerge.commit g message branch []
|
liftIO $ GitUnionMerge.commit g message fullname []
|
||||||
|
|
||||||
{- Gets the content of a file on the branch, or content staged in the index
|
{- Gets the content of a file on the branch, or content staged in the index
|
||||||
- if it's newer. Returns an empty string if the file didn't exist yet. -}
|
- if it's newer. Returns an empty string if the file didn't exist yet. -}
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module GitUnionMerge (
|
module GitUnionMerge (
|
||||||
merge,
|
merge,
|
||||||
stage,
|
|
||||||
commit
|
commit
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -19,38 +18,54 @@ import Data.String.Utils
|
||||||
import qualified GitRepo as Git
|
import qualified GitRepo as Git
|
||||||
import Utility
|
import Utility
|
||||||
|
|
||||||
{- Performs a union merge. Should be run with a temporary index file
|
{- Performs a union merge between two branches, staging it in the index.
|
||||||
- configured by Git.useIndex.
|
- Any previously staged changes in the index will be lost.
|
||||||
-
|
-
|
||||||
- Use indexpopulated only if the index file already contains exactly the
|
- When only one branch is specified, it is merged into the index.
|
||||||
- contents of aref.
|
- In this case, previously staged changes in the index are preserved.
|
||||||
|
-
|
||||||
|
- Should be run with a temporary index file configured by Git.useIndex.
|
||||||
-}
|
-}
|
||||||
merge :: Git.Repo -> String -> String -> String -> Bool -> IO ()
|
merge :: Git.Repo -> [String] -> IO ()
|
||||||
merge g aref bref newref indexpopulated = do
|
merge g (x:y:[]) = do
|
||||||
stage g aref bref indexpopulated
|
a <- ls_tree g x
|
||||||
commit g "union merge" newref [aref, bref]
|
b <- merge_trees g x y
|
||||||
|
update_index g (a++b)
|
||||||
|
merge g [x] = merge_tree_index g x >>= update_index g
|
||||||
|
merge _ _ = error "wrong number of branches to merge"
|
||||||
|
|
||||||
{- Stages the content of both refs into the index. -}
|
{- Feeds a list into update-index. Later items in the list can override
|
||||||
stage :: Git.Repo -> String -> String -> Bool -> IO ()
|
- earlier ones, so the list can be generated from any combination of
|
||||||
stage g aref bref indexpopulated = do
|
- ls_tree, merge_trees, and merge_tree. -}
|
||||||
-- Get the contents of aref, as a starting point, unless
|
update_index :: Git.Repo -> [String] -> IO ()
|
||||||
-- the index is already populated with it.
|
update_index g l = togit ["update-index", "-z", "--index-info"] (join "\0" l)
|
||||||
ls <- if indexpopulated
|
|
||||||
then return []
|
|
||||||
else fromgit ["ls-tree", "-z", "-r", "--full-tree", aref]
|
|
||||||
-- Identify files that are different between aref and bref, and
|
|
||||||
-- inject merged versions into git.
|
|
||||||
diff <- fromgit
|
|
||||||
["diff-tree", "--raw", "-z", "-r", "--no-renames", "-l0", aref, bref]
|
|
||||||
ls' <- mapM mergefile (pairs diff)
|
|
||||||
-- Populate the index file. Later lines override earlier ones.
|
|
||||||
togit ["update-index", "-z", "--index-info"]
|
|
||||||
(join "\0" $ ls++catMaybes ls')
|
|
||||||
where
|
where
|
||||||
fromgit l = Git.pipeNullSplit g (map Param l)
|
togit ps content = Git.pipeWrite g (map Param ps) content
|
||||||
togit l content = Git.pipeWrite g (map Param l) content
|
|
||||||
>>= forceSuccess
|
>>= forceSuccess
|
||||||
|
|
||||||
|
{- Gets the contents of a tree in a format suitable for update_index. -}
|
||||||
|
ls_tree :: Git.Repo -> String -> IO [String]
|
||||||
|
ls_tree g x = Git.pipeNullSplit g $
|
||||||
|
map Param ["ls-tree", "-z", "-r", "--full-tree", x]
|
||||||
|
|
||||||
|
{- For merging two trees. -}
|
||||||
|
merge_trees :: Git.Repo -> String -> String -> IO [String]
|
||||||
|
merge_trees g x y = calc_merge g
|
||||||
|
["diff-tree", "--raw", "-z", "-r", "--no-renames", "-l0", x, y]
|
||||||
|
|
||||||
|
{- For merging a single tree into the index. -}
|
||||||
|
merge_tree_index :: Git.Repo -> String -> IO [String]
|
||||||
|
merge_tree_index g x = calc_merge g
|
||||||
|
["diff-index", "--raw", "-z", "-r", "--no-renames", "-l0", x]
|
||||||
|
|
||||||
|
{- Calculates how to perform a merge, using git to get a raw diff,
|
||||||
|
- and returning a list suitable for update_index. -}
|
||||||
|
calc_merge :: Git.Repo -> [String] -> IO [String]
|
||||||
|
calc_merge g differ = do
|
||||||
|
diff <- Git.pipeNullSplit g $ map Param differ
|
||||||
|
l <- mapM mergefile (pairs diff)
|
||||||
|
return $ catMaybes l
|
||||||
|
where
|
||||||
pairs [] = []
|
pairs [] = []
|
||||||
pairs (_:[]) = error "parse error"
|
pairs (_:[]) = error "parse error"
|
||||||
pairs (a:b:rest) = (a,b):pairs rest
|
pairs (a:b:rest) = (a,b):pairs rest
|
||||||
|
@ -62,7 +77,7 @@ stage g aref bref indexpopulated = do
|
||||||
mergefile (info, file) = do
|
mergefile (info, file) = do
|
||||||
let [_colonamode, _bmode, asha, bsha, _status] = words info
|
let [_colonamode, _bmode, asha, bsha, _status] = words info
|
||||||
if bsha == nullsha
|
if bsha == nullsha
|
||||||
then return Nothing -- already staged from aref
|
then return Nothing -- already staged
|
||||||
else mergefile' file asha bsha
|
else mergefile' file asha bsha
|
||||||
mergefile' file asha bsha = do
|
mergefile' file asha bsha = do
|
||||||
let shas = filter (/= nullsha) [asha, bsha]
|
let shas = filter (/= nullsha) [asha, bsha]
|
||||||
|
@ -70,10 +85,10 @@ stage g aref bref indexpopulated = do
|
||||||
sha <- Git.hashObject g $ unionmerge content
|
sha <- Git.hashObject g $ unionmerge content
|
||||||
return $ Just $ ls_tree_line sha file
|
return $ Just $ ls_tree_line sha file
|
||||||
|
|
||||||
{- Commits the index into the specified branch. If refs are specified,
|
{- Commits the index into the specified branch,
|
||||||
- commits a merge. -}
|
- with the specified parent refs. -}
|
||||||
commit :: Git.Repo -> String -> String -> [String] -> IO ()
|
commit :: Git.Repo -> String -> String -> [String] -> IO ()
|
||||||
commit g message newref mergedrefs = do
|
commit g message newref parentrefs = do
|
||||||
tree <- Git.getSha "write-tree" $ ignorehandle $
|
tree <- Git.getSha "write-tree" $ ignorehandle $
|
||||||
pipeFrom "git" ["write-tree"]
|
pipeFrom "git" ["write-tree"]
|
||||||
sha <- Git.getSha "commit-tree" $ ignorehandle $
|
sha <- Git.getSha "commit-tree" $ ignorehandle $
|
||||||
|
@ -81,4 +96,4 @@ commit g message newref mergedrefs = do
|
||||||
Git.run g "update-ref" [Param newref, Param sha]
|
Git.run g "update-ref" [Param newref, Param sha]
|
||||||
where
|
where
|
||||||
ignorehandle a = return . snd =<< a
|
ignorehandle a = return . snd =<< a
|
||||||
ps = concatMap (\r -> ["-p", r]) mergedrefs
|
ps = concatMap (\r -> ["-p", r]) parentrefs
|
||||||
|
|
|
@ -44,5 +44,6 @@ main = do
|
||||||
g <- Git.configRead =<< Git.repoFromCwd
|
g <- Git.configRead =<< Git.repoFromCwd
|
||||||
Git.useIndex (tmpIndex g)
|
Git.useIndex (tmpIndex g)
|
||||||
setup g
|
setup g
|
||||||
GitUnionMerge.merge g aref bref newref False
|
GitUnionMerge.merge g [aref, bref]
|
||||||
|
GitUnionMerge.commit g "union merge" newref [aref, bref]
|
||||||
cleanup g
|
cleanup g
|
||||||
|
|
Loading…
Reference in a new issue