Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
- subparser :: Mod CommandFields a -> Parser a
- strArgument :: Mod ArgumentFields String -> Parser String
- 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 :: Mod OptionFields String -> Parser String
- option :: ReadM a -> Mod OptionFields a -> Parser a
- nullOption :: 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
- eitherReader :: (String -> Either String a) -> ReadM a
- noArgError :: ParseError -> Mod OptionFields a
- data ParseError
- hidden :: Mod f a
- internal :: Mod f a
- command :: String -> ParserInfo a -> 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
- (<>) :: Monoid m => m -> m -> m
- mappend :: Monoid a => a -> a -> a
- auto :: Read a => ReadM a
- str :: ReadM String
- 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
- info :: Parser a -> InfoMod a -> ParserInfo a
- data PrefsMod
- multiSuffix :: String -> PrefsMod
- disambiguate :: PrefsMod
- showHelpOnError :: PrefsMod
- noBacktrack :: PrefsMod
- columns :: 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
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.
strArgument :: Mod ArgumentFields String -> Parser String 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.
:: 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.
switch :: Mod FlagFields Bool -> Parser Bool Source
Builder for a boolean flag.
switch = flag False True
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 :: Mod OptionFields String -> Parser String 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.
nullOption :: ReadM a -> Mod OptionFields a -> Parser a Source
Modifiers
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.
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.
eitherReader :: (String -> Either String a) -> ReadM a Source
Convert a function in the Either
monad to a reader.
noArgError :: ParseError -> Mod OptionFields a Source
Specify the error to display when no argument is provided to this option.
data ParseError Source
command :: String -> ParserInfo a -> Mod CommandFields a Source
Add a command to a subparser option.
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.
Readers
A collection of basic Option
readers.
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
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
info :: Parser a -> InfoMod a -> ParserInfo a Source
Create a ParserInfo
given a Parser
and a modifier.
Builder for ParserPrefs
multiSuffix :: String -> PrefsMod Source
prefs :: PrefsMod -> ParserPrefs Source
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.
You rarely need 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
data FlagFields a Source
data ArgumentFields a Source