Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Options m a
- data Keyword = Keyword {}
- type OptionCallback m f = (Monad m, GetOpaqueParsers f, WrapCallback m f)
- addOption :: OptionCallback m f => Keyword -> f -> Options m ()
- newtype HelpDescription = HelpDescription String
- class ToKeyword a
- kw :: ToKeyword a => a -> Keyword
- data OptionsError = ParseFailed String Int Int
- runOptions :: Monad m => Options m a -> [String] -> m (Maybe OptionsError)
- class Parseable a where
- newtype List a = List [a]
Documentation
A monad transformer for parsing options.
An option keyword, such as "--help"
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
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.
ParseFailed String Int Int | Contains |
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 ()