refactor RemoteTrackingBranch

Not specific to Import; export will use it too.
This commit is contained in:
Joey Hess 2019-03-01 14:44:22 -04:00
parent d28b0a8bd0
commit 519cadd1de
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
5 changed files with 38 additions and 15 deletions

View file

@ -8,8 +8,6 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Annex.Import ( module Annex.Import (
RemoteTrackingBranch(..),
mkRemoteTrackingBranch,
ImportTreeConfig(..), ImportTreeConfig(..),
ImportCommitConfig(..), ImportCommitConfig(..),
buildImportCommit, buildImportCommit,
@ -45,16 +43,6 @@ import qualified Database.ContentIdentifier as CID
import Control.Concurrent.STM import Control.Concurrent.STM
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
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

View file

@ -0,0 +1,34 @@
{- git-annex remote tracking branches
-
- Copyright 2019 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Annex.RemoteTrackingBranch
( RemoteTrackingBranch
, mkRemoteTrackingBranch
, fromRemoteTrackingBranch
, setRemoteTrackingBranch
) where
import Annex.Common
import Git.Types
import qualified Git.Ref
import qualified Git.Branch
import qualified Types.Remote as Remote
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 need to exist yet. -}
mkRemoteTrackingBranch :: Remote -> Branch -> RemoteTrackingBranch
mkRemoteTrackingBranch remote ref = RemoteTrackingBranch $
Git.Ref.underBase ("refs/remotes/" ++ Remote.name remote) ref
{- Set remote tracking branch to point to a commit. -}
setRemoteTrackingBranch :: RemoteTrackingBranch -> Sha -> Annex ()
setRemoteTrackingBranch tb commit =
inRepo $ Git.Branch.update' (fromRemoteTrackingBranch tb) commit

View file

@ -10,7 +10,7 @@ Copyright: © 2012-2017 Joey Hess <id@joeyh.name>
© 2014 Sören Brunk © 2014 Sören Brunk
License: AGPL-3+ License: AGPL-3+
Files: Annex/AdjustedBranch.hs Annex/AdjustedBranch/Name.hs Annex/CurrentBranch.hs Annex/Import.hs Annex/Version.hs Benchmark.hs Database/ContentIdentifier.hs Logs/File.hs Logs/Line.hs Logs/Smudge.hs Logs/ContentIdentifier.hs Logs/ContentIdentifier/Pure.hs Remote/Git.hs Remote/Helper/Ssh.hs Remote/Adb.hs Remote/External.hs Remote/Extermal/Types.hs Types/AdjustedBranch.hs Types/RepoVersion.hs Upgrade/V6.hs Files: Annex/AdjustedBranch.hs Annex/AdjustedBranch/Name.hs Annex/CurrentBranch.hs Annex/Import.hs Annex/RemoteTrackingBranch.hs Benchmark.hs Database/ContentIdentifier.hs Logs/File.hs Logs/Line.hs Logs/Smudge.hs Logs/ContentIdentifier.hs Logs/ContentIdentifier/Pure.hs Remote/Git.hs Remote/Helper/Ssh.hs Remote/Adb.hs Remote/External.hs Remote/Extermal/Types.hs Types/AdjustedBranch.hs Types/RepoVersion.hs Upgrade/V6.hs
Copyright: © 2011-2019 Joey Hess <id@joeyh.name> Copyright: © 2011-2019 Joey Hess <id@joeyh.name>
License: AGPL-3+ License: AGPL-3+

View file

@ -16,7 +16,6 @@ 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.Ref
import qualified Git.Branch
import Utility.CopyFile import Utility.CopyFile
import Backend import Backend
import Types.KeySource import Types.KeySource
@ -26,6 +25,7 @@ import Annex.FileMatcher
import Annex.Ingest import Annex.Ingest
import Annex.InodeSentinal import Annex.InodeSentinal
import Annex.Import import Annex.Import
import Annex.RemoteTrackingBranch
import Utility.InodeCache import Utility.InodeCache
import Logs.Location import Logs.Location
import Git.FilePath import Git.FilePath
@ -296,7 +296,7 @@ commitRemote remote branch tb parentcommit importtreeconfig importcommitconfig i
updateremotetrackingbranch importcommit = updateremotetrackingbranch importcommit =
case importcommit <|> parentcommit of case importcommit <|> parentcommit of
Just c -> do Just c -> do
inRepo $ Git.Branch.update' (fromRemoteTrackingBranch tb) c setRemoteTrackingBranch tb c
return True return True
Nothing -> do Nothing -> do
warning $ "Nothing to import and " ++ fromRef branch ++ " does not exist." warning $ "Nothing to import and " ++ fromRef branch ++ " does not exist."

View file

@ -650,6 +650,7 @@ Executable git-annex
Annex.Perms Annex.Perms
Annex.Queue Annex.Queue
Annex.ReplaceFile Annex.ReplaceFile
Annex.RemoteTrackingBranch
Annex.SpecialRemote Annex.SpecialRemote
Annex.Ssh Annex.Ssh
Annex.TaggedPush Annex.TaggedPush