Copyright | (c) Fumiaki Kinoshita 2018 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
A wrapper for GetOpt
.
Synopsis
- data OptionDescr h a = OptionDescr (s -> h a) !s (OptDescr (s -> s))
- type OptDescr' = OptionDescr Identity
- 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
- optFlag :: [Char] -> [String] -> String -> OptDescr' Bool
- optLastArg :: [Char] -> [String] -> String -> String -> OptDescr' (Maybe String)
- 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
- optionOptArg :: ([Maybe String] -> h a) -> [Char] -> [String] -> String -> String -> OptionDescr h a
Documentation
data OptionDescr h a Source #
OptDescr
with a default
OptionDescr (s -> h a) !s (OptDescr (s -> s)) |
Instances
Wrapper (OptionDescr h :: k -> Type) Source # | |
Defined in Data.Extensible.GetOpt type Repr (OptionDescr h) v :: Type Source # _Wrapper :: (Functor f, Profunctor p) => Optic' p f (OptionDescr h v) (Repr (OptionDescr h) v) Source # wrap :: Repr (OptionDescr h) v -> OptionDescr h v Source # unwrap :: OptionDescr h v -> Repr (OptionDescr h) v Source # | |
Functor h => Functor (OptionDescr h) Source # | |
Defined in Data.Extensible.GetOpt fmap :: (a -> b) -> OptionDescr h a -> OptionDescr h b # (<$) :: a -> OptionDescr h b -> OptionDescr h a # | |
type Repr (OptionDescr h :: k -> Type) (a :: k) Source # | |
Defined in Data.Extensible.GetOpt |
type OptDescr' = OptionDescr Identity Source #
Simple option descriptor
:: RecordOf (OptionDescr h) xs | a record of option descriptors |
-> [String] | arguments |
-> (RecordOf h xs, [String], [String], String -> String) | (result, remaining non-options, errors, usageInfo) |
Parse option arguments.
:: MonadIO m | |
=> String | Non-option usage |
-> RecordOf (OptionDescr h) xs | option desciptors |
-> (RecordOf h xs -> [String] -> m a) | the result and non-option arguments |
-> m a |
An all-in-one utility function.
When there's an error, print it along with the usage info to stderr
and terminate with exitFailure
.
Basic descriptors
True when specified
:: [Char] | short option |
-> [String] | long option |
-> String | placeholder |
-> String | explanation |
-> OptDescr' (Maybe String) |
Takes the last argument when more than one is specified.
More generic descriptors
Option without an argument; the result is the total count of this option.
:: [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 #
Wrapper-generic version of optNoArg
optionReqArg :: ([String] -> h a) -> [Char] -> [String] -> String -> String -> OptionDescr h a Source #
Wrapper-generic version of optReqArg
optionOptArg :: ([Maybe String] -> h a) -> [Char] -> [String] -> String -> String -> OptionDescr h a Source #
Construct an option with an optional argument