2008-01-13 20:53:15 +03:00
|
|
|
|
-- |
|
2015-08-01 19:24:45 +03:00
|
|
|
|
-- Module : Text.Megaparsec.Expr
|
|
|
|
|
-- Copyright : © 2015 Megaparsec contributors
|
2015-07-30 19:20:37 +03:00
|
|
|
|
-- © 2007 Paolo Martini
|
|
|
|
|
-- © 1999–2001 Daan Leijen
|
2015-07-28 16:32:19 +03:00
|
|
|
|
-- License : BSD3
|
|
|
|
|
--
|
|
|
|
|
-- Maintainer : Mark Karpov <markkarpov@opmbx.org>
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- Stability : experimental
|
2008-01-13 20:53:15 +03:00
|
|
|
|
-- Portability : non-portable
|
2015-07-28 16:32:19 +03:00
|
|
|
|
--
|
2015-08-12 15:41:22 +03:00
|
|
|
|
-- A helper module to parse expressions. Builds a parser given a table of
|
|
|
|
|
-- operators.
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2015-08-01 19:24:45 +03:00
|
|
|
|
module Text.Megaparsec.Expr
|
2015-08-12 20:51:06 +03:00
|
|
|
|
( Assoc (..)
|
|
|
|
|
, Operator (..)
|
|
|
|
|
, OperatorTable
|
|
|
|
|
, buildExpressionParser )
|
2015-07-28 16:32:19 +03:00
|
|
|
|
where
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2015-08-01 17:39:20 +03:00
|
|
|
|
import Control.Applicative ((<|>))
|
2015-07-30 18:45:06 +03:00
|
|
|
|
import Data.List (foldl')
|
|
|
|
|
|
2015-08-01 19:24:45 +03:00
|
|
|
|
import Text.Megaparsec.Combinator
|
|
|
|
|
import Text.Megaparsec.Prim
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- | This data type specifies the associativity of operators: left, right
|
2008-01-20 09:43:50 +03:00
|
|
|
|
-- or none.
|
|
|
|
|
|
2015-07-30 18:45:06 +03:00
|
|
|
|
data Assoc
|
2015-08-12 20:51:06 +03:00
|
|
|
|
= AssocNone
|
|
|
|
|
| AssocLeft
|
|
|
|
|
| AssocRight
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2008-01-20 09:43:50 +03:00
|
|
|
|
-- | This data type specifies operators that work on values of type @a@.
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- An operator is either binary infix or unary prefix or postfix. A binary
|
|
|
|
|
-- operator has also an associated associativity.
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2015-07-30 18:45:06 +03:00
|
|
|
|
data Operator s u m a
|
2015-08-12 20:51:06 +03:00
|
|
|
|
= Infix (ParsecT s u m (a -> a -> a)) Assoc
|
|
|
|
|
| Prefix (ParsecT s u m (a -> a))
|
|
|
|
|
| Postfix (ParsecT s u m (a -> a))
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2008-01-20 09:43:50 +03:00
|
|
|
|
-- | An @OperatorTable s u m a@ is a list of @Operator s u m a@
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- lists. The list is ordered in descending precedence. All operators in one
|
|
|
|
|
-- list have the same precedence (but may have a different associativity).
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2008-01-20 09:43:50 +03:00
|
|
|
|
type OperatorTable s u m a = [[Operator s u m a]]
|
2008-01-13 20:53:15 +03:00
|
|
|
|
|
2008-01-20 09:43:50 +03:00
|
|
|
|
-- | @buildExpressionParser table term@ builds an expression parser for
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- terms @term@ with operators from @table@, taking the associativity and
|
|
|
|
|
-- precedence specified in @table@ into account. 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@).
|
2008-01-20 09:43:50 +03:00
|
|
|
|
--
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- The @buildExpressionParser@ takes care of all the complexity involved in
|
|
|
|
|
-- building expression parser. Here is an example of an expression parser
|
|
|
|
|
-- that handles prefix signs, postfix increment and basic arithmetic.
|
2008-01-20 09:43:50 +03:00
|
|
|
|
--
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- > expr = buildExpressionParser table term <?> "expression"
|
2008-01-20 09:43:50 +03:00
|
|
|
|
-- >
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- > term = parens expr <|> natural <?> "simple expression"
|
2008-01-20 09:43:50 +03:00
|
|
|
|
-- >
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- > table = [ [ prefix "-" negate
|
|
|
|
|
-- > , prefix "+" id ]
|
|
|
|
|
-- > , [ postfix "++" (+1) ]
|
|
|
|
|
-- > , [ binary "*" (*) AssocLeft
|
|
|
|
|
-- > , binary "/" div AssocLeft ]
|
|
|
|
|
-- > , [ binary "+" (+) AssocLeft
|
|
|
|
|
-- > , binary "-" (-) AssocLeft ] ]
|
2015-07-28 16:32:19 +03:00
|
|
|
|
-- >
|
2015-07-30 18:45:06 +03:00
|
|
|
|
-- > binary name fun assoc = Infix (reservedOp name >> return fun) assoc
|
|
|
|
|
-- > prefix name fun = Prefix (reservedOp name >> return fun)
|
|
|
|
|
-- > postfix name fun = Postfix (reservedOp name >> return fun)
|
|
|
|
|
|
|
|
|
|
buildExpressionParser :: Stream s m t => OperatorTable s u m a ->
|
|
|
|
|
ParsecT s u m a -> ParsecT s u m a
|
|
|
|
|
buildExpressionParser ops simpleExpr = foldl' makeParser simpleExpr ops
|
|
|
|
|
|
|
|
|
|
makeParser :: (Foldable t, Stream s m t1) =>
|
|
|
|
|
ParsecT s u m b -> t (Operator s u m b) -> ParsecT s u m b
|
|
|
|
|
makeParser term ops =
|
2015-08-12 20:51:06 +03:00
|
|
|
|
termP >>= \x -> rasP x <|> lasP x <|> nasP x <|> return x <?> "operator"
|
|
|
|
|
where (ras, las, nas, prefix, postfix) = foldr splitOp ([],[],[],[],[]) ops
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
rasOp = choice ras
|
|
|
|
|
lasOp = choice las
|
|
|
|
|
nasOp = choice nas
|
|
|
|
|
prefixOp = choice prefix <?> ""
|
|
|
|
|
postfixOp = choice postfix <?> ""
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
ambigious assoc op =
|
|
|
|
|
try $ op >> fail ("ambiguous use of a " ++ assoc
|
|
|
|
|
++ " associative operator")
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
ambigiousRight = ambigious "right" rasOp
|
|
|
|
|
ambigiousLeft = ambigious "left" lasOp
|
|
|
|
|
ambigiousNon = ambigious "non" nasOp
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
termP = do
|
|
|
|
|
pre <- prefixP
|
|
|
|
|
x <- term
|
|
|
|
|
post <- postfixP
|
|
|
|
|
return $ post (pre x)
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
postfixP = postfixOp <|> return id
|
|
|
|
|
prefixP = prefixOp <|> return id
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
rasP x = do { f <- rasOp; y <- termP >>= rasP1; return (f x y)}
|
|
|
|
|
<|> ambigiousLeft
|
|
|
|
|
<|> ambigiousNon
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
rasP1 x = rasP x <|> return x
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
lasP x = do { f <- lasOp; y <- termP; lasP1 (f x y) }
|
|
|
|
|
<|> ambigiousRight
|
|
|
|
|
<|> ambigiousNon
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
lasP1 x = lasP x <|> return x
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
2015-08-12 20:51:06 +03:00
|
|
|
|
nasP x = do
|
|
|
|
|
f <- nasOp
|
|
|
|
|
y <- termP
|
|
|
|
|
ambigiousRight <|> ambigiousLeft <|> ambigiousNon <|> return (f x y)
|
2015-07-30 18:45:06 +03:00
|
|
|
|
|
|
|
|
|
splitOp :: Operator s u m a ->
|
|
|
|
|
( [ParsecT s u m (a -> a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a)] ) ->
|
|
|
|
|
( [ParsecT s u m (a -> a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a)]
|
|
|
|
|
, [ParsecT s u m (a -> a)] )
|
|
|
|
|
splitOp (Infix op assoc) (ras, las, nas, prefix, postfix) =
|
2015-08-12 20:51:06 +03:00
|
|
|
|
case assoc of
|
|
|
|
|
AssocNone -> (ras, las, op:nas, prefix, postfix)
|
|
|
|
|
AssocLeft -> (ras, op:las, nas, prefix, postfix)
|
|
|
|
|
AssocRight -> (op:ras, las, nas, prefix, postfix)
|
2015-07-30 18:45:06 +03:00
|
|
|
|
splitOp (Prefix op) (ras, las, nas, prefix, postfix) =
|
2015-08-12 20:51:06 +03:00
|
|
|
|
(ras, las, nas, op:prefix, postfix)
|
2015-07-30 18:45:06 +03:00
|
|
|
|
splitOp (Postfix op) (ras, las, nas, prefix, postfix) =
|
2015-08-12 20:51:06 +03:00
|
|
|
|
(ras, las, nas, prefix, op:postfix)
|