2011-01-16 20:05:05 +00:00
|
|
|
|
{- git-annex command line parsing and dispatch
|
2010-11-02 23:04:24 +00:00
|
|
|
|
-
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
- Copyright 2010-2021 Joey Hess <id@joeyh.name>
|
2010-11-02 23:04:24 +00:00
|
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2010-11-02 23:04:24 +00:00
|
|
|
|
-}
|
|
|
|
|
|
2010-12-30 19:06:26 +00:00
|
|
|
|
module CmdLine (
|
2010-12-30 20:52:24 +00:00
|
|
|
|
dispatch,
|
2010-12-31 00:08:22 +00:00
|
|
|
|
usage,
|
2019-01-04 17:43:53 +00:00
|
|
|
|
parseCmd,
|
|
|
|
|
prepRunCommand,
|
2010-12-30 19:06:26 +00:00
|
|
|
|
) where
|
2010-11-02 23:04:24 +00:00
|
|
|
|
|
2015-07-08 23:38:56 +00:00
|
|
|
|
import qualified Options.Applicative as O
|
2015-07-09 15:49:52 +00:00
|
|
|
|
import qualified Options.Applicative.Help as H
|
2011-11-16 04:49:09 +00:00
|
|
|
|
import Control.Exception (throw)
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
import Control.Monad.IO.Class (MonadIO)
|
|
|
|
|
import System.Exit
|
2010-11-02 23:04:24 +00:00
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
|
import Annex.Common
|
2010-11-02 23:04:24 +00:00
|
|
|
|
import qualified Annex
|
2011-06-30 17:16:57 +00:00
|
|
|
|
import qualified Git
|
2012-04-12 19:34:41 +00:00
|
|
|
|
import qualified Git.AutoCorrect
|
2014-08-23 23:51:33 +00:00
|
|
|
|
import qualified Git.Config
|
2015-07-31 20:00:13 +00:00
|
|
|
|
import Annex.Action
|
2013-04-22 19:36:34 +00:00
|
|
|
|
import Annex.Environment
|
2010-11-02 23:04:24 +00:00
|
|
|
|
import Command
|
2013-07-31 00:24:27 +00:00
|
|
|
|
import Types.Messages
|
2010-11-02 23:04:24 +00:00
|
|
|
|
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
{- Parses input arguments, finds a matching Command, and runs it. -}
|
|
|
|
|
dispatch :: Bool -> Bool -> CmdParams -> [Command] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO ()
|
|
|
|
|
dispatch addonok fuzzyok allargs allcmds fields getgitrepo progname progdesc =
|
|
|
|
|
go addonok allcmds $
|
|
|
|
|
findAddonCommand subcommandname >>= \case
|
2021-02-02 23:06:33 +00:00
|
|
|
|
Just c -> go addonok (c:allcmds) noop
|
|
|
|
|
Nothing -> go addonok allcmds $
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
findAllAddonCommands >>= \cs ->
|
|
|
|
|
go False (cs++allcmds) noop
|
|
|
|
|
where
|
|
|
|
|
go p allcmds' cont =
|
|
|
|
|
let (fuzzy, cmds) = selectCmd fuzzyok allcmds' subcommandname
|
|
|
|
|
in if not p || (not fuzzy && not (null cmds))
|
|
|
|
|
then dispatch' subcommandname args fuzzy cmds allargs allcmds' fields getgitrepo progname progdesc
|
|
|
|
|
else cont
|
|
|
|
|
|
|
|
|
|
(subcommandname, args) = subCmdName allargs
|
|
|
|
|
|
|
|
|
|
dispatch' :: (Maybe String) -> CmdParams -> Bool -> [Command] -> CmdParams -> [Command] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO ()
|
|
|
|
|
dispatch' subcommandname args fuzzy cmds allargs allcmds fields getgitrepo progname progdesc = do
|
2011-03-12 19:30:17 +00:00
|
|
|
|
setupConsole
|
2020-06-05 19:16:57 +00:00
|
|
|
|
go =<< tryNonAsync getgitrepo
|
2015-07-08 16:33:27 +00:00
|
|
|
|
where
|
|
|
|
|
go (Right g) = do
|
2021-04-06 16:22:56 +00:00
|
|
|
|
g' <- Git.Config.read g
|
2022-06-29 17:28:08 +00:00
|
|
|
|
(cmd, seek, annexsetter) <- parsewith False cmdparser
|
2021-04-06 16:22:56 +00:00
|
|
|
|
(\a -> a (Just g'))
|
|
|
|
|
O.handleParseResult
|
2022-06-29 17:28:08 +00:00
|
|
|
|
state <- applyAnnexReadSetter annexsetter <$> Annex.new g'
|
2015-07-08 16:33:27 +00:00
|
|
|
|
Annex.eval state $ do
|
|
|
|
|
checkEnvironment
|
|
|
|
|
forM_ fields $ uncurry Annex.setField
|
2022-06-29 17:28:08 +00:00
|
|
|
|
prepRunCommand cmd annexsetter
|
2015-07-08 16:33:27 +00:00
|
|
|
|
startup
|
2021-06-04 20:43:47 +00:00
|
|
|
|
performCommandAction True cmd seek $
|
2015-11-04 20:19:00 +00:00
|
|
|
|
shutdown $ cmdnocommit cmd
|
2015-07-08 19:39:05 +00:00
|
|
|
|
go (Left norepo) = do
|
2015-09-09 19:55:13 +00:00
|
|
|
|
let ingitrepo = \a -> a =<< Git.Config.global
|
|
|
|
|
-- Parse command line with full cmdparser first,
|
|
|
|
|
-- so that help can be displayed for bad parses
|
|
|
|
|
-- even when not run in a repo.
|
|
|
|
|
res <- parsewith False cmdparser ingitrepo return
|
|
|
|
|
case res of
|
|
|
|
|
Failure _ -> void (O.handleParseResult res)
|
|
|
|
|
_ -> do
|
|
|
|
|
-- Parse command line in norepo mode.
|
|
|
|
|
(_, a, _globalconfig) <- parsewith True
|
|
|
|
|
(fromMaybe (throw norepo) . cmdnorepo)
|
|
|
|
|
ingitrepo
|
|
|
|
|
O.handleParseResult
|
|
|
|
|
a
|
2015-07-08 16:33:27 +00:00
|
|
|
|
|
2015-09-09 19:55:13 +00:00
|
|
|
|
parsewith secondrun getparser ingitrepo handleresult =
|
2021-02-02 19:55:45 +00:00
|
|
|
|
case parseCmd progname progdesc allargs allcmds getparser of
|
2015-07-08 23:38:56 +00:00
|
|
|
|
O.Failure _ -> do
|
|
|
|
|
-- parse failed, so fall back to
|
|
|
|
|
-- fuzzy matching, or to showing usage
|
2015-09-09 19:55:13 +00:00
|
|
|
|
when (fuzzy && not secondrun) $
|
2015-07-08 23:38:56 +00:00
|
|
|
|
ingitrepo autocorrect
|
2021-02-02 19:55:45 +00:00
|
|
|
|
handleresult (parseCmd progname progdesc correctedargs allcmds getparser)
|
2015-09-09 19:55:13 +00:00
|
|
|
|
res -> handleresult res
|
2015-07-08 23:38:56 +00:00
|
|
|
|
where
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
autocorrect = Git.AutoCorrect.prepare (fromJust subcommandname) cmdname cmds
|
2015-07-08 23:38:56 +00:00
|
|
|
|
name
|
|
|
|
|
| fuzzy = case cmds of
|
2015-07-09 15:49:52 +00:00
|
|
|
|
(c:_) -> Just (cmdname c)
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
_ -> subcommandname
|
|
|
|
|
| otherwise = subcommandname
|
2015-07-09 15:49:52 +00:00
|
|
|
|
correctedargs = case name of
|
|
|
|
|
Nothing -> allargs
|
|
|
|
|
Just n -> n:args
|
2015-07-08 16:33:27 +00:00
|
|
|
|
|
2015-07-08 19:39:05 +00:00
|
|
|
|
{- Parses command line, selecting one of the commands from the list. -}
|
2022-06-29 17:28:08 +00:00
|
|
|
|
parseCmd :: String -> String -> CmdParams -> [Command] -> (Command -> O.Parser v) -> O.ParserResult (Command, v, AnnexSetter)
|
2021-02-02 19:55:45 +00:00
|
|
|
|
parseCmd progname progdesc allargs allcmds getparser =
|
2015-07-10 06:03:03 +00:00
|
|
|
|
O.execParserPure (O.prefs O.idm) pinfo allargs
|
2015-07-08 16:33:27 +00:00
|
|
|
|
where
|
2015-07-10 06:18:08 +00:00
|
|
|
|
pinfo = O.info (O.helper <*> subcmds) (O.progDescDoc (Just intro))
|
2015-07-09 05:53:15 +00:00
|
|
|
|
subcmds = O.hsubparser $ mconcat $ map mkcommand allcmds
|
2015-07-09 15:49:52 +00:00
|
|
|
|
mkcommand c = O.command (cmdname c) $ O.info (mkparser c) $ O.fullDesc
|
|
|
|
|
<> O.header (synopsis (progname ++ " " ++ cmdname c) (cmddesc c))
|
|
|
|
|
<> O.footer ("For details, run: " ++ progname ++ " help " ++ cmdname c)
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
<> cmdinfomod c
|
2015-07-10 06:18:08 +00:00
|
|
|
|
mkparser c = (,,)
|
2015-07-08 16:33:27 +00:00
|
|
|
|
<$> pure c
|
2015-07-08 19:39:05 +00:00
|
|
|
|
<*> getparser c
|
2022-06-29 17:28:08 +00:00
|
|
|
|
<*> parserAnnexOptions (cmdannexoptions c)
|
2015-07-09 15:49:52 +00:00
|
|
|
|
synopsis n d = n ++ " - " ++ d
|
|
|
|
|
intro = mconcat $ concatMap (\l -> [H.text l, H.line])
|
|
|
|
|
(synopsis progname progdesc : commandList allcmds)
|
2010-12-30 19:44:15 +00:00
|
|
|
|
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
{- Selects the Command that matches the subcommand name.
|
2012-04-12 19:34:41 +00:00
|
|
|
|
- Does fuzzy matching if necessary, which may result in multiple Commands. -}
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
selectCmd :: Bool -> [Command] -> Maybe String -> (Bool, [Command])
|
|
|
|
|
selectCmd fuzzyok cmds (Just n)
|
2021-02-02 18:27:42 +00:00
|
|
|
|
| not (null exactcmds) = (False, exactcmds)
|
|
|
|
|
| fuzzyok && not (null inexactcmds) = (True, inexactcmds)
|
|
|
|
|
| otherwise = (False, [])
|
|
|
|
|
where
|
|
|
|
|
exactcmds = filter (\c -> cmdname c == n) cmds
|
|
|
|
|
inexactcmds = Git.AutoCorrect.fuzzymatches n cmdname cmds
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
selectCmd _ _ Nothing = (False, [])
|
2021-02-02 18:27:42 +00:00
|
|
|
|
|
|
|
|
|
{- Parses command line params far enough to find the subcommand name. -}
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
subCmdName :: CmdParams -> (Maybe String, CmdParams)
|
|
|
|
|
subCmdName argv = (name, args)
|
2012-11-11 04:51:07 +00:00
|
|
|
|
where
|
|
|
|
|
(name, args) = findname argv []
|
|
|
|
|
findname [] c = (Nothing, reverse c)
|
|
|
|
|
findname (a:as) c
|
|
|
|
|
| "-" `isPrefixOf` a = findname as (a:c)
|
|
|
|
|
| otherwise = (Just a, reverse c ++ as)
|
2019-01-04 17:43:53 +00:00
|
|
|
|
|
2022-06-29 17:28:08 +00:00
|
|
|
|
-- | Note that the AnnexSetter must have already had its annexReadSetter
|
2021-04-06 20:28:37 +00:00
|
|
|
|
-- applied before entering the Annex monad to run this; that cannot be
|
|
|
|
|
-- changed while running in the Annex monad.
|
2022-06-29 17:28:08 +00:00
|
|
|
|
prepRunCommand :: Command -> AnnexSetter -> Annex ()
|
|
|
|
|
prepRunCommand cmd annexsetter = do
|
2019-06-12 17:33:15 +00:00
|
|
|
|
when (cmdnomessages cmd) $
|
2019-01-04 17:43:53 +00:00
|
|
|
|
Annex.setOutput QuietOutput
|
2022-06-29 17:28:08 +00:00
|
|
|
|
annexStateSetter annexsetter
|
2021-04-06 20:28:37 +00:00
|
|
|
|
whenM (Annex.getRead Annex.debugenabled) $
|
2021-04-05 19:21:20 +00:00
|
|
|
|
enableDebugOutput
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
|
|
|
|
|
findAddonCommand :: Maybe String -> IO (Maybe Command)
|
|
|
|
|
findAddonCommand Nothing = return Nothing
|
|
|
|
|
findAddonCommand (Just subcommandname) =
|
|
|
|
|
searchPath c >>= \case
|
|
|
|
|
Nothing -> return Nothing
|
|
|
|
|
Just p -> return (Just (mkAddonCommand p subcommandname))
|
|
|
|
|
where
|
|
|
|
|
c = "git-annex-" ++ subcommandname
|
|
|
|
|
|
|
|
|
|
findAllAddonCommands :: IO [Command]
|
2021-02-02 23:06:33 +00:00
|
|
|
|
findAllAddonCommands =
|
|
|
|
|
filter isaddoncommand
|
|
|
|
|
. map (\p -> mkAddonCommand p (deprefix p))
|
|
|
|
|
<$> searchPathContents ("git-annex-" `isPrefixOf`)
|
|
|
|
|
where
|
|
|
|
|
deprefix = replace "git-annex-" "" . takeFileName
|
|
|
|
|
isaddoncommand c
|
|
|
|
|
-- git-annex-shell
|
|
|
|
|
| cmdname c == "shell" = False
|
|
|
|
|
-- external special remotes
|
|
|
|
|
| "remote-" `isPrefixOf` cmdname c = False
|
|
|
|
|
-- external backends
|
|
|
|
|
| "backend-" `isPrefixOf` cmdname c = False
|
|
|
|
|
| otherwise = True
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
|
|
|
|
|
mkAddonCommand :: FilePath -> String -> Command
|
|
|
|
|
mkAddonCommand p subcommandname = Command
|
|
|
|
|
{ cmdcheck = []
|
|
|
|
|
, cmdnocommit = True
|
|
|
|
|
, cmdnomessages = True
|
|
|
|
|
, cmdname = subcommandname
|
|
|
|
|
, cmdparamdesc = "[PARAMS]"
|
|
|
|
|
, cmdsection = SectionAddOn
|
|
|
|
|
, cmddesc = "addon command"
|
2022-06-29 17:28:08 +00:00
|
|
|
|
, cmdannexoptions = []
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
|
, cmdinfomod = O.forwardOptions
|
|
|
|
|
, cmdparser = parse
|
|
|
|
|
, cmdnorepo = Just parse
|
|
|
|
|
}
|
|
|
|
|
where
|
|
|
|
|
parse :: (Monad m, MonadIO m) => Parser (m ())
|
|
|
|
|
parse = (liftIO . run) <$> cmdParams "PARAMS"
|
|
|
|
|
|
|
|
|
|
run ps = withCreateProcess (proc p ps) $ \_ _ _ pid ->
|
|
|
|
|
exitWith =<< waitForProcess pid
|