import command is updating tracking branch

This commit is contained in:
Joey Hess 2019-02-26 13:11:25 -04:00
parent 5afe4135c2
commit e4e464da65
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
5 changed files with 68 additions and 21 deletions

View file

@ -96,7 +96,8 @@ newtype Annex a = Annex { runAnnex :: ReaderT (MVar AnnexState) IO a }
MonadMask,
Fail.MonadFail,
Functor,
Applicative
Applicative,
Alternative
)
-- internal state storage

View file

@ -6,6 +6,8 @@
-}
module Annex.Import (
RemoteTrackingBranch(..),
mkRemoteTrackingBranch,
ImportTreeConfig(..),
ImportCommitConfig(..),
buildImportCommit,
@ -14,7 +16,7 @@ module Annex.Import (
import Annex.Common
import Types.Import
import Types.Remote (uuid)
import qualified Types.Remote as Remote
import Git.Types
import Git.Tree
import Git.Sha
@ -27,6 +29,16 @@ import Annex.LockFile
import Logs.Export
import Database.Export
newtype RemoteTrackingBranch = RemoteTrackingBranch
{ fromRemoteTrackingBranch :: Ref }
deriving (Show, Eq)
{- Makes a remote tracking branch corresponding to a local branch.
- Note that the local branch does not have to exist yet. -}
mkRemoteTrackingBranch :: Remote -> Ref -> RemoteTrackingBranch
mkRemoteTrackingBranch remote ref = RemoteTrackingBranch $
Git.Ref.underBase ("refs/remotes/" ++ Remote.name remote) ref
{- Configures how to build an import tree. -}
data ImportTreeConfig
= ImportTree
@ -39,9 +51,8 @@ data ImportTreeConfig
{- Configures how to build an import commit. -}
data ImportCommitConfig = ImportCommitConfig
{ importCommitParentRef :: Maybe Ref
-- ^ Use the commit that the Ref points to as the parent of the
-- commit. The Ref may be a branch name.
{ importCommitParent :: Maybe Sha
-- ^ Commit to use as a parent of the import commit.
, importCommitMode :: Git.Branch.CommitMode
, importCommitMessage :: String
}
@ -67,16 +78,13 @@ buildImportCommit
-> ImportTreeConfig
-> ImportCommitConfig
-> ImportableContents Key
-> Annex (Either String (Maybe Ref))
-> Annex (Maybe Ref)
buildImportCommit remote importtreeconfig importcommitconfig importable =
case importCommitParentRef importcommitconfig of
case importCommitParent importcommitconfig of
Nothing -> go emptyTree Nothing
Just parentref -> inRepo (Git.Ref.sha parentref) >>= \case
Nothing -> return $
Left $ "Cannot find ref " ++ fromRef parentref
Just basecommit -> inRepo (Git.Ref.tree basecommit) >>= \case
Nothing -> go emptyTree Nothing
Just origtree -> go origtree (Just basecommit)
Just basecommit -> inRepo (Git.Ref.tree basecommit) >>= \case
Nothing -> go emptyTree Nothing
Just origtree -> go origtree (Just basecommit)
where
basetree = case importtreeconfig of
ImportTree -> emptyTree
@ -89,11 +97,11 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
imported@(History finaltree _) <-
buildImportTrees basetree subdir importable
mkcommits origtree basecommit imported >>= \case
Nothing -> return (Right Nothing)
Nothing -> return Nothing
Just finalcommit -> do
updateexportdb finaltree
updateexportlog finaltree
return (Right (Just finalcommit))
return (Just finalcommit)
mkcommits origtree basecommit (History importedtree hs) = do
parents <- catMaybes <$> mapM (mkcommits origtree basecommit) hs
@ -111,8 +119,8 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
return (Just commit)
updateexportdb importedtree =
withExclusiveLock (gitAnnexExportLock (uuid remote)) $ do
db <- openDb (uuid remote)
withExclusiveLock (gitAnnexExportLock (Remote.uuid remote)) $ do
db <- openDb (Remote.uuid remote)
prevtree <- liftIO $ fromMaybe emptyTree
<$> getExportTreeCurrent db
when (importedtree /= prevtree) $ do
@ -122,8 +130,8 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
liftIO $ flushDbQueue db
updateexportlog importedtree = do
old <- getExport (uuid remote)
recordExport (uuid remote) $ ExportChange
old <- getExport (Remote.uuid remote)
recordExport (Remote.uuid remote) $ ExportChange
{ oldTreeish = exportedTreeishes old
, newTreeish = importedtree
}

View file

@ -15,6 +15,8 @@ import qualified Annex
import qualified Command.Add
import qualified Command.Reinject
import qualified Types.Remote as Remote
import qualified Git.Ref
import qualified Git.Branch
import Utility.CopyFile
import Backend
import Types.KeySource
@ -28,6 +30,8 @@ import Utility.InodeCache
import Logs.Location
import Git.FilePath
import Git.Types
import Git.Branch
import Types.Import
cmd :: Command
cmd = notBareRepo $
@ -240,6 +244,29 @@ verifyExisting key destfile (yes, no) = do
(const yes) no
startRemote :: Remote -> Branch -> Maybe TopFilePath -> CommandStart
startRemote remote branch subdir = do
startRemote remote branch msubdir = do
showStart' "import" (Just (Remote.name remote))
importtreeconfig <- case msubdir of
Nothing -> return ImportTree
Just subdir -> frombranch Git.Ref.tree >>= \case
Nothing -> giveup $ "Unable to find base tree for branch " ++ fromRef branch
Just tree -> pure $ ImportSubTree subdir tree
parentcommit <- frombranch Git.Ref.sha
let importcommitconfig = ImportCommitConfig parentcommit ManualCommit importmessage
-- TODO enumerate and download
let importable = ImportableContents [] []
importcommit <- buildImportCommit remote importtreeconfig importcommitconfig importable
-- Update the tracking branch. Done even when there is nothing new
-- to import, to make sure it exists.
inRepo $ Git.Branch.update importmessage (fromRemoteTrackingBranch tb) $
fromMaybe (giveup $ "Nothing to import and " ++ fromRef branch ++ " does not exist.") $
importcommit <|> parentcommit
next stop
where
importmessage = "import from " ++ Remote.name remote
tb = mkRemoteTrackingBranch remote branch
-- If the remote tracking branch already exists, get from it,
-- otherwise get from the branch.
frombranch a = inRepo (a (fromRemoteTrackingBranch tb)) >>= \case
Just v -> return (Just v)
Nothing -> inRepo (a branch)

View file

@ -4,7 +4,7 @@ git-annex import - add files from a directory or special remote
# SYNOPSIS
git annex import `[path ...]` | git annex import branch[:subdir] --from remote
git annex import `[path ...]` | git annex import --from remote branch[:subdir]
# DESCRIPTION

View file

@ -10,6 +10,17 @@ this.
## implementation notes
* "git annex import master --from rmt" followed by "git annex import master:sub --from rmt"
first makes the tracking branch contain only what's in the remote,
and then grafts what's in the remote into a subdir. Is that the behavior
a user would expect, or would they instead expect that importing to a new
place starts the tracking branch over fresh on the contents of master?
Hmm, one way to look at it is that if there was a merge from
refs/remotes/rmt/master in between the two commands, and then after, the
result would be the same as if there was only a merge after. So the
current behavior seems to make sense.
* Database.ContentIdentifier needs a way to update the database with
information coming from the git-annex branch. This will allow multiple
clones to import from the same remote, and share content identifier