[project @ 1998-04-07 07:51:07 by simonpj]
[ghc-hetmet.git] / ghc / compiler / parser / hsparser.y
1 /**************************************************************************
2 *   File:               hsparser.y                                        *
3 *                                                                         *
4 *                       Author:                 Maria M. Gutierrez        *
5 *                       Modified by:            Kevin Hammond             *
6 *                       Last date revised:      December 13 1991. KH.     *
7 *                       Modification:           Haskell 1.1 Syntax.       *
8 *                                                                         *
9 *                                                                         *
10 *   Description:  This file contains the LALR(1) grammar for Haskell.     *
11 *                                                                         *
12 *   Entry Point:  module                                                  *
13 *                                                                         *
14 *   Problems:     None known.                                             *
15 *                                                                         *
16 *                                                                         *
17 *                 LALR(1) Syntax for Haskell 1.2                          *
18 *                                                                         *
19 **************************************************************************/
20
21
22 %{
23 #ifdef HSP_DEBUG
24 # define YYDEBUG 1
25 #endif
26
27 #include <stdio.h>
28 #include <ctype.h>
29 #include <string.h>
30 #include "hspincl.h"
31 #include "constants.h"
32 #include "utils.h"
33
34 /**********************************************************************
35 *                                                                     *
36 *                                                                     *
37 *     Imported Variables and Functions                                *
38 *                                                                     *
39 *                                                                     *
40 **********************************************************************/
41
42 static BOOLEAN expect_ccurly = FALSE; /* Used to signal that a CCURLY could be inserted here */
43 extern BOOLEAN etags;
44
45 extern char *input_filename;
46 static char *the_module_name;
47 static maybe module_exports;
48
49 extern list Lnil;
50 extern list reverse_list();
51 extern tree root;
52
53 /* For FN, PREVPATT and SAMEFN macros */
54 extern qid      fns[];
55 extern BOOLEAN  samefn[];
56 extern tree     prevpatt[];
57 extern short    icontexts;
58
59 /* Line Numbers */
60 extern int hsplineno, hspcolno;
61 extern int modulelineno;
62 extern int startlineno;
63 extern int endlineno;
64
65 /**********************************************************************
66 *                                                                     *
67 *                                                                     *
68 *      Fixity and Precedence Declarations                             *
69 *                                                                     *
70 *                                                                     *
71 **********************************************************************/
72
73 static int Fixity = 0, Precedence = 0;
74
75 char *ineg PROTO((char *));
76
77 long    source_version = 0;
78
79 %}
80
81 %union {
82         tree utree;
83         list ulist;
84         ttype uttype;
85         constr uconstr;
86         binding ubinding;
87         pbinding upbinding;
88         entidt uentid;
89         id uid;
90         qid uqid;
91         literal uliteral;
92         maybe umaybe;
93         either ueither;
94         long ulong;
95         float ufloat;
96         char *ustring;
97         hstring uhstring;
98 }
99
100
101 /**********************************************************************
102 *                                                                     *
103 *                                                                     *
104 *     These are lexemes.                                              *
105 *                                                                     *
106 *                                                                     *
107 **********************************************************************/
108
109
110 %token  VARID           CONID           QVARID          QCONID
111         VARSYM          CONSYM          QVARSYM         QCONSYM
112
113 %token  INTEGER         FLOAT           CHAR            STRING
114         CHARPRIM        STRINGPRIM      INTPRIM         FLOATPRIM
115         DOUBLEPRIM      CLITLIT
116
117
118
119 /**********************************************************************
120 *                                                                     *
121 *                                                                     *
122 *      Special Symbols                                                *
123 *                                                                     *
124 *                                                                     *
125 **********************************************************************/
126
127 %token  OCURLY          CCURLY          VCCURLY 
128 %token  COMMA           SEMI            OBRACK          CBRACK
129 %token  WILDCARD        BQUOTE          OPAREN          CPAREN
130
131
132 /**********************************************************************
133 *                                                                     *
134 *                                                                     *
135 *     Reserved Operators                                              *
136 *                                                                     *
137 *                                                                     *
138 **********************************************************************/
139
140 %token  DOTDOT          DCOLON          EQUAL           LAMBDA          
141 %token  VBAR            RARROW          LARROW
142 %token  AT              LAZY            DARROW
143
144
145 /**********************************************************************
146 *                                                                     *
147 *                                                                     *
148 *     Reserved Identifiers                                            *
149 *                                                                     *
150 *                                                                     *
151 **********************************************************************/
152
153 %token  CASE            CLASS           DATA
154 %token  DEFAULT         DERIVING        DO
155 %token  ELSE            IF              IMPORT
156 %token  IN              INFIX           INFIXL
157 %token  INFIXR          INSTANCE        LET
158 %token  MODULE          NEWTYPE         OF
159 %token  THEN            TYPE            WHERE
160
161 %token  SCC
162 %token  CCALL           CCALL_GC        CASM            CASM_GC
163
164
165 /**********************************************************************
166 *                                                                     *
167 *                                                                     *
168 *     Special symbols/identifiers which need to be recognised         *
169 *                                                                     *
170 *                                                                     *
171 **********************************************************************/
172
173 %token  MINUS           BANG            PLUS
174 %token  AS              HIDING          QUALIFIED
175
176
177 /**********************************************************************
178 *                                                                     *
179 *                                                                     *
180 *     Special Symbols for the Lexer                                   *
181 *                                                                     *
182 *                                                                     *
183 **********************************************************************/
184
185 %token  INTERFACE_UPRAGMA SPECIALISE_UPRAGMA
186 %token  INLINE_UPRAGMA MAGIC_UNFOLDING_UPRAGMA
187 %token  END_UPRAGMA 
188 %token  SOURCE_UPRAGMA
189
190 /**********************************************************************
191 *                                                                     *
192 *                                                                     *
193 *     Precedences of the various tokens                               *
194 *                                                                     *
195 *                                                                     *
196 **********************************************************************/
197
198
199 %left   CASE    LET     IN
200         IF      ELSE    LAMBDA
201         SCC     CASM    CCALL   CASM_GC CCALL_GC
202
203 %left   VARSYM  CONSYM  QVARSYM QCONSYM
204         MINUS   BQUOTE  BANG    DARROW  PLUS
205
206 %left   DCOLON
207
208 %left   SEMI    COMMA
209
210 %left   OCURLY  OBRACK  OPAREN
211
212 %left   EQUAL
213
214 %right  RARROW
215
216 /**********************************************************************
217 *                                                                     *
218 *                                                                     *
219 *      Type Declarations                                              *
220 *                                                                     *
221 *                                                                     *
222 **********************************************************************/
223
224
225 %type <ulist>   caserest alts alt quals
226                 dorest stmts stmt
227                 rbinds rbinds1 rpats rpats1 list_exps list_rest
228                 qvarsk qvars_list
229                 constrs constr1 fields 
230                 types atypes batypes
231                 types_and_maybe_ids
232                 pats simple_context simple_context_list 
233                 export_list enames
234                 import_list inames
235                 impdecls maybeimpdecls impdecl
236                 maybefixes fixes fix ops
237                 dtyclses dtycls_list
238                 gdrhs gdpat valrhs
239                 lampats cexps gd
240
241 %type <umaybe>  maybeexports impspec deriving
242
243 %type <uliteral> lit_constant
244
245 %type <utree>   exp oexp dexp kexp fexp aexp rbind texps
246                 expL oexpL kexpL expLno oexpLno dexpLno kexpLno
247                 vallhs funlhs qual leftexp
248                 pat cpat bpat apat apatc conpat rpat
249                         patk bpatk apatck conpatk
250
251
252 %type <uid>     MINUS PLUS DARROW AS LAZY
253                 VARID CONID VARSYM CONSYM 
254                 var con varop conop op
255                 vark varid varsym varsym_nominus
256                 tycon modid ccallid
257
258 %type <uqid>    QVARID QCONID QVARSYM QCONSYM 
259                 qvarid qconid qvarsym qconsym
260                 qvar qcon qvarop qconop qop
261                 qvark qconk qtycon qtycls
262                 gcon gconk gtycon itycon qop1 qvarop1 
263                 ename iname 
264
265 %type <ubinding>  topdecl topdecls letdecls
266                   typed datad newtd classd instd defaultd
267                   decl decls valdef instdef instdefs
268                   maybe_where cbody rinst type_and_maybe_id
269
270 %type <upbinding> valrhs1 altrest
271
272 %type <uttype>    ctype sigtype sigarrowtype type atype bigatype btype
273                   bbtype batype bxtype wierd_atype
274                   simple_con_app simple_con_app1 tyvar contype inst_type
275
276 %type <uconstr>   constr constr_after_context field
277
278 %type <ustring>   FLOAT INTEGER INTPRIM
279                   FLOATPRIM DOUBLEPRIM CLITLIT
280
281 %type <uhstring>  STRING STRINGPRIM CHAR CHARPRIM
282
283 %type <uentid>    export import
284
285 %type <ulong>     commas importkey get_line_no
286
287 /**********************************************************************
288 *                                                                     *
289 *                                                                     *
290 *      Start Symbol for the Parser                                    *
291 *                                                                     *
292 *                                                                     *
293 **********************************************************************/
294
295 %start module
296
297 %%
298 module  :  modulekey modid maybeexports
299                 {
300                   modulelineno = startlineno;
301                   the_module_name = $2;
302                   module_exports = $3;
303                 }
304            WHERE body
305         |       { 
306                   modulelineno = 0;
307                   the_module_name = install_literal("Main");
308                   module_exports = mknothing();
309                 }
310            body
311         ;
312
313 body    :  ocurly { setstartlineno(); } interface_pragma orestm
314         |  vocurly interface_pragma vrestm
315         ;
316
317 interface_pragma : /* empty */
318         | INTERFACE_UPRAGMA INTEGER END_UPRAGMA SEMI
319                {
320                  source_version = atoi($2);
321                }
322         ;
323
324 orestm  :  maybeimpdecls maybefixes topdecls ccurly
325                {
326                  root = mkhmodule(the_module_name,$1,module_exports,
327                                   $2,$3,source_version,modulelineno);
328                }
329         |  impdecls ccurly
330                {
331                  root = mkhmodule(the_module_name,$1,module_exports,
332                                   Lnil,mknullbind(),source_version,modulelineno);
333                }
334
335 vrestm  :  maybeimpdecls maybefixes topdecls vccurly
336                {
337                  root = mkhmodule(the_module_name,$1,module_exports,
338                                   $2,$3,source_version,modulelineno);
339                }
340         |  impdecls vccurly
341                {
342                  root = mkhmodule(the_module_name,$1,module_exports,
343                                   Lnil,mknullbind(),source_version,modulelineno);
344                }
345
346 maybeexports :  /* empty */                     { $$ = mknothing(); }
347         |  OPAREN export_list CPAREN            { $$ = mkjust($2); }
348         |  OPAREN export_list COMMA CPAREN      { $$ = mkjust($2); }
349         ;
350
351 export_list:
352            export                               { $$ = lsing($1); }
353         |  export_list COMMA export             { $$ = lapp($1, $3); }
354         ;
355
356 export  :  qvar                                 { $$ = mkentid($1); }
357         |  gtycon                               { $$ = mkenttype($1); }
358         |  gtycon OPAREN DOTDOT CPAREN          { $$ = mkenttypeall($1); }
359         |  gtycon OPAREN CPAREN                 { $$ = mkenttypenamed($1,Lnil); }
360         |  gtycon OPAREN enames CPAREN          { $$ = mkenttypenamed($1,$3); }
361         |  MODULE modid                         { $$ = mkentmod($2); }
362         ;
363
364 enames  :  ename                                { $$ = lsing($1); }
365         |  enames COMMA ename                   { $$ = lapp($1,$3); }
366         ;
367 ename   :  qvar
368         |  qcon
369         ;
370
371
372 maybeimpdecls : /* empty */                     { $$ = Lnil; }
373         |  impdecls SEMI                        { $$ = $1; }
374         ;
375
376 impdecls:  impdecl                              { $$ = $1; }
377         |  impdecls SEMI impdecl                { $$ = lconc($1,$3); }
378         ;
379
380
381 impdecl :  importkey modid impspec
382                 { $$ = lsing(mkimport($2,0,mknothing(),$3,$1,startlineno)); }
383         |  importkey QUALIFIED modid impspec
384                 { $$ = lsing(mkimport($3,1,mknothing(),$4,$1,startlineno)); }
385         |  importkey QUALIFIED modid AS modid impspec
386                 { $$ = lsing(mkimport($3,1,mkjust($5),$6,$1,startlineno)); }
387         |  importkey modid AS modid impspec
388                 { $$ = lsing(mkimport($3,1,mkjust($4),$5,$1,startlineno)); }
389         ;
390
391 impspec :  /* empty */                            { $$ = mknothing(); }
392         |  OPAREN CPAREN                          { $$ = mkjust(mkleft(Lnil)); }
393         |  OPAREN import_list CPAREN              { $$ = mkjust(mkleft($2));   }
394         |  OPAREN import_list COMMA CPAREN        { $$ = mkjust(mkleft($2));   }
395         |  HIDING OPAREN import_list CPAREN       { $$ = mkjust(mkright($3));  }
396         |  HIDING OPAREN import_list COMMA CPAREN { $$ = mkjust(mkright($3));  }
397         ;
398
399 import_list:
400            import                               { $$ = lsing($1); }
401         |  import_list COMMA import             { $$ = lapp($1, $3); }
402         ;
403
404 import  :  var                                  { $$ = mkentid(mknoqual($1)); }
405         |  itycon                               { $$ = mkenttype($1); }
406         |  itycon OPAREN DOTDOT CPAREN          { $$ = mkenttypeall($1); }
407         |  itycon OPAREN CPAREN                 { $$ = mkenttypenamed($1,Lnil);}
408         |  itycon OPAREN inames CPAREN          { $$ = mkenttypenamed($1,$3); }
409         ;
410
411 itycon  :  tycon                                { $$ = mknoqual($1); }
412         |  OBRACK CBRACK                        { $$ = creategid(NILGID); }
413         |  OPAREN CPAREN                        { $$ = creategid(UNITGID); }         
414         |  OPAREN commas CPAREN                 { $$ = creategid($2); }
415         ;
416
417 inames  :  iname                                { $$ = lsing($1); }
418         |  inames COMMA iname                   { $$ = lapp($1,$3); }
419         ;
420 iname   :  var                                  { $$ = mknoqual($1); }
421         |  con                                  { $$ = mknoqual($1); }
422         ;
423
424 /**********************************************************************
425 *                                                                     *
426 *                                                                     *
427 *     Fixes and Decls etc                                             *
428 *                                                                     *
429 *                                                                     *
430 **********************************************************************/
431
432 maybefixes:  /* empty */                { $$ = Lnil; }
433         |  fixes SEMI                   { $$ = $1; }
434         ;
435
436 fixes   :  fix                          { $$ = $1; }
437         |  fixes SEMI fix               { $$ = lconc($1,$3); }
438         ;
439
440 fix     :  INFIXL INTEGER       { Precedence = checkfixity($2); Fixity = INFIXL; }
441            ops                  { $$ = $4; }
442         |  INFIXR INTEGER       { Precedence = checkfixity($2); Fixity = INFIXR; }
443            ops                  { $$ = $4; }
444         |  INFIX  INTEGER       { Precedence = checkfixity($2); Fixity = INFIX; }
445            ops                  { $$ = $4; }
446         |  INFIXL               { Fixity = INFIXL; Precedence = 9; }
447            ops                  { $$ = $3; }
448         |  INFIXR               { Fixity = INFIXR; Precedence = 9; }
449            ops                  { $$ = $3; }
450         |  INFIX                { Fixity = INFIX; Precedence = 9; }
451            ops                  { $$ = $3; }
452         ;
453
454 ops     :  op            { $$ = lsing(mkfixop(mknoqual($1),infixint(Fixity),Precedence,startlineno)); }
455         |  ops COMMA op  { $$ = lapp($1,mkfixop(mknoqual($3),infixint(Fixity),Precedence,startlineno)); }
456         ;
457
458 topdecls:  topdecl
459         |  topdecls SEMI topdecl
460                 {
461                   if($1 != NULL)
462                     if($3 != NULL)
463                       if(SAMEFN)
464                         {
465                           extendfn($1,$3);
466                           $$ = $1;
467                         }
468                       else
469                         $$ = mkabind($1,$3);
470                     else
471                       $$ = $1;
472                   else
473                     $$ = $3;
474                   SAMEFN = 0;
475                 }
476         ;
477
478 topdecl :  typed                                { $$ = $1; FN = NULL; SAMEFN = 0; }
479         |  datad                                { $$ = $1; FN = NULL; SAMEFN = 0; }
480         |  newtd                                { $$ = $1; FN = NULL; SAMEFN = 0; }
481         |  classd                               { $$ = $1; FN = NULL; SAMEFN = 0; }
482         |  instd                                { $$ = $1; FN = NULL; SAMEFN = 0; }
483         |  defaultd                             { $$ = $1; FN = NULL; SAMEFN = 0; }
484         |  decl                                 { $$ = $1; }
485         ;
486
487 typed   :  typekey simple_con_app EQUAL type            { $$ = mknbind($2,$4,startlineno); }
488         ;
489
490
491 datad   :  datakey simple_con_app EQUAL constrs deriving
492                 { $$ = mktbind(Lnil,$2,$4,$5,startlineno); }
493         |  datakey simple_context DARROW simple_con_app EQUAL constrs deriving
494                 { $$ = mktbind($2,$4,$6,$7,startlineno); }
495         ;
496
497 newtd   :  newtypekey simple_con_app EQUAL constr1 deriving
498                 { $$ = mkntbind(Lnil,$2,$4,$5,startlineno); }
499         |  newtypekey simple_context DARROW simple_con_app EQUAL constr1 deriving
500                 { $$ = mkntbind($2,$4,$6,$7,startlineno); }
501         ;
502
503 deriving: /* empty */                           { $$ = mknothing(); }
504         | DERIVING dtyclses                     { $$ = mkjust($2); }
505         ;
506
507 classd  :  classkey simple_context DARROW simple_con_app1 cbody
508                 { $$ = mkcbind($2,$4,$5,startlineno); }
509         |  classkey simple_con_app1 cbody                       
510                 { $$ = mkcbind(Lnil,$2,$3,startlineno); }
511         ;
512
513 cbody   :  /* empty */                          { $$ = mknullbind(); }
514         |  WHERE ocurly decls ccurly            { checkorder($3); $$ = $3; }
515         |  WHERE vocurly decls vccurly          { checkorder($3); $$ = $3; }
516         ;
517
518 instd   :  instkey inst_type rinst              { $$ = mkibind($2,$3,startlineno); }
519         ;
520
521 /* Compare ctype */
522 inst_type : type DARROW type                    { is_context_format( $3, 0 );   /* Check the instance head */
523                                                   $$ = mkcontext(type2context($1),$3); }
524           | type                                { is_context_format( $1, 0 );   /* Check the instance head */
525                                                   $$ = $1; }
526           ;
527
528
529 rinst   :  /* empty */                                          { $$ = mknullbind(); }
530         |  WHERE ocurly  instdefs ccurly                        { $$ = $3; }
531         |  WHERE vocurly instdefs vccurly                       { $$ = $3; }
532         ;
533
534 defaultd:  defaultkey OPAREN types CPAREN       { $$ = mkdbind($3,startlineno); }
535         |  defaultkey OPAREN CPAREN             { $$ = mkdbind(Lnil,startlineno); }
536         ;
537
538 decls   : decl
539         | decls SEMI decl
540                 {
541                   if(SAMEFN)
542                     {
543                       extendfn($1,$3);
544                       $$ = $1;
545                     }
546                   else
547                     $$ = mkabind($1,$3);
548                 }
549         ;
550
551 /*
552     Note: if there is an iclasop_pragma here, then we must be
553     doing a class-op in an interface -- unless the user is up
554     to real mischief (ugly, but likely to work).
555 */
556
557 decl    : qvarsk DCOLON sigtype
558                 { $$ = mksbind($1,$3,startlineno);
559                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
560                 }
561
562         /* User-specified pragmas come in as "signatures"...
563            They are similar in that they can appear anywhere in the module,
564            and have to be "joined up" with their related entity.
565
566            Have left out the case specialising to an overloaded type.
567            Let's get real, OK?  (WDP)
568         */
569         |  SPECIALISE_UPRAGMA qvark DCOLON types_and_maybe_ids END_UPRAGMA
570                 {
571                   $$ = mkvspec_uprag($2, $4, startlineno);
572                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
573                 }
574
575         |  SPECIALISE_UPRAGMA INSTANCE gtycon atype END_UPRAGMA
576                 {
577                   $$ = mkispec_uprag($3, $4, startlineno);
578                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
579                 }
580
581         |  SPECIALISE_UPRAGMA DATA gtycon atypes END_UPRAGMA
582                 {
583                   $$ = mkdspec_uprag($3, $4, startlineno);
584                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
585                 }
586
587         |  INLINE_UPRAGMA qvark END_UPRAGMA
588                 {
589                   $$ = mkinline_uprag($2, startlineno);
590                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
591                 }
592
593         |  MAGIC_UNFOLDING_UPRAGMA qvark vark END_UPRAGMA
594                 {
595                   $$ = mkmagicuf_uprag($2, $3, startlineno);
596                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
597                 }
598
599         /* end of user-specified pragmas */
600
601         |  valdef
602         |  /* empty */ { $$ = mknullbind(); PREVPATT = NULL; FN = NULL; SAMEFN = 0; }
603         ;
604
605 qvarsk  :  qvark COMMA qvars_list               { $$ = mklcons($1,$3); }
606         |  qvark                                { $$ = lsing($1); }
607         ;
608
609 qvars_list: qvar                                { $$ = lsing($1); }
610         |   qvars_list COMMA qvar               { $$ = lapp($1,$3); }
611         ;
612
613 types_and_maybe_ids :
614            type_and_maybe_id                            { $$ = lsing($1); }
615         |  types_and_maybe_ids COMMA type_and_maybe_id  { $$ = lapp($1,$3); }
616         ;
617
618 type_and_maybe_id :
619            type                                 { $$ = mkvspec_ty_and_id($1,mknothing()); }
620         |  type EQUAL qvark                     { $$ = mkvspec_ty_and_id($1,mkjust($3)); }
621
622
623 /**********************************************************************
624 *                                                                     *
625 *                                                                     *
626 *     Types etc                                                       *
627 *                                                                     *
628 *                                                                     *
629 **********************************************************************/
630
631 /*  "DCOLON context => type" vs "DCOLON type" is a problem,
632     because you can't distinguish between
633
634         foo :: (Baz a, Baz a)
635         bar :: (Baz a, Baz a) => [a] -> [a] -> [a]
636
637     with one token of lookahead.  The HACK is to have "DCOLON ttype"
638     [tuple type] in the first case, then check that it has the right
639     form C a, or (C1 a, C2 b, ... Cn z) and convert it into a
640     context.  Blaach!
641 */
642
643 /* A sigtype is a rank 2 type; it can have for-alls as function args:
644         f :: All a => (All b => ...) -> Int
645 */
646 sigtype : type DARROW sigarrowtype              { $$ = mkcontext(type2context($1),$3); }
647         | sigarrowtype 
648         ;
649
650 sigarrowtype : bigatype RARROW sigarrowtype     { $$ = mktfun($1,$3); }
651              | btype RARROW sigarrowtype        { $$ = mktfun($1,$3); }
652              | btype
653              ;
654
655 /* A "big" atype can be a forall-type in brackets.  */
656 bigatype: OPAREN type DARROW type CPAREN        { $$ = mkcontext(type2context($2),$4); }
657         ;
658
659         /* 1 S/R conflict at DARROW -> shift */
660 ctype   : type DARROW type                      { $$ = mkcontext(type2context($1),$3); }
661         | type
662         ;
663
664         /* 1 S/R conflict at RARROW -> shift */
665 type    :  btype RARROW type                    { $$ = mktfun($1,$3); }
666         |  btype                                { $$ = $1; }
667         ;
668
669 btype   :  btype atype                          { $$ = mktapp($1,$2); }
670         |  atype                                { $$ = $1; }
671         ;
672
673 atype   :  gtycon                               { $$ = mktname($1); }
674         |  tyvar                                { $$ = $1; }
675         |  OPAREN type COMMA types CPAREN       { $$ = mkttuple(mklcons($2,$4)); }
676         |  OBRACK type CBRACK                   { $$ = mktllist($2); }
677         |  OPAREN type CPAREN                   { $$ = $2; }
678         ;
679
680 gtycon  :  qtycon
681         |  OPAREN RARROW CPAREN                 { $$ = creategid(ARROWGID); }
682         |  OBRACK CBRACK                        { $$ = creategid(NILGID); }         
683         |  OPAREN CPAREN                        { $$ = creategid(UNITGID); }         
684         |  OPAREN commas CPAREN                 { $$ = creategid($2); }
685         ;
686
687 atypes  :  atype                                { $$ = lsing($1); }
688         |  atypes atype                         { $$ = lapp($1,$2); }
689         ;
690
691 types   :  type                                 { $$ = lsing($1); }
692         |  types COMMA type                     { $$ = lapp($1,$3); }
693         ;
694
695 commas  : COMMA                                 { $$ = 1; }
696         | commas COMMA                          { $$ = $1 + 1; }
697         ;
698
699 /**********************************************************************
700 *                                                                     *
701 *                                                                     *
702 *     Declaration stuff                                               *
703 *                                                                     *
704 *                                                                     *
705 **********************************************************************/
706
707 /* C a b c, where a,b,c are type variables */
708 /* C can be a class or tycon */
709 simple_con_app: gtycon                          { $$ = mktname($1); }
710         |  simple_con_app1                      { $$ = $1; }
711         ;
712    
713 simple_con_app1:  gtycon tyvar                  { $$ = mktapp(mktname($1),$2); }
714         |  simple_con_app tyvar                 { $$ = mktapp($1, $2); } 
715         ;
716
717 simple_context  :  OPAREN simple_context_list CPAREN            { $$ = $2; }
718         |  simple_con_app1                                      { $$ = lsing($1); }
719         ;
720
721 simple_context_list:  simple_con_app1                           { $$ = lsing($1); }
722         |  simple_context_list COMMA simple_con_app1            { $$ = lapp($1,$3); }
723         ;
724
725 constrs :  constr                               { $$ = lsing($1); }
726         |  constrs VBAR constr                  { $$ = lapp($1,$3); }
727         ;
728
729 constr  :  constr_after_context
730         |  type DARROW constr_after_context     { $$ = mkconstrcxt ( type2context($1), $3 ); }
731         ;
732
733 constr_after_context :
734
735         /* We have to parse the constructor application as a *type*, else we get
736            into terrible ambiguity problems.  Consider the difference between
737
738                 data T = S Int Int Int `R` Int
739            and
740                 data T = S Int Int Int
741         
742            It isn't till we get to the operator that we discover that the "S" is
743            part of a type in the first, but part of a constructor application in the
744            second.
745         */
746
747 /* Con !Int (Tree a) */
748            contype                              { qid tyc; list tys;
749                                                   splittyconapp($1, &tyc, &tys);
750                                                   $$ = mkconstrpre(tyc,tys,hsplineno); }
751
752 /* !Int `Con` Tree a */
753         |  bbtype qconop bbtype                 { $$ = mkconstrinf($1,$2,$3,hsplineno); }
754
755 /* (::) (Tree a) Int */
756         |  OPAREN qconsym CPAREN batypes        { $$ = mkconstrpre($2,$4,hsplineno); }
757
758 /* Con { op1 :: Int } */
759         | qtycon OCURLY fields CCURLY           { $$ = mkconstrrec($1,$3,hsplineno); }
760         | OPAREN qconsym CPAREN OCURLY fields CCURLY { $$ = mkconstrrec($2,$5,hsplineno); }
761         ;
762                 /* 1 S/R conflict on OCURLY -> shift */
763
764
765 /* contype has to reduce to a btype unless there are !'s, so that
766    we don't get reduce/reduce conflicts with the second production of constr.
767    But as soon as we see a ! we must switch to using bxtype. */
768
769 contype : btype                                 { $$ = $1; }
770         | bxtype                                { $$ = $1; }
771         ;
772
773 /* S !Int Bool; at least one ! */
774 bxtype  : btype wierd_atype                     { $$ = mktapp($1, $2); }
775         | bxtype batype                         { $$ = mktapp($1, $2); }
776         ;
777
778 bbtype  :  btype                                { $$ = $1; }
779         |  wierd_atype                          { $$ = $1; }
780         ;
781
782 batype  :  atype                                { $$ = $1; }
783         |  wierd_atype                          { $$ = $1; }
784         ;
785
786 /* A wierd atype is one that isn't a regular atype;
787    it starts with a "!", or with a forall. */
788 wierd_atype : BANG bigatype                     { $$ = mktbang( $2 ); }
789             | BANG atype                        { $$ = mktbang( $2 ); }
790             | bigatype 
791             ;
792
793 batypes :                                       { $$ = Lnil; }
794         |  batypes batype                       { $$ = lapp($1,$2); }
795         ;
796
797
798 fields  : field                                 { $$ = lsing($1); }
799         | fields COMMA field                    { $$ = lapp($1,$3); }
800         ;
801
802 field   :  qvars_list DCOLON ctype              { $$ = mkfield($1,$3); }
803         |  qvars_list DCOLON BANG atype         { $$ = mkfield($1,mktbang($4)); }
804         |  qvars_list DCOLON BANG bigatype      { $$ = mkfield($1,mktbang($4)); }
805         ; 
806
807 constr1 :  gtycon atype                         { $$ = lsing(mkconstrnew($1,$2,hsplineno)); }
808         ;
809
810
811 dtyclses:  OPAREN dtycls_list CPAREN            { $$ = $2; }
812         |  OPAREN CPAREN                        { $$ = Lnil; }
813         |  qtycls                               { $$ = lsing($1); }
814         ;
815
816 dtycls_list:  qtycls                            { $$ = lsing($1); }
817         |  dtycls_list COMMA qtycls             { $$ = lapp($1,$3); }
818         ;
819
820 instdefs : /* empty */                          { $$ = mknullbind(); }
821          | instdef                              { $$ = $1; }
822          | instdefs SEMI instdef
823                 {
824                   if(SAMEFN)
825                     {
826                       extendfn($1,$3);
827                       $$ = $1;
828                     }
829                   else
830                     $$ = mkabind($1,$3);
831                 }
832         ;
833
834 /* instdef: same as valdef, except certain user-pragmas may appear */
835 instdef :
836            SPECIALISE_UPRAGMA qvark DCOLON types_and_maybe_ids END_UPRAGMA
837                 {
838                   $$ = mkvspec_uprag($2, $4, startlineno);
839                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
840                 }
841
842         |  INLINE_UPRAGMA qvark END_UPRAGMA
843                 {
844                   $$ = mkinline_uprag($2, startlineno);
845                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
846                 }
847
848         |  MAGIC_UNFOLDING_UPRAGMA qvark vark END_UPRAGMA
849                 {
850                   $$ = mkmagicuf_uprag($2, $3, startlineno);
851                   PREVPATT = NULL; FN = NULL; SAMEFN = 0;
852                 }
853
854         |  valdef
855         ;
856
857
858 valdef  :  vallhs
859
860                 {
861                   tree fn = function($1);
862                   PREVPATT = $1;
863
864                   if(ttree(fn) == ident)
865                     {
866                       qid fun_id = gident((struct Sident *) fn);
867                       checksamefn(fun_id);
868                       FN = fun_id;
869                     }
870
871                   else if (ttree(fn) == infixap)
872                     {
873                       qid fun_id = ginffun((struct Sinfixap *) fn); 
874                       checksamefn(fun_id);
875                       FN = fun_id;
876                     }
877
878                   else if(etags)
879 #if 1/*etags*/
880                     printf("%u\n",startlineno);
881 #else
882                     fprintf(stderr,"%u\tvaldef\n",startlineno);
883 #endif
884                 }       
885
886            get_line_no
887            valrhs
888                 {
889                   if ( lhs_is_patt($1) )
890                     {
891                       $$ = mkpbind($4, $3);
892                       FN = NULL;
893                       SAMEFN = 0;
894                     }
895                   else
896                     $$ = mkfbind($4, $3);
897
898                   PREVPATT = NULL;
899                 }
900         ;
901
902 get_line_no :                                   { $$ = startlineno; }
903             ;
904
905 vallhs  : patk                                  { $$ = $1; }
906         | patk qvarop pat                       { $$ = mkinfixap($2,$1,$3); }
907         | funlhs                                { $$ = $1; }
908         ;
909
910 funlhs  :  qvark apat                           { $$ = mkap(mkident($1),$2); }
911         |  funlhs apat                          { $$ = mkap($1,$2); }
912         ;
913
914
915 valrhs  :  valrhs1 maybe_where                  { $$ = lsing(createpat($1, $2)); }
916         ;
917
918 valrhs1 :  gdrhs                                { $$ = mkpguards($1); }
919         |  EQUAL exp                            { $$ = mkpnoguards($2); }
920         ;
921
922 gdrhs   :  gd EQUAL exp                         { $$ = lsing(mkpgdexp($1,$3)); }
923         |  gd EQUAL exp gdrhs                   { $$ = mklcons(mkpgdexp($1,$3),$4); }
924         ;
925
926 maybe_where:
927            WHERE ocurly decls ccurly            { $$ = $3; }
928         |  WHERE vocurly decls vccurly          { $$ = $3; }
929            /* A where containing no decls is OK */
930         |  WHERE SEMI                           { $$ = mknullbind(); }
931         |  /* empty */                          { $$ = mknullbind(); }
932         ;
933
934 gd      :  VBAR quals                           { $$ = $2; }
935         ;
936
937
938 /**********************************************************************
939 *                                                                     *
940 *                                                                     *
941 *     Expressions                                                     *
942 *                                                                     *
943 *                                                                     *
944 **********************************************************************/
945
946 exp     :  oexp DCOLON ctype                    { $$ = mkrestr($1,$3); }
947         |  oexp
948         ;
949
950 /*
951   Operators must be left-associative at the same precedence for
952   precedence parsing to work.
953 */
954         /* 8 S/R conflicts on qop -> shift */
955 oexp    :  oexp qop oexp %prec MINUS            { $$ = mkinfixap($2,$1,$3); }
956         |  dexp
957         ;
958
959 /*
960   This comes here because of the funny precedence rules concerning
961   prefix minus.
962 */
963 dexp    :  MINUS kexp                           { $$ = mknegate($2); }
964         |  kexp
965         ;
966
967 /*
968   We need to factor out a leading let expression so we can set
969   inpat=TRUE when parsing (non let) expressions inside stmts and quals
970 */
971 expLno  : oexpLno DCOLON ctype                  { $$ = mkrestr($1,$3); }
972         | oexpLno
973         ;
974 oexpLno :  oexpLno qop oexp %prec MINUS         { $$ = mkinfixap($2,$1,$3); }
975         |  dexpLno
976         ;
977 dexpLno :  MINUS kexp                           { $$ = mknegate($2); }
978         |  kexpLno
979         ;
980
981 expL    :  oexpL DCOLON ctype                   { $$ = mkrestr($1,$3); }
982         |  oexpL
983         ;
984 oexpL   :  oexpL qop oexp %prec MINUS           { $$ = mkinfixap($2,$1,$3); }
985         |  kexpL
986         ;
987
988 /*
989   let/if/lambda/case have higher precedence than infix operators.
990 */
991
992 kexp    :  kexpL
993         |  kexpLno
994         ;
995
996 /* kexpL = a let expression */
997 kexpL   :  letdecls IN exp                      { $$ = mklet($1,$3); }
998         ;
999
1000 /* kexpLno = any other expression more tightly binding than operator application */
1001 kexpLno :  LAMBDA
1002                 { hsincindent();        /* push new context for FN = NULL;        */
1003                   FN = NULL;            /* not actually concerned about indenting */
1004                   $<ulong>$ = hsplineno; /* remember current line number           */
1005                 }
1006            lampats
1007                 { hsendindent();
1008                 }
1009            RARROW exp                   /* lambda abstraction */
1010                 {
1011                   $$ = mklambda($3, $6, $<ulong>2);
1012                 }
1013
1014         /* If Expression */
1015         |  IF {$<ulong>$ = hsplineno;}
1016            exp THEN exp ELSE exp                { $$ = mkife($3,$5,$7,$<ulong>2); }
1017
1018         /* Case Expression */
1019         |  CASE {$<ulong>$ = hsplineno;}
1020            exp OF caserest                      { $$ = mkcasee($3,$5,$<ulong>2); }
1021
1022         /* Do Expression */
1023         |  DO {$<ulong>$ = hsplineno;}
1024            dorest                               { $$ = mkdoe($3,$<ulong>2); }
1025
1026         /* CCALL/CASM Expression */
1027         |  CCALL ccallid cexps                  { $$ = mkccall($2,install_literal("n"),$3); }
1028         |  CCALL ccallid                        { $$ = mkccall($2,install_literal("n"),Lnil); }
1029         |  CCALL_GC ccallid cexps               { $$ = mkccall($2,install_literal("p"),$3); }
1030         |  CCALL_GC ccallid                     { $$ = mkccall($2,install_literal("p"),Lnil); }
1031         |  CASM CLITLIT cexps                   { $$ = mkccall($2,install_literal("N"),$3); }
1032         |  CASM CLITLIT                         { $$ = mkccall($2,install_literal("N"),Lnil); }
1033         |  CASM_GC CLITLIT cexps                { $$ = mkccall($2,install_literal("P"),$3); }
1034         |  CASM_GC CLITLIT                      { $$ = mkccall($2,install_literal("P"),Lnil); }
1035
1036         /* SCC Expression */
1037         |  SCC STRING exp
1038                 { if (ignoreSCC) {
1039                     if (warnSCC) {
1040                         fprintf(stderr,
1041                                 "\"%s\":%d: _scc_ (`set [profiling] cost centre') ignored\n",
1042                                 input_filename, hsplineno);
1043                     }
1044                     $$ = mkpar($3);     /* Note the mkpar().  If we don't have it, then
1045                                            (x >> _scc_ y >> z) parses as (x >> (y >> z)),
1046                                            right associated.  But the precedence reorganiser expects
1047                                            the parser to *left* associate all operators unless there
1048                                            are explicit parens.  The _scc_ acts like an explicit paren,
1049                                            so if we omit it we'd better add explicit parens instead. */
1050                   } else {
1051                     $$ = mkscc($2, $3);
1052                   }
1053                 }
1054         |  fexp
1055         ;
1056
1057 fexp    :  fexp aexp                            { $$ = mkap($1,$2); }
1058         |  aexp
1059         ;
1060
1061         /* simple expressions */
1062 aexp    :  qvar                                 { $$ = mkident($1); }
1063         |  gcon                                 { $$ = mkident($1); }
1064         |  lit_constant                         { $$ = mklit($1); }
1065         |  OPAREN exp CPAREN                    { $$ = mkpar($2); }         /* mkpar: stop infix parsing at ()'s */
1066         |  qcon OCURLY rbinds CCURLY            { $$ = mkrecord($1,$3); }   /* 1 S/R conflict on OCURLY -> shift */
1067         |  OBRACK list_exps CBRACK              { $$ = mkllist($2); }
1068         |  OPAREN exp COMMA texps CPAREN        { if (ttree($4) == tuple)
1069                                                      $$ = mktuple(mklcons($2, gtuplelist((struct Stuple *) $4)));
1070                                                   else
1071                                                      $$ = mktuple(ldub($2, $4)); }
1072
1073         /* only in expressions ... */
1074         |  aexp OCURLY rbinds1 CCURLY           { $$ = mkrupdate($1,$3); }
1075         |  OBRACK exp VBAR quals CBRACK         { $$ = mkcomprh($2,$4); }
1076         |  OBRACK exp COMMA exp DOTDOT exp CBRACK {$$= mkeenum($2,mkjust($4),mkjust($6)); }
1077         |  OBRACK exp COMMA exp DOTDOT CBRACK   { $$ = mkeenum($2,mkjust($4),mknothing()); }
1078         |  OBRACK exp DOTDOT exp CBRACK         { $$ = mkeenum($2,mknothing(),mkjust($4)); }
1079         |  OBRACK exp DOTDOT CBRACK             { $$ = mkeenum($2,mknothing(),mknothing()); }
1080         |  OPAREN oexp qop CPAREN               { $$ = mklsection($2,$3); }
1081         |  OPAREN qop1 oexp CPAREN              { $$ = mkrsection($2,$3); }
1082
1083         /* only in patterns ... */
1084         /* these add 2 S/R conflict with with  aexp . OCURLY rbinds CCURLY */
1085         |  qvar AT aexp                         { $$ = mkas($1,$3); }
1086         |  LAZY aexp                            { $$ = mklazyp($2); }
1087         |  WILDCARD                             { $$ = mkwildp();   }
1088         ;
1089
1090         /* ccall arguments */
1091 cexps   :  cexps aexp                           { $$ = lapp($1,$2); }
1092         |  aexp                                 { $$ = lsing($1); }
1093         ;
1094
1095 caserest:  ocurly alts ccurly                   { $$ = $2; }
1096         |  vocurly alts vccurly                 { $$ = $2; }
1097
1098 dorest  :  ocurly stmts ccurly                  { checkdostmts($2); $$ = $2; }
1099         |  vocurly stmts vccurly                { checkdostmts($2); $$ = $2; }
1100         ;
1101
1102 rbinds  :  /* empty */                          { $$ = Lnil; }
1103         |  rbinds1
1104         ;
1105
1106 rbinds1 :  rbind                                { $$ = lsing($1); }
1107         |  rbinds1 COMMA rbind                  { $$ = lapp($1,$3); }
1108         ;
1109
1110 rbind   :  qvar                                 { $$ = mkrbind($1,mknothing()); }
1111         |  qvar EQUAL exp                       { $$ = mkrbind($1,mkjust($3)); }
1112         ;
1113
1114 texps   :  exp  { $$ = mkpar($1); }     /* mkpar: so we don't flatten last element in tuple */
1115         |  exp COMMA texps
1116                 { if (ttree($3) == tuple)
1117                     $$ = mktuple(mklcons($1, gtuplelist((struct Stuple *) $3)));
1118                   else if (ttree($3) == par)
1119                     $$ = mktuple(ldub($1, gpare((struct Spar *) $3)));
1120                   else
1121                     hsperror("hsparser:texps: panic");
1122                 }
1123         /* right recursion? WDP */
1124         ;
1125
1126 list_exps :
1127            exp                                  { $$ = lsing($1); }
1128         |  exp COMMA exp                        { $$ = mklcons( $1, lsing($3) ); }
1129         |  exp COMMA exp COMMA list_rest        { $$ = mklcons( $1, mklcons( $3, reverse_list( $5 ))); }
1130         ;
1131
1132 /* Use left recusion for list_rest, because we sometimes get programs with
1133    very long explicit lists. */
1134 list_rest :     exp                             { $$ = lsing($1); }
1135           | list_rest COMMA exp                 { $$ = mklcons( $3, $1 ); }
1136           ;
1137
1138 /* 
1139            exp                                  { $$ = lsing($1); }
1140         |  exp COMMA list_exps          { $$ = mklcons($1, $3); }
1141 */
1142         /* right recursion? (WDP)
1143
1144            It has to be this way, though, otherwise you
1145            may do the wrong thing to distinguish between...
1146
1147            [ e1 , e2 .. ]       -- an enumeration ...
1148            [ e1 , e2 , e3 ]     -- a list
1149
1150            (In fact, if you change the grammar and throw yacc/bison
1151            at it, it *will* do the wrong thing [WDP 94/06])
1152         */
1153
1154 letdecls:  LET ocurly decls ccurly              { $$ = $3; }
1155         |  LET vocurly decls vccurly            { $$ = $3; }
1156         ;
1157
1158 quals   :  qual                                 { $$ = lsing($1); }
1159         |  quals COMMA qual                     { $$ = lapp($1,$3); }
1160         ;
1161
1162 qual    :  letdecls                             { $$ = mkseqlet($1); }
1163         |  expL                                 { $$ = $1; }
1164         |  expLno leftexp
1165                 { if ($2 == NULL) {
1166                       expORpat(LEGIT_EXPR,$1);
1167                       $$ = mkguard($1);
1168                   } else {
1169                       expORpat(LEGIT_PATT,$1);
1170                       $$ = mkqual($1,$2);
1171                   }
1172                 }
1173         ;
1174
1175 alts    :  alt                                  { $$ = $1; }
1176         |  alts SEMI alt                        { $$ = lconc($1,$3); }
1177         ;
1178
1179 alt     :  pat { PREVPATT = $1; } altrest       { expORpat(LEGIT_PATT,$1); $$ = lsing($3); PREVPATT = NULL; }
1180         |  /* empty */                          { $$ = Lnil; }
1181         ;
1182
1183 altrest :  gdpat maybe_where                    { $$ = createpat(mkpguards($1), $2); }
1184         |  RARROW exp maybe_where               { $$ = createpat(mkpnoguards($2),$3); }
1185         ;
1186
1187 gdpat   :  gd RARROW exp                        { $$ = lsing(mkpgdexp($1,$3)); }
1188         |  gd RARROW exp gdpat                  { $$ = mklcons(mkpgdexp($1,$3),$4);  }
1189         ;
1190
1191 stmts   :  stmt                                 { $$ = $1; }
1192         |  stmts SEMI stmt                      { $$ = lconc($1,$3); }
1193         ;
1194
1195 stmt    : /* empty */                           { $$ = Lnil; } 
1196         | letdecls                              { $$ = lsing(mkseqlet($1)); }
1197         |  expL                                 { $$ = lsing(mkdoexp($1,hsplineno)); }
1198         |  expLno leftexp
1199                 { if ($2 == NULL) {
1200                       expORpat(LEGIT_EXPR,$1);
1201                       $$ = lsing(mkdoexp($1,endlineno));
1202                   } else {
1203                       expORpat(LEGIT_PATT,$1);
1204                       $$ = lsing(mkdobind($1,$2,endlineno));
1205                   }
1206                 }
1207         ;
1208
1209 leftexp :  LARROW exp                           { $$ = $2; }
1210         |  /* empty */                          { $$ = NULL; }
1211         ;
1212
1213 /**********************************************************************
1214 *                                                                     *
1215 *                                                                     *
1216 *     Patterns                                                        *
1217 *                                                                     *
1218 *                                                                     *
1219 **********************************************************************/
1220
1221 pat     :  qvar PLUS INTEGER                    { $$ = mkplusp($1, mkinteger($3)); }
1222         |  cpat
1223         ;
1224
1225 cpat    :  cpat qconop bpat                     { $$ = mkinfixap($2,$1,$3); }
1226         |  bpat
1227         ;
1228
1229 bpat    :  apatc
1230         |  conpat
1231         |  qcon OCURLY rpats CCURLY             { $$ = mkrecord($1,$3); }
1232         |  MINUS INTEGER                        { $$ = mknegate(mklit(mkinteger($2))); }
1233         |  MINUS FLOAT                          { $$ = mknegate(mklit(mkfloatr($2))); }
1234         ;
1235
1236 conpat  :  gcon                                 { $$ = mkident($1); }
1237         |  conpat apat                          { $$ = mkap($1,$2); }
1238         ;
1239
1240 apat    :  gcon                                 { $$ = mkident($1); }
1241         |  qcon OCURLY rpats CCURLY             { $$ = mkrecord($1,$3); }
1242         |  apatc
1243         ;
1244
1245 apatc   :  qvar                                 { $$ = mkident($1); }
1246         |  qvar AT apat                         { $$ = mkas($1,$3); }
1247         |  lit_constant                         { $$ = mklit($1); }
1248         |  WILDCARD                             { $$ = mkwildp(); }
1249         |  OPAREN pat CPAREN                    { $$ = mkpar($2); }
1250         |  OPAREN pat COMMA pats CPAREN         { $$ = mktuple(mklcons($2,$4)); }
1251         |  OBRACK pats CBRACK                   { $$ = mkllist($2); }
1252         |  LAZY apat                            { $$ = mklazyp($2); }
1253         ;
1254
1255 lit_constant:
1256            INTEGER                              { $$ = mkinteger($1); }
1257         |  FLOAT                                { $$ = mkfloatr($1); }
1258         |  CHAR                                 { $$ = mkcharr($1); }
1259         |  STRING                               { $$ = mkstring($1); }
1260         |  CHARPRIM                             { $$ = mkcharprim($1); }
1261         |  STRINGPRIM                           { $$ = mkstringprim($1); }
1262         |  INTPRIM                              { $$ = mkintprim($1); }
1263         |  FLOATPRIM                            { $$ = mkfloatprim($1); }
1264         |  DOUBLEPRIM                           { $$ = mkdoubleprim($1); }
1265         |  CLITLIT /* yurble yurble */          { $$ = mkclitlit($1); }
1266         ;
1267
1268 lampats :  apat lampats                         { $$ = mklcons($1,$2); }
1269         |  apat                                 { $$ = lsing($1); }
1270         /* right recursion? (WDP) */
1271         ;
1272
1273 pats    :  pat COMMA pats                       { $$ = mklcons($1, $3); }
1274         |  pat                                  { $$ = lsing($1); }
1275         /* right recursion? (WDP) */
1276         ;
1277
1278 rpats   : /* empty */                           { $$ = Lnil; }
1279         | rpats1
1280         ;
1281
1282 rpats1  : rpat                                  { $$ = lsing($1); }
1283         | rpats1 COMMA rpat                     { $$ = lapp($1,$3); }
1284         ;
1285
1286 rpat    :  qvar                                 { $$ = mkrbind($1,mknothing()); }
1287         |  qvar EQUAL pat                       { $$ = mkrbind($1,mkjust($3)); }
1288         ;
1289
1290
1291 patk    :  patk qconop bpat                     { $$ = mkinfixap($2,$1,$3); }
1292         |  bpatk
1293         ;
1294
1295 bpatk   :  apatck
1296         |  conpatk
1297         |  qconk OCURLY rpats CCURLY            { $$ = mkrecord($1,$3); }
1298         |  minuskey INTEGER                     { $$ = mknegate(mklit(mkinteger($2))); }
1299         |  minuskey FLOAT                       { $$ = mknegate(mklit(mkfloatr($2))); }
1300         ;
1301
1302 conpatk :  gconk                                { $$ = mkident($1); }
1303         |  conpatk apat                         { $$ = mkap($1,$2); }
1304         ;
1305
1306 apatck  :  qvark                                { $$ = mkident($1); }
1307         |  qvark AT apat                        { $$ = mkas($1,$3); }
1308         |  lit_constant                         { $$ = mklit($1); setstartlineno(); }
1309         |  WILDCARD                             { $$ = mkwildp(); setstartlineno(); }
1310         |  oparenkey pat CPAREN                 { $$ = mkpar($2); }
1311         |  oparenkey pat COMMA pats CPAREN      { $$ = mktuple(mklcons($2,$4)); }
1312         |  obrackkey pats CBRACK                { $$ = mkllist($2); }
1313         |  lazykey apat                         { $$ = mklazyp($2); }
1314         ;
1315
1316
1317 gcon    :  qcon
1318         |  OBRACK CBRACK                        { $$ = creategid(NILGID); }
1319         |  OPAREN CPAREN                        { $$ = creategid(UNITGID); }
1320         |  OPAREN commas CPAREN                 { $$ = creategid($2); }
1321         ;
1322
1323 gconk   :  qconk
1324         |  obrackkey CBRACK                     { $$ = creategid(NILGID); }
1325         |  oparenkey CPAREN                     { $$ = creategid(UNITGID); }
1326         |  oparenkey commas CPAREN              { $$ = creategid($2); }
1327         ;
1328
1329 /**********************************************************************
1330 *                                                                     *
1331 *                                                                     *
1332 *     Keywords which record the line start                            *
1333 *                                                                     *
1334 *                                                                     *
1335 **********************************************************************/
1336
1337 importkey: IMPORT                { setstartlineno(); $$ = 0; }
1338         |  IMPORT SOURCE_UPRAGMA { setstartlineno(); $$ = 1; }
1339         ;
1340
1341 datakey :   DATA        { setstartlineno();
1342                           if(etags)
1343 #if 1/*etags*/
1344                             printf("%u\n",startlineno);
1345 #else
1346                             fprintf(stderr,"%u\tdata\n",startlineno);
1347 #endif
1348                         }
1349         ;
1350
1351 typekey :   TYPE        { setstartlineno();
1352                           if(etags)
1353 #if 1/*etags*/
1354                             printf("%u\n",startlineno);
1355 #else
1356                             fprintf(stderr,"%u\ttype\n",startlineno);
1357 #endif
1358                         }
1359         ;
1360
1361 newtypekey : NEWTYPE    { setstartlineno();
1362                           if(etags)
1363 #if 1/*etags*/
1364                             printf("%u\n",startlineno);
1365 #else
1366                             fprintf(stderr,"%u\tnewtype\n",startlineno);
1367 #endif
1368                         }
1369         ;
1370
1371 instkey :   INSTANCE    { setstartlineno();
1372 #if 1/*etags*/
1373 /* OUT:                   if(etags)
1374                             printf("%u\n",startlineno);
1375 */
1376 #else
1377                             fprintf(stderr,"%u\tinstance\n",startlineno);
1378 #endif
1379                         }
1380         ;
1381
1382 defaultkey: DEFAULT     { setstartlineno(); }
1383         ;
1384
1385 classkey:   CLASS       { setstartlineno();
1386                           if(etags)
1387 #if 1/*etags*/
1388                             printf("%u\n",startlineno);
1389 #else
1390                             fprintf(stderr,"%u\tclass\n",startlineno);
1391 #endif
1392                         }
1393         ;
1394
1395 modulekey:  MODULE      { setstartlineno();
1396                           if(etags)
1397 #if 1/*etags*/
1398                             printf("%u\n",startlineno);
1399 #else
1400                             fprintf(stderr,"%u\tmodule\n",startlineno);
1401 #endif
1402                         }
1403         ;
1404
1405 oparenkey:  OPAREN      { setstartlineno(); }
1406         ;
1407
1408 obrackkey:  OBRACK      { setstartlineno(); }
1409         ;
1410
1411 lazykey :   LAZY        { setstartlineno(); }
1412         ;
1413
1414 minuskey:   MINUS       { setstartlineno(); }
1415         ;
1416
1417
1418 /**********************************************************************
1419 *                                                                     *
1420 *                                                                     *
1421 *     Basic qualified/unqualified ids/ops                             *
1422 *                                                                     *
1423 *                                                                     *
1424 **********************************************************************/
1425
1426 qvar    :  qvarid
1427         |  OPAREN qvarsym CPAREN        { $$ = $2; }
1428         ;
1429 qcon    :  qconid
1430         |  OPAREN qconsym CPAREN        { $$ = $2; }
1431         ;
1432 qvarop  :  qvarsym
1433         |  BQUOTE qvarid BQUOTE         { $$ = $2; }
1434         ;
1435 qconop  :  qconsym
1436         |  BQUOTE qconid BQUOTE         { $$ = $2; }
1437         ;
1438 qop     :  qconop
1439         |  qvarop
1440         ;
1441
1442 /* Non "-" op, used in right sections */
1443 qop1    :  qconop
1444         |  qvarop1
1445         ;
1446
1447 /* Non "-" varop, used in right sections */
1448 qvarop1 :  QVARSYM
1449         |  varsym_nominus               { $$ = mknoqual($1); }
1450         |  BQUOTE qvarid BQUOTE         { $$ = $2; }
1451         ;
1452
1453
1454 var     :  varid
1455         |  OPAREN varsym CPAREN         { $$ = $2; }
1456         ;
1457 con     :  tycon                        /* using tycon removes conflicts */
1458         |  OPAREN CONSYM CPAREN         { $$ = $2; }
1459         ;
1460 varop   :  varsym
1461         |  BQUOTE varid BQUOTE          { $$ = $2; }
1462         ;
1463 conop   :  CONSYM
1464         |  BQUOTE CONID BQUOTE          { $$ = $2; }
1465         ;
1466 op      :  conop
1467         |  varop
1468         ;
1469
1470 qvark   :  qvarid                       { setstartlineno(); $$ = $1; }
1471         |  oparenkey qvarsym CPAREN     { $$ = $2; }
1472         ;
1473 qconk   :  qconid                       { setstartlineno(); $$ = $1; }
1474         |  oparenkey qconsym CPAREN     { $$ = $2; }
1475         ;
1476 vark    :  varid                        { setstartlineno(); $$ = $1; }
1477         |  oparenkey varsym CPAREN      { $$ = $2; }
1478         ;
1479
1480 qvarid  :  QVARID
1481         |  varid                        { $$ = mknoqual($1); }
1482         ;
1483 qvarsym :  QVARSYM
1484         |  varsym                       { $$ = mknoqual($1); }
1485         ;
1486 qconid  :  QCONID
1487         |  tycon                        { $$ = mknoqual($1); } /* using tycon removes conflicts */
1488         ;
1489 qconsym :  QCONSYM
1490         |  CONSYM                       { $$ = mknoqual($1); }
1491         ;
1492 qtycon  :  QCONID
1493         |  tycon                        { $$ = mknoqual($1); } /* using tycon removes conflicts */
1494         ;
1495 qtycls  :  QCONID
1496         |  tycon                        { $$ = mknoqual($1); } /* using tycon removes conflicts */
1497         ;
1498
1499 varsym  :  varsym_nominus
1500         |  MINUS                        { $$ = install_literal("-"); }
1501         ;
1502
1503 /* PLUS, BANG are valid varsyms */
1504 varsym_nominus : VARSYM
1505         |  PLUS                         { $$ = install_literal("+"); }
1506         |  BANG                         { $$ = install_literal("!"); }  
1507         ;
1508
1509 /* AS HIDING QUALIFIED are valid varids */
1510 varid   :  VARID
1511         |  AS                           { $$ = install_literal("as"); }
1512         |  HIDING                       { $$ = install_literal("hiding"); }
1513         |  QUALIFIED                    { $$ = install_literal("qualified"); }
1514         ;
1515
1516
1517 ccallid :  VARID
1518         |  CONID
1519         ;
1520
1521 tyvar   :  varid                        { $$ = mknamedtvar(mknoqual($1)); }
1522         ;
1523 tycon   :  CONID
1524         ;
1525 modid   :  CONID
1526         ;
1527
1528 /*
1529 tyvar_list: tyvar                       { $$ = lsing($1); }
1530         |  tyvar_list COMMA tyvar       { $$ = lapp($1,$3); }
1531         ;
1532 */
1533
1534 /**********************************************************************
1535 *                                                                     *
1536 *                                                                     *
1537 *     Stuff to do with layout                                         *
1538 *                                                                     *
1539 *                                                                     *
1540 **********************************************************************/
1541
1542 ocurly  : layout OCURLY                         { hsincindent(); }
1543
1544 vocurly : layout                                { hssetindent(); }
1545         ;
1546
1547 layout  :                                       { hsindentoff(); }
1548         ;
1549
1550 ccurly  :
1551          CCURLY
1552                 {
1553                   FN = NULL; SAMEFN = 0; PREVPATT = NULL;
1554                   hsendindent();
1555                 }
1556         ;
1557
1558 vccurly :  { expect_ccurly = 1; }  vccurly1  { expect_ccurly = 0; }
1559         ;
1560
1561 vccurly1:
1562          VCCURLY
1563                 {
1564                   FN = NULL; SAMEFN = 0; PREVPATT = NULL;
1565                   hsendindent();
1566                 }
1567         | error
1568                 {
1569                   yyerrok;
1570                   FN = NULL; SAMEFN = 0; PREVPATT = NULL;
1571                   hsendindent();
1572                 }
1573         ;
1574
1575 %%
1576
1577 /**********************************************************************
1578 *                                                                     *
1579 *      Error Processing and Reporting                                 *
1580 *                                                                     *
1581 *  (This stuff is here in case we want to use Yacc macros and such.)  *
1582 *                                                                     *
1583 **********************************************************************/
1584
1585
1586 /*
1587 void
1588 checkinpat()
1589 {
1590   if(!inpat)
1591     hsperror("pattern syntax used in expression");
1592 }
1593 */
1594
1595 /* The parser calls "hsperror" when it sees a
1596    `report this and die' error.  It sets the stage
1597    and calls "yyerror".
1598
1599    There should be no direct calls in the parser to
1600    "yyerror", except for the one from "hsperror".  Thus,
1601    the only other calls will be from the error productions
1602    introduced by yacc/bison/whatever.
1603
1604    We need to be able to recognise the from-error-production
1605    case, because we sometimes want to say, "Oh, never mind",
1606    because the layout rule kicks into action and may save
1607    the day.  [WDP]
1608 */
1609
1610 static BOOLEAN error_and_I_mean_it = FALSE;
1611
1612 void
1613 hsperror(s)
1614   char *s;
1615 {
1616     error_and_I_mean_it = TRUE;
1617     yyerror(s);
1618 }
1619
1620 extern char *yytext;
1621 extern int yyleng;
1622
1623 void
1624 yyerror(s)
1625   char *s;
1626 {
1627     /* We want to be able to distinguish 'error'-raised yyerrors
1628        from yyerrors explicitly coded by the parser hacker.
1629     */
1630     if (expect_ccurly && ! error_and_I_mean_it ) {
1631         /*NOTHING*/;
1632
1633     } else {
1634         fprintf(stderr, "%s:%d:%d: %s on input: ",
1635           input_filename, hsplineno, hspcolno + 1, s);
1636
1637         if (yyleng == 1 && *yytext == '\0')
1638             fprintf(stderr, "<EOF>");
1639
1640         else {
1641             fputc('"', stderr);
1642             format_string(stderr, (unsigned char *) yytext, yyleng);
1643             fputc('"', stderr);
1644         }
1645         fputc('\n', stderr);
1646
1647         /* a common problem */
1648         if (strcmp(yytext, "#") == 0)
1649             fprintf(stderr, "\t(Perhaps you forgot a `-cpp' or `-fglasgow-exts' flag?)\n");
1650
1651         exit(1);
1652     }
1653 }
1654
1655 void
1656 format_string(fp, s, len)
1657   FILE *fp;
1658   unsigned char *s;
1659   int len;
1660 {
1661     while (len-- > 0) {
1662         switch (*s) {
1663         case '\0':    fputs("\\NUL", fp);   break;
1664         case '\007':  fputs("\\a", fp);     break;
1665         case '\010':  fputs("\\b", fp);     break;
1666         case '\011':  fputs("\\t", fp);     break;
1667         case '\012':  fputs("\\n", fp);     break;
1668         case '\013':  fputs("\\v", fp);     break;
1669         case '\014':  fputs("\\f", fp);     break;
1670         case '\015':  fputs("\\r", fp);     break;
1671         case '\033':  fputs("\\ESC", fp);   break;
1672         case '\034':  fputs("\\FS", fp);    break;
1673         case '\035':  fputs("\\GS", fp);    break;
1674         case '\036':  fputs("\\RS", fp);    break;
1675         case '\037':  fputs("\\US", fp);    break;
1676         case '\177':  fputs("\\DEL", fp);   break;
1677         default:
1678             if (*s >= ' ')
1679                 fputc(*s, fp);
1680             else
1681                 fprintf(fp, "\\^%c", *s + '@');
1682             break;
1683         }
1684         s++;
1685     }
1686 }