Safe Haskell | Safe |
---|---|
Language | Haskell98 |
- data ParseError
- data ParserInfo a = ParserInfo {
- infoParser :: Parser a
- infoFullDesc :: Bool
- infoProgDesc :: Chunk Doc
- infoHeader :: Chunk Doc
- infoFooter :: Chunk Doc
- infoFailureCode :: Int
- infoPolicy :: ArgPolicy
- data ParserPrefs = ParserPrefs {}
- data Option a = Option {
- optMain :: OptReader a
- optProps :: OptProperties
- data OptName
- data OptReader a
- data OptProperties = OptProperties {
- propVisibility :: OptVisibility
- propHelp :: Chunk Doc
- propMetaVar :: String
- propShowDefault :: Maybe String
- propDescMod :: Maybe (Doc -> Doc)
- data OptVisibility
- newtype ReadM a = ReadM {
- unReadM :: ReaderT String (Except ParseError) a
- readerAsk :: ReadM String
- readerAbort :: ParseError -> ReadM a
- readerError :: String -> ReadM a
- data CReader a = CReader {
- crCompleter :: Completer
- crReader :: ReadM a
- data Parser a
- newtype ParserM r = ParserM {
- runParserM :: forall x. (r -> Parser x) -> Parser x
- newtype Completer = Completer {
- runCompleter :: String -> IO [String]
- mkCompleter :: (String -> IO [String]) -> Completer
- newtype CompletionResult = CompletionResult {
- execCompletion :: String -> IO String
- newtype ParserFailure h = ParserFailure {
- execFailure :: String -> (h, ExitCode, Int)
- data ParserResult a
- overFailure :: (ParserHelp -> ParserHelp) -> ParserResult a -> ParserResult a
- type Args = [String]
- data ArgPolicy
- data OptHelpInfo = OptHelpInfo {}
- data OptTree a
- data ParserHelp = ParserHelp {}
- data SomeParser = SomeParser (Parser a)
- data Context = Context String (ParserInfo a)
- data IsCmdStart
- fromM :: ParserM a -> Parser a
- oneM :: Parser a -> ParserM a
- manyM :: Parser a -> ParserM [a]
- someM :: Parser a -> ParserM [a]
- optVisibility :: Option a -> OptVisibility
- optMetaVar :: Option a -> String
- optHelp :: Option a -> Chunk Doc
- optShowDefault :: Option a -> Maybe String
- optDescMod :: Option a -> Maybe (Doc -> Doc)
Documentation
data ParseError Source #
data ParserInfo a Source #
A full description for a runnable Parser
for a program.
ParserInfo | |
|
data ParserPrefs Source #
Global preferences for a top-level Parser
.
ParserPrefs | |
|
A single option of a parser.
Option | |
|
An OptReader
defines whether an option matches an command line argument.
data OptProperties Source #
Specification for an individual parser option.
OptProperties | |
|
data OptVisibility Source #
Visibility of an option in the help text.
A newtype over 'ReaderT String Except', used by option readers.
readerAbort :: ParseError -> ReadM a Source #
Abort option reader by exiting with a ParseError
.
readerError :: String -> ReadM a Source #
Abort option reader by exiting with an error message.
CReader | |
|
A Parser a
is an option parser returning a value of type a
.
ParserM | |
|
A shell complete function.
Completer | |
|
newtype CompletionResult Source #
newtype ParserFailure h Source #
ParserFailure | |
|
Functor ParserFailure Source # | |
Show h => Show (ParserFailure h) Source # | |
data ParserResult a Source #
Result of execParserPure
.
overFailure :: (ParserHelp -> ParserHelp) -> ParserResult a -> ParserResult a Source #
Policy for how to handle options within the parse
Intersperse | The default policy, options and arguments can be interspersed. A `--` option can be passed to ensure all following commands are treated as arguments. |
NoIntersperse | Options must all come before arguments, once a
single positional argument or subcommand is parsed,
all remaining arguments are treated as positionals.
A `--` option can be passed if the first positional
one needs starts with |
AllPositionals | No options are parsed at all, all arguments are treated as positionals. Is the policy used after `--` is encountered. |
ForwardOptions | Options and arguments can be interspersed, but if a given option is not found, it is treated as a positional argument. This is sometimes useful if one is passing through most options to another tool, but are supplying just a few of their own options. |
data OptHelpInfo Source #
OptHelpInfo | |
|
data ParserHelp Source #
data SomeParser Source #
SomeParser (Parser a) |
Subparser context, containing the name
of the subparser, and its parser info.
Used by parserFailure to display relevant usage information when parsing inside a subparser fails.
Context String (ParserInfo a) |
optVisibility :: Option a -> OptVisibility Source #
optMetaVar :: Option a -> String Source #