[Haskell-cafe] Generating AST using Parsec

Tom Davie tom.davie at gmail.com
Sun Dec 27 07:32:16 EST 2009


This isn't quite what you're asking for, but by using the applicative
interface to parsers, you need do little more than spell out what your AST
looks like:

import Control.Applicative
import Control.Applicative.Infix

data Equation = String :=: Expression
data Expression = EApp fun arg | EInt Int | EId String

parseEquation :: Parser Equation
parseEquation = parseIdentifier <^(:=:)^> parseExpression

parseExpression :: Parser Expression
parseExpression =
      (EApp <$> parseExpression <*> parseExpression)
  <|> (EInt <$> parseInt)
  <|> (EId <$> parseIdentifier)

parseIdentifier :: Parser String
parseIdentifier = parseLowercaseChar <^(:)^> parseString

etc

Bob

On Sun, Dec 27, 2009 at 10:18 AM, CK Kashyap <ck_kashyap at yahoo.com> 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
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091227/5954a70e/attachment.html


More information about the Haskell-Cafe mailing list