[Haskell-beginners] prefix instead of infix

Stephen Tetley stephen.tetley at gmail.com
Sun Jan 10 15:52:56 EST 2010


2010/1/10 John Moore <john.moore54 at gmail.com>:

>    Can anyone explain how to turn the code from infix to Prefix. I want to
> include a let statement below. I not sure of how prefix  works.
>

Hi John

For a let expression you want to extend the 'topmost' expr parser to
include a case for "let" rather than try to accommodate it in the
'table' parser.

Putting a extra 'in' keyword probably makes parsing simpler, i.e. "
let var = ... in ...", should you want to add other syntax later
(especially function application).

Once you start adding keywords you then start to be concerned about
whitespace and lexing - Parsec has a couple of modules for this -
Language and Token. In a nutshell where the parser previously used the
'string' parser it should use the 'symbol' parser as symbol consumes
trailing whitespace. The Token module is usually imported qualified
and you then redefine the functions you want to use with a particular
language definition (in this case emptyDef) - the bottom of the file
shows this idiom for the 'symbol', 'identifier' and 'integer' parsers.


Best wishes

Stephen
module ExprSyn where

import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Expr

-- new imports ...
import qualified Text.ParserCombinators.Parsec.Token as P
import Text.ParserCombinators.Parsec.Language (emptyDef)


runExpr :: String -> IO ()
runExpr str = case  runParser expr () "nofile"  str of
   Left err -> putStrLn "Error:" >> print err
   Right val -> print val

demo1 = runExpr "1+1"

demo2 = runExpr "let x = 5+3 in x+7"


type Variable = String

data Expr = Mul Expr Expr
         | Div Expr Expr
         | Add Expr Expr
         | Sub Expr Expr
         | Val Integer
         | Var String
         | LetIn Variable Expr Expr
 deriving (Eq,Show)

expr :: Parser Expr
expr = letInExpr
    <|> buildExpressionParser table factor
    <?> "expression"

letInExpr :: Parser Expr
letInExpr = do { symbol "let"
               ; var <- identifier
               ; symbol "="
               ; bind <- expr
               ; symbol "in"
               ; body <- expr
               ; return (LetIn var bind body)
               }


table :: [[Operator Char st Expr]]
table = [[op "*" Mul AssocLeft, op "/" Div AssocLeft]
        ,[op "+" Add AssocLeft, op "-" Sub AssocLeft]
        ]
 where
   op s f assoc
      = Infix (do{ symbol s; return f}) assoc

factor :: Parser Expr
factor = do{ char '('
          ; x <- expr
          ; char ')'
          ; return x
          }
     <|> number
     <|> variable
     <?> "simple expression"

number :: Parser Expr
number = do{ n <- integer
           ; return (Val $ fromIntegral n)
           }
      <?> "number"

variable :: Parser Expr
variable = do{ cs <- identifier
             ; return (Var cs)
             }
        <?> "number"


---
-- Bit of work to get 'symbol' and 'identifier' parsers working
-- both are useful as they consume trailing white space


-- Lexical analysis
baseLex           :: P.TokenParser st
baseLex           = P.makeTokenParser emptyDef

symbol            :: String -> CharParser st String
symbol            = P.symbol baseLex

identifier        :: CharParser st String
identifier        = P.identifier baseLex

integer           :: CharParser st Integer
integer           = P.integer baseLex


More information about the Beginners mailing list