sync: When in an adjusted branch, merge changes from the original branch

This causes changes to the original branch to get merged with a single
sync. Before, it took 2 syncs; the first happened to update the synced/
branch, and the second merged changes from the synced/ branch into the
ajusted branch.

Using mergeToAdjustedBranch when tomerge == origbranch is probably
overkill, but it does work fine.

Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
This commit is contained in:
Joey Hess 2023-07-06 12:42:00 -04:00
parent 51b24aac91
commit 240bae38f6
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
6 changed files with 72 additions and 49 deletions

View file

@ -1,6 +1,6 @@
{- adjusted branch merging
-
- Copyright 2016-2020 Joey Hess <id@joeyh.name>
- Copyright 2016-2023 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@ -8,6 +8,7 @@
{-# LANGUAGE BangPatterns, OverloadedStrings #-}
module Annex.AdjustedBranch.Merge (
canMergeToAdjustedBranch,
mergeToAdjustedBranch,
) where
@ -32,6 +33,12 @@ import Utility.Directory.Create
import qualified Data.ByteString as S
import qualified System.FilePath.ByteString as P
canMergeToAdjustedBranch :: Branch -> (OrigBranch, Adjustment) -> Annex Bool
canMergeToAdjustedBranch tomerge (origbranch, adj) =
inRepo $ Git.Branch.changed currbranch tomerge
where
AdjBranch currbranch = originalToAdjusted origbranch adj
{- Update the currently checked out adjusted branch, merging the provided
- branch into it. Note that the provided branch should be a non-adjusted
- branch. -}
@ -42,16 +49,10 @@ mergeToAdjustedBranch tomerge (origbranch, adj) mergeconfig canresolvemerge comm
adjbranch@(AdjBranch currbranch) = originalToAdjusted origbranch adj
basis = basisBranch adjbranch
go commitsprevented =
ifM (inRepo $ Git.Branch.changed currbranch tomerge)
( do
(updatedorig, _) <- propigateAdjustedCommits'
False origbranch adj commitsprevented
changestomerge updatedorig
, nochangestomerge
)
nochangestomerge = return $ return True
go commitsprevented = do
(updatedorig, _) <- propigateAdjustedCommits'
False origbranch adj commitsprevented
changestomerge updatedorig
{- Since the adjusted branch changes files, merging tomerge
- directly into it would likely result in unnecessary merge
@ -98,7 +99,8 @@ mergeToAdjustedBranch tomerge (origbranch, adj) mergeconfig canresolvemerge comm
-- (for an unknown reason).
-- http://thread.gmane.org/gmane.comp.version-control.git/297237
inRepo $ Git.Command.run [Param "reset", Param "HEAD", Param "--quiet"]
showAction $ UnquotedString $ "Merging into " ++ fromRef (Git.Ref.base origbranch)
when (tomerge /= origbranch) $
showAction $ UnquotedString $ "Merging into " ++ fromRef (Git.Ref.base origbranch)
merged <- autoMergeFrom' tomerge Nothing mergeconfig commitmode True
(const $ resolveMerge (Just updatedorig) tomerge True)
if merged

View file

@ -99,7 +99,7 @@ onChange file
mc
def
cmode
changedbranch
[changedbranch]
recordCommit
| changedbranch == b =
-- Record commit so the pusher pushes it out.

View file

@ -62,7 +62,7 @@ mergeBranch o r = starting "merge" ai si $ do
currbranch <- getCurrentBranch
mc <- mergeConfig (allowUnrelatedHistories o)
let so = def { notOnlyAnnexOption = True }
next $ merge currbranch mc so Git.Branch.ManualCommit r
next $ merge currbranch mc so Git.Branch.ManualCommit [r]
where
ai = ActionItemOther (Just (UnquotedString (Git.fromRef r)))
si = SeekInput []

View file

@ -351,14 +351,16 @@ mergeConfig mergeunrelated = do
else Nothing
]
merge :: CurrBranch -> [Git.Merge.MergeConfig] -> SyncOptions -> Git.Branch.CommitMode -> Git.Branch -> Annex Bool
merge currbranch mergeconfig o commitmode tomerge = do
merge :: CurrBranch -> [Git.Merge.MergeConfig] -> SyncOptions -> Git.Branch.CommitMode -> [Git.Branch] -> Annex Bool
merge currbranch mergeconfig o commitmode tomergel = do
canresolvemerge <- if resolveMergeOverride o
then getGitConfigVal annexResolveMerge
else return False
case currbranch of
(Just b, Just adj) -> mergeToAdjustedBranch tomerge (b, adj) mergeconfig canresolvemerge commitmode
(b, _) -> autoMergeFrom tomerge b mergeconfig commitmode canresolvemerge
and <$> case currbranch of
(Just b, Just adj) -> forM tomergel $ \tomerge ->
mergeToAdjustedBranch tomerge (b, adj) mergeconfig canresolvemerge commitmode
(b, _) -> forM tomergel $ \tomerge ->
autoMergeFrom tomerge b mergeconfig commitmode canresolvemerge
syncBranch :: Git.Branch -> Git.Branch
syncBranch = Git.Ref.underBase "refs/heads/synced" . origBranch
@ -440,46 +442,54 @@ mergeLocal mergeconfig o currbranch = stopUnless (notOnlyAnnex o) $
mergeLocal' :: [Git.Merge.MergeConfig] -> SyncOptions -> CurrBranch -> CommandStart
mergeLocal' mergeconfig o currbranch@(Just branch, _) =
needMerge currbranch branch >>= \case
Nothing -> stop
Just syncbranch -> do
let ai = ActionItemOther (Just $ UnquotedString $ Git.Ref.describe syncbranch)
[] -> stop
tomerge -> do
let ai = ActionItemOther (Just $ UnquotedString $ unwords $ map Git.Ref.describe tomerge)
let si = SeekInput []
starting "merge" ai si $
next $ merge currbranch mergeconfig o Git.Branch.ManualCommit syncbranch
next $ merge currbranch mergeconfig o Git.Branch.ManualCommit tomerge
mergeLocal' _ _ currbranch@(Nothing, _) = inRepo Git.Branch.currentUnsafe >>= \case
Just branch -> needMerge currbranch branch >>= \case
Nothing -> stop
Just syncbranch -> do
let ai = ActionItemOther (Just $ UnquotedString $ Git.Ref.describe syncbranch)
[] -> stop
tomerge -> do
let ai = ActionItemOther (Just $ UnquotedString $ unwords $ map Git.Ref.describe tomerge)
let si = SeekInput []
starting "merge" ai si $ do
warning $ UnquotedString $ "There are no commits yet to branch " ++ Git.fromRef branch ++ ", so cannot merge " ++ Git.fromRef syncbranch ++ " into it."
warning $ UnquotedString $ "There are no commits yet to branch " ++ Git.fromRef branch ++ ", so cannot merge " ++ unwords (map Git.fromRef tomerge) ++ " into it."
next $ return False
Nothing -> stop
-- Returns the branch that should be merged, if any.
needMerge :: CurrBranch -> Git.Branch -> Annex (Maybe Git.Branch)
-- Returns the branches that should be merged, if any.
--
-- Usually this is the sync branch. However, when in an adjusted branch,
-- it can be either the sync branch or the original branch, or both.
needMerge :: CurrBranch -> Git.Branch -> Annex [Git.Branch]
needMerge currbranch headbranch
| is_branchView headbranch = return Nothing
| otherwise =
ifM (allM id checks)
( return (Just syncbranch)
, return Nothing
)
| is_branchView headbranch = return []
| otherwise = ifM isBareRepo
( return []
, do
syncbranchret <- usewhen syncbranch syncbranchchecks
adjbranchret <- case currbranch of
(Just origbranch, Just adj) ->
usewhen origbranch $
canMergeToAdjustedBranch origbranch (origbranch, adj)
_ -> return []
return (syncbranchret++adjbranchret)
)
where
usewhen v c = ifM c
( return [v]
, return []
)
syncbranch = syncBranch headbranch
checks = case currbranch of
(Just _, madj) ->
let branch' = maybe headbranch (adjBranch . originalToAdjusted headbranch) madj
in
[ not <$> isBareRepo
, inRepo (Git.Ref.exists syncbranch)
, inRepo (Git.Branch.changed branch' syncbranch)
]
(Nothing, _) ->
[ not <$> isBareRepo
, inRepo (Git.Ref.exists syncbranch)
]
syncbranchchecks = case currbranch of
(Just _, madj) -> syncbranchchanged madj
(Nothing, _) -> hassyncbranch
hassyncbranch = inRepo (Git.Ref.exists syncbranch)
syncbranchchanged madj =
let branch' = maybe headbranch (adjBranch . originalToAdjusted headbranch) madj
in hassyncbranch <&&> inRepo (Git.Branch.changed branch' syncbranch)
pushLocal :: SyncOptions -> CurrBranch -> CommandStart
pushLocal o b = stopUnless (notOnlyAnnex o) $ do
@ -631,8 +641,9 @@ mergeRemote remote currbranch mergeconfig o = ifM isBareRepo
mergelisted (tomerge (branchlist (Just branch)))
)
where
mergelisted getlist = and <$>
(mapM (merge currbranch mergeconfig o Git.Branch.ManualCommit . remoteBranch remote) =<< getlist)
mergelisted getlist =
merge currbranch mergeconfig o Git.Branch.ManualCommit
=<< map (remoteBranch remote) <$> getlist
tomerge = filterM (changed remote)
branchlist Nothing = []
branchlist (Just branch)

View file

@ -22,3 +22,5 @@ PS investigation of adjusted/unlocked came up in ReproNim context where people w
[[!meta author=yoh]]
[[!tag projects/repronim]]
> [[fixed|done]] --[[Joey]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="joey"
subject="""comment 3"""
date="2023-07-06T16:16:36Z"
content="""
Ok, fixed git-annex sync to immediately merge the changes from the original
branch into the adjusted branch.
"""]]