[Haskell-cafe] Re: Generating AST using Parsec
Maciej Piechotka
uzytkownik2 at gmail.com
Sun Dec 27 12:19:35 EST 2009
On Sun, 2009-12-27 at 02:18 -0800, CK Kashyap wrote:
> Hi All,
> I recently came across the paper titled "Monadic Parser Combinators" - After going through it a few times, I think I am beginning to understand monads.
> However, the parser developed in the paper does not generate an AST - I feel, I'd grasp the whole thing a lot better if I could go over a sample that generates an AST from a simple expression (or even a standard language such as C or Java) ... Can someone please point me to a sample that generates AST - preferably with the simple parser combinator given in the paper.
> Regards,
> Kashyap
It parses something like "x+y+z*pi"
import Control.Applicative
import Text.ParserCombinators.Parsec hiding ((<|>))
data Expr = Variable String
| Add Expr Expr
| Mul Expr Expr deriving (Show)
parseAST :: Parser Expr
parseAST = parseAdd
parseAdd :: Parser Expr
parseAdd = parseMul >>= \e -> ((string "+" >> (Add e <$> parseAdd)) <|>
(return e))
parseMul :: Parser Expr
parseMul = parseBase >>= \e -> ((string "*" >> (Mul e <$> parseMul)) <|>
(return e))
parseBase :: Parser Expr
parseBase = (string "(" *> parseAST <* string ")") <|>
(Variable <$> many1 letter)
Regards
More information about the Haskell-Cafe
mailing list