| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Options.Applicative.Helper
Description
Helper functions to complement Options.Applicative
To use, do something like this:
module Main where
import Options.Applicative
import Options.Applicative.Helper
data ParserResult = Result1
| Result2
| Result3
deriving (Show)
main :: IO ()
main =
do myResult <- helperExecParser myParser (fpDesc "Demonstration")
doSomethingWith myResult
myParser :: Parser ParserResult
myParser =
subconcat [ command "result1"
(infoHelper (pure Result1)
(fpDesc "Result1"))
, command "result2"
(infoHelper (pure Result2)
(fpDesc "Result2"))
, command "result3"
(infoHelper (pure Result3)
(fpDesc "Result3"))
]
doSomethingWith :: ParserResult -> IO ()
doSomethingWith = print- infoHelper :: Parser a -> InfoMod a -> ParserInfo a
- altconcat :: Alternative f => [f a] -> f a
- subconcat :: [Mod CommandFields a] -> Parser a
- fpDesc :: String -> InfoMod a
- helperPrefs :: ParserPrefs
- helperPrefsMod :: PrefsMod
- helperExecParser :: Parser a -> InfoMod a -> IO a
Documentation
infoHelper :: Parser a -> InfoMod a -> ParserInfo a Source
altconcat :: Alternative f => [f a] -> f a Source
Sort of like mconcat for Alternatives
Instead of
foo <|> bar <|> baz <|> quux <|> ...
Now, it's just
altconcat [ foo
, bar
, baz
, quux
...
]subconcat :: [Mod CommandFields a] -> Parser a Source
altconcat . fmap subparser
Instead of
subparser (command "foo" ...) <|> subparser (command "bar" ...) <|> subparser (command "baz" ...) ...
Instead it's
subconcat [ command "foo" ...
, command "bar" ...
, command "baz" ...
...
]fpDesc :: String -> InfoMod a Source
mappend fullDesc . progDesc
mconcat [ fullDesc
, progDesc "whatever"
...
]Now, it's just
mconcat [ fpDesc "whatever"
...
]helperPrefs :: ParserPrefs Source
Preferences that I like. Using these preferences, your app will
- disambiguate shortened subcommands
- show help whenever someone makes an error.
Note that you should use this in combination with infoHelper for
maximum helpfulness.
prefs helperPrefsMod
helperPrefsMod :: PrefsMod Source
The PrefsMod for helperPrefs so that you can add on your own
preferences.
mappend disambiguate showHelpOnError
helperExecParser :: Parser a -> InfoMod a -> IO a Source
Wrapper around customExecParser, helperPrefs, and infoHelper
helperExecParser a b = customExecParser helperPrefs (infoHelper a b)