docopt-0.7.0.8: A command-line interface parser that will make you smile
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Console.Docopt.NoTH

Synopsis

Usage parsers

parseUsage :: String -> Either ParseError Docopt Source #

Parse docopt-formatted usage patterns.

For help with the docopt usage format, see the readme on github.

parseUsageOrExit :: String -> IO Docopt Source #

Same as parseUsage, but exitWithUsage on parse failure. E.g.

let usageStr = "Usage:\n  prog [--option]\n"
patterns <- parseUsageOrExit usageStr

Command line arguments parsers

parseArgs :: Docopt -> [String] -> Either ParseError Arguments Source #

Parse command line arguments.

parseArgsOrExit :: Docopt -> [String] -> IO Arguments Source #

Same as parseArgs, but exitWithUsage on parse failure. E.g.

args <- parseArgsOrExit patterns =<< getArgs

Re-exported from Parsec

data ParseError #

The abstract data type ParseError represents parse errors. It provides the source position (SourcePos) of the error and a list of error messages (Message). A ParseError can be returned by the function parse. ParseError is an instance of the Show and Eq classes.

Instances

Instances details
Show ParseError 
Instance details

Defined in Text.Parsec.Error

Eq ParseError 
Instance details

Defined in Text.Parsec.Error

Parsed usage string

data Docopt Source #

An abstract data type which represents Docopt usage patterns.

Instances

Instances details
Lift Docopt Source # 
Instance details

Defined in System.Console.Docopt.QQ.Instances

Methods

lift :: Quote m => Docopt -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Docopt -> Code m Docopt #

usage :: Docopt -> String Source #

Retrieve the original usage string.

exitWithUsage :: Docopt -> IO a Source #

Exit after printing usage text.

exitWithUsageMessage :: Docopt -> String -> IO a Source #

Exit after printing a custom message followed by usage text. Intended for convenience when more context can be given about what went wrong.

Argument lookup

data Option Source #

A named leaf node of the usage pattern tree

Instances

Instances details
Show Option Source # 
Instance details

Defined in System.Console.Docopt.Types

Eq Option Source # 
Instance details

Defined in System.Console.Docopt.Types

Methods

(==) :: Option -> Option -> Bool #

(/=) :: Option -> Option -> Bool #

Ord Option Source # 
Instance details

Defined in System.Console.Docopt.Types

Lift Option Source # 
Instance details

Defined in System.Console.Docopt.Types

Methods

lift :: Quote m => Option -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Option -> Code m Option #

type Arguments = Map Option ArgValue Source #

Maps each Option to all of the valued parsed from the command line (in order of last to first, if multiple values encountered)

Query functions

isPresent :: Arguments -> Option -> Bool Source #

True if an option was present at all in an invocation.

Useful with longOptions and shortOptions, and in conjunction with when.

getArg :: Arguments -> Option -> Maybe String Source #

Just the value of the argument supplied, or Nothing if one was not given.

If the option's presence is required by your Docopt usage text (e.g. a positional argument), as in

Usage:
  prog <required>

then getArg args (argument "required") is guaranteed to be a Just.

getArgOrExitWith :: Docopt -> Arguments -> Option -> IO String Source #

Same as getArg, but exitWithUsage if Nothing.

As in getArg, if your usage pattern required the option, getArgOrExitWith will not exit.

getArgWithDefault :: Arguments -> String -> Option -> String Source #

Same as getArg, but eliminate Nothing with a default argument.

getAllArgs :: Arguments -> Option -> [String] Source #

Returns all occurrences of a repeatable option, e.g. <file>....

getArgCount :: Arguments -> Option -> Int Source #

Return the number of occurrences of an option in an invocation.

Useful with repeatable flags, e.g. [ -v | -vv | -vvv].

Option constructors

command :: String -> Option Source #

For Usage: prog cmd, ask for command "cmd".

For Usage: prog - or Usage: prog [-], ask for command "-". Same for --.

argument :: String -> Option Source #

For Usage: prog <file>, ask for argument "file".

Note: A Usage: prog --output=<file> is not matched by argument "file". See longOption.

shortOption :: Char -> Option Source #

For Usage: prog -h, ask for shortOption 'h'.

For Usage: prog -o=<file>, ask for shortOption 'o'.

longOption :: String -> Option Source #

For Usage: prog --version, ask for longOption "version".

For Usage: prog --output=<file>, ask for longOption "output".

Deprecated

getAllArgsM :: Monad m => Arguments -> Option -> m [String] Source #

Deprecated: Monadic query functions will soon be removed

notPresentM :: Monad m => Arguments -> Option -> m Bool Source #

Deprecated: Monadic query functions will soon be removed

isPresentM :: Monad m => Arguments -> Option -> m Bool Source #

Deprecated: Monadic query functions will soon be removed

getFirstArg :: MonadFail m => Arguments -> Option -> m String Source #

Deprecated: Use getAllArgs instead