| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Options.Applicative.Types
- data ParseError
 - 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] (CReader a) ParseError
 - | FlagReader [OptName] !a
 - | ArgReader (CReader a)
 - | CmdReader [String] (String -> Maybe (ParserInfo a))
 
 - data OptProperties = OptProperties {}
 - 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 {
- hinfoMulti :: Bool
 - hinfoDefault :: Bool
 
 - data OptTree a
 - data ParserHelp = ParserHelp {}
 - 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 ParseError Source
Constructors
| ErrorMsg String | |
| InfoMsg String | |
| ShowHelpText | |
| UnknownError | |
| MissingError (OptTree (Chunk Doc)) | 
Instances
data ParserInfo a Source
A full description for a runnable Parser for a program.
Constructors
| ParserInfo | |
Fields 
  | |
Instances
data ParserPrefs Source
Global preferences for a top-level Parser.
Constructors
| ParserPrefs | |
Fields 
  | |
Instances
A single option of a parser.
Constructors
| Option | |
Fields 
  | |
An OptReader defines whether an option matches an command line argument.
Constructors
| OptReader [OptName] (CReader a) ParseError | option reader  | 
| FlagReader [OptName] !a | flag reader  | 
| ArgReader (CReader a) | argument reader  | 
| CmdReader [String] (String -> Maybe (ParserInfo a)) | command reader  | 
data OptProperties Source
Specification for an individual parser option.
Constructors
| OptProperties | |
Fields 
  | |
Instances
data OptVisibility Source
Visibility of an option in the help text.
Constructors
| Internal | does not appear in the help text at all  | 
| Hidden | only visible in the full description  | 
| Visible | visible both in the full and brief descriptions  | 
Instances
A newtype over 'ReaderT String Except', used by option readers.
Instances
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.
Constructors
| CReader | |
Fields 
  | |
A Parser a is an option parser returning a value of type a.
Constructors
| NilP (Maybe a) | |
| OptP (Option a) | |
| forall x . MultP (Parser (x -> a)) (Parser x) | |
| AltP (Parser a) (Parser a) | |
| forall x . BindP (Parser x) (x -> Parser a) | 
Instances
Constructors
| ParserM | |
Fields 
  | |
Constructors
| Completer | |
Fields 
  | |
newtype CompletionResult Source
Constructors
| CompletionResult | |
Fields 
  | |
Instances
newtype ParserFailure h Source
Constructors
| ParserFailure | |
Fields 
  | |
Instances
| Functor ParserFailure | |
| Show h => Show (ParserFailure h) | 
data ParserResult a Source
Result of execParserPure.
Constructors
| Success a | |
| Failure (ParserFailure ParserHelp) | |
| CompletionInvoked CompletionResult | 
Instances
overFailure :: (ParserHelp -> ParserHelp) -> ParserResult a -> ParserResult a Source
data OptHelpInfo Source
Constructors
| OptHelpInfo | |
Fields 
  | |
Instances
optVisibility :: Option a -> OptVisibility Source
optMetaVar :: Option a -> String Source
optShowDefault :: Option a -> Maybe String Source