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

Safe HaskellSafe
LanguageHaskell98

Options.Applicative.Types

Synopsis

Documentation

data ParserInfo a Source #

A full description for a runnable Parser for a program.

Constructors

ParserInfo 

Fields

Instances

Functor ParserInfo Source # 

Methods

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

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

data ParserPrefs Source #

Global preferences for a top-level Parser.

Constructors

ParserPrefs 

Fields

data Option a Source #

A single option of a parser.

Constructors

Option 

Fields

Instances

Functor Option Source # 

Methods

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

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

Show (Option a) Source # 

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

data OptReader a Source #

An OptReader defines whether an option matches an command line argument.

Constructors

OptReader [OptName] (CReader a) ParseError

option reader

FlagReader [OptName] !a

flag reader

ArgReader (CReader a)

argument reader

CmdReader (Maybe String) [String] (String -> Maybe (ParserInfo a))

command reader

Instances

Functor OptReader Source # 

Methods

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

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

data OptProperties Source #

Specification for an individual parser option.

Constructors

OptProperties 

Fields

data OptVisibility Source #

Visibility of an option in the help text.

Constructors

Internal

does not appear in the help text at all

Hidden

only visible in the full description

Visible

visible both in the full and brief descriptions

newtype ReadM a Source #

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

Constructors

ReadM 

Instances

Monad ReadM Source # 

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 # 

Methods

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

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

Applicative ReadM Source # 

Methods

pure :: a -> ReadM a #

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

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

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

Alternative ReadM Source # 

Methods

empty :: ReadM a #

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

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

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

MonadPlus ReadM Source # 

Methods

mzero :: ReadM a #

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

readerAsk :: ReadM String Source #

Return the value being read.

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.

data CReader a Source #

Constructors

CReader 

Instances

Functor CReader Source # 

Methods

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

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

data Parser a Source #

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

Constructors

NilP (Maybe a) 
OptP (Option a) 
MultP (Parser (x -> a)) (Parser x) 
AltP (Parser a) (Parser a) 
BindP (Parser x) (x -> Parser a) 

Instances

Functor Parser Source # 

Methods

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

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

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

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

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

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

Alternative Parser Source # 

Methods

empty :: Parser a #

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

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

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

newtype ParserM r Source #

Constructors

ParserM 

Fields

Instances

Monad ParserM Source # 

Methods

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

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

return :: a -> ParserM a #

fail :: String -> ParserM a #

Functor ParserM Source # 

Methods

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

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

Applicative ParserM Source # 

Methods

pure :: a -> ParserM a #

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

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

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

newtype ParserFailure h Source #

Constructors

ParserFailure 

Fields

type Args = [String] Source #

data ArgPolicy Source #

Policy for how to handle options within the parse

Constructors

SkipOpts

Inputs beginning with - or `--` are treated as options or flags, and can be mixed with arguments.

AllowOpts

All input is treated as positional arguments. Used after a bare `--` input, and also with noIntersperse policy.

data OptTree a Source #

Constructors

Leaf a 
MultNode [OptTree a] 
AltNode [OptTree a] 

Instances

Show a => Show (OptTree a) Source # 

Methods

showsPrec :: Int -> OptTree a -> ShowS #

show :: OptTree a -> String #

showList :: [OptTree a] -> ShowS #

data SomeParser Source #

Constructors

SomeParser (Parser a) 

data Context Source #

Subparser context, containing the name of the subparser, and its parser info. Used by parserFailure to display relevant usage information when parsing inside a subparser fails.

Constructors

Context String (ParserInfo a)