improve global options display in --help

Put them in the help of subcommands, not the main command.

And, hide them from the synopsis, to avoid cluttering it.
This commit is contained in:
Joey Hess 2015-07-10 02:18:08 -04:00
parent b66a2d6c5b
commit 7af0893abd
6 changed files with 50 additions and 17 deletions

View file

@ -31,6 +31,7 @@ import Annex.Content
import Annex.Environment import Annex.Environment
import Command import Command
import Types.Messages import Types.Messages
import CmdLine.GlobalSetter
{- Runs the passed command line. -} {- Runs the passed command line. -}
dispatch :: Bool -> CmdParams -> [Command] -> [Parser GlobalSetter] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO () dispatch :: Bool -> CmdParams -> [Command] -> [Parser GlobalSetter] -> [(String, String)] -> IO Git.Repo -> String -> String -> IO ()
@ -43,7 +44,7 @@ dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progde
Annex.eval state $ do Annex.eval state $ do
checkEnvironment checkEnvironment
forM_ fields $ uncurry Annex.setField forM_ fields $ uncurry Annex.setField
((cmd, seek), globalconfig) <- parsewith cmdparser (cmd, seek, globalconfig) <- parsewith cmdparser
(\a -> inRepo $ a . Just) (\a -> inRepo $ a . Just)
when (cmdnomessages cmd) $ when (cmdnomessages cmd) $
Annex.setOutput QuietOutput Annex.setOutput QuietOutput
@ -54,7 +55,7 @@ dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progde
performCommandAction cmd seek $ performCommandAction cmd seek $
shutdown $ cmdnocommit cmd shutdown $ cmdnocommit cmd
go (Left norepo) = do go (Left norepo) = do
((_, a), _) <- parsewith (_, a, _globalconfig) <- parsewith
(fromMaybe (throw norepo) . cmdnorepo) (fromMaybe (throw norepo) . cmdnorepo)
(\a -> a =<< Git.Config.global) (\a -> a =<< Git.Config.global)
a a
@ -81,20 +82,19 @@ dispatch fuzzyok allargs allcmds globaloptions fields getgitrepo progname progde
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 -> [Parser GlobalSetter] -> CmdParams -> [Command] -> (Command -> O.Parser v) -> O.ParserResult ((Command, v), GlobalSetter) parseCmd :: String -> String -> [Parser GlobalSetter] -> CmdParams -> [Command] -> (Command -> O.Parser v) -> O.ParserResult (Command, v, GlobalSetter)
parseCmd progname progdesc globaloptions allargs allcmds getparser = parseCmd progname progdesc globaloptions allargs allcmds getparser =
O.execParserPure (O.prefs O.idm) pinfo allargs O.execParserPure (O.prefs O.idm) pinfo allargs
where where
pinfo = O.info pinfo = O.info (O.helper <*> subcmds) (O.progDescDoc (Just intro))
(O.helper <*> ((,) <$> subcmds <*> combineGlobalSetters globaloptions))
(O.progDescDoc (Just intro))
subcmds = O.hsubparser $ mconcat $ map mkcommand allcmds subcmds = O.hsubparser $ mconcat $ map mkcommand allcmds
mkcommand c = O.command (cmdname c) $ O.info (mkparser c) $ O.fullDesc mkcommand c = O.command (cmdname c) $ O.info (mkparser c) $ O.fullDesc
<> O.header (synopsis (progname ++ " " ++ cmdname c) (cmddesc c)) <> O.header (synopsis (progname ++ " " ++ cmdname c) (cmddesc c))
<> O.footer ("For details, run: " ++ progname ++ " help " ++ cmdname c) <> O.footer ("For details, run: " ++ progname ++ " help " ++ cmdname c)
mkparser c = (,) mkparser c = (,,)
<$> pure c <$> pure c
<*> getparser c <*> getparser c
<*> combineGlobalSetters globaloptions
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)

View file

@ -26,6 +26,7 @@ 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
-- Global options that are accepted by all git-annex sub-commands, -- Global options that are accepted by all git-annex sub-commands,
-- although not always used. -- although not always used.
@ -34,38 +35,47 @@ gitAnnexGlobalOptions = commonGlobalOptions ++
[ globalSetter setnumcopies $ option auto [ globalSetter setnumcopies $ option auto
( long "numcopies" <> short 'N' <> metavar paramNumber ( long "numcopies" <> short 'N' <> metavar paramNumber
<> help "override default number of copies" <> help "override default number of copies"
<> hidden
) )
, globalSetter (Remote.forceTrust Trusted) $ strOption , globalSetter (Remote.forceTrust Trusted) $ strOption
( long "trust" <> metavar paramRemote ( long "trust" <> metavar paramRemote
<> help "override trust setting" <> help "override trust setting"
<> hidden
) )
, globalSetter (Remote.forceTrust SemiTrusted) $ strOption , globalSetter (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
) )
, globalSetter (Remote.forceTrust UnTrusted) $ strOption , globalSetter (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
) )
, globalSetter setgitconfig $ strOption , globalSetter 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
) )
, globalSetter setuseragent $ strOption , globalSetter setuseragent $ strOption
( long "user-agent" <> metavar paramName ( long "user-agent" <> metavar paramName
<> help "override default User-Agent" <> help "override default User-Agent"
<> hidden
) )
, globalFlag (Annex.setFlag "trustglacier") , globalFlag (Annex.setFlag "trustglacier")
( long "trust-glacier" ( long "trust-glacier"
<> help "Trust Amazon Glacier inventory" <> help "Trust Amazon Glacier inventory"
<> hidden
) )
, globalFlag (setdesktopnotify mkNotifyFinish) , globalFlag (setdesktopnotify mkNotifyFinish)
( long "notify-finish" ( long "notify-finish"
<> help "show desktop notification after transfer finishes" <> help "show desktop notification after transfer finishes"
<> hidden
) )
, globalFlag (setdesktopnotify mkNotifyStart) , globalFlag (setdesktopnotify mkNotifyStart)
( long "notify-start" ( long "notify-start"
<> help "show desktop notification after transfer completes" <> help "show desktop notification after transfer completes"
<> hidden
) )
] ]
where where

View file

@ -13,6 +13,7 @@ import Common.Annex
import qualified Git.Construct import qualified Git.Construct
import qualified Git.Config import qualified Git.Config
import CmdLine import CmdLine
import CmdLine.GlobalSetter
import Command import Command
import Annex.UUID import Annex.UUID
import CmdLine.GitAnnexShell.Fields import CmdLine.GitAnnexShell.Fields

24
CmdLine/GlobalSetter.hs Normal file
View file

@ -0,0 +1,24 @@
{- git-annex global options
-
- Copyright 2015 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module CmdLine.GlobalSetter where
import Types.DeferredParse
import Common
import Annex
import Options.Applicative
globalFlag :: Annex () -> Mod FlagFields GlobalSetter -> Parser GlobalSetter
globalFlag setter = flag' (DeferredParse setter)
globalSetter :: (v -> Annex ()) -> Parser v -> Parser GlobalSetter
globalSetter setter parser = DeferredParse . setter <$> parser
combineGlobalSetters :: [Parser GlobalSetter] -> Parser GlobalSetter
combineGlobalSetters l = DeferredParse . sequence_ . map getParsed
<$> many (foldl1 (<|>) l)

View file

@ -20,6 +20,7 @@ import System.Console.GetOpt
import Common.Annex import Common.Annex
import CmdLine.Usage import CmdLine.Usage
import CmdLine.GlobalSetter
import qualified Annex import qualified Annex
import Types.Messages import Types.Messages
import Types.DeferredParse import Types.DeferredParse
@ -30,30 +31,37 @@ commonGlobalOptions =
[ globalFlag (setforce True) [ globalFlag (setforce True)
( long "force" ( long "force"
<> help "allow actions that may lose annexed data" <> help "allow actions that may lose annexed data"
<> hidden
) )
, globalFlag (setfast True) , globalFlag (setfast True)
( long "fast" <> short 'F' ( long "fast" <> short 'F'
<> help "avoid slow operations" <> help "avoid slow operations"
<> hidden
) )
, globalFlag (Annex.setOutput QuietOutput) , globalFlag (Annex.setOutput QuietOutput)
( long "quiet" <> short 'q' ( long "quiet" <> short 'q'
<> help "avoid verbose output" <> help "avoid verbose output"
<> hidden
) )
, globalFlag (Annex.setOutput NormalOutput) , globalFlag (Annex.setOutput NormalOutput)
( long "verbose" <> short 'v' ( long "verbose" <> short 'v'
<> help "allow verbose output (default)" <> help "allow verbose output (default)"
<> hidden
) )
, globalFlag setdebug , globalFlag setdebug
( long "debug" <> short 'd' ( long "debug" <> short 'd'
<> help "show debug messages" <> help "show debug messages"
<> hidden
) )
, globalFlag unsetdebug , globalFlag unsetdebug
( long "no-debug" ( long "no-debug"
<> help "don't show debug messages" <> help "don't show debug messages"
<> hidden
) )
, globalSetter setforcebackend $ strOption , globalSetter setforcebackend $ strOption
( long "backend" <> short 'b' <> metavar paramName ( long "backend" <> short 'b' <> metavar paramName
<> help "specify key-value backend to use" <> help "specify key-value backend to use"
<> hidden
) )
] ]
where where

View file

@ -39,13 +39,3 @@ instance DeferredParseClass [DeferredParse a] where
-- Use when the Annex action modifies Annex state. -- Use when the Annex action modifies Annex state.
type GlobalSetter = DeferredParse () type GlobalSetter = DeferredParse ()
globalFlag :: Annex () -> Mod FlagFields GlobalSetter -> Parser GlobalSetter
globalFlag setter = flag' (DeferredParse setter)
globalSetter :: (v -> Annex ()) -> Parser v -> Parser GlobalSetter
globalSetter setter parser = DeferredParse . setter <$> parser
combineGlobalSetters :: [Parser GlobalSetter] -> Parser GlobalSetter
combineGlobalSetters l = DeferredParse . sequence_ . map getParsed
<$> many (foldl1 (<|>) l)