fix auto merge conflict resolution when doing out of tree merge for adjusted branch

This commit is contained in:
Joey Hess 2016-04-06 17:32:04 -04:00
parent b9e4e2ba84
commit 60bdffe43e
Failed to extract signature
6 changed files with 60 additions and 65 deletions

View file

@ -272,7 +272,7 @@ updateAdjustedBranch tomerge (origbranch, adj) commitmode = catchBoolIO $
withemptydir tmpwt $ withWorkTree tmpwt $ do withemptydir tmpwt $ withWorkTree tmpwt $ do
liftIO $ writeFile (tmpgit </> "HEAD") (fromRef updatedorig) liftIO $ writeFile (tmpgit </> "HEAD") (fromRef updatedorig)
showAction $ "Merging into " ++ fromRef (Git.Ref.base origbranch) showAction $ "Merging into " ++ fromRef (Git.Ref.base origbranch)
ifM (autoMergeFrom tomerge (Just updatedorig) commitmode) ifM (autoMergeFrom tomerge (Just origbranch) True commitmode)
( do ( do
!mergecommit <- liftIO $ extractSha <$> readFile (tmpgit </> "HEAD") !mergecommit <- liftIO $ extractSha <$> readFile (tmpgit </> "HEAD")
-- This is run after the commit lock is dropped. -- This is run after the commit lock is dropped.
@ -305,7 +305,7 @@ updateAdjustedBranch tomerge (origbranch, adj) commitmode = catchBoolIO $
adjmergecommit <- commitAdjustedTree' adjtree mergecommit adjmergecommit <- commitAdjustedTree' adjtree mergecommit
[mergecommit, currbranch] [mergecommit, currbranch]
showAction "Merging into adjusted branch" showAction "Merging into adjusted branch"
ifM (autoMergeFrom adjmergecommit (Just currbranch) commitmode) ifM (autoMergeFrom adjmergecommit (Just currbranch) False commitmode)
-- The adjusted branch has a merge commit on top; -- The adjusted branch has a merge commit on top;
-- clean that up and propigate any changes made -- clean that up and propigate any changes made
-- in that merge to the origbranch. -- in that merge to the origbranch.

View file

@ -42,17 +42,17 @@ import qualified Data.ByteString.Lazy as L
- Callers should use Git.Branch.changed first, to make sure that - Callers should use Git.Branch.changed first, to make sure that
- there are changes from the current branch to the branch being merged in. - there are changes from the current branch to the branch being merged in.
-} -}
autoMergeFrom :: Git.Ref -> Maybe Git.Ref -> Git.Branch.CommitMode -> Annex Bool autoMergeFrom :: Git.Ref -> Maybe Git.Ref -> Bool -> Git.Branch.CommitMode -> Annex Bool
autoMergeFrom branch currbranch commitmode = do autoMergeFrom branch currbranch inoverlay commitmode = do
showOutput showOutput
case currbranch of case currbranch of
Nothing -> go Nothing Nothing -> go Nothing
Just b -> go =<< inRepo (Git.Ref.sha b) Just b -> go =<< inRepo (Git.Ref.sha b)
where where
go old = ifM isDirect go old = ifM isDirect
( mergeDirect currbranch old branch (resolveMerge old branch) commitmode ( mergeDirect currbranch old branch (resolveMerge old branch False) commitmode
, inRepo (Git.Merge.mergeNonInteractive branch commitmode) , inRepo (Git.Merge.mergeNonInteractive branch commitmode)
<||> (resolveMerge old branch <&&> commitResolvedMerge commitmode) <||> (resolveMerge old branch inoverlay <&&> commitResolvedMerge commitmode)
) )
{- Resolves a conflicted merge. It's important that any conflicts be {- Resolves a conflicted merge. It's important that any conflicts be
@ -77,11 +77,16 @@ autoMergeFrom branch currbranch commitmode = do
- -
- In indirect mode, the merge is resolved in the work tree and files - In indirect mode, the merge is resolved in the work tree and files
- staged, to clean up from a conflicted merge that was run in the work - staged, to clean up from a conflicted merge that was run in the work
- tree. - tree.
- -
- In direct mode, the work tree is not touched here; files are staged to - In direct mode, the work tree is not touched here; files are staged to
- the index, and written to the gitAnnexMergeDir, for later handling by - the index, and written to the gitAnnexMergeDir, for later handling by
- the direct mode merge code. - the direct mode merge code.
-
- This is complicated by needing to support merges run in an overlay
- work tree, in which case the CWD won't be within the work tree.
- In this mode, there is no need to update the work tree at all,
- as the overlay work tree will get deleted.
- -
- Unlocked files remain unlocked after merging, and locked files - Unlocked files remain unlocked after merging, and locked files
- remain locked. When the merge conflict is between a locked and unlocked - remain locked. When the merge conflict is between a locked and unlocked
@ -93,12 +98,16 @@ autoMergeFrom branch currbranch commitmode = do
- A git merge can fail for other reasons, and this allows detecting - A git merge can fail for other reasons, and this allows detecting
- such failures. - such failures.
-} -}
resolveMerge :: Maybe Git.Ref -> Git.Ref -> Annex Bool resolveMerge :: Maybe Git.Ref -> Git.Ref -> Bool -> Annex Bool
resolveMerge us them = do resolveMerge us them inoverlay = do
top <- fromRepo Git.repoPath top <- if inoverlay
then pure "."
else fromRepo Git.repoPath
(fs, cleanup) <- inRepo (LsFiles.unmerged [top]) (fs, cleanup) <- inRepo (LsFiles.unmerged [top])
srcmap <- inodeMap $ pure (map LsFiles.unmergedFile fs, return True) srcmap <- if inoverlay
(mergedks, mergedfs) <- unzip <$> mapM (resolveMerge' srcmap us them) fs then pure M.empty
else inodeMap $ pure (map LsFiles.unmergedFile fs, return True)
(mergedks, mergedfs) <- unzip <$> mapM (resolveMerge' srcmap us them inoverlay) fs
let mergedks' = concat mergedks let mergedks' = concat mergedks
let mergedfs' = catMaybes mergedfs let mergedfs' = catMaybes mergedfs
let merged = not (null mergedfs') let merged = not (null mergedfs')
@ -114,15 +123,15 @@ resolveMerge us them = do
when merged $ do when merged $ do
Annex.Queue.flush Annex.Queue.flush
unlessM isDirect $ do unlessM (pure inoverlay <||> isDirect) $ do
unstagedmap <- inodeMap $ inRepo $ LsFiles.notInRepo False [top] unstagedmap <- inodeMap $ inRepo $ LsFiles.notInRepo False [top]
cleanConflictCruft mergedks' mergedfs' unstagedmap cleanConflictCruft mergedks' mergedfs' unstagedmap
showLongNote "Merge conflict was automatically resolved; you may want to examine the result." showLongNote "Merge conflict was automatically resolved; you may want to examine the result."
return merged return merged
resolveMerge' :: InodeMap -> Maybe Git.Ref -> Git.Ref -> LsFiles.Unmerged -> Annex ([Key], Maybe FilePath) resolveMerge' :: InodeMap -> Maybe Git.Ref -> Git.Ref -> Bool -> LsFiles.Unmerged -> Annex ([Key], Maybe FilePath)
resolveMerge' _ Nothing _ _ = return ([], Nothing) resolveMerge' _ Nothing _ _ _ = return ([], Nothing)
resolveMerge' unstagedmap (Just us) them u = do resolveMerge' unstagedmap (Just us) them inoverlay u = do
kus <- getkey LsFiles.valUs kus <- getkey LsFiles.valUs
kthem <- getkey LsFiles.valThem kthem <- getkey LsFiles.valThem
case (kus, kthem) of case (kus, kthem) of
@ -133,8 +142,9 @@ resolveMerge' unstagedmap (Just us) them u = do
makeannexlink keyThem LsFiles.valThem makeannexlink keyThem LsFiles.valThem
-- cleanConflictCruft can't handle unlocked -- cleanConflictCruft can't handle unlocked
-- files, so delete here. -- files, so delete here.
unless (islocked LsFiles.valUs) $ unless inoverlay $
liftIO $ nukeFile file unless (islocked LsFiles.valUs) $
liftIO $ nukeFile file
| otherwise -> do | otherwise -> do
-- Only resolve using symlink when both -- Only resolve using symlink when both
-- were locked, otherwise use unlocked -- were locked, otherwise use unlocked
@ -170,23 +180,33 @@ resolveMerge' unstagedmap (Just us) them u = do
where where
dest = variantFile file key dest = variantFile file key
stagefile :: FilePath -> Annex FilePath
stagefile f
| inoverlay = (</> f) <$> fromRepo Git.repoPath
| otherwise = pure f
makesymlink key dest = do makesymlink key dest = do
l <- calcRepo $ gitAnnexLink dest key l <- calcRepo $ gitAnnexLink dest key
replacewithsymlink dest l unless inoverlay $ replacewithsymlink dest l
stageSymlink dest =<< hashSymlink l dest' <- stagefile dest
stageSymlink dest' =<< hashSymlink l
replacewithsymlink dest link = withworktree dest $ \f -> replacewithsymlink dest link = withworktree dest $ \f ->
replaceFile f $ makeGitLink link replaceFile f $ makeGitLink link
makepointer key dest = do makepointer key dest = do
unlessM (reuseOldFile unstagedmap key file dest) $ do unless inoverlay $
r <- linkFromAnnex key dest unlessM (reuseOldFile unstagedmap key file dest) $ do
case r of r <- linkFromAnnex key dest
LinkAnnexFailed -> liftIO $ case r of
writeFile dest (formatPointer key) LinkAnnexFailed -> liftIO $
_ -> noop writeFile dest (formatPointer key)
stagePointerFile dest =<< hashPointerFile key _ -> noop
Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath dest) dest' <- stagefile dest
stagePointerFile dest' =<< hashPointerFile key
unless inoverlay $
Database.Keys.addAssociatedFile key
=<< inRepo (toTopFilePath dest)
withworktree f a = ifM isDirect withworktree f a = ifM isDirect
( do ( do
@ -202,7 +222,7 @@ resolveMerge' unstagedmap (Just us) them u = do
=<< fromRepo (UpdateIndex.lsSubTree b item) =<< fromRepo (UpdateIndex.lsSubTree b item)
-- Update the work tree to reflect the graft. -- Update the work tree to reflect the graft.
case (selectwant (LsFiles.unmergedBlobType u), selectunwant (LsFiles.unmergedBlobType u)) of unless inoverlay $ case (selectwant (LsFiles.unmergedBlobType u), selectunwant (LsFiles.unmergedBlobType u)) of
-- Symlinks are never left in work tree when -- Symlinks are never left in work tree when
-- there's a conflict with anything else. -- there's a conflict with anything else.
-- So, when grafting in a symlink, we must create it: -- So, when grafting in a symlink, we must create it:

View file

@ -21,14 +21,20 @@ withIndexFile f = withAltRepo
(\g -> addGitEnv g "GIT_INDEX_FILE" f) (\g -> addGitEnv g "GIT_INDEX_FILE" f)
(\g g' -> g' { gitEnv = gitEnv g }) (\g g' -> g' { gitEnv = gitEnv g })
{- Runs an action using a different git work tree. -} {- Runs an action using a different git work tree.
-
- Smudge and clean filters are disabled in this work tree. -}
withWorkTree :: FilePath -> Annex a -> Annex a withWorkTree :: FilePath -> Annex a -> Annex a
withWorkTree d = withAltRepo withWorkTree d = withAltRepo
(\g -> return $ g { location = modlocation (location g) }) (\g -> return $ g { location = modlocation (location g), gitGlobalOpts = gitGlobalOpts g ++ disableSmudgeConfig })
(\g g' -> g' { location = location g }) (\g g' -> g' { location = location g, gitGlobalOpts = gitGlobalOpts g })
where where
modlocation l@(Local {}) = l { worktree = Just d } modlocation l@(Local {}) = l { worktree = Just d }
modlocation _ = error "withWorkTree of non-local git repo" modlocation _ = error "withWorkTree of non-local git repo"
disableSmudgeConfig = map Param
[ "-c", "filter.annex.smudge="
, "-c", "filter.annex.clean="
]
{- Runs an action with the git index file and HEAD, and a few other {- Runs an action with the git index file and HEAD, and a few other
- files that are related to the work tree coming from an overlay - files that are related to the work tree coming from an overlay

View file

@ -29,7 +29,7 @@ start = do
let merge_head = d </> "MERGE_HEAD" let merge_head = d </> "MERGE_HEAD"
them <- fromMaybe (error nomergehead) . extractSha them <- fromMaybe (error nomergehead) . extractSha
<$> liftIO (readFile merge_head) <$> liftIO (readFile merge_head)
ifM (resolveMerge (Just us) them) ifM (resolveMerge (Just us) them False)
( do ( do
void $ commitResolvedMerge Git.Branch.ManualCommit void $ commitResolvedMerge Git.Branch.ManualCommit
next $ next $ return True next $ next $ return True

View file

@ -170,7 +170,7 @@ merge :: CurrBranch -> Git.Branch.CommitMode -> Git.Branch -> Annex Bool
merge (Just b, Just adj) commitmode tomerge = merge (Just b, Just adj) commitmode tomerge =
updateAdjustedBranch tomerge (b, adj) commitmode updateAdjustedBranch tomerge (b, adj) commitmode
merge (b, _) commitmode tomerge = merge (b, _) commitmode tomerge =
autoMergeFrom tomerge b commitmode autoMergeFrom tomerge b False commitmode
syncBranch :: Git.Branch -> Git.Branch syncBranch :: Git.Branch -> Git.Branch
syncBranch = Git.Ref.under "refs/heads/synced" . fromDirectBranch . fromAdjustedBranch syncBranch = Git.Ref.under "refs/heads/synced" . fromDirectBranch . fromAdjustedBranch

View file

@ -279,37 +279,6 @@ into adjusted view worktrees.]
will make copies of the content of annexed files, so this would need will make copies of the content of annexed files, so this would need
to checkout the adjusted branch some other way. Maybe generalize so this to checkout the adjusted branch some other way. Maybe generalize so this
more efficient checkout is available as a git-annex command? more efficient checkout is available as a git-annex command?
* sync in adjusted branch runs merge in overlay worktree,
but the merge conflict resolution code does not know to use that
worktree.
* sync in adjusted branch can trigger merge conflict detection where
there should be no conflict.
git init a
cd a
git annex init --version=6
echo hi > f
git annex add f
git annex sync
cd ..
git clone a b
cd b
git annex init --version=6
git annex get
git annex adjust --unlock
cd ..
cd a
git mv f f2
git annex sync
cd ..
cd b
git annex sync
To fix, implement "avoiding conflicted merge" above.
* There are potentially races in code that assumes a branch like * There are potentially races in code that assumes a branch like
master is not being changed by someone else. In particular, master is not being changed by someone else. In particular,
propigateAdjustedCommits rebases the adjusted branch on top of master. propigateAdjustedCommits rebases the adjusted branch on top of master.