reuse old imported commits
This avoids proliferation of different import commits for the same trees, and makes the resulting git history nice.
This commit is contained in:
parent
4a8f02e939
commit
a32f31235a
3 changed files with 51 additions and 22 deletions
|
@ -166,30 +166,30 @@ buildImportCommit' importcommitconfig mtrackingcommit imported@(History ti _) =
|
||||||
Nothing -> Just <$> mkcommits imported
|
Nothing -> Just <$> mkcommits imported
|
||||||
Just trackingcommit -> do
|
Just trackingcommit -> do
|
||||||
-- Get history of tracking branch to at most
|
-- Get history of tracking branch to at most
|
||||||
-- one more level deep, so sametodepth will
|
-- one more level deep than what was imported,
|
||||||
-- always have enough history to compare,
|
-- so we'll have enough history to compare,
|
||||||
-- but unncessary history won't be loaded.
|
-- but not spend too much time getting it.
|
||||||
let maxdepth = succ (historyDepth imported)
|
let maxdepth = succ (historyDepth imported)
|
||||||
inRepo (getHistoryToDepth maxdepth trackingcommit)
|
inRepo (getHistoryToDepth maxdepth trackingcommit)
|
||||||
>>= go trackingcommit
|
>>= go trackingcommit
|
||||||
where
|
where
|
||||||
go _ Nothing = Just <$> mkcommits imported
|
go _ Nothing = Just <$> mkcommits imported
|
||||||
go trackingcommit (Just h)
|
go trackingcommit (Just h)
|
||||||
-- If the tracking branch matches the history,
|
|
||||||
-- nothing new needs to be committed.
|
|
||||||
| sametodepth imported h' = return Nothing
|
|
||||||
-- If the tracking branch head is a merge commit
|
-- If the tracking branch head is a merge commit
|
||||||
-- with a tree that matches the head of the history,
|
-- with a tree that matches the head of the history,
|
||||||
-- and one side of the merge matches the history,
|
-- and one side of the merge matches the history,
|
||||||
-- nothing new needs to be committed.
|
-- nothing new needs to be committed.
|
||||||
| t == ti && any (sametodepth imported) (S.toList s) = return Nothing
|
| t == ti && any (sametodepth imported) (S.toList s) = return Nothing
|
||||||
-- Make a merge commit, with one side being the import, and
|
-- If the tracking branch matches the history,
|
||||||
-- the other being the trackingcommit. This way the history
|
-- nothing new needs to be committed.
|
||||||
-- as imported is preserved, even when it differs from the
|
-- (This is unlikely to happen.)
|
||||||
-- history as exported, and git merge will understand that
|
| sametodepth imported h' = return Nothing
|
||||||
-- the history is connected.
|
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
importedcommit <- mkcommits imported
|
importedcommit <- case getRemoteTrackingBranchImportHistory h of
|
||||||
|
Nothing ->
|
||||||
|
mkcommits imported
|
||||||
|
Just oldimported ->
|
||||||
|
mknewcommits oldimported imported
|
||||||
Just <$> makeRemoteTrackingBranchMergeCommit'
|
Just <$> makeRemoteTrackingBranchMergeCommit'
|
||||||
trackingcommit importedcommit ti
|
trackingcommit importedcommit ti
|
||||||
where
|
where
|
||||||
|
@ -197,15 +197,30 @@ buildImportCommit' importcommitconfig mtrackingcommit imported@(History ti _) =
|
||||||
|
|
||||||
sametodepth a b = a == truncateHistoryToDepth (historyDepth a) b
|
sametodepth a b = a == truncateHistoryToDepth (historyDepth a) b
|
||||||
|
|
||||||
mkcommits (History importedtree hs) = do
|
|
||||||
parents <- mapM mkcommits (S.toList hs)
|
|
||||||
mkcommit parents importedtree
|
|
||||||
mkcommit parents tree = inRepo $ Git.Branch.commitTree
|
mkcommit parents tree = inRepo $ Git.Branch.commitTree
|
||||||
(importCommitMode importcommitconfig)
|
(importCommitMode importcommitconfig)
|
||||||
(importCommitMessage importcommitconfig)
|
(importCommitMessage importcommitconfig)
|
||||||
parents
|
parents
|
||||||
tree
|
tree
|
||||||
|
|
||||||
|
mkcommits (History importedtree hs) = do
|
||||||
|
parents <- mapM mkcommits (S.toList hs)
|
||||||
|
mkcommit parents importedtree
|
||||||
|
|
||||||
|
-- Reuse the commits from the oldimported History when possible.
|
||||||
|
mknewcommits old@(History oldhc _) new@(History importedtree hs)
|
||||||
|
| sameasold old new = return $ historyCommit oldhc
|
||||||
|
| otherwise = do
|
||||||
|
parents <- mapM (mknewcommits old) (S.toList hs)
|
||||||
|
mkcommit parents importedtree
|
||||||
|
|
||||||
|
-- Are the trees in the old History the same as the newly imported
|
||||||
|
-- trees, all the way down?
|
||||||
|
sameasold (History oldhc olds) (History importedtree hs)
|
||||||
|
| historyCommitTree oldhc /= importedtree = False
|
||||||
|
| otherwise = all (sameasold' olds) (S.toList hs)
|
||||||
|
sameasold' olds h = any (\old -> sameasold old h) (S.toList olds)
|
||||||
|
|
||||||
{- Builds a history of git trees reflecting the ImportableContents.
|
{- Builds a history of git trees reflecting the ImportableContents.
|
||||||
-
|
-
|
||||||
- When a subdir is provided, imported tree is grafted into the basetree at
|
- When a subdir is provided, imported tree is grafted into the basetree at
|
||||||
|
|
|
@ -12,15 +12,18 @@ module Annex.RemoteTrackingBranch
|
||||||
, setRemoteTrackingBranch
|
, setRemoteTrackingBranch
|
||||||
, makeRemoteTrackingBranchMergeCommit
|
, makeRemoteTrackingBranchMergeCommit
|
||||||
, makeRemoteTrackingBranchMergeCommit'
|
, makeRemoteTrackingBranchMergeCommit'
|
||||||
|
, getRemoteTrackingBranchImportHistory
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
import Git.Types
|
import Git.Types
|
||||||
import qualified Git.Ref
|
import qualified Git.Ref
|
||||||
import qualified Git.Branch
|
import qualified Git.Branch
|
||||||
import qualified Git.History
|
import Git.History
|
||||||
import qualified Types.Remote as Remote
|
import qualified Types.Remote as Remote
|
||||||
|
|
||||||
|
import qualified Data.Set as S
|
||||||
|
|
||||||
newtype RemoteTrackingBranch = RemoteTrackingBranch
|
newtype RemoteTrackingBranch = RemoteTrackingBranch
|
||||||
{ fromRemoteTrackingBranch :: Ref }
|
{ fromRemoteTrackingBranch :: Ref }
|
||||||
deriving (Show, Eq)
|
deriving (Show, Eq)
|
||||||
|
@ -54,9 +57,9 @@ makeRemoteTrackingBranchMergeCommit tb commitsha treesha =
|
||||||
-- Check if the tracking branch exists.
|
-- Check if the tracking branch exists.
|
||||||
inRepo (Git.Ref.sha (fromRemoteTrackingBranch tb)) >>= \case
|
inRepo (Git.Ref.sha (fromRemoteTrackingBranch tb)) >>= \case
|
||||||
Nothing -> return commitsha
|
Nothing -> return commitsha
|
||||||
Just _ -> inRepo (Git.History.getHistoryToDepth 1 (fromRemoteTrackingBranch tb)) >>= \case
|
Just _ -> inRepo (getHistoryToDepth 1 (fromRemoteTrackingBranch tb)) >>= \case
|
||||||
Nothing -> return commitsha
|
Nothing -> return commitsha
|
||||||
Just (Git.History.History hc _) -> case Git.History.historyCommitParents hc of
|
Just (History hc _) -> case historyCommitParents hc of
|
||||||
[_, importhistory] ->
|
[_, importhistory] ->
|
||||||
makeRemoteTrackingBranchMergeCommit' commitsha importhistory treesha
|
makeRemoteTrackingBranchMergeCommit' commitsha importhistory treesha
|
||||||
-- Earlier versions of git-annex did not
|
-- Earlier versions of git-annex did not
|
||||||
|
@ -72,3 +75,17 @@ makeRemoteTrackingBranchMergeCommit' commitsha importedhistory treesha =
|
||||||
"remote tracking branch"
|
"remote tracking branch"
|
||||||
[commitsha, importedhistory]
|
[commitsha, importedhistory]
|
||||||
treesha
|
treesha
|
||||||
|
|
||||||
|
{- When makeRemoteTrackingBranchMergeCommit was used, this finds the
|
||||||
|
- import history, starting from the second parent of the merge commit.
|
||||||
|
-}
|
||||||
|
getRemoteTrackingBranchImportHistory :: History HistoryCommit -> Maybe (History HistoryCommit)
|
||||||
|
getRemoteTrackingBranchImportHistory (History hc s) =
|
||||||
|
case historyCommitParents hc of
|
||||||
|
[_, importhistory] -> go importhistory (S.toList s)
|
||||||
|
_ -> Nothing
|
||||||
|
where
|
||||||
|
go _ [] = Nothing
|
||||||
|
go i (h@(History hc' _):hs)
|
||||||
|
| historyCommit hc' == i = Just h
|
||||||
|
| otherwise = go i hs
|
||||||
|
|
|
@ -13,14 +13,11 @@ and `git annex sync --content` can be configured to use it.
|
||||||
|
|
||||||
## remaining todo
|
## remaining todo
|
||||||
|
|
||||||
* When generating commits for an imported history, provide a stable author,
|
|
||||||
committer, and date, so the same commit sha1 is always generated.
|
|
||||||
|
|
||||||
* When the imported history has only one level and matches the last export,
|
* When the imported history has only one level and matches the last export,
|
||||||
there is no need to generate a merge commit, can just add a new commit on
|
there is no need to generate a merge commit, can just add a new commit on
|
||||||
top of the last export. A simple fast-forward.
|
top of the last export. A simple fast-forward.
|
||||||
|
|
||||||
* Detect more complex fast-forwards from the import? This may be hard..
|
May not be needed?
|
||||||
|
|
||||||
* S3 buckets can be set up to allow reads and listing by an anonymous user.
|
* S3 buckets can be set up to allow reads and listing by an anonymous user.
|
||||||
That should allow importing from such a bucket, but the S3 remote
|
That should allow importing from such a bucket, but the S3 remote
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue