lambda-options-0.4.0.0: A modern command-line parser for Haskell.

Safe HaskellNone
LanguageHaskell2010

Text.LambdaOptions

Synopsis

Documentation

runOptions :: Monad m => Options m () -> [String] -> m (Either OptionsError (m ())) Source

Tries to parse the supplied options against input arguments. If successful, parsed option callbacks are executed. Otherwise none of the callbacks are executed.

Example program:

import System.Environment
import Text.LambdaOptions

options :: Options IO ()
options = do
    addOption (kw ["--help", "-h"] `text` "Display this help text.") $ \(HelpDescription desc) -> do
        putStrLn "Usage:"
        putStrLn desc
    addOption (kw "--user" `argText` "NAME" `text` "Prints name.") $ \name -> do
        putStrLn $ "Name:" ++ name
    addOption (kw "--user" `argText` "NAME AGE" `text` "Prints name and age.") $ \name age -> do
        putStrLn $ "Name:" ++ name ++ " Age:" ++ show (age :: Int)

main :: IO ()
main = do
    args <- getArgs
    result <- runOptions options args
    case result of
        Left (ParseFailed msg _ _) -> do
            putStrLn msg
            desc <- getHelpDescription options
            putStrLn desc
        Right action -> action
>>> example.exe --user John 20 --user Jane
Name:John Age:20
Name:Jane
>>> example.exe -h
Usage:
-h, --help                  Display this help text.
    --user NAME             Prints name.
    --user NAME AGE         Prints name and age.
>>> example.exe --user BadLuckBrian thirteen
Unknown option at index 2: `thirteen'
Usage:
-h, --help                  Display this help text.
    --user NAME             Prints name.
    --user NAME AGE         Prints name and age.

data Options m a Source

A monad transformer for parsing options.

data OptionsError Source

Contains information about what went wrong during an unsuccessful options parse.

Constructors

ParseFailed String Int Int

Contains (error-message) (begin-args-index) (end-args-index)

Instances

data Keyword Source

An option keyword, such as "--help"

Constructors

Keyword 

Fields

kwNames :: [String]

All the aliases for this keyword.

kwArgText :: String

Text to describe the arguments to the option given by this keyword.

kwText :: String

Text to describe the function of the option given by this keyword.

type OptionCallback m f = (Monad m, GetOpaqueParsers f, WrapCallback m f) Source

Describes the callback f to be called for a successfully parsed option.

The function (or value) f can have any arity and ultimately returns a value with type Monad m => m ()

Each of the callback's arguments must have a type t which implements Parseable and Typeable.

Think of this as the following constraint synonym:

type OptionCallback m f = (Monad m, f ~ (Parseable t*, Typeable t*) => t0 -> t1 -> ... -> tN -> m ())

Example callbacks:

f0 = putStrLn "Option parsed!" :: IO ()
f1 = put :: String -> State String ()
f2 n = liftIO (print n) :: (MonadIO m) => Int -> m ()
f3 name year ratio = lift (print (name, year, ratio)) :: (MonadTrans m) => String -> Int -> Float -> m IO ()

addOption :: OptionCallback m f => Keyword -> f -> Options m () Source

Adds the supplied option to the Options m () context.

If the keyword is matched and the types of the callback's parameters can successfully be parsed, the callback is called with the parsed arguments.

newtype HelpDescription Source

When used as a callback argument, this contains the help description given by the added options.

Example:

addOption (kw ["--help", "-h"]) $ \(HelpDescription desc) -> do
    putStrLn desc

Constructors

HelpDescription String 

Instances

Parseable HelpDescription

Consumes nothing. Returns the options' help description. Never fails.

Typeable * HelpDescription 

getHelpDescription :: Monad m => Options m a -> m String Source

Produces the help description given by the input options.

class ToKeyword a where Source

Convenience Keyword creation class.

Methods

toKeyword :: a -> Keyword Source

Instances

ToKeyword String

Used to create a Keyword with a single alias.

ToKeyword Keyword

Identiy mapping.

ToKeyword [String]

Used to create a Keyword with many (or no) aliases

kw :: ToKeyword a => a -> Keyword Source

Shorthand for toKeyword.

text :: Keyword -> String -> Keyword Source

Sets the kwText field in the keyword. Intended to be used infix.

kw "--quiet" `text` "Suppress message display."

argText :: Keyword -> String -> Keyword Source

Sets the kwArgText field in the keyword. Intended to be used infix:

kw "--directory" `argText` "DIR" `text` "Write files to DIR."

class Parseable a where Source

Class describing parseable values. Much like the Read class.

Methods

parse :: [String] -> (Maybe a, Int) Source

Given a sequence of strings, returns Nothing and the number of strings consumed if the parse failed. Otherwise, return Just the parsed value and the number of strings consumed. Element-wise, an entire string must be parsed in the sequence to be considered a successful parse.

Instances

Parseable Float

Parses a Float using its Read instance.

Parseable Int

Parses an Int using its Read instance.

Parseable String

Identity parser.

Parseable HelpDescription

Consumes nothing. Returns the options' help description. Never fails.

Parseable a => Parseable (Maybe a)

Greedily parses a single argument or no argument. Never fails.

Parseable a => Parseable (List a)

Greedily parses arguments item-wise. Never fails.

newtype List a Source

A simple wrapper over [a]. Used to avoid overlapping instances for Parseable [a] and Parseable String

Constructors

List [a] 

Instances

Eq a => Eq (List a) 
Ord a => Ord (List a) 
Read a => Read (List a) 
Show a => Show (List a) 
Parseable a => Parseable (List a)

Greedily parses arguments item-wise. Never fails.

Typeable (* -> *) List