Search code examples
haskellcompiler-constructioninterpreterparseclambda-calculus

How to manually manipulate precedence of special expressions in Parsec?


I tried to write a parser for a lambda-calculus interpreter that uses the expression closures grammars of JavaScript 1.8, which means function(x) x * x same with function(x) { return x * x; }.

Here is my parser code.

module Parser where

import Text.Parsec
import Text.Parsec.String
import qualified Text.Parsec.Token as P
import qualified Text.ParserCombinators.Parsec.Token as T
import Text.Parsec.Language (emptyDef)
import Text.Parsec.Expr
import Control.Applicative ((<*>), (<$>), (*>), (<*), pure, (<$))
import Control.Monad

import Ast

jsparse :: String -> Either ParseError [Term]
jsparse  = parse prog ""

-- The scanner.
lexer = P.makeTokenParser emptyDef {
  T.commentStart = "/*",
  T.commentEnd   = "*/",
  T.commentLine  = "//",
  T.nestedComments = True,
  T.identStart = letter <|> char '_' <|> char '$',
  T.identLetter     = alphaNum,
  T.reservedNames   = ["function"],
  T.reservedOpNames = ["="],
  T.caseSensitive   = True
}

parens = P.parens lexer
reserved = P.reserved lexer
identifier = P.identifier lexer
whiteSpace = P.whiteSpace lexer
semi = P.semi lexer

-- The parser
prog :: Parser [Term]
prog = expr `endBy` semi

term :: Parser Term
term = termE expr

termE :: Parser Term -> Parser Term
termE e = try (parens e) <|> try var <|> func

expr :: Parser Term
expr = do whiteSpace
          e <- term
          maybeAddSuffix e
  where addSuffix e0 = do e1 <- term
                          maybeAddSuffix $ TermApp e0 e1
        maybeAddSuffix e = addSuffix e
                           <|> return e

var :: Parser Term
var = do whiteSpace
         v <- identifier
         return $ TermVar v

func :: Parser Term
func  = do whiteSpace
           reserved "function"
           v  <- parens identifier
           body <- term
           return $ TermAbs v body 

However, there is a trouble that function(x) x(x) should be parsed to (function(x) (x(x))), but my parser gets (function(x) x) (x).


Solution

  • In the definition of func, body <- term means the body can only consist of a simple term. To allow all expressions in a function body, change it to body <- expr.