Safe Haskell | None |
---|---|
Language | Haskell2010 |
- runOptions :: Monad m => Options m () -> [String] -> m (Either OptionsError (m ()))
- data Options m a
- data OptionsError = ParseFailed String Int Int
- 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
- getHelpDescription :: Monad m => Options m a -> m String
- class ToKeyword a where
- kw :: ToKeyword a => a -> Keyword
- text :: Keyword -> String -> Keyword
- argText :: Keyword -> String -> Keyword
- class Parseable a where
- newtype List a = List [a]
Documentation
runOptions :: Monad m => Options m () -> [String] -> m (Either OptionsError (m ())) 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 program:
import System.Environment import Text.LambdaOptions options :: Options IO () options = do addOption (kw ["--help", "-h"] `text` "Display this help text.") $ \(HelpDescription desc) -> do putStrLn "Usage:" putStrLn desc 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 result <- runOptions options args case result of Left (ParseFailed msg _ _) -> do putStrLn msg desc <- getHelpDescription options putStrLn desc Right action -> action
>>>
example.exe --user John 20 --user Jane
Name:John Age:20 Name:Jane>>>
example.exe -h
Usage: -h, --help Display this help text. --user NAME Prints name. --user NAME AGE Prints name and age.>>>
example.exe --user BadLuckBrian thirteen
Unknown option at index 2: `thirteen' Usage: -h, --help Display this help text. --user NAME Prints name. --user NAME AGE Prints name and age.
A monad transformer for parsing options.
data OptionsError Source
Contains information about what went wrong during an unsuccessful options parse.
ParseFailed String Int Int | Contains |
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
Parseable HelpDescription | Consumes nothing. Returns the options' help description. Never fails. |
Typeable * HelpDescription |
getHelpDescription :: Monad m => Options m a -> m String Source
Produces the help description given by the input options.
text :: Keyword -> String -> Keyword Source
Sets the kwText
field in the keyword. Intended to be used infix.
kw "--quiet" `text` "Suppress message display."
argText :: Keyword -> String -> Keyword Source
Sets the kwArgText
field in the keyword. Intended to be used infix:
kw "--directory" `argText` "DIR" `text` "Write files to DIR."
class Parseable a where Source
Class describing parseable values. Much like the Read
class.
Parseable Float | |
Parseable Int | |
Parseable String | Identity parser. |
Parseable HelpDescription | Consumes nothing. Returns the options' help description. Never fails. |
Parseable a => Parseable (Maybe a) | Greedily parses a single argument or no argument. Never fails. |
Parseable a => Parseable (List a) | Greedily parses arguments item-wise. Never fails. |
A simple wrapper over [a]
. Used to avoid overlapping instances for Parseable [a]
and Parseable String
List [a] |