Search code examples
parsinghaskellparsecmutual-recursion

precedence climbing in haskell: parsec mutual recursion error


I'm programming the precedence climbing algorithm in Haskell, but for a reason unknown to me, does not work. I think that Parsec state info is lost at some point, but I don't even know that is the source of the error:

module PrecedenceClimbing where

import Text.Parsec
import Text.Parsec.Char

{-
Algorithm

compute_expr(min_prec):
  result = compute_atom()

  while cur token is a binary operator with precedence >= min_prec:
    prec, assoc = precedence and associativity of current token
    if assoc is left:
      next_min_prec = prec + 1
    else:
      next_min_prec = prec
    rhs = compute_expr(next_min_prec)
    result = compute operator(result, rhs)

  return result
-}

type Precedence = Int
data Associativity = LeftAssoc
                   | RightAssoc
                   deriving (Eq, Show)
data OperatorInfo = OPInfo Precedence Associativity (Int -> Int -> Int)

mkOperator :: Char -> OperatorInfo
mkOperator = \c -> case c of
                     '+' -> OPInfo 1 LeftAssoc  (+)
                     '-' -> OPInfo 1 LeftAssoc  (-)
                     '*' -> OPInfo 2 LeftAssoc  (*)
                     '/' -> OPInfo 2 LeftAssoc  div
                     '^' -> OPInfo 3 RightAssoc (^)

getPrecedence :: OperatorInfo -> Precedence
getPrecedence (OPInfo prec _ _) = prec

getAssoc :: OperatorInfo -> Associativity
getAssoc (OPInfo _ assoc _) = assoc

getFun :: OperatorInfo -> (Int -> Int -> Int)
getFun (OPInfo _ _ fun) = fun

number :: Parsec String () Int
number = do
  spaces
  fmap read $ many1 digit

operator :: Parsec String () OperatorInfo
operator = do
  spaces
  fmap mkOperator $ oneOf "+-*/^"

computeAtom = do
  spaces
  number

loop minPrec res = (do
  oper <- operator
  let prec = getPrecedence oper
  if prec >= minPrec
  then do
    let assoc = getAssoc oper
        next_min_prec = if assoc == LeftAssoc
                        then prec + 1
                        else prec
    rhs <- computeExpr(next_min_prec)
    loop minPrec $ getFun oper res rhs
  else return res) <|> (return res)

computeExpr :: Int -> Parsec String () Int
computeExpr minPrec = (do
  result <- computeAtom
  loop minPrec result) <|> (computeAtom)

getResult minPrec = parse (computeExpr minPrec) ""

My program for some reason is only processing the first operation or the first operand depending on the case, but does not go any further

GHCi session:

*PrecedenceClimbing> getResult 1 "46+10"
Right 56
*PrecedenceClimbing> getResult 1 "46+10+1"
Right 56

Solution

  • I'm not sure exactly what's wrong with your code but I'll offer these comments:

    (1) These statements are not equivalent:

    Generic Imperative: rhs = compute_expr(next_min_prec)
    
    Haskell:            rhs <- computeExpr(next_min_prec)
    

    The imperative call to compute_expr will always return. The Haskell call may fail in which case the stuff following the call never happens.

    (2) You are really working against Parsec's strengths by trying to parse tokens one at a time in sequence. To see the "Parsec way" of generically parsing expressions with operators of various precedences and associativities, have a look at:

    Update

    I've posted a solution to http://lpaste.net/165651