2015-07-08 21:59:06 +00:00
|
|
|
{- git-annex command-line option parsing
|
2013-03-27 17:51:24 +00:00
|
|
|
-
|
2023-01-18 18:42:39 +00:00
|
|
|
- Copyright 2010-2023 Joey Hess <id@joeyh.name>
|
2013-03-27 17:51:24 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2013-03-27 17:51:24 +00:00
|
|
|
-}
|
|
|
|
|
filter out control characters in warning messages
Converted warning and similar to use StringContainingQuotedPath. Most
warnings are static strings, some do refer to filepaths that need to be
quoted, and others don't need quoting.
Note that, since quote filters out control characters of even
UnquotedString, this makes all warnings safe, even when an attacker
sneaks in a control character in some other way.
When json is being output, no quoting is done, since json gets its own
quoting.
This does, as a side effect, make warning messages in json output not
be indented. The indentation is only needed to offset warning messages
underneath the display of the file they apply to, so that's ok.
Sponsored-by: Brett Eisenberg on Patreon
2023-04-10 18:47:32 +00:00
|
|
|
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, OverloadedStrings #-}
|
2018-04-09 18:29:28 +00:00
|
|
|
|
2014-01-26 20:25:55 +00:00
|
|
|
module CmdLine.GitAnnex.Options where
|
2013-03-27 17:51:24 +00:00
|
|
|
|
2020-02-28 16:57:55 +00:00
|
|
|
import Control.Monad.Fail as Fail (MonadFail(..))
|
2015-07-08 21:59:06 +00:00
|
|
|
import Options.Applicative
|
2021-01-04 19:25:28 +00:00
|
|
|
import Data.Time.Clock.POSIX
|
2021-06-04 20:08:42 +00:00
|
|
|
import Control.Concurrent.STM
|
2018-01-09 19:36:56 +00:00
|
|
|
import qualified Data.Map as M
|
2013-03-27 17:51:24 +00:00
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2013-03-27 17:51:24 +00:00
|
|
|
import qualified Git.Config
|
2015-09-14 17:19:04 +00:00
|
|
|
import qualified Git.Construct
|
2018-01-09 19:36:56 +00:00
|
|
|
import Git.Remote
|
2013-11-05 17:38:37 +00:00
|
|
|
import Git.Types
|
2017-02-24 19:16:56 +00:00
|
|
|
import Types.Key
|
2013-03-27 17:51:24 +00:00
|
|
|
import Types.TrustLevel
|
2014-01-21 20:08:19 +00:00
|
|
|
import Types.NumCopies
|
2014-01-18 15:54:43 +00:00
|
|
|
import Types.Messages
|
2015-07-08 21:59:06 +00:00
|
|
|
import Types.Command
|
2015-07-09 20:20:30 +00:00
|
|
|
import Types.DeferredParse
|
2015-07-10 04:55:53 +00:00
|
|
|
import Types.DesktopNotify
|
2016-09-09 16:57:42 +00:00
|
|
|
import Types.Concurrency
|
2013-03-27 17:51:24 +00:00
|
|
|
import qualified Annex
|
|
|
|
import qualified Remote
|
|
|
|
import qualified Limit
|
2013-10-28 18:50:17 +00:00
|
|
|
import qualified Limit.Wanted
|
2014-01-26 20:25:55 +00:00
|
|
|
import CmdLine.Option
|
|
|
|
import CmdLine.Usage
|
2022-06-29 17:28:08 +00:00
|
|
|
import CmdLine.AnnexSetter
|
2015-09-14 17:19:04 +00:00
|
|
|
import qualified Backend
|
|
|
|
import qualified Types.Backend as Backend
|
2018-08-01 19:20:18 +00:00
|
|
|
import Utility.HumanTime
|
2021-06-04 20:08:42 +00:00
|
|
|
import Utility.DataUnits
|
2020-04-20 17:53:27 +00:00
|
|
|
import Annex.Concurrent
|
2013-03-27 17:51:24 +00:00
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
-- Options that are accepted by all git-annex sub-commands,
|
2015-02-06 21:08:14 +00:00
|
|
|
-- although not always used.
|
2022-06-29 17:28:08 +00:00
|
|
|
gitAnnexCommonOptions :: [AnnexOption]
|
|
|
|
gitAnnexCommonOptions = commonOptions ++
|
|
|
|
[ annexOption setnumcopies $ option auto
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "numcopies" <> short 'N' <> metavar paramNumber
|
2021-01-06 18:11:08 +00:00
|
|
|
<> help "override desired number of copies"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption setmincopies $ option auto
|
2021-01-06 18:11:08 +00:00
|
|
|
( long "mincopies" <> short 'N' <> metavar paramNumber
|
|
|
|
<> help "override minimum number of copies"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Remote.forceTrust Trusted) $ strOption
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "trust" <> metavar paramRemote
|
2021-01-07 14:12:37 +00:00
|
|
|
<> help "deprecated, does not override trust setting"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeRemotes
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Remote.forceTrust SemiTrusted) $ strOption
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "semitrust" <> metavar paramRemote
|
|
|
|
<> help "override trust setting back to default"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeRemotes
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Remote.forceTrust UnTrusted) $ strOption
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "untrust" <> metavar paramRemote
|
|
|
|
<> help "override trust setting to untrusted"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeRemotes
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . setgitconfig) $ strOption
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "config" <> short 'c' <> metavar "NAME=VALUE"
|
|
|
|
<> help "override git configuration setting"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption setuseragent $ strOption
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "user-agent" <> metavar paramName
|
|
|
|
<> help "override default User-Agent"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setAnnexState $ toplevelWarning False "--trust-glacier no longer has any effect")
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "trust-glacier"
|
2021-01-07 14:37:43 +00:00
|
|
|
<> help "deprecated, does not trust Amazon Glacier inventory"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setdesktopnotify mkNotifyFinish)
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "notify-finish"
|
|
|
|
<> help "show desktop notification after transfer finishes"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setdesktopnotify mkNotifyStart)
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "notify-start"
|
2015-07-13 22:15:24 +00:00
|
|
|
<> help "show desktop notification after transfer starts"
|
2015-07-10 06:18:08 +00:00
|
|
|
<> hidden
|
2015-07-10 04:55:53 +00:00
|
|
|
)
|
2015-02-06 21:08:14 +00:00
|
|
|
]
|
2013-03-27 17:51:24 +00:00
|
|
|
where
|
2022-06-28 19:28:14 +00:00
|
|
|
setnumcopies n = setAnnexRead $ \rd -> rd { Annex.forcenumcopies = Just $ configuredNumCopies n }
|
|
|
|
setmincopies n = setAnnexRead $ \rd -> rd { Annex.forcemincopies = Just $ configuredMinCopies n }
|
2022-06-28 20:02:01 +00:00
|
|
|
setuseragent v = setAnnexRead $ \rd -> rd { Annex.useragent = Just v }
|
|
|
|
setdesktopnotify v = setAnnexRead $ \rd -> rd { Annex.desktopnotify = Annex.desktopnotify rd <> v }
|
refix bug in a better way
Always run Git.Config.store, so when the git config gets reloaded,
the override gets re-added to it, and changeGitRepo then calls extractGitConfig
on it and sees the annex.* settings from the override.
Remove any prior occurance of -c v and add it to the end. This way,
-c foo=1 -c foo=2 -c foo=1 will pass -c foo=1 to git, rather than -c foo=2
Note that, if git had some multiline config that got built up by
multiple -c's, this would not work still. But it never worked because
before the bug got fixed in the first place, the -c value was repeated
many times, so the multivalue thing would have been wrong. I don't think
-c can be used with multiline configs anyway, though git-config does
talk about them?
2020-07-02 17:32:33 +00:00
|
|
|
setgitconfig v = Annex.addGitConfigOverride v
|
2013-07-03 17:02:42 +00:00
|
|
|
|
2015-07-10 17:18:46 +00:00
|
|
|
{- Parser that accepts all non-option params. -}
|
|
|
|
cmdParams :: CmdParamsDesc -> Parser CmdParams
|
|
|
|
cmdParams paramdesc = many $ argument str
|
|
|
|
( metavar paramdesc
|
2017-06-09 15:38:20 +00:00
|
|
|
<> action "file"
|
2015-07-10 17:18:46 +00:00
|
|
|
)
|
|
|
|
|
|
|
|
parseAutoOption :: Parser Bool
|
|
|
|
parseAutoOption = switch
|
|
|
|
( long "auto" <> short 'a'
|
|
|
|
<> help "automatic mode"
|
|
|
|
)
|
|
|
|
|
2023-04-05 19:46:51 +00:00
|
|
|
mkParseRemoteOption :: RemoteName -> DeferredParse Remote
|
|
|
|
mkParseRemoteOption = DeferredParse
|
2015-09-14 17:19:04 +00:00
|
|
|
. (fromJust <$$> Remote.byNameWithUUID)
|
2017-05-31 20:20:55 +00:00
|
|
|
. Just
|
2015-07-09 19:23:14 +00:00
|
|
|
|
2019-10-01 16:36:25 +00:00
|
|
|
parseUUIDOption :: String -> DeferredParse UUID
|
|
|
|
parseUUIDOption = DeferredParse
|
|
|
|
. (Remote.nameToUUID)
|
|
|
|
|
2022-08-03 15:16:04 +00:00
|
|
|
parseDryRunOption :: Parser DryRun
|
|
|
|
parseDryRunOption = DryRun <$> switch
|
|
|
|
( long "dry-run"
|
|
|
|
<> help "don't make changes, but show what would be done"
|
|
|
|
)
|
|
|
|
|
2023-01-18 18:42:39 +00:00
|
|
|
-- | From or To a remote but not both.
|
2015-07-09 19:23:14 +00:00
|
|
|
data FromToOptions
|
|
|
|
= FromRemote (DeferredParse Remote)
|
|
|
|
| ToRemote (DeferredParse Remote)
|
|
|
|
|
|
|
|
instance DeferredParseClass FromToOptions where
|
|
|
|
finishParse (FromRemote v) = FromRemote <$> finishParse v
|
|
|
|
finishParse (ToRemote v) = ToRemote <$> finishParse v
|
|
|
|
|
|
|
|
parseFromToOptions :: Parser FromToOptions
|
|
|
|
parseFromToOptions =
|
2023-04-05 19:46:51 +00:00
|
|
|
(FromRemote . mkParseRemoteOption <$> parseFromOption)
|
|
|
|
<|> (ToRemote . mkParseRemoteOption <$> parseToOption)
|
2015-07-09 19:23:14 +00:00
|
|
|
|
2017-05-31 20:20:55 +00:00
|
|
|
parseFromOption :: Parser RemoteName
|
|
|
|
parseFromOption = strOption
|
2015-07-09 19:23:14 +00:00
|
|
|
( long "from" <> short 'f' <> metavar paramRemote
|
|
|
|
<> help "source remote"
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeRemotes
|
2015-07-09 19:23:14 +00:00
|
|
|
)
|
|
|
|
|
2017-05-31 20:20:55 +00:00
|
|
|
parseToOption :: Parser RemoteName
|
|
|
|
parseToOption = strOption
|
2015-07-09 19:23:14 +00:00
|
|
|
( long "to" <> short 't' <> metavar paramRemote
|
|
|
|
<> help "destination remote"
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeRemotes
|
2015-07-09 19:23:14 +00:00
|
|
|
)
|
|
|
|
|
2023-04-05 19:46:51 +00:00
|
|
|
parseRemoteOption :: Parser RemoteName
|
|
|
|
parseRemoteOption = strOption
|
|
|
|
( long "remote" <> metavar paramRemote
|
|
|
|
<> completeRemotes
|
|
|
|
)
|
|
|
|
|
2023-01-18 18:42:39 +00:00
|
|
|
-- | From or to a remote, or both, or a special --to=here
|
|
|
|
data FromToHereOptions
|
|
|
|
= FromOrToRemote FromToOptions
|
|
|
|
| ToHere
|
|
|
|
| FromRemoteToRemote (DeferredParse Remote) (DeferredParse Remote)
|
2018-04-09 18:29:28 +00:00
|
|
|
|
2023-01-18 18:42:39 +00:00
|
|
|
parseFromToHereOptions :: Parser (Maybe FromToHereOptions)
|
|
|
|
parseFromToHereOptions = go
|
|
|
|
<$> optional parseFromOption
|
|
|
|
<*> optional parseToOption
|
2018-04-09 18:29:28 +00:00
|
|
|
where
|
2023-01-18 18:42:39 +00:00
|
|
|
go (Just from) (Just to) = Just $ FromRemoteToRemote
|
2023-04-05 19:46:51 +00:00
|
|
|
(mkParseRemoteOption from)
|
|
|
|
(mkParseRemoteOption to)
|
2023-01-18 18:42:39 +00:00
|
|
|
go (Just from) Nothing = Just $ FromOrToRemote
|
2023-04-05 19:46:51 +00:00
|
|
|
(FromRemote $ mkParseRemoteOption from)
|
2023-01-18 18:42:39 +00:00
|
|
|
go Nothing (Just to) = Just $ case to of
|
|
|
|
"here" -> ToHere
|
|
|
|
"." -> ToHere
|
2023-04-05 19:46:51 +00:00
|
|
|
_ -> FromOrToRemote $ ToRemote $ mkParseRemoteOption to
|
2023-01-18 18:42:39 +00:00
|
|
|
go Nothing Nothing = Nothing
|
2018-04-09 18:29:28 +00:00
|
|
|
|
|
|
|
instance DeferredParseClass FromToHereOptions where
|
2023-01-18 18:42:39 +00:00
|
|
|
finishParse (FromOrToRemote v) = FromOrToRemote <$> finishParse v
|
|
|
|
finishParse ToHere = pure ToHere
|
|
|
|
finishParse (FromRemoteToRemote v1 v2) = FromRemoteToRemote
|
|
|
|
<$> finishParse v1
|
|
|
|
<*> finishParse v2
|
2018-04-09 18:29:28 +00:00
|
|
|
|
2015-07-08 21:59:06 +00:00
|
|
|
-- Options for acting on keys, rather than work tree files.
|
2015-07-09 16:44:03 +00:00
|
|
|
data KeyOptions
|
|
|
|
= WantAllKeys
|
|
|
|
| WantUnusedKeys
|
2016-08-03 16:37:12 +00:00
|
|
|
| WantFailedTransfers
|
2015-07-09 16:44:03 +00:00
|
|
|
| WantSpecificKey Key
|
|
|
|
| WantIncompleteKeys
|
--branch, stage 1
Added --branch option to copy, drop, fsck, get, metadata, mirror, move, and
whereis commands. This option makes git-annex operate on files that are
included in a specified branch (or other treeish).
The names of the files from the branch that are being operated on are not
displayed yet; only the keys. Displaying the filenames will need changes
to every affected command.
Also, note that --branch can be specified repeatedly. This is not really
documented, but seemed worth supporting, especially since we may later want
the ability to operate on all branches matching a refspec. However, when
operating on two branches that contain the same key, that key will be
operated on twice.
2016-07-20 16:05:22 +00:00
|
|
|
| WantBranchKeys [Branch]
|
2015-07-08 21:59:06 +00:00
|
|
|
|
2016-08-03 16:37:12 +00:00
|
|
|
parseKeyOptions :: Parser KeyOptions
|
|
|
|
parseKeyOptions = parseAllOption
|
2018-12-09 18:10:37 +00:00
|
|
|
<|> parseBranchKeysOption
|
2019-12-18 18:04:14 +00:00
|
|
|
<|> parseUnusedKeysOption
|
|
|
|
<|> parseSpecificKeyOption
|
|
|
|
|
|
|
|
parseUnusedKeysOption :: Parser KeyOptions
|
|
|
|
parseUnusedKeysOption = flag' WantUnusedKeys
|
|
|
|
( long "unused" <> short 'U'
|
|
|
|
<> help "operate on files found by last run of git-annex unused"
|
|
|
|
)
|
|
|
|
|
|
|
|
parseSpecificKeyOption :: Parser KeyOptions
|
|
|
|
parseSpecificKeyOption = WantSpecificKey <$> option (str >>= parseKey)
|
|
|
|
( long "key" <> metavar paramKey
|
|
|
|
<> help "operate on specified key"
|
|
|
|
)
|
2016-08-03 16:37:12 +00:00
|
|
|
|
2018-12-09 18:10:37 +00:00
|
|
|
parseBranchKeysOption :: Parser KeyOptions
|
2019-12-18 18:04:14 +00:00
|
|
|
parseBranchKeysOption = WantBranchKeys <$> some (option (str >>= pure . Ref)
|
|
|
|
( long "branch" <> metavar paramRef
|
|
|
|
<> help "operate on files in the specified branch or treeish"
|
|
|
|
))
|
2018-12-09 18:10:37 +00:00
|
|
|
|
2016-08-03 16:37:12 +00:00
|
|
|
parseFailedTransfersOption :: Parser KeyOptions
|
|
|
|
parseFailedTransfersOption = flag' WantFailedTransfers
|
|
|
|
( long "failed"
|
|
|
|
<> help "operate on files that recently failed to be transferred"
|
|
|
|
)
|
|
|
|
|
|
|
|
parseIncompleteOption :: Parser KeyOptions
|
|
|
|
parseIncompleteOption = flag' WantIncompleteKeys
|
|
|
|
( long "incomplete"
|
|
|
|
<> help "resume previous downloads"
|
|
|
|
)
|
2015-07-08 21:59:06 +00:00
|
|
|
|
2015-07-09 23:03:21 +00:00
|
|
|
parseAllOption :: Parser KeyOptions
|
|
|
|
parseAllOption = flag' WantAllKeys
|
|
|
|
( long "all" <> short 'A'
|
|
|
|
<> help "operate on all versions of all files"
|
|
|
|
)
|
|
|
|
|
2020-02-28 10:56:48 +00:00
|
|
|
parseKey :: MonadFail m => String -> m Key
|
|
|
|
parseKey = maybe (Fail.fail "invalid key") return . deserializeKey
|
2015-07-08 21:59:06 +00:00
|
|
|
|
2015-02-06 21:08:14 +00:00
|
|
|
-- Options to match properties of annexed files.
|
2022-06-29 17:28:08 +00:00
|
|
|
annexedMatchingOptions :: [AnnexOption]
|
2015-02-06 21:08:14 +00:00
|
|
|
annexedMatchingOptions = concat
|
support findred and --branch with file matching options
* findref: Support file matching options: --include, --exclude,
--want-get, --want-drop, --largerthan, --smallerthan, --accessedwithin
* Commands supporting --branch now apply file matching options --include,
--exclude, --want-get, --want-drop to filenames from the branch.
Previously, combining --branch with those would fail to match anything.
* add, import, findref: Support --time-limit.
This commit was sponsored by Jake Vosloo on Patreon.
2018-12-09 17:38:35 +00:00
|
|
|
[ keyMatchingOptions'
|
2020-10-19 19:36:18 +00:00
|
|
|
, fileMatchingOptions' Limit.LimitAnnexFiles
|
2023-01-17 18:42:29 +00:00
|
|
|
, anythingNothingOptions
|
2015-07-10 17:18:46 +00:00
|
|
|
, combiningOptions
|
2018-02-19 18:28:17 +00:00
|
|
|
, timeLimitOption
|
2021-06-04 20:08:42 +00:00
|
|
|
, sizeLimitOption
|
2015-02-06 21:08:14 +00:00
|
|
|
]
|
|
|
|
|
2023-01-17 18:42:29 +00:00
|
|
|
-- Options to match properties of keys.
|
2022-06-29 17:28:08 +00:00
|
|
|
keyMatchingOptions :: [AnnexOption]
|
2023-01-17 18:42:29 +00:00
|
|
|
keyMatchingOptions = concat
|
|
|
|
[ keyMatchingOptions'
|
|
|
|
, anythingNothingOptions
|
|
|
|
, combiningOptions
|
|
|
|
, timeLimitOption
|
|
|
|
, sizeLimitOption
|
|
|
|
]
|
2015-02-06 21:08:14 +00:00
|
|
|
|
2023-01-17 18:42:29 +00:00
|
|
|
-- Matching options that can operate on keys as well as files.
|
2022-06-29 17:28:08 +00:00
|
|
|
keyMatchingOptions' :: [AnnexOption]
|
support findred and --branch with file matching options
* findref: Support file matching options: --include, --exclude,
--want-get, --want-drop, --largerthan, --smallerthan, --accessedwithin
* Commands supporting --branch now apply file matching options --include,
--exclude, --want-get, --want-drop to filenames from the branch.
Previously, combining --branch with those would fail to match anything.
* add, import, findref: Support --time-limit.
This commit was sponsored by Jake Vosloo on Patreon.
2018-12-09 17:38:35 +00:00
|
|
|
keyMatchingOptions' =
|
2022-06-29 17:28:08 +00:00
|
|
|
[ annexOption (setAnnexState . Limit.addIn) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "in" <> short 'i' <> metavar paramRemote
|
|
|
|
<> help "match files present in a remote"
|
|
|
|
<> hidden
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeRemotes
|
2015-07-10 17:18:46 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addCopies) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "copies" <> short 'C' <> metavar paramRemote
|
|
|
|
<> help "skip files with fewer copies"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addLackingCopies False) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "lackingcopies" <> metavar paramNumber
|
|
|
|
<> help "match files that need more copies"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addLackingCopies True) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "approxlackingcopies" <> metavar paramNumber
|
|
|
|
<> help "match files that need more copies (faster)"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addInBackend) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "inbackend" <> short 'B' <> metavar paramName
|
|
|
|
<> help "match files using a key-value backend"
|
|
|
|
<> hidden
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeBackends
|
2015-07-10 17:18:46 +00:00
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setAnnexState Limit.addSecureHash)
|
2017-02-27 19:02:38 +00:00
|
|
|
( long "securehash"
|
|
|
|
<> help "match files using a cryptographically secure hash"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addInAllGroup) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "inallgroup" <> metavar paramGroup
|
|
|
|
<> help "match files present in all remotes in a group"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addMetaData) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "metadata" <> metavar "FIELD=VALUE"
|
|
|
|
<> help "match files with attached metadata"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setAnnexState Limit.Wanted.addWantGet)
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "want-get"
|
2022-07-28 17:26:03 +00:00
|
|
|
<> help "match files the local repository wants to get"
|
2015-07-10 17:18:46 +00:00
|
|
|
<> hidden
|
|
|
|
)
|
2022-07-28 17:26:03 +00:00
|
|
|
, annexOption (setAnnexState . Limit.Wanted.addWantGetBy) $ strOption
|
|
|
|
( long "want-get-by" <> metavar paramRemote
|
|
|
|
<> help "match files the specified repository wants to get"
|
|
|
|
<> hidden
|
|
|
|
<> completeRemotes
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setAnnexState Limit.Wanted.addWantDrop)
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "want-drop"
|
2022-07-28 17:26:03 +00:00
|
|
|
<> help "match files the local repository wants to drop"
|
|
|
|
<> hidden
|
|
|
|
)
|
|
|
|
, annexOption (setAnnexState . Limit.Wanted.addWantDropBy) $ strOption
|
|
|
|
( long "want-drop-by" <> metavar paramRemote
|
|
|
|
<> help "match files the specified repository wants to drop"
|
2015-07-10 17:18:46 +00:00
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addAccessedWithin) $
|
2021-04-06 19:14:00 +00:00
|
|
|
option (eitherReader parseDuration)
|
|
|
|
( long "accessedwithin"
|
|
|
|
<> metavar paramTime
|
|
|
|
<> help "match files accessed within a time interval"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addMimeType) $ strOption
|
2019-09-19 15:32:12 +00:00
|
|
|
( long "mimetype" <> metavar paramGlob
|
|
|
|
<> help "match files by mime type"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addMimeEncoding) $ strOption
|
2019-09-19 15:32:12 +00:00
|
|
|
( long "mimeencoding" <> metavar paramGlob
|
|
|
|
<> help "match files by mime encoding"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setAnnexState Limit.addUnlocked)
|
2019-09-19 16:20:35 +00:00
|
|
|
( long "unlocked"
|
|
|
|
<> help "match files that are unlocked"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setAnnexState Limit.addLocked)
|
2019-09-19 16:20:35 +00:00
|
|
|
( long "locked"
|
|
|
|
<> help "match files that are locked"
|
|
|
|
<> hidden
|
|
|
|
)
|
2015-02-06 21:08:14 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
-- Options to match files which may not yet be annexed.
|
2022-06-29 17:28:08 +00:00
|
|
|
fileMatchingOptions :: Limit.LimitBy -> [AnnexOption]
|
2020-10-19 19:36:18 +00:00
|
|
|
fileMatchingOptions lb = fileMatchingOptions' lb ++ combiningOptions ++ timeLimitOption
|
2015-02-06 21:08:14 +00:00
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
fileMatchingOptions' :: Limit.LimitBy -> [AnnexOption]
|
2020-10-19 19:36:18 +00:00
|
|
|
fileMatchingOptions' lb =
|
2022-06-29 17:28:08 +00:00
|
|
|
[ annexOption (setAnnexState . Limit.addExclude) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "exclude" <> short 'x' <> metavar paramGlob
|
|
|
|
<> help "skip files matching the glob pattern"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addInclude) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "include" <> short 'I' <> metavar paramGlob
|
|
|
|
<> help "limit to files matching the glob pattern"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addExcludeSameContent) $ strOption
|
2021-05-25 17:05:42 +00:00
|
|
|
( long "excludesamecontent" <> short 'x' <> metavar paramGlob
|
|
|
|
<> help "skip files whose content is the same as another file matching the glob pattern"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addIncludeSameContent) $ strOption
|
2021-05-25 17:05:42 +00:00
|
|
|
( long "includesamecontent" <> short 'I' <> metavar paramGlob
|
|
|
|
<> help "limit to files whose content is the same as another file matching the glob pattern"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addLargerThan lb) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "largerthan" <> metavar paramSize
|
|
|
|
<> help "match files larger than a size"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexOption (setAnnexState . Limit.addSmallerThan lb) $ strOption
|
2015-07-10 17:18:46 +00:00
|
|
|
( long "smallerthan" <> metavar paramSize
|
|
|
|
<> help "match files smaller than a size"
|
|
|
|
<> hidden
|
|
|
|
)
|
2023-01-17 18:42:29 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
anythingNothingOptions :: [AnnexOption]
|
|
|
|
anythingNothingOptions =
|
|
|
|
[ annexFlag (setAnnexState Limit.addAnything)
|
2022-12-20 19:42:34 +00:00
|
|
|
( long "anything"
|
|
|
|
<> help "match all files"
|
|
|
|
<> hidden
|
|
|
|
)
|
|
|
|
, annexFlag (setAnnexState Limit.addNothing)
|
|
|
|
( long "nothing"
|
|
|
|
<> help "don't match any files"
|
|
|
|
<> hidden
|
|
|
|
)
|
2015-02-06 21:08:14 +00:00
|
|
|
]
|
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
combiningOptions :: [AnnexOption]
|
2015-07-10 16:47:35 +00:00
|
|
|
combiningOptions =
|
2015-07-10 17:18:46 +00:00
|
|
|
[ longopt "not" "negate next option"
|
|
|
|
, longopt "and" "both previous and next option must match"
|
|
|
|
, longopt "or" "either previous or next option must match"
|
|
|
|
, shortopt '(' "open group of options"
|
|
|
|
, shortopt ')' "close group of options"
|
|
|
|
]
|
2015-04-10 21:08:07 +00:00
|
|
|
where
|
2022-06-29 17:28:08 +00:00
|
|
|
longopt o h = annexFlag (setAnnexState $ Limit.addSyntaxToken o)
|
2021-04-06 19:14:00 +00:00
|
|
|
( long o <> help h <> hidden )
|
2022-06-29 17:28:08 +00:00
|
|
|
shortopt o h = annexFlag (setAnnexState $ Limit.addSyntaxToken [o])
|
2021-04-06 19:14:00 +00:00
|
|
|
( short o <> help h <> hidden )
|
2015-07-09 23:03:21 +00:00
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
jsonOptions :: [AnnexOption]
|
2018-02-19 18:28:17 +00:00
|
|
|
jsonOptions =
|
2022-06-29 17:28:08 +00:00
|
|
|
[ annexFlag (setAnnexState $ Annex.setOutput (JSONOutput stdjsonoptions))
|
2018-02-19 18:28:17 +00:00
|
|
|
( long "json" <> short 'j'
|
|
|
|
<> help "enable JSON output"
|
|
|
|
<> hidden
|
|
|
|
)
|
2022-06-29 17:28:08 +00:00
|
|
|
, annexFlag (setAnnexState $ Annex.setOutput (JSONOutput jsonerrormessagesoptions))
|
2018-02-19 18:28:17 +00:00
|
|
|
( long "json-error-messages"
|
|
|
|
<> help "include error messages in JSON"
|
|
|
|
<> hidden
|
|
|
|
)
|
|
|
|
]
|
2018-02-19 18:03:23 +00:00
|
|
|
where
|
2018-02-19 18:28:17 +00:00
|
|
|
stdjsonoptions = JSONOptions
|
2018-02-19 18:03:23 +00:00
|
|
|
{ jsonProgress = False
|
2018-02-19 18:28:17 +00:00
|
|
|
, jsonErrorMessages = False
|
2018-02-19 18:03:23 +00:00
|
|
|
}
|
2018-02-19 18:28:17 +00:00
|
|
|
jsonerrormessagesoptions = stdjsonoptions { jsonErrorMessages = True }
|
2015-03-25 21:06:14 +00:00
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
jsonProgressOption :: [AnnexOption]
|
2018-02-19 18:28:17 +00:00
|
|
|
jsonProgressOption =
|
2022-06-29 17:28:08 +00:00
|
|
|
[ annexFlag (setAnnexState $ Annex.setOutput (JSONOutput jsonoptions))
|
2018-02-19 18:28:17 +00:00
|
|
|
( long "json-progress"
|
|
|
|
<> help "include progress in JSON output"
|
|
|
|
<> hidden
|
|
|
|
)
|
|
|
|
]
|
2018-02-19 18:03:23 +00:00
|
|
|
where
|
|
|
|
jsonoptions = JSONOptions
|
|
|
|
{ jsonProgress = True
|
2018-02-19 18:28:17 +00:00
|
|
|
, jsonErrorMessages = False
|
2018-02-19 18:03:23 +00:00
|
|
|
}
|
2016-09-09 19:06:54 +00:00
|
|
|
|
2015-11-04 20:19:00 +00:00
|
|
|
-- Note that a command that adds this option should wrap its seek
|
|
|
|
-- action in `allowConcurrentOutput`.
|
2022-06-29 17:28:08 +00:00
|
|
|
jobsOption :: [AnnexOption]
|
2018-02-19 18:28:17 +00:00
|
|
|
jobsOption =
|
2022-06-29 17:28:08 +00:00
|
|
|
[ annexOption (setAnnexState . setConcurrency . ConcurrencyCmdLine) $
|
2019-05-10 17:24:31 +00:00
|
|
|
option (maybeReader parseConcurrency)
|
|
|
|
( long "jobs" <> short 'J'
|
2019-05-10 18:52:52 +00:00
|
|
|
<> metavar (paramNumber `paramOr` "cpus")
|
2018-02-19 18:28:17 +00:00
|
|
|
<> help "enable concurrent jobs"
|
|
|
|
<> hidden
|
|
|
|
)
|
|
|
|
]
|
2015-07-09 23:03:21 +00:00
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
timeLimitOption :: [AnnexOption]
|
2018-02-19 18:28:17 +00:00
|
|
|
timeLimitOption =
|
2022-06-29 17:28:08 +00:00
|
|
|
[ annexOption settimelimit $ option (eitherReader parseDuration)
|
2018-02-19 18:28:17 +00:00
|
|
|
( long "time-limit" <> short 'T' <> metavar paramTime
|
|
|
|
<> help "stop after the specified amount of time"
|
|
|
|
<> hidden
|
|
|
|
)
|
|
|
|
]
|
2021-01-04 19:25:28 +00:00
|
|
|
where
|
2021-04-06 19:14:00 +00:00
|
|
|
settimelimit duration = setAnnexState $ do
|
2021-01-04 19:25:28 +00:00
|
|
|
start <- liftIO getPOSIXTime
|
|
|
|
let cutoff = start + durationToPOSIXTime duration
|
|
|
|
Annex.changeState $ \s -> s { Annex.timelimit = Just (duration, cutoff) }
|
2015-07-13 15:42:42 +00:00
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
sizeLimitOption :: [AnnexOption]
|
2021-06-04 20:08:42 +00:00
|
|
|
sizeLimitOption =
|
2022-06-29 17:28:08 +00:00
|
|
|
[ annexOption setsizelimit $ option (maybeReader (readSize dataUnits))
|
2021-06-04 20:08:42 +00:00
|
|
|
( long "size-limit" <> metavar paramSize
|
|
|
|
<> help "total size of annexed files to process"
|
|
|
|
<> hidden
|
|
|
|
)
|
|
|
|
]
|
|
|
|
where
|
|
|
|
setsizelimit n = setAnnexState $ do
|
|
|
|
v <- liftIO $ newTVarIO n
|
|
|
|
Annex.changeState $ \s -> s { Annex.sizelimit = Just v }
|
2022-06-29 17:28:08 +00:00
|
|
|
|
|
|
|
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 }
|
2021-06-04 20:08:42 +00:00
|
|
|
|
2015-07-13 15:42:42 +00:00
|
|
|
data DaemonOptions = DaemonOptions
|
|
|
|
{ foregroundDaemonOption :: Bool
|
|
|
|
, stopDaemonOption :: Bool
|
|
|
|
}
|
|
|
|
|
2019-09-30 18:40:46 +00:00
|
|
|
parseDaemonOptions :: Bool -> Parser DaemonOptions
|
|
|
|
parseDaemonOptions canstop
|
|
|
|
| canstop = DaemonOptions <$> foreground <*> stop
|
|
|
|
| otherwise = DaemonOptions <$> foreground <*> pure False
|
|
|
|
where
|
|
|
|
foreground = switch
|
2015-07-13 15:42:42 +00:00
|
|
|
( long "foreground"
|
|
|
|
<> help "do not daemonize"
|
|
|
|
)
|
2019-09-30 18:40:46 +00:00
|
|
|
stop = switch
|
2015-07-13 15:42:42 +00:00
|
|
|
( long "stop"
|
|
|
|
<> help "stop daemon"
|
|
|
|
)
|
2019-09-30 18:40:46 +00:00
|
|
|
|
2015-09-14 17:19:04 +00:00
|
|
|
completeRemotes :: HasCompleter f => Mod f a
|
|
|
|
completeRemotes = completer $ mkCompleter $ \input -> do
|
|
|
|
r <- maybe (pure Nothing) (Just <$$> Git.Config.read)
|
|
|
|
=<< Git.Construct.fromCwd
|
2018-01-09 19:36:56 +00:00
|
|
|
return $ filter (input `isPrefixOf`) $
|
2021-04-23 17:28:23 +00:00
|
|
|
mapMaybe remoteKeyToRemoteName $
|
|
|
|
filter isRemoteUrlKey $
|
2018-01-09 19:36:56 +00:00
|
|
|
maybe [] (M.keys . config) r
|
2015-09-14 17:19:04 +00:00
|
|
|
|
|
|
|
completeBackends :: HasCompleter f => Mod f a
|
2017-02-24 19:16:56 +00:00
|
|
|
completeBackends = completeWith $
|
2020-07-29 19:23:18 +00:00
|
|
|
map (decodeBS . formatKeyVariety . Backend.backendVariety) Backend.builtinList
|