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

Safe HaskellSafe
LanguageHaskell98

Options.Applicative

Contents

Synopsis

Applicative option parsers

This module exports all one should need for defining and using optparse-applicative command line option parsers.

See https://github.com/pcapriotti/optparse-applicative for a tutorial, and a general introduction to applicative option parsers.

See the sections below for more detail

Exported modules

The standard Applicative module is re-exported here for convenience.

Option Parsers

A Parser is the core type in optparse-applicative. A value of type Parser a represents a specification for a set of options, which will yield a value of type a when the command line arguments are successfully parsed.

There are several types of primitive Parser.

  • Flags: simple no-argument options. When a flag is encountered on the command line, its value is returned.
  • Options: options with an argument. An option can define a reader, which converts its argument from String to the desired value, or throws a parse error if the argument does not validate correctly.
  • Arguments: positional arguments, validated in the same way as option arguments.
  • Commands. A command defines a completely independent sub-parser. When a command is encountered, the whole command line is passed to the corresponding parser.

See the "Parser Builders" section for how to construct and customise these parsers.

data Parser a Source #

A Parser a is an option parser returning a value of type a.

Instances
Functor Parser Source # 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Applicative Parser Source # 
Instance details

Defined in Options.Applicative.Types

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser Source # 
Instance details

Defined in Options.Applicative.Types

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

Parser builders

This section 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 here 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".

flag Source #

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.

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

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, alternatively

flag' True (long "on") <|> flag' False (long "off")

will require the user to enter '--on' or '--off' on the command line.

switch :: Mod FlagFields Bool -> Parser Bool Source #

Builder for a boolean flag.

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

switch = flag False True

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' )

strArgument :: IsString s => Mod ArgumentFields s -> Parser s Source #

Builder for a String argument.

argument :: ReadM a -> Mod ArgumentFields a -> Parser a Source #

Builder for an argument parser.

subparser :: Mod CommandFields a -> Parser a Source #

Builder for a command parser. The command modifier can be used to specify individual commands.

hsubparser :: Mod CommandFields a -> Parser a Source #

Builder for a command parser with a "helper" option attached. Used in the same way as subparser, but includes a "--help|-h" inside the subcommand.

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.

helper :: Parser (a -> a) Source #

A hidden "helper" option which always fails.

A common usage pattern is to apply this applicatively when creating a ParserInfo

opts :: ParserInfo Sample
opts = info (sample <**> helper) mempty

Modifiers

Parser builders take a modifier, which represents a modification of the properties of an option, and can be composed as a monoid.

Contraints are often used to ensure that the modifiers can be sensibly applied. For example, positional arguments can't be specified by long or short names, so the HasName constraint is used to ensure we have a flag or option.

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.

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

Instances
Semigroup (Mod f a) Source #

Since: 0.13.0.0

Instance details

Defined in Options.Applicative.Builder.Internal

Methods

(<>) :: Mod f a -> Mod f a -> Mod f a #

sconcat :: NonEmpty (Mod f a) -> Mod f a #

stimes :: Integral b => b -> Mod f a -> Mod f a #

Monoid (Mod f a) Source # 
Instance details

Defined in Options.Applicative.Builder.Internal

Methods

mempty :: Mod f a #

mappend :: Mod f a -> Mod f a -> Mod f a #

mconcat :: [Mod f a] -> Mod f a #

short :: HasName f => Char -> Mod f a Source #

Specify a short name for an option.

long :: HasName f => String -> Mod f a Source #

Specify a long name for an option.

help :: String -> Mod f a Source #

Specify the help text for an option.

helpDoc :: Maybe Doc -> Mod f a Source #

Specify the help text for an option as a Doc 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.

hidden :: Mod f a Source #

Hide this option from the brief description.

internal :: Mod f a Source #

Hide this option from the help text

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 bold)

NOTE: This builder is more flexible than its name and example allude. One of the motivating examples for its addition was to used 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 #

Add a description to a group of commands.

Advanced feature for separating logical groups of commands on the parse line.

If using the same metavar for each group of commands, it may yield a more attractive usage text combined with hidden for some groups.

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.

idm :: Monoid m => m Source #

Trivial option modifier.

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

An associative operation

NOTE: This method is redundant and has the default implementation mappend = '(<>)' since base-4.11.0.0.

data FlagFields a Source #

Instances
HasName FlagFields Source # 
Instance details

Defined in Options.Applicative.Builder.Internal

class HasName f Source #

Minimal complete definition

name

class HasValue f Source #

Minimal complete definition

hasValueDummy

Readers

A reader is used by the option and argument builders to parse the data passed by the user on the command line into a data type.

The most common are str which is used for String like types, including ByteString and Text; and auto, which uses the Read typeclass, and is good for simple types like Int or Double.

More complex types can use the eitherReader or maybeReader functions to pattern match or use a more expressive parser like a member of the Parsec family.

data ReadM a Source #

A newtype over 'ReaderT String Except', used by option readers.

Instances
Monad ReadM Source # 
Instance details

Defined in Options.Applicative.Types

Methods

(>>=) :: ReadM a -> (a -> ReadM b) -> ReadM b #

(>>) :: ReadM a -> ReadM b -> ReadM b #

return :: a -> ReadM a #

fail :: String -> ReadM a #

Functor ReadM Source # 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> ReadM a -> ReadM b #

(<$) :: a -> ReadM b -> ReadM a #

MonadFail ReadM Source # 
Instance details

Defined in Options.Applicative.Types

Methods

fail :: String -> ReadM a #

Applicative ReadM Source # 
Instance details

Defined in Options.Applicative.Types

Methods

pure :: a -> ReadM a #

(<*>) :: ReadM (a -> b) -> ReadM a -> ReadM b #

liftA2 :: (a -> b -> c) -> ReadM a -> ReadM b -> ReadM c #

(*>) :: ReadM a -> ReadM b -> ReadM b #

(<*) :: ReadM a -> ReadM b -> ReadM a #

Alternative ReadM Source # 
Instance details

Defined in Options.Applicative.Types

Methods

empty :: ReadM a #

(<|>) :: ReadM a -> ReadM a -> ReadM a #

some :: ReadM a -> ReadM [a] #

many :: ReadM a -> ReadM [a] #

MonadPlus ReadM Source # 
Instance details

Defined in Options.Applicative.Types

Methods

mzero :: ReadM a #

mplus :: ReadM a -> ReadM a -> ReadM a #

auto :: Read a => ReadM a Source #

Option reader based on the Read type class.

str :: IsString s => ReadM s Source #

String Option reader.

Polymorphic over the IsString type class since 0.14.

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)

disabled :: ReadM a Source #

Null Option reader. All arguments will fail validation.

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.

Program descriptions

ParserInfo

A ParserInfo describes a command line program, used to generate a help screen. Two help modes are supported: brief and full. In brief mode, only an option and argument summary is displayed, while in full mode each available option and command, including hidden ones, is described.

A ParserInfo should be created with the info function and a set of InfoMod modifiers.

info :: Parser a -> InfoMod a -> ParserInfo a Source #

Create a ParserInfo given a Parser and a modifier.

data ParserInfo a Source #

A full description for a runnable Parser for a program.

Constructors

ParserInfo 

Fields

Instances
Functor ParserInfo Source # 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> ParserInfo a -> ParserInfo b #

(<$) :: a -> ParserInfo b -> ParserInfo a #

data InfoMod a Source #

Modifier for ParserInfo.

Instances
Semigroup (InfoMod a) Source # 
Instance details

Defined in Options.Applicative.Builder

Methods

(<>) :: InfoMod a -> InfoMod a -> InfoMod a #

sconcat :: NonEmpty (InfoMod a) -> InfoMod a #

stimes :: Integral b => b -> InfoMod a -> InfoMod a #

Monoid (InfoMod a) Source # 
Instance details

Defined in Options.Applicative.Builder

Methods

mempty :: InfoMod a #

mappend :: InfoMod a -> InfoMod a -> InfoMod a #

mconcat :: [InfoMod a] -> InfoMod a #

fullDesc :: InfoMod a Source #

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

briefDesc :: InfoMod a Source #

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

header :: String -> InfoMod a Source #

Specify a header for this parser.

headerDoc :: Maybe Doc -> InfoMod a Source #

Specify a header for this parser as a Doc value.

footer :: String -> InfoMod a Source #

Specify a footer for this parser.

footerDoc :: Maybe Doc -> InfoMod a Source #

Specify a footer for this parser as a Doc value.

progDesc :: String -> InfoMod a Source #

Specify a short program description.

progDescDoc :: Maybe Doc -> InfoMod a Source #

Specify a short program description as a Doc 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.

Running parsers

The execParser family of functions are used to run parsers

execParser :: ParserInfo a -> IO a Source #

Run a program description.

Parse command line arguments. Display help text and exit if any parse error occurs.

customExecParser :: ParserPrefs -> ParserInfo a -> IO a Source #

Run a program description with custom preferences.

execParserPure Source #

Arguments

:: ParserPrefs

Global preferences for this parser

-> ParserInfo a

Description of the program to run

-> [String]

Program arguments

-> ParserResult a 

The most general way to run a program description in pure code.

Handling parser results manually

getParseResult :: ParserResult a -> Maybe a Source #

Extract the actual result from a ParserResult value.

This function returns Nothing in case of errors. Possible error messages or completion actions are simply discarded.

If you want to display error messages and invoke completion actions appropriately, use handleParseResult instead.

parserFailure :: ParserPrefs -> ParserInfo a -> ParseError -> [Context] -> ParserFailure ParserHelp Source #

Generate a ParserFailure from a ParseError in a given Context.

This function can be used, for example, to show the help text for a parser:

handleParseResult . Failure $ parserFailure pprefs pinfo ShowHelpText mempty

ParserPrefs

A ParserPrefs contains general preferences for all command-line options, and should be built with the prefs function.

prefs :: PrefsMod -> ParserPrefs Source #

Create a ParserPrefs given a modifier

data ParserPrefs Source #

Global preferences for a top-level Parser.

Constructors

ParserPrefs 

Fields

multiSuffix :: String -> PrefsMod Source #

Include a suffix to attach to the metavar when multiple values can be entered.

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.

columns :: Int -> PrefsMod Source #

Set the maximum width of the generated help text.

helpLongEquals :: PrefsMod Source #

Show equals sign, rather than space, in usage and help text for options with long names.

defaultPrefs :: ParserPrefs Source #

Default preferences.

Completions

optparse-applicative supplies a rich completion system for bash, zsh, and fish shells.

Completer functions are used for option and argument to complete their values.

Use the completer builder to use these. The action and completeWith builders are also provided for convenience, to use bashCompleter and listCompleter as a Mod.

data Completer Source #

A shell complete function.

mkCompleter :: (String -> IO [String]) -> Completer Source #

Smart constructor for a Completer

listIOCompleter :: IO [String] -> Completer Source #

Create a Completer from an IO action

listCompleter :: [String] -> Completer Source #

Create a Completer from a constant list of strings.

bashCompleter :: String -> Completer Source #

Run a compgen 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.

Types

newtype ParserFailure h Source #

Constructors

ParserFailure 

Fields

Instances
Functor ParserFailure Source # 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> ParserFailure a -> ParserFailure b #

(<$) :: a -> ParserFailure b -> ParserFailure a #

Show h => Show (ParserFailure h) Source # 
Instance details

Defined in Options.Applicative.Types

data ParserResult a Source #

Result of execParserPure.

Instances
Monad ParserResult Source # 
Instance details

Defined in Options.Applicative.Types

Functor ParserResult Source # 
Instance details

Defined in Options.Applicative.Types

Methods

fmap :: (a -> b) -> ParserResult a -> ParserResult b #

(<$) :: a -> ParserResult b -> ParserResult a #

Applicative ParserResult Source # 
Instance details

Defined in Options.Applicative.Types

Show a => Show (ParserResult a) Source # 
Instance details

Defined in Options.Applicative.Types