Safe Haskell | Safe-Inferred |
---|
- subparser :: Mod CommandFields a -> Parser a
- argument :: (String -> Maybe a) -> Mod ArgumentFields a -> Parser a
- arguments :: (String -> Maybe a) -> Mod ArgumentFields a -> Parser [a]
- arguments1 :: (String -> Maybe 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
- nullOption :: Mod OptionFields a -> Parser a
- 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 :: Read 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
- reader :: (String -> ReadM a) -> Mod OptionFields a
- eitherReader :: (String -> Either String a) -> Mod OptionFields a
- noArgError :: ParseError -> Mod OptionFields a
- data ParseError
- = ErrorMsg String
- | InfoMsg String
- | ShowHelpText
- 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
- (<>) :: Monoid m => m -> m -> m
- mappend :: Monoid a => a -> a -> a
- auto :: Monad m => Read a => String -> m a
- str :: Monad m => String -> m String
- disabled :: Monad m => String -> m 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
- 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 aSource
Builder for a command parser. The command
modifier can be used to
specify individual commands.
argument :: (String -> Maybe a) -> Mod ArgumentFields a -> Parser aSource
Builder for an argument parser.
arguments :: (String -> Maybe a) -> Mod ArgumentFields a -> Parser [a]Source
Deprecated: Use many and argument instead
Builder for an argument list parser. All arguments are collected and returned as a list.
arguments1 :: (String -> Maybe a) -> Mod ArgumentFields a -> Parser [a]Source
Deprecated: Use some and argument instead
Like arguments
, but require at least one 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 BoolSource
Builder for a boolean flag.
switch = flag False True
nullOption :: Mod OptionFields a -> Parser aSource
Builder for an option with a null reader. A non-trivial reader can be
added using the reader
modifier.
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 StringSource
Builder for an option taking a String
argument.
option :: Read a => Mod OptionFields a -> Parser aSource
Builder for an option using the auto
reader.
Modifiers
showDefaultWith :: (a -> String) -> Mod f aSource
Specify a function to show the default value for an option.
showDefault :: Show a => Mod f aSource
Show the default value for this option using its Show
instance.
metavar :: HasMetavar f => String -> Mod f aSource
Specify the metavariable.
eitherReader :: (String -> Either String a) -> Mod OptionFields aSource
noArgError :: ParseError -> Mod OptionFields aSource
Specify the error to display when no argument is provided to this option.
command :: String -> ParserInfo a -> Mod CommandFields aSource
Add a command to a subparser option.
completeWith :: HasCompleter f => [String] -> Mod f aSource
Add a list of possible completion values.
action :: HasCompleter f => String -> Mod f aSource
Add a bash completion action. Common actions include file
and
directory
. See
http:www.gnu.orgsoftwarebashmanualhtml_node/Programmable-Completion-Builtins.html#Programmable-Completion-Builtins
for a complete list.
completer :: HasCompleter f => Completer -> Mod f aSource
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 aSource
Abort option reader by exiting with a ParseError
.
readerError :: String -> ReadM aSource
Abort option reader by exiting with an error message.
Builder for ParserInfo
failureCode :: Int -> InfoMod aSource
Specify an exit code if a parse error occurs.
noIntersperse :: InfoMod aSource
Disable parsing of regular options after arguments
info :: Parser a -> InfoMod a -> ParserInfo aSource
Create a ParserInfo
given a Parser
and a modifier.
Builder for ParserPrefs
multiSuffix :: String -> PrefsModSource
prefs :: PrefsMod -> ParserPrefsSource
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 the Either
monad used by option readers.
data OptionFields a Source
data FlagFields a Source
data ArgumentFields a Source