happy icon indicating copy to clipboard operation
happy copied to clipboard

Monadic productions with threaded lexer produces ill-formed haskell code

Open gllghr opened this issue 11 years ago • 5 comments

I am using Alex along with Happy, and I have a rule that looks something like:

gdecl   :  typedef type ident ';'         {%^ mkTypDef $2 $3 }

The documentation says that this is the proper way to get a hold of the lookahead token when using a threaded lexer (%lexer). Running Happy on this produces a .hs file which GHC can't parse:

Parser.hs:301:47: parse error on input ‘tk’

Here is the function that contains the error:

happyReduce_6 = happyMonadReduce 4# 2# happyReduction_6
happyReduction_6 (happy_x_4 `HappyStk`
        happy_x_3 `HappyStk`
        happy_x_2 `HappyStk`
        happy_x_1 `HappyStk`
        happyRest) tk 
         = happyThen (case happyOut21 happy_x_2 of { happy_var_2 ->
        case happyOutTok happy_x_3 of { (LocTok _ (TokIdent happy_var_3)) ->
        ( mkTypDef happy_var_2 happy_var_3)}} tk        <-- Error Here
        ) (\r -> happyReturn (happyIn6 r))

Normal monadic productions, i.e. {% expn}, work fine. I am using Happy 1.19.4 and GHC 7.8.3. I can't post the entire Happy file, but if necessary I could probably put together a minimal working example.

gllghr avatar Oct 19 '14 17:10 gllghr

I could probably put together a minimal working example

Please do, and without using Alex, if possible.

int-index avatar Oct 19 '14 17:10 int-index

Ok, I have written a smallish example, though it does use Alex. If you don't mind waiting until I have a little more time to figure out how to write a threaded lexer, I will write one that doesn't use Alex. But for now anyway, Parser.y:

{
module Parser where

import Lexer

}

%name parser
%tokentype { Tok }
%error { error "Parse error" }
%monad { Alex }
%lexer { alexMonadScan >>= } { TokEOF }

%token
    '['     { TokOBrack }
    ']'     { TokCBrack }
    z       { TokZ }

%%

brack   : z                             { Z }
        | '[' brack brack brack ']'     {%^ monadActWLookahead $2 $3 $4 }  
-- If the rule above uses a normal monadic action like {% monadAct $2 $3 $4 },
-- everything works fine. 

{
data Brack = Z | Brack Brack Brack Brack deriving Show

parse input = runAlex input parser

-- Example monadic action
monadAct :: Brack -> Brack -> Brack -> Alex Brack
monadAct b1 b2 b3 = do
    c <- alexGetUserState
    alexSetUserState $ c { counter = (counter c) + 1 }
    return $ Brack b1 b2 b3

-- Example monadic action with lookahead
monadActWLookahead :: Brack -> Brack -> Brack -> Tok -> Alex Brack
monadActWLookahead b1 b2 b3 nextTok = do
    case nextTok of
      TokEOF -> alexSetUserState $ AlexUserState { counter = 0 }
      _ -> return ()
    return $ Brack b1 b2 b3
}

And a simple lexer, Lexer.x

{ module Lexer where }

%wrapper "monadUserState"

tokens :-
    "["     { mkTok TokOBrack }
    "]"     { mkTok TokCBrack }
    "z"     { mkTok TokZ }

{
data AlexUserState = AlexUserState { counter :: Int }

alexInitUserState = AlexUserState { counter = 0 }

data Tok = TokOBrack
         | TokCBrack
         | TokZ
         | TokEOF

alexEOF = return TokEOF

mkTok tok _ _ = return tok
}

To reproduce the error, invoke alex alex Lexer.x, invoke happy happy Parser.y -g -c, and then compile the generated .hs file ghc Parser.hs. This generates an error Parser.hs:80:70: parse error on input ‘tk’

This seems to occur only when monadic actions with lookahead which take multiple arguments are used in conjunction with the -c and -g compilation flags. If you use fewer arguments, i.e, {%^ func $1 }, it compiles correctly. That is, in ghci,

*Parser> parse "[zz[z[zzz]z]]"
Right (Brack Z Z (Brack Z (Brack Z Z Z) Z))
*Parser> 

Likewise if you run happy without any flags, everything works. If you use normal monadic actions, without lookahead, everything works.

gllghr avatar Oct 20 '14 18:10 gllghr

Any chance you could turn the example into a test case?

simonmar avatar Nov 17 '15 15:11 simonmar

Yeah, I'll work on that.

pgarrison avatar Nov 22 '15 20:11 pgarrison

I just ran into this exact bug (and the merged PR solves it for me). I see that the last release of Happy (1.19.5) on Hackage was over a year ago. When is 1.19.6 scheduled to be released?

harpocrates avatar Mar 08 '17 10:03 harpocrates

FTR, the fix (#54) was that we need to wrap parens around the case ... of {} in case ... of {} tk.

Let's just close this without a reproducer; at the moment it just steals bandwidth.

sgraf812 avatar Sep 13 '24 09:09 sgraf812

What an old thread -- I believe this PR was my first ever contribution to an open source project! Somehow my plan to make a test case got lost in the last 9 years 😂

pgarrison avatar Sep 13 '24 18:09 pgarrison