Copyright | (c) 2022 Lev Dvorkin |
---|---|
License | BSD3 |
Maintainer | Lev Dvorkin <lev_135@mail.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides alternative to Text.Megaparsec.Char.Lexer approach for lexing process, especially for indentation-sensitive parsing. It's highly not recommended to mix functions from these two modules.
Parsing of white space is an important part of any parser. We propose a special policy for consuming line spaces (i. e. spaces and tabs) and line endings:
- For line spaces we follow Text.Megaparsec.Char.Lexer: each lexeme should
consume all line spaces after it and this can be done by wrapping it in
lexeme
combinator. - For end of line symbols we have a different convention: parser should consume only eols inside it's block, but not those, which follow it.
Also note that you need to call space
manually to consume any white space
before the first lexeme (i.e. at the beginning of the file).
This module is intended to be imported qualified:
import qualified Text.Megaparsec.Char.Lexer.New as L
Synopsis
- newtype Sc m = Sc {
- unSc :: m ()
- type Scn m = m ()
- space :: MonadParsec e s m => m () -> m () -> m () -> m ()
- lexeme :: MonadParsec e s m => Sc m -> m a -> m a
- symbol :: MonadParsec e s m => Sc m -> Tokens s -> m (Tokens s)
- symbol' :: (MonadParsec e s m, FoldCase (Tokens s)) => Sc m -> Tokens s -> m (Tokens s)
- skipLineComment :: (MonadParsec e s m, Token s ~ Char) => Tokens s -> m ()
- skipBlockComment :: (MonadParsec e s m, Token s ~ Char) => Tokens s -> Tokens s -> m ()
- skipBlockCommentNested :: (MonadParsec e s m, Token s ~ Char) => Tokens s -> Tokens s -> m ()
- indentLevel :: (TraversableStream s, MonadParsec e s m) => m Pos
- incorrectIndent :: MonadParsec e s m => Ordering -> Pos -> Pos -> m a
- indentGuard :: (TraversableStream s, MonadParsec e s m) => m () -> Ordering -> Pos -> m Pos
- block :: (TraversableStream s, MonadParsec e s m) => Scn m -> (Scn m -> m a) -> m a
- blockWith :: (TraversableStream s, MonadParsec e s m) => Ordering -> Pos -> Scn m -> (Scn m -> m a) -> m a
- headedOne :: (TraversableStream s, MonadParsec e s m) => Scn m -> Scn m -> m (el -> a) -> (Scn m -> m el) -> m a
- headedOptional :: (TraversableStream s, MonadParsec e s m) => Scn m -> Scn m -> m (Maybe el -> a) -> (Scn m -> m el) -> m a
- headedSome :: (TraversableStream s, MonadParsec e s m) => Scn m -> Scn m -> m ([el] -> a) -> m el -> m a
- headedMany :: (TraversableStream s, MonadParsec e s m) => Scn m -> Scn m -> m ([el] -> a) -> m el -> m a
- headedBlock :: (TraversableStream s, MonadParsec e s m) => Scn m -> Scn m -> m (Body m a) -> m a
- data Body m a
- pureBody :: a -> Body m a
- oneBody :: (Scn m -> m a) -> Body m a
- optionBody :: a -> (Scn m -> m a) -> Body m a
- optionalBody :: (Scn m -> m (Maybe a)) -> Body m (Maybe a)
- someBody :: (TraversableStream s, MonadParsec e s m) => m el -> Body m [el]
- manyBody :: (TraversableStream s, MonadParsec e s m) => m el -> Body m [el]
- lineFold :: (TraversableStream s, MonadParsec e s m) => Sc m -> Scn m -> (Sc m -> m a) -> m a
- paragraph :: (TraversableStream s, MonadParsec e s m) => Sc m -> Scn m -> (Sc m -> m a) -> m a
- lineFoldWith :: (TraversableStream s, MonadParsec e s m) => Ordering -> Pos -> Sc m -> Scn m -> (Sc m -> m a) -> m a
- charLiteral :: (MonadParsec e s m, Token s ~ Char) => m Char
- decimal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
- binary :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
- octal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
- hexadecimal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a
- scientific :: (MonadParsec e s m, Token s ~ Char) => m Scientific
- float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a
- signed :: (MonadParsec e s m, Token s ~ Char, Num a) => m () -> m a -> m a
Space consumer wrappers
Newtype wrapper for line space consumer. In common cases you should use standard combinators from Text.Megaparsec.Char.Lexer.New rather than unwrap it manually
A type synonym for space and eol consumer. Should be called manually wherever line break is expected
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 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 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 that the parser does not
succeed on the empty input though. In an earlier version of the library
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.
lexeme :: MonadParsec e s m => Sc m -> m a -> m a Source #
A lexeme sc p
behaves like p
and consumes spaces by sc
after it
symbol :: MonadParsec e s m => Sc m -> Tokens s -> m (Tokens s) Source #
symbol sc toks
parse toks and consumes spaces by sc
after them
symbol' :: (MonadParsec e s m, FoldCase (Tokens s)) => Sc m -> Tokens s -> m (Tokens s) Source #
A case-insensitive version of symbol
:: (MonadParsec e s m, Token s ~ Char) | |
=> Tokens s | Line comment prefix |
-> m () |
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
parser or picked up manually.
:: (MonadParsec e s m, Token s ~ Char) | |
=> 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
.
:: (MonadParsec e s m, Token s ~ Char) | |
=> 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
Indentation
Primitives for indentation-sensitive parsing
indentLevel :: (TraversableStream s, MonadParsec e s m) => m Pos #
Return the current indentation level.
The function is a simple shortcut defined as:
indentLevel = sourceColumn <$> getPosition
Since: megaparsec-4.3.0
:: MonadParsec e s m | |
=> Ordering | Desired ordering between reference level and actual level |
-> Pos | Reference indentation level |
-> Pos | Actual indentation level |
-> m a |
Fail reporting incorrect indentation error. The error has attached information:
- Desired ordering between reference level and actual level
- Reference indentation level
- Actual indentation level
Since: megaparsec-5.0.0
:: (TraversableStream s, MonadParsec e s m) | |
=> m () | How to consume indentation (white space) |
-> Ordering | Desired ordering between reference level and actual level |
-> Pos | Reference indentation level |
-> m Pos | Current column (indentation level) |
first consumes all white space
(indentation) with indentGuard
spaceConsumer ord refspaceConsumer
parser, then it checks the column
position. Ordering between current indentation level and the reference
indentation level ref
should be ord
, otherwise the parser fails. On
success the current column position is returned.
When you want to parse a block of indentation, first run this parser with
arguments like
—this will make
sure you have some indentation. Use returned value to check indentation
on every subsequent line according to syntax of your language.indentGuard
spaceConsumer GT
pos1
Blocks of line
block :: (TraversableStream s, MonadParsec e s m) => Scn m -> (Scn m -> m a) -> m a Source #
Parse a block of consecutive lines with the same Indentation
For example, for parsing something like
foo bar baz
you can use something like this
block space $ scn -> do string "foo" <* scn string "bar" <* scn string "baz" -- we do not use eol consumer after the last string!
:: (TraversableStream s, MonadParsec e s m) | |
=> Ordering | desired ordering |
-> Pos | reference indentation level |
-> Scn m | space and eols consumer |
-> (Scn m -> m a) | callback that uses provided space consumer |
-> m a | result returned by a callback |
Generalized version of block
, providing a way to change what is desired
ordering related to a reference indentation level
Headed blocks
Simple combinators
:: (TraversableStream s, MonadParsec e s m) | |
=> Scn m | how to consume white space after the head |
-> Scn m | how to consume white space after each line of body |
-> m (el -> a) | how to parse a head |
-> (Scn m -> m el) | callback to parse a body |
-> m a |
:: (TraversableStream s, MonadParsec e s m) | |
=> Scn m | how to consume white space after the head |
-> Scn m | how to consume white space after each line of body |
-> m (Maybe el -> a) | how to parse a head |
-> (Scn m -> m el) | callback to parse a body |
-> m a |
:: (TraversableStream s, MonadParsec e s m) | |
=> Scn m | how to consume white space after the head |
-> Scn m | how to consume white space after each line of body |
-> m ([el] -> a) | how to parse a head |
-> m el | how to parse each element of the body |
-> m a |
:: (TraversableStream s, MonadParsec e s m) | |
=> Scn m | how to consume white space after the head |
-> Scn m | how to consume white space after each line of body |
-> m ([el] -> a) | how to parse a head |
-> m el | how to parse each element of the body |
-> m a |
General combinators
:: (TraversableStream s, MonadParsec e s m) | |
=> Scn m | how to consume white space after the head |
-> Scn m | how to consume white space after each line of body |
-> m (Body m a) | how to parse a head and get body parser |
-> m a | the value, returned by body parser |
Parse a head of the block and then its body, depending on what Body
is returned after processing of the head. Use it if the choice of body parser
depends on the head parser's result. In other cases you should prefer
headedOne
headedSome
headedMany
/headedOptional
For example, suppose we want to parse something like this (in the first line we have an arbitrary identifier and than it's repeated in all subsequent lines):
foo: foo 42 foo 36
we can use something like this:
headedBlock space space $ do name <- takeWhile1P isLetter string ":" pure $ someBody (L.symbol hspace name *> L.decimal)
Opaque type, containing information about parsing headedBlock
s body
Functor
instance can be used to modify a result value
pureBody :: a -> Body m a Source #
Don't parse anything, just return a constant value. Can be used if after parsing head you realized that there should be no body here
oneBody :: (Scn m -> m a) -> Body m a Source #
Parse a body by given callback. Callback can use space consumer to
parse a multiline body. If the body consists of some identical parts use
someBody
/manyBody
instead.
Note, that it will always fail, if the body is empty, even if a callback can
succeed without consuming input. Use optionBody
/optionalBody
in this case.
optionBody :: a -> (Scn m -> m a) -> Body m a Source #
Parse a body by given callback, if the next line after a head has greater indentation level, otherwise return a constant value
optionalBody :: (Scn m -> m (Maybe a)) -> Body m (Maybe a) Source #
Parse a body by given callback, if the next line after a head has greater indentation level, otherwise return Nothing
optionalBody = optionBody Nothing
someBody :: (TraversableStream s, MonadParsec e s m) => m el -> Body m [el] Source #
Parse some (greater, than zero) number of lines by given parser
someBody pEl = oneBody (pEl `sepBy1`)
manyBody :: (TraversableStream s, MonadParsec e s m) => m el -> Body m [el] Source #
Parse many (maybe zero) lines by given parser
manyBody pEl = optionBody [] (pEl `sepBy`)
Line folds
:: (TraversableStream s, MonadParsec e s m) | |
=> Sc m | Line space consumer |
-> Scn m | Line space and eols consumer |
-> (Sc m -> m a) | Callback that uses provided space-consumer |
-> m a |
:: (TraversableStream s, MonadParsec e s m) | |
=> Sc m | Line space consumer |
-> Scn m | Line space and eols consumer |
-> (Sc m -> m a) | Callback that uses provided space-consumer |
-> m a |
lineFoldWith :: (TraversableStream s, MonadParsec e s m) => Ordering -> Pos -> Sc m -> Scn m -> (Sc m -> m a) -> m a Source #
Character and string literals
charLiteral :: (MonadParsec e s m, Token s ~ Char) => m Char #
The lexeme parser parses a single literal character without quotes. The purpose of this parser is to help with parsing of conventional escape sequences. It's your responsibility to take care of character literal syntax in your language (by surrounding it with single quotes or similar).
The literal character is parsed according to the grammar rules defined in the Haskell report.
Note that you can use this parser as a building block to parse various string literals:
stringLiteral = char '"' >> manyTill L.charLiteral (char '"')
Performance note: the parser is not particularly efficient at the moment.
Numbers
binary :: (MonadParsec e s m, Token s ~ Char, Num a) => m a #
Parse an integer in 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 '0' >> char' 'b' >> L.binary
Since: megaparsec-7.0.0
octal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a #
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 '0' >> char' 'o' >> L.octal
Note: before version 6.0.0 the function returned Integer
, i.e. it
wasn't polymorphic in its return type.
hexadecimal :: (MonadParsec e s m, Token s ~ Char, Num a) => m a #
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 '0' >> char' 'x' >> L.hexadecimal
Note: before version 6.0.0 the function returned Integer
, i.e. it
wasn't polymorphic in its return type.
scientific :: (MonadParsec e s m, Token s ~ Char) => m Scientific #
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
.
Since: megaparsec-5.0.0
float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a #
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: before version 6.0.0 the function returned Double
, i.e. it
wasn't polymorphic in its return type.
Note: in versions 6.0.0–6.1.1 this function accepted plain integers.
:: (MonadParsec e s m, Token s ~ Char, 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 |
parses an optional sign character (“+” or “-”), then
if there is a sign it consumes optional white space (using the signed
space pspace
parser), then it runs the 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