optparse-applicative-0.9.0: Utilities and combinators for parsing command line options

Safe HaskellSafe-Inferred

Options.Applicative.Builder

Contents

Synopsis

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.

flagSource

Arguments

:: 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.

flag'Source

Arguments

:: 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

short :: HasName f => Char -> Mod f aSource

Specify a short name for an option.

long :: HasName f => String -> Mod f aSource

Specify a long name for an option.

help :: String -> Mod f aSource

Specify the help text for an option.

helpDoc :: Maybe Doc -> Mod f aSource

Specify the help text for an option as a Doc value.

value :: HasValue f => a -> Mod f aSource

Specify a default value for an option.

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.

reader :: (String -> ReadM a) -> Mod OptionFields aSource

Specify the Option reader.

eitherReader :: (String -> Either String a) -> Mod OptionFields aSource

Specify the Option reader as a function in the Either monad.

noArgError :: ParseError -> Mod OptionFields aSource

Specify the error to display when no argument is provided to this option.

hidden :: Mod f aSource

Hide this option from the brief description.

internal :: Mod f aSource

Hide this option from the help text

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.

idm :: Monoid m => mSource

Trivial option modifier.

(&) :: Monoid m => m -> m -> mSource

Deprecated: Use () instead

Compose modifiers.

(<>) :: Monoid m => m -> m -> m

An infix synonym for mappend.

mappend :: Monoid a => a -> a -> a

An associative operation

Readers

A collection of basic Option readers.

auto :: Monad m => Read a => String -> m aSource

Option reader based on the Read type class.

str :: Monad m => String -> m StringSource

String Option reader.

disabled :: Monad m => String -> m aSource

Null Option reader. All arguments will fail validation.

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

data InfoMod a Source

Modifier for ParserInfo.

Instances

fullDesc :: InfoMod aSource

Show a full description in the help text of this parser.

briefDesc :: InfoMod aSource

Only show a brief description in the help text of this parser.

header :: String -> InfoMod aSource

Specify a header for this parser.

headerDoc :: Maybe Doc -> InfoMod aSource

Specify a header for this parser as a Doc value.

footer :: String -> InfoMod aSource

Specify a footer for this parser.

footerDoc :: Maybe Doc -> InfoMod aSource

Specify a footer for this parser as a Doc value.

progDesc :: String -> InfoMod aSource

Specify a short program description.

progDescDoc :: Maybe Doc -> InfoMod aSource

Specify a short program description as a Doc value.

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

Types

data Mod f a Source

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 by f.
  • 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).

Instances

Monoid (Mod f a) 

data ReadM a Source

A newtype over the Either monad used by option readers.