remove --backend from global options

--backend is no longer a global option, and is only accepted by commands
that actually need it.

Three commands that used to support backend but don't any longer are
watch, webapp, and assistant. It would be possible to make them support it,
but I doubt anyone used the option with these. And in the case of webapp
and assistant, the option was handled inconsistently, only taking affect
when the command is run with an existing git-annex repo, not when it
creates a new one.

Also, renamed GlobalOption etc to AnnexOption. Because there are many
options of this type that are not actually global (any more) and get
added to commands that need them.

Sponsored-by: Kevin Mueller on Patreon
This commit is contained in:
Joey Hess 2022-06-29 13:28:08 -04:00
parent 3eecf2033a
commit b223988e22
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
49 changed files with 209 additions and 196 deletions

View file

@ -3,6 +3,8 @@ git-annex (10.20220625) UNRELEASED; urgency=medium
* Improve handling of parallelization with -J when copying content * Improve handling of parallelization with -J when copying content
from/to a git remote that is a local path. from/to a git remote that is a local path.
* stack.yaml: Updated to lts-19.13 * stack.yaml: Updated to lts-19.13
* --backend is no longer a global option, and is only accepted by
commands that actually need it.
-- Joey Hess <id@joeyh.name> Tue, 28 Jun 2022 14:49:17 -0400 -- Joey Hess <id@joeyh.name> Tue, 28 Jun 2022 14:49:17 -0400

View file

@ -53,14 +53,14 @@ dispatch' subcommandname args fuzzy cmds allargs allcmds fields getgitrepo progn
where where
go (Right g) = do go (Right g) = do
g' <- Git.Config.read g g' <- Git.Config.read g
(cmd, seek, globalsetter) <- parsewith False cmdparser (cmd, seek, annexsetter) <- parsewith False cmdparser
(\a -> a (Just g')) (\a -> a (Just g'))
O.handleParseResult O.handleParseResult
state <- applyAnnexReadSetter globalsetter <$> Annex.new g' state <- applyAnnexReadSetter annexsetter <$> Annex.new g'
Annex.eval state $ do Annex.eval state $ do
checkEnvironment checkEnvironment
forM_ fields $ uncurry Annex.setField forM_ fields $ uncurry Annex.setField
prepRunCommand cmd globalsetter prepRunCommand cmd annexsetter
startup startup
performCommandAction True cmd seek $ performCommandAction True cmd seek $
shutdown $ cmdnocommit cmd shutdown $ cmdnocommit cmd
@ -101,7 +101,7 @@ dispatch' subcommandname args fuzzy cmds allargs allcmds fields getgitrepo progn
Just n -> n:args Just n -> n:args
{- Parses command line, selecting one of the commands from the list. -} {- Parses command line, selecting one of the commands from the list. -}
parseCmd :: String -> String -> CmdParams -> [Command] -> (Command -> O.Parser v) -> O.ParserResult (Command, v, GlobalSetter) parseCmd :: String -> String -> CmdParams -> [Command] -> (Command -> O.Parser v) -> O.ParserResult (Command, v, AnnexSetter)
parseCmd progname progdesc allargs allcmds getparser = parseCmd progname progdesc allargs allcmds getparser =
O.execParserPure (O.prefs O.idm) pinfo allargs O.execParserPure (O.prefs O.idm) pinfo allargs
where where
@ -114,7 +114,7 @@ parseCmd progname progdesc allargs allcmds getparser =
mkparser c = (,,) mkparser c = (,,)
<$> pure c <$> pure c
<*> getparser c <*> getparser c
<*> parserGlobalOptions (cmdglobaloptions c) <*> parserAnnexOptions (cmdannexoptions c)
synopsis n d = n ++ " - " ++ d synopsis n d = n ++ " - " ++ d
intro = mconcat $ concatMap (\l -> [H.text l, H.line]) intro = mconcat $ concatMap (\l -> [H.text l, H.line])
(synopsis progname progdesc : commandList allcmds) (synopsis progname progdesc : commandList allcmds)
@ -141,14 +141,14 @@ subCmdName argv = (name, args)
| "-" `isPrefixOf` a = findname as (a:c) | "-" `isPrefixOf` a = findname as (a:c)
| otherwise = (Just a, reverse c ++ as) | otherwise = (Just a, reverse c ++ as)
-- | Note that the GlobalSetter must have already had its annexReadSetter -- | Note that the AnnexSetter must have already had its annexReadSetter
-- applied before entering the Annex monad to run this; that cannot be -- applied before entering the Annex monad to run this; that cannot be
-- changed while running in the Annex monad. -- changed while running in the Annex monad.
prepRunCommand :: Command -> GlobalSetter -> Annex () prepRunCommand :: Command -> AnnexSetter -> Annex ()
prepRunCommand cmd globalsetter = do prepRunCommand cmd annexsetter = do
when (cmdnomessages cmd) $ when (cmdnomessages cmd) $
Annex.setOutput QuietOutput Annex.setOutput QuietOutput
annexStateSetter globalsetter annexStateSetter annexsetter
whenM (Annex.getRead Annex.debugenabled) $ whenM (Annex.getRead Annex.debugenabled) $
enableDebugOutput enableDebugOutput
@ -186,7 +186,7 @@ mkAddonCommand p subcommandname = Command
, cmdparamdesc = "[PARAMS]" , cmdparamdesc = "[PARAMS]"
, cmdsection = SectionAddOn , cmdsection = SectionAddOn
, cmddesc = "addon command" , cmddesc = "addon command"
, cmdglobaloptions = [] , cmdannexoptions = []
, cmdinfomod = O.forwardOptions , cmdinfomod = O.forwardOptions
, cmdparser = parse , cmdparser = parse
, cmdnorepo = Just parse , cmdnorepo = Just parse

36
CmdLine/AnnexSetter.hs Normal file
View file

@ -0,0 +1,36 @@
{- git-annex options that are stored in Annex
-
- Copyright 2015-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module CmdLine.AnnexSetter where
import Common
import Annex
import Types.DeferredParse
import Options.Applicative
setAnnexState :: Annex () -> AnnexSetter
setAnnexState a = AnnexSetter a id
setAnnexRead :: (AnnexRead -> AnnexRead) -> AnnexSetter
setAnnexRead f = AnnexSetter (return ()) f
annexFlag :: AnnexSetter -> Mod FlagFields AnnexSetter -> AnnexOption
annexFlag = flag'
annexOption :: (v -> AnnexSetter) -> Parser v -> AnnexOption
annexOption mk parser = mk <$> parser
-- | Combines a bunch of AnnexOptions together into a Parser
-- that returns a AnnexSetter that can be used to set all the options that
-- are enabled.
parserAnnexOptions :: [AnnexOption] -> Parser AnnexSetter
parserAnnexOptions [] = pure mempty
parserAnnexOptions l = mconcat <$> many (foldl1 (<|>) l)
applyAnnexReadSetter :: AnnexSetter -> (AnnexState, AnnexRead) -> (AnnexState, AnnexRead)
applyAnnexReadSetter gs (st, rd) = (st, annexReadSetter gs rd)

View file

@ -130,7 +130,7 @@ import qualified Command.TestRemote
import qualified Command.Benchmark import qualified Command.Benchmark
cmds :: Parser TestOptions -> TestRunner -> MkBenchmarkGenerator -> [Command] cmds :: Parser TestOptions -> TestRunner -> MkBenchmarkGenerator -> [Command]
cmds testoptparser testrunner mkbenchmarkgenerator = map addGitAnnexGlobalOptions $ cmds testoptparser testrunner mkbenchmarkgenerator = map addGitAnnexCommonOptions $
[ Command.Help.cmd [ Command.Help.cmd
, Command.Add.cmd , Command.Add.cmd
, Command.Get.cmd , Command.Get.cmd
@ -245,8 +245,8 @@ cmds testoptparser testrunner mkbenchmarkgenerator = map addGitAnnexGlobalOption
mkbenchmarkgenerator $ cmds testoptparser testrunner (\_ _ -> return noop) mkbenchmarkgenerator $ cmds testoptparser testrunner (\_ _ -> return noop)
] ]
addGitAnnexGlobalOptions :: Command -> Command addGitAnnexCommonOptions :: Command -> Command
addGitAnnexGlobalOptions c = c { cmdglobaloptions = gitAnnexGlobalOptions ++ cmdglobaloptions c } addGitAnnexCommonOptions c = c { cmdannexoptions = gitAnnexCommonOptions ++ cmdannexoptions c }
run :: Parser TestOptions -> TestRunner -> MkBenchmarkGenerator -> [String] -> IO () run :: Parser TestOptions -> TestRunner -> MkBenchmarkGenerator -> [String] -> IO ()
run testoptparser testrunner mkbenchmarkgenerator args = go envmodes run testoptparser testrunner mkbenchmarkgenerator args = go envmodes

View file

@ -34,66 +34,66 @@ import qualified Limit
import qualified Limit.Wanted import qualified Limit.Wanted
import CmdLine.Option import CmdLine.Option
import CmdLine.Usage import CmdLine.Usage
import CmdLine.GlobalSetter import CmdLine.AnnexSetter
import qualified Backend import qualified Backend
import qualified Types.Backend as Backend import qualified Types.Backend as Backend
import Utility.HumanTime import Utility.HumanTime
import Utility.DataUnits import Utility.DataUnits
import Annex.Concurrent import Annex.Concurrent
-- Global options that are accepted by all git-annex sub-commands, -- Options that are accepted by all git-annex sub-commands,
-- although not always used. -- although not always used.
gitAnnexGlobalOptions :: [GlobalOption] gitAnnexCommonOptions :: [AnnexOption]
gitAnnexGlobalOptions = commonGlobalOptions ++ gitAnnexCommonOptions = commonOptions ++
[ globalOption setnumcopies $ option auto [ annexOption setnumcopies $ option auto
( long "numcopies" <> short 'N' <> metavar paramNumber ( long "numcopies" <> short 'N' <> metavar paramNumber
<> help "override desired number of copies" <> help "override desired number of copies"
<> hidden <> hidden
) )
, globalOption setmincopies $ option auto , annexOption setmincopies $ option auto
( long "mincopies" <> short 'N' <> metavar paramNumber ( long "mincopies" <> short 'N' <> metavar paramNumber
<> help "override minimum number of copies" <> help "override minimum number of copies"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Remote.forceTrust Trusted) $ strOption , annexOption (setAnnexState . Remote.forceTrust Trusted) $ strOption
( long "trust" <> metavar paramRemote ( long "trust" <> metavar paramRemote
<> help "deprecated, does not override trust setting" <> help "deprecated, does not override trust setting"
<> hidden <> hidden
<> completeRemotes <> completeRemotes
) )
, globalOption (setAnnexState . Remote.forceTrust SemiTrusted) $ strOption , annexOption (setAnnexState . Remote.forceTrust SemiTrusted) $ strOption
( long "semitrust" <> metavar paramRemote ( long "semitrust" <> metavar paramRemote
<> help "override trust setting back to default" <> help "override trust setting back to default"
<> hidden <> hidden
<> completeRemotes <> completeRemotes
) )
, globalOption (setAnnexState . Remote.forceTrust UnTrusted) $ strOption , annexOption (setAnnexState . Remote.forceTrust UnTrusted) $ strOption
( long "untrust" <> metavar paramRemote ( long "untrust" <> metavar paramRemote
<> help "override trust setting to untrusted" <> help "override trust setting to untrusted"
<> hidden <> hidden
<> completeRemotes <> completeRemotes
) )
, globalOption (setAnnexState . setgitconfig) $ strOption , annexOption (setAnnexState . setgitconfig) $ strOption
( long "config" <> short 'c' <> metavar "NAME=VALUE" ( long "config" <> short 'c' <> metavar "NAME=VALUE"
<> help "override git configuration setting" <> help "override git configuration setting"
<> hidden <> hidden
) )
, globalOption setuseragent $ strOption , annexOption setuseragent $ strOption
( long "user-agent" <> metavar paramName ( long "user-agent" <> metavar paramName
<> help "override default User-Agent" <> help "override default User-Agent"
<> hidden <> hidden
) )
, globalFlag (setAnnexState $ toplevelWarning False "--trust-glacier no longer has any effect") , annexFlag (setAnnexState $ toplevelWarning False "--trust-glacier no longer has any effect")
( long "trust-glacier" ( long "trust-glacier"
<> help "deprecated, does not trust Amazon Glacier inventory" <> help "deprecated, does not trust Amazon Glacier inventory"
<> hidden <> hidden
) )
, globalFlag (setdesktopnotify mkNotifyFinish) , annexFlag (setdesktopnotify mkNotifyFinish)
( long "notify-finish" ( long "notify-finish"
<> help "show desktop notification after transfer finishes" <> help "show desktop notification after transfer finishes"
<> hidden <> hidden
) )
, globalFlag (setdesktopnotify mkNotifyStart) , annexFlag (setdesktopnotify mkNotifyStart)
( long "notify-start" ( long "notify-start"
<> help "show desktop notification after transfer starts" <> help "show desktop notification after transfer starts"
<> hidden <> hidden
@ -229,7 +229,7 @@ parseKey :: MonadFail m => String -> m Key
parseKey = maybe (Fail.fail "invalid key") return . deserializeKey parseKey = maybe (Fail.fail "invalid key") return . deserializeKey
-- Options to match properties of annexed files. -- Options to match properties of annexed files.
annexedMatchingOptions :: [GlobalOption] annexedMatchingOptions :: [AnnexOption]
annexedMatchingOptions = concat annexedMatchingOptions = concat
[ keyMatchingOptions' [ keyMatchingOptions'
, fileMatchingOptions' Limit.LimitAnnexFiles , fileMatchingOptions' Limit.LimitAnnexFiles
@ -239,86 +239,86 @@ annexedMatchingOptions = concat
] ]
-- Matching options that can operate on keys as well as files. -- Matching options that can operate on keys as well as files.
keyMatchingOptions :: [GlobalOption] keyMatchingOptions :: [AnnexOption]
keyMatchingOptions = keyMatchingOptions' ++ combiningOptions ++ timeLimitOption ++ sizeLimitOption keyMatchingOptions = keyMatchingOptions' ++ combiningOptions ++ timeLimitOption ++ sizeLimitOption
keyMatchingOptions' :: [GlobalOption] keyMatchingOptions' :: [AnnexOption]
keyMatchingOptions' = keyMatchingOptions' =
[ globalOption (setAnnexState . Limit.addIn) $ strOption [ annexOption (setAnnexState . Limit.addIn) $ strOption
( long "in" <> short 'i' <> metavar paramRemote ( long "in" <> short 'i' <> metavar paramRemote
<> help "match files present in a remote" <> help "match files present in a remote"
<> hidden <> hidden
<> completeRemotes <> completeRemotes
) )
, globalOption (setAnnexState . Limit.addCopies) $ strOption , annexOption (setAnnexState . Limit.addCopies) $ strOption
( long "copies" <> short 'C' <> metavar paramRemote ( long "copies" <> short 'C' <> metavar paramRemote
<> help "skip files with fewer copies" <> help "skip files with fewer copies"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addLackingCopies False) $ strOption , annexOption (setAnnexState . Limit.addLackingCopies False) $ strOption
( long "lackingcopies" <> metavar paramNumber ( long "lackingcopies" <> metavar paramNumber
<> help "match files that need more copies" <> help "match files that need more copies"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addLackingCopies True) $ strOption , annexOption (setAnnexState . Limit.addLackingCopies True) $ strOption
( long "approxlackingcopies" <> metavar paramNumber ( long "approxlackingcopies" <> metavar paramNumber
<> help "match files that need more copies (faster)" <> help "match files that need more copies (faster)"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addInBackend) $ strOption , annexOption (setAnnexState . Limit.addInBackend) $ strOption
( long "inbackend" <> short 'B' <> metavar paramName ( long "inbackend" <> short 'B' <> metavar paramName
<> help "match files using a key-value backend" <> help "match files using a key-value backend"
<> hidden <> hidden
<> completeBackends <> completeBackends
) )
, globalFlag (setAnnexState Limit.addSecureHash) , annexFlag (setAnnexState Limit.addSecureHash)
( long "securehash" ( long "securehash"
<> help "match files using a cryptographically secure hash" <> help "match files using a cryptographically secure hash"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addInAllGroup) $ strOption , annexOption (setAnnexState . Limit.addInAllGroup) $ strOption
( long "inallgroup" <> metavar paramGroup ( long "inallgroup" <> metavar paramGroup
<> help "match files present in all remotes in a group" <> help "match files present in all remotes in a group"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addMetaData) $ strOption , annexOption (setAnnexState . Limit.addMetaData) $ strOption
( long "metadata" <> metavar "FIELD=VALUE" ( long "metadata" <> metavar "FIELD=VALUE"
<> help "match files with attached metadata" <> help "match files with attached metadata"
<> hidden <> hidden
) )
, globalFlag (setAnnexState Limit.Wanted.addWantGet) , annexFlag (setAnnexState Limit.Wanted.addWantGet)
( long "want-get" ( long "want-get"
<> help "match files the repository wants to get" <> help "match files the repository wants to get"
<> hidden <> hidden
) )
, globalFlag (setAnnexState Limit.Wanted.addWantDrop) , annexFlag (setAnnexState Limit.Wanted.addWantDrop)
( long "want-drop" ( long "want-drop"
<> help "match files the repository wants to drop" <> help "match files the repository wants to drop"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addAccessedWithin) $ , annexOption (setAnnexState . Limit.addAccessedWithin) $
option (eitherReader parseDuration) option (eitherReader parseDuration)
( long "accessedwithin" ( long "accessedwithin"
<> metavar paramTime <> metavar paramTime
<> help "match files accessed within a time interval" <> help "match files accessed within a time interval"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addMimeType) $ strOption , annexOption (setAnnexState . Limit.addMimeType) $ strOption
( long "mimetype" <> metavar paramGlob ( long "mimetype" <> metavar paramGlob
<> help "match files by mime type" <> help "match files by mime type"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addMimeEncoding) $ strOption , annexOption (setAnnexState . Limit.addMimeEncoding) $ strOption
( long "mimeencoding" <> metavar paramGlob ( long "mimeencoding" <> metavar paramGlob
<> help "match files by mime encoding" <> help "match files by mime encoding"
<> hidden <> hidden
) )
, globalFlag (setAnnexState Limit.addUnlocked) , annexFlag (setAnnexState Limit.addUnlocked)
( long "unlocked" ( long "unlocked"
<> help "match files that are unlocked" <> help "match files that are unlocked"
<> hidden <> hidden
) )
, globalFlag (setAnnexState Limit.addLocked) , annexFlag (setAnnexState Limit.addLocked)
( long "locked" ( long "locked"
<> help "match files that are locked" <> help "match files that are locked"
<> hidden <> hidden
@ -326,44 +326,44 @@ keyMatchingOptions' =
] ]
-- Options to match files which may not yet be annexed. -- Options to match files which may not yet be annexed.
fileMatchingOptions :: Limit.LimitBy -> [GlobalOption] fileMatchingOptions :: Limit.LimitBy -> [AnnexOption]
fileMatchingOptions lb = fileMatchingOptions' lb ++ combiningOptions ++ timeLimitOption fileMatchingOptions lb = fileMatchingOptions' lb ++ combiningOptions ++ timeLimitOption
fileMatchingOptions' :: Limit.LimitBy -> [GlobalOption] fileMatchingOptions' :: Limit.LimitBy -> [AnnexOption]
fileMatchingOptions' lb = fileMatchingOptions' lb =
[ globalOption (setAnnexState . Limit.addExclude) $ strOption [ annexOption (setAnnexState . Limit.addExclude) $ strOption
( long "exclude" <> short 'x' <> metavar paramGlob ( long "exclude" <> short 'x' <> metavar paramGlob
<> help "skip files matching the glob pattern" <> help "skip files matching the glob pattern"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addInclude) $ strOption , annexOption (setAnnexState . Limit.addInclude) $ strOption
( long "include" <> short 'I' <> metavar paramGlob ( long "include" <> short 'I' <> metavar paramGlob
<> help "limit to files matching the glob pattern" <> help "limit to files matching the glob pattern"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addExcludeSameContent) $ strOption , annexOption (setAnnexState . Limit.addExcludeSameContent) $ strOption
( long "excludesamecontent" <> short 'x' <> metavar paramGlob ( long "excludesamecontent" <> short 'x' <> metavar paramGlob
<> help "skip files whose content is the same as another file matching the glob pattern" <> help "skip files whose content is the same as another file matching the glob pattern"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addIncludeSameContent) $ strOption , annexOption (setAnnexState . Limit.addIncludeSameContent) $ strOption
( long "includesamecontent" <> short 'I' <> metavar paramGlob ( long "includesamecontent" <> short 'I' <> metavar paramGlob
<> help "limit to files whose content is the same as another file matching the glob pattern" <> help "limit to files whose content is the same as another file matching the glob pattern"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addLargerThan lb) $ strOption , annexOption (setAnnexState . Limit.addLargerThan lb) $ strOption
( long "largerthan" <> metavar paramSize ( long "largerthan" <> metavar paramSize
<> help "match files larger than a size" <> help "match files larger than a size"
<> hidden <> hidden
) )
, globalOption (setAnnexState . Limit.addSmallerThan lb) $ strOption , annexOption (setAnnexState . Limit.addSmallerThan lb) $ strOption
( long "smallerthan" <> metavar paramSize ( long "smallerthan" <> metavar paramSize
<> help "match files smaller than a size" <> help "match files smaller than a size"
<> hidden <> hidden
) )
] ]
combiningOptions :: [GlobalOption] combiningOptions :: [AnnexOption]
combiningOptions = combiningOptions =
[ longopt "not" "negate next option" [ longopt "not" "negate next option"
, longopt "and" "both previous and next option must match" , longopt "and" "both previous and next option must match"
@ -372,19 +372,19 @@ combiningOptions =
, shortopt ')' "close group of options" , shortopt ')' "close group of options"
] ]
where where
longopt o h = globalFlag (setAnnexState $ Limit.addSyntaxToken o) longopt o h = annexFlag (setAnnexState $ Limit.addSyntaxToken o)
( long o <> help h <> hidden ) ( long o <> help h <> hidden )
shortopt o h = globalFlag (setAnnexState $ Limit.addSyntaxToken [o]) shortopt o h = annexFlag (setAnnexState $ Limit.addSyntaxToken [o])
( short o <> help h <> hidden ) ( short o <> help h <> hidden )
jsonOptions :: [GlobalOption] jsonOptions :: [AnnexOption]
jsonOptions = jsonOptions =
[ globalFlag (setAnnexState $ Annex.setOutput (JSONOutput stdjsonoptions)) [ annexFlag (setAnnexState $ Annex.setOutput (JSONOutput stdjsonoptions))
( long "json" <> short 'j' ( long "json" <> short 'j'
<> help "enable JSON output" <> help "enable JSON output"
<> hidden <> hidden
) )
, globalFlag (setAnnexState $ Annex.setOutput (JSONOutput jsonerrormessagesoptions)) , annexFlag (setAnnexState $ Annex.setOutput (JSONOutput jsonerrormessagesoptions))
( long "json-error-messages" ( long "json-error-messages"
<> help "include error messages in JSON" <> help "include error messages in JSON"
<> hidden <> hidden
@ -397,9 +397,9 @@ jsonOptions =
} }
jsonerrormessagesoptions = stdjsonoptions { jsonErrorMessages = True } jsonerrormessagesoptions = stdjsonoptions { jsonErrorMessages = True }
jsonProgressOption :: [GlobalOption] jsonProgressOption :: [AnnexOption]
jsonProgressOption = jsonProgressOption =
[ globalFlag (setAnnexState $ Annex.setOutput (JSONOutput jsonoptions)) [ annexFlag (setAnnexState $ Annex.setOutput (JSONOutput jsonoptions))
( long "json-progress" ( long "json-progress"
<> help "include progress in JSON output" <> help "include progress in JSON output"
<> hidden <> hidden
@ -413,9 +413,9 @@ jsonProgressOption =
-- Note that a command that adds this option should wrap its seek -- Note that a command that adds this option should wrap its seek
-- action in `allowConcurrentOutput`. -- action in `allowConcurrentOutput`.
jobsOption :: [GlobalOption] jobsOption :: [AnnexOption]
jobsOption = jobsOption =
[ globalOption (setAnnexState . setConcurrency . ConcurrencyCmdLine) $ [ annexOption (setAnnexState . setConcurrency . ConcurrencyCmdLine) $
option (maybeReader parseConcurrency) option (maybeReader parseConcurrency)
( long "jobs" <> short 'J' ( long "jobs" <> short 'J'
<> metavar (paramNumber `paramOr` "cpus") <> metavar (paramNumber `paramOr` "cpus")
@ -424,9 +424,9 @@ jobsOption =
) )
] ]
timeLimitOption :: [GlobalOption] timeLimitOption :: [AnnexOption]
timeLimitOption = timeLimitOption =
[ globalOption settimelimit $ option (eitherReader parseDuration) [ annexOption settimelimit $ option (eitherReader parseDuration)
( long "time-limit" <> short 'T' <> metavar paramTime ( long "time-limit" <> short 'T' <> metavar paramTime
<> help "stop after the specified amount of time" <> help "stop after the specified amount of time"
<> hidden <> hidden
@ -438,9 +438,9 @@ timeLimitOption =
let cutoff = start + durationToPOSIXTime duration let cutoff = start + durationToPOSIXTime duration
Annex.changeState $ \s -> s { Annex.timelimit = Just (duration, cutoff) } Annex.changeState $ \s -> s { Annex.timelimit = Just (duration, cutoff) }
sizeLimitOption :: [GlobalOption] sizeLimitOption :: [AnnexOption]
sizeLimitOption = sizeLimitOption =
[ globalOption setsizelimit $ option (maybeReader (readSize dataUnits)) [ annexOption setsizelimit $ option (maybeReader (readSize dataUnits))
( long "size-limit" <> metavar paramSize ( long "size-limit" <> metavar paramSize
<> help "total size of annexed files to process" <> help "total size of annexed files to process"
<> hidden <> hidden
@ -450,6 +450,18 @@ sizeLimitOption =
setsizelimit n = setAnnexState $ do setsizelimit n = setAnnexState $ do
v <- liftIO $ newTVarIO n v <- liftIO $ newTVarIO n
Annex.changeState $ \s -> s { Annex.sizelimit = Just v } Annex.changeState $ \s -> s { Annex.sizelimit = Just v }
backendOption :: [AnnexOption]
backendOption =
[ annexOption setforcebackend $ strOption
( long "backend" <> short 'b' <> metavar paramName
<> help "specify key-value backend to use"
<> hidden
)
]
where
setforcebackend v = setAnnexRead $
\rd -> rd { Annex.forcebackend = Just v }
data DaemonOptions = DaemonOptions data DaemonOptions = DaemonOptions
{ foregroundDaemonOption :: Bool { foregroundDaemonOption :: Bool

View file

@ -11,7 +11,7 @@ import Annex.Common
import qualified Git.Construct import qualified Git.Construct
import qualified Git.Config import qualified Git.Config
import CmdLine import CmdLine
import CmdLine.GlobalSetter import CmdLine.AnnexSetter
import Command import Command
import Annex.UUID import Annex.UUID
import CmdLine.GitAnnexShell.Checks import CmdLine.GitAnnexShell.Checks
@ -37,7 +37,7 @@ cmdsMap = M.fromList $ map mk
, (ServeReadWrite, allcmds) , (ServeReadWrite, allcmds)
] ]
where where
readonlycmds = map addGlobalOptions readonlycmds = map addAnnexOptions
[ Command.ConfigList.cmd [ Command.ConfigList.cmd
, gitAnnexShellCheck Command.NotifyChanges.cmd , gitAnnexShellCheck Command.NotifyChanges.cmd
-- p2pstdio checks the enviroment variables to -- p2pstdio checks the enviroment variables to
@ -46,10 +46,10 @@ cmdsMap = M.fromList $ map mk
, gitAnnexShellCheck Command.InAnnex.cmd , gitAnnexShellCheck Command.InAnnex.cmd
, gitAnnexShellCheck Command.SendKey.cmd , gitAnnexShellCheck Command.SendKey.cmd
] ]
appendcmds = readonlycmds ++ map addGlobalOptions appendcmds = readonlycmds ++ map addAnnexOptions
[ gitAnnexShellCheck Command.RecvKey.cmd [ gitAnnexShellCheck Command.RecvKey.cmd
] ]
allcmds = appendcmds ++ map addGlobalOptions allcmds = appendcmds ++ map addAnnexOptions
[ gitAnnexShellCheck Command.DropKey.cmd [ gitAnnexShellCheck Command.DropKey.cmd
, Command.GCryptSetup.cmd , Command.GCryptSetup.cmd
] ]
@ -63,16 +63,16 @@ cmdsFor = fromMaybe [] . flip M.lookup cmdsMap
cmdsList :: [Command] cmdsList :: [Command]
cmdsList = nub $ concat $ M.elems cmdsMap cmdsList = nub $ concat $ M.elems cmdsMap
addGlobalOptions :: Command -> Command addAnnexOptions :: Command -> Command
addGlobalOptions c = c { cmdglobaloptions = globalOptions ++ cmdglobaloptions c } addAnnexOptions c = c { cmdannexoptions = commonShellOptions ++ cmdannexoptions c }
globalOptions :: [GlobalOption] commonShellOptions :: [AnnexOption]
globalOptions = commonShellOptions =
globalOption (setAnnexState . checkUUID) (strOption annexOption (setAnnexState . checkUUID) (strOption
( long "uuid" <> metavar paramUUID ( long "uuid" <> metavar paramUUID
<> help "local repository uuid" <> help "local repository uuid"
)) ))
: commonGlobalOptions : commonOptions
where where
checkUUID expected = getUUID >>= check checkUUID expected = getUUID >>= check
where where

View file

@ -1,36 +0,0 @@
{- git-annex global options
-
- Copyright 2015-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module CmdLine.GlobalSetter where
import Common
import Annex
import Types.DeferredParse
import Options.Applicative
setAnnexState :: Annex () -> GlobalSetter
setAnnexState a = GlobalSetter a id
setAnnexRead :: (AnnexRead -> AnnexRead) -> GlobalSetter
setAnnexRead f = GlobalSetter (return ()) f
globalFlag :: GlobalSetter -> Mod FlagFields GlobalSetter -> GlobalOption
globalFlag = flag'
globalOption :: (v -> GlobalSetter) -> Parser v -> GlobalOption
globalOption mk parser = mk <$> parser
-- | Combines a bunch of GlobalOptions together into a Parser
-- that returns a GlobalSetter that can be used to set all the options that
-- are enabled.
parserGlobalOptions :: [GlobalOption] -> Parser GlobalSetter
parserGlobalOptions [] = pure mempty
parserGlobalOptions l = mconcat <$> many (foldl1 (<|>) l)
applyAnnexReadSetter :: GlobalSetter -> (AnnexState, AnnexRead) -> (AnnexState, AnnexRead)
applyAnnexReadSetter gs (st, rd) = (st, annexReadSetter gs rd)

View file

@ -11,8 +11,7 @@ module CmdLine.Option where
import Options.Applicative import Options.Applicative
import CmdLine.Usage import CmdLine.AnnexSetter
import CmdLine.GlobalSetter
import qualified Annex import qualified Annex
import Types.Messages import Types.Messages
import Types.DeferredParse import Types.DeferredParse
@ -22,58 +21,50 @@ import Git.Config
import Utility.FileSystemEncoding import Utility.FileSystemEncoding
import Annex.Debug import Annex.Debug
-- Global options accepted by both git-annex and git-annex-shell sub-commands. -- Options accepted by both git-annex and git-annex-shell sub-commands.
commonGlobalOptions :: [GlobalOption] commonOptions :: [AnnexOption]
commonGlobalOptions = commonOptions =
[ globalFlag (setforce True) [ annexFlag (setforce True)
( long "force" ( long "force"
<> help "allow actions that may lose annexed data" <> help "allow actions that may lose annexed data"
<> hidden <> hidden
) )
, globalFlag (setfast True) , annexFlag (setfast True)
( long "fast" <> short 'F' ( long "fast" <> short 'F'
<> help "avoid slow operations" <> help "avoid slow operations"
<> hidden <> hidden
) )
, globalFlag (setAnnexState $ Annex.setOutput QuietOutput) , annexFlag (setAnnexState $ Annex.setOutput QuietOutput)
( long "quiet" <> short 'q' ( long "quiet" <> short 'q'
<> help "avoid verbose output" <> help "avoid verbose output"
<> hidden <> hidden
) )
, globalFlag (setAnnexState $ Annex.setOutput NormalOutput) , annexFlag (setAnnexState $ Annex.setOutput NormalOutput)
( long "verbose" <> short 'v' ( long "verbose" <> short 'v'
<> help "allow verbose output (default)" <> help "allow verbose output (default)"
<> hidden <> hidden
) )
, globalFlag (setdebug True) , annexFlag (setdebug True)
( long "debug" <> short 'd' ( long "debug" <> short 'd'
<> help "show debug messages" <> help "show debug messages"
<> hidden <> hidden
) )
, globalFlag (setdebug False) , annexFlag (setdebug False)
( long "no-debug" ( long "no-debug"
<> help "don't show debug messages" <> help "don't show debug messages"
<> hidden <> hidden
) )
, globalOption setdebugfilter $ strOption , annexOption setdebugfilter $ strOption
( long "debugfilter" <> metavar "NAME[,NAME..]" ( long "debugfilter" <> metavar "NAME[,NAME..]"
<> help "show debug messages coming from a module" <> help "show debug messages coming from a module"
<> hidden <> hidden
) )
, globalOption setforcebackend $ strOption
( long "backend" <> short 'b' <> metavar paramName
<> help "specify key-value backend to use"
<> hidden
)
] ]
where where
setforce v = setAnnexRead $ \rd -> rd { Annex.force = v } setforce v = setAnnexRead $ \rd -> rd { Annex.force = v }
setfast v = setAnnexRead $ \rd -> rd { Annex.fast = v } setfast v = setAnnexRead $ \rd -> rd { Annex.fast = v }
setforcebackend v = setAnnexRead $
\rd -> rd { Annex.forcebackend = Just v }
setdebug v = mconcat setdebug v = mconcat
[ setAnnexRead $ \rd -> rd { Annex.debugenabled = v } [ setAnnexRead $ \rd -> rd { Annex.debugenabled = v }
-- Also set in git config so it will be passed on to any -- Also set in git config so it will be passed on to any

View file

@ -18,7 +18,7 @@ import CmdLine.Seek as ReExported
import CmdLine.Usage as ReExported import CmdLine.Usage as ReExported
import CmdLine.Action as ReExported import CmdLine.Action as ReExported
import CmdLine.Option as ReExported import CmdLine.Option as ReExported
import CmdLine.GlobalSetter as ReExported import CmdLine.AnnexSetter as ReExported
import CmdLine.GitAnnex.Options as ReExported import CmdLine.GitAnnex.Options as ReExported
import CmdLine.Batch as ReExported import CmdLine.Batch as ReExported
import Options.Applicative as ReExported hiding (command) import Options.Applicative as ReExported hiding (command)
@ -69,9 +69,9 @@ noMessages c = c { cmdnomessages = True }
noRepo :: (String -> Parser (IO ())) -> Command -> Command noRepo :: (String -> Parser (IO ())) -> Command -> Command
noRepo a c = c { cmdnorepo = Just (a (cmdparamdesc c)) } noRepo a c = c { cmdnorepo = Just (a (cmdparamdesc c)) }
{- Adds global options to a command. -} {- Adds Annex options to a command. -}
withGlobalOptions :: [[GlobalOption]] -> Command -> Command withAnnexOptions :: [[AnnexOption]] -> Command -> Command
withGlobalOptions os c = c { cmdglobaloptions = cmdglobaloptions c ++ concat os } withAnnexOptions os c = c { cmdannexoptions = cmdannexoptions c ++ concat os }
{- For start stage to indicate what will be done. -} {- For start stage to indicate what will be done. -}
starting:: MkActionItem actionitem => String -> actionitem -> SeekInput -> CommandPerform -> CommandStart starting:: MkActionItem actionitem => String -> actionitem -> SeekInput -> CommandPerform -> CommandStart

View file

@ -34,12 +34,13 @@ import System.PosixCompat.Files
cmd :: Command cmd :: Command
cmd = notBareRepo $ cmd = notBareRepo $
withGlobalOptions opts $ withAnnexOptions opts $
command "add" SectionCommon "add files to annex" command "add" SectionCommon "add files to annex"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)
where where
opts = opts =
[ jobsOption [ backendOption
, jobsOption
, jsonOptions , jsonOptions
, jsonProgressOption , jsonProgressOption
, fileMatchingOptions LimitDiskFiles , fileMatchingOptions LimitDiskFiles

View file

@ -37,7 +37,7 @@ import Network.URI
import qualified System.FilePath.ByteString as P import qualified System.FilePath.ByteString as P
cmd :: Command cmd :: Command
cmd = notBareRepo $ withGlobalOptions [jobsOption, jsonOptions, jsonProgressOption] $ cmd = notBareRepo $ withAnnexOptions [jobsOption, jsonOptions, jsonProgressOption] $
command "addurl" SectionCommon "add urls to annex" command "addurl" SectionCommon "add urls to annex"
(paramRepeating paramUrl) (seek <$$> optParser) (paramRepeating paramUrl) (seek <$$> optParser)

View file

@ -14,10 +14,11 @@ import Utility.Metered
cmd :: Command cmd :: Command
cmd = noCommit $ noMessages $ dontCheck repoExists $ cmd = noCommit $ noMessages $ dontCheck repoExists $
command "calckey" SectionPlumbing withAnnexOptions [backendOption] $
"calulate key for a file" command "calckey" SectionPlumbing
(paramRepeating paramFile) "calulate key for a file"
(batchable run (pure ())) (paramRepeating paramFile)
(batchable run (pure ()))
run :: () -> SeekInput -> String -> Annex Bool run :: () -> SeekInput -> String -> Annex Bool
run _ _ file = tryNonAsync (genKey ks nullMeterUpdate Nothing) >>= \case run _ _ file = tryNonAsync (genKey ks nullMeterUpdate Nothing) >>= \case

View file

@ -14,7 +14,7 @@ import Annex.Wanted
import Annex.NumCopies import Annex.NumCopies
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $ cmd = withAnnexOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $
command "copy" SectionCommon command "copy" SectionCommon
"copy content of files to/from another repository" "copy content of files to/from another repository"
paramPaths (seek <--< optParser) paramPaths (seek <--< optParser)

View file

@ -22,7 +22,7 @@ import Annex.Wanted
import Annex.Notification import Annex.Notification
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, annexedMatchingOptions] $ cmd = withAnnexOptions [jobsOption, jsonOptions, annexedMatchingOptions] $
command "drop" SectionCommon command "drop" SectionCommon
"remove content of files from repository" "remove content of files from repository"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -13,7 +13,7 @@ import Logs.Location
import Annex.Content import Annex.Content
cmd :: Command cmd :: Command
cmd = noCommit $ withGlobalOptions [jsonOptions] $ cmd = noCommit $ withAnnexOptions [jsonOptions] $
command "dropkey" SectionPlumbing command "dropkey" SectionPlumbing
"drops annexed content for specified keys" "drops annexed content for specified keys"
(paramRepeating paramKey) (paramRepeating paramKey)

View file

@ -20,7 +20,7 @@ import qualified Data.ByteString as B
cmd :: Command cmd :: Command
cmd = noCommit $ noMessages $ dontCheck repoExists $ cmd = noCommit $ noMessages $ dontCheck repoExists $
withGlobalOptions [jsonOptions] $ withAnnexOptions [jsonOptions] $
command "examinekey" SectionPlumbing command "examinekey" SectionPlumbing
"prints information from a key" "prints information from a key"
(paramRepeating paramKey) (paramRepeating paramKey)

View file

@ -44,7 +44,7 @@ import qualified Data.Map as M
import Control.Concurrent import Control.Concurrent
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, jsonProgressOption] $ cmd = withAnnexOptions [jobsOption, jsonOptions, jsonProgressOption] $
command "export" SectionCommon command "export" SectionCommon
"export a tree of files to a special remote" "export a tree of files to a special remote"
paramTreeish (seek <$$> optParser) paramTreeish (seek <$$> optParser)

View file

@ -36,7 +36,7 @@ import Data.ByteString.Builder
import qualified System.FilePath.ByteString as P import qualified System.FilePath.ByteString as P
cmd :: Command cmd :: Command
cmd = noMessages $ withGlobalOptions [annexedMatchingOptions] $ cmd = noMessages $ withAnnexOptions [annexedMatchingOptions] $
command "filter-branch" SectionMaintenance command "filter-branch" SectionMaintenance
"filter information from the git-annex branch" "filter information from the git-annex branch"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -21,12 +21,12 @@ import qualified Utility.Format
import Utility.DataUnits import Utility.DataUnits
cmd :: Command cmd :: Command
cmd = notBareRepo $ withGlobalOptions [annexedMatchingOptions] $ mkCommand $ cmd = notBareRepo $ withAnnexOptions [annexedMatchingOptions] $ mkCommand $
command "find" SectionQuery "lists available files" command "find" SectionQuery "lists available files"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)
mkCommand :: Command -> Command mkCommand :: Command -> Command
mkCommand = noCommit . noMessages . withGlobalOptions [jsonOptions] mkCommand = noCommit . noMessages . withAnnexOptions [jsonOptions]
data FindOptions = FindOptions data FindOptions = FindOptions
{ findThese :: CmdParams { findThese :: CmdParams

View file

@ -12,7 +12,7 @@ import qualified Command.Find as Find
import qualified Git import qualified Git
cmd :: Command cmd :: Command
cmd = withGlobalOptions [annexedMatchingOptions] $ Find.mkCommand $ cmd = withAnnexOptions [annexedMatchingOptions] $ Find.mkCommand $
command "findref" SectionPlumbing command "findref" SectionPlumbing
"lists files in a git ref (deprecated)" "lists files in a git ref (deprecated)"
paramRef (seek <$$> Find.optParser) paramRef (seek <$$> Find.optParser)

View file

@ -25,7 +25,7 @@ import qualified System.Posix.Files as Posix
#endif #endif
cmd :: Command cmd :: Command
cmd = noCommit $ withGlobalOptions [annexedMatchingOptions] $ cmd = noCommit $ withAnnexOptions [annexedMatchingOptions] $
command "fix" SectionMaintenance command "fix" SectionMaintenance
"fix up links to annexed content" "fix up links to annexed content"
paramPaths (withParams seek) paramPaths (withParams seek)

View file

@ -22,7 +22,7 @@ import Git.FilePath
import Network.URI import Network.URI
cmd :: Command cmd :: Command
cmd = notBareRepo $ withGlobalOptions [jsonOptions] $ cmd = notBareRepo $ withAnnexOptions [jsonOptions] $
command "fromkey" SectionPlumbing "adds a file using a specific key" command "fromkey" SectionPlumbing "adds a file using a specific key"
(paramRepeating (paramPair paramKey paramPath)) (paramRepeating (paramPair paramKey paramPath))
(seek <$$> optParser) (seek <$$> optParser)

View file

@ -51,7 +51,7 @@ import Data.Either
import qualified System.FilePath.ByteString as P import qualified System.FilePath.ByteString as P
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, annexedMatchingOptions] $ cmd = withAnnexOptions [jobsOption, jsonOptions, annexedMatchingOptions] $
command "fsck" SectionMaintenance command "fsck" SectionMaintenance
"find and fix problems" "find and fix problems"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -15,7 +15,7 @@ import Annex.Wanted
import qualified Command.Move import qualified Command.Move
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $ cmd = withAnnexOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $
command "get" SectionCommon command "get" SectionCommon
"make content of annexed files available" "make content of annexed files available"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -40,14 +40,15 @@ import Control.Concurrent.STM
cmd :: Command cmd :: Command
cmd = notBareRepo $ cmd = notBareRepo $
withGlobalOptions opts $ withAnnexOptions opts $
command "import" SectionCommon command "import" SectionCommon
"add a tree of files to the repository" "add a tree of files to the repository"
(paramPaths ++ "|BRANCH") (paramPaths ++ "|BRANCH")
(seek <$$> optParser) (seek <$$> optParser)
where where
opts = opts =
[ jobsOption [ backendOption
, jobsOption
, jsonOptions , jsonOptions
, jsonProgressOption , jsonProgressOption
-- These options are only used when importing from a -- These options are only used when importing from a

View file

@ -97,7 +97,7 @@ emptyStatInfo = StatInfo Nothing Nothing M.empty Nothing
type StatState = StateT StatInfo Annex type StatState = StateT StatInfo Annex
cmd :: Command cmd :: Command
cmd = noCommit $ withGlobalOptions [jsonOptions, annexedMatchingOptions] $ cmd = noCommit $ withAnnexOptions [jsonOptions, annexedMatchingOptions] $
command "info" SectionQuery command "info" SectionQuery
"information about an item or the repository" "information about an item or the repository"
(paramRepeating paramItem) (seek <$$> optParser) (paramRepeating paramItem) (seek <$$> optParser)

View file

@ -22,7 +22,7 @@ import Git.Types (RemoteName)
import Utility.Tuple import Utility.Tuple
cmd :: Command cmd :: Command
cmd = noCommit $ withGlobalOptions [annexedMatchingOptions] $ cmd = noCommit $ withAnnexOptions [annexedMatchingOptions] $
command "list" SectionQuery command "list" SectionQuery
"show which remotes contain files" "show which remotes contain files"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -22,7 +22,7 @@ import Git.FilePath
import qualified Utility.RawFilePath as R import qualified Utility.RawFilePath as R
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jsonOptions, annexedMatchingOptions] $ cmd = withAnnexOptions [jsonOptions, annexedMatchingOptions] $
command "lock" SectionCommon command "lock" SectionCommon
"undo unlock command" "undo unlock command"
paramPaths (withParams seek) paramPaths (withParams seek)

View file

@ -36,7 +36,7 @@ data LogChange = Added | Removed
type Outputter = LogChange -> POSIXTime -> [UUID] -> Annex () type Outputter = LogChange -> POSIXTime -> [UUID] -> Annex ()
cmd :: Command cmd :: Command
cmd = withGlobalOptions [annexedMatchingOptions] $ cmd = withAnnexOptions [annexedMatchingOptions] $
command "log" SectionQuery "shows location log" command "log" SectionQuery "shows location log"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -25,7 +25,7 @@ import qualified Data.ByteString.Lazy.UTF8 as BU
import Control.Concurrent import Control.Concurrent
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jsonOptions, annexedMatchingOptions] $ cmd = withAnnexOptions [jsonOptions, annexedMatchingOptions] $
command "metadata" SectionMetaData command "metadata" SectionMetaData
"sets or gets metadata of a file" "sets or gets metadata of a file"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -20,7 +20,7 @@ import Logs.Web
import Utility.Metered import Utility.Metered
cmd :: Command cmd :: Command
cmd = withGlobalOptions [annexedMatchingOptions] $ cmd = withAnnexOptions [backendOption, annexedMatchingOptions] $
command "migrate" SectionUtility command "migrate" SectionUtility
"switch data to different backend" "switch data to different backend"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -17,7 +17,7 @@ import Annex.NumCopies
import Types.Transfer import Types.Transfer
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $ cmd = withAnnexOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $
command "mirror" SectionCommon command "mirror" SectionCommon
"mirror content of files to/from another repository" "mirror content of files to/from another repository"
paramPaths (seek <--< optParser) paramPaths (seek <--< optParser)

View file

@ -25,7 +25,7 @@ import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $ cmd = withAnnexOptions [jobsOption, jsonOptions, jsonProgressOption, annexedMatchingOptions] $
command "move" SectionCommon command "move" SectionCommon
"move content of files to/from another repository" "move content of files to/from another repository"
paramPaths (seek <--< optParser) paramPaths (seek <--< optParser)

View file

@ -13,7 +13,7 @@ import Command.FromKey (keyOpt, keyOpt')
import qualified Remote import qualified Remote
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jsonOptions] $ command "registerurl" cmd = withAnnexOptions [jsonOptions] $ command "registerurl"
SectionPlumbing "registers an url for a key" SectionPlumbing "registers an url for a key"
(paramPair paramKey paramUrl) (paramPair paramKey paramUrl)
(seek <$$> optParser) (seek <$$> optParser)

View file

@ -16,10 +16,11 @@ import Utility.Metered
import qualified Git import qualified Git
cmd :: Command cmd :: Command
cmd = command "reinject" SectionUtility cmd = withAnnexOptions [backendOption] $
"inject content of file back into annex" command "reinject" SectionUtility
(paramRepeating (paramPair "SRC" "DEST")) "inject content of file back into annex"
(seek <$$> optParser) (paramRepeating (paramPair "SRC" "DEST"))
(seek <$$> optParser)
data ReinjectOptions = ReinjectOptions data ReinjectOptions = ReinjectOptions
{ params :: CmdParams { params :: CmdParams

View file

@ -13,7 +13,7 @@ import Git.FilePath
cmd :: Command cmd :: Command
cmd = notBareRepo $ noCommit $ noMessages $ cmd = notBareRepo $ noCommit $ noMessages $
withGlobalOptions [jsonOptions] $ withAnnexOptions [jsonOptions] $
command "status" SectionCommon command "status" SectionCommon
"show the working tree status" "show the working tree status"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -83,7 +83,7 @@ import qualified Data.ByteString as S
import Data.Char import Data.Char
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jobsOption] $ cmd = withAnnexOptions [jobsOption, backendOption] $
command "sync" SectionCommon command "sync" SectionCommon
"synchronize local repository with remotes" "synchronize local repository with remotes"
(paramRepeating paramRemote) (seek <--< optParser) (paramRepeating paramRemote) (seek <--< optParser)

View file

@ -20,7 +20,7 @@ import Git.FilePath
import qualified Utility.RawFilePath as R import qualified Utility.RawFilePath as R
cmd :: Command cmd :: Command
cmd = withGlobalOptions [annexedMatchingOptions] $ cmd = withAnnexOptions [annexedMatchingOptions] $
command "unannex" SectionUtility command "unannex" SectionUtility
"undo accidental add command" "undo accidental add command"
paramPaths (withParams seek) paramPaths (withParams seek)

View file

@ -25,7 +25,7 @@ editcmd :: Command
editcmd = mkcmd "edit" "same as unlock" editcmd = mkcmd "edit" "same as unlock"
mkcmd :: String -> String -> Command mkcmd :: String -> String -> Command
mkcmd n d = withGlobalOptions [jsonOptions, annexedMatchingOptions] $ mkcmd n d = withAnnexOptions [jsonOptions, annexedMatchingOptions] $
command n SectionCommon d paramPaths (withParams seek) command n SectionCommon d paramPaths (withParams seek)
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek

View file

@ -14,7 +14,7 @@ import Logs.Web
import Command.RegisterUrl (seekBatch, start, optParser, RegisterUrlOptions(..)) import Command.RegisterUrl (seekBatch, start, optParser, RegisterUrlOptions(..))
cmd :: Command cmd :: Command
cmd = withGlobalOptions [jsonOptions] $ command "unregisterurl" cmd = withAnnexOptions [jsonOptions] $ command "unregisterurl"
SectionPlumbing "unregisters an url for a key" SectionPlumbing "unregisters an url for a key"
(paramPair paramKey paramUrl) (paramPair paramKey paramUrl)
(seek <$$> optParser) (seek <$$> optParser)

View file

@ -24,7 +24,7 @@ import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
cmd :: Command cmd :: Command
cmd = noCommit $ withGlobalOptions [annexedMatchingOptions] $ cmd = noCommit $ withAnnexOptions [annexedMatchingOptions] $
command "whereused" SectionQuery command "whereused" SectionQuery
"lists repositories that have file content" "lists repositories that have file content"
paramNothing (seek <$$> optParser) paramNothing (seek <$$> optParser)

View file

@ -23,7 +23,7 @@ import qualified Data.Map as M
import qualified Data.Vector as V import qualified Data.Vector as V
cmd :: Command cmd :: Command
cmd = noCommit $ withGlobalOptions [jsonOptions, annexedMatchingOptions] $ cmd = noCommit $ withAnnexOptions [jsonOptions, annexedMatchingOptions] $
command "whereis" SectionQuery command "whereis" SectionQuery
"lists repositories that have file content" "lists repositories that have file content"
paramPaths (seek <$$> optParser) paramPaths (seek <$$> optParser)

View file

@ -87,8 +87,8 @@ data Command = Command
-- ^ command line parser -- ^ command line parser
, cmdinfomod :: forall a. InfoMod a , cmdinfomod :: forall a. InfoMod a
-- ^ command-specific modifier for ParserInfo -- ^ command-specific modifier for ParserInfo
, cmdglobaloptions :: [GlobalOption] , cmdannexoptions :: [AnnexOption]
-- ^ additional global options -- ^ additional options not parsed by the CommandParser
, cmdnorepo :: Maybe (Parser (IO ())) , cmdnorepo :: Maybe (Parser (IO ()))
-- ^used when not in a repo -- ^used when not in a repo
} }

View file

@ -38,20 +38,20 @@ instance DeferredParseClass (Maybe (DeferredParse a)) where
instance DeferredParseClass [DeferredParse a] where instance DeferredParseClass [DeferredParse a] where
finishParse v = mapM finishParse v finishParse v = mapM finishParse v
type GlobalOption = Parser GlobalSetter type AnnexOption = Parser AnnexSetter
-- Used for global options that can modify Annex state by running -- Used for options that can modify Annex state by running
-- an arbitrary action in it, and can also set up AnnexRead. -- an arbitrary action in it, and can also set up AnnexRead.
data GlobalSetter = GlobalSetter data AnnexSetter = AnnexSetter
{ annexStateSetter :: Annex () { annexStateSetter :: Annex ()
, annexReadSetter :: AnnexRead -> AnnexRead , annexReadSetter :: AnnexRead -> AnnexRead
} }
instance Sem.Semigroup GlobalSetter where instance Sem.Semigroup AnnexSetter where
a <> b = GlobalSetter a <> b = AnnexSetter
{ annexStateSetter = annexStateSetter a >> annexStateSetter b { annexStateSetter = annexStateSetter a >> annexStateSetter b
, annexReadSetter = annexReadSetter b . annexReadSetter a , annexReadSetter = annexReadSetter b . annexReadSetter a
} }
instance Monoid GlobalSetter where instance Monoid AnnexSetter where
mempty = GlobalSetter (return ()) id mempty = AnnexSetter (return ()) id

View file

@ -73,3 +73,5 @@ $> grep -r MD5E .
### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders) ### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders)
kinda kinda
> [[fixed|done]], --backend is no longer a global option. --[[Joey]]

View file

@ -108,13 +108,6 @@ Most of these options are accepted by all git-annex commands.
but now will not do so, because it could lead to data loss, but now will not do so, because it could lead to data loss,
and data loss is now only enabled when using the `--force` option. and data loss is now only enabled when using the `--force` option.
* `--backend=name`
Specifies which key-value backend to use. This can be used when
adding a file to the annex, or migrating a file. Once files
are in the annex, their backend is known and this option is not
necessary.
* `--user-agent=value` * `--user-agent=value`
Overrides the User-Agent to use when downloading files from the web. Overrides the User-Agent to use when downloading files from the web.

View file

@ -185,6 +185,10 @@ and `--reinject-duplicates` documentation below.
Setting this to "cpus" will run one job per CPU core. Setting this to "cpus" will run one job per CPU core.
* `--backend`
Specifies which key-value backend to use for the imported files.
* `--no-check-gitignore` * `--no-check-gitignore`
Add gitignored files. Add gitignored files.

View file

@ -167,6 +167,11 @@ have the same value as the currently checked out branch.
resolution. It can also be disabled by setting `annex.resolvemerge` resolution. It can also be disabled by setting `annex.resolvemerge`
to false. to false.
* `--backend`
Specifies which key-value backend to use when adding files,
or when importing from a special remote.
* `--cleanup` * `--cleanup`
Removes the local and remote `synced/` branches, which were created Removes the local and remote `synced/` branches, which were created

View file

@ -699,7 +699,7 @@ Executable git-annex
CmdLine.GitAnnexShell CmdLine.GitAnnexShell
CmdLine.GitAnnexShell.Checks CmdLine.GitAnnexShell.Checks
CmdLine.GitAnnexShell.Fields CmdLine.GitAnnexShell.Fields
CmdLine.GlobalSetter CmdLine.AnnexSetter
CmdLine.Option CmdLine.Option
CmdLine.GitRemoteTorAnnex CmdLine.GitRemoteTorAnnex
CmdLine.Seek CmdLine.Seek