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

Safe HaskellNone
LanguageHaskell2010

Text.LambdaOptions

Synopsis

Documentation

data Options m a

A monad transformer for parsing options.

Instances

MonadTrans Options 
Monad m => Monad (Options m) 
Functor m => Functor (Options m) 
(Monad m, Functor m) => Applicative (Options m) 
MonadIO m => MonadIO (Options m) 

type Keyword = String

An option keyword, such as "--help"

NB: In the future, this will become a proper data type that contains a list of aliases and help descriptions.

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

The callback to be called for a successfully parsed option.

This function (or value) 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:

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

addOption :: forall m f. 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.

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

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

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

Example:

options :: Options IO ()
options = do
    addOption "--help" $ do
        putStrLn "--user NAME [AGE]"
    addOption "--user" $ name -> do
        putStrLn $ Name: ++ name
    addOption "--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 _ _ _) -> exitFailure
        Nothing -> exitSuccess

class Parseable a where

Class describing parseable values. Much like the Read class.

Methods

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

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

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)