docopt-0.7.0.1: A command-line interface parser that will make you smile

Safe HaskellNone
LanguageHaskell98

System.Console.Docopt

Contents

Description

Example:

{-# LANGUAGE QuasiQuotes #-}
module Main where

import Control.Monad (when)
import Data.Char (toUpper)
import System.Environment (getArgs)
import System.Console.Docopt

patterns :: Docopt
patterns = [docopt|
docopt-sample version 0.1.0

Usage:
  docopt-sample cat <file>
  docopt-sample echo [--caps] <string>

Options:
  -c, --caps    Caps-lock the echoed argument
|]

getArgOrExit = getArgOrExitWith patterns

main :: IO ()
main = do
  args <- parseArgsOrExit patterns =<< getArgs

  when (args `isPresent` (command "cat")) $ do
    file <- args `getArgOrExit` (argument "file")
    putStr =<< readFile file

  when (args `isPresent` (command "echo")) $ do
    let charTransform = if args `isPresent` (longOption "caps")
                        then toUpper
                        else id
    string <- args `getArgOrExit` (argument "string")
    putStrLn $ map charTransform string

Synopsis

QuasiQuoter usage parsers

docopt :: QuasiQuoter Source

A QuasiQuoter which parses a usage string and returns a Docopt.

Example usage:

patterns :: Docopt
patterns = [docopt|
docopt-sample version 0.1.0

Usage:
  docopt-sample cat <file>
  docopt-sample echo [--caps] <string>

Options:
  -c, --caps    Caps-lock the echoed argument
|]

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

docoptFile :: QuasiQuoter Source

Same as docopt, but parses the given file instead of a literal string.

Example:

patterns :: Docopt
patterns = [docoptFile|USAGE|]

where USAGE is the name of a file which contains the usage string (relative to the directory from which ghc is invoked).

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

Instances

Parsed usage string

data Docopt Source

An abstract data type which represents Docopt usage patterns.

Instances

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

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

argument :: String -> Option Source

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

shortOption :: Char -> Option Source

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

longOption :: String -> Option Source

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

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 :: Monad m => Arguments -> Option -> m String Source

Deprecated: Use getAllArgs instead