Safe Haskell | Safe-Inferred |
---|
- data ParseError
- = ErrorMsg String
- | InfoMsg String
- | ShowHelpText
- data ParserInfo a = ParserInfo {
- infoParser :: Parser a
- infoFullDesc :: Bool
- infoProgDesc :: Chunk Doc
- infoHeader :: Chunk Doc
- infoFooter :: Chunk Doc
- infoFailureCode :: Int
- infoIntersperse :: Bool
- data ParserPrefs = ParserPrefs {}
- data Option a = Option {
- optMain :: OptReader a
- optProps :: OptProperties
- data OptName
- data OptReader a
- = OptReader [OptName] (OptCReader a) ParseError
- | FlagReader [OptName] !a
- | ArgReader (ArgCReader a)
- | CmdReader [String] (String -> Maybe (ParserInfo a))
- data OptProperties = OptProperties {}
- data OptVisibility
- newtype ReadM a = ReadM {
- runReadM :: Either ParseError a
- readerAbort :: ParseError -> ReadM a
- readerError :: String -> ReadM a
- data CReader m a = CReader {
- crCompleter :: Completer
- crReader :: String -> m a
- data Parser a where
- 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 = ParserFailure {
- execFailure :: String -> (String, ExitCode)
- data ParserResult a
- type Args = [String]
- data ArgPolicy
- data OptHelpInfo = OptHelpInfo {
- hinfoMulti :: Bool
- hinfoDefault :: Bool
- data OptTree a
- 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
Documentation
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.
OptReader [OptName] (OptCReader a) ParseError | option reader |
FlagReader [OptName] !a | flag reader |
ArgReader (ArgCReader a) | argument reader |
CmdReader [String] (String -> Maybe (ParserInfo a)) | command reader |
data OptProperties Source
Specification for an individual parser option.
OptProperties | |
|
data OptVisibility Source
Visibility of an option in the help text.
A newtype over the Either
monad used by option readers.
ReadM | |
|
readerAbort :: ParseError -> ReadM aSource
Abort option reader by exiting with a ParseError
.
readerError :: String -> ReadM aSource
Abort option reader by exiting with an error message.
CReader | |
|
A Parser a
is an option parser returning a value of type a
.
ParserM | |
|
newtype CompletionResult Source
newtype ParserFailure Source
ParserFailure | |
|
data ParserResult a Source
Result of execParserPure
.
data OptHelpInfo Source
optVisibility :: Option a -> OptVisibilitySource
optMetaVar :: Option a -> StringSource
optShowDefault :: Option a -> Maybe StringSource