[Haskell-cafe] Indentation problem using Happy
Amy de Buitléir
amy at nualeargais.ie
Fri Sep 30 12:27:36 CEST 2011
I'm trying to use Happy for the first time, and I'm having trouble with this
very simple example:
===== BEGIN: PolyParser.y =====
{
module Main where
import Char ( isAlpha, isDigit, isSpace )
}
%name calc
%tokentype { Token }
%error { parseError }
%token
id { TokenId $$ }
',' { TokenCOMMA }
wombat { TokenWombat $$ }
%%
Poly : id ',' wombat
{
parseError :: [Token] -> a
parseError _ = error "Parse error"
data Poly = Poly Int String deriving Show
data Token
= TokenId Int
| TokenCOMMA
| TokenWombat String deriving Show
lexer :: String -> [Token]
lexer [] = []
lexer (c:cs)
| isSpace c = lexer cs
| isAlpha c = lexVar (c:cs)
| isDigit c = lexNum (c:cs)
lexer (',':cs) = TokenCOMMA : lexer cs
lexNum cs = TokenInt (read num) : lexer rest
where (num,rest) = span isDigit cs
lexVar cs =
case span isAlpha cs of
(wombat,rest) -> TokenWombat wombat : lexer rest
(id,rest) -> TokenId id : lexer rest
main = getContents >>= print . calc . lexer
}
===== END: PolyParser.y =====
The resulting PolyParser.hs has an indentation problem (second-to-last line,
below), so it won't compile.
happyReduce_1 = happySpecReduce_3 4 happyReduction_1
happyReduction_1 _
_
_
= HappyAbsSyn4
(parseError :: [Token] -> a
parseError _ = error "Parse error"
Thank you in advance to anyone who can tell me where I've gone wrong.
More information about the Haskell-Cafe
mailing list