sync --only-annex and annex.synconlyannex

* Added sync --only-annex, which syncs the git-annex branch and annexed
  content but leaves managing the other git branches up to you.
* Added annex.synconlyannex git config setting, which can also be set with
  git-annex config to configure sync in all clones of the repo.

Use case is then the user has their own git workflow, and wants to use
git-annex without disrupting that, so they sync --only-annex to get the
git-annex stuff in sync in addition to their usual git workflow.

When annex.synconlyannex is set, --not-only-annex can be used to override
it.

It's not entirely clear what --only-annex --commit or --only-annex
--push should do, and I left that combination not documented because I
don't know if I might want to change the current behavior, which is that
such options do not override the --only-annex. My gut feeling is that
there is no good reasons to use such combinations; if you want to use
your own git workflow, you'll be doing your own committing and pulling
and pushing.

A subtle question is, how should import/export special remotes be handled?
Importing updates their remote tracking branch and merges it into master.
If --only-annex prevented that git branch stuff, then it would prevent
exporting to the special remote, in the case where it has changes that
were not imported yet, because there would be a unresolved conflict.

I decided that it's best to treat the fact that there's a remote tracking
branch for import/export as an implementation detail in this case. The more
important thing is that an import/export special remote is entirely annexed
content, and so it makes a lot of sense that --only-annex will still sync
with it.
This commit is contained in:
Joey Hess 2020-02-17 15:19:58 -04:00
parent ae4177d456
commit a78eb6dd58
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
11 changed files with 177 additions and 74 deletions

View file

@ -164,7 +164,7 @@ pushToRemotes' now remotes = do
updatemap succeeded failed updatemap succeeded failed
return failed return failed
push branch remote = Command.Sync.pushBranch remote branch push branch remote = Command.Sync.pushBranch remote (Just branch)
parallelPush :: Git.Repo -> [Remote] -> (Remote -> Git.Repo -> IO Bool)-> Assistant ([Remote], [Remote]) parallelPush :: Git.Repo -> [Remote] -> (Remote -> Git.Repo -> IO Bool)-> Assistant ([Remote], [Remote])
parallelPush g rs a = do parallelPush g rs a = do

View file

@ -1,5 +1,9 @@
git-annex (7.20200205) UNRELEASED; urgency=medium git-annex (7.20200205) UNRELEASED; urgency=medium
* Added sync --only-annex, which syncs the git-annex branch and annexed
content but leaves managing the other git branches up to you.
* Added annex.synconlyannex git config setting, which can also be set with
git-annex config to configure sync in all clones of the repo.
* fsck --from remote: Fix a concurrency bug that could make it incorrectly * fsck --from remote: Fix a concurrency bug that could make it incorrectly
detect that content in the remote is corrupt, and remove it, resulting in detect that content in the remote is corrupt, and remove it, resulting in
data loss. data loss.

View file

@ -12,7 +12,7 @@ import qualified Annex.Branch
import qualified Git import qualified Git
import qualified Git.Branch import qualified Git.Branch
import Annex.CurrentBranch import Annex.CurrentBranch
import Command.Sync (prepMerge, mergeLocal, mergeConfig, merge) import Command.Sync (prepMerge, mergeLocal, mergeConfig, merge, SyncOptions(..))
cmd :: Command cmd :: Command
cmd = command "merge" SectionMaintenance cmd = command "merge" SectionMaintenance
@ -41,4 +41,5 @@ mergeSyncedBranch = mergeLocal mergeConfig def =<< getCurrentBranch
mergeBranch :: Git.Ref -> CommandStart mergeBranch :: Git.Ref -> CommandStart
mergeBranch r = starting "merge" (ActionItemOther (Just (Git.fromRef r))) $ do mergeBranch r = starting "merge" (ActionItemOther (Just (Git.fromRef r))) $ do
currbranch <- getCurrentBranch currbranch <- getCurrentBranch
next $ merge currbranch mergeConfig def Git.Branch.ManualCommit r let o = def { notOnlyAnnexOption = True }
next $ merge currbranch mergeConfig o Git.Branch.ManualCommit r

View file

@ -14,7 +14,7 @@ import qualified Annex
import Git.Types import Git.Types
import Annex.UpdateInstead import Annex.UpdateInstead
import Annex.CurrentBranch import Annex.CurrentBranch
import Command.Sync (mergeLocal, prepMerge, mergeConfig) import Command.Sync (mergeLocal, prepMerge, mergeConfig, SyncOptions(..))
-- This does not need to modify the git-annex branch to update the -- This does not need to modify the git-annex branch to update the
-- work tree, but auto-initialization might change the git-annex branch. -- work tree, but auto-initialization might change the git-annex branch.
@ -51,4 +51,5 @@ fixPostReceiveHookEnv = do
updateInsteadEmulation :: CommandStart updateInsteadEmulation :: CommandStart
updateInsteadEmulation = do updateInsteadEmulation = do
prepMerge prepMerge
mergeLocal mergeConfig def =<< getCurrentBranch let o = def { notOnlyAnnexOption = True }
mergeLocal mergeConfig o =<< getCurrentBranch

View file

@ -1,7 +1,7 @@
{- git-annex command {- git-annex command
- -
- Copyright 2011 Joachim Breitner <mail@joachim-breitner.de> - Copyright 2011 Joachim Breitner <mail@joachim-breitner.de>
- Copyright 2011-2019 Joey Hess <id@joeyh.name> - Copyright 2011-2020 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -24,6 +24,7 @@ module Command.Sync (
syncBranch, syncBranch,
updateBranches, updateBranches,
seekExportContent, seekExportContent,
SyncOptions(..),
) where ) where
import Command import Command
@ -78,8 +79,10 @@ cmd = withGlobalOptions [jobsOption] $
"synchronize local repository with remotes" "synchronize local repository with remotes"
(paramRepeating paramRemote) (seek <--< optParser) (paramRepeating paramRemote) (seek <--< optParser)
data SyncOptions = SyncOptions data SyncOptions = SyncOptions
{ syncWith :: CmdParams { syncWith :: CmdParams
, onlyAnnexOption :: Bool
, notOnlyAnnexOption :: Bool
, commitOption :: Bool , commitOption :: Bool
, noCommitOption :: Bool , noCommitOption :: Bool
, messageOption :: Maybe String , messageOption :: Maybe String
@ -90,13 +93,26 @@ data SyncOptions = SyncOptions
, contentOfOption :: [FilePath] , contentOfOption :: [FilePath]
, cleanupOption :: Bool , cleanupOption :: Bool
, keyOptions :: Maybe KeyOptions , keyOptions :: Maybe KeyOptions
, resolveMergeOverride :: ResolveMergeOverride , resolveMergeOverride :: Bool
} }
newtype ResolveMergeOverride = ResolveMergeOverride Bool instance Default SyncOptions where
def = SyncOptions
instance Default ResolveMergeOverride where { syncWith = []
def = ResolveMergeOverride False , onlyAnnexOption = False
, notOnlyAnnexOption = False
, commitOption = False
, noCommitOption = False
, messageOption = Nothing
, pullOption = False
, pushOption = False
, contentOption = False
, noContentOption = False
, contentOfOption = []
, cleanupOption = False
, keyOptions = Nothing
, resolveMergeOverride = False
}
optParser :: CmdParamsDesc -> Parser SyncOptions optParser :: CmdParamsDesc -> Parser SyncOptions
optParser desc = SyncOptions optParser desc = SyncOptions
@ -104,6 +120,15 @@ optParser desc = SyncOptions
( metavar desc ( metavar desc
<> completeRemotes <> completeRemotes
)) ))
<*> switch
( long "only-annex"
<> short 'a'
<> help "only sync git-annex branch and annexed file contents"
)
<*> switch
( long "not-only-annex"
<> help "sync git branches as well as annex"
)
<*> switch <*> switch
( long "commit" ( long "commit"
<> help "commit changes to git" <> help "commit changes to git"
@ -124,16 +149,16 @@ optParser desc = SyncOptions
) )
<*> switch <*> switch
( long "content" ( long "content"
<> help "transfer file contents" <> help "transfer annexed file contents"
) )
<*> switch <*> switch
( long "no-content" ( long "no-content"
<> help "do not transfer file contents" <> help "do not transfer annexed file contents"
) )
<*> many (strOption <*> many (strOption
( long "content-of" ( long "content-of"
<> short 'C' <> short 'C'
<> help "transfer file contents of files in a given location" <> help "transfer contents of annexed files in a given location"
<> metavar paramPath <> metavar paramPath
)) ))
<*> switch <*> switch
@ -141,15 +166,17 @@ optParser desc = SyncOptions
<> help "remove synced/ branches from previous sync" <> help "remove synced/ branches from previous sync"
) )
<*> optional parseAllOption <*> optional parseAllOption
<*> (ResolveMergeOverride <$> invertableSwitch "resolvemerge" True <*> invertableSwitch "resolvemerge" True
( help "do not automatically resolve merge conflicts" ( help "do not automatically resolve merge conflicts"
)) )
-- Since prepMerge changes the working directory, FilePath options -- Since prepMerge changes the working directory, FilePath options
-- have to be adjusted. -- have to be adjusted.
instance DeferredParseClass SyncOptions where instance DeferredParseClass SyncOptions where
finishParse v = SyncOptions finishParse v = SyncOptions
<$> pure (syncWith v) <$> pure (syncWith v)
<*> pure (onlyAnnexOption v)
<*> pure (notOnlyAnnexOption v)
<*> pure (commitOption v) <*> pure (commitOption v)
<*> pure (noCommitOption v) <*> pure (noCommitOption v)
<*> pure (messageOption v) <*> pure (messageOption v)
@ -189,7 +216,7 @@ seek' o = do
-- These actions cannot be run concurrently. -- These actions cannot be run concurrently.
mapM_ includeCommandAction $ concat mapM_ includeCommandAction $ concat
[ [ commit o ] [ [ commit o ]
, [ withbranch (mergeLocal mergeConfig (resolveMergeOverride o)) ] , [ withbranch (mergeLocal mergeConfig o) ]
, map (withbranch . pullRemote o mergeConfig) gitremotes , map (withbranch . pullRemote o mergeConfig) gitremotes
, [ mergeAnnex ] , [ mergeAnnex ]
] ]
@ -215,13 +242,14 @@ seek' o = do
, [ commitAnnex, mergeAnnex ] , [ commitAnnex, mergeAnnex ]
] ]
void $ includeCommandAction $ withbranch pushLocal void $ includeCommandAction $ withbranch $ pushLocal o
-- Pushes to remotes can run concurrently. -- Pushes to remotes can run concurrently.
mapM_ (commandAction . withbranch . pushRemote o) gitremotes mapM_ (commandAction . withbranch . pushRemote o) gitremotes
where where
shouldsynccontent = pure (contentOption o) shouldsynccontent = pure (contentOption o)
<||> pure (not (null (contentOfOption o))) <||> pure (not (null (contentOfOption o)))
<||> (pure (not (noContentOption o)) <&&> getGitConfigVal annexSyncContent) <||> (pure (not (noContentOption o)) <&&> getGitConfigVal annexSyncContent)
<||> onlyAnnex o
{- Merging may delete the current directory, so go to the top {- Merging may delete the current directory, so go to the top
- of the repo. This also means that sync always acts on all files in the - of the repo. This also means that sync always acts on all files in the
@ -241,14 +269,14 @@ mergeConfig =
, Git.Merge.MergeUnrelatedHistories , Git.Merge.MergeUnrelatedHistories
] ]
merge :: CurrBranch -> [Git.Merge.MergeConfig] -> ResolveMergeOverride -> Git.Branch.CommitMode -> Git.Branch -> Annex Bool merge :: CurrBranch -> [Git.Merge.MergeConfig] -> SyncOptions -> Git.Branch.CommitMode -> Git.Branch -> Annex Bool
merge currbranch mergeconfig resolvemergeoverride commitmode tomerge = case currbranch of merge currbranch mergeconfig o commitmode tomerge = case currbranch of
(Just b, Just adj) -> mergeToAdjustedBranch tomerge (b, adj) mergeconfig canresolvemerge commitmode (Just b, Just adj) -> mergeToAdjustedBranch tomerge (b, adj) mergeconfig canresolvemerge commitmode
(b, _) -> autoMergeFrom tomerge b mergeconfig canresolvemerge commitmode (b, _) -> autoMergeFrom tomerge b mergeconfig canresolvemerge commitmode
where where
canresolvemerge = case resolvemergeoverride of canresolvemerge = if resolveMergeOverride o
ResolveMergeOverride True -> getGitConfigVal annexResolveMerge then getGitConfigVal annexResolveMerge
ResolveMergeOverride False -> return False else return False
syncBranch :: Git.Branch -> Git.Branch syncBranch :: Git.Branch -> Git.Branch
syncBranch = Git.Ref.underBase "refs/heads/synced" . fromAdjustedBranch syncBranch = Git.Ref.underBase "refs/heads/synced" . fromAdjustedBranch
@ -296,8 +324,10 @@ commit o = stopUnless shouldcommit $ starting "commit" (ActionItemOther Nothing)
] ]
return True return True
where where
shouldcommit = pure (commitOption o) shouldcommit = notOnlyAnnex o <&&>
( pure (commitOption o)
<||> (pure (not (noCommitOption o)) <&&> getGitConfigVal annexAutoCommit) <||> (pure (not (noCommitOption o)) <&&> getGitConfigVal annexAutoCommit)
)
commitMsg :: Annex String commitMsg :: Annex String
commitMsg = do commitMsg = do
@ -316,14 +346,18 @@ commitStaged commitmode commitmessage = do
void $ inRepo $ Git.Branch.commit commitmode False commitmessage branch parents void $ inRepo $ Git.Branch.commit commitmode False commitmessage branch parents
return True return True
mergeLocal :: [Git.Merge.MergeConfig] -> ResolveMergeOverride -> CurrBranch -> CommandStart mergeLocal :: [Git.Merge.MergeConfig] -> SyncOptions -> CurrBranch -> CommandStart
mergeLocal mergeconfig resolvemergeoverride currbranch@(Just _, _) = mergeLocal mergeconfig o currbranch = stopUnless (notOnlyAnnex o) $
mergeLocal' mergeconfig o currbranch
mergeLocal' :: [Git.Merge.MergeConfig] -> SyncOptions -> CurrBranch -> CommandStart
mergeLocal' mergeconfig o currbranch@(Just _, _) =
needMerge currbranch >>= \case needMerge currbranch >>= \case
Nothing -> stop Nothing -> stop
Just syncbranch -> Just syncbranch ->
starting "merge" (ActionItemOther (Just $ Git.Ref.describe syncbranch)) $ starting "merge" (ActionItemOther (Just $ Git.Ref.describe syncbranch)) $
next $ merge currbranch mergeconfig resolvemergeoverride Git.Branch.ManualCommit syncbranch next $ merge currbranch mergeconfig o Git.Branch.ManualCommit syncbranch
mergeLocal _ _ (Nothing, madj) = do mergeLocal' _ _ (Nothing, madj) = do
b <- inRepo Git.Branch.currentUnsafe b <- inRepo Git.Branch.currentUnsafe
needMerge (b, madj) >>= \case needMerge (b, madj) >>= \case
Nothing -> stop Nothing -> stop
@ -348,8 +382,8 @@ needMerge (Just branch, madj) = ifM (allM id checks)
syncbranch = syncBranch branch syncbranch = syncBranch branch
branch' = maybe branch (adjBranch . originalToAdjusted branch) madj branch' = maybe branch (adjBranch . originalToAdjusted branch) madj
pushLocal :: CurrBranch -> CommandStart pushLocal :: SyncOptions -> CurrBranch -> CommandStart
pushLocal b = do pushLocal o b = stopUnless (notOnlyAnnex o) $ do
updateBranches b updateBranches b
stop stop
@ -388,16 +422,25 @@ pullRemote :: SyncOptions -> [Git.Merge.MergeConfig] -> Remote -> CurrBranch ->
pullRemote o mergeconfig remote branch = stopUnless (pure $ pullOption o && wantpull) $ pullRemote o mergeconfig remote branch = stopUnless (pure $ pullOption o && wantpull) $
starting "pull" (ActionItemOther (Just (Remote.name remote))) $ do starting "pull" (ActionItemOther (Just (Remote.name remote))) $ do
showOutput showOutput
ifM fetch ifM (onlyAnnex o)
( next $ mergeRemote remote branch mergeconfig (resolveMergeOverride o) ( do
, next $ return True void $ fetch $ map Git.fromRef
[ Annex.Branch.name
, syncBranch $ Annex.Branch.name
]
next $ return True
, ifM (fetch [])
( next $ mergeRemote remote branch mergeconfig o
, next $ return True
)
) )
where where
fetch = do fetch bs = do
repo <- Remote.getRepo remote repo <- Remote.getRepo remote
inRepoWithSshOptionsTo repo (Remote.gitconfig remote) $ inRepoWithSshOptionsTo repo (Remote.gitconfig remote) $
Git.Command.runBool Git.Command.runBool $
[Param "fetch", Param $ Remote.name remote] [Param "fetch", Param $ Remote.name remote]
++ map Param bs
wantpull = remoteAnnexPull (Remote.gitconfig remote) wantpull = remoteAnnexPull (Remote.gitconfig remote)
importRemote :: SyncOptions -> [Git.Merge.MergeConfig] -> Remote -> CurrBranch -> CommandSeek importRemote :: SyncOptions -> [Git.Merge.MergeConfig] -> Remote -> CurrBranch -> CommandSeek
@ -412,8 +455,7 @@ importRemote o mergeconfig remote currbranch
then Nothing then Nothing
else Just (asTopFilePath (toRawFilePath s)) else Just (asTopFilePath (toRawFilePath s))
Command.Import.seekRemote remote branch subdir Command.Import.seekRemote remote branch subdir
void $ mergeRemote remote currbranch mergeconfig void $ mergeRemote remote currbranch mergeconfig o
(resolveMergeOverride o)
where where
wantpull = remoteAnnexPull (Remote.gitconfig remote) wantpull = remoteAnnexPull (Remote.gitconfig remote)
@ -422,8 +464,8 @@ importRemote o mergeconfig remote currbranch
- were committed (or pushed changes, if this is a bare remote), - were committed (or pushed changes, if this is a bare remote),
- while the synced/master may have changes that some - while the synced/master may have changes that some
- other remote synced to this remote. So, merge them both. -} - other remote synced to this remote. So, merge them both. -}
mergeRemote :: Remote -> CurrBranch -> [Git.Merge.MergeConfig] -> ResolveMergeOverride -> CommandCleanup mergeRemote :: Remote -> CurrBranch -> [Git.Merge.MergeConfig] -> SyncOptions -> CommandCleanup
mergeRemote remote currbranch mergeconfig resolvemergeoverride = ifM isBareRepo mergeRemote remote currbranch mergeconfig o = ifM isBareRepo
( return True ( return True
, case currbranch of , case currbranch of
(Nothing, _) -> do (Nothing, _) -> do
@ -435,31 +477,37 @@ mergeRemote remote currbranch mergeconfig resolvemergeoverride = ifM isBareRepo
) )
where where
mergelisted getlist = and <$> mergelisted getlist = and <$>
(mapM (merge currbranch mergeconfig resolvemergeoverride Git.Branch.ManualCommit . remoteBranch remote) =<< getlist) (mapM (merge currbranch mergeconfig o Git.Branch.ManualCommit . remoteBranch remote) =<< getlist)
tomerge = filterM (changed remote) tomerge = filterM (changed remote)
branchlist Nothing = [] branchlist Nothing = []
branchlist (Just branch) = [fromAdjustedBranch branch, syncBranch branch] branchlist (Just branch) = [fromAdjustedBranch branch, syncBranch branch]
pushRemote :: SyncOptions -> Remote -> CurrBranch -> CommandStart pushRemote :: SyncOptions -> Remote -> CurrBranch -> CommandStart
pushRemote _o _remote (Nothing, _) = stop pushRemote _o _remote (Nothing, _) = stop
pushRemote o remote (Just branch, _) = stopUnless (pure (pushOption o) <&&> needpush) $ pushRemote o remote (Just branch, _) = do
starting "push" (ActionItemOther (Just (Remote.name remote))) $ next $ do onlyannex <- onlyAnnex o
repo <- Remote.getRepo remote let mainbranch = if onlyannex then Nothing else Just branch
showOutput stopUnless (pure (pushOption o) <&&> needpush mainbranch) $
ok <- inRepoWithSshOptionsTo repo gc $ starting "push" (ActionItemOther (Just (Remote.name remote))) $ next $ do
pushBranch remote branch repo <- Remote.getRepo remote
if ok showOutput
then postpushupdate repo ok <- inRepoWithSshOptionsTo repo gc $
else do pushBranch remote mainbranch
warning $ unwords [ "Pushing to " ++ Remote.name remote ++ " failed." ] if ok
showLongNote "(non-fast-forward problems can be solved by setting receive.denyNonFastforwards to false in the remote's git config)" then postpushupdate repo
return ok else do
warning $ unwords [ "Pushing to " ++ Remote.name remote ++ " failed." ]
showLongNote "(non-fast-forward problems can be solved by setting receive.denyNonFastforwards to false in the remote's git config)"
return ok
where where
gc = Remote.gitconfig remote gc = Remote.gitconfig remote
needpush needpush mainbranch
| remoteAnnexReadOnly gc = return False | remoteAnnexReadOnly gc = return False
| not (remoteAnnexPush gc) = return False | not (remoteAnnexPush gc) = return False
| otherwise = anyM (newer remote) [syncBranch branch, Annex.Branch.name] | otherwise = anyM (newer remote) $ catMaybes
[ syncBranch <$> mainbranch
, Just (Annex.Branch.name)
]
-- Older remotes on crippled filesystems may not have a -- Older remotes on crippled filesystems may not have a
-- post-receive hook set up, so when updateInstead emulation -- post-receive hook set up, so when updateInstead emulation
-- is needed, run post-receive manually. -- is needed, run post-receive manually.
@ -509,16 +557,17 @@ pushRemote o remote (Just branch, _) = stopUnless (pure (pushOption o) <&&> need
- The sync push will fail to overwrite if receive.denyNonFastforwards is - The sync push will fail to overwrite if receive.denyNonFastforwards is
- set on the remote. - set on the remote.
-} -}
pushBranch :: Remote -> Git.Branch -> Git.Repo -> IO Bool pushBranch :: Remote -> Maybe Git.Branch -> Git.Repo -> IO Bool
pushBranch remote branch g = directpush `after` annexpush `after` syncpush pushBranch remote mbranch g = directpush `after` annexpush `after` syncpush
where where
syncpush = flip Git.Command.runBool g $ pushparams syncpush = flip Git.Command.runBool g $ pushparams $ catMaybes
[ Git.Branch.forcePush $ refspec Annex.Branch.name [ Just $ Git.Branch.forcePush $ refspec Annex.Branch.name
, refspec $ fromAdjustedBranch branch , (refspec . fromAdjustedBranch) <$> mbranch
] ]
annexpush = void $ tryIO $ flip Git.Command.runQuiet g $ pushparams annexpush = void $ tryIO $ flip Git.Command.runQuiet g $ pushparams
[ Git.fromRef $ Git.Ref.base $ Annex.Branch.name ] [ Git.fromRef $ Git.Ref.base $ Annex.Branch.name ]
directpush = do directpush = case mbranch of
Nothing -> noop
-- Git prints out an error message when this fails. -- Git prints out an error message when this fails.
-- In the default configuration of receive.denyCurrentBranch, -- In the default configuration of receive.denyCurrentBranch,
-- the error message mentions that config setting -- the error message mentions that config setting
@ -529,11 +578,12 @@ pushBranch remote branch g = directpush `after` annexpush `after` syncpush
-- including the error displayed when -- including the error displayed when
-- receive.denyCurrentBranch=updateInstead -- the user -- receive.denyCurrentBranch=updateInstead -- the user
-- will want to see that one. -- will want to see that one.
let p = flip Git.Command.gitCreateProcess g $ pushparams Just branch -> do
[ Git.fromRef $ Git.Ref.base $ fromAdjustedBranch branch ] let p = flip Git.Command.gitCreateProcess g $ pushparams
(transcript, ok) <- processTranscript' p Nothing [ Git.fromRef $ Git.Ref.base $ fromAdjustedBranch branch ]
when (not ok && not ("denyCurrentBranch" `isInfixOf` transcript)) $ (transcript, ok) <- processTranscript' p Nothing
hPutStr stderr transcript when (not ok && not ("denyCurrentBranch" `isInfixOf` transcript)) $
hPutStr stderr transcript
pushparams branches = pushparams branches =
[ Param "push" [ Param "push"
, Param $ Remote.name remote , Param $ Remote.name remote
@ -784,3 +834,11 @@ cleanupRemote remote (Just b, _) =
, Param $ Git.fromRef $ syncBranch $ , Param $ Git.fromRef $ syncBranch $
Git.Ref.base $ Annex.Branch.name Git.Ref.base $ Annex.Branch.name
] ]
notOnlyAnnex :: SyncOptions -> Annex Bool
notOnlyAnnex o = not <$> onlyAnnex o
onlyAnnex :: SyncOptions -> Annex Bool
onlyAnnex o = do
cfg <- getGitConfigVal annexSyncOnlyAnnex
return $ not (notOnlyAnnexOption o) && (cfg || onlyAnnexOption o)

View file

@ -80,6 +80,7 @@ data GitConfig = GitConfig
, annexAutoCommit :: Configurable Bool , annexAutoCommit :: Configurable Bool
, annexResolveMerge :: Configurable Bool , annexResolveMerge :: Configurable Bool
, annexSyncContent :: Configurable Bool , annexSyncContent :: Configurable Bool
, annexSyncOnlyAnnex :: Configurable Bool
, annexDebug :: Bool , annexDebug :: Bool
, annexWebOptions :: [String] , annexWebOptions :: [String]
, annexYoutubeDlOptions :: [String] , annexYoutubeDlOptions :: [String]
@ -151,6 +152,8 @@ extractGitConfig configsource r = GitConfig
getmaybebool (annex "resolvemerge") getmaybebool (annex "resolvemerge")
, annexSyncContent = configurable False $ , annexSyncContent = configurable False $
getmaybebool (annex "synccontent") getmaybebool (annex "synccontent")
, annexSyncOnlyAnnex = configurable False $
getmaybebool (annex "synconlyannex")
, annexDebug = getbool (annex "debug") False , annexDebug = getbool (annex "debug") False
, annexWebOptions = getwords (annex "web-options") , annexWebOptions = getwords (annex "web-options")
, annexYoutubeDlOptions = getwords (annex "youtube-dl-options") , annexYoutubeDlOptions = getwords (annex "youtube-dl-options")
@ -230,6 +233,7 @@ mergeGitConfig :: GitConfig -> GitConfig -> GitConfig
mergeGitConfig gitconfig repoglobals = gitconfig mergeGitConfig gitconfig repoglobals = gitconfig
{ annexAutoCommit = merge annexAutoCommit { annexAutoCommit = merge annexAutoCommit
, annexSyncContent = merge annexSyncContent , annexSyncContent = merge annexSyncContent
, annexSyncOnlyAnnex = merge annexSyncOnlyAnnex
, annexResolveMerge = merge annexResolveMerge , annexResolveMerge = merge annexResolveMerge
, annexLargeFiles = merge annexLargeFiles , annexLargeFiles = merge annexLargeFiles
, annexAddUnlocked = merge annexAddUnlocked , annexAddUnlocked = merge annexAddUnlocked

View file

@ -64,7 +64,12 @@ These settings can be overridden on a per-repository basis using
* `annex.synccontent` * `annex.synccontent`
Set to true to make git-annex sync default to syncing content. Set to true to make git-annex sync default to syncing annexed content.
* `annex.synconlyannex`
Set to true to make git-annex sync default to only sincing the git-annex
branch and annexed content.
* `annex.securehashesonly` * `annex.securehashesonly`

View file

@ -39,9 +39,20 @@ by running "git annex sync" on the remote.
Only sync with the remotes with the lowest annex-cost value configured. Only sync with the remotes with the lowest annex-cost value configured.
* `--only-annex` `-a`, `--not-only-annex`
Only get sync the git-annex branch and annexed content with remotes.
This avoids pulling and pushing other branches, and it avoids committing
any local changes. It's up to you to use regular git commands to do that.
The `annex.synconlyannex` configuration can be set to true to make
this be the default behavior of `git-annex sync`. To override such
a setting, use `--not-only-annex`.
* `--commit`, `--no-commit` * `--commit`, `--no-commit`
A commit is done by default (unless annex.autocommit is set to false). A commit is done by default (unless `annex.autocommit` is set to false).
Use --no-commit to avoid committing local changes. Use --no-commit to avoid committing local changes.
@ -51,8 +62,8 @@ by running "git annex sync" on the remote.
* `--pull`, `--no-pull` * `--pull`, `--no-pull`
By default, git pulls from remotes and imports from some special remotes. By default, syncing pulls from remotes and imports from some special
Use --no-pull to disable all pulling. remotes. Use --no-pull to disable all pulling.
When `remote.<name>.annex-pull` or `remote.<name>.annex-sync` When `remote.<name>.annex-pull` or `remote.<name>.annex-sync`
are set to false, pulling is disabled for those remotes, and using are set to false, pulling is disabled for those remotes, and using
@ -60,7 +71,7 @@ by running "git annex sync" on the remote.
* `--push`, `--no-push` * `--push`, `--no-push`
By default, git pushes changes to remotes and exports to some By default, syncing pushes changes to remotes and exports to some
special remotes. Use --no-push to disable all pushing. special remotes. Use --no-push to disable all pushing.
When `remote.<name>.annex-push` or `remote.<name>.annex-sync` are When `remote.<name>.annex-push` or `remote.<name>.annex-sync` are
@ -128,7 +139,7 @@ by running "git annex sync" on the remote.
[[git-annex-resolvemerge]](1) for details.) [[git-annex-resolvemerge]](1) for details.)
Use `--no-resolvemerge` to disable this automatic merge conflict Use `--no-resolvemerge` to disable this automatic merge conflict
resolution. It can also be disabled by setting annex.resolvemerge resolution. It can also be disabled by setting `annex.resolvemerge`
to false. to false.
* `--cleanup` * `--cleanup`

View file

@ -1097,7 +1097,15 @@ Like other git commands, git-annex is configured via `.git/config`.
* `annex.synccontent` * `annex.synccontent`
Set to true to make git-annex sync default to syncing content. Set to true to make git-annex sync default to syncing annexed content.
To configure the behavior in all clones of the repository,
this can be set in [[git-annex-config]](1).
* `annex.synconlyannex`
Set to true to make git-annex sync default to only sincing the git-annex
branch and annexed content.
To configure the behavior in all clones of the repository, To configure the behavior in all clones of the repository,
this can be set in [[git-annex-config]](1). this can be set in [[git-annex-config]](1).

View file

@ -2,4 +2,5 @@ As we briefly discussed via email, it would be nice if sync could sync only some
[[!meta author=yoh]] [[!meta author=yoh]]
[[!tag projects/datalad]] [[!tag projects/datalad]]
[[!tag needsthought]]
> [[fixed|done]] --[[Joey]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="joey"
subject="""comment 7"""
date="2020-02-17T19:07:47Z"
content="""
Implemented --only-annex.
I'm going to close this todo, but do follow up if that does not adequately
cover your use case.
"""]]