Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype List a = List [a]
- class Parseable a where
- type Keyword = String
- type OptionCallback m f = (Monad m, GetOpaqueParsers f, WrapCallback m f)
- data Options m a
- data OptionsError = ParseFailed String Int Int
- addOption :: forall m f. OptionCallback m f => Keyword -> f -> Options m ()
- runOptions :: Monad m => Options m a -> [String] -> m (Maybe OptionsError)
Documentation
A simple wrapper over [a]
. Used to avoid overlapping instances for Parseable [a]
and Parseable String
List [a] |
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 ()
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 |
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