megaparsec-4.1.0: Monadic parser combinators

Copyright© 2015 Megaparsec contributors © 2007 Paolo Martini © 1999–2001 Daan Leijen
LicenseBSD3
MaintainerMark Karpov <markkarpov@opmbx.org>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Text.Megaparsec.Lexer

Contents

Description

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

Synopsis

White space and indentation

space Source

Arguments

:: MonadParsec s m Char 
=> m ()

A parser for a space character (e.g. spaceChar)

-> m ()

A parser for a line comment (e.g. skipLineComment)

-> m ()

A parser for a block comment (e.g. skipBlockComment)

-> 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).

lexeme :: MonadParsec s m Char => m () -> m a -> m a Source

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

symbol :: MonadParsec s m Char => m () -> String -> m String Source

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 "."

symbol' :: MonadParsec s m Char => m () -> String -> m String Source

Case-insensitive version of symbol. This may be helpful if you're working with case-insensitive languages.

indentGuard :: MonadParsec s m Char => m () -> (Int -> Bool) -> m Int Source

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.

skipLineComment :: MonadParsec s m Char => String -> m () Source

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.

skipBlockComment :: MonadParsec s m Char => String -> String -> m () Source

skipBlockComment start end skips non-nested block comment starting with start and ending with end.

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 commonly used 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

The same as integer, but integer is labeled with “integer” label, while this parser is labeled with “decimal integer”.

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, Num 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 = signed spaceConsumer integer