2016-03-11 20:00:14 +00:00
|
|
|
{- adjusted branch
|
2016-02-25 20:11:13 +00:00
|
|
|
-
|
2020-10-30 17:31:35 +00:00
|
|
|
- Copyright 2016-2020 Joey Hess <id@joeyh.name>
|
2016-02-25 20:11:13 +00:00
|
|
|
-
|
2018-10-18 16:51:20 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2016-02-25 20:11:13 +00:00
|
|
|
-}
|
|
|
|
|
2020-04-07 21:41:09 +00:00
|
|
|
{-# LANGUAGE BangPatterns, OverloadedStrings #-}
|
2016-04-06 19:33:29 +00:00
|
|
|
|
2016-02-29 19:04:03 +00:00
|
|
|
module Annex.AdjustedBranch (
|
|
|
|
Adjustment(..),
|
2018-10-18 16:51:20 +00:00
|
|
|
LinkAdjustment(..),
|
|
|
|
PresenceAdjustment(..),
|
2020-11-13 18:32:06 +00:00
|
|
|
LinkPresentAdjustment(..),
|
2018-10-19 19:17:48 +00:00
|
|
|
adjustmentHidesFiles,
|
2020-11-13 18:58:42 +00:00
|
|
|
adjustmentIsStable,
|
2016-02-29 19:04:03 +00:00
|
|
|
OrigBranch,
|
2016-04-09 19:10:26 +00:00
|
|
|
AdjBranch(..),
|
2016-03-03 20:19:09 +00:00
|
|
|
originalToAdjusted,
|
2016-02-29 19:04:03 +00:00
|
|
|
adjustedToOriginal,
|
2016-03-03 18:13:54 +00:00
|
|
|
fromAdjustedBranch,
|
2016-03-29 17:26:06 +00:00
|
|
|
getAdjustment,
|
2016-02-29 19:04:03 +00:00
|
|
|
enterAdjustedBranch,
|
2018-10-20 18:12:04 +00:00
|
|
|
updateAdjustedBranch,
|
2016-04-04 17:17:24 +00:00
|
|
|
adjustBranch,
|
2016-03-29 17:52:13 +00:00
|
|
|
adjustToCrippledFileSystem,
|
2018-10-20 18:12:04 +00:00
|
|
|
mergeToAdjustedBranch,
|
2016-03-03 18:13:54 +00:00
|
|
|
propigateAdjustedCommits,
|
2016-06-02 19:58:22 +00:00
|
|
|
AdjustedClone(..),
|
2016-04-04 17:51:42 +00:00
|
|
|
checkAdjustedClone,
|
2016-04-22 16:29:32 +00:00
|
|
|
checkVersionSupported,
|
2018-12-03 16:57:23 +00:00
|
|
|
isGitVersionSupported,
|
2016-02-29 19:04:03 +00:00
|
|
|
) where
|
2016-02-25 20:11:13 +00:00
|
|
|
|
|
|
|
import Annex.Common
|
2018-10-19 19:17:48 +00:00
|
|
|
import Types.AdjustedBranch
|
|
|
|
import Annex.AdjustedBranch.Name
|
2016-02-25 20:11:13 +00:00
|
|
|
import qualified Annex
|
2016-03-03 20:19:09 +00:00
|
|
|
import Git
|
2016-02-25 20:11:13 +00:00
|
|
|
import Git.Types
|
|
|
|
import qualified Git.Branch
|
|
|
|
import qualified Git.Ref
|
|
|
|
import qualified Git.Command
|
2016-03-03 20:19:09 +00:00
|
|
|
import qualified Git.Tree
|
2016-03-11 20:00:14 +00:00
|
|
|
import qualified Git.DiffTree
|
2016-04-06 22:40:28 +00:00
|
|
|
import qualified Git.Merge
|
2016-03-03 20:19:09 +00:00
|
|
|
import Git.Tree (TreeItem(..))
|
2016-03-11 20:00:14 +00:00
|
|
|
import Git.Sha
|
2016-02-25 20:11:13 +00:00
|
|
|
import Git.Env
|
2016-03-03 16:55:00 +00:00
|
|
|
import Git.Index
|
2016-03-03 20:19:09 +00:00
|
|
|
import Git.FilePath
|
2016-03-03 16:55:00 +00:00
|
|
|
import qualified Git.LockFile
|
2016-04-22 16:29:32 +00:00
|
|
|
import qualified Git.Version
|
2016-02-25 20:11:13 +00:00
|
|
|
import Annex.CatFile
|
|
|
|
import Annex.Link
|
2016-02-29 21:16:56 +00:00
|
|
|
import Annex.AutoMerge
|
2016-03-11 23:53:18 +00:00
|
|
|
import Annex.Content
|
2019-01-17 19:40:44 +00:00
|
|
|
import Annex.Tmp
|
2016-04-06 19:33:29 +00:00
|
|
|
import Annex.GitOverlay
|
2017-12-31 20:08:31 +00:00
|
|
|
import Utility.Tmp.Dir
|
2017-05-16 18:35:37 +00:00
|
|
|
import Utility.CopyFile
|
2020-10-30 17:31:35 +00:00
|
|
|
import Utility.Directory.Create
|
2016-02-29 21:27:19 +00:00
|
|
|
import qualified Database.Keys
|
2016-06-02 21:02:38 +00:00
|
|
|
import Config
|
2016-02-25 20:11:13 +00:00
|
|
|
|
2016-03-11 20:00:14 +00:00
|
|
|
import qualified Data.Map as M
|
2020-04-07 21:41:09 +00:00
|
|
|
import qualified Data.ByteString as S
|
2020-10-30 17:31:35 +00:00
|
|
|
import qualified System.FilePath.ByteString as P
|
2016-03-11 20:00:14 +00:00
|
|
|
|
2018-10-18 16:51:20 +00:00
|
|
|
class AdjustTreeItem t where
|
2020-11-13 18:58:42 +00:00
|
|
|
-- How to perform various adjustments to a TreeItem.
|
2018-10-18 16:51:20 +00:00
|
|
|
adjustTreeItem :: t -> TreeItem -> Annex (Maybe TreeItem)
|
2020-11-13 18:58:42 +00:00
|
|
|
-- Will adjusting a given tree always yield the same adjusted tree?
|
|
|
|
adjustmentIsStable :: t -> Bool
|
2018-10-18 16:51:20 +00:00
|
|
|
|
|
|
|
instance AdjustTreeItem Adjustment where
|
|
|
|
adjustTreeItem (LinkAdjustment l) t = adjustTreeItem l t
|
|
|
|
adjustTreeItem (PresenceAdjustment p Nothing) t = adjustTreeItem p t
|
|
|
|
adjustTreeItem (PresenceAdjustment p (Just l)) t =
|
|
|
|
adjustTreeItem p t >>= \case
|
|
|
|
Nothing -> return Nothing
|
|
|
|
Just t' -> adjustTreeItem l t'
|
2020-11-13 18:32:06 +00:00
|
|
|
adjustTreeItem (LinkPresentAdjustment l) t = adjustTreeItem l t
|
2018-10-18 16:51:20 +00:00
|
|
|
|
2020-11-13 18:58:42 +00:00
|
|
|
adjustmentIsStable (LinkAdjustment l) = adjustmentIsStable l
|
|
|
|
adjustmentIsStable (PresenceAdjustment p _) = adjustmentIsStable p
|
|
|
|
adjustmentIsStable (LinkPresentAdjustment l) = adjustmentIsStable l
|
|
|
|
|
2018-10-18 16:51:20 +00:00
|
|
|
instance AdjustTreeItem LinkAdjustment where
|
2020-11-13 17:27:03 +00:00
|
|
|
adjustTreeItem UnlockAdjustment =
|
|
|
|
ifSymlink adjustToPointer noAdjust
|
|
|
|
adjustTreeItem LockAdjustment =
|
|
|
|
ifSymlink noAdjust adjustToSymlink
|
|
|
|
adjustTreeItem FixAdjustment =
|
|
|
|
ifSymlink adjustToSymlink noAdjust
|
|
|
|
adjustTreeItem UnFixAdjustment =
|
|
|
|
ifSymlink (adjustToSymlink' gitAnnexLinkCanonical) noAdjust
|
2020-11-13 18:58:42 +00:00
|
|
|
|
|
|
|
adjustmentIsStable _ = True
|
2018-10-18 16:51:20 +00:00
|
|
|
|
|
|
|
instance AdjustTreeItem PresenceAdjustment where
|
2020-11-13 17:27:03 +00:00
|
|
|
adjustTreeItem HideMissingAdjustment =
|
|
|
|
ifPresent noAdjust hideAdjust
|
|
|
|
adjustTreeItem ShowMissingAdjustment =
|
|
|
|
noAdjust
|
|
|
|
|
2020-11-13 18:58:42 +00:00
|
|
|
adjustmentIsStable HideMissingAdjustment = False
|
|
|
|
adjustmentIsStable ShowMissingAdjustment = True
|
|
|
|
|
2020-11-13 18:32:06 +00:00
|
|
|
instance AdjustTreeItem LinkPresentAdjustment where
|
|
|
|
adjustTreeItem UnlockPresentAdjustment =
|
2020-11-13 17:27:03 +00:00
|
|
|
ifPresent adjustToPointer adjustToSymlink
|
2020-11-13 18:32:06 +00:00
|
|
|
adjustTreeItem LockPresentAdjustment =
|
|
|
|
-- Turn all pointers back to symlinks, whether the content
|
|
|
|
-- is present or not. This is done because the content
|
|
|
|
-- availability may have changed and the branch not been
|
|
|
|
-- re-adjusted to keep up, so there may be pointers whose
|
|
|
|
-- content is not present.
|
|
|
|
ifSymlink noAdjust adjustToSymlink
|
2020-11-13 17:27:03 +00:00
|
|
|
|
2020-11-13 18:58:42 +00:00
|
|
|
adjustmentIsStable UnlockPresentAdjustment = False
|
|
|
|
adjustmentIsStable LockPresentAdjustment = True
|
|
|
|
|
2020-11-13 17:27:03 +00:00
|
|
|
ifSymlink
|
|
|
|
:: (TreeItem -> Annex a)
|
|
|
|
-> (TreeItem -> Annex a)
|
|
|
|
-> TreeItem
|
|
|
|
-> Annex a
|
2016-05-16 21:05:42 +00:00
|
|
|
ifSymlink issymlink notsymlink ti@(TreeItem _f m _s)
|
2018-05-14 18:22:44 +00:00
|
|
|
| toTreeItemType m == Just TreeSymlink = issymlink ti
|
2016-05-16 21:05:42 +00:00
|
|
|
| otherwise = notsymlink ti
|
|
|
|
|
2020-11-13 17:27:03 +00:00
|
|
|
ifPresent
|
|
|
|
:: (TreeItem -> Annex (Maybe TreeItem))
|
|
|
|
-> (TreeItem -> Annex (Maybe TreeItem))
|
|
|
|
-> TreeItem
|
|
|
|
-> Annex (Maybe TreeItem)
|
|
|
|
ifPresent ispresent notpresent ti@(TreeItem _ _ s) =
|
|
|
|
catKey s >>= \case
|
|
|
|
Just k -> ifM (inAnnex k) (ispresent ti, notpresent ti)
|
|
|
|
Nothing -> return (Just ti)
|
|
|
|
|
2016-05-16 21:05:42 +00:00
|
|
|
noAdjust :: TreeItem -> Annex (Maybe TreeItem)
|
|
|
|
noAdjust = return . Just
|
|
|
|
|
2020-11-13 17:27:03 +00:00
|
|
|
hideAdjust :: TreeItem -> Annex (Maybe TreeItem)
|
|
|
|
hideAdjust _ = return Nothing
|
|
|
|
|
2016-05-16 21:05:42 +00:00
|
|
|
adjustToPointer :: TreeItem -> Annex (Maybe TreeItem)
|
2017-11-15 20:55:38 +00:00
|
|
|
adjustToPointer ti@(TreeItem f _m s) = catKey s >>= \case
|
|
|
|
Just k -> do
|
|
|
|
Database.Keys.addAssociatedFile k f
|
2018-05-14 18:22:44 +00:00
|
|
|
Just . TreeItem f (fromTreeItemType TreeFile)
|
2017-11-15 20:55:38 +00:00
|
|
|
<$> hashPointerFile k
|
|
|
|
Nothing -> return (Just ti)
|
2016-05-16 21:05:42 +00:00
|
|
|
|
|
|
|
adjustToSymlink :: TreeItem -> Annex (Maybe TreeItem)
|
|
|
|
adjustToSymlink = adjustToSymlink' gitAnnexLink
|
|
|
|
|
2020-10-30 17:31:35 +00:00
|
|
|
adjustToSymlink' :: (RawFilePath -> Key -> Git.Repo -> GitConfig -> IO RawFilePath) -> TreeItem -> Annex (Maybe TreeItem)
|
2017-11-15 20:55:38 +00:00
|
|
|
adjustToSymlink' gitannexlink ti@(TreeItem f _m s) = catKey s >>= \case
|
|
|
|
Just k -> do
|
2020-10-30 17:31:35 +00:00
|
|
|
absf <- inRepo $ \r -> absPath $ fromTopFilePath f r
|
2017-11-15 20:55:38 +00:00
|
|
|
linktarget <- calcRepo $ gitannexlink absf k
|
2018-05-14 18:22:44 +00:00
|
|
|
Just . TreeItem f (fromTreeItemType TreeSymlink)
|
2017-11-15 20:55:38 +00:00
|
|
|
<$> hashSymlink linktarget
|
|
|
|
Nothing -> return (Just ti)
|
2016-02-25 20:11:13 +00:00
|
|
|
|
2016-04-09 18:12:25 +00:00
|
|
|
-- This is a hidden branch ref, that's used as the basis for the AdjBranch,
|
|
|
|
-- since pushes can overwrite the OrigBranch at any time. So, changes
|
|
|
|
-- are propigated from the AdjBranch to the head of the BasisBranch.
|
|
|
|
newtype BasisBranch = BasisBranch Ref
|
|
|
|
|
|
|
|
-- The basis for refs/heads/adjusted/master(unlocked) is
|
2016-04-09 18:17:20 +00:00
|
|
|
-- refs/basis/adjusted/master(unlocked).
|
2016-04-09 18:12:25 +00:00
|
|
|
basisBranch :: AdjBranch -> BasisBranch
|
2016-04-09 19:10:26 +00:00
|
|
|
basisBranch (AdjBranch adjbranch) = BasisBranch $
|
2020-04-07 21:41:09 +00:00
|
|
|
Ref ("refs/basis/" <> fromRef' (Git.Ref.base adjbranch))
|
2016-04-09 18:12:25 +00:00
|
|
|
|
2016-03-29 17:26:06 +00:00
|
|
|
getAdjustment :: Branch -> Maybe Adjustment
|
|
|
|
getAdjustment = fmap fst . adjustedToOriginal
|
|
|
|
|
2016-04-09 19:10:26 +00:00
|
|
|
fromAdjustedBranch :: Branch -> OrigBranch
|
2016-03-03 18:13:54 +00:00
|
|
|
fromAdjustedBranch b = maybe b snd (adjustedToOriginal b)
|
|
|
|
|
2016-02-25 20:11:13 +00:00
|
|
|
{- Enter an adjusted version of current branch (or, if already in an
|
|
|
|
- adjusted version of a branch, changes the adjustment of the original
|
2016-04-09 18:12:25 +00:00
|
|
|
- branch).
|
2016-02-25 20:11:13 +00:00
|
|
|
-
|
2016-05-13 18:04:22 +00:00
|
|
|
- Can fail, if no branch is checked out, or if the adjusted branch already
|
2018-10-18 19:32:42 +00:00
|
|
|
- exists, or if staged changes prevent a checkout.
|
2016-02-25 20:11:13 +00:00
|
|
|
-}
|
2016-05-13 18:04:22 +00:00
|
|
|
enterAdjustedBranch :: Adjustment -> Annex Bool
|
2018-10-18 19:32:42 +00:00
|
|
|
enterAdjustedBranch adj = inRepo Git.Branch.current >>= \case
|
|
|
|
Just currbranch -> case getAdjustment currbranch of
|
|
|
|
Just curradj | curradj == adj ->
|
2018-10-20 18:12:04 +00:00
|
|
|
updateAdjustedBranch adj (AdjBranch currbranch)
|
2018-10-18 19:32:42 +00:00
|
|
|
(fromAdjustedBranch currbranch)
|
|
|
|
_ -> go currbranch
|
|
|
|
Nothing -> do
|
|
|
|
warning "not on any branch!"
|
|
|
|
return False
|
2016-02-25 20:11:13 +00:00
|
|
|
where
|
2018-10-18 19:32:42 +00:00
|
|
|
go currbranch = do
|
|
|
|
let origbranch = fromAdjustedBranch currbranch
|
2016-05-13 18:04:22 +00:00
|
|
|
let adjbranch = adjBranch $ originalToAdjusted origbranch adj
|
2016-05-23 15:23:30 +00:00
|
|
|
ifM (inRepo (Git.Ref.exists adjbranch) <&&> (not <$> Annex.getState Annex.force))
|
2016-05-13 18:04:22 +00:00
|
|
|
( do
|
|
|
|
mapM_ (warning . unwords)
|
|
|
|
[ [ "adjusted branch"
|
|
|
|
, Git.Ref.describe adjbranch
|
|
|
|
, "already exists."
|
|
|
|
]
|
|
|
|
, [ "Aborting because that branch may have changes that have not yet reached"
|
|
|
|
, Git.Ref.describe origbranch
|
|
|
|
]
|
|
|
|
, [ "You can check out the adjusted branch manually to enter it,"
|
2018-10-20 15:53:35 +00:00
|
|
|
, "or add the --force option to overwrite the old branch."
|
2016-05-13 18:04:22 +00:00
|
|
|
]
|
|
|
|
]
|
|
|
|
return False
|
|
|
|
, do
|
2018-10-18 19:32:42 +00:00
|
|
|
b <- preventCommits $ const $
|
2016-05-13 18:04:22 +00:00
|
|
|
adjustBranch adj origbranch
|
2018-10-18 19:32:42 +00:00
|
|
|
checkoutAdjustedBranch b []
|
2016-05-13 18:04:22 +00:00
|
|
|
)
|
2018-10-18 19:32:42 +00:00
|
|
|
|
|
|
|
checkoutAdjustedBranch :: AdjBranch -> [CommandParam] -> Annex Bool
|
|
|
|
checkoutAdjustedBranch (AdjBranch b) checkoutparams = do
|
|
|
|
showOutput -- checkout can have output in large repos
|
|
|
|
inRepo $ Git.Command.runBool $
|
|
|
|
[ Param "checkout"
|
|
|
|
, Param $ fromRef $ Git.Ref.base b
|
|
|
|
-- always show checkout progress, even if --quiet is used
|
|
|
|
-- to suppress other messages
|
|
|
|
, Param "--progress"
|
|
|
|
] ++ checkoutparams
|
|
|
|
|
|
|
|
{- Already in a branch with this adjustment, but the user asked to enter it
|
2020-11-13 18:58:42 +00:00
|
|
|
- again. This should have the same result as propagating any commits
|
|
|
|
- back to the original branch, checking out the original branch, deleting
|
|
|
|
- and rebuilding the adjusted branch, and then checking it out.
|
2018-10-18 19:32:42 +00:00
|
|
|
- But, it can be implemented more efficiently than that.
|
|
|
|
-}
|
2018-10-20 18:12:04 +00:00
|
|
|
updateAdjustedBranch :: Adjustment -> AdjBranch -> OrigBranch -> Annex Bool
|
2020-11-13 18:58:42 +00:00
|
|
|
updateAdjustedBranch adj (AdjBranch currbranch) origbranch
|
|
|
|
| not (adjustmentIsStable adj) = do
|
|
|
|
b <- preventCommits $ \commitlck -> do
|
|
|
|
-- Avoid losing any commits that the adjusted branch
|
|
|
|
-- has that have not yet been propigated back to the
|
|
|
|
-- origbranch.
|
|
|
|
_ <- propigateAdjustedCommits' origbranch adj commitlck
|
2018-10-18 19:32:42 +00:00
|
|
|
|
2020-11-13 18:58:42 +00:00
|
|
|
-- Git normally won't do anything when asked to check
|
|
|
|
-- out the currently checked out branch, even when its
|
|
|
|
-- ref has changed. Work around this by writing a raw
|
|
|
|
-- sha to .git/HEAD.
|
|
|
|
inRepo (Git.Ref.sha currbranch) >>= \case
|
|
|
|
Just headsha -> inRepo $ \r ->
|
|
|
|
writeFile (Git.Ref.headFile r) (fromRef headsha)
|
|
|
|
_ -> noop
|
2018-10-18 19:32:42 +00:00
|
|
|
|
2020-11-13 18:58:42 +00:00
|
|
|
adjustBranch adj origbranch
|
2018-10-18 19:32:42 +00:00
|
|
|
|
2020-11-13 18:58:42 +00:00
|
|
|
-- Make git checkout quiet to avoid warnings about
|
|
|
|
-- disconnected branch tips being lost.
|
|
|
|
checkoutAdjustedBranch b [Param "--quiet"]
|
|
|
|
| otherwise = preventCommits $ \commitlck -> do
|
|
|
|
-- Done for consistency.
|
|
|
|
_ <- propigateAdjustedCommits' origbranch adj commitlck
|
|
|
|
-- No need to actually update the branch because the
|
|
|
|
-- adjustment is stable.
|
|
|
|
return True
|
2016-02-25 20:11:13 +00:00
|
|
|
|
2016-03-29 17:52:13 +00:00
|
|
|
adjustToCrippledFileSystem :: Annex ()
|
|
|
|
adjustToCrippledFileSystem = do
|
|
|
|
warning "Entering an adjusted branch where files are unlocked as this filesystem does not support locked files."
|
2018-12-03 16:57:23 +00:00
|
|
|
checkVersionSupported
|
2019-11-11 20:15:05 +00:00
|
|
|
whenM (isNothing <$> inRepo Git.Branch.current) $ do
|
2019-11-11 22:20:35 +00:00
|
|
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
2019-11-11 20:15:05 +00:00
|
|
|
void $ inRepo $ Git.Branch.commitCommand cmode
|
2016-03-29 17:52:13 +00:00
|
|
|
[ Param "--quiet"
|
|
|
|
, Param "--allow-empty"
|
|
|
|
, Param "-m"
|
|
|
|
, Param "commit before entering adjusted unlocked branch"
|
|
|
|
]
|
init: Fix a failure when used in a submodule on a crippled filesystem.
When the submodule's parent repo has an adjusted unlocked branch,
it gets cloned by git, but git checks out master. git annex init then
fails because it wants to enter the adjusted branch, but:
adjusted branch adjusted/master(unlocked) already exists.
Aborting because that branch may have changes that have not yet reached master
Note that init actually then exits 0, leaving master checked out.
This could also happen, absent submodules, if the parent repo has
an adjusted unlocked branch, but it is not checked out. In the more common
case where that branch is checked out, the clone uses the same branch,
so no problem.
The choices to fix this:
* Init could delete the existing adjusted branch, and re-adjust.
But then running init inside an adjusted branch on a crippled filesystem
would lose any changes that have not been synced back to master.
* Init could sync any changes back to master, but that would be very surprising
behavior for it.
* Init could simply check out the existing adjusted branch. If the branch
is diverged from master, well, sync will sort that out later.
This mirrors the behavior of cloning a repo that has an adjusted branch
checked out that has not yet been synced back to master.
Picked this choice.
2019-10-21 15:04:24 +00:00
|
|
|
inRepo Git.Branch.current >>= \case
|
|
|
|
Just currbranch -> case getAdjustment currbranch of
|
|
|
|
Just curradj | curradj == adj -> return ()
|
|
|
|
_ -> do
|
|
|
|
let adjbranch = originalToAdjusted currbranch adj
|
|
|
|
ifM (inRepo (Git.Ref.exists $ adjBranch adjbranch))
|
|
|
|
( unlessM (checkoutAdjustedBranch adjbranch []) $
|
|
|
|
failedenter
|
|
|
|
, unlessM (enterAdjustedBranch adj) $
|
|
|
|
failedenter
|
|
|
|
)
|
|
|
|
Nothing -> failedenter
|
|
|
|
where
|
|
|
|
adj = LinkAdjustment UnlockAdjustment
|
|
|
|
failedenter = warning "Failed to enter adjusted branch!"
|
2016-03-29 17:52:13 +00:00
|
|
|
|
2016-04-09 19:10:26 +00:00
|
|
|
setBasisBranch :: BasisBranch -> Ref -> Annex ()
|
|
|
|
setBasisBranch (BasisBranch basis) new =
|
2016-04-09 18:12:25 +00:00
|
|
|
inRepo $ Git.Branch.update' basis new
|
|
|
|
|
2016-04-09 19:10:26 +00:00
|
|
|
setAdjustedBranch :: String -> AdjBranch -> Ref -> Annex ()
|
|
|
|
setAdjustedBranch msg (AdjBranch b) r = inRepo $ Git.Branch.update msg b r
|
|
|
|
|
2016-03-11 23:41:11 +00:00
|
|
|
adjustBranch :: Adjustment -> OrigBranch -> Annex AdjBranch
|
|
|
|
adjustBranch adj origbranch = do
|
2016-04-09 18:12:25 +00:00
|
|
|
-- Start basis off with the current value of the origbranch.
|
2016-04-09 19:10:26 +00:00
|
|
|
setBasisBranch basis origbranch
|
2016-04-09 18:12:25 +00:00
|
|
|
sha <- adjustCommit adj basis
|
2016-04-09 19:10:26 +00:00
|
|
|
setAdjustedBranch "entering adjusted branch" adjbranch sha
|
2016-02-25 20:11:13 +00:00
|
|
|
return adjbranch
|
|
|
|
where
|
2016-02-29 19:04:03 +00:00
|
|
|
adjbranch = originalToAdjusted origbranch adj
|
2016-04-09 18:12:25 +00:00
|
|
|
basis = basisBranch adjbranch
|
2016-02-25 20:11:13 +00:00
|
|
|
|
2016-04-09 18:12:25 +00:00
|
|
|
adjustCommit :: Adjustment -> BasisBranch -> Annex Sha
|
|
|
|
adjustCommit adj basis = do
|
|
|
|
treesha <- adjustTree adj basis
|
|
|
|
commitAdjustedTree treesha basis
|
2016-03-03 20:19:09 +00:00
|
|
|
|
2016-04-09 18:12:25 +00:00
|
|
|
adjustTree :: Adjustment -> BasisBranch -> Annex Sha
|
|
|
|
adjustTree adj (BasisBranch basis) = do
|
2016-03-29 15:15:21 +00:00
|
|
|
let toadj = adjustTreeItem adj
|
2019-05-20 20:37:04 +00:00
|
|
|
treesha <- Git.Tree.adjustTree
|
|
|
|
toadj
|
|
|
|
[]
|
|
|
|
(\_old new -> new)
|
|
|
|
[]
|
|
|
|
basis =<< Annex.gitRepo
|
2016-03-03 20:19:09 +00:00
|
|
|
return treesha
|
2016-02-29 21:16:56 +00:00
|
|
|
|
2016-03-11 20:00:14 +00:00
|
|
|
type CommitsPrevented = Git.LockFile.LockHandle
|
|
|
|
|
2016-03-03 16:55:00 +00:00
|
|
|
{- Locks git's index file, preventing git from making a commit, merge,
|
|
|
|
- or otherwise changing the HEAD ref while the action is run.
|
|
|
|
-
|
|
|
|
- Throws an IO exception if the index file is already locked.
|
|
|
|
-}
|
2016-03-11 20:00:14 +00:00
|
|
|
preventCommits :: (CommitsPrevented -> Annex a) -> Annex a
|
|
|
|
preventCommits = bracket setup cleanup
|
2016-03-03 16:55:00 +00:00
|
|
|
where
|
|
|
|
setup = do
|
2018-08-17 20:03:40 +00:00
|
|
|
lck <- fromRepo $ indexFileLock . indexFile
|
2020-11-06 18:10:58 +00:00
|
|
|
liftIO $ Git.LockFile.openLock (fromRawFilePath lck)
|
2016-03-11 20:00:14 +00:00
|
|
|
cleanup = liftIO . Git.LockFile.closeLock
|
2016-03-03 16:55:00 +00:00
|
|
|
|
2016-02-25 20:11:13 +00:00
|
|
|
{- Commits a given adjusted tree, with the provided parent ref.
|
|
|
|
-
|
|
|
|
- This should always yield the same value, even if performed in different
|
|
|
|
- clones of a repo, at different times. The commit message and other
|
|
|
|
- metadata is based on the parent.
|
|
|
|
-}
|
2016-04-09 18:12:25 +00:00
|
|
|
commitAdjustedTree :: Sha -> BasisBranch -> Annex Sha
|
|
|
|
commitAdjustedTree treesha parent@(BasisBranch b) =
|
|
|
|
commitAdjustedTree' treesha parent [b]
|
2016-03-31 22:54:35 +00:00
|
|
|
|
2016-04-09 18:12:25 +00:00
|
|
|
commitAdjustedTree' :: Sha -> BasisBranch -> [Ref] -> Annex Sha
|
|
|
|
commitAdjustedTree' treesha (BasisBranch basis) parents =
|
|
|
|
go =<< catCommit basis
|
2016-02-25 20:11:13 +00:00
|
|
|
where
|
2019-11-11 20:15:05 +00:00
|
|
|
go Nothing = do
|
2019-11-11 22:20:35 +00:00
|
|
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
2019-11-11 20:15:05 +00:00
|
|
|
inRepo $ mkcommit cmode
|
|
|
|
go (Just basiscommit) = do
|
2019-11-11 22:20:35 +00:00
|
|
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
2019-11-11 20:15:05 +00:00
|
|
|
inRepo $ commitWithMetaData
|
|
|
|
(commitAuthorMetaData basiscommit)
|
|
|
|
(commitCommitterMetaData basiscommit)
|
|
|
|
(mkcommit cmode)
|
|
|
|
mkcommit cmode = Git.Branch.commitTree cmode
|
2016-03-31 22:54:35 +00:00
|
|
|
adjustedBranchCommitMessage parents treesha
|
2016-03-03 20:19:09 +00:00
|
|
|
|
2016-06-09 18:11:00 +00:00
|
|
|
{- This message should never be changed. -}
|
2016-03-03 20:19:09 +00:00
|
|
|
adjustedBranchCommitMessage :: String
|
|
|
|
adjustedBranchCommitMessage = "git-annex adjusted branch"
|
2016-02-29 19:04:03 +00:00
|
|
|
|
2016-06-09 18:11:00 +00:00
|
|
|
findAdjustingCommit :: AdjBranch -> Annex (Maybe Commit)
|
|
|
|
findAdjustingCommit (AdjBranch b) = go =<< catCommit b
|
|
|
|
where
|
|
|
|
go Nothing = return Nothing
|
|
|
|
go (Just c)
|
|
|
|
| commitMessage c == adjustedBranchCommitMessage = return (Just c)
|
|
|
|
| otherwise = case commitParent c of
|
|
|
|
[p] -> go =<< catCommit p
|
|
|
|
_ -> return Nothing
|
|
|
|
|
2016-02-29 19:04:03 +00:00
|
|
|
{- Update the currently checked out adjusted branch, merging the provided
|
2016-04-06 19:33:29 +00:00
|
|
|
- branch into it. Note that the provided branch should be a non-adjusted
|
|
|
|
- branch. -}
|
2020-09-07 17:26:16 +00:00
|
|
|
mergeToAdjustedBranch :: Branch -> (OrigBranch, Adjustment) -> [Git.Merge.MergeConfig] -> Bool -> Git.Branch.CommitMode -> Annex Bool
|
2018-10-20 18:12:04 +00:00
|
|
|
mergeToAdjustedBranch tomerge (origbranch, adj) mergeconfig canresolvemerge commitmode = catchBoolIO $
|
2016-04-09 19:10:26 +00:00
|
|
|
join $ preventCommits go
|
2016-02-29 21:16:56 +00:00
|
|
|
where
|
2016-04-09 19:10:26 +00:00
|
|
|
adjbranch@(AdjBranch currbranch) = originalToAdjusted origbranch adj
|
2016-04-09 18:12:25 +00:00
|
|
|
basis = basisBranch adjbranch
|
|
|
|
|
2016-04-09 19:10:26 +00:00
|
|
|
go commitsprevented =
|
2016-04-06 19:33:29 +00:00
|
|
|
ifM (inRepo $ Git.Branch.changed currbranch tomerge)
|
2016-03-11 20:00:14 +00:00
|
|
|
( do
|
2016-04-09 18:12:25 +00:00
|
|
|
(updatedorig, _) <- propigateAdjustedCommits'
|
2016-04-09 19:10:26 +00:00
|
|
|
origbranch adj commitsprevented
|
|
|
|
changestomerge updatedorig
|
2016-03-31 16:04:05 +00:00
|
|
|
, nochangestomerge
|
2016-03-11 20:00:14 +00:00
|
|
|
)
|
2016-04-06 19:33:29 +00:00
|
|
|
|
2016-03-31 16:04:05 +00:00
|
|
|
nochangestomerge = return $ return True
|
2016-03-31 22:54:35 +00:00
|
|
|
|
2016-04-06 19:33:29 +00:00
|
|
|
{- Since the adjusted branch changes files, merging tomerge
|
|
|
|
- directly into it would likely result in unncessary merge
|
|
|
|
- conflicts. To avoid those conflicts, instead merge tomerge into
|
|
|
|
- updatedorig. The result of the merge can the be
|
|
|
|
- adjusted to yield the final adjusted branch.
|
|
|
|
-
|
2016-04-09 18:12:25 +00:00
|
|
|
- In order to do a merge into a ref that is not checked out,
|
2016-04-06 19:33:29 +00:00
|
|
|
- set the work tree to a temp directory, and set GIT_DIR
|
|
|
|
- to another temp directory, in which HEAD contains the
|
|
|
|
- updatedorig sha. GIT_COMMON_DIR is set to point to the real
|
|
|
|
- git directory, and so git can read and write objects from there,
|
|
|
|
- but will use GIT_DIR for HEAD and index.
|
2016-02-29 21:16:56 +00:00
|
|
|
-
|
2016-04-06 19:33:29 +00:00
|
|
|
- (Doing the merge this way also lets it run even though the main
|
|
|
|
- index file is currently locked.)
|
2016-02-29 21:16:56 +00:00
|
|
|
-}
|
2019-01-17 19:40:44 +00:00
|
|
|
changestomerge (Just updatedorig) = withOtherTmp $ \othertmpdir -> do
|
2020-10-30 17:31:35 +00:00
|
|
|
git_dir <- fromRepo Git.localGitDir
|
|
|
|
let git_dir' = fromRawFilePath git_dir
|
2020-03-05 18:56:47 +00:00
|
|
|
tmpwt <- fromRepo gitAnnexMergeDir
|
2020-10-30 17:31:35 +00:00
|
|
|
withTmpDirIn (fromRawFilePath othertmpdir) "git" $ \tmpgit -> withWorkTreeRelated tmpgit $
|
2020-03-05 18:56:47 +00:00
|
|
|
withemptydir git_dir tmpwt $ withWorkTree tmpwt $ do
|
2016-04-06 19:33:29 +00:00
|
|
|
liftIO $ writeFile (tmpgit </> "HEAD") (fromRef updatedorig)
|
2017-05-16 18:35:37 +00:00
|
|
|
-- Copy in refs and packed-refs, to work
|
|
|
|
-- around bug in git 2.13.0, which
|
|
|
|
-- causes it not to look in GIT_DIR for refs.
|
|
|
|
refs <- liftIO $ dirContentsRecursive $
|
2020-10-30 17:31:35 +00:00
|
|
|
git_dir' </> "refs"
|
|
|
|
let refs' = (git_dir' </> "packed-refs") : refs
|
2017-05-16 18:35:37 +00:00
|
|
|
liftIO $ forM_ refs' $ \src ->
|
|
|
|
whenM (doesFileExist src) $ do
|
2020-10-30 17:31:35 +00:00
|
|
|
dest <- relPathDirToFile git_dir
|
|
|
|
(toRawFilePath src)
|
|
|
|
let dest' = toRawFilePath tmpgit P.</> dest
|
|
|
|
createDirectoryUnder git_dir
|
|
|
|
(P.takeDirectory dest')
|
|
|
|
void $ createLinkOrCopy src
|
|
|
|
(fromRawFilePath dest')
|
2016-06-13 18:18:22 +00:00
|
|
|
-- This reset makes git merge not care
|
|
|
|
-- that the work tree is empty; otherwise
|
|
|
|
-- it will think that all the files have
|
|
|
|
-- been staged for deletion, and sometimes
|
|
|
|
-- the merge includes these deletions
|
|
|
|
-- (for an unknown reason).
|
|
|
|
-- http://thread.gmane.org/gmane.comp.version-control.git/297237
|
|
|
|
inRepo $ Git.Command.run [Param "reset", Param "HEAD", Param "--quiet"]
|
2016-04-06 19:33:29 +00:00
|
|
|
showAction $ "Merging into " ++ fromRef (Git.Ref.base origbranch)
|
2020-09-07 17:50:58 +00:00
|
|
|
merged <- autoMergeFrom' tomerge Nothing mergeconfig commitmode True
|
2020-09-07 17:26:16 +00:00
|
|
|
(const $ resolveMerge (Just updatedorig) tomerge True)
|
2016-04-06 22:40:28 +00:00
|
|
|
if merged
|
|
|
|
then do
|
2020-04-07 21:41:09 +00:00
|
|
|
!mergecommit <- liftIO $ extractSha
|
|
|
|
<$> S.readFile (tmpgit </> "HEAD")
|
2016-04-06 19:33:29 +00:00
|
|
|
-- This is run after the commit lock is dropped.
|
2016-04-09 19:10:26 +00:00
|
|
|
return $ postmerge mergecommit
|
2016-04-06 22:40:28 +00:00
|
|
|
else return $ return False
|
2016-04-09 19:10:26 +00:00
|
|
|
changestomerge Nothing = return $ return False
|
2016-04-06 19:33:29 +00:00
|
|
|
|
2020-03-05 18:56:47 +00:00
|
|
|
withemptydir git_dir d a = bracketIO setup cleanup (const a)
|
2016-04-06 19:33:29 +00:00
|
|
|
where
|
|
|
|
setup = do
|
|
|
|
whenM (doesDirectoryExist d) $
|
|
|
|
removeDirectoryRecursive d
|
2020-10-30 17:31:35 +00:00
|
|
|
createDirectoryUnder git_dir (toRawFilePath d)
|
2016-04-06 19:33:29 +00:00
|
|
|
cleanup _ = removeDirectoryRecursive d
|
2016-02-29 21:16:56 +00:00
|
|
|
|
2016-04-09 18:12:25 +00:00
|
|
|
{- A merge commit has been made between the basisbranch and
|
|
|
|
- tomerge. Update the basisbranch and origbranch to point
|
|
|
|
- to that commit, adjust it to get the new adjusted branch,
|
|
|
|
- and check it out.
|
2016-04-06 19:33:29 +00:00
|
|
|
-
|
|
|
|
- But, there may be unstaged work tree changes that conflict,
|
|
|
|
- so the check out is done by making a normal merge of
|
|
|
|
- the new adjusted branch.
|
2016-03-31 22:54:35 +00:00
|
|
|
-}
|
2016-04-09 19:10:26 +00:00
|
|
|
postmerge (Just mergecommit) = do
|
|
|
|
setBasisBranch basis mergecommit
|
2016-04-09 18:12:25 +00:00
|
|
|
inRepo $ Git.Branch.update' origbranch mergecommit
|
|
|
|
adjtree <- adjustTree adj (BasisBranch mergecommit)
|
|
|
|
adjmergecommit <- commitAdjustedTree adjtree (BasisBranch mergecommit)
|
2016-04-06 23:22:15 +00:00
|
|
|
-- Make currbranch be the parent, so that merging
|
2016-04-06 19:33:29 +00:00
|
|
|
-- this commit will be a fast-forward.
|
2016-04-09 18:12:25 +00:00
|
|
|
adjmergecommitff <- commitAdjustedTree' adjtree (BasisBranch mergecommit) [currbranch]
|
2016-04-06 19:33:29 +00:00
|
|
|
showAction "Merging into adjusted branch"
|
2020-09-07 17:26:16 +00:00
|
|
|
ifM (autoMergeFrom adjmergecommitff (Just currbranch) mergeconfig commitmode canresolvemerge)
|
2016-04-09 19:10:26 +00:00
|
|
|
( reparent adjtree adjmergecommit =<< getcurrentcommit
|
2016-04-06 19:33:29 +00:00
|
|
|
, return False
|
|
|
|
)
|
2016-04-09 19:10:26 +00:00
|
|
|
postmerge Nothing = return False
|
2016-03-31 22:54:35 +00:00
|
|
|
|
2016-04-06 23:22:15 +00:00
|
|
|
-- Now that the merge into the adjusted branch is complete,
|
|
|
|
-- take the tree from that merge, and attach it on top of the
|
|
|
|
-- adjmergecommit, if it's different.
|
2016-04-09 19:10:26 +00:00
|
|
|
reparent adjtree adjmergecommit (Just currentcommit) = do
|
2016-04-06 23:22:15 +00:00
|
|
|
if (commitTree currentcommit /= adjtree)
|
|
|
|
then do
|
2019-11-11 22:20:35 +00:00
|
|
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
2019-11-11 20:15:05 +00:00
|
|
|
c <- inRepo $ Git.Branch.commitTree cmode
|
2016-04-06 23:22:15 +00:00
|
|
|
("Merged " ++ fromRef tomerge) [adjmergecommit]
|
|
|
|
(commitTree currentcommit)
|
|
|
|
inRepo $ Git.Branch.update "updating adjusted branch" currbranch c
|
2016-04-09 19:10:26 +00:00
|
|
|
propigateAdjustedCommits origbranch adj
|
2016-04-06 23:22:15 +00:00
|
|
|
else inRepo $ Git.Branch.update "updating adjusted branch" currbranch adjmergecommit
|
|
|
|
return True
|
2016-04-09 19:10:26 +00:00
|
|
|
reparent _ _ Nothing = return False
|
2016-04-06 23:22:15 +00:00
|
|
|
|
2017-11-15 20:55:38 +00:00
|
|
|
getcurrentcommit = inRepo Git.Branch.currentUnsafe >>= \case
|
|
|
|
Nothing -> return Nothing
|
|
|
|
Just c -> catCommit c
|
2016-04-06 23:22:15 +00:00
|
|
|
|
2016-02-29 21:16:56 +00:00
|
|
|
{- Check for any commits present on the adjusted branch that have not yet
|
2016-04-09 18:12:25 +00:00
|
|
|
- been propigated to the basis branch, and propigate them to the basis
|
|
|
|
- branch and from there on to the orig branch.
|
2016-03-03 20:19:09 +00:00
|
|
|
-
|
2016-04-09 18:12:25 +00:00
|
|
|
- After propigating the commits back to the basis banch,
|
|
|
|
- rebase the adjusted branch on top of the updated basis branch.
|
2016-03-03 20:19:09 +00:00
|
|
|
-}
|
2016-04-09 19:10:26 +00:00
|
|
|
propigateAdjustedCommits :: OrigBranch -> Adjustment -> Annex ()
|
|
|
|
propigateAdjustedCommits origbranch adj =
|
2016-04-06 19:33:29 +00:00
|
|
|
preventCommits $ \commitsprevented ->
|
2016-04-09 19:10:26 +00:00
|
|
|
join $ snd <$> propigateAdjustedCommits' origbranch adj commitsprevented
|
2016-03-31 22:54:35 +00:00
|
|
|
|
2016-04-09 18:12:25 +00:00
|
|
|
{- Returns sha of updated basis branch, and action which will rebase
|
|
|
|
- the adjusted branch on top of the updated basis branch. -}
|
2016-03-31 22:54:35 +00:00
|
|
|
propigateAdjustedCommits'
|
|
|
|
:: OrigBranch
|
2016-04-09 19:10:26 +00:00
|
|
|
-> Adjustment
|
2016-03-31 22:54:35 +00:00
|
|
|
-> CommitsPrevented
|
2016-04-06 19:33:29 +00:00
|
|
|
-> Annex (Maybe Sha, Annex ())
|
2017-11-15 20:55:38 +00:00
|
|
|
propigateAdjustedCommits' origbranch adj _commitsprevented =
|
|
|
|
inRepo (Git.Ref.sha basis) >>= \case
|
|
|
|
Just origsha -> catCommit currbranch >>= \case
|
|
|
|
Just currcommit ->
|
|
|
|
newcommits >>= go origsha False >>= \case
|
|
|
|
Left e -> do
|
|
|
|
warning e
|
|
|
|
return (Nothing, return ())
|
|
|
|
Right newparent -> return
|
|
|
|
( Just newparent
|
|
|
|
, rebase currcommit newparent
|
|
|
|
)
|
|
|
|
Nothing -> return (Nothing, return ())
|
2016-04-06 19:33:29 +00:00
|
|
|
Nothing -> return (Nothing, return ())
|
2016-03-03 20:19:09 +00:00
|
|
|
where
|
2016-04-09 18:12:25 +00:00
|
|
|
(BasisBranch basis) = basisBranch adjbranch
|
2016-04-09 19:10:26 +00:00
|
|
|
adjbranch@(AdjBranch currbranch) = originalToAdjusted origbranch adj
|
2016-04-09 18:12:25 +00:00
|
|
|
newcommits = inRepo $ Git.Branch.changedCommits basis currbranch
|
2016-03-03 20:19:09 +00:00
|
|
|
-- Get commits oldest first, so they can be processed
|
|
|
|
-- in order made.
|
|
|
|
[Param "--reverse"]
|
2016-03-29 15:15:21 +00:00
|
|
|
go parent _ [] = do
|
2016-04-09 19:10:26 +00:00
|
|
|
setBasisBranch (BasisBranch basis) parent
|
2016-04-09 18:12:25 +00:00
|
|
|
inRepo $ Git.Branch.update' origbranch parent
|
2016-03-11 20:00:14 +00:00
|
|
|
return (Right parent)
|
2017-11-15 20:55:38 +00:00
|
|
|
go parent pastadjcommit (sha:l) = catCommit sha >>= \case
|
|
|
|
Just c
|
|
|
|
| commitMessage c == adjustedBranchCommitMessage ->
|
|
|
|
go parent True l
|
|
|
|
| pastadjcommit ->
|
|
|
|
reverseAdjustedCommit parent adj (sha, c) origbranch
|
|
|
|
>>= \case
|
2016-03-11 20:00:14 +00:00
|
|
|
Left e -> return (Left e)
|
2016-03-29 15:15:21 +00:00
|
|
|
Right commit -> go commit pastadjcommit l
|
2017-11-15 20:55:38 +00:00
|
|
|
_ -> go parent pastadjcommit l
|
2016-03-03 21:00:48 +00:00
|
|
|
rebase currcommit newparent = do
|
2016-04-09 18:12:25 +00:00
|
|
|
-- Reuse the current adjusted tree, and reparent it
|
|
|
|
-- on top of the newparent.
|
|
|
|
commitAdjustedTree (commitTree currcommit) (BasisBranch newparent)
|
2016-03-31 22:54:35 +00:00
|
|
|
>>= inRepo . Git.Branch.update rebaseOnTopMsg currbranch
|
2016-03-03 20:19:09 +00:00
|
|
|
|
2016-03-31 22:54:35 +00:00
|
|
|
rebaseOnTopMsg :: String
|
|
|
|
rebaseOnTopMsg = "rebasing adjusted branch on top of updated original branch"
|
|
|
|
|
|
|
|
{- Reverses an adjusted commit, and commit with provided commitparent,
|
2016-03-11 20:00:14 +00:00
|
|
|
- yielding a commit sha.
|
|
|
|
-
|
2016-03-31 22:54:35 +00:00
|
|
|
- Adjusts the tree of the commitparent, changing only the files that the
|
2016-03-11 20:00:14 +00:00
|
|
|
- commit changed, and reverse adjusting those changes.
|
2016-03-03 20:19:09 +00:00
|
|
|
-
|
2016-03-31 22:54:35 +00:00
|
|
|
- The commit message, and the author and committer metadata are
|
|
|
|
- copied over from the basiscommit. However, any gpg signature
|
|
|
|
- will be lost, and any other headers are not copied either. -}
|
2016-03-29 15:15:21 +00:00
|
|
|
reverseAdjustedCommit :: Sha -> Adjustment -> (Sha, Commit) -> OrigBranch -> Annex (Either String Sha)
|
2016-03-31 22:54:35 +00:00
|
|
|
reverseAdjustedCommit commitparent adj (csha, basiscommit) origbranch
|
|
|
|
| length (commitParent basiscommit) > 1 = return $
|
2016-03-11 20:00:14 +00:00
|
|
|
Left $ "unable to propigate merge commit " ++ show csha ++ " back to " ++ show origbranch
|
|
|
|
| otherwise = do
|
2019-11-11 22:20:35 +00:00
|
|
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
2016-03-31 22:54:35 +00:00
|
|
|
treesha <- reverseAdjustedTree commitparent adj csha
|
2016-03-11 20:00:14 +00:00
|
|
|
revadjcommit <- inRepo $ commitWithMetaData
|
2016-03-31 22:54:35 +00:00
|
|
|
(commitAuthorMetaData basiscommit)
|
|
|
|
(commitCommitterMetaData basiscommit) $
|
2019-11-11 20:15:05 +00:00
|
|
|
Git.Branch.commitTree cmode
|
|
|
|
(commitMessage basiscommit)
|
|
|
|
[commitparent] treesha
|
2016-03-11 20:00:14 +00:00
|
|
|
return (Right revadjcommit)
|
2016-03-31 22:54:35 +00:00
|
|
|
|
|
|
|
{- Adjusts the tree of the basis, changing only the files that the
|
|
|
|
- commit changed, and reverse adjusting those changes.
|
|
|
|
-
|
|
|
|
- commitDiff does not support merge commits, so the csha must not be a
|
|
|
|
- merge commit. -}
|
|
|
|
reverseAdjustedTree :: Sha -> Adjustment -> Sha -> Annex Sha
|
|
|
|
reverseAdjustedTree basis adj csha = do
|
|
|
|
(diff, cleanup) <- inRepo (Git.DiffTree.commitDiff csha)
|
2020-01-07 15:35:17 +00:00
|
|
|
let (adds, others) = partition (\dti -> Git.DiffTree.srcsha dti `elem` nullShas) diff
|
|
|
|
let (removes, changes) = partition (\dti -> Git.DiffTree.dstsha dti `elem` nullShas) others
|
2016-03-31 22:54:35 +00:00
|
|
|
adds' <- catMaybes <$>
|
|
|
|
mapM (adjustTreeItem reverseadj) (map diffTreeToTreeItem adds)
|
|
|
|
treesha <- Git.Tree.adjustTree
|
|
|
|
(propchanges changes)
|
|
|
|
adds'
|
2019-05-20 20:37:04 +00:00
|
|
|
(\_old new -> new)
|
2016-03-31 22:54:35 +00:00
|
|
|
(map Git.DiffTree.file removes)
|
|
|
|
basis
|
|
|
|
=<< Annex.gitRepo
|
|
|
|
void $ liftIO cleanup
|
|
|
|
return treesha
|
2016-03-11 20:00:14 +00:00
|
|
|
where
|
2016-03-11 23:41:11 +00:00
|
|
|
reverseadj = reverseAdjustment adj
|
2016-03-11 20:00:14 +00:00
|
|
|
propchanges changes ti@(TreeItem f _ _) =
|
2016-05-04 16:57:07 +00:00
|
|
|
case M.lookup (norm f) m of
|
2016-03-11 20:00:14 +00:00
|
|
|
Nothing -> return (Just ti) -- not changed
|
2016-03-29 15:15:21 +00:00
|
|
|
Just change -> adjustTreeItem reverseadj change
|
2016-03-11 20:00:14 +00:00
|
|
|
where
|
2016-05-04 16:57:07 +00:00
|
|
|
m = M.fromList $ map (\i@(TreeItem f' _ _) -> (norm f', i)) $
|
2016-03-11 20:00:14 +00:00
|
|
|
map diffTreeToTreeItem changes
|
2019-12-09 17:49:05 +00:00
|
|
|
norm = normalise . fromRawFilePath . getTopFilePath
|
2016-03-11 20:00:14 +00:00
|
|
|
|
|
|
|
diffTreeToTreeItem :: Git.DiffTree.DiffTreeItem -> TreeItem
|
|
|
|
diffTreeToTreeItem dti = TreeItem
|
|
|
|
(Git.DiffTree.file dti)
|
|
|
|
(Git.DiffTree.dstmode dti)
|
|
|
|
(Git.DiffTree.dstsha dti)
|
2016-04-04 17:51:42 +00:00
|
|
|
|
2019-08-30 17:54:57 +00:00
|
|
|
data AdjustedClone = InAdjustedClone | NotInAdjustedClone
|
2016-06-02 19:58:22 +00:00
|
|
|
|
2016-04-04 17:51:42 +00:00
|
|
|
{- Cloning a repository that has an adjusted branch checked out will
|
|
|
|
- result in the clone having the same adjusted branch checked out -- but
|
2016-06-09 18:11:00 +00:00
|
|
|
- the origbranch won't exist in the clone, nor will the basis. So
|
|
|
|
- to properly set up the adjusted branch, the origbranch and basis need
|
|
|
|
- to be set.
|
|
|
|
-
|
|
|
|
- We can't trust that the origin's origbranch matches up with the currently
|
|
|
|
- checked out adjusted branch; the origin could have the two branches
|
|
|
|
- out of sync (eg, due to another branch having been pushed to the origin's
|
|
|
|
- origbranch), or due to a commit on its adjusted branch not having been
|
|
|
|
- propigated back to origbranch.
|
|
|
|
-
|
|
|
|
- So, find the adjusting commit on the currently checked out adjusted
|
|
|
|
- branch, and use the parent of that commit as the basis, and set the
|
|
|
|
- origbranch to it.
|
2016-06-02 19:34:30 +00:00
|
|
|
-
|
|
|
|
- The repository may also need to be upgraded to a new version, if the
|
2016-06-09 18:11:00 +00:00
|
|
|
- current version is too old to support adjusted branches. -}
|
2016-06-02 19:58:22 +00:00
|
|
|
checkAdjustedClone :: Annex AdjustedClone
|
2016-06-02 21:02:38 +00:00
|
|
|
checkAdjustedClone = ifM isBareRepo
|
|
|
|
( return NotInAdjustedClone
|
|
|
|
, go =<< inRepo Git.Branch.current
|
|
|
|
)
|
2016-04-04 17:51:42 +00:00
|
|
|
where
|
2016-06-02 19:58:22 +00:00
|
|
|
go Nothing = return NotInAdjustedClone
|
2016-04-04 17:51:42 +00:00
|
|
|
go (Just currbranch) = case adjustedToOriginal currbranch of
|
2016-06-02 19:58:22 +00:00
|
|
|
Nothing -> return NotInAdjustedClone
|
2016-04-09 18:12:25 +00:00
|
|
|
Just (adj, origbranch) -> do
|
|
|
|
let basis@(BasisBranch bb) = basisBranch (originalToAdjusted origbranch adj)
|
2016-06-09 18:11:00 +00:00
|
|
|
unlessM (inRepo $ Git.Ref.exists bb) $ do
|
|
|
|
unlessM (inRepo $ Git.Ref.exists origbranch) $ do
|
|
|
|
let remotebranch = Git.Ref.underBase "refs/remotes/origin" origbranch
|
|
|
|
inRepo $ Git.Branch.update' origbranch remotebranch
|
|
|
|
aps <- fmap commitParent <$> findAdjustingCommit (AdjBranch currbranch)
|
|
|
|
case aps of
|
|
|
|
Just [p] -> setBasisBranch basis p
|
2016-11-16 01:29:54 +00:00
|
|
|
_ -> giveup $ "Unable to clean up from clone of adjusted branch; perhaps you should check out " ++ Git.Ref.describe origbranch
|
2019-08-30 17:54:57 +00:00
|
|
|
return InAdjustedClone
|
2016-04-22 16:29:32 +00:00
|
|
|
|
|
|
|
checkVersionSupported :: Annex ()
|
2019-08-30 17:54:57 +00:00
|
|
|
checkVersionSupported =
|
2016-04-22 16:29:32 +00:00
|
|
|
unlessM (liftIO isGitVersionSupported) $
|
2016-11-16 01:29:54 +00:00
|
|
|
giveup "Your version of git is too old; upgrade it to 2.2.0 or newer to use adjusted branches."
|
2018-10-22 20:51:09 +00:00
|
|
|
|
|
|
|
-- git 2.2.0 needed for GIT_COMMON_DIR which is needed
|
|
|
|
-- by updateAdjustedBranch to use withWorkTreeRelated.
|
|
|
|
isGitVersionSupported :: IO Bool
|
|
|
|
isGitVersionSupported = not <$> Git.Version.older "2.2.0"
|