semicolons

Sigbjorn Finne sof@galois.com
Mon, 15 Jul 2002 22:20:36 -0700


thanks, gist of the patch applied (+extended to also
cover 'alts' -- see actual commit for details.)

--sigbjorn

----- Original Message -----
From: "Ross Paterson" <ross@soi.city.ac.uk>
To: <hugs-bugs@haskell.org>
Sent: Monday, July 15, 2002 04:44
Subject: semicolons


> Haskell 98 allows things separated by semicolons to be empty, unlike
> earlier versions.  Hugs implements this for decls and ldecls, but not
> other contexts, e.g. it rejects stuff like
>
> module Foo where {import A;;x = 1;;y = 2;}
> do {;;;x <- [1];;;return x;;}
>
> The attached patch fixes this for impDecls, topDecls and stmts.
> That leaves alts, I think.
> -------------------------------------------------------------------
> Index: src/parser.y
> ===================================================================
> RCS file: /cvs/hugs98/src/parser.y,v
> retrieving revision 1.33
> diff -u -r1.33 parser.y
> --- src/parser.y 2002/06/14 14:41:10 1.33
> +++ src/parser.y 2002/07/15 11:21:15
> @@ -163,7 +163,8 @@
>     }
>   }
>     ;
> -modBody   : topDecls {$$ = $1;}
> +modBody   : /* empty */ {$$ = gc0(NIL);}
> +   | topDecls {$$ = gc1($1);}
>     | impDecls chase {$$ = gc2(NIL);}
>     | impDecls ';' chase topDecls {$$ = gc4($4);}
>     ;
> @@ -203,6 +204,7 @@
>  /*- Import
declarations: --------------------------------------------------*/
>
>  impDecls  : impDecls ';' impDecl {imps = cons($3,imps); $$=gc3(NIL);}
> +   | impDecls ';' {$$=gc2(NIL);}
>     | impDecl {imps = singleton($1); $$=gc1(NIL);}
>     ;
>  chase   : /* empty */ {if (chase(imps)) {
> @@ -260,13 +262,9 @@
>
>  /*- Top-level
declarations: -----------------------------------------------*/
>
> -topDecls  : /* empty */ {$$ = gc0(NIL);}
> -   | ';' {$$ = gc1(NIL);}
> -   | topDecls1 {$$ = $1;}
> -   | topDecls1 ';' {$$ = gc2($1);}
> -   ;
> -topDecls1 : topDecls1 ';' topDecl {$$ = gc2($1);}
> -   | topDecls1 ';' decl {$$ = gc3(cons($3,$1));}
> +topDecls  : topDecls ';' {$$ = gc2($1);}
> +   | topDecls ';' topDecl {$$ = gc2($1);}
> +   | topDecls ';' decl {$$ = gc3(cons($3,$1));}
>     | topDecl {$$ = gc0(NIL);}
>     | decl {$$ = gc1(cons($1,NIL));}
>     ;
> @@ -879,11 +877,9 @@
>     | guardAlt {$$ = gc1(cons($1,NIL));}
>     ;
>  guardAlt  : '|' exp0 ARROW exp {$$ = gc4(pair($3,pair($2,$4)));}
> -   ;
> -stmts   : stmts1 ';' {$$ = gc2($1);}
> -   | stmts1 {$$ = $1;}
>     ;
> -stmts1    : stmts1 ';' stmt {$$ = gc3(cons($3,$1));}
> +stmts   : stmts ';' stmt {$$ = gc3(cons($3,$1));}
> +   | stmts ';' {$$ = gc2($1);}
>     | stmt {$$ = gc1(cons($1,NIL));}
>     ;
>  stmt      : exp_err FROM exp {$$ = gc3(ap(FROMQUAL,pair($1,$3)));}
> _______________________________________________
> Hugs-Bugs mailing list
> Hugs-Bugs@haskell.org
> http://www.haskell.org/mailman/listinfo/hugs-bugs