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

Safe HaskellNone
LanguageHaskell2010

Text.LambdaOptions

Synopsis

Documentation

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) 

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.

type Keyword = String Source

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

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.

Example callbacks:

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

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

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

Adds the following option into the monadic context.

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.

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