Copyright | © 2015–2016 Megaparsec contributors © 2007 Paolo Martini © 1999–2001 Daan Leijen |
---|---|
License | FreeBSD |
Maintainer | Mark Karpov <markkarpov@opmbx.org> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
High-level parsers to help you write your lexer. The module doesn't impose how you should write your parser, but certain approaches may be more elegant than others. Especially important theme is parsing of white space, comments, and indentation.
This module is intended to be imported qualified:
import qualified Text.Megaparsec.Lexer as L
- space :: MonadParsec s m Char => m () -> m () -> m () -> m ()
- lexeme :: MonadParsec s m Char => m () -> m a -> m a
- symbol :: MonadParsec s m Char => m () -> String -> m String
- symbol' :: MonadParsec s m Char => m () -> String -> m String
- skipLineComment :: MonadParsec s m Char => String -> m ()
- skipBlockComment :: MonadParsec s m Char => String -> String -> m ()
- indentLevel :: MonadParsec s m t => m Int
- indentGuard :: MonadParsec s m Char => m () -> (Int -> Bool) -> m Int
- nonIndented :: MonadParsec s m Char => m () -> m a -> m a
- data IndentOpt m a b
- = IndentNone a
- | IndentMany (Maybe Int) ([b] -> m a) (m b)
- | IndentSome (Maybe Int) ([b] -> m a) (m b)
- indentBlock :: MonadParsec s m Char => m () -> m (IndentOpt m a b) -> m a
- charLiteral :: MonadParsec s m Char => m Char
- class Signed a where
- negate :: a -> a
- integer :: MonadParsec s m Char => m Integer
- decimal :: MonadParsec s m Char => m Integer
- hexadecimal :: MonadParsec s m Char => m Integer
- octal :: MonadParsec s m Char => m Integer
- float :: MonadParsec s m Char => m Double
- number :: MonadParsec s m Char => m (Either Integer Double)
- signed :: (MonadParsec s m Char, Signed a) => m () -> m a -> m a
White space
:: MonadParsec s m Char | |
=> m () | A parser for a space character (e.g. |
-> m () | A parser for a line comment (e.g. |
-> m () | A parser for a block comment (e.g. |
-> m () |
space spaceChar lineComment blockComment
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 spaceConsumer
in documentation, usually it means that something
like space
is expected there).
spaceChar
is used to parse trivial space characters. You can use
spaceChar
from Text.Megaparsec.Char for this purpose as well as
your own parser (if you don't want automatically consume newlines, for
example).
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
if you don't need anything special.
Parsing of white space is an important part of any parser. We propose a
convention where every lexeme parser assumes no spaces before the lexeme
and consumes all spaces after the lexeme; this is what the lexeme
combinator does, and so it's enough to wrap every lexeme parser with
lexeme
to achieve this. Note that you'll need to call space
manually
to consume any white space before the first lexeme (i.e. at the beginning
of the file).
:: MonadParsec s m Char | |
=> m () | How to consume white space after lexeme |
-> m a | How to parse actual lexeme |
-> m a |
This is wrapper for lexemes. Typical usage is to supply 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.integer
:: MonadParsec s m Char | |
=> m () | How to consume white space after lexeme |
-> String | String to parse |
-> m String |
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 s m Char | |
=> m () | How to consume white space after lexeme |
-> String | String to parse (case-insensitive) |
-> m String |
Case-insensitive version of symbol
. This may be helpful if you're
working with case-insensitive languages.
:: MonadParsec s m Char | |
=> String | Line comment prefix |
-> m () |
Given comment prefix this function returns parser that skips line
comments. Note that it stops just before newline character but doesn't
consume the newline. Newline is either supposed to be consumed by space
parser or picked up manually.
:: MonadParsec s m Char | |
=> String | Start of block comment |
-> String | End of block comment |
-> m () |
skipBlockComment start end
skips non-nested block comment starting
with start
and ending with end
.
Indentation
indentLevel :: MonadParsec s m t => m Int Source
Return current indentation level.
The function is a simple shortcut defined as:
indentLevel = sourceColumn <$> getPosition
Since: 4.3.0
:: MonadParsec s m Char | |
=> m () | How to consume indentation (white space) |
-> (Int -> Bool) | Predicate checking indentation level |
-> m Int | Current column (indentation level) |
indentGuard spaceConsumer test
first consumes all white space
(indentation) with spaceConsumer
parser, then it checks column
position. It should satisfy supplied predicate test
, otherwise the
parser fails with error message “incorrect indentation”. On success
current column position is returned.
When you want to parse block of indentation first run this parser with
predicate like (> 1)
— this will make sure you have some
indentation. Use returned value to check indentation on every subsequent
line according to syntax of your language.
:: MonadParsec s m Char | |
=> m () | How to consume indentation (white space) |
-> m a | How to parse actual data |
-> m a |
Parse non-indented construction. This ensures that there is no indentation before actual data. Useful, for example, as a wrapper for top-level function definitions.
Since: 4.3.0
The data type represents available behaviors for parsing of indented
tokens. This is used in indentBlock
, which see.
Since: 4.3.0
IndentNone a | Parse no indented tokens, just return the value |
IndentMany (Maybe Int) ([b] -> m a) (m b) | Parse many indented tokens (possibly zero), use given indentation
level (if |
IndentSome (Maybe Int) ([b] -> m a) (m b) | Just like |
:: MonadParsec s m Char | |
=> m () | How to consume indentation (white space) |
-> m (IndentOpt m a b) | How to parse “reference” token |
-> m a |
Parse a “reference” token and a number of other tokens that have
greater (but the same) level of indentation than that of “reference”
token. Reference token can influence parsing, see IndentOpt
for more
information.
Tokens must not consume newlines after them. On the other hand, the first argument of this function must consume newlines among other white space characters.
Since: 4.3.0
Character and string literals
charLiteral :: MonadParsec s m Char => m Char Source
The lexeme parser parses a single literal character without quotes. 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 '"')
Numbers
integer :: MonadParsec s m Char => m Integer Source
Parse an integer without sign in decimal representation (according to format of integer literals described in Haskell report).
If you need to parse signed integers, see signed
combinator.
decimal :: MonadParsec s m Char => m Integer Source
hexadecimal :: MonadParsec s m Char => m Integer Source
Parse an integer in hexadecimal representation. Representation of hexadecimal number is expected to be according to Haskell report except for the fact that this parser doesn't parse “0x” or “0X” prefix. It is responsibility of the programmer to parse correct prefix before parsing the number itself.
For example you can make it conform to Haskell report like this:
hexadecimal = char '0' >> char' 'x' >> L.hexadecimal
octal :: MonadParsec s m Char => m Integer Source
Parse an integer in octal representation. Representation of octal number is expected to be according to Haskell report except for the fact that this parser doesn't parse “0o” or “0O” prefix. It is responsibility of the programmer to parse correct prefix before parsing the number itself.
float :: MonadParsec s m Char => m Double Source
Parse a floating point value without sign. Representation of floating point value is expected to be according to Haskell report.
If you need to parse signed floats, see signed
.
number :: MonadParsec s m Char => m (Either Integer Double) Source
Parse a number: either integer or floating point. The parser can handle overlapping grammars graciously.
signed :: (MonadParsec s m Char, Signed a) => m () -> m a -> m a Source
signed space p
parser parses optional sign, then if there is a sign
it will consume optional white space (using space
parser), then it runs
parser p
which should return a number. Sign of the number is changed
according to previously parsed sign.
For example, to parse signed integer you can write:
lexeme = L.lexeme spaceConsumer integer = lexeme L.integer signedInteger = L.signed spaceConsumer integer