import command is updating tracking branch
This commit is contained in:
parent
5afe4135c2
commit
e4e464da65
5 changed files with 68 additions and 21 deletions
3
Annex.hs
3
Annex.hs
|
@ -96,7 +96,8 @@ newtype Annex a = Annex { runAnnex :: ReaderT (MVar AnnexState) IO a }
|
||||||
MonadMask,
|
MonadMask,
|
||||||
Fail.MonadFail,
|
Fail.MonadFail,
|
||||||
Functor,
|
Functor,
|
||||||
Applicative
|
Applicative,
|
||||||
|
Alternative
|
||||||
)
|
)
|
||||||
|
|
||||||
-- internal state storage
|
-- internal state storage
|
||||||
|
|
|
@ -6,6 +6,8 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Annex.Import (
|
module Annex.Import (
|
||||||
|
RemoteTrackingBranch(..),
|
||||||
|
mkRemoteTrackingBranch,
|
||||||
ImportTreeConfig(..),
|
ImportTreeConfig(..),
|
||||||
ImportCommitConfig(..),
|
ImportCommitConfig(..),
|
||||||
buildImportCommit,
|
buildImportCommit,
|
||||||
|
@ -14,7 +16,7 @@ module Annex.Import (
|
||||||
|
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
import Types.Import
|
import Types.Import
|
||||||
import Types.Remote (uuid)
|
import qualified Types.Remote as Remote
|
||||||
import Git.Types
|
import Git.Types
|
||||||
import Git.Tree
|
import Git.Tree
|
||||||
import Git.Sha
|
import Git.Sha
|
||||||
|
@ -27,6 +29,16 @@ import Annex.LockFile
|
||||||
import Logs.Export
|
import Logs.Export
|
||||||
import Database.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. -}
|
{- Configures how to build an import tree. -}
|
||||||
data ImportTreeConfig
|
data ImportTreeConfig
|
||||||
= ImportTree
|
= ImportTree
|
||||||
|
@ -39,9 +51,8 @@ data ImportTreeConfig
|
||||||
|
|
||||||
{- Configures how to build an import commit. -}
|
{- Configures how to build an import commit. -}
|
||||||
data ImportCommitConfig = ImportCommitConfig
|
data ImportCommitConfig = ImportCommitConfig
|
||||||
{ importCommitParentRef :: Maybe Ref
|
{ importCommitParent :: Maybe Sha
|
||||||
-- ^ Use the commit that the Ref points to as the parent of the
|
-- ^ Commit to use as a parent of the import commit.
|
||||||
-- commit. The Ref may be a branch name.
|
|
||||||
, importCommitMode :: Git.Branch.CommitMode
|
, importCommitMode :: Git.Branch.CommitMode
|
||||||
, importCommitMessage :: String
|
, importCommitMessage :: String
|
||||||
}
|
}
|
||||||
|
@ -67,16 +78,13 @@ buildImportCommit
|
||||||
-> ImportTreeConfig
|
-> ImportTreeConfig
|
||||||
-> ImportCommitConfig
|
-> ImportCommitConfig
|
||||||
-> ImportableContents Key
|
-> ImportableContents Key
|
||||||
-> Annex (Either String (Maybe Ref))
|
-> Annex (Maybe Ref)
|
||||||
buildImportCommit remote importtreeconfig importcommitconfig importable =
|
buildImportCommit remote importtreeconfig importcommitconfig importable =
|
||||||
case importCommitParentRef importcommitconfig of
|
case importCommitParent importcommitconfig of
|
||||||
Nothing -> go emptyTree Nothing
|
Nothing -> go emptyTree Nothing
|
||||||
Just parentref -> inRepo (Git.Ref.sha parentref) >>= \case
|
Just basecommit -> inRepo (Git.Ref.tree basecommit) >>= \case
|
||||||
Nothing -> return $
|
Nothing -> go emptyTree Nothing
|
||||||
Left $ "Cannot find ref " ++ fromRef parentref
|
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
|
where
|
||||||
basetree = case importtreeconfig of
|
basetree = case importtreeconfig of
|
||||||
ImportTree -> emptyTree
|
ImportTree -> emptyTree
|
||||||
|
@ -89,11 +97,11 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
|
||||||
imported@(History finaltree _) <-
|
imported@(History finaltree _) <-
|
||||||
buildImportTrees basetree subdir importable
|
buildImportTrees basetree subdir importable
|
||||||
mkcommits origtree basecommit imported >>= \case
|
mkcommits origtree basecommit imported >>= \case
|
||||||
Nothing -> return (Right Nothing)
|
Nothing -> return Nothing
|
||||||
Just finalcommit -> do
|
Just finalcommit -> do
|
||||||
updateexportdb finaltree
|
updateexportdb finaltree
|
||||||
updateexportlog finaltree
|
updateexportlog finaltree
|
||||||
return (Right (Just finalcommit))
|
return (Just finalcommit)
|
||||||
|
|
||||||
mkcommits origtree basecommit (History importedtree hs) = do
|
mkcommits origtree basecommit (History importedtree hs) = do
|
||||||
parents <- catMaybes <$> mapM (mkcommits origtree basecommit) hs
|
parents <- catMaybes <$> mapM (mkcommits origtree basecommit) hs
|
||||||
|
@ -111,8 +119,8 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
|
||||||
return (Just commit)
|
return (Just commit)
|
||||||
|
|
||||||
updateexportdb importedtree =
|
updateexportdb importedtree =
|
||||||
withExclusiveLock (gitAnnexExportLock (uuid remote)) $ do
|
withExclusiveLock (gitAnnexExportLock (Remote.uuid remote)) $ do
|
||||||
db <- openDb (uuid remote)
|
db <- openDb (Remote.uuid remote)
|
||||||
prevtree <- liftIO $ fromMaybe emptyTree
|
prevtree <- liftIO $ fromMaybe emptyTree
|
||||||
<$> getExportTreeCurrent db
|
<$> getExportTreeCurrent db
|
||||||
when (importedtree /= prevtree) $ do
|
when (importedtree /= prevtree) $ do
|
||||||
|
@ -122,8 +130,8 @@ buildImportCommit remote importtreeconfig importcommitconfig importable =
|
||||||
liftIO $ flushDbQueue db
|
liftIO $ flushDbQueue db
|
||||||
|
|
||||||
updateexportlog importedtree = do
|
updateexportlog importedtree = do
|
||||||
old <- getExport (uuid remote)
|
old <- getExport (Remote.uuid remote)
|
||||||
recordExport (uuid remote) $ ExportChange
|
recordExport (Remote.uuid remote) $ ExportChange
|
||||||
{ oldTreeish = exportedTreeishes old
|
{ oldTreeish = exportedTreeishes old
|
||||||
, newTreeish = importedtree
|
, newTreeish = importedtree
|
||||||
}
|
}
|
||||||
|
|
|
@ -15,6 +15,8 @@ import qualified Annex
|
||||||
import qualified Command.Add
|
import qualified Command.Add
|
||||||
import qualified Command.Reinject
|
import qualified Command.Reinject
|
||||||
import qualified Types.Remote as Remote
|
import qualified Types.Remote as Remote
|
||||||
|
import qualified Git.Ref
|
||||||
|
import qualified Git.Branch
|
||||||
import Utility.CopyFile
|
import Utility.CopyFile
|
||||||
import Backend
|
import Backend
|
||||||
import Types.KeySource
|
import Types.KeySource
|
||||||
|
@ -28,6 +30,8 @@ import Utility.InodeCache
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Git.FilePath
|
import Git.FilePath
|
||||||
import Git.Types
|
import Git.Types
|
||||||
|
import Git.Branch
|
||||||
|
import Types.Import
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = notBareRepo $
|
cmd = notBareRepo $
|
||||||
|
@ -240,6 +244,29 @@ verifyExisting key destfile (yes, no) = do
|
||||||
(const yes) no
|
(const yes) no
|
||||||
|
|
||||||
startRemote :: Remote -> Branch -> Maybe TopFilePath -> CommandStart
|
startRemote :: Remote -> Branch -> Maybe TopFilePath -> CommandStart
|
||||||
startRemote remote branch subdir = do
|
startRemote remote branch msubdir = do
|
||||||
showStart' "import" (Just (Remote.name remote))
|
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
|
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)
|
||||||
|
|
|
@ -4,7 +4,7 @@ git-annex import - add files from a directory or special remote
|
||||||
|
|
||||||
# SYNOPSIS
|
# SYNOPSIS
|
||||||
|
|
||||||
git annex import `[path ...]` | git annex import branch[:subdir] --from remote
|
git annex import `[path ...]` | git annex import --from remote branch[:subdir]
|
||||||
|
|
||||||
# DESCRIPTION
|
# DESCRIPTION
|
||||||
|
|
||||||
|
|
|
@ -10,6 +10,17 @@ this.
|
||||||
|
|
||||||
## implementation notes
|
## 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
|
* Database.ContentIdentifier needs a way to update the database with
|
||||||
information coming from the git-annex branch. This will allow multiple
|
information coming from the git-annex branch. This will allow multiple
|
||||||
clones to import from the same remote, and share content identifier
|
clones to import from the same remote, and share content identifier
|
||||||
|
|
Loading…
Reference in a new issue