2015-07-08 21:59:06 +00:00
|
|
|
{- git-annex command-line option parsing
|
2013-03-27 17:51:24 +00:00
|
|
|
-
|
2015-02-06 21:08:14 +00:00
|
|
|
- Copyright 2010-2015 Joey Hess <id@joeyh.name>
|
2013-03-27 17:51:24 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2014-01-26 20:25:55 +00:00
|
|
|
module CmdLine.GitAnnex.Options where
|
2013-03-27 17:51:24 +00:00
|
|
|
|
|
|
|
import System.Console.GetOpt
|
2015-07-08 21:59:06 +00:00
|
|
|
import Options.Applicative
|
2013-03-27 17:51:24 +00:00
|
|
|
|
|
|
|
import Common.Annex
|
|
|
|
import qualified Git.Config
|
2013-11-05 17:38:37 +00:00
|
|
|
import Git.Types
|
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.Key
|
|
|
|
import Types.Command
|
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
|
2013-03-27 17:51:24 +00:00
|
|
|
|
2015-02-06 21:08:14 +00:00
|
|
|
-- Options that are accepted by all git-annex sub-commands,
|
|
|
|
-- although not always used.
|
2014-01-26 20:25:55 +00:00
|
|
|
gitAnnexOptions :: [Option]
|
|
|
|
gitAnnexOptions = commonOptions ++
|
2013-03-27 17:51:24 +00:00
|
|
|
[ Option ['N'] ["numcopies"] (ReqArg setnumcopies paramNumber)
|
|
|
|
"override default number of copies"
|
|
|
|
, Option [] ["trust"] (trustArg Trusted)
|
|
|
|
"override trust setting"
|
|
|
|
, Option [] ["semitrust"] (trustArg SemiTrusted)
|
|
|
|
"override trust setting back to default"
|
|
|
|
, Option [] ["untrust"] (trustArg UnTrusted)
|
|
|
|
"override trust setting to untrusted"
|
|
|
|
, Option ['c'] ["config"] (ReqArg setgitconfig "NAME=VALUE")
|
|
|
|
"override git configuration setting"
|
2013-09-28 18:35:21 +00:00
|
|
|
, Option [] ["user-agent"] (ReqArg setuseragent paramName)
|
|
|
|
"override default User-Agent"
|
2013-03-27 17:51:24 +00:00
|
|
|
, Option [] ["trust-glacier"] (NoArg (Annex.setFlag "trustglacier"))
|
|
|
|
"Trust Amazon Glacier inventory"
|
2015-02-06 21:08:14 +00:00
|
|
|
]
|
2013-03-27 17:51:24 +00:00
|
|
|
where
|
2013-11-05 17:38:37 +00:00
|
|
|
trustArg t = ReqArg (Remote.forceTrust t) paramRemote
|
2013-03-27 17:51:24 +00:00
|
|
|
setnumcopies v = maybe noop
|
2014-01-21 21:08:49 +00:00
|
|
|
(\n -> Annex.changeState $ \s -> s { Annex.forcenumcopies = Just $ NumCopies n })
|
2013-03-27 17:51:24 +00:00
|
|
|
(readish v)
|
2013-09-28 18:35:21 +00:00
|
|
|
setuseragent v = Annex.changeState $ \s -> s { Annex.useragent = Just v }
|
2013-11-05 17:38:37 +00:00
|
|
|
setgitconfig v = inRepo (Git.Config.store v)
|
|
|
|
>>= pure . (\r -> r { gitGlobalOpts = gitGlobalOpts r ++ [Param "-c", Param v] })
|
|
|
|
>>= Annex.changeGitRepo
|
2013-07-03 17:02:42 +00:00
|
|
|
|
2015-07-08 21:59:06 +00:00
|
|
|
-- Options for acting on keys, rather than work tree files.
|
|
|
|
data KeyOptions = KeyOptions
|
|
|
|
{ wantAllKeys :: Bool
|
|
|
|
, wantUnusedKeys :: Bool
|
|
|
|
, wantIncompleteKeys :: Bool
|
|
|
|
, wantSpecificKey :: Maybe Key
|
|
|
|
}
|
|
|
|
|
|
|
|
parseKeyOptions :: Bool -> Parser KeyOptions
|
|
|
|
parseKeyOptions allowincomplete = KeyOptions
|
|
|
|
<$> parseAllKeysOption
|
|
|
|
<*> parseUnusedKeysOption
|
|
|
|
<*> (if allowincomplete then parseIncompleteOption else pure False)
|
|
|
|
<*> parseSpecificKeyOption
|
|
|
|
|
|
|
|
parseAllKeysOption :: Parser Bool
|
|
|
|
parseAllKeysOption = switch
|
2015-07-09 14:41:17 +00:00
|
|
|
( long "all" <> short 'A'
|
2015-07-08 21:59:06 +00:00
|
|
|
<> help "operate on all versions of all files"
|
|
|
|
)
|
|
|
|
|
|
|
|
parseUnusedKeysOption :: Parser Bool
|
|
|
|
parseUnusedKeysOption = switch
|
2015-07-09 14:41:17 +00:00
|
|
|
( long "unused" <> short 'U'
|
2015-07-08 21:59:06 +00:00
|
|
|
<> help "operate on files found by last run of git-annex unused"
|
|
|
|
)
|
|
|
|
|
|
|
|
parseSpecificKeyOption :: Parser (Maybe Key)
|
2015-07-09 05:02:27 +00:00
|
|
|
parseSpecificKeyOption = optional $ option (str >>= parseKey)
|
2015-07-09 14:41:17 +00:00
|
|
|
( long "key" <> metavar paramKey
|
2015-07-08 21:59:06 +00:00
|
|
|
<> help "operate on specified key"
|
|
|
|
)
|
|
|
|
|
|
|
|
parseKey :: Monad m => String -> m Key
|
|
|
|
parseKey = maybe (fail "invalid key") return . file2key
|
|
|
|
|
|
|
|
parseIncompleteOption :: Parser Bool
|
|
|
|
parseIncompleteOption = switch
|
|
|
|
( long "incomplete"
|
|
|
|
<> help "resume previous downloads"
|
|
|
|
)
|
2015-06-02 18:20:38 +00:00
|
|
|
|
2015-02-06 21:08:14 +00:00
|
|
|
-- Options to match properties of annexed files.
|
|
|
|
annexedMatchingOptions :: [Option]
|
|
|
|
annexedMatchingOptions = concat
|
|
|
|
[ nonWorkTreeMatchingOptions'
|
|
|
|
, fileMatchingOptions'
|
|
|
|
, combiningOptions
|
|
|
|
, [timeLimitOption]
|
|
|
|
]
|
|
|
|
|
|
|
|
-- Matching options that don't need to examine work tree files.
|
|
|
|
nonWorkTreeMatchingOptions :: [Option]
|
|
|
|
nonWorkTreeMatchingOptions = nonWorkTreeMatchingOptions' ++ combiningOptions
|
|
|
|
|
|
|
|
nonWorkTreeMatchingOptions' :: [Option]
|
|
|
|
nonWorkTreeMatchingOptions' =
|
|
|
|
[ Option ['i'] ["in"] (ReqArg Limit.addIn paramRemote)
|
|
|
|
"match files present in a remote"
|
|
|
|
, Option ['C'] ["copies"] (ReqArg Limit.addCopies paramNumber)
|
|
|
|
"skip files with fewer copies"
|
|
|
|
, Option [] ["lackingcopies"] (ReqArg (Limit.addLackingCopies False) paramNumber)
|
|
|
|
"match files that need more copies"
|
|
|
|
, Option [] ["approxlackingcopies"] (ReqArg (Limit.addLackingCopies True) paramNumber)
|
|
|
|
"match files that need more copies (faster)"
|
|
|
|
, Option ['B'] ["inbackend"] (ReqArg Limit.addInBackend paramName)
|
|
|
|
"match files using a key-value backend"
|
|
|
|
, Option [] ["inallgroup"] (ReqArg Limit.addInAllGroup paramGroup)
|
|
|
|
"match files present in all remotes in a group"
|
|
|
|
, Option [] ["metadata"] (ReqArg Limit.addMetaData "FIELD=VALUE")
|
|
|
|
"match files with attached metadata"
|
|
|
|
, Option [] ["want-get"] (NoArg Limit.Wanted.addWantGet)
|
|
|
|
"match files the repository wants to get"
|
|
|
|
, Option [] ["want-drop"] (NoArg Limit.Wanted.addWantDrop)
|
|
|
|
"match files the repository wants to drop"
|
|
|
|
]
|
|
|
|
|
|
|
|
-- Options to match files which may not yet be annexed.
|
|
|
|
fileMatchingOptions :: [Option]
|
|
|
|
fileMatchingOptions = fileMatchingOptions' ++ combiningOptions
|
|
|
|
|
|
|
|
fileMatchingOptions' :: [Option]
|
|
|
|
fileMatchingOptions' =
|
|
|
|
[ Option ['x'] ["exclude"] (ReqArg Limit.addExclude paramGlob)
|
|
|
|
"skip files matching the glob pattern"
|
|
|
|
, Option ['I'] ["include"] (ReqArg Limit.addInclude paramGlob)
|
|
|
|
"limit to files matching the glob pattern"
|
|
|
|
, Option [] ["largerthan"] (ReqArg Limit.addLargerThan paramSize)
|
|
|
|
"match files larger than a size"
|
|
|
|
, Option [] ["smallerthan"] (ReqArg Limit.addSmallerThan paramSize)
|
|
|
|
"match files smaller than a size"
|
|
|
|
]
|
|
|
|
|
|
|
|
combiningOptions :: [Option]
|
|
|
|
combiningOptions =
|
|
|
|
[ 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"
|
|
|
|
]
|
|
|
|
where
|
|
|
|
longopt o = Option [] [o] $ NoArg $ Limit.addToken o
|
|
|
|
shortopt o = Option o [] $ NoArg $ Limit.addToken o
|
|
|
|
|
2013-08-20 19:46:35 +00:00
|
|
|
fromOption :: Option
|
2014-01-26 20:25:55 +00:00
|
|
|
fromOption = fieldOption ['f'] "from" paramRemote "source remote"
|
2013-08-20 19:46:35 +00:00
|
|
|
|
|
|
|
toOption :: Option
|
2014-01-26 20:25:55 +00:00
|
|
|
toOption = fieldOption ['t'] "to" paramRemote "destination remote"
|
2013-08-20 19:46:35 +00:00
|
|
|
|
|
|
|
fromToOptions :: [Option]
|
|
|
|
fromToOptions = [fromOption, toOption]
|
2014-01-18 15:54:43 +00:00
|
|
|
|
|
|
|
jsonOption :: Option
|
|
|
|
jsonOption = Option ['j'] ["json"] (NoArg (Annex.setOutput JSONOutput))
|
|
|
|
"enable JSON output"
|
2015-02-06 21:08:14 +00:00
|
|
|
|
2015-04-10 21:08:07 +00:00
|
|
|
jobsOption :: Option
|
|
|
|
jobsOption = Option ['J'] ["jobs"] (ReqArg set paramNumber)
|
|
|
|
"enable concurrent jobs"
|
|
|
|
where
|
|
|
|
set s = case readish s of
|
|
|
|
Nothing -> error "Bad --jobs number"
|
|
|
|
Just n -> Annex.setOutput (ParallelOutput n)
|
|
|
|
|
2015-02-06 21:08:14 +00:00
|
|
|
timeLimitOption :: Option
|
|
|
|
timeLimitOption = Option ['T'] ["time-limit"]
|
|
|
|
(ReqArg Limit.addTimeLimit paramTime)
|
|
|
|
"stop after the specified amount of time"
|
2015-03-25 21:06:14 +00:00
|
|
|
|
|
|
|
autoOption :: Option
|
|
|
|
autoOption = flagOption ['a'] "auto" "automatic mode"
|
2015-07-08 21:59:06 +00:00
|
|
|
|
|
|
|
parseAutoOption :: Parser Bool
|
|
|
|
parseAutoOption = switch
|
2015-07-09 14:41:17 +00:00
|
|
|
( long "auto" <> short 'a'
|
2015-07-08 21:59:06 +00:00
|
|
|
<> help "automatic mode"
|
|
|
|
)
|
|
|
|
|
|
|
|
{- Parser that accepts all non-option params. -}
|
|
|
|
cmdParams :: CmdParamsDesc -> Parser CmdParams
|
2015-07-09 06:01:27 +00:00
|
|
|
cmdParams paramdesc = many $ argument str
|
|
|
|
( metavar paramdesc
|
|
|
|
-- Let bash completion complete files
|
|
|
|
<> action "file"
|
|
|
|
)
|