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

Safe HaskellNone
LanguageHaskell2010

Text.LambdaOptions

Synopsis

Documentation

data Options m a Source

A monad transformer for parsing options.

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 

class ToKeyword a Source

Minimal complete definition

toKeyword

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

Convenience Keyword to build upon. Takes either a single alias or a list of name aliases to start with. Use record syntax to set the rest.

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

runOptions :: Monad m => Options m a -> [String] -> m (Maybe OptionsError) 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:

import System.Environment
import Text.LambdaOptions

options :: Options IO ()
options = do
    addOption (kw "--help") $ do
        putStrLn "--user NAME [AGE]"
    addOption (kw "--user") $ name -> do
        putStrLn $ Name: ++ name
    addOption (kw "--user") $ name age -> do
        putStrLn $ Name: ++ name ++ " Age:" ++ show (age :: Int)

main :: IO ()
main = do
    args <- getArgs
    mError <- runOptions options args
    case mError of
        Just (ParseFailed msg _ _) -> putStrLn msg
        Nothing -> return ()

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.

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) 
Typeable (* -> *) List