megaparsec-7.0.5: Monadic parser combinators

Copyright© 2015–2019 Megaparsec contributors
© 2007 Paolo Martini
© 1999–2001 Daan Leijen
LicenseFreeBSD
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Internal

Contents

Description

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

Data types

newtype Hints t Source #

Hints represent a collection of ErrorItems 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

Constructors

Hints [Set (ErrorItem t)] 
Instances
Semigroup (Hints t) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

(<>) :: Hints t -> Hints t -> Hints t #

sconcat :: NonEmpty (Hints t) -> Hints t #

stimes :: Integral b => b -> Hints t -> Hints t #

Monoid (Hints t) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

mempty :: Hints t #

mappend :: Hints t -> Hints t -> Hints t #

mconcat :: [Hints t] -> Hints t #

data Reply e s a Source #

All information available after parsing. This includes consumption of input, success (with returned value) or failure (with parse error), and parser state at the end of parsing.

See also: Consumption, Result.

Constructors

Reply (State s) Consumption (Result s e a) 

data Consumption Source #

Whether the input has been consumed or not.

See also: Result, Reply.

Constructors

Consumed

Some part of input stream was consumed

Virgin

No input was consumed

data Result s e a Source #

Whether the parser has failed or not. On success we include the resulting value, on failure we include a ParseError.

See also: Consumption, Reply.

Constructors

OK a

Parser succeeded

Error (ParseError s e)

Parser failed

newtype ParsecT e s m a Source #

ParsecT e s m a is a parser with custom data component of error e, stream type s, underlying monad m and return type a.

Constructors

ParsecT 

Fields

Instances
(Ord e, Stream s) => MonadParsec e s (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

failure :: Maybe (ErrorItem (Token s)) -> Set (ErrorItem (Token s)) -> ParsecT e s m a Source #

fancyFailure :: Set (ErrorFancy 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) Source #

updateParserState :: (State s -> State s) -> ParsecT e s m () Source #

(Stream s, MonadState st m) => MonadState st (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

get :: ParsecT e s m st #

put :: st -> ParsecT e s m () #

state :: (st -> (a, st)) -> ParsecT e s m a #

(Stream s, MonadReader r m) => MonadReader r (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

ask :: ParsecT e s m r #

local :: (r -> r) -> ParsecT e s m a -> ParsecT e s m a #

reader :: (r -> a) -> ParsecT e s m a #

(Stream s, MonadError e' m) => MonadError e' (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

throwError :: e' -> ParsecT e s m a #

catchError :: ParsecT e s m a -> (e' -> ParsecT e s m a) -> ParsecT e s m a #

MonadTrans (ParsecT e s) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

lift :: Monad m => m a -> ParsecT e s m a #

Stream s => Monad (ParsecT e s m) Source #

return returns a parser that succeeds without consuming input.

Instance details

Defined in Text.Megaparsec.Internal

Methods

(>>=) :: ParsecT e s m a -> (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 b #

return :: a -> ParsecT e s m a #

fail :: String -> ParsecT e s m a #

Functor (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

fmap :: (a -> b) -> ParsecT e s m a -> ParsecT e s m b #

(<$) :: a -> ParsecT e s m b -> ParsecT e s m a #

(Stream s, MonadFix m) => MonadFix (ParsecT e s m) Source #

Since: 6.0.0

Instance details

Defined in Text.Megaparsec.Internal

Methods

mfix :: (a -> ParsecT e s m a) -> ParsecT e s m a #

Stream s => MonadFail (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

fail :: String -> ParsecT e s m a #

Stream s => Applicative (ParsecT e s m) Source #

pure returns a parser that succeeds without consuming input.

Instance details

Defined in Text.Megaparsec.Internal

Methods

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 #

(Stream s, MonadIO m) => MonadIO (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

liftIO :: IO a -> ParsecT e s m a #

(Ord e, Stream s) => Alternative (ParsecT e s m) Source #

empty is a parser that fails without consuming input.

Instance details

Defined in Text.Megaparsec.Internal

Methods

empty :: ParsecT e s m a #

(<|>) :: ParsecT e s m a -> ParsecT e s m a -> ParsecT e s m a #

some :: ParsecT e s m a -> ParsecT e s m [a] #

many :: ParsecT e s m a -> ParsecT e s m [a] #

(Ord e, Stream s) => MonadPlus (ParsecT e s m) Source #

mzero is a parser that fails without consuming input.

Instance details

Defined in Text.Megaparsec.Internal

Methods

mzero :: ParsecT e s m a #

mplus :: ParsecT e s m a -> ParsecT e s m a -> ParsecT e s m a #

(Stream s, MonadCont m) => MonadCont (ParsecT e s m) Source # 
Instance details

Defined in Text.Megaparsec.Internal

Methods

callCC :: ((a -> ParsecT e s m b) -> ParsecT e s m a) -> ParsecT e s m a #

(a ~ Tokens s, IsString a, Eq a, Stream s, Ord e) => IsString (ParsecT e s m a) Source #

Since: 6.3.0

Instance details

Defined in Text.Megaparsec.Internal

Methods

fromString :: String -> ParsecT e s m a #

(Stream s, Semigroup a) => Semigroup (ParsecT e s m a) Source #

Since: 5.3.0

Instance details

Defined in Text.Megaparsec.Internal

Methods

(<>) :: ParsecT e s m a -> ParsecT e s m a -> ParsecT e s m a #

sconcat :: NonEmpty (ParsecT e s m a) -> ParsecT e s m a #

stimes :: Integral b => b -> ParsecT e s m a -> ParsecT e s m a #

(Stream s, Monoid a) => Monoid (ParsecT e s m a) Source #

Since: 5.3.0

Instance details

Defined in Text.Megaparsec.Internal

Methods

mempty :: ParsecT e s m a #

mappend :: ParsecT e s m a -> ParsecT e s m a -> ParsecT e s m a #

mconcat :: [ParsecT e s m a] -> ParsecT e s m a #

Helper functions

toHints Source #

Arguments

:: Stream s 
=> Int

Current offset in input stream

-> ParseError s e

Parse error to convert

-> Hints (Token s) 

Convert ParseError record to Hints.

withHints Source #

Arguments

:: Stream s 
=> Hints (Token s)

Hints to use

-> (ParseError s e -> State s -> m b)

Continuation to influence

-> ParseError s e

First argument of resulting continuation

-> State s

Second argument of resulting continuation

-> m b 

withHints hs c makes “error” continuation c use given hints hs.

Note that if resulting continuation gets ParseError that has custom data in it, hints are ignored.

accHints Source #

Arguments

:: Hints t

Hints to add

-> (a -> State s -> Hints t -> m b)

An “OK” continuation to alter

-> a -> State s -> Hints t -> m b

Altered “OK” continuation

accHints hs c results in “OK” continuation that will add given hints hs to third argument of original continuation c.

refreshLastHint :: Hints t -> Maybe (ErrorItem t) -> Hints t Source #

Replace the most recent group of hints (if any) with the given ErrorItem (or delete it if Nothing is given). This is used in the label primitive.

runParsecT Source #

Arguments

:: Monad m 
=> ParsecT e s m a

Parser to run

-> State s

Initial state

-> m (Reply e s a) 

Low-level unpacking of the ParsecT type.

withParsecT :: (Monad m, Ord e') => (e -> e') -> ParsecT e s m a -> ParsecT e' s m a Source #

Transform any custom errors thrown by the parser using the given function. Similar in function and purpose to withExceptT.

Since: 7.0.0