In my Haskell executable, created using optparse-applicative
, I would like to have a global option for --version
alongside the global --help
option that is available from all subcommands. However the example provided (see below) for adding a --version
option to to a CLI with subcommands results in a --version
option that is inconsistently available
$ cli create --version
Invalid option `--version'
Usage: cli create NAME
Create a thing
$ cli delete --version
0.0
and never shows up in help for subcommands
$ cli create -h
Usage: cli create NAME
Create a thing
Available options:
NAME Name of the thing to create
-h,--help Show this help text
$ cli delete -h
Usage: cli delete
Delete the thing
Available options:
-h,--help Show this help text
The behavior I would like is for --version
to be available globally and to all subcommands:
$ cli create -h
Usage: cli create NAME
Create a thing
Available options:
NAME Name of the thing to create
--version Show version
-h,--help Show this help text
$ cli delete -h
Usage: cli delete
Delete the thing
Available options:
--version Show version
-h,--help Show this help text
$ cli create --version
0.0
$ cli delete --version
0.0
It's not clear from the documentation how to achieve this.
In fact, I'd ideally like to be able to clearly group options in the help output:
$ cli create -h
Usage: cli create NAME
Create a thing
Arguments:
NAME Name of the thing to create
Global options:
--version Show version
-h,--help Show this help text
$ cli delete -h
Usage: cli delete
Delete the thing
Global options:
--version Show version
-h,--help Show this help text
Is there a way to achieve this using optparse-applicative
?
{-#LANGUAGE ScopedTypeVariables#-}
import Data.Semigroup ((<>))
import Options.Applicative
data Opts = Opts
{ optGlobalFlag :: !Bool
, optCommand :: !Command
}
data Command
= Create String
| Delete
main :: IO ()
main = do
(opts :: Opts) <- execParser optsParser
case optCommand opts of
Create name -> putStrLn ("Created the thing named " ++ name)
Delete -> putStrLn "Deleted the thing!"
putStrLn ("global flag: " ++ show (optGlobalFlag opts))
where
optsParser :: ParserInfo Opts
optsParser =
info
(helper <*> versionOption <*> programOptions)
(fullDesc <> progDesc "optparse subcommands example" <>
header
"optparse-sub-example - a small example program for optparse-applicative with subcommands")
versionOption :: Parser (a -> a)
versionOption = infoOption "0.0" (long "version" <> help "Show version")
programOptions :: Parser Opts
programOptions =
Opts <$> switch (long "global-flag" <> help "Set a global flag") <*>
hsubparser (createCommand <> deleteCommand)
createCommand :: Mod CommandFields Command
createCommand =
command
"create"
(info createOptions (progDesc "Create a thing"))
createOptions :: Parser Command
createOptions =
Create <$>
strArgument (metavar "NAME" <> help "Name of the thing to create")
deleteCommand :: Mod CommandFields Command
deleteCommand =
command
"delete"
(info (pure Delete) (progDesc "Delete the thing"))
As far as I know, this (in particular, the categorized help text) isn't really easy to do with optparse-applicative
, since it isn't quite the pattern that they were planning for with global arguments. If you are okay with using program --global-options command --local-options
(which is a fairly standard pattern) instead of program command --global-and-local-options
, then you can use the approach shown in the linked example:
$ ./optparse-sub-example
optparse-sub-example - a small example program for optparse-applicative with
subcommands
Usage: optparse [--version] [--global-flag] COMMAND
optparse subcommands example
Available options:
-h,--help Show this help text
--version Show version
--global-flag Set a global flag
Available commands:
create Create a thing
delete Delete the thing
$ ./optparse-sub-example --version create
0.0
$ ./optparse-sub-example --version delete
0.0
$ ./optparse-sub-example --global-flag create HI
Created the thing named HI
global flag: True
$ ./optparse-sub-example --global-flag delete
Deleted the thing!
global flag: True
(Note: I would advise going with this approach, since "global options before the command" is fairly standard).
If you also want the global options to be available in every subcommand, you will have a few issues.
subparser
-like function that adds your global options & merges them with any global options before the command.For #2, one way to restructure the example to support this might be something along these lines:
To start with, standard boilerplate and imports:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ApplicativeDo #-}
import Data.Monoid
import Data.Semigroup ((<>))
import Options.Applicative
import Options.Applicative.Types
Opts
are explicitly split into optGlobals
and optCommand
, making it easy to deal with all of the global options at once if more are available:
data Opts = Opts
{ optGlobals :: !GlobalOpts
, optCommand :: !Command
}
data GlobalOpts = GlobalOpts { optGlobalFlag :: Bool }
GlobalOpts
should be a Semigroup
and a Monoid
, since we need to merge options seen at various different points (before the command, after the command, etc.). It should also be possible, with suitable alterations to mysubparser
below, to require global options to be given only after commands and omit this requirement.
instance Semigroup GlobalOpts where
-- Code for merging option parser results from the multiple parsers run
-- at various different places. Note that this may be run with the default
-- values returned by one parser (from a location with no options present)
-- and the true option values from another, so it may be important
-- to distinguish between "the default value" and "no option" (since "no
-- option" shouldn't override another value provided earlier, while
-- "user-supplied value that happens to match the default" probably should).
--
-- In this case this doesn't matter, since the flag being provided anywhere
-- should be enough for it to be considered true.
(GlobalOpts f1) <> (GlobalOpts f2) = GlobalOpts (f1 || f2)
instance Monoid GlobalOpts where
-- Default values for the various options. These should probably match the
-- defaults used in the option declarations.
mempty = GlobalOpts False
As before, a Command
type to represent the different possible commands:
data Command
= Create String
| Delete
The real magic: mysubparser
wraps hsubparser
to add global options and deal with merging them. It takes the parser for global options as an argument:
mysubparser :: forall a b. Monoid a
=> Parser a
-> Mod CommandFields b
-> Parser (a, b)
mysubparser globals cmds = do
To start with, it runs the global parser (to catch any globals given before a command):
g1 <- globals
It then uses hsubparser
to get a command parser, and modifies it to also parse global options:
(g2, r) <- addGlobals $ hsubparser cmds
Finally, it merges the two global option sets, and returns the parsed global options and the command parser result:
pure (g1 <> g2, r)
where
The addGlobals
helper function:
addGlobals :: forall c. Parser c -> Parser (a, c)
If NilP
was given, we just use mempty
to get the default option set:
addGlobals (NilP x) = NilP $ (mempty,) <$> x
The important case: if we have an OptP
around an Option
that uses a CommandReader
, the globals
parser is added to every command parser:
addGlobals (OptP (Option (CmdReader n cs g) ps)) =
OptP (Option (CmdReader n cs $ fmap go . g) ps)
where go pi = pi { infoParser = (,) <$> globals <*> infoParser pi }
In all other cases, either just use the default option set, or merge option sets from recursive Parser
s as appropriate:
addGlobals (OptP o) = OptP ((mempty,) <$> o)
addGlobals (AltP p1 p2) = AltP (addGlobals p1) (addGlobals p2)
addGlobals (MultP p1 p2) =
MultP ((\(g2, f) -> \(g1, x) -> (g1 <> g2, f x)) <$> addGlobals p1)
(addGlobals p2)
addGlobals (BindP p k) = BindP (addGlobals p) $ \(g1, x) ->
BindP (addGlobals $ k x) $ \(g2, x') ->
pure (g1 <> g2, x')
Modifications to the main
function are fairly minimal, and mostly related to using the new GlobalOpts
. Once a parser for GlobalOpts
is available, passing it to mysubparser
is quite easy:
main :: IO ()
main = do
(opts :: Opts) <- execParser optsParser
case optCommand opts of
Create name -> putStrLn ("Created the thing named " ++ name)
Delete -> putStrLn "Deleted the thing!"
putStrLn ("global flag: " ++ show (optGlobalFlag (optGlobals opts)))
where
optsParser :: ParserInfo Opts
optsParser =
info
(helper <*> programOptions)
(fullDesc <> progDesc "optparse subcommands example" <>
header
"optparse-sub-example - a small example program for optparse-applicative with subcommands")
versionOption :: Parser (a -> a)
versionOption = infoOption "0.0" (long "version" <> help "Show version")
globalOpts :: Parser GlobalOpts
globalOpts = versionOption <*>
(GlobalOpts <$> switch (long "global-flag" <> help "Set a global flag"))
programOptions :: Parser Opts
programOptions =
uncurry Opts <$> mysubparser globalOpts (createCommand <> deleteCommand)
createCommand :: Mod CommandFields Command
createCommand =
command
"create"
(info createOptions (progDesc "Create a thing"))
createOptions :: Parser Command
createOptions =
Create <$>
strArgument (metavar "NAME" <> help "Name of the thing to create")
deleteCommand :: Mod CommandFields Command
deleteCommand =
command
"delete"
(info (pure Delete) (progDesc "Delete the thing"))
Notice that mysubparser
should be a quite generic/reusable component.
This exhibits behavior closer to what you wanted:
$ ./optparse-sub-example create --global-flag HI
Created the thing named HI
global flag: True
$ ./optparse-sub-example --global-flag create HI
Created the thing named HI
global flag: True
$ ./optparse-sub-example --global-flag delete
Deleted the thing!
global flag: True
$ ./optparse-sub-example delete --global-flag
Deleted the thing!
global flag: True
$ ./optparse-sub-example delete
Deleted the thing!
global flag: False
$ ./optparse-sub-example delete --version
0.0
$ ./optparse-sub-example create --version
0.0
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With