lambda-options-1.0.2.0: Declarative command-line parser using type-driven pattern matching.

Safe HaskellSafe
LanguageHaskell2010

Text.LambdaOptions.Core

Description

Contains the core functionality for LambdaOptions.

Synopsis

Documentation

runOptions :: Options r () -> [String] -> Either OptionsError [r] Source #

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

Example program:

import qualified System.Environment as IO
import qualified Text.LambdaOptions as L

options :: L.Options (IO ()) ()
options = do

  L.addOption
    (L.kw ["--help", "-h"]
    `L.text` "Display this help text.")
    $ do
      putStrLn "Usage:"
      putStrLn $ L.getHelpDescription options

  L.addOption
    (L.kw "--user"
    `L.argText` "NAME"
    `L.text` "Prints name.")
    $ \name -> do
      putStrLn $ "Name:" ++ name

  L.addOption
    (L.kw "--user"
    `L.argText` "NAME AGE"
    `L.text` "Prints name and age.")
    $ \name age -> do
      putStrLn $ "Name:" ++ name ++ " Age:" ++ show (age :: Int)

main :: IO ()
main = do
  args <- IO.getArgs
  case L.runOptions options args of
    Left e -> do
      putStrLn $ L.prettyOptionsError e
      putStrLn $ L.getHelpDescription options
    Right actions -> sequence_ actions
>>> example.exe --user HaskellCurry 81 --user GraceHopper
Name:HaskellCurry Age:81
Name:GraceHopper
>>> example.exe -h
Usage:
-h, --help                  Display this help text.
    --user NAME             Prints name.
    --user NAME AGE         Prints name and age.
>>> example.exe --user Pythagoras LXXV
Unknown option at index 2: `LXXV'
Usage:
-h, --help                  Display this help text.
    --user NAME             Prints name.
    --user NAME AGE         Prints name and age.

data Options r a Source #

A monad for parsing options.

Instances
Monad (Options r) Source # 
Instance details

Defined in Text.LambdaOptions.Core

Methods

(>>=) :: Options r a -> (a -> Options r b) -> Options r b #

(>>) :: Options r a -> Options r b -> Options r b #

return :: a -> Options r a #

fail :: String -> Options r a #

Functor (Options r) Source # 
Instance details

Defined in Text.LambdaOptions.Core

Methods

fmap :: (a -> b) -> Options r a -> Options r b #

(<$) :: a -> Options r b -> Options r a #

Applicative (Options r) Source # 
Instance details

Defined in Text.LambdaOptions.Core

Methods

pure :: a -> Options r a #

(<*>) :: Options r (a -> b) -> Options r a -> Options r b #

liftA2 :: (a -> b -> c) -> Options r a -> Options r b -> Options r c #

(*>) :: Options r a -> Options r b -> Options r b #

(<*) :: Options r a -> Options r b -> Options r a #

data OptionsError Source #

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

type OptionCallback r f = (GetOpaqueParsers r f, Wrap r 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 r

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 r f = (f ~ (Parseable t*, Typeable t*) => t0 -> t1 -> ... -> tN -> r)

Example callbacks:

f0 = putStrLn "Option parsed!" :: IO ()
f1 = put :: String -> State String ()
f2 = liftIO . print :: (MonadIO m) => Int -> m ()
f3 name year ratio = lift (print (name, year, ratio)) :: (MonadTrans m) => String -> Int -> Float -> m IO ()
f4 = 7 :: Int
f5 = (:) :: Double -> [Double] -> [Double]

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

Adds the supplied option to the Options r () 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.

getHelpDescription :: Options r () -> String Source #

Produces the help description given by the input options.

getKeywords :: Options r () -> [Keyword] Source #

Produces the Keywords inserted into the input options.