Copyright | © 2015–present Megaparsec contributors © 2007 Paolo Martini © 1999–2001 Daan Leijen |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Internal definitions. Versioning rules do not apply here. Please do not rely on these unless you really know what you're doing.
Since: 6.5.0
Synopsis
- newtype Hints t = Hints (Set (ErrorItem t))
- data Reply e s a = Reply (State s e) Consumption (Result s e a)
- data Consumption
- data Result s e a
- = OK (Hints (Token s)) a
- | Error (ParseError s e)
- newtype ParsecT e s m a = ParsecT {}
- toHints :: Stream s => Int -> ParseError s e -> Hints (Token s)
- withHints :: Stream s => Hints (Token s) -> (ParseError s e -> State s e -> m b) -> ParseError s e -> State s e -> m b
- accHints :: Stream s => Hints (Token s) -> (a -> State s e -> Hints (Token s) -> m b) -> a -> State s e -> Hints (Token s) -> m b
- refreshHints :: Hints t -> Maybe (ErrorItem t) -> Hints t
- runParsecT :: Monad m => ParsecT e s m a -> State s e -> m (Reply e s a)
- withParsecT :: forall e e' s m a. (Monad m, Ord e') => (e -> e') -> ParsecT e s m a -> ParsecT e' s m a
Data types
Hints
represent a collection of ErrorItem
s to be included into
ParseError
(when it's a TrivialError
) as “expected” message items
when a parser fails without consuming input right after successful parser
that produced the hints.
For example, without hints you could get:
>>>
parseTest (many (char 'r') <* eof) "ra"
1:2: unexpected 'a' expecting end of input
We're getting better error messages with the help of hints:
>>>
parseTest (many (char 'r') <* eof) "ra"
1:2: unexpected 'a' expecting 'r' or end of input
All information available after parsing. This includes consumption of
input, success (with the returned value) or failure (with the parse
error), and parser state at the end of parsing. Reply
can also be used
to resume parsing.
See also: Consumption
, Result
.
Reply (State s e) Consumption (Result s e a) |
data Consumption Source #
Consumed | Some part of input stream was consumed |
NotConsumed | No input was consumed |
Whether the parser has failed or not. On success we include the
resulting value, on failure we include a ParseError
.
See also: Consumption
, Reply
.
OK (Hints (Token s)) a | Parser succeeded (includes hints) |
Error (ParseError s e) | Parser failed |
newtype ParsecT e s m a Source #
is a parser with custom data component of error
ParsecT
e s m ae
, stream type s
, underlying monad m
and return type a
.
Instances
(Ord e, Stream s) => MonadParsec e s (ParsecT e s m) Source # | |
Defined in Text.Megaparsec.Internal parseError :: ParseError s e -> ParsecT e s m a Source # label :: String -> ParsecT e s m a -> ParsecT e s m a Source # hidden :: ParsecT e s m a -> ParsecT e s m a Source # try :: ParsecT e s m a -> ParsecT e s m a Source # lookAhead :: ParsecT e s m a -> ParsecT e s m a Source # notFollowedBy :: ParsecT e s m a -> ParsecT e s m () Source # withRecovery :: (ParseError s e -> ParsecT e s m a) -> ParsecT e s m a -> ParsecT e s m a Source # observing :: ParsecT e s m a -> ParsecT e s m (Either (ParseError s e) a) Source # eof :: ParsecT e s m () Source # token :: (Token s -> Maybe a) -> Set (ErrorItem (Token s)) -> ParsecT e s m a Source # tokens :: (Tokens s -> Tokens s -> Bool) -> Tokens s -> ParsecT e s m (Tokens s) Source # takeWhileP :: Maybe String -> (Token s -> Bool) -> ParsecT e s m (Tokens s) Source # takeWhile1P :: Maybe String -> (Token s -> Bool) -> ParsecT e s m (Tokens s) Source # takeP :: Maybe String -> Int -> ParsecT e s m (Tokens s) Source # getParserState :: ParsecT e s m (State s e) Source # updateParserState :: (State s e -> State s e) -> ParsecT e s m () Source # mkParsec :: (State s e -> Reply e s a) -> ParsecT e s m a Source # | |
(VisualStream s, ShowErrorComponent e) => MonadParsecDbg e s (ParsecT e s m) Source # | |
(Stream s, MonadError e' m) => MonadError e' (ParsecT e s m) Source # | |
Defined in Text.Megaparsec.Internal throwError :: e' -> ParsecT e s m a # catchError :: ParsecT e s m a -> (e' -> ParsecT e s m a) -> ParsecT e s m a # | |
(Stream s, MonadReader r m) => MonadReader r (ParsecT e s m) Source # | |
(Stream s, MonadState st m) => MonadState st (ParsecT e s m) Source # | |
Stream s => MonadTrans (ParsecT e s) Source # | |
Defined in Text.Megaparsec.Internal | |
Stream s => MonadFail (ParsecT e s m) Source # | |
Defined in Text.Megaparsec.Internal | |
(Stream s, MonadFix m) => MonadFix (ParsecT e s m) Source # | Since: 6.0.0 |
Defined in Text.Megaparsec.Internal | |
(Stream s, MonadIO m) => MonadIO (ParsecT e s m) Source # | |
Defined in Text.Megaparsec.Internal | |
(Ord e, Stream s) => Alternative (ParsecT e s m) Source # |
|
Stream s => Applicative (ParsecT e s m) Source # |
|
Defined in Text.Megaparsec.Internal pure :: a -> ParsecT e s m a # (<*>) :: ParsecT e s m (a -> b) -> ParsecT e s m a -> ParsecT e s m b # liftA2 :: (a -> b -> c) -> ParsecT e s m a -> ParsecT e s m b -> ParsecT e s m c # (*>) :: ParsecT e s m a -> ParsecT e s m b -> ParsecT e s m b # (<*) :: ParsecT e s m a -> ParsecT e s m b -> ParsecT e s m a # | |
Functor (ParsecT e s m) Source # | |
Stream s => Monad (ParsecT e s m) Source # |
|
(Ord e, Stream s) => MonadPlus (ParsecT e s m) Source # |
Note: strictly speaking, this instance is unlawful. The right identity law does not hold, e.g. in general this is not true: v >> mzero = mero However the following holds: try v >> mzero = mzero |
(Stream s, MonadCont m) => MonadCont (ParsecT e s m) Source # | |
(a ~ Tokens s, IsString a, Eq a, Stream s, Ord e) => IsString (ParsecT e s m a) Source # | Since: 6.3.0 |
Defined in Text.Megaparsec.Internal fromString :: String -> ParsecT e s m a # | |
(Stream s, Monoid a) => Monoid (ParsecT e s m a) Source # | Since: 5.3.0 |
(Stream s, Semigroup a) => Semigroup (ParsecT e s m a) Source # | Since: 5.3.0 |
Helper functions
:: Stream s | |
=> Int | Current offset in input stream |
-> ParseError s e | Parse error to convert |
-> Hints (Token s) |
Convert a ParseError
record into Hints
.
:: Stream s | |
=> Hints (Token s) | Hints to use |
-> (ParseError s e -> State s e -> m b) | Continuation to influence |
-> ParseError s e | First argument of resulting continuation |
-> State s e | Second argument of resulting continuation |
-> m b |
makes “error” continuation withHints
hs cc
use given hints hs
.
Note that if resulting continuation gets ParseError
that has custom
data in it, hints are ignored.
:: Stream s | |
=> Hints (Token s) |
|
-> (a -> State s e -> Hints (Token s) -> m b) | An “OK” continuation to alter |
-> a -> State s e -> Hints (Token s) -> m b | Altered “OK” continuation |
results in “OK” continuation that will add given
hints accHints
hs chs
to third argument of original continuation c
.
Low-level unpacking of the ParsecT
type.
:: forall e e' s m a. (Monad m, Ord e') | |
=> (e -> e') | |
-> ParsecT e s m a | Inner parser |
-> ParsecT e' s m a | Outer parser |
Transform any custom errors thrown by the parser using the given
function. Similar in function and purpose to withExceptT
.
Note that the inner parser will start with an empty collection of
“delayed” ParseError
s. Any delayed ParseError
s produced in the inner
parser will be lifted by applying the provided function and added to the
collection of delayed parse errors of the outer parser.
Since: 7.0.0