
Hi, What I'm trying to do is create a parser so as when I enter say 1+1 it will return Add(Val 1)(Val 1). A couple of questions do I have to state three basic parser. As in item, fail, synbol and then combine them with below. And by the way the one below seems to be all wrong. parse :: String -> expr parse expr = [(expr,string)] expr :: Parser value expr = do t <- term do char '+' e <- expr return Add (Val t)(Val e) +++ return t (+++) :: Parser a -> Parser a -> Parser a t +++ w inp = case t inp of [] -> w inp [(v,out)] -> [(v,out)] This is what I mean by item fail and symbol type Parser s a = [s] -> [(a,[s])] item [] = [] item (c:cs) = [(c,cs)] pFail :: Parser s a pFail = \cs -> [] pSymbol :: Eq s => s -> Parser s s pSymbol a (b:bs) |a == b = [(b,bs)] |otherwise = [] I know this is a bit of a mess, but could someone explain where I should start and if I should use any of the code above. Also to point out I want to write the complete parser without using prelude and other built in functions as I will be changing as I go. John

Hi John Are you working from the "Monadic Parser Combinators" paper by Graham Hutton and Erik Meijer? That was written for Gofer a predecessor to Haskell which is similar Haskell but has some slight differences - particularly in Haskell you would really want to make the Parser a newtype then use can make a Monad instance. Here are some of the bits from that paper with the newtype for Parser - unfortunately it adds some clutter. I think there should be a full version converted to Haskell if you do a web search. You will certainly need the sat and char parsers from the paper - I can post them later if you can't find them through a web search: newtype Parser s a = Parser { getParser :: [s] -> [(a,[s])] } result :: a -> Parser s a result v = Parser $ \inp -> [(v,inp)] bind :: Parser s a -> (a -> Parser s b) -> Parser s b p `bind` f = Parser $ \inp -> concat [ (getParser . f) v inp' | (v,inp') <- (getParser p) inp] instance Monad (Parser s) where return a = result a mf >>= k = mf `bind` k pFail :: Parser s a pFail = Parser $ \cs -> [] pSymbol :: Eq s => s -> Parser s s pSymbol a = Parser $ \inp -> case inp of (b:bs) | a == b -> [(b,bs)] _ -> [] (+++) :: Parser s a -> Parser s a -> Parser s a t +++ w = Parser $ \inp -> case (getParser t) inp of [] -> (getParser w) inp [(v,out)] -> [(v,out)]

Hi John Whilst this won't have the learning value of working through parser combinators yourself, here's code that uses Parsec 2 to do want you want. Its the code from page 12 of Daan Leijen's Parsec manual [1] except it builds a syntax tree of the expression rather than evaluates it. I modified it for a query on Haskell cafe today, but only posted it off list. Some formatting might get "lost in the mail" of course. [1] http://research.microsoft.com/en-us/um/people/daan/download/parsec/parsec.pd... Best wishes Stephen module ExprSyn where import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec.Expr 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" data Expr = Mul Expr Expr | Div Expr Expr | Add Expr Expr | Sub Expr Expr | Val Integer deriving (Eq,Show) expr :: Parser Expr expr = buildExpressionParser table factor <?> "expression" 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{ string s; return f}) assoc factor :: Parser Expr factor = do{ char '(' ; x <- expr ; char ')' ; return x } <|> number <?> "simple expression" number :: Parser Expr number = do{ ds <- many1 digit ; return (Val $ read ds) } > "number"
participants (2)
-
John Moore
-
Stephen Tetley