Text.Megaparsec (original) (raw)
Description
This module includes everything you need to get started writing a parser. If you are new to Megaparsec and don't know where to begin, take a look at the tutorial https://markkarpov.com/tutorial/megaparsec.html.
In addition to the Text.Megaparsec module, which exports and re-exports almost everything that you may need, we advise to importText.Megaparsec.Char if you plan to work with a stream of [Char](/package/base-4.18.1.0/docs/Data-Char.html#t:Char "Data.Char")
tokens or Text.Megaparsec.Byte if you intend to parse binary data.
It is common to start working with the library by defining a type synonym like this:
type Parser = Parsec Void Text ^ ^ | | Custom error component Input stream type
Then you can write type signatures like Parser `[Int](/package/base-4.18.1.0/docs/Data-Int.html#t:Int "Data.Int")`
—for a parser that returns an [Int](/package/base-4.18.1.0/docs/Data-Int.html#t:Int "Data.Int")
for example.
Similarly (since it's known to cause confusion), you should use[ParseErrorBundle](Text-Megaparsec-Error.html#t:ParseErrorBundle "Text.Megaparsec.Error")
type parametrized like this:
ParseErrorBundle Text Void ^ ^ | | Input stream type Custom error component (the same you used in Parser)
Megaparsec uses some type-level machinery to provide flexibility without compromising on type safety. Thus type signatures are sometimes necessary to avoid ambiguous types. If you're seeing an error message that reads like “Type variable e0
is ambiguous …”, you need to give an explicit signature to your parser to resolve the ambiguity. It's a good idea to provide type signatures for all top-level definitions.
This is the Megaparsec's state parametrized over stream type s
and custom error component type e
.
Constructors
| State | |
| -------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- | |
| FieldsstateInput :: sThe rest of input to processstateOffset :: Number of processed tokens so far_Since: 7.0.0_statePosState :: PosState sState that is used for line/column calculation_Since: 7.0.0_stateParseErrors :: [ParseError s e]Collection of “delayed” ParseErrors in reverse order. This means that the last registered error is the first element of the list.Since: 8.0.0 | |
`[ParsecT](Text-Megaparsec.html#t:ParsecT "Text.Megaparsec")` e s m a
is a parser with custom data component of errore
, stream type s
, underlying monad m
and return type a
.
Instances
Instances details
(Ord e, Stream s) => MonadParsec e s (ParsecT e s m) Source # | |
---|---|
Instance detailsDefined in Text.Megaparsec.Internal MethodsparseError :: 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 # | |
Instance detailsDefined in Text.Megaparsec.Debug Methodsdbg :: Show a => String -> ParsecT e s m a -> ParsecT e s m a Source # | |
(Stream s, MonadError e' m) => MonadError e' (ParsecT e s m) Source # | |
Instance detailsDefined in Text.Megaparsec.Internal MethodsthrowError :: 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 # | |
Instance detailsDefined in Text.Megaparsec.Internal Methodsask :: 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, MonadState st m) => MonadState st (ParsecT e s m) Source # | |
Instance detailsDefined in Text.Megaparsec.Internal Methodsget :: ParsecT e s m st #put :: st -> ParsecT e s m () #state :: (st -> (a, st)) -> ParsecT e s m a # | |
(Stream s, MonadWriter w m) => MonadWriter w (ParsecT e s m) Source # | Since: 9.5.0 |
Instance detailsDefined in Text.Megaparsec.Internal Methodswriter :: (a, w) -> ParsecT e s m a #tell :: w -> ParsecT e s m () #listen :: ParsecT e s m a -> ParsecT e s m (a, w) #pass :: ParsecT e s m (a, w -> w) -> ParsecT e s m a # | |
Stream s => MonadTrans (ParsecT e s) Source # | |
Instance detailsDefined in Text.Megaparsec.Internal Methodslift :: Monad m => m a -> ParsecT e s m a # | |
Stream s => MonadFail (ParsecT e s m) Source # | |
Instance detailsDefined in Text.Megaparsec.Internal Methodsfail :: String -> ParsecT e s m a # | |
(Stream s, MonadFix m) => MonadFix (ParsecT e s m) Source # | Since: 6.0.0 |
Instance detailsDefined in Text.Megaparsec.Internal Methodsmfix :: (a -> ParsecT e s m a) -> ParsecT e s m a # | |
(Stream s, MonadIO m) => MonadIO (ParsecT e s m) Source # | |
Instance detailsDefined in Text.Megaparsec.Internal MethodsliftIO :: 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 detailsDefined in Text.Megaparsec.Internal Methodsempty :: 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] # | |
Stream s => Applicative (ParsecT e s m) Source # | pure returns a parser that succeeds without consuming input. |
Instance detailsDefined in Text.Megaparsec.Internal Methodspure :: 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 # | |
Instance detailsDefined in Text.Megaparsec.Internal Methodsfmap :: (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 => Monad (ParsecT e s m) Source # | return returns a parser that succeeds without consuming input. |
Instance detailsDefined 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 # | |
(Ord e, Stream s) => MonadPlus (ParsecT e s m) Source # | mzero is a parser that fails without consuming input.Note: strictly speaking, this instance is unlawful. The right identity law does not hold, e.g. in general this is not true:v >> mzero = mzeroHowever the following holds:try v >> mzero = mzero |
Instance detailsDefined in Text.Megaparsec.Internal Methodsmzero :: 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 detailsDefined in Text.Megaparsec.Internal MethodscallCC :: ((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 detailsDefined in Text.Megaparsec.Internal MethodsfromString :: String -> ParsecT e s m a # | |
(Stream s, Monoid a) => Monoid (ParsecT e s m a) Source # | Since: 5.3.0 |
Instance detailsDefined in Text.Megaparsec.Internal Methodsmempty :: 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 # | |
(Stream s, Semigroup a) => Semigroup (ParsecT e s m a) Source # | Since: 5.3.0 |
Instance detailsDefined 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 # |
parseMaybe :: (Ord e, Stream s) => Parsec e s a -> s -> Maybe a Source #
`[parseMaybe](Text-Megaparsec.html#v:parseMaybe "Text.Megaparsec")` p input
runs the parser p
on input
and returns the result inside [Just](/package/base-4.18.1.0/docs/Data-Maybe.html#v:Just "Data.Maybe")
on success and [Nothing](/package/base-4.18.1.0/docs/Data-Maybe.html#v:Nothing "Data.Maybe")
on failure. This function also parses [eof](Text-Megaparsec.html#v:eof "Text.Megaparsec")
, so if the parser doesn't consume all of its input, it will fail.
The function is supposed to be useful for lightweight parsing, where error messages (and thus file names) are not important and entire input should be consumed. For example, it can be used for parsing of a single number according to a specification of its format.
The expression `[parseTest](Text-Megaparsec.html#v:parseTest "Text.Megaparsec")` p input
applies the parser p
on the input input
and prints the result to stdout. Useful for testing.
`[runParser](Text-Megaparsec.html#v:runParser "Text.Megaparsec")` p file input
runs parser p
on the input stream of tokens input
, obtained from source file
. The file
is only used in error messages and may be the empty string. Returns either a[ParseErrorBundle](Text-Megaparsec-Error.html#t:ParseErrorBundle "Text.Megaparsec.Error")
([Left](/package/base-4.18.1.0/docs/Data-Either.html#v:Left "Data.Either")
) or a value of type a
([Right](/package/base-4.18.1.0/docs/Data-Either.html#v:Right "Data.Either")
).
parseFromFile p file = runParser p file <$> readFile file
[runParser](Text-Megaparsec.html#v:runParser "Text.Megaparsec")
is the same as [parse](Text-Megaparsec.html#v:parse "Text.Megaparsec")
.
The function is similar to [runParser](Text-Megaparsec.html#v:runParser "Text.Megaparsec")
with the difference that it accepts and returns the parser state. This allows us e.g. to specify arbitrary textual position at the beginning of parsing. This is the most general way to run a parser over the [Identity](/package/base-4.18.1.0/docs/Data-Functor-Identity.html#t:Identity "Data.Functor.Identity")
monad.
Since: 4.2.0
`[runParserT](Text-Megaparsec.html#v:runParserT "Text.Megaparsec")` p file input
runs parser p
on the input list of tokensinput
, obtained from source file
. The file
is only used in error messages and may be the empty string. Returns a computation in the underlying monad m
that returns either a [ParseErrorBundle](Text-Megaparsec-Error.html#t:ParseErrorBundle "Text.Megaparsec.Error")
([Left](/package/base-4.18.1.0/docs/Data-Either.html#v:Left "Data.Either")
) or a value of type a
([Right](/package/base-4.18.1.0/docs/Data-Either.html#v:Right "Data.Either")
).
class (Stream s, MonadPlus m) => MonadParsec e s m | m -> e s where Source #
Type class describing monads that implement the full set of primitive parsers.
Note that the following primitives are “fast” and should be taken advantage of as much as possible if your aim is a fast parser: [tokens](Text-Megaparsec.html#v:tokens "Text.Megaparsec")
,[takeWhileP](Text-Megaparsec.html#v:takeWhileP "Text.Megaparsec")
, [takeWhile1P](Text-Megaparsec.html#v:takeWhile1P "Text.Megaparsec")
, and [takeP](Text-Megaparsec.html#v:takeP "Text.Megaparsec")
.
Minimal complete definition
parseError, label, try, lookAhead, notFollowedBy, withRecovery, observing, eof, token, tokens, takeWhileP, takeWhile1P, takeP, getParserState, updateParserState, mkParsec
Methods
parseError :: ParseError s e -> m a Source #
Stop parsing and report the [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
. This is the only way to control position of the error without manipulating the parser state manually.
Since: 8.0.0
label :: String -> m a -> m a Source #
The parser `[label](Text-Megaparsec.html#v:label "Text.Megaparsec")` name p
behaves as parser p
, but whenever the parser p
fails without consuming any input, it replaces names of “expected” tokens with the name name
.
`[hidden](Text-Megaparsec.html#v:hidden "Text.Megaparsec")` p
behaves just like parser p
, but it doesn't show any “expected” tokens in error message when p
fails.
Please use [hidden](Text-Megaparsec.html#v:hidden "Text.Megaparsec")
instead of the old `[label](Text-Megaparsec.html#v:label "Text.Megaparsec")` ""
idiom.
The parser `[try](Text-Megaparsec.html#v:try "Text.Megaparsec")` p
behaves like the parser p
, except that it backtracks the parser state when p
fails (either consuming input or not).
This combinator is used whenever arbitrary look ahead is needed. Since it pretends that it hasn't consumed any input when p
fails, the ([<|>](A.html#v:-60--124--62- "A")
) combinator will try its second alternative even if the first parser failed while consuming input.
For example, here is a parser that is supposed to parse the word “let” or the word “lexical”:
>>>
**parseTest (string "let" <|> string "lexical") "lexical"** **
**1:1:
unexpected "lex"
expecting "let"
What happens here? The first parser consumes “le” and fails (because it doesn't see a “t”). The second parser, however, isn't tried, since the first parser has already consumed some input! [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
fixes this behavior and allows backtracking to work:
>>>
parseTest (try (string "let") <|> string "lexical") "lexical"** **
"lexical"
[try](Text-Megaparsec.html#v:try "Text.Megaparsec")
also improves error messages in case of overlapping alternatives, because Megaparsec's hint system can be used:
>>>
**parseTest (try (string "let") <|> string "lexical") "le"** **
**1:1:
unexpected "le"
expecting "let" or "lexical"
Note that as of Megaparsec 4.4.0, [string](Text-Megaparsec-Char.html#v:string "Text.Megaparsec.Char")
backtracks automatically (see [tokens](Text-Megaparsec.html#v:tokens "Text.Megaparsec")
), so it does not need [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
. However, the examples above demonstrate the idea behind [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
so well that it was decided to keep them. You still need to use [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
when your alternatives are complex, composite parsers.
lookAhead :: m a -> m a Source #
If p
in `[lookAhead](Text-Megaparsec.html#v:lookAhead "Text.Megaparsec")` p
succeeds (either consuming input or not) the whole parser behaves like p
succeeded without consuming anything (parser state is not updated as well). If p
fails, [lookAhead](Text-Megaparsec.html#v:lookAhead "Text.Megaparsec")
has no effect, i.e. it will fail consuming input if p
fails consuming input. Combine with [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
if this is undesirable.
notFollowedBy :: m a -> m () Source #
`[notFollowedBy](Text-Megaparsec.html#v:notFollowedBy "Text.Megaparsec")` p
only succeeds when the parser p
fails. This parser never consumes any input and never modifies parser state. It can be used to implement the “longest match” rule.
Arguments
:: (ParseError s e -> m a) | How to recover from failure |
---|---|
-> m a | Original parser |
-> m a | Parser that can recover from failures |
`[withRecovery](Text-Megaparsec.html#v:withRecovery "Text.Megaparsec")` r p
allows us to continue parsing even if the parserp
fails. In this case r
is called with the actual [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
as its argument. Typical usage is to return a value signifying failure to parse this particular object and to consume some part of the input up to the point where the next object starts.
Note that if r
fails, the original error message is reported as if without [withRecovery](Text-Megaparsec.html#v:withRecovery "Text.Megaparsec")
. In no way recovering parser r
can influence error messages.
Since: 4.4.0
`[observing](Text-Megaparsec.html#v:observing "Text.Megaparsec")` p
allows us to “observe” failure of the p
parser, should it happen, without actually ending parsing but instead getting the [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
in [Left](/package/base-4.18.1.0/docs/Data-Either.html#v:Left "Data.Either")
. On success parsed value is returned in[Right](/package/base-4.18.1.0/docs/Data-Either.html#v:Right "Data.Either")
as usual. Note that this primitive just allows you to observe parse errors as they happen, it does not backtrack or change how thep
parser works in any way.
Since: 5.1.0
This parser only succeeds at the end of input.
Arguments
:: (Token s -> Maybe a) | Matching function for the token to parse |
---|---|
-> Set (ErrorItem (Token s)) | Used in the error message to mention the items that were expected |
-> m a |
The parser `[token](Text-Megaparsec.html#v:token "Text.Megaparsec")` test expected
accepts tokens for which the matching function test
returns [Just](/package/base-4.18.1.0/docs/Data-Maybe.html#v:Just "Data.Maybe")
results. If [Nothing](/package/base-4.18.1.0/docs/Data-Maybe.html#v:Nothing "Data.Maybe")
is returned the expected
set is used to report the items that were expected.
For example, the [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
parser is implemented as:
satisfy f = token testToken Set.empty where testToken x = if f x then Just x else Nothing
Note: type signature of this primitive was changed in the version_7.0.0_.
The parser `[tokens](Text-Megaparsec.html#v:tokens "Text.Megaparsec")` test chk
parses a chunk of input chk
and returns it. The supplied predicate test
is used to check equality of given and parsed chunks after a candidate chunk of correct length is fetched from the stream.
This can be used for example to write [chunk](Text-Megaparsec.html#v:chunk "Text.Megaparsec")
:
chunk = tokens (==)
Note that beginning from Megaparsec 4.4.0, this is an auto-backtracking primitive, which means that if it fails, it never consumes any input. This is done to make its consumption model match how error messages for this primitive are reported (which becomes an important thing as user gets more control with primitives like [withRecovery](Text-Megaparsec.html#v:withRecovery "Text.Megaparsec")
):
>>>
**parseTest (string "abc") "abd"** **
**1:1:
unexpected "abd"
expecting "abc"
This means, in particular, that it's no longer necessary to use [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
with [tokens](Text-Megaparsec.html#v:tokens "Text.Megaparsec")
-based parsers, such as [string](Text-Megaparsec-Char.html#v:string "Text.Megaparsec.Char")
and[string'](Text-Megaparsec-Char.html#v:string-39- "Text.Megaparsec.Char")
. This feature does not affect performance in any way.
Arguments
:: Maybe String | Name for a single token in the row |
---|---|
-> (Token s -> Bool) | Predicate to use to test tokens |
-> m (Tokens s) | A chunk of matching tokens |
Parse zero or more tokens for which the supplied predicate holds. Try to use this as much as possible because for many streams this combinator is much faster than parsers built with[many](/package/parser-combinators-1.3.0/docs/Control-Monad-Combinators.html#v:many "Control.Monad.Combinators")
and [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
.
takeWhileP (Just "foo") f = many (satisfy f <?> "foo") takeWhileP Nothing f = many (satisfy f)
The combinator never fails, although it may parse the empty chunk.
Since: 6.0.0
Arguments
:: Maybe String | Name for a single token in the row |
---|---|
-> (Token s -> Bool) | Predicate to use to test tokens |
-> m (Tokens s) | A chunk of matching tokens |
Similar to [takeWhileP](Text-Megaparsec.html#v:takeWhileP "Text.Megaparsec")
, but fails if it can't parse at least one token. Try to use this as much as possible because for many streams this combinator is much faster than parsers built with[some](/package/parser-combinators-1.3.0/docs/Control-Monad-Combinators.html#v:some "Control.Monad.Combinators")
and [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
.
takeWhile1P (Just "foo") f = some (satisfy f <?> "foo") takeWhile1P Nothing f = some (satisfy f)
Note that the combinator either succeeds or fails without consuming any input, so [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
is not necessary with it.
Since: 6.0.0
Arguments
:: Maybe String | Name for a single token in the row |
---|---|
-> Int | How many tokens to extract |
-> m (Tokens s) | A chunk of matching tokens |
Extract the specified number of tokens from the input stream and return them packed as a chunk of stream. If there is not enough tokens in the stream, a parse error will be signaled. It's guaranteed that if the parser succeeds, the requested number of tokens will be returned.
The parser is roughly equivalent to:
takeP (Just "foo") n = count n (anySingle <?> "foo") takeP Nothing n = count n anySingle
Note that if the combinator fails due to insufficient number of tokens in the input stream, it backtracks automatically. No [try](Text-Megaparsec.html#v:try "Text.Megaparsec")
is necessary with [takeP](Text-Megaparsec.html#v:takeP "Text.Megaparsec")
.
Since: 6.0.0
getParserState :: m (State s e) Source #
Return the full parser state as a [State](Text-Megaparsec.html#t:State "Text.Megaparsec")
record.
updateParserState :: (State s e -> State s e) -> m () Source #
mkParsec :: (State s e -> Reply e s a) -> m a Source #
The most general function to fail and end parsing is [parseError](Text-Megaparsec.html#v:parseError "Text.Megaparsec")
. These are built on top of it. The section also includes functions starting with the register
prefix which allow users to register “delayed”[ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
s.
Specify how to process [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
s that happen inside of this wrapper. This applies to both normal and delayed [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
s.
As a side-effect of the implementation the inner computation will start with an empty collection of delayed errors and they will be updated and “restored” on the way out of [region](Text-Megaparsec.html#v:region "Text.Megaparsec")
.
Since: 5.3.0
registerParseError :: MonadParsec e s m => ParseError s e -> m () Source #
Register a [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
for later reporting. This action does not end parsing and has no effect except for adding the given [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
to the collection of “delayed” [ParseError](Text-Megaparsec-Error.html#t:ParseError "Text.Megaparsec.Error")
s which will be taken into consideration at the end of parsing. Only if this collection is empty the parser will succeed. This is the main way to report several parse errors at once.
Since: 8.0.0
Derivatives of primitive combinators
The parser `[satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")` f
succeeds for any token for which the supplied function f
returns [True](/package/base-4.18.1.0/docs/Data-Bool.html#v:True "Data.Bool")
.
digitChar = satisfy isDigit <?> "digit"
oneOf cs = satisfy (elem
cs)
Performance note: when you need to parse a single token, it is often a good idea to use [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
with the right predicate function instead of creating a complex parser using the combinators.
See also: [anySingle](Text-Megaparsec.html#v:anySingle "Text.Megaparsec")
, [anySingleBut](Text-Megaparsec.html#v:anySingleBut "Text.Megaparsec")
, [oneOf](Text-Megaparsec.html#v:oneOf "Text.Megaparsec")
, [noneOf](Text-Megaparsec.html#v:noneOf "Text.Megaparsec")
.
Since: 7.0.0
`[oneOf](Text-Megaparsec.html#v:oneOf "Text.Megaparsec")` ts
succeeds if the current token is in the supplied collection of tokens ts
. Returns the parsed token. Note that this parser cannot automatically generate the “expected” component of error message, so usually you should label it manually with [label](Text-Megaparsec.html#v:label "Text.Megaparsec")
or ([<?>](Text-Megaparsec.html#v:-60--63--62- "Text.Megaparsec")
).
oneOf cs = satisfy (elem
cs)
See also: [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
.
digit = oneOf ['0'..'9'] <?> "digit"
Performance note: prefer [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
when you can because it's faster when you have only a couple of tokens to compare to:
quoteFast = satisfy (\x -> x == ''' || x == '"') quoteSlow = oneOf "'""
Since: 7.0.0
As the dual of [oneOf](Text-Megaparsec.html#v:oneOf "Text.Megaparsec")
, `[noneOf](Text-Megaparsec.html#v:noneOf "Text.Megaparsec")` ts
succeeds if the current token_not_ in the supplied list of tokens ts
. Returns the parsed character. Note that this parser cannot automatically generate the “expected” component of error message, so usually you should label it manually with[label](Text-Megaparsec.html#v:label "Text.Megaparsec")
or ([<?>](Text-Megaparsec.html#v:-60--63--62- "Text.Megaparsec")
).
noneOf cs = satisfy (notElem
cs)
See also: [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
.
Performance note: prefer [satisfy](Text-Megaparsec.html#v:satisfy "Text.Megaparsec")
and [anySingleBut](Text-Megaparsec.html#v:anySingleBut "Text.Megaparsec")
when you can because it's faster.
Since: 7.0.0
match :: MonadParsec e s m => m a -> m (Tokens s, a) Source #
Return both the result of a parse and a chunk of input that was consumed during parsing. This relies on the change of the [stateOffset](Text-Megaparsec.html#v:stateOffset "Text.Megaparsec")
value to evaluate how many tokens were consumed. If you mess with it manually in the argument parser, prepare for troubles.
Since: 5.3.0
takeRest :: MonadParsec e s m => m (Tokens s) Source #
Consume the rest of the input and return it as a chunk. This parser never fails, but may return the empty chunk.
takeRest = takeWhileP Nothing (const True)
Since: 6.0.0
getSourcePos :: (TraversableStream s, MonadParsec e s m) => m SourcePos Source #
Return the current source position. This function is not cheap, do not call it e.g. on matching of every token, that's a bad idea. Still you can use it to get [SourcePos](Text-Megaparsec-Pos.html#t:SourcePos "Text.Megaparsec.Pos")
to attach to things that you parse.
The function works under the assumption that we move in the input stream only forwards and never backwards, which is always true unless the user abuses the library.
Since: 7.0.0