[Haskell-cafe] alex + happy parser problem
Sean McLaughlin
seanmcl at gmail.com
Fri May 16 21:22:10 EDT 2008
Hi,
To learn alex and happy, I'm trying to write a parser for a simple
expression language.
When I wrote my own lexer and just used happy, it was fine.
When I used the basic wrapper of alex it was also fine. However, when
I use the posn wrapper
to get position information, I get a strange exception when the parse
error occurs at the end
of the input.
For example, parsing "1 + " yields "Internal Happy error" rather than
something like
"Parse error at line 1, column 5"
The lexer and parser are attached. Can anyone see what I'm doing wrong?
calling
parse "1+"
yields a "Internal Happy error"
instead of a parse error as I would expect.
Thanks,
Sean
------------------
-- Lexer
------------------
{
module ExprLexer (
Token(..),
AlexPosn(..),
alexScanTokens,
tokenPosn
) where
}
%wrapper "posn"
$digit = 0-9
tokens :-
$digit+ { (\p s -> Int p (read s)) }
[\+] { (\p s -> Sym p (head s)) }
{
data Token = Sym AlexPosn Char
| Int AlexPosn Int
deriving (Eq, Show)
tokenPosn (Sym p _) = p
tokenPosn (Int p _) = p
}
--------------------------
--- Parser
--------------------------
{
module ExprParser where
import ExprLexer (Token(..), alexScanTokens, tokenPosn, AlexPosn(..))
}
%name parseExp
%tokentype { Token }
%token
int { Int _ $$ }
'+' { Sym _ '+' }
%right '+'
%%
Exp : Exp '+' Exp { Add $1 $3 }
| int { Const $1 }
{
data Expr = Const Int
| Add Expr Expr
deriving Show
parse :: String -> Expr
parse = parseExp . alexScanTokens
happyError :: [Token] -> a
happyError tks = error ("Parse error at " ++ lcn ++ "\n")
where lcn = case tks of
[] -> "end of file"
tk:_ -> "line " ++ show l ++ ", column " ++ show c
where AlexPn _ l c = tokenPosn tk
}
More information about the Haskell-Cafe
mailing list