[project @ 1999-04-27 10:06:47 by sewardj]
[ghc-hetmet.git] / ghc / interpreter / parser.y
1
2 /* --------------------------------------------------------------------------
3  * Hugs parser (included as part of input.c)
4  *
5  * Expect 6 shift/reduce conflicts when passing this grammar through yacc,
6  * but don't worry; they should all be resolved in an appropriate manner.
7  *
8  * Hugs 98 is Copyright (c) Mark P Jones, Alastair Reid and the Yale
9  * Haskell Group 1994-99, and is distributed as Open Source software
10  * under the Artistic License; see the file "Artistic" that is included
11  * in the distribution for details.
12  *
13  * $RCSfile: parser.y,v $
14  * $Revision: 1.5 $
15  * $Date: 1999/04/27 10:06:58 $
16  * ------------------------------------------------------------------------*/
17
18 %{
19 #ifndef lint
20 #define lint
21 #endif
22 #define defTycon(n,l,lhs,rhs,w)  tyconDefn(intOf(l),lhs,rhs,w); sp-=n
23 #define sigdecl(l,vs,t)          ap(SIGDECL,triple(l,vs,t))
24 #define fixdecl(l,ops,a,p)       ap(FIXDECL,\
25                                     triple(l,ops,mkInt(mkSyntax(a,intOf(p)))))
26 #define grded(gs)                ap(GUARDED,gs)
27 #define bang(t)                  ap(BANG,t)
28 #define only(t)                  ap(ONLY,t)
29 #define letrec(bs,e)             (nonNull(bs) ? ap(LETREC,pair(bs,e)) : e)
30 #define qualify(ps,t)            (nonNull(ps) ? ap(QUAL,pair(ps,t)) : t)
31 #define exportSelf()             singleton(ap(MODULEENT,mkCon(module(currentModule).text)))
32 #define yyerror(s)               /* errors handled elsewhere */
33 #define YYSTYPE                  Cell
34
35 static Cell   local gcShadow     Args((Int,Cell));
36 static Void   local syntaxError  Args((String));
37 static String local unexpected   Args((Void));
38 static Cell   local checkPrec    Args((Cell));
39 static Cell   local buildTuple   Args((List));
40 static List   local checkContext Args((List));
41 static Cell   local checkPred    Args((Cell));
42 static Pair   local checkDo      Args((List));
43 static Cell   local checkTyLhs   Args((Cell));
44 #if !TREX
45 static Void   local noTREX       Args((String));
46 #endif
47
48 /* For the purposes of reasonably portable garbage collection, it is
49  * necessary to simulate the YACC stack on the Hugs stack to keep
50  * track of all intermediate constructs.  The lexical analyser
51  * pushes a token onto the stack for each token that is found, with
52  * these elements being removed as reduce actions are performed,
53  * taking account of look-ahead tokens as described by gcShadow()
54  * below.
55  *
56  * Of the non-terminals used below, only start, topDecl & begin
57  * do not leave any values on the Hugs stack.  The same is true for the
58  * terminals EXPR and SCRIPT.  At the end of a successful parse, there
59  * should only be one element left on the stack, containing the result
60  * of the parse.
61  */
62
63 #define gc0(e)                  gcShadow(0,e)
64 #define gc1(e)                  gcShadow(1,e)
65 #define gc2(e)                  gcShadow(2,e)
66 #define gc3(e)                  gcShadow(3,e)
67 #define gc4(e)                  gcShadow(4,e)
68 #define gc5(e)                  gcShadow(5,e)
69 #define gc6(e)                  gcShadow(6,e)
70 #define gc7(e)                  gcShadow(7,e)
71
72 %}
73
74 %token EXPR       SCRIPT
75 %token CASEXP     OF         DATA       TYPE       IF
76 %token THEN       ELSE       WHERE      LET        IN
77 %token INFIXN     INFIXL     INFIXR     FOREIGN    TNEWTYPE
78 %token DEFAULT    DERIVING   DO         TCLASS     TINSTANCE
79 %token REPEAT     ALL        NUMLIT     CHARLIT    STRINGLIT
80 %token VAROP      VARID      CONOP      CONID
81 %token QVAROP     QVARID     QCONOP     QCONID
82 /*#if TREX*/
83 %token RECSELID
84 /*#endif*/
85 %token COCO       '='        UPTO       '@'        '\\'
86 %token '|'        '-'        FROM       ARROW      '~'
87 %token '!'        IMPLIES    '('        ','        ')'
88 %token '['        ';'        ']'        '`'        '.'
89 %token TMODULE    IMPORT     HIDING     QUALIFIED  ASMOD
90 %token EXPORT     UNSAFE
91
92 %%
93 /*- Top level script/module structure -------------------------------------*/
94
95 start     : EXPR exp wherePart          {inputExpr = letrec($3,$2); sp-=2;}
96           | SCRIPT topModule            {valDefns  = $2;            sp-=1;}
97           | error                       {syntaxError("input");}
98           ;
99
100 /*- Haskell module header/import parsing: -----------------------------------
101  * Syntax for Haskell modules (module headers and imports) is parsed but
102  * most of it is ignored.  However, module names in import declarations
103  * are used, of course, if import chasing is turned on.
104  *-------------------------------------------------------------------------*/
105
106 /* In Haskell 1.2, the default module header was "module Main where"
107  * In 1.3, this changed to "module Main(main) where".
108  * We use the 1.2 header because it breaks much less pre-module code.
109  */
110 topModule : startMain begin modBody end {
111                                          setExportList(singleton(ap(MODULEENT,mkCon(module(currentModule).text))));
112                                          $$ = gc3($3);
113                                         }
114           | TMODULE modname expspec WHERE '{' modBody end
115                                         {setExportList($3);   $$ = gc7($6);}
116           | TMODULE error               {syntaxError("module definition");}
117           ;
118 /* To implement the Haskell module system, we have to keep track of the
119  * current module.  We rely on the use of LALR parsing to ensure that this 
120  * side effect happens before any declarations within the module.
121  */
122 startMain : /* empty */                 {startModule(conMain); 
123                                          $$ = gc0(NIL);}
124           ;
125 modname   : CONID                       {startModule($1); $$ = gc1(NIL);}
126           ;
127 modid     : CONID                       {$$ = $1;}
128           | STRINGLIT                   { extern String scriptFile;
129                                           String modName = findPathname(scriptFile,textToStr(textOf($1)));
130                                           if (modName) { /* fillin pathname if known */
131                                               $$ = mkStr(findText(modName));
132                                           } else {
133                                               $$ = $1;
134                                           }
135                                         }
136           ;
137 modBody   : topDecls                    {$$ = $1;}
138           | impDecls chase              {$$ = gc2(NIL);}
139           | impDecls ';' chase topDecls {$$ = gc4($4);}
140           ;
141
142 /*- Exports: --------------------------------------------------------------*/
143
144 expspec   : /* empty */                 {$$ = gc0(exportSelf());}
145           | '(' ')'                     {$$ = gc2(NIL);}
146           | '(' exports ')'             {$$ = gc3($2);}
147           | '(' exports ',' ')'         {$$ = gc4($2);}
148           ;
149 exports   : exports ',' export          {$$ = gc3(cons($3,$1));}
150           | export                      {$$ = gc1(singleton($1));}
151           ;
152 /* The qcon should be qconid.  
153  * Relaxing the rule lets us explicitly export (:) from the Prelude.
154  */
155 export    : qvar                        {$$ = $1;}
156           | qcon                        {$$ = $1;}
157           | qconid '(' UPTO ')'         {$$ = gc4(pair($1,DOTDOT));}
158           | qconid '(' qnames ')'       {$$ = gc4(pair($1,$3));}
159           | TMODULE modid               {$$ = gc2(ap(MODULEENT,$2));}
160           ;
161 qnames    : /* empty */                 {$$ = gc0(NIL);}
162           | ','                         {$$ = gc1(NIL);}
163           | qnames1                     {$$ = $1;}
164           | qnames1 ','                 {$$ = gc2($1);}
165           ;
166 qnames1   : qnames1 ',' qname           {$$ = gc3(cons($3,$1));}
167           | qname                       {$$ = gc1(singleton($1));}
168           ;
169 qname     : qvar                        {$$ = $1;}
170           | qcon                        {$$ = $1;}
171           ;
172
173 /*- Import declarations: --------------------------------------------------*/
174
175 impDecls  : impDecls ';' impDecl        {imps = cons($3,imps); $$=gc3(NIL);}
176           | impDecl                     {imps = singleton($1); $$=gc1(NIL);}
177           ;
178 chase     : /* empty */                 {if (chase(imps)) {
179                                              clearStack();
180                                              onto(imps);
181                                              done();
182                                              closeAnyInput();
183                                              return 0;
184                                          }
185                                          $$ = gc0(NIL);
186                                         }
187           ;
188 /* Note that qualified import ignores the import list. */
189 impDecl   : IMPORT modid impspec        {addQualImport($2,$2);
190                                          addUnqualImport($2,$3);
191                                          $$ = gc3($2);}
192           | IMPORT modid ASMOD modid impspec
193                                         {addQualImport($2,$4);
194                                          addUnqualImport($2,$5);
195                                          $$ = gc5($2);}
196           | IMPORT QUALIFIED modid ASMOD modid impspec
197                                         {addQualImport($3,$5);
198                                          $$ = gc6($3);}
199           | IMPORT QUALIFIED modid impspec
200                                         {addQualImport($3,$3);
201                                          $$ = gc4($3);}
202           | IMPORT error                {syntaxError("import declaration");}
203           ;
204 impspec   : /* empty */                 {$$ = gc0(DOTDOT);}
205           | HIDING '(' imports ')'      {$$ = gc4(ap(HIDDEN,$3));}
206           | '(' imports ')'             {$$ = gc3($2);}
207           ;
208 imports   : /* empty */                 {$$ = gc0(NIL);}
209           | ','                         {$$ = gc1(NIL);}
210           | imports1                    {$$ = $1;}
211           | imports1 ','                {$$ = gc2($1);}
212           ;
213 imports1  : imports1 ',' import         {$$ = gc3(cons($3,$1));}
214           | import                      {$$ = gc1(singleton($1));}
215           ;
216 import    : var                         {$$ = $1;}
217           | CONID                       {$$ = $1;}
218           | CONID '(' UPTO ')'          {$$ = gc4(pair($1,DOTDOT));}
219           | CONID '(' names ')'         {$$ = gc4(pair($1,$3));}
220           ;
221 names     : /* empty */                 {$$ = gc0(NIL);}
222           | ','                         {$$ = gc1(NIL);}
223           | names1                      {$$ = $1;}
224           | names1 ','                  {$$ = gc2($1);}
225           ;
226 names1    : names1 ',' name             {$$ = gc3(cons($3,$1));}
227           | name                        {$$ = gc1(singleton($1));}
228           ;
229 name      : var                         {$$ = $1;}
230           | con                         {$$ = $1;}
231           ;
232
233 /*- Top-level declarations: -----------------------------------------------*/
234
235 topDecls  : /* empty */                 {$$ = gc0(NIL);}
236           | ';'                         {$$ = gc1(NIL);}
237           | topDecls1                   {$$ = $1;}
238           | topDecls1 ';'               {$$ = gc2($1);}
239           ;
240 topDecls1 : topDecls1 ';' topDecl       {$$ = gc2($1);}
241           | topDecls1 ';' decl          {$$ = gc3(cons($3,$1));}
242           | topDecl                     {$$ = gc0(NIL);}
243           | decl                        {$$ = gc1(cons($1,NIL));}
244           ;
245
246 /*- Type declarations: ----------------------------------------------------*/
247
248 topDecl   : TYPE tyLhs '=' type         {defTycon(4,$3,$2,$4,SYNONYM);}
249           | TYPE tyLhs '=' type IN invars
250                                         {defTycon(6,$3,$2,
251                                                     ap($4,$6),RESTRICTSYN);}
252           | TYPE error                  {syntaxError("type definition");}
253           | DATA btype2 '=' constrs deriving
254                                         {defTycon(5,$3,checkTyLhs($2),
255                                                     ap(rev($4),$5),DATATYPE);}
256           | DATA context IMPLIES tyLhs '=' constrs deriving
257                                         {defTycon(7,$5,$4,
258                                                   ap(qualify($2,rev($6)),
259                                                      $7),DATATYPE);}
260           | DATA btype2                 {defTycon(2,$1,checkTyLhs($2),
261                                                     ap(NIL,NIL),DATATYPE);}
262           | DATA context IMPLIES tyLhs  {defTycon(4,$1,$4,
263                                                   ap(qualify($2,NIL),
264                                                      NIL),DATATYPE);}
265           | DATA error                  {syntaxError("data definition");}
266           | TNEWTYPE btype2 '=' nconstr deriving
267                                         {defTycon(5,$3,checkTyLhs($2),
268                                                     ap($4,$5),NEWTYPE);}
269           | TNEWTYPE context IMPLIES tyLhs '=' nconstr deriving
270                                         {defTycon(7,$5,$4,
271                                                   ap(qualify($2,$6),
272                                                      $7),NEWTYPE);}
273           | TNEWTYPE error              {syntaxError("newtype definition");}
274           ;
275 tyLhs     : tyLhs varid                 {$$ = gc2(ap($1,$2));}
276           | CONID                       {$$ = $1;}
277           | error                       {syntaxError("type defn lhs");}
278           ;
279 invars    : invars ',' invar            {$$ = gc3(cons($3,$1));}
280           | invar                       {$$ = gc1(cons($1,NIL));}
281           ;
282 invar     : var COCO topType            {$$ = gc3(sigdecl($2,singleton($1),
283                                                                         $3));}
284           | var                         {$$ = $1;}
285           ;
286 constrs   : constrs '|' pconstr         {$$ = gc3(cons($3,$1));}
287           | pconstr                     {$$ = gc1(cons($1,NIL));}
288           ;
289 pconstr   : ALL varids '.' qconstr      {$$ = gc4(ap(POLYTYPE,
290                                                      pair(rev($2),$4)));}
291           | qconstr                     {$$ = $1;}
292           ;
293 qconstr   : context IMPLIES constr      {$$ = gc3(qualify($1,$3));}
294           | constr                      {$$ = $1;}
295           ;
296 constr    : '!' btype conop bbtype      {$$ = gc4(ap(ap($3,bang($2)),$4));}
297           | btype1    conop bbtype      {$$ = gc3(ap(ap($2,$1),$3));}
298           | btype2    conop bbtype      {$$ = gc3(ap(ap($2,$1),$3));}
299           | bpolyType conop bbtype      {$$ = gc3(ap(ap($2,$1),$3));}
300           | btype2                      {$$ = $1;}
301           | btype3                      {$$ = $1;}
302           | btype4                      {$$ = $1;}
303           | con '{' fieldspecs '}'      {$$ = gc4(ap(LABC,pair($1,rev($3))));}
304           | con '{' '}'                 {$$ = gc3(ap(LABC,pair($1,NIL)));}
305           | error                       {syntaxError("data type definition");}
306           ;
307 btype3    : btype2 '!' atype            {$$ = gc3(ap($1,bang($3)));}
308           | btype3 '!' atype            {$$ = gc3(ap($1,bang($3)));}
309           | btype3 atype                {$$ = gc2(ap($1,$2));}
310           ;
311 btype4    : btype2 bpolyType            {$$ = gc2(ap($1,$2));}
312           | btype3 bpolyType            {$$ = gc2(ap($1,$2));}
313           | btype4 bpolyType            {$$ = gc2(ap($1,$2));}
314           | btype4 atype                {$$ = gc2(ap($1,$2));}
315           | btype4 '!' atype            {$$ = gc3(ap($1,bang($3)));}
316           ;
317 bbtype    : '!' btype                   {$$ = gc2(bang($2));}
318           | btype                       {$$ = $1;}
319           | bpolyType                   {$$ = $1;}
320           ;
321 nconstr   : pconstr                     {$$ = gc1(singleton($1));}
322           ;
323 fieldspecs: fieldspecs ',' fieldspec    {$$ = gc3(cons($3,$1));}
324           | fieldspec                   {$$ = gc1(cons($1,NIL));}
325           ;
326 fieldspec : vars COCO polyType          {$$ = gc3(pair(rev($1),$3));}
327           | vars COCO type              {$$ = gc3(pair(rev($1),$3));}
328           | vars COCO '!' type          {$$ = gc4(pair(rev($1),bang($4)));}
329           ;
330 deriving  : /* empty */                 {$$ = gc0(NIL);}
331           | DERIVING qconid             {$$ = gc2(singleton($2));}
332           | DERIVING '(' derivs0 ')'    {$$ = gc4($3);}
333           ;
334 derivs0   : /* empty */                 {$$ = gc0(NIL);}
335           | derivs                      {$$ = gc1(rev($1));}
336           ;
337 derivs    : derivs ',' qconid           {$$ = gc3(cons($3,$1));}
338           | qconid                      {$$ = gc1(singleton($1));}
339           ;
340
341 /*- Processing definitions of primitives ----------------------------------*/
342
343 topDecl   : FOREIGN IMPORT callconv ext_loc ext_name unsafe_flag var COCO type 
344                                         {foreignImport($1,pair($4,$5),$7,$9); sp-=9;}
345           | FOREIGN EXPORT callconv ext_name qvarid COCO type 
346                                         {foreignExport($1,$4,$5,$7); sp-=7;}
347           ;
348
349 callconv  : var                  {$$ = gc1(NIL); /* ignored */ }
350           ;
351 ext_loc   : STRINGLIT            {$$ = $1;}
352           ;
353 ext_name  : STRINGLIT            {$$ = $1;}
354           ;
355 unsafe_flag: /* empty */         {$$ = gc0(NIL);}
356           | UNSAFE               {$$ = gc1(NIL); /* ignored */ }
357           ;
358
359
360 /*- Class declarations: ---------------------------------------------------*/
361
362 topDecl   : TCLASS crule wherePart      {classDefn(intOf($1),$2,$3); sp-=3;}
363           | TINSTANCE irule wherePart   {instDefn(intOf($1),$2,$3);  sp-=3;}
364           | DEFAULT '(' dtypes ')'      {defaultDefn(intOf($1),$3);  sp-=4;}
365           | TCLASS error                {syntaxError("class declaration");}
366           | TINSTANCE error             {syntaxError("instance declaration");}
367           | DEFAULT error               {syntaxError("default declaration");}
368           ;
369 crule     : context IMPLIES btype2      {$$ = gc3(pair($1,checkPred($3)));}
370           | btype2                      {$$ = gc1(pair(NIL,checkPred($1)));}
371           ;
372 irule     : context IMPLIES btype2      {$$ = gc3(pair($1,checkPred($3)));}
373           | btype2                      {$$ = gc1(pair(NIL,checkPred($1)));}
374           ;
375 dtypes    : /* empty */                 {$$ = gc0(NIL);}
376           | dtypes1                     {$$ = gc1(rev($1));}
377           ;
378 dtypes1   : dtypes1 ',' type            {$$ = gc3(cons($3,$1));}
379           | type                        {$$ = gc1(cons($1,NIL));}
380           ;
381
382 /*- Type expressions: -----------------------------------------------------*/
383
384 topType   : context IMPLIES topType1    {$$ = gc3(qualify($1,$3));}
385           | topType1                    {$$ = $1;}
386           ;
387 topType1  : bpolyType ARROW topType1    {$$ = gc3(fn($1,$3));}
388           | btype1    ARROW topType1    {$$ = gc3(fn($1,$3));}
389           | btype2    ARROW topType1    {$$ = gc3(fn($1,$3));}
390           | btype                       {$$ = $1;}
391           ;
392 polyType  : ALL varids '.' sigType      {$$ = gc4(ap(POLYTYPE,
393                                                      pair(rev($2),$4)));}
394           | bpolyType                   {$$ = $1;}
395           ;
396 bpolyType : '(' polyType ')'            {$$ = gc3($2);}
397           ;
398 varids    : varids ',' varid            {$$ = gc3(cons($3,$1));}
399           | varid                       {$$ = gc1(singleton($1));}
400           ;
401 sigType   : context IMPLIES type        {$$ = gc3(qualify($1,$3));}
402           | type                        {$$ = $1;}
403           ;
404 context   : '(' ')'                     {$$ = gc2(NIL);}
405           | btype2                      {$$ = gc1(singleton(checkPred($1)));}
406           | '(' btype2 ')'              {$$ = gc3(singleton(checkPred($2)));}
407           | '(' btypes2 ')'             {$$ = gc3(checkContext(rev($2)));}
408 /*#if TREX*/
409           | lacks                       {$$ = gc1(singleton($1));}
410           | '(' lacks1 ')'              {$$ = gc3(checkContext(rev($2)));}
411           ;
412 lacks     : varid '\\' varid            {
413 #if TREX
414                                          $$ = gc3(ap(mkExt(textOf($3)),$1));
415 #else
416                                          noTREX("a type context");
417 #endif
418                                         }
419           ;
420 lacks1    : btypes2 ',' lacks           {$$ = gc3(cons($3,$1));}
421           | lacks1  ',' btype2          {$$ = gc3(cons($3,$1));}
422           | lacks1  ',' lacks           {$$ = gc3(cons($3,$1));}
423           | btype2  ',' lacks           {$$ = gc3(cons($3,cons($1,NIL)));}
424           | lacks                       {$$ = gc1(singleton($1));}
425           ;
426 /*#endif*/
427
428 type      : type1                       {$$ = $1;}
429           | btype2                      {$$ = $1;}
430           ;
431 type1     : btype1                      {$$ = $1;}
432           | btype1 ARROW type           {$$ = gc3(fn($1,$3));}
433           | btype2 ARROW type           {$$ = gc3(fn($1,$3));}
434           | error                       {syntaxError("type expression");}
435           ;
436 btype     : btype1                      {$$ = $1;}
437           | btype2                      {$$ = $1;}
438           ;
439 btype1    : btype1 atype                {$$ = gc2(ap($1,$2));}
440           | atype1                      {$$ = $1;}
441           ;
442 btype2    : btype2 atype                {$$ = gc2(ap($1,$2));}
443           | qconid                      {$$ = $1;}
444           ;
445 atype     : atype1                      {$$ = $1;}
446           | qconid                      {$$ = $1;}
447           ;
448 atype1    : varid                       {$$ = $1;}
449           | '(' ')'                     {$$ = gc2(typeUnit);}
450           | '(' ARROW ')'               {$$ = gc3(typeArrow);}
451           | '(' type1 ')'               {$$ = gc3($2);}
452           | '(' btype2 ')'              {$$ = gc3($2);}
453           | '(' tupCommas ')'           {$$ = gc3($2);}
454           | '(' btypes2 ')'             {$$ = gc3(buildTuple($2));}
455           | '(' typeTuple ')'           {$$ = gc3(buildTuple($2));}
456 /*#if TREX*/
457           | '(' tfields ')'             {
458 #if TREX
459                                          $$ = gc3(revOnto($2,typeNoRow));
460 #else
461                                          noTREX("a type");
462 #endif
463                                         }
464           | '(' tfields '|' type ')'    {$$ = gc5(revOnto($2,$4));}
465 /*#endif*/
466           | '[' type ']'                {$$ = gc3(ap(typeList,$2));}
467           | '[' ']'                     {$$ = gc2(typeList);}
468           | '_'                         {$$ = gc1(inventVar());}
469           ;
470 btypes2   : btypes2 ',' btype2          {$$ = gc3(cons($3,$1));}
471           | btype2  ',' btype2          {$$ = gc3(cons($3,cons($1,NIL)));}
472           ;
473 typeTuple : type1     ',' type          {$$ = gc3(cons($3,cons($1,NIL)));}
474           | btype2    ',' type1         {$$ = gc3(cons($3,cons($1,NIL)));}
475           | btypes2   ',' type1         {$$ = gc3(cons($3,$1));}
476           | typeTuple ',' type          {$$ = gc3(cons($3,$1));}
477           ;
478 /*#if TREX*/
479 tfields   : tfields ',' tfield          {$$ = gc3(cons($3,$1));}
480           | tfield                      {$$ = gc1(singleton($1));}
481           ;
482 tfield    : varid COCO type             {$$ = gc3(ap(mkExt(textOf($1)),$3));}
483           ;
484 /*#endif*/
485
486 /*- Value declarations: ---------------------------------------------------*/
487
488 gendecl   : INFIXN optDigit ops         {$$ = gc3(fixdecl($1,$3,NON_ASS,$2));}
489           | INFIXN error                {syntaxError("fixity decl");}
490           | INFIXL optDigit ops         {$$ = gc3(fixdecl($1,$3,LEFT_ASS,$2));}
491           | INFIXL error                {syntaxError("fixity decl");}
492           | INFIXR optDigit ops         {$$ = gc3(fixdecl($1,$3,RIGHT_ASS,$2));}
493           | INFIXR error                {syntaxError("fixity decl");}
494           | vars COCO topType           {$$ = gc3(sigdecl($2,$1,$3));}
495           | vars COCO error             {syntaxError("type signature");}
496           ;
497 optDigit  : NUMLIT                      {$$ = gc1(checkPrec($1));}
498           | /* empty */                 {$$ = gc0(mkInt(DEF_PREC));}
499           ;
500 ops       : ops ',' op                  {$$ = gc3(cons($3,$1));}
501           | op                          {$$ = gc1(singleton($1));}
502           ;
503 vars      : vars ',' var                {$$ = gc3(cons($3,$1));}
504           | var                         {$$ = gc1(singleton($1));}
505           ;
506 decls     : '{' decls0 end              {$$ = gc3($2);}
507           | '{' decls1 end              {$$ = gc3($2);}
508           ;
509 decls0    : /* empty */                 {$$ = gc0(NIL);}
510           | decls0 ';'                  {$$ = gc2($1);}
511           | decls1 ';'                  {$$ = gc2($1);}
512           ;
513 decls1    : decls0 decl                 {$$ = gc2(cons($2,$1));}
514           ;
515 decl      : gendecl                     {$$ = $1;}
516           | funlhs rhs                  {$$ = gc2(ap(FUNBIND,pair($1,$2)));}
517           | funlhs COCO type rhs        {$$ = gc4(ap(FUNBIND,
518                                                      pair($1,ap(RSIGN,
519                                                                 ap($4,$3)))));}
520           | pat0 rhs                    {$$ = gc2(ap(PATBIND,pair($1,$2)));}
521           ;
522 funlhs    : funlhs0                     {$$ = $1;}
523           | funlhs1                     {$$ = $1;}
524           | npk                         {$$ = $1;}
525           ;
526 funlhs0   : pat10_vI varop    pat0      {$$ = gc3(ap2($2,$1,$3));}
527           | infixPat varop    pat0      {$$ = gc3(ap2($2,$1,$3));}
528           | NUMLIT   varop    pat0      {$$ = gc3(ap2($2,$1,$3));}
529           | var      varop_pl pat0      {$$ = gc3(ap2($2,$1,$3));}
530           | var      '+'      pat0_INT  {$$ = gc3(ap2(varPlus,$1,$3));}
531           ;
532 funlhs1   : '(' funlhs0 ')' apat        {$$ = gc4(ap($2,$4));}
533           | '(' funlhs1 ')' apat        {$$ = gc4(ap($2,$4));}
534           | '(' npk     ')' apat        {$$ = gc4(ap($2,$4));}
535           | var     apat                {$$ = gc2(ap($1,$2));}
536           | funlhs1 apat                {$$ = gc2(ap($1,$2));}
537           ;
538 rhs       : rhs1 wherePart              {$$ = gc2(letrec($2,$1));}
539           | error                       {syntaxError("declaration");}
540           ;
541 rhs1      : '=' exp                     {$$ = gc2(pair($1,$2));}
542           | gdrhs                       {$$ = gc1(grded(rev($1)));}
543           ;
544 gdrhs     : gdrhs gddef                 {$$ = gc2(cons($2,$1));}
545           | gddef                       {$$ = gc1(singleton($1));}
546           ;
547 gddef     : '|' exp0 '=' exp            {$$ = gc4(pair($3,pair($2,$4)));}
548           ;
549 wherePart : /* empty */                 {$$ = gc0(NIL);}
550           | WHERE decls                 {$$ = gc2($2);}
551           ;
552
553 /*- Patterns: -------------------------------------------------------------*/
554
555 pat       : npk                         {$$ = $1;}
556           | pat_npk                     {$$ = $1;}
557           ;
558 pat_npk   : pat0 COCO type              {$$ = gc3(ap(ESIGN,pair($1,$3)));}
559           | pat0                        {$$ = $1;}
560           ;
561 npk       : var '+' NUMLIT              {$$ = gc3(ap2(varPlus,$1,$3));}
562           ;
563 pat0      : var                         {$$ = $1;}
564           | NUMLIT                      {$$ = $1;}
565           | pat0_vI                     {$$ = $1;}
566           ;
567 pat0_INT  : var                         {$$ = $1;}
568           | pat0_vI                     {$$ = $1;}
569           ;
570 pat0_vI   : pat10_vI                    {$$ = $1;}
571           | infixPat                    {$$ = gc1(ap(INFIX,$1));}
572           ;
573 infixPat  : '-' pat10                   {$$ = gc2(ap(NEG,only($2)));}
574           | var qconop pat10            {$$ = gc3(ap(ap($2,only($1)),$3));}
575           | var qconop '-' pat10        {$$ = gc4(ap(NEG,ap2($2,only($1),$4)));}
576           | NUMLIT qconop pat10         {$$ = gc3(ap(ap($2,only($1)),$3));}
577           | NUMLIT qconop '-' pat10     {$$ = gc4(ap(NEG,ap2($2,only($1),$4)));}
578           | pat10_vI qconop pat10       {$$ = gc3(ap(ap($2,only($1)),$3));}
579           | pat10_vI qconop '-' pat10   {$$ = gc4(ap(NEG,ap2($2,only($1),$4)));}
580           | infixPat qconop pat10       {$$ = gc3(ap(ap($2,$1),$3));}
581           | infixPat qconop '-' pat10   {$$ = gc4(ap(NEG,ap(ap($2,$1),$4)));}
582           ;
583 pat10     : fpat                        {$$ = $1;}
584           | apat                        {$$ = $1;}
585           ;
586 pat10_vI  : fpat                        {$$ = $1;}
587           | apat_vI                     {$$ = $1;}
588           ;
589 fpat      : fpat apat                   {$$ = gc2(ap($1,$2));}
590           | gcon apat                   {$$ = gc2(ap($1,$2));}
591           ;
592 apat      : NUMLIT                      {$$ = $1;}
593           | var                         {$$ = $1;}
594           | apat_vI                     {$$ = $1;}
595           ;
596 apat_vI   : var '@' apat                {$$ = gc3(ap(ASPAT,pair($1,$3)));}
597           | gcon                        {$$ = $1;}
598           | qcon '{' patbinds '}'       {$$ = gc4(ap(CONFLDS,pair($1,$3)));}
599           | CHARLIT                     {$$ = $1;}
600           | STRINGLIT                   {$$ = $1;}
601           | '_'                         {$$ = gc1(WILDCARD);}
602           | '(' pat_npk ')'             {$$ = gc3($2);}
603           | '(' npk ')'                 {$$ = gc3($2);}
604           | '(' pats2 ')'               {$$ = gc3(buildTuple($2));}
605           | '[' pats1 ']'               {$$ = gc3(ap(FINLIST,rev($2)));}
606           | '~' apat                    {$$ = gc2(ap(LAZYPAT,$2));}
607 /*#if TREX*/
608           | '(' patfields ')'           {
609 #if TREX
610                                          $$ = gc3(revOnto($2,nameNoRec));
611 #else
612                                          $$ = gc3(NIL);
613 #endif
614                                         }
615           | '(' patfields '|' pat ')'   {$$ = gc5(revOnto($2,$4));}
616 /*#endif TREX*/
617           ;
618 pats2     : pats2 ',' pat               {$$ = gc3(cons($3,$1));}
619           | pat ',' pat                 {$$ = gc3(cons($3,singleton($1)));}
620           ;
621 pats1     : pats1 ',' pat               {$$ = gc3(cons($3,$1));}
622           | pat                         {$$ = gc1(singleton($1));}
623           ;
624 patbinds  : /* empty */                 {$$ = gc0(NIL);}
625           | patbinds1                   {$$ = gc1(rev($1));}
626           ;
627 patbinds1 : patbinds1 ',' patbind       {$$ = gc3(cons($3,$1));}
628           | patbind                     {$$ = gc1(singleton($1));}
629           ;
630 patbind   : qvar '=' pat                {$$ = gc3(pair($1,$3));}
631           | var                         {$$ = $1;}
632           ;
633 /*#if TREX*/
634 patfields : patfields ',' patfield      {$$ = gc3(cons($3,$1));}
635           | patfield                    {$$ = gc1(singleton($1));}
636           ;
637 patfield  : varid '=' pat               {
638 #if TREX
639                                          $$ = gc3(ap(mkExt(textOf($1)),$3));
640 #else
641                                          noTREX("a pattern");
642 #endif
643                                         }
644           ;
645 /*#endif TREX*/
646
647 /*- Expressions: ----------------------------------------------------------*/
648
649 exp       : exp_err                     {$$ = $1;}
650           | error                       {syntaxError("expression");}
651           ;
652 exp_err   : exp0a COCO sigType          {$$ = gc3(ap(ESIGN,pair($1,$3)));}
653           | exp0                        {$$ = $1;}
654           ;
655 exp0      : exp0a                       {$$ = $1;}
656           | exp0b                       {$$ = $1;}
657           ;
658 exp0a     : infixExpa                   {$$ = gc1(ap(INFIX,$1));}
659           | exp10a                      {$$ = $1;}
660           ;
661 exp0b     : infixExpb                   {$$ = gc1(ap(INFIX,$1));}
662           | exp10b                      {$$ = $1;}
663           ;
664 infixExpa : infixExpa qop '-' exp10a    {$$ = gc4(ap(NEG,ap(ap($2,$1),$4)));}
665           | infixExpa qop exp10a        {$$ = gc3(ap(ap($2,$1),$3));}
666           | '-' exp10a                  {$$ = gc2(ap(NEG,only($2)));}
667           | exp10a qop '-' exp10a       {$$ = gc4(ap(NEG,
668                                                      ap(ap($2,only($1)),$4)));}
669           | exp10a qop exp10a           {$$ = gc3(ap(ap($2,only($1)),$3));}
670           ;
671 infixExpb : infixExpa qop '-' exp10b    {$$ = gc4(ap(NEG,ap(ap($2,$1),$4)));}
672           | infixExpa qop exp10b        {$$ = gc3(ap(ap($2,$1),$3));}
673           | '-' exp10b                  {$$ = gc2(ap(NEG,only($2)));}
674           | exp10a qop '-' exp10b       {$$ = gc4(ap(NEG,
675                                                      ap(ap($2,only($1)),$4)));}
676           | exp10a qop exp10b           {$$ = gc3(ap(ap($2,only($1)),$3));}
677           ;
678 exp10a    : CASEXP exp OF '{' alts end  {$$ = gc6(ap(CASE,pair($2,rev($5))));}
679           | DO '{' stmts end            {$$ = gc4(ap(DOCOMP,checkDo($3)));}
680           | appExp                      {$$ = $1;}
681           ;
682 exp10b    : '\\' pats ARROW exp         {$$ = gc4(ap(LAMBDA,      
683                                                      pair(rev($2),
684                                                           pair($3,$4))));}
685           | LET decls IN exp            {$$ = gc4(letrec($2,$4));}
686           | IF exp THEN exp ELSE exp    {$$ = gc6(ap(COND,triple($2,$4,$6)));}
687           ;
688 pats      : pats apat                   {$$ = gc2(cons($2,$1));}
689           | apat                        {$$ = gc1(cons($1,NIL));}
690           ;
691 appExp    : appExp aexp                 {$$ = gc2(ap($1,$2));}
692           | aexp                        {$$ = $1;}
693           ;
694 aexp      : qvar                        {$$ = $1;}
695           | qvar '@' aexp               {$$ = gc3(ap(ASPAT,pair($1,$3)));}
696           | '~' aexp                    {$$ = gc2(ap(LAZYPAT,$2));}
697           | '_'                         {$$ = gc1(WILDCARD);}
698           | gcon                        {$$ = $1;}
699           | qcon '{' fbinds '}'         {$$ = gc4(ap(CONFLDS,pair($1,$3)));}
700           | aexp '{' fbinds '}'         {$$ = gc4(ap(UPDFLDS,
701                                                      triple($1,NIL,$3)));}
702           | NUMLIT                      {$$ = $1;}
703           | CHARLIT                     {$$ = $1;}
704           | STRINGLIT                   {$$ = $1;}
705           | REPEAT                      {$$ = $1;}
706           | '(' exp ')'                 {$$ = gc3($2);}
707           | '(' exps2 ')'               {$$ = gc3(buildTuple($2));}
708 /*#if TREX*/
709           | '(' vfields ')'             {
710 #if TREX
711                                          $$ = gc3(revOnto($2,nameNoRec));
712 #else
713                                          $$ = gc3(NIL);
714 #endif
715                                         }
716           | '(' vfields '|' exp ')'     {$$ = gc5(revOnto($2,$4));}
717           | RECSELID                    {$$ = $1;}
718 /*#endif*/
719           | '[' list ']'                {$$ = gc3($2);}
720           | '(' exp10a qop ')'          {$$ = gc4(ap($3,$2));}
721           | '(' qvarop_mi exp0 ')'      {$$ = gc4(ap(ap(nameFlip,$2),$3));}
722           | '(' qconop exp0 ')'         {$$ = gc4(ap(ap(nameFlip,$2),$3));}
723           ;
724 exps2     : exps2 ',' exp               {$$ = gc3(cons($3,$1));}
725           | exp ',' exp                 {$$ = gc3(cons($3,cons($1,NIL)));}
726           ;
727 /*#if TREX*/
728 vfields   : vfields ',' vfield          {$$ = gc3(cons($3,$1));}
729           | vfield                      {$$ = gc1(singleton($1));}
730           ;
731 vfield    : varid '=' exp               {
732 #if TREX
733                                          $$ = gc3(ap(mkExt(textOf($1)),$3));
734 #else
735                                          noTREX("an expression");
736 #endif
737                                         }
738           ;
739 /*#endif*/
740 alts      : alts1                       {$$ = $1;}
741           | alts1 ';'                   {$$ = gc2($1);}
742           ;
743 alts1     : alts1 ';' alt               {$$ = gc3(cons($3,$1));}
744           | alt                         {$$ = gc1(cons($1,NIL));}
745           ;
746 alt       : pat altRhs wherePart        {$$ = gc3(pair($1,letrec($3,$2)));}
747           ;
748 altRhs    : guardAlts                   {$$ = gc1(grded(rev($1)));}
749           | ARROW exp                   {$$ = gc2(pair($1,$2));}
750           | error                       {syntaxError("case expression");}
751           ;
752 guardAlts : guardAlts guardAlt          {$$ = gc2(cons($2,$1));}
753           | guardAlt                    {$$ = gc1(cons($1,NIL));}
754           ;
755 guardAlt  : '|' exp0 ARROW exp          {$$ = gc4(pair($3,pair($2,$4)));}
756           ;
757 stmts     : stmts1 ';'                  {$$ = gc2($1);}
758           | stmts1                      {$$ = $1;}
759           ;
760 stmts1    : stmts1 ';' stmt             {$$ = gc3(cons($3,$1));}
761           | stmt                        {$$ = gc1(cons($1,NIL));}
762           ;
763 stmt      : exp_err FROM exp            {$$ = gc3(ap(FROMQUAL,pair($1,$3)));}
764           | LET decls                   {$$ = gc2(ap(QWHERE,$2));}
765 /*        | IF exp                      {$$ = gc2(ap(BOOLQUAL,$2));}*/
766           | exp_err                     {$$ = gc1(ap(DOQUAL,$1));}
767           ;
768 fbinds    : /* empty */                 {$$ = gc0(NIL);}
769           | fbinds1                     {$$ = gc1(rev($1));}
770           ;
771 fbinds1   : fbinds1 ',' fbind           {$$ = gc3(cons($3,$1));}
772           | fbind                       {$$ = gc1(singleton($1));}
773           ;
774 fbind     : var                         {$$ = $1;}
775           | qvar '=' exp                {$$ = gc3(pair($1,$3));}
776           ;
777
778 /*- List Expressions: -------------------------------------------------------*/
779
780 list      : exp                         {$$ = gc1(ap(FINLIST,cons($1,NIL)));}
781           | exps2                       {$$ = gc1(ap(FINLIST,rev($1)));}
782           | exp '|' quals               {$$ = gc3(ap(COMP,pair($1,rev($3))));}
783           | exp         UPTO exp        {$$ = gc3(ap(ap(nameFromTo,$1),$3));}
784           | exp ',' exp UPTO            {$$ = gc4(ap(ap(nameFromThen,$1),$3));}
785           | exp         UPTO            {$$ = gc2(ap(nameFrom,$1));}
786           | exp ',' exp UPTO exp        {$$ = gc5(ap(ap(ap(nameFromThenTo,
787                                                                 $1),$3),$5));}
788           ;
789 quals     : quals ',' qual              {$$ = gc3(cons($3,$1));}
790           | qual                        {$$ = gc1(cons($1,NIL));}
791           ;
792 qual      : exp FROM exp                {$$ = gc3(ap(FROMQUAL,pair($1,$3)));}
793           | exp                         {$$ = gc1(ap(BOOLQUAL,$1));}
794           | LET decls                   {$$ = gc2(ap(QWHERE,$2));}
795           ;
796
797 /*- Identifiers and symbols: ----------------------------------------------*/
798
799 gcon      : qcon                        {$$ = $1;}
800           | '(' ')'                     {$$ = gc2(nameUnit);}
801           | '[' ']'                     {$$ = gc2(nameNil);}
802           | '(' tupCommas ')'           {$$ = gc3($2);}
803           ;
804 tupCommas : tupCommas ','               {$$ = gc2(mkTuple(tupleOf($1)+1));}
805           | ','                         {$$ = gc1(mkTuple(2));}
806           ;
807 varid     : VARID                       {$$ = $1;}
808           | HIDING                      {$$ = gc1(varHiding);}
809           | QUALIFIED                   {$$ = gc1(varQualified);}
810           | ASMOD                       {$$ = gc1(varAsMod);}
811           ;
812 qconid    : QCONID                      {$$ = $1;}
813           | CONID                       {$$ = $1;}
814           ;
815 var       : varid                       {$$ = $1;}
816           | '(' VAROP ')'               {$$ = gc3($2);}
817           | '(' '+' ')'                 {$$ = gc3(varPlus);}
818           | '(' '-' ')'                 {$$ = gc3(varMinus);}
819           | '(' '!' ')'                 {$$ = gc3(varBang);}
820           | '(' '.' ')'                 {$$ = gc3(varDot);}
821           ;
822 qvar      : QVARID                      {$$ = $1;}
823           | '(' QVAROP ')'              {$$ = gc3($2);}
824           | var                         {$$ = $1;}
825           ;
826 con       : CONID                       {$$ = $1;}
827           | '(' CONOP ')'               {$$ = gc3($2);}
828           ;
829 qcon      : QCONID                      {$$ = $1;}
830           | '(' QCONOP ')'              {$$ = gc3($2);}
831           | con                         {$$ = $1;}
832           ;
833 varop     : '+'                         {$$ = gc1(varPlus);}
834           | '-'                         {$$ = gc1(varMinus);}
835           | varop_mipl                  {$$ = $1;}
836           ;
837 varop_mi  : '+'                         {$$ = gc1(varPlus);}
838           | varop_mipl                  {$$ = $1;}
839           ;
840 varop_pl  : '-'                         {$$ = gc1(varMinus);}
841           | varop_mipl                  {$$ = $1;}
842           ;
843 varop_mipl: VAROP                       {$$ = $1;}
844           | '`' varid '`'               {$$ = gc3($2);}
845           | '!'                         {$$ = gc1(varBang);}
846           | '.'                         {$$ = gc1(varDot);}
847           ;
848 qvarop    : '-'                         {$$ = gc1(varMinus);}
849           | qvarop_mi                   {$$ = $1;}
850           ;
851 qvarop_mi : QVAROP                      {$$ = $1;}
852           | '`' QVARID '`'              {$$ = gc3($2);}
853           | varop_mi                    {$$ = $1;}
854           ;
855
856 conop     : CONOP                       {$$ = $1;}
857           | '`' CONID  '`'              {$$ = gc3($2);}
858           ;
859 qconop    : QCONOP                      {$$ = $1;}
860           | '`' QCONID '`'              {$$ = gc3($2);}
861           | conop                       {$$ = $1;}
862           ;
863 op        : varop                       {$$ = $1;}
864           | conop                       {$$ = $1;}
865           ;
866 qop       : qvarop                      {$$ = $1;}
867           | qconop                      {$$ = $1;}
868           ;
869
870 /*- Stuff from STG hugs ---------------------------------------------------*/
871
872 qvarid    : varid1                      {$$ = gc1($1);}
873           | QVARID                      {$$ = gc1($1);}
874
875 varid1    : VARID                       {$$ = gc1($1);}
876           | HIDING                      {$$ = gc1(varHiding);}
877           | QUALIFIED                   {$$ = gc1(varQualified);}
878           | ASMOD                       {$$ = gc1(varAsMod);}
879           ;
880
881 /*- Tricks to force insertion of leading and closing braces ---------------*/
882
883 begin     : error                       {yyerrok; goOffside(startColumn);}
884           ;
885                                         /* deal with trailing semicolon    */
886 end       : '}'                         {$$ = $1;}
887           | error                       {yyerrok; 
888                                          if (canUnOffside()) {
889                                              unOffside();
890                                              /* insert extra token on stack*/
891                                              push(NIL);
892                                              pushed(0) = pushed(1);
893                                              pushed(1) = mkInt(column);
894                                          }
895                                          else
896                                              syntaxError("definition");
897                                         }
898           ;
899
900 /*-------------------------------------------------------------------------*/
901
902 %%
903
904 static Cell local gcShadow(n,e)         /* keep parsed fragments on stack  */
905 Int  n;
906 Cell e; {
907     /* If a look ahead token is held then the required stack transformation
908      * is:
909      *   pushed: n               1     0          1     0
910      *           x1  |  ...  |  xn  |  la   ===>  e  |  la
911      *                                top()            top()
912      *
913      * Othwerwise, the transformation is:
914      *   pushed: n-1             0        0
915      *           x1  |  ...  |  xn  ===>  e
916      *                         top()     top()
917      */
918     if (yychar>=0) {
919         pushed(n-1) = top();
920         pushed(n)   = e;
921     }
922     else
923         pushed(n-1) = e;
924     sp -= (n-1);
925     return e;
926 }
927
928 static Void local syntaxError(s)        /* report on syntax error          */
929 String s; {
930     ERRMSG(row) "Syntax error in %s (unexpected %s)", s, unexpected()
931     EEND;
932 }
933
934 static String local unexpected() {     /* find name for unexpected token   */
935     static char buffer[100];
936     static char *fmt = "%s \"%s\"";
937     static char *kwd = "keyword";
938
939     switch (yychar) {
940         case 0         : return "end of input";
941
942 #define keyword(kw) sprintf(buffer,fmt,kwd,kw); return buffer;
943         case INFIXL    : keyword("infixl");
944         case INFIXR    : keyword("infixr");
945         case INFIXN    : keyword("infix");
946         case FOREIGN   : keyword("foreign");
947         case UNSAFE    : keyword("unsafe");
948         case TINSTANCE : keyword("instance");
949         case TCLASS    : keyword("class");
950         case CASEXP    : keyword("case");
951         case OF        : keyword("of");
952         case IF        : keyword("if");
953         case THEN      : keyword("then");
954         case ELSE      : keyword("else");
955         case WHERE     : keyword("where");
956         case TYPE      : keyword("type");
957         case DATA      : keyword("data");
958         case TNEWTYPE  : keyword("newtype");
959         case LET       : keyword("let");
960         case IN        : keyword("in");
961         case DERIVING  : keyword("deriving");
962         case DEFAULT   : keyword("default");
963         case IMPORT    : keyword("import");
964         case TMODULE   : keyword("module");
965         case ALL       : keyword("forall");
966 #undef keyword
967
968         case ARROW     : return "`->'";
969         case '='       : return "`='";
970         case COCO      : return "`::'";
971         case '-'       : return "`-'";
972         case '!'       : return "`!'";
973         case ','       : return "comma";
974         case '@'       : return "`@'";
975         case '('       : return "`('";
976         case ')'       : return "`)'";
977         case '{'       : return "`{'";
978         case '}'       : return "`}'";
979         case '_'       : return "`_'";
980         case '|'       : return "`|'";
981         case '.'       : return "`.'";
982         case ';'       : return "`;'";
983         case UPTO      : return "`..'";
984         case '['       : return "`['";
985         case ']'       : return "`]'";
986         case FROM      : return "`<-'";
987         case '\\'      : return "backslash (lambda)";
988         case '~'       : return "tilde";
989         case '`'       : return "backquote";
990 #if TREX
991         case RECSELID  : sprintf(buffer,"selector \"#%s\"",
992                                  textToStr(extText(snd(yylval))));
993                          return buffer;
994 #endif
995         case VAROP     :
996         case VARID     :
997         case CONOP     :
998         case CONID     : sprintf(buffer,"symbol \"%s\"",
999                                  textToStr(textOf(yylval)));
1000                          return buffer;
1001         case QVAROP    :
1002         case QVARID    :
1003         case QCONOP    : 
1004         case QCONID    : sprintf(buffer,"symbol \"%s\"",
1005                                  identToStr(yylval));
1006                          return buffer;
1007         case HIDING    : return "symbol \"hiding\"";
1008         case QUALIFIED : return "symbol \"qualified\"";
1009         case ASMOD     : return "symbol \"as\"";
1010         case NUMLIT    : return "numeric literal";
1011         case CHARLIT   : return "character literal";
1012         case STRINGLIT : return "string literal";
1013         case IMPLIES   : return "`=>'";
1014         default        : return "token";
1015     }
1016 }
1017
1018 static Cell local checkPrec(p)          /* Check for valid precedence value*/
1019 Cell p; {
1020     if (!isInt(p) || intOf(p)<MIN_PREC || intOf(p)>MAX_PREC) {
1021         ERRMSG(row) "Precedence value must be an integer in the range [%d..%d]",
1022                     MIN_PREC, MAX_PREC
1023         EEND;
1024     }
1025     return p;
1026 }
1027
1028 static Cell local buildTuple(tup)       /* build tuple (x1,...,xn) from    */
1029 List tup; {                             /* list [xn,...,x1]                */
1030     Int  n = 0;
1031     Cell t = tup;
1032     Cell x;
1033
1034     do {                                /*    .                    .       */
1035         x      = fst(t);                /*   / \                  / \      */
1036         fst(t) = snd(t);                /*  xn  .                .   xn    */
1037         snd(t) = x;                     /*       .    ===>      .          */
1038         x      = t;                     /*        .            .           */
1039         t      = fun(x);                /*         .          .            */
1040         n++;                            /*        / \        / \           */
1041     } while (nonNull(t));               /*       x1  NIL   (n)  x1         */
1042     fst(x) = mkTuple(n);
1043     return tup;
1044 }
1045
1046 static List local checkContext(con)     /* validate context                */
1047 Type con; {
1048     mapOver(checkPred, con);
1049     return con;
1050 }
1051
1052 static Cell local checkPred(c)          /* check that type expr is a valid */
1053 Cell c; {                               /* constraint                      */
1054     Cell cn = getHead(c);
1055 #if TREX
1056     if (isExt(cn) && argCount==1)
1057         return c;
1058 #endif
1059     if (!isQCon(cn) || argCount==0)
1060         syntaxError("class expression");
1061     return c;
1062 }
1063
1064 static Pair local checkDo(dqs)          /* convert reversed list of dquals */
1065 List dqs; {                             /* to an (expr,quals) pair         */
1066     if (isNull(dqs) || whatIs(hd(dqs))!=DOQUAL) {
1067         ERRMSG(row) "Last generator in do {...} must be an expression"
1068         EEND;
1069     }
1070     fst(dqs) = snd(fst(dqs));           /* put expression in fst of pair   */
1071     snd(dqs) = rev(snd(dqs));           /* & reversed list of quals in snd */
1072     return dqs;
1073 }
1074
1075 static Cell local checkTyLhs(c)         /* check that lhs is of the form   */
1076 Cell c; {                               /* T a1 ... a                      */
1077     Cell tlhs = c;
1078     while (isAp(tlhs) && whatIs(arg(tlhs))==VARIDCELL)
1079         tlhs = fun(tlhs);
1080     switch (whatIs(tlhs)) {
1081         case CONIDCELL  : return c;
1082
1083         default :
1084             ERRMSG(row) "Illegal left hand side in datatype definition"
1085             EEND;
1086     }
1087     return 0; /* NOTREACHED */
1088 }
1089
1090 #if !TREX
1091 static Void local noTREX(where)
1092 String where; {
1093     ERRMSG(row) "Attempt to use TREX records while parsing %s.\n", where ETHEN
1094     ERRTEXT     "(TREX is disabled in this build of Hugs)"
1095     EEND;
1096 }
1097 #endif
1098
1099 /*-------------------------------------------------------------------------*/