Text.Megaparsec.Byte.Lexer (original) (raw)
Contents
Description
Stripped-down version of Text.Megaparsec.Char.Lexer for streams of bytes.
This module is intended to be imported qualified:
import qualified Text.Megaparsec.Byte.Lexer as L
Synopsis
- space :: MonadParsec e s m => m () -> m () -> m () -> m ()
- lexeme :: MonadParsec e s m => m () -> m a -> m a
- symbol :: MonadParsec e s m => m () -> Tokens s -> m (Tokens s)
- symbol' :: (MonadParsec e s m, FoldCase (Tokens s)) => m () -> Tokens s -> m (Tokens s)
- skipLineComment :: (MonadParsec e s m, Token s ~ Word8) => Tokens s -> m ()
- skipBlockComment :: MonadParsec e s m => Tokens s -> Tokens s -> m ()
- skipBlockCommentNested :: (MonadParsec e s m, Token s ~ Word8) => Tokens s -> Tokens s -> m ()
- decimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a
- binary :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a
- octal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a
- hexadecimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a
- scientific :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m Scientific
- float :: (MonadParsec e s m, Token s ~ Word8, RealFloat a) => m a
- signed :: (MonadParsec e s m, Token s ~ Word8, Num a) => m () -> m a -> m a
Arguments
:: MonadParsec e s m | |
---|---|
=> m () | A parser for space characters which does not accept empty input (e.g. space1) |
-> m () | A parser for a line comment (e.g. skipLineComment) |
-> m () | A parser for a block comment (e.g. skipBlockComment) |
-> m () |
`[space](Text-Megaparsec-Byte-Lexer.html#v:space "Text.Megaparsec.Byte.Lexer")` sc lineComment blockComment
produces a parser that can parse white space in general. It's expected that you create such a parser once and pass it to other functions in this module as needed (when you seespaceConsumer
in documentation, usually it means that something like[space](Text-Megaparsec-Byte-Lexer.html#v:space "Text.Megaparsec.Byte.Lexer")
is expected there).
sc
is used to parse blocks of space characters. You can use[space1](Text-Megaparsec-Char.html#v:space1 "Text.Megaparsec.Char")
from Text.Megaparsec.Char for this purpose as well as your own parser (if you don't want to automatically consume newlines, for example). Make sure that the parser does not succeed on the empty input though. In an earlier version of the library[spaceChar](Text-Megaparsec-Char.html#v:spaceChar "Text.Megaparsec.Char")
was recommended, but now parsers based on [takeWhile1P](Text-Megaparsec.html#v:takeWhile1P "Text.Megaparsec")
are preferred because of their speed.
lineComment
is used to parse line comments. You can useskipLineComment
if you don't need anything special.
blockComment
is used to parse block (multi-line) comments. You can useskipBlockComment
or skipBlockCommentNested
if you don't need anything special.
If you don't want to allow a kind of comment, simply pass [empty](/package/base-4.18.1.0/docs/Control-Applicative.html#v:empty "Control.Applicative")
which will fail instantly when parsing of that sort of comment is attempted and[space](Text-Megaparsec-Byte-Lexer.html#v:space "Text.Megaparsec.Byte.Lexer")
will just move on or finish depending on whether there is more white space for it to consume.
Arguments
:: MonadParsec e s m | |
---|---|
=> m () | How to consume white space after lexeme |
-> m a | How to parse actual lexeme |
-> m a |
This is a wrapper for lexemes. The typical usage is to supply the first argument (parser that consumes white space, probably defined via [space](Text-Megaparsec-Byte-Lexer.html#v:space "Text.Megaparsec.Byte.Lexer")
) and use the resulting function to wrap parsers for every lexeme.
lexeme = L.lexeme spaceConsumer integer = lexeme L.decimal
This is a helper to parse symbols, i.e. verbatim strings. You pass the first argument (parser that consumes white space, probably defined via[space](Text-Megaparsec-Byte-Lexer.html#v:space "Text.Megaparsec.Byte.Lexer")
) and then you can use the resulting function to parse strings:
symbol = L.symbol spaceConsumer
parens = between (symbol "(") (symbol ")") braces = between (symbol "{") (symbol "}") angles = between (symbol "<") (symbol ">") brackets = between (symbol "[") (symbol "]") semicolon = symbol ";" comma = symbol "," colon = symbol ":" dot = symbol "."
A case-insensitive version of [symbol](Text-Megaparsec-Byte-Lexer.html#v:symbol "Text.Megaparsec.Byte.Lexer")
. This may be helpful if you're working with case-insensitive languages.
Given a comment prefix this function returns a parser that skips line comments. Note that it stops just before the newline character but doesn't consume the newline. Newline is either supposed to be consumed by[space](Text-Megaparsec-Byte-Lexer.html#v:space "Text.Megaparsec.Byte.Lexer")
parser or picked up manually.
decimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a Source #
Parse an integer in the decimal representation according to the format of integer literals described in the Haskell report.
If you need to parse signed integers, see the [signed](Text-Megaparsec-Byte-Lexer.html#v:signed "Text.Megaparsec.Byte.Lexer")
combinator.
Warning: this function does not perform range checks.
binary :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a Source #
Parse an integer in the binary representation. The binary number is expected to be a non-empty sequence of zeroes “0” and ones “1”.
You could of course parse some prefix before the actual number:
binary = char 48 >> char' 98 >> L.binary
Warning: this function does not perform range checks.
Since: 7.0.0
octal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a Source #
Parse an integer in the octal representation. The format of the octal number is expected to be according to the Haskell report except for the fact that this parser doesn't parse “0o” or “0O” prefix. It is a responsibility of the programmer to parse correct prefix before parsing the number itself.
For example you can make it conform to the Haskell report like this:
octal = char 48 >> char' 111 >> L.octal
Warning: this function does not perform range checks.
hexadecimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Num a) => m a Source #
Parse an integer in the hexadecimal representation. The format of the hexadecimal number is expected to be according to the Haskell report except for the fact that this parser doesn't parse “0x” or “0X” prefix. It is a responsibility of the programmer to parse correct prefix before parsing the number itself.
For example you can make it conform to the Haskell report like this:
hexadecimal = char 48 >> char' 120 >> L.hexadecimal
Warning: this function does not perform range checks.
float :: (MonadParsec e s m, Token s ~ Word8, RealFloat a) => m a Source #
Parse a floating point number according to the syntax for floating point literals described in the Haskell report.
This function does not parse sign, if you need to parse signed numbers, see [signed](Text-Megaparsec-Byte-Lexer.html#v:signed "Text.Megaparsec.Byte.Lexer")
.
Note: in versions 6.0.0_–_6.1.1 this function accepted plain integers.
Arguments
:: (MonadParsec e s m, Token s ~ Word8, Num a) | |
---|---|
=> m () | How to consume white space after the sign |
-> m a | How to parse the number itself |
-> m a | Parser for signed numbers |
`[signed](Text-Megaparsec-Byte-Lexer.html#v:signed "Text.Megaparsec.Byte.Lexer")` space p
parser parses an optional sign character (“+” or “-”), then if there is a sign it consumes optional white space (usingspace
parser), then it runs parser p
which should return a number. Sign of the number is changed according to the previously parsed sign character.
For example, to parse signed integer you can write:
lexeme = L.lexeme spaceConsumer integer = lexeme L.decimal signedInteger = L.signed spaceConsumer integer