Safe Haskell | None |
---|---|
Language | Haskell2010 |
- runOptions :: Monad m => Options m a () -> [String] -> Either OptionsError [m a]
- data Options m a b
- data OptionsError = ParseFailed {}
- type OptionCallback m a f = (Monad m, GetOpaqueParsers a f, Wrap (m a) f)
- addOption :: OptionCallback m a f => Keyword -> f -> Options m a ()
- getHelpDescription :: Monad m => Options m a () -> String
- getKeywords :: Monad m => Options m a () -> [Keyword]
Documentation
runOptions :: Monad m => Options m a () -> [String] -> Either OptionsError [m a] Source #
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.") $ do putStrLn "Usage:" putStrLn $ getHelpDescription options 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 (e @ ParseFailed{}) -> do putStrLn $ parseFailedMessage e putStrLn $ 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.
A monad for parsing options.
data OptionsError Source #
Contains information about what went wrong during an unsuccessful options parse.
type OptionCallback m a f = (Monad m, GetOpaqueParsers a f, Wrap (m a) 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 a
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 a f = (Monad m, f ~ (Parseable t*, Typeable t*) => t0 -> t1 -> ... -> tN -> m a)
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 () f4 = return 7 :: Identity Int
addOption :: OptionCallback m a f => Keyword -> f -> Options m a () Source #
Adds the supplied option to the Options m a ()
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.