megaparsec-5.1.1: Monadic parser combinators

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

Text.Megaparsec.Expr

Description

A helper module to parse expressions. It can build a parser given a table of operators.

Synopsis

Documentation

data Operator m a Source #

This data type specifies operators that work on values of type a. An operator is either binary infix or unary prefix or postfix. A binary operator has also an associated associativity.

Constructors

InfixN (m (a -> a -> a))

Non-associative infix

InfixL (m (a -> a -> a))

Left-associative infix

InfixR (m (a -> a -> a))

Right-associative infix

Prefix (m (a -> a))

Prefix

Postfix (m (a -> a))

Postfix

makeExprParser Source #

Arguments

:: MonadParsec e s m 
=> m a

Term parser

-> [[Operator m a]]

Operator table, see Operator

-> m a

Resulting expression parser

makeExprParser term table builds an expression parser for terms term with operators from table, taking the associativity and precedence specified in table into account.

table is a list of [Operator m a] lists. The list is ordered in descending precedence. All operators in one list have the same precedence (but may have different associativity).

Prefix and postfix operators of the same precedence associate to the left (i.e. if ++ is postfix increment, than -2++ equals -1, not -3).

Unary operators of the same precedence can only occur once (i.e. --2 is not allowed if - is prefix negate). If you need to parse several prefix or postfix operators in a row, (like C pointers — **i) you can use this approach:

manyUnaryOp = foldr1 (.) <$> some singleUnaryOp

This is not done by default because in some cases you don't want to allow repeating prefix or postfix operators.

If you want to have an operator that is a prefix of another operator in the table, use the following (or similar) wrapper instead of plain symbol:

op n = (lexeme . try) (string n <* notFollowedBy punctuationChar)

makeExprParser takes care of all the complexity involved in building an expression parser. Here is an example of an expression parser that handles prefix signs, postfix increment and basic arithmetic:

expr = makeExprParser term table <?> "expression"

term = parens expr <|> integer <?> "term"

table = [ [ prefix  "-"  negate
          , prefix  "+"  id ]
        , [ postfix "++" (+1) ]
        , [ binary  "*"  (*)
          , binary  "/"  div  ]
        , [ binary  "+"  (+)
          , binary  "-"  (-)  ] ]

binary  name f = InfixL  (f <$ symbol name)
prefix  name f = Prefix  (f <$ symbol name)
postfix name f = Postfix (f <$ symbol name)