| Copyright | (c) Dan Shved 2022 |
|---|---|
| License | BSD-3 |
| Maintainer | danshved@gmail.com |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Options.OptStream.Raw
Description
This module contains RawParser and RawFollower, which are the actual types
used by Parser and Follower internally.
RawParser is the core type of the optstream library. It provides a
twice-applicative and once-monadic interface for building command line parsers.
It takes care of the parsing itself, but doesn't deal with higher-level
features such as help generation. Parser is a (rather thin)
wrapper built on top of RawParser in order to provide basic handling of
--help. You can build your own interface on top of RawParser to provide
more sophisticated features.
Synopsis
- module Options.OptStream.Classes
- data RawParser a
- runParser :: RawParser a -> [String] -> Either ParserError a
- runParserIO :: IOOps m => RawParser a -> [String] -> m a
- parseArgs :: IOOps m => RawParser a -> m a
- type OptionForm = String
- isLegalOptionForm :: OptionForm -> Bool
- flag' :: [OptionForm] -> RawParser ()
- flagSep' :: [OptionForm] -> RawParser ()
- param' :: [OptionForm] -> String -> RawParser String
- paramRead' :: Read a => [OptionForm] -> String -> RawParser a
- paramChar' :: [OptionForm] -> String -> RawParser Char
- freeArg' :: String -> RawParser String
- freeArgRead' :: Read a => String -> RawParser a
- freeArgChar' :: String -> RawParser Char
- anyArg' :: String -> RawParser String
- anyArgRead' :: Read a => String -> RawParser a
- anyArgChar' :: String -> RawParser Char
- multiParam' :: [OptionForm] -> RawFollower a -> RawParser a
- data RawFollower a
- next :: String -> RawFollower String
- nextRead :: Read a => String -> RawFollower a
- nextChar :: String -> RawFollower Char
- nextMetavar :: RawFollower a -> Maybe String
- withVersion' :: String -> RawParser a -> RawParser (Either String a)
- withVersionIO' :: IOOps m => String -> RawParser (m a) -> RawParser (m a)
- beforeDashes :: RawParser a -> RawParser a
- block :: String -> (String -> Maybe (RawFollower a)) -> RawParser a
- short :: String -> (Char -> Maybe a) -> RawParser a
- match :: String -> RawParser String
- matchAndFollow :: String -> RawFollower a -> RawParser a
- matchShort :: Char -> RawParser Char
- quiet :: RawParser a -> RawParser a
- eject :: RawParser a -> RawParser b -> RawParser (Either b a)
- data ParserError
- formatParserError :: ParserError -> String
Documentation
module Options.OptStream.Classes
Parsers
A RawParser processes part of a stream of command line arguments and
produces an output value of type a. RawParser is the type that
Parser uses internally. The differences between these
two types are:
Instances
| Monad RawParser Source # | |
| Functor RawParser Source # | |
| MonadFail RawParser Source # | |
Defined in Options.OptStream.Raw | |
| Applicative RawParser Source # | |
| Alternative RawParser Source # | |
| SelectiveParser RawParser Source # | |
Defined in Options.OptStream.Raw Methods (<#>) :: RawParser (a -> b) -> RawParser a -> RawParser b Source # (<-#>) :: RawParser (a -> b) -> RawParser a -> RawParser b Source # (<#->) :: RawParser (a -> b) -> RawParser a -> RawParser b Source # (<-|>) :: RawParser a -> RawParser a -> RawParser a Source # (<|->) :: RawParser a -> RawParser a -> RawParser a Source # many :: RawParser a -> RawParser [a] Source # some :: RawParser a -> RawParser [a] Source # optional :: RawParser a -> RawParser (Maybe a) Source # between :: Int -> Int -> RawParser a -> RawParser [a] Source # | |
| ApplicativeFail RawParser Source # | |
| FunctorFail RawParser Source # | |
Defined in Options.OptStream.Raw | |
runParserIO :: IOOps m => RawParser a -> [String] -> m a Source #
See runParserIO.
Atomic parsers
type OptionForm = String Source #
High-level option parsers all accept a list of option forms. An option
form is simply a String.
There are two kinds of legal option forms: short forms, e.g. "-f", and
long forms, e.g. "--foo". Any function that accepts an OptionForm will
fail with an error if the option form is illegal. See isLegalOptionForm.
isLegalOptionForm :: OptionForm -> Bool Source #
Checks whether the given string is a legal option form. A legal short form
is -C, where C is any character other than -. A legal long form is
--STR, where STR is any non-empty string.
This function is here just in case. Normally the programmer will provide option forms as string literals, so they will probably be legal.
Example:
>>>isLegalOptionForm "-f"True>>>isLegalOptionForm "--foo"True>>>isLegalOptionForm "bar"False>>>isLegalOptionForm ""False>>>isLegalOptionForm "-"False>>>isLegalOptionForm "--"False>>>isLegalOptionForm "---"True
Flags
Arguments
| :: [OptionForm] | Flag forms, e.g. |
| -> RawParser () | A parser that succeeds upon consuming the flag. |
See flag'.
Arguments
| :: [OptionForm] | Flag forms, e.g. |
| -> RawParser () | A parser that succeeds upon consuming the flag. |
See flagSep'.
Parameters
Arguments
| :: [OptionForm] | All parameter forms, e.g. |
| -> String | Metavariable for error messages. |
| -> RawParser String | A parser that returns the parameter value. |
See param'.
Arguments
| :: Read a | |
| => [OptionForm] | All parameter forms, e.g. |
| -> String | Metavariable for error messages. |
| -> RawParser a | A parser that returns the parsed parameter value. |
See paramRead'.
Arguments
| :: [OptionForm] | All parameter forms, e.g. |
| -> String | Metavariable for error messages. |
| -> RawParser Char | A parser that returns the parsed parameter value. |
See paramChar'.
Free arguments
Arguments
| :: String | Metavariable for error messages (arbitrary string). |
| -> RawParser String | Parser that consumes and returns the first free argument it sees. |
See freeArg'.
Arguments
| :: Read a | |
| => String | Metavariable for error messages (arbitrary string). |
| -> RawParser a | Parser that consumes the first free argument it sees and
parses it down to type |
See freeArgRead'.
Arguments
| :: String | Metavariable for error messages. |
| -> RawParser Char | Parser that consumes the first free argument it sees and
parses it down to a |
See freeArgChar'.
Arguments
| :: String | Metavariable for error messages. |
| -> RawParser String | Parser that consumes and returns the first argument it sees. |
See anyArg'.
Arguments
| :: Read a | |
| => String | Metavariable for error messages. |
| -> RawParser a | Parser that consumes the first argument it sees and parses
it down to type |
See anyArgRead'.
Arguments
| :: String | Metavariable for error messages. |
| -> RawParser Char | Parser that consumes the first argument it sees and parses
it down to a |
See anyArgChar'.
Multi-parameters
Arguments
| :: [OptionForm] | All multi-parameter forms, e.g. |
| -> RawFollower a | How to process the following arguments. |
| -> RawParser a | A parser that consumes the option form and the following arguments. |
See multiParam'.
data RawFollower a Source #
A RawFollower consumes zero or more strings from a stream and then
produces a result of type a. This is the type that
Follower uses internally. The differences between
RawFollower and Follower are:
- A
Followerhas a help string attached to it, aRawFollowerdoesn't. RawFolloweris aMonad, whereasFolloweris only anApplicative.
Instances
Arguments
| :: Read a | |
| => String | Metavariable for error messages. |
| -> RawFollower a |
See nextRead.
Arguments
| :: String | Metavariable for error messages. |
| -> RawFollower Char |
See nextChar.
nextMetavar :: RawFollower a -> Maybe String Source #
See nextMetavar.
Utilities
Arguments
| :: String | Version info to be shown to the user. |
| -> RawParser a | An existing |
| -> RawParser (Either String a) | A wrapper |
See withVersion'.
Arguments
| :: IOOps m | |
| => String | Version information to show to the user. |
| -> RawParser (m a) | An existing |
| -> RawParser (m a) | A wrapper that handles |
See withVersionIO'.
See beforeDashes.
Low-level parsers
Arguments
| :: String | Block name for "missing argument" error messages. Arbitrary string. |
| -> (String -> Maybe (RawFollower a)) | A function that decides whether to skip or consume a command line argument. |
| -> RawParser a | A |
See block.
Arguments
| :: String | Short flag name for "missing argument" error messages. Arbitrary string. |
| -> (Char -> Maybe a) | A function that decides whether to skip or consume a short flag. |
| -> RawParser a | A |
See short.
Arguments
| :: String | The exact command line argument to match. |
| -> RawParser String | A parser that finishes after matching and consuming the argument. |
See match.
Arguments
| :: String | Command line argument that starts a block. |
| -> RawFollower a | A follower that consumes the rest of the block. |
| -> RawParser a |
See matchAndFollow.
Arguments
| :: Char | A short flag, e.g. |
| -> RawParser Char |
See matchShort.
Arguments
| :: RawParser a | An existing parser. |
| -> RawParser b | A parser that may trigger an ejection. |
| -> RawParser (Either b a) |
See eject.
Errors
data ParserError Source #
An error returned by runParser. There are three kinds of errors:
- An unexpected command line argument. This means that the top-level
parser skipped (didn't consume) an input token (a command-line argument or
a
shortflag inside an argument). - A missing argument. This means that either the top-level parser refused
to consume EOF, or that EOF was reached when a
Followerwas holding the stream and wanted more input. The error message will generally contain a list of possible items missing (flags or metavariables). - A custom error thrown with e.g.
failAorfmapOrFail.
Instances
| Eq ParserError Source # | |
Defined in Options.OptStream.Raw | |
| Ord ParserError Source # | |
Defined in Options.OptStream.Raw Methods compare :: ParserError -> ParserError -> Ordering # (<) :: ParserError -> ParserError -> Bool # (<=) :: ParserError -> ParserError -> Bool # (>) :: ParserError -> ParserError -> Bool # (>=) :: ParserError -> ParserError -> Bool # max :: ParserError -> ParserError -> ParserError # min :: ParserError -> ParserError -> ParserError # | |
| Show ParserError Source # | |
Defined in Options.OptStream.Raw Methods showsPrec :: Int -> ParserError -> ShowS # show :: ParserError -> String # showList :: [ParserError] -> ShowS # | |
formatParserError :: ParserError -> String Source #
Formats a ParserError to a human-readable string.