megaparsec-4.0.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.Expr

Description

A helper module to parse expressions. Builds 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 :: MonadParsec s m t => m a -> [[Operator m a]] -> m a Source

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 s u m a] lists. The list is ordered in descending precedence. All operators in one list have the same precedence (but may have a different associativity).

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

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  (reservedOp name >> return f)
prefix  name f = Prefix  (reservedOp name >> return f)
postfix name f = Postfix (reservedOp name >> return f)

Please note that multi-character operators should use try in order to be reported correctly in error messages.