[Haskell-cafe] Type checking and locating token with Parsec
Stefan O'Rear
stefanor at cox.net
Tue Apr 10 19:44:13 EDT 2007
On Tue, Apr 10, 2007 at 02:09:03PM +0100, Joel Reymont wrote:
> Folks,
>
> Imagine a language where Num + Num yields a Num and Str + Num yields
> a Str but Num + Str should not be allowed.
>
> I implemented parsing for such a language in OCaml with a yacc-based
> parser without an additional type-checking pass, entirely within the
> yacc grammar. I tried to take such an approach with Parsec but hit
> the roadblock with buildExpressionParser since it returns the same
> type as the token parser given to it.
Just because you have a hammer doesn't mean you have a nail. I've
gotten along all this time never learning buildExpressionParser,
instead hand-coding my precedence parsers.
> Rather than have numerical expressions, string expressions, etc., as
> separate types, I simplified things down to a single expression type
> that holds my booleans, strings and numbers. I now need to implement
> type checking of my parsed AST.
Would something like this work for you:
data NumExpr = ...
data StrExpr = ...
data Expr = NumExpr NumExpr | StrExpr StrExpr
addExpr :: Expr -> Expr -> CharParser <st> Expr
addExpr (NumExpr n) (NumExpr m) = NumExpr (Add n m)
addExpr (StrExpr n) (NumExpr m) = StrExpr (Cat n (ToString m))
...
op3 ch fn a b = join $ liftM3 (\x _ y -> fn x y) a (char ch) b
...
exp0 = op3 '+' addExpr exp1 exp0 ...
It might also be good to modify chainl1/chainr1, with support for
possibly failing operations.
Remember - the provided abstractions have failed you, but you can
still define your own!
> The main issue is error reporting. I'm not sure where to get token
> location with Parsec and how to elegantly embed it in my AST.
>
> Has anyone implemented type checking on top of a Parsec-based parser?
>
> How did you locate your tokens?
There's haskell-src:
http://haskell.org/ghc/dist/current/docs/libraries/haskell-src/Language-Haskell-Syntax.html
And people wonder why I decided to abuse template haskell instead of
using the standard AST type. You do NOT want to go there. Not until
Oleg invents a way to make this stuff automatic, anyway.
Stefan
More information about the Haskell-Cafe
mailing list