Copyright | © 2015–2018 Megaparsec contributors |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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, Token s ~ Word8) => 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, Integral a) => m a
- octal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral a) => m a
- hexadecimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral 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
White space
:: MonadParsec e s m | |
=> m () | A parser for space characters which does not accept empty
input (e.g. |
-> m () | A parser for a line comment (e.g. |
-> m () | A parser for a block comment (e.g. |
-> m () |
produces 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 see
space
sc lineComment blockCommentspaceConsumer
in documentation, usually it means that something like
space
is expected there).
sc
is used to parse blocks of space characters. You can use space1
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 the parser does not succeed on empty input though. In earlier
version spaceChar
was recommended, but now parsers based on
takeWhile1P
are preferred because of their speed.
lineComment
is used to parse line comments. You can use
skipLineComment
if you don't need anything special.
blockComment
is used to parse block (multi-line) comments. You can use
skipBlockComment
or skipBlockCommentNested
if you don't need anything
special.
If you don't want to allow a kind of comment, simply pass empty
which
will fail instantly when parsing of that sort of comment is attempted and
space
will just move on or finish depending on whether there is more
white space for it to consume.
:: 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. Typical usage is to supply the first
argument (parser that consumes white space, probably defined via space
)
and use the resulting function to wrap parsers for every lexeme.
lexeme = L.lexeme spaceConsumer integer = lexeme L.decimal
:: MonadParsec e s m | |
=> m () | How to consume white space after lexeme |
-> Tokens s | Symbol to parse |
-> m (Tokens s) |
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
) 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 "."
:: (MonadParsec e s m, FoldCase (Tokens s)) | |
=> m () | How to consume white space after lexeme |
-> Tokens s | Symbol to parse (case-insensitive) |
-> m (Tokens s) |
Case-insensitive version of symbol
. This may be helpful if you're
working with case-insensitive languages.
:: (MonadParsec e s m, Token s ~ Word8) | |
=> Tokens s | Line comment prefix |
-> m () |
Given 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
parser or picked up manually.
:: (MonadParsec e s m, Token s ~ Word8) | |
=> Tokens s | Start of block comment |
-> Tokens s | End of block comment |
-> m () |
skips non-nested block comment starting
with skipBlockComment
start endstart
and ending with end
.
skipBlockCommentNested Source #
:: (MonadParsec e s m, Token s ~ Word8) | |
=> Tokens s | Start of block comment |
-> Tokens s | End of block comment |
-> m () |
skips possibly nested block
comment starting with skipBlockCommentNested
start endstart
and ending with end
.
Since: megaparsec-5.0.0
Numbers
decimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral a) => m a Source #
Parse an integer in decimal representation according to the format of integer literals described in the Haskell report.
If you need to parse signed integers, see signed
combinator.
octal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral a) => m a Source #
Parse an integer in octal representation. Representation of 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 '0' >> char' 'o' >> L.octal
hexadecimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral a) => m a Source #
Parse an integer in hexadecimal representation. Representation of 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 '0' >> char' 'x' >> L.hexadecimal
scientific :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m Scientific Source #
Parse a floating point value as a Scientific
number. Scientific
is
great for parsing of arbitrary precision numbers coming from an untrusted
source. See documentation in Data.Scientific for more information.
The parser can be used to parse integers or floating point values. Use
functions like floatingOrInteger
from Data.Scientific
to test and extract integer or real values.
This function does not parse sign, if you need to parse signed numbers,
see signed
.
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
.
Note: in versions 6.0.0–6.1.1 this function accepted plain integers.
:: (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 |
parser parses an optional sign character (“+” or
“-”), then if there is a sign it consumes optional white space (using
signed
space pspace
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