Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- subparser :: Mod CommandFields a -> Parser a
- strArgument :: IsString s => Mod ArgumentFields s -> Parser s
- argument :: ReadM a -> Mod ArgumentFields a -> Parser a
- flag :: a -> a -> Mod FlagFields a -> Parser a
- flag' :: a -> Mod FlagFields a -> Parser a
- switch :: Mod FlagFields Bool -> Parser Bool
- abortOption :: ParseError -> Mod OptionFields (a -> a) -> Parser (a -> a)
- infoOption :: String -> Mod OptionFields (a -> a) -> Parser (a -> a)
- strOption :: IsString s => Mod OptionFields s -> Parser s
- option :: ReadM a -> Mod OptionFields a -> Parser a
- short :: HasName f => Char -> Mod f a
- long :: HasName f => String -> Mod f a
- help :: String -> Mod f a
- helpDoc :: Maybe Doc -> Mod f a
- value :: HasValue f => a -> Mod f a
- showDefaultWith :: (a -> String) -> Mod f a
- showDefault :: Show a => Mod f a
- metavar :: HasMetavar f => String -> Mod f a
- noArgError :: ParseError -> Mod OptionFields a
- data ParseError
- hidden :: Mod f a
- internal :: Mod f a
- style :: (Doc -> Doc) -> Mod f a
- command :: String -> ParserInfo a -> Mod CommandFields a
- commandGroup :: String -> Mod CommandFields a
- completeWith :: HasCompleter f => [String] -> Mod f a
- action :: HasCompleter f => String -> Mod f a
- completer :: HasCompleter f => Completer -> Mod f a
- idm :: Monoid m => m
- mappend :: Monoid a => a -> a -> a
- auto :: Read a => ReadM a
- str :: IsString s => ReadM s
- maybeReader :: (String -> Maybe a) -> ReadM a
- eitherReader :: (String -> Either String a) -> ReadM a
- disabled :: ReadM a
- readerAbort :: ParseError -> ReadM a
- readerError :: String -> ReadM a
- data InfoMod a
- fullDesc :: InfoMod a
- briefDesc :: InfoMod a
- header :: String -> InfoMod a
- headerDoc :: Maybe Doc -> InfoMod a
- footer :: String -> InfoMod a
- footerDoc :: Maybe Doc -> InfoMod a
- progDesc :: String -> InfoMod a
- progDescDoc :: Maybe Doc -> InfoMod a
- failureCode :: Int -> InfoMod a
- noIntersperse :: InfoMod a
- forwardOptions :: InfoMod a
- allPositional :: InfoMod a
- info :: Parser a -> InfoMod a -> ParserInfo a
- data PrefsMod
- multiSuffix :: String -> PrefsMod
- disambiguate :: PrefsMod
- showHelpOnError :: PrefsMod
- showHelpOnEmpty :: PrefsMod
- noBacktrack :: PrefsMod
- subparserInline :: PrefsMod
- columns :: Int -> PrefsMod
- helpLongEquals :: PrefsMod
- helpShowGlobals :: PrefsMod
- helpIndent :: Int -> PrefsMod
- prefs :: PrefsMod -> ParserPrefs
- defaultPrefs :: ParserPrefs
- data Mod f a
- data ReadM a
- data OptionFields a
- data FlagFields a
- data ArgumentFields a
- data CommandFields a
- class HasName f
- class HasCompleter f
- class HasValue f
- class HasMetavar f
Parser builders
This module contains utility functions and combinators to create parsers for individual options.
Each parser builder takes an option modifier. A modifier can be created by
composing the basic modifiers provided by this module using the Monoid
operations mempty
and mappend
, or their aliases idm
and <>
.
For example:
out = strOption ( long "output" <> short 'o' <> metavar "FILENAME" )
creates a parser for an option called "output".
subparser :: Mod CommandFields a -> Parser a Source #
Builder for a command parser. The command
modifier can be used to
specify individual commands.
By default, sub-parsers allow backtracking to their parent's options when
they are completed. To allow full mixing of parent and sub-parser options,
turn on subparserInline
; otherwise, to disable backtracking completely,
use noBacktrack
.
strArgument :: IsString s => Mod ArgumentFields s -> Parser s Source #
Builder for a String
argument.
:: a | default value |
-> a | active value |
-> Mod FlagFields a | option modifier |
-> Parser a |
Builder for a flag parser.
A flag that switches from a "default value" to an "active value" when
encountered. For a simple boolean value, use switch
instead.
Note: Because this parser will never fail, it can not be used with
combinators such as some
or many
, as these combinators continue until
a failure occurs. See flag'
.
:: a | active value |
-> Mod FlagFields a | option modifier |
-> Parser a |
Builder for a flag parser without a default value.
Same as flag
, but with no default value. In particular, this flag will
never parse successfully by itself.
It still makes sense to use it as part of a composite parser. For example
length <$> many (flag' () (short 't'))
is a parser that counts the number of "-t" arguments on the command line, alternatively
flag' True (long "on") <|> flag' False (long "off")
will require the user to enter '--on' or '--off' on the command line.
abortOption :: ParseError -> Mod OptionFields (a -> a) -> Parser (a -> a) Source #
An option that always fails.
When this option is encountered, the option parser immediately aborts with
the given parse error. If you simply want to output a message, use
infoOption
instead.
infoOption :: String -> Mod OptionFields (a -> a) -> Parser (a -> a) Source #
An option that always fails and displays a message.
strOption :: IsString s => Mod OptionFields s -> Parser s Source #
Builder for an option taking a String
argument.
option :: ReadM a -> Mod OptionFields a -> Parser a Source #
Builder for an option using the given reader.
This is a regular option, and should always have either a long
or
short
name specified in the modifiers (or both).
nameParser = option str ( long "name" <> short 'n' )
Modifiers
helpDoc :: Maybe Doc -> Mod f a Source #
Specify the help text for an option as a 'Prettyprinter.Doc AnsiStyle' value.
value :: HasValue f => a -> Mod f a Source #
Specify a default value for an option.
Note: Because this modifier means the parser will never fail,
do not use it with combinators such as some
or many
, as
these combinators continue until a failure occurs.
Careless use will thus result in a hang.
To display the default value, combine with showDefault or showDefaultWith.
showDefaultWith :: (a -> String) -> Mod f a Source #
Specify a function to show the default value for an option.
showDefault :: Show a => Mod f a Source #
Show the default value for this option using its Show
instance.
metavar :: HasMetavar f => String -> Mod f a Source #
Specify a metavariable for the argument.
Metavariables have no effect on the actual parser, and only serve to specify the symbolic name for an argument to be displayed in the help text.
noArgError :: ParseError -> Mod OptionFields a Source #
Specify the error to display when no argument is provided to this option.
data ParseError Source #
ErrorMsg String | |
InfoMsg String | |
ShowHelpText (Maybe String) | |
UnknownError | |
MissingError IsCmdStart SomeParser | |
ExpectsArgError String | |
UnexpectedError String SomeParser |
Instances
Monoid ParseError Source # | |
Defined in Options.Applicative.Types mempty :: ParseError # mappend :: ParseError -> ParseError -> ParseError # mconcat :: [ParseError] -> ParseError # | |
Semigroup ParseError Source # | |
Defined in Options.Applicative.Types (<>) :: ParseError -> ParseError -> ParseError # sconcat :: NonEmpty ParseError -> ParseError # stimes :: Integral b => b -> ParseError -> ParseError # |
Hide this option from the brief description.
Use internal
to hide the option from the help text too.
Hide this option completely from the help text
Use hidden
if the option should remain visible in the full description.
style :: (Doc -> Doc) -> Mod f a Source #
Apply a function to the option description in the usage text.
import Options.Applicative.Help flag' () (short 't' <> style (annotate bold))
NOTE: This builder is more flexible than its name and example
allude. One of the motivating examples for its addition was to
use const
to completely replace the usage text of an option.
command :: String -> ParserInfo a -> Mod CommandFields a Source #
Add a command to a subparser option.
Suggested usage for multiple commands is to add them to a single subparser. e.g.
sample :: Parser Sample sample = subparser ( command "hello" (info hello (progDesc "Print greeting")) <> command "goodbye" (info goodbye (progDesc "Say goodbye")) )
commandGroup :: String -> Mod CommandFields a Source #
completeWith :: HasCompleter f => [String] -> Mod f a Source #
Add a list of possible completion values.
action :: HasCompleter f => String -> Mod f a Source #
Add a bash completion action. Common actions include file
and
directory
. See
http://www.gnu.org/software/bash/manual/html_node/Programmable-Completion-Builtins.html#Programmable-Completion-Builtins
for a complete list.
completer :: HasCompleter f => Completer -> Mod f a Source #
Add a completer to an argument.
A completer is a function String -> IO String which, given a partial argument, returns all possible completions for that argument.
mappend :: Monoid a => a -> a -> a #
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
Readers
A collection of basic Option
readers.
maybeReader :: (String -> Maybe a) -> ReadM a Source #
Convert a function producing a Maybe
into a reader.
eitherReader :: (String -> Either String a) -> ReadM a Source #
Convert a function producing an Either
into a reader.
As an example, one can create a ReadM from an attoparsec Parser easily with
import qualified Data.Attoparsec.Text as A import qualified Data.Text as T attoparsecReader :: A.Parser a -> ReadM a attoparsecReader p = eitherReader (A.parseOnly p . T.pack)
readerAbort :: ParseError -> ReadM a Source #
Abort option reader by exiting with a ParseError
.
readerError :: String -> ReadM a Source #
Abort option reader by exiting with an error message.
Builder for ParserInfo
headerDoc :: Maybe Doc -> InfoMod a Source #
Specify a header for this parser as a 'Prettyprinter.Doc AnsiStyle' value.
footerDoc :: Maybe Doc -> InfoMod a Source #
Specify a footer for this parser as a 'Prettyprinter.Doc AnsiStyle' value.
progDescDoc :: Maybe Doc -> InfoMod a Source #
Specify a short program description as a 'Prettyprinter.Doc AnsiStyle' value.
failureCode :: Int -> InfoMod a Source #
Specify an exit code if a parse error occurs.
noIntersperse :: InfoMod a Source #
Disable parsing of regular options after arguments. After a positional argument is parsed, all remaining options and arguments will be treated as a positional arguments. Not recommended in general as users often expect to be able to freely intersperse regular options and flags within command line options.
forwardOptions :: InfoMod a Source #
Intersperse matched options and arguments normally, but allow unmatched options to be treated as positional arguments. This is sometimes useful if one is wrapping a third party cli tool and needs to pass options through, while also providing a handful of their own options. Not recommended in general as typos by the user may not yield a parse error and cause confusion.
allPositional :: InfoMod a Source #
Disable parsing of regular options completely. All options and arguments will be treated as a positional arguments. Obviously not recommended in general as options will be unreachable. This is the same behaviour one sees after the "--" pseudo-argument.
info :: Parser a -> InfoMod a -> ParserInfo a Source #
Create a ParserInfo
given a Parser
and a modifier.
Builder for ParserPrefs
multiSuffix :: String -> PrefsMod Source #
Include a suffix to attach to the metavar when multiple values can be entered.
disambiguate :: PrefsMod Source #
Turn on disambiguation.
See https://github.com/pcapriotti/optparse-applicative#disambiguation
showHelpOnError :: PrefsMod Source #
Show full help text on any error.
showHelpOnEmpty :: PrefsMod Source #
Show the help text if the user enters only the program name or subcommand.
This will suppress a "Missing:" error and show the full usage instead if a user just types the name of the program.
noBacktrack :: PrefsMod Source #
Turn off backtracking after subcommand is parsed.
subparserInline :: PrefsMod Source #
Allow full mixing of subcommand and parent arguments by inlining selected subparsers into the parent parser.
NOTE: When this option is used, preferences for the subparser which effect the parser behaviour (such as noIntersperse) are ignored.
helpLongEquals :: PrefsMod Source #
Show equals sign, rather than space, in usage and help text for options with long names.
helpShowGlobals :: PrefsMod Source #
Show global help information in subparser usage.
helpIndent :: Int -> PrefsMod Source #
Set fill width in help text presentation.
prefs :: PrefsMod -> ParserPrefs Source #
Create a ParserPrefs
given a modifier
defaultPrefs :: ParserPrefs Source #
Default preferences.
Types
An option modifier.
Option modifiers are values that represent a modification of the properties of an option.
The type parameter a
is the return type of the option, while f
is a
record containing its properties (e.g. OptionFields
for regular options,
FlagFields
for flags, etc...).
An option modifier consists of 3 elements:
- A field modifier, of the form
f a -> f a
. These are essentially (compositions of) setters for some of the properties supported byf
. - An optional default value and function to display it.
- A property modifier, of the form
OptProperties -> OptProperties
. This is just like the field modifier, but for properties applicable to any option.
Modifiers are instances of Monoid
, and can be composed as such.
One rarely needs to deal with modifiers directly, as most of the times it is
sufficient to pass them to builders (such as strOption
or flag
) to
create options (see Builder
).
A newtype over 'ReaderT String Except', used by option readers.
data OptionFields a Source #
Instances
HasCompleter OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal modCompleter :: (Completer -> Completer) -> OptionFields a -> OptionFields a Source # | |
HasMetavar OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal hasMetavarDummy :: OptionFields a -> () Source # | |
HasName OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal name :: OptName -> OptionFields a -> OptionFields a Source # | |
HasValue OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal hasValueDummy :: OptionFields a -> () Source # |
data FlagFields a Source #
Instances
HasName FlagFields Source # | |
Defined in Options.Applicative.Builder.Internal name :: OptName -> FlagFields a -> FlagFields a Source # |
data ArgumentFields a Source #
Instances
HasCompleter ArgumentFields Source # | |
Defined in Options.Applicative.Builder.Internal modCompleter :: (Completer -> Completer) -> ArgumentFields a -> ArgumentFields a Source # | |
HasMetavar ArgumentFields Source # | |
Defined in Options.Applicative.Builder.Internal hasMetavarDummy :: ArgumentFields a -> () Source # | |
HasValue ArgumentFields Source # | |
Defined in Options.Applicative.Builder.Internal hasValueDummy :: ArgumentFields a -> () Source # |
data CommandFields a Source #
Instances
HasMetavar CommandFields Source # | |
Defined in Options.Applicative.Builder.Internal hasMetavarDummy :: CommandFields a -> () Source # |
Instances
HasName FlagFields Source # | |
Defined in Options.Applicative.Builder.Internal name :: OptName -> FlagFields a -> FlagFields a Source # | |
HasName OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal name :: OptName -> OptionFields a -> OptionFields a Source # |
class HasCompleter f Source #
Instances
HasCompleter ArgumentFields Source # | |
Defined in Options.Applicative.Builder.Internal modCompleter :: (Completer -> Completer) -> ArgumentFields a -> ArgumentFields a Source # | |
HasCompleter OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal modCompleter :: (Completer -> Completer) -> OptionFields a -> OptionFields a Source # |
Instances
HasValue ArgumentFields Source # | |
Defined in Options.Applicative.Builder.Internal hasValueDummy :: ArgumentFields a -> () Source # | |
HasValue OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal hasValueDummy :: OptionFields a -> () Source # |
class HasMetavar f Source #
Instances
HasMetavar ArgumentFields Source # | |
Defined in Options.Applicative.Builder.Internal hasMetavarDummy :: ArgumentFields a -> () Source # | |
HasMetavar CommandFields Source # | |
Defined in Options.Applicative.Builder.Internal hasMetavarDummy :: CommandFields a -> () Source # | |
HasMetavar OptionFields Source # | |
Defined in Options.Applicative.Builder.Internal hasMetavarDummy :: OptionFields a -> () Source # |