| Copyright | (c) Fumiaki Kinoshita 2017 |
|---|---|
| License | BSD3 |
| Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Extensible.GetOpt
Description
A wrapper for GetOpt
- data OptionDescr h a = OptionDescr (s -> h a) !s (OptDescr (s -> s))
- type OptDescr' = OptionDescr Identity
- optNoArg :: [Char] -> [String] -> String -> OptDescr' Int
- optReqArg :: [Char] -> [String] -> String -> String -> OptDescr' [String]
- optionNoArg :: (Int -> h a) -> [Char] -> [String] -> String -> OptionDescr h a
- optionReqArg :: ([String] -> h a) -> [Char] -> [String] -> String -> String -> OptionDescr h a
- getOptRecord :: RecordOf (OptionDescr h) xs -> [String] -> (RecordOf h xs, [String], [String], String -> String)
- withGetOpt :: MonadIO m => String -> RecordOf (OptionDescr h) xs -> (RecordOf h xs -> [String] -> m a) -> m a
Documentation
data OptionDescr h a Source #
OptDescr with a default
Constructors
| OptionDescr (s -> h a) !s (OptDescr (s -> s)) |
Instances
| Wrapper k (OptionDescr k h) Source # | |
| Functor h => Functor (OptionDescr * h) Source # | |
| type Repr k (OptionDescr k h) a Source # | |
type OptDescr' = OptionDescr Identity Source #
Option without an argument; the result is the total count of this option.
Arguments
| :: [Char] | short option |
| -> [String] | long option |
| -> String | placeholder |
| -> String | explanation |
| -> OptDescr' [String] |
Option with an argument
optionNoArg :: (Int -> h a) -> [Char] -> [String] -> String -> OptionDescr h a Source #
optionReqArg :: ([String] -> h a) -> [Char] -> [String] -> String -> String -> OptionDescr h a Source #
withGetOpt :: MonadIO m => String -> RecordOf (OptionDescr h) xs -> (RecordOf h xs -> [String] -> m a) -> m a Source #
When there's an error, print it along with the usage info to stderr
and terminate with exitFailure.