Marko Schuetz <[EMAIL PROTECTED]> writes:

> ghc-3.01 complains about a syntax error in the following cut down
> program:
> 
> > module Fehler where
> >
> > data Constr 
> >  = (:<-:) { expr :: LambdaCExpr, context :: ContextTerm }
> 
> kinetic% ghc Fehler.hs
> Fehler.hs:4:12: parse error on input: "{"

Yes, it looks like a bug.  The following patch should fix it:

*** hsparser.y  1998/01/21 17:37:09     1.16
--- hsparser.y  1998/02/26 10:47:34
***************
*** 755,761 ****
        |  OPAREN qconsym CPAREN batypes        { $$ = mkconstrpre($2,$4,hsplineno); }
  
  /* Con { op1 :: Int } */
!       |  gtycon OCURLY fields CCURLY          { $$ = mkconstrrec($1,$3,hsplineno); }
        ;
                /* 1 S/R conflict on OCURLY -> shift */
  
--- 755,762 ----
        |  OPAREN qconsym CPAREN batypes        { $$ = mkconstrpre($2,$4,hsplineno); }
  
  /* Con { op1 :: Int } */
!       | qtycon OCURLY fields CCURLY           { $$ = mkconstrrec($1,$3,hsplineno); }
!       | OPAREN qconsym CPAREN OCURLY fields CCURLY { $$ = 
mkconstrrec($2,$5,hsplineno); }
        ;
                /* 1 S/R conflict on OCURLY -> shift */
  

Cheers,
        Simon

-- 
Simon Marlow                                             [EMAIL PROTECTED]
University of Glasgow                       http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key

Reply via email to