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

Safe HaskellSafe-Inferred

Options.Applicative.Types

Synopsis

Documentation

data ParserInfo a Source

A full description for a runnable Parser for a program.

Constructors

ParserInfo 

Fields

infoParser :: Parser a

the option parser for the program

infoFullDesc :: Bool

whether the help text should contain full documentation

infoProgDesc :: String

brief parser description

infoHeader :: String

header of the full parser description

infoFooter :: String

footer of the full parser description

infoFailureCode :: Int

exit code for a parser failure

Instances

data ParserPrefs Source

Global preferences for a top-level Parser.

Constructors

ParserPrefs 

Fields

prefMultiSuffix :: String

metavar suffix for multiple options

prefDisambiguate :: Bool

automatically disambiguate abbreviations (default: False)

prefShowHelpOnError :: Bool

always show help text on parse errors (default: False)

prefBacktrack :: Bool

backtrack to parent parser when a subcommand fails (default: True)

prefIntersperse :: Bool

allow regular options and flags to occur after arguments (default: True)

data Option a Source

A single option of a parser.

Constructors

Option 

Fields

optMain :: OptReader a

reader for this option

optProps :: OptProperties

properties of this option

Instances

data OptName Source

Constructors

OptShort !Char 
OptLong !String 

Instances

data OptReader a Source

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

Constructors

OptReader [OptName] (OptCReader a) ParseError

option reader

FlagReader [OptName] !a

flag reader

ArgReader (ArgCReader a)

argument reader

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

command reader

Instances

data OptProperties Source

Specification for an individual parser option.

Constructors

OptProperties 

Fields

propVisibility :: OptVisibility

whether this flag is shown is the brief description

propHelp :: String

help text for this option

propMetaVar :: String

metavariable for this option

propShowDefault :: Maybe String

what to show in the help text as the default

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 the Either monad used by option readers.

Constructors

ReadM 

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.

data CReader m a Source

Constructors

CReader 

Fields

crCompleter :: Completer
 
crReader :: String -> m a
 

Instances

data Parser a whereSource

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

Constructors

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

newtype ParserM r Source

Constructors

ParserM 

Fields

runParserM :: forall x. (r -> Parser x) -> Parser x
 

newtype Completer Source

Constructors

Completer 

Fields

runCompleter :: String -> IO [String]
 

Instances

data ParserFailure Source

Result after a parse error.

Constructors

ParserFailure 

Fields

errMessage :: String -> IO String

Function which takes the program name as input and returns an error message

errExitCode :: ExitCode

Exit code to use for this error

Instances

data OptTree a Source

Constructors

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

Instances

Show a => Show (OptTree a)