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

Safe HaskellNone
LanguageHaskell2010

Text.LambdaOptions.Core

Synopsis

Documentation

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

Tries to parse the supplied options against input arguments. If successful, parsed option callbacks are returned in Right. Otherwise an OptionsError is returned in Left.

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
    case runOptions options args of
        Left (ParseFailed msg _ _) -> do
            putStrLn msg
            putStrLn $ getHelpDescription options
        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

A monad for parsing options.

Instances

data OptionsError

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

type OptionCallback m f = (Monad m, GetOpaqueParsers f, Wrap (m ()) f)

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 ()

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

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 -> String

Produces the help description given by the input options.