| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Options.Applicative.Types
Synopsis
- 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 #
Constructors
| ErrorMsg String | |
| InfoMsg String | |
| ShowHelpText | |
| UnknownError | |
| MissingError IsCmdStart SomeParser | |
| ExpectsArgError String | |
| UnexpectedError String SomeParser | 
Instances
| Semigroup ParseError Source # | |
Defined in Options.Applicative.Types Methods (<>) :: ParseError -> ParseError -> ParseError # sconcat :: NonEmpty ParseError -> ParseError # stimes :: Integral b => b -> ParseError -> ParseError #  | |
| Monoid ParseError Source # | |
Defined in Options.Applicative.Types Methods mempty :: ParseError # mappend :: ParseError -> ParseError -> ParseError # mconcat :: [ParseError] -> ParseError #  | |
data ParserInfo a Source #
A full description for a runnable Parser for a program.
Constructors
| ParserInfo | |
Fields 
  | |
Instances
| Functor ParserInfo Source # | |
Defined in Options.Applicative.Types Methods fmap :: (a -> b) -> ParserInfo a -> ParserInfo b # (<$) :: a -> ParserInfo b -> ParserInfo a #  | |
data ParserPrefs Source #
Global preferences for a top-level Parser.
Constructors
| ParserPrefs | |
Fields 
  | |
Instances
| Eq ParserPrefs Source # | |
Defined in Options.Applicative.Types  | |
| Show ParserPrefs Source # | |
Defined in Options.Applicative.Types Methods showsPrec :: Int -> ParserPrefs -> ShowS # show :: ParserPrefs -> String # showList :: [ParserPrefs] -> ShowS #  | |
A single option of a parser.
Constructors
| Option | |
Fields 
  | |
An OptReader defines whether an option matches an command line argument.
data OptProperties Source #
Specification for an individual parser option.
Constructors
| OptProperties | |
Fields 
  | |
Instances
| Show OptProperties Source # | |
Defined in Options.Applicative.Types Methods showsPrec :: Int -> OptProperties -> ShowS # show :: OptProperties -> String # showList :: [OptProperties] -> ShowS #  | |
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
| Eq OptVisibility Source # | |
Defined in Options.Applicative.Types Methods (==) :: OptVisibility -> OptVisibility -> Bool # (/=) :: OptVisibility -> OptVisibility -> Bool #  | |
| Ord OptVisibility Source # | |
Defined in Options.Applicative.Types Methods compare :: OptVisibility -> OptVisibility -> Ordering # (<) :: OptVisibility -> OptVisibility -> Bool # (<=) :: OptVisibility -> OptVisibility -> Bool # (>) :: OptVisibility -> OptVisibility -> Bool # (>=) :: OptVisibility -> OptVisibility -> Bool # max :: OptVisibility -> OptVisibility -> OptVisibility # min :: OptVisibility -> OptVisibility -> OptVisibility #  | |
| Show OptVisibility Source # | |
Defined in Options.Applicative.Types Methods showsPrec :: Int -> OptVisibility -> ShowS # show :: OptVisibility -> String # showList :: [OptVisibility] -> ShowS #  | |
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.
Constructors
| CReader | |
Fields 
  | |
A Parser a is an option parser returning a value of type a.
Constructors
| NilP (Maybe a) | |
| OptP (Option a) | |
| MultP (Parser (x -> a)) (Parser x) | |
| AltP (Parser a) (Parser a) | |
| BindP (Parser x) (x -> Parser a) | 
Constructors
| ParserM | |
Fields 
  | |
A shell complete function.
Constructors
| Completer | |
Fields 
  | |
newtype CompletionResult Source #
Constructors
| CompletionResult | |
Fields 
  | |
Instances
| Show CompletionResult Source # | |
Defined in Options.Applicative.Types Methods showsPrec :: Int -> CompletionResult -> ShowS # show :: CompletionResult -> String # showList :: [CompletionResult] -> ShowS #  | |
newtype ParserFailure h Source #
Constructors
| ParserFailure | |
Fields 
  | |
Instances
| Functor ParserFailure Source # | |
Defined in Options.Applicative.Types Methods fmap :: (a -> b) -> ParserFailure a -> ParserFailure b # (<$) :: a -> ParserFailure b -> ParserFailure a #  | |
| Show h => Show (ParserFailure h) Source # | |
Defined in Options.Applicative.Types Methods showsPrec :: Int -> ParserFailure h -> ShowS # show :: ParserFailure h -> String # showList :: [ParserFailure h] -> ShowS #  | |
data ParserResult a Source #
Result of execParserPure.
Constructors
| Success a | |
| Failure (ParserFailure ParserHelp) | |
| CompletionInvoked CompletionResult | 
Instances
overFailure :: (ParserHelp -> ParserHelp) -> ParserResult a -> ParserResult a Source #
Policy for how to handle options within the parse
Constructors
| 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.  | 
Instances
| Eq ArgPolicy Source # | |
| Ord ArgPolicy Source # | |
| Show ArgPolicy Source # | |
data OptHelpInfo Source #
Constructors
| OptHelpInfo | |
Fields 
  | |
Instances
| Eq OptHelpInfo Source # | |
Defined in Options.Applicative.Types  | |
| Show OptHelpInfo Source # | |
Defined in Options.Applicative.Types Methods showsPrec :: Int -> OptHelpInfo -> ShowS # show :: OptHelpInfo -> String # showList :: [OptHelpInfo] -> ShowS #  | |
data ParserHelp Source #
Constructors
| ParserHelp | |
Instances
| Show ParserHelp Source # | |
Defined in Options.Applicative.Help.Types Methods showsPrec :: Int -> ParserHelp -> ShowS # show :: ParserHelp -> String # showList :: [ParserHelp] -> ShowS #  | |
| Semigroup ParserHelp Source # | |
Defined in Options.Applicative.Help.Types Methods (<>) :: ParserHelp -> ParserHelp -> ParserHelp # sconcat :: NonEmpty ParserHelp -> ParserHelp # stimes :: Integral b => b -> ParserHelp -> ParserHelp #  | |
| Monoid ParserHelp Source # | |
Defined in Options.Applicative.Help.Types Methods mempty :: ParserHelp # mappend :: ParserHelp -> ParserHelp -> ParserHelp # mconcat :: [ParserHelp] -> ParserHelp #  | |
data SomeParser Source #
Constructors
| 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.
Constructors
| Context String (ParserInfo a) | 
data IsCmdStart Source #
Instances
| Show IsCmdStart Source # | |
Defined in Options.Applicative.Types Methods showsPrec :: Int -> IsCmdStart -> ShowS # show :: IsCmdStart -> String # showList :: [IsCmdStart] -> ShowS #  | |
optVisibility :: Option a -> OptVisibility Source #
optMetaVar :: Option a -> String Source #