[project @ 1999-11-29 18:59:23 by sewardj]
[ghc-hetmet.git] / ghc / interpreter / static.c
1
2 /* --------------------------------------------------------------------------
3  * Static Analysis for Hugs
4  *
5  * The Hugs 98 system is Copyright (c) Mark P Jones, Alastair Reid, the
6  * Yale Haskell Group, and the Oregon Graduate Institute of Science and
7  * Technology, 1994-1999, All rights reserved.  It is distributed as
8  * free software under the license in the file "License", which is
9  * included in the distribution.
10  *
11  * $RCSfile: static.c,v $
12  * $Revision: 1.18 $
13  * $Date: 1999/11/29 18:59:30 $
14  * ------------------------------------------------------------------------*/
15
16 #include "prelude.h"
17 #include "storage.h"
18 #include "backend.h"
19 #include "connect.h"
20 #include "link.h"
21 #include "errors.h"
22 #include "subst.h"
23
24 /* --------------------------------------------------------------------------
25  * local function prototypes:
26  * ------------------------------------------------------------------------*/
27
28 static Void   local kindError           Args((Int,Constr,Constr,String,Kind,Int));
29 static Void   local checkQualImport     Args((Pair));
30 static Void   local checkUnqualImport   Args((Triple));
31
32 static Name   local lookupName          Args((Text,List));
33 static List   local checkSubentities    Args((List,List,List,String,Text));
34 static List   local checkExportTycon    Args((List,Text,Cell,Tycon));
35 static List   local checkExportClass    Args((List,Text,Cell,Class));
36 static List   local checkExport         Args((List,Text,Cell));
37 static List   local checkImportEntity   Args((List,Module,Cell));
38 static List   local resolveImportList   Args((Module,Cell));
39 static Void   local checkImportList     Args((Pair));
40
41 static Void   local importEntity        Args((Module,Cell));
42 static Void   local importName          Args((Module,Name));
43 static Void   local importTycon         Args((Module,Tycon));
44 static Void   local importClass         Args((Module,Class));
45 static List   local checkExports        Args((List));
46
47 static Void   local checkTyconDefn      Args((Tycon));
48 static Void   local depConstrs          Args((Tycon,List,Cell));
49 static List   local addSels             Args((Int,Name,List,List));
50 static List   local selectCtxt          Args((List,List));
51 static Void   local checkSynonyms       Args((List));
52 static List   local visitSyn            Args((List,Tycon,List));
53 static Type   local instantiateSyn      Args((Type,Type));
54
55 static Void   local checkClassDefn      Args((Class));
56 static Cell   local depPredExp          Args((Int,List,Cell));
57 static Void   local checkMems           Args((Class,List,Cell));
58 static Void   local checkMems2           Args((Class,Cell));
59 static Void   local addMembers          Args((Class));
60 static Name   local newMember           Args((Int,Int,Cell,Type,Class));
61 static Name   local newDSel             Args((Class,Int));
62 static Text   local generateText        Args((String,Class));
63 static Int    local visitClass          Args((Class));
64
65 static List   local classBindings       Args((String,Class,List));
66 static Name   local memberName          Args((Class,Text));
67 static List   local numInsert           Args((Int,Cell,List));
68
69 static List   local maybeAppendVar      Args((Cell,List));
70
71 static Type   local checkSigType        Args((Int,String,Cell,Type));
72 static Void   local checkOptQuantVars   Args((Int,List,List));
73 static Type   local depTopType          Args((Int,List,Type));
74 static Type   local depCompType         Args((Int,List,Type));
75 static Type   local depTypeExp          Args((Int,List,Type));
76 static Type   local depTypeVar          Args((Int,List,Text));
77 static List   local checkQuantVars      Args((Int,List,List,Cell));
78 static List   local otvars              Args((Cell,List));
79 static Bool   local osubset             Args((List,List));
80 static Void   local kindConstr          Args((Int,Int,Int,Constr));
81 static Kind   local kindAtom            Args((Int,Constr));
82 static Void   local kindPred            Args((Int,Int,Int,Cell));
83 static Void   local kindType            Args((Int,String,Type));
84 static Void   local fixKinds            Args((Void));
85
86 static Void   local kindTCGroup         Args((List));
87 static Void   local initTCKind          Args((Cell));
88 static Void   local kindTC              Args((Cell));
89 static Void   local genTC               Args((Cell));
90
91 static Void   local checkInstDefn       Args((Inst));
92 static Void   local insertInst          Args((Inst));
93 static Bool   local instCompare         Args((Inst,Inst));
94 static Name   local newInstImp          Args((Inst));
95 static Void   local kindInst            Args((Inst,Int));
96 static Void   local checkDerive         Args((Tycon,List,List,Cell));
97 static Void   local addDerInst          Args((Int,Class,List,List,Type,Int));
98 static Void   local deriveContexts      Args((List));
99 static Void   local initDerInst         Args((Inst));
100 static Void   local calcInstPreds       Args((Inst));
101 static Void   local maybeAddPred        Args((Cell,Int,Int,List));
102 static List   local calcFunDeps         Args((List));
103 static Cell   local copyAdj             Args((Cell,Int,Int));
104 static Void   local tidyDerInst         Args((Inst));
105 static List   local otvarsZonk          Args((Cell,List,Int));
106
107 static Void   local addDerivImp         Args((Inst));
108
109 static Void   local checkDefaultDefns   Args((Void));
110
111 static Void   local checkForeignImport Args((Name));
112 static Void   local checkForeignExport Args((Name));
113
114 static Cell   local tidyInfix           Args((Int,Cell));
115 static Pair   local attachFixity        Args((Int,Cell));
116 static Syntax local lookupSyntax        Args((Text));
117
118 static Cell   local checkPat            Args((Int,Cell));
119 static Cell   local checkMaybeCnkPat    Args((Int,Cell));
120 static Cell   local checkApPat          Args((Int,Int,Cell));
121 static Void   local addToPatVars        Args((Int,Cell));
122 static Name   local conDefined          Args((Int,Cell));
123 static Void   local checkIsCfun         Args((Int,Name));
124 static Void   local checkCfunArgs       Args((Int,Cell,Int));
125 static Cell   local checkPatType        Args((Int,String,Cell,Type));
126 static Cell   local applyBtyvs          Args((Cell));
127 static Cell   local bindPat             Args((Int,Cell));
128 static Void   local bindPats            Args((Int,List));
129
130 static List   local extractSigdecls     Args((List));
131 static List   local extractFixdecls     Args((List));
132 static List   local extractBindings     Args((List));
133 static List   local getPatVars          Args((Int,Cell,List));
134 static List   local addPatVar           Args((Int,Cell,List));
135 static List   local eqnsToBindings      Args((List,List,List,List));
136 static Void   local notDefined          Args((Int,List,Cell));
137 static Cell   local findBinding         Args((Text,List));
138 static Cell   local getAttr             Args((List,Cell));
139 static Void   local addSigdecl          Args((List,Cell));
140 static Void   local addFixdecl          Args((List,List,List,List,Triple));
141 static Void   local dupFixity           Args((Int,Text));
142 static Void   local missFixity          Args((Int,Text));
143
144 static List   local dependencyAnal      Args((List));
145 static List   local topDependAnal       Args((List));
146 static Void   local addDepField         Args((Cell));
147 static Void   local remDepField         Args((List));
148 static Void   local remDepField1        Args((Cell));
149 static Void   local clearScope          Args((Void));
150 static Void   local withinScope         Args((List));
151 static Void   local leaveScope          Args((Void));
152 static Void   local saveSyntax          Args((Cell,Cell));
153
154 static Void   local depBinding          Args((Cell));
155 static Void   local depDefaults         Args((Class));
156 static Void   local depInsts            Args((Inst));
157 static Void   local depClassBindings    Args((List));
158 static Void   local depAlt              Args((Cell));
159 static Void   local depRhs              Args((Cell));
160 static Void   local depGuard            Args((Cell));
161 static Cell   local depExpr             Args((Int,Cell));
162 static Void   local depPair             Args((Int,Cell));
163 static Void   local depTriple           Args((Int,Cell));
164 static Void   local depComp             Args((Int,Cell,List));
165 static Void   local depCaseAlt          Args((Int,Cell));
166 static Cell   local depVar              Args((Int,Cell));
167 static Cell   local depQVar             Args((Int,Cell));
168 static Void   local depConFlds          Args((Int,Cell,Bool));
169 static Void   local depUpdFlds          Args((Int,Cell));
170 static List   local depFields           Args((Int,Cell,List,Bool));
171 #if IPARAM
172 static Void   local depWith             Args((Int,Cell));
173 static List   local depDwFlds           Args((Int,Cell,List));
174 #endif
175 #if TREX
176 static Cell   local depRecord           Args((Int,Cell));
177 #endif
178
179 static List   local tcscc               Args((List,List));
180 static List   local bscc                Args((List));
181
182 static Void   local addRSsigdecls       Args((Pair));
183 static Void   local allNoPrevDef        Args((Cell));
184 static Void   local noPrevDef           Args((Int,Cell));
185 static Bool   local odiff               Args((List,List));
186  
187 static Void   local duplicateErrorAux   Args((Int,Module,Text,String));
188 #define duplicateError(l,m,t,k) duplicateErrorAux(l,m,t,k)
189 static Void   local checkTypeIn         Args((Pair));
190
191 /* --------------------------------------------------------------------------
192  * The code in this file is arranged in roughly the following order:
193  *  - Kind inference preliminaries
194  *  - Module declarations
195  *  - Type declarations (data, type, newtype, type in)
196  *  - Class declarations
197  *  - Type signatures
198  *  - Instance declarations
199  *  - Default declarations
200  *  - Primitive definitions
201  *  - Patterns
202  *  - Infix expressions
203  *  - Value definitions
204  *  - Top-level static analysis and control
205  *  - Haskell 98 compatibility tests
206  * ------------------------------------------------------------------------*/
207
208 /* --------------------------------------------------------------------------
209  * Kind checking preliminaries:
210  * ------------------------------------------------------------------------*/
211
212 Bool kindExpert = FALSE;                /* TRUE => display kind errors in  */
213                                         /*         full detail             */
214
215 static Void local kindError(l,c,in,wh,k,o)
216 Int    l;                               /* line number near constuctor exp */
217 Constr c;                               /* constructor                     */
218 Constr in;                              /* context (if any)                */
219 String wh;                              /* place in which error occurs     */
220 Kind   k;                               /* expected kind (k,o)             */
221 Int    o; {                             /* inferred kind (typeIs,typeOff)  */
222     clearMarks();
223
224     if (!kindExpert) {                  /* for those with a fear of kinds  */
225         ERRMSG(l) "Illegal type" ETHEN
226         if (nonNull(in)) {
227             ERRTEXT " \"" ETHEN ERRTYPE(in);
228             ERRTEXT "\""  ETHEN
229         }
230         ERRTEXT " in %s\n", wh
231         EEND;
232     }
233
234     ERRMSG(l) "Kind error in %s", wh ETHEN
235     if (nonNull(in)) {
236         ERRTEXT "\n*** expression     : " ETHEN ERRTYPE(in);
237     }
238     ERRTEXT "\n*** constructor    : " ETHEN ERRTYPE(c);
239     ERRTEXT "\n*** kind           : " ETHEN ERRKIND(copyType(typeIs,typeOff));
240     ERRTEXT "\n*** does not match : " ETHEN ERRKIND(copyType(k,o));
241     if (unifyFails) {
242         ERRTEXT "\n*** because        : %s", unifyFails ETHEN
243     }
244     ERRTEXT "\n"
245     EEND;
246 }
247
248 #define shouldKind(l,c,in,wh,k,o)       if (!kunify(typeIs,typeOff,k,o)) \
249                                             kindError(l,c,in,wh,k,o)
250 #define checkKind(l,a,m,c,in,wh,k,o)    kindConstr(l,a,m,c); \
251                                         shouldKind(l,c,in,wh,k,o)
252 #define inferKind(k,o)                  typeIs=k; typeOff=o
253
254 static List unkindTypes;                /* types in need of kind annotation*/
255 #if TREX
256 Kind   extKind;                         /* Kind of extension, *->row->row  */
257 #endif
258
259 /* --------------------------------------------------------------------------
260  * Static analysis of modules:
261  * ------------------------------------------------------------------------*/
262
263 #if HSCRIPT
264 String reloadModule;
265 #endif
266
267 Void startModule(nm)                             /* switch to a new module */
268 Cell nm; {
269     Module m;
270     if (!isCon(nm)) internal("startModule");
271     if (isNull(m = findModule(textOf(nm))))
272         m = newModule(textOf(nm));
273     else if (!isPreludeScript()) {
274         /* You're allowed to break the rules in the Prelude! */
275 #if HSCRIPT
276         reloadModule = textToStr(textOf(nm));
277 #endif
278         ERRMSG(0) "Module \"%s\" already loaded", textToStr(textOf(nm))
279         EEND;
280     }
281     setCurrModule(m);
282 }
283
284 Void setExportList(exps)              /* Add export list to current module */
285 List exps; {
286     module(currentModule).exports = exps;
287 }
288
289 Void addQualImport(orig,new)         /* Add to qualified import list       */
290 Cell orig;     /* Original name of module                                  */
291 Cell new;  {   /* Name module is called within this module (or NIL)        */
292     module(currentModule).qualImports = 
293       cons(pair(isNull(new)?orig:new,orig),module(currentModule).qualImports);
294 }
295
296 Void addUnqualImport(mod,entities)     /* Add to unqualified import list   */
297 Cell mod;         /* Name of module                                        */
298 List entities;  { /* List of entity names                                  */
299     unqualImports = cons(pair(mod,entities),unqualImports);
300 }
301
302 static Void local checkQualImport(i)   /* Process qualified import         */
303 Pair i; {
304     Module m = findModid(snd(i));
305     if (isNull(m)) {
306         ERRMSG(0) "Module \"%s\" not previously loaded", 
307                   textToStr(textOf(snd(i)))
308         EEND;
309     }
310     snd(i)=m;
311 }
312
313 static Void local checkUnqualImport(i) /* Process unqualified import       */
314 Pair i; {
315     Module m = findModid(fst(i));
316     if (isNull(m)) {
317         ERRMSG(0) "Module \"%s\" not previously loaded", 
318                   textToStr(textOf(fst(i)))
319         EEND;
320     }
321     fst(i)=m;
322 }
323
324 static Name local lookupName(t,nms)    /* find text t in list of Names     */
325 Text t;
326 List nms; { /* :: [Name] */
327     for(; nonNull(nms); nms=tl(nms)) {
328         if (t == name(hd(nms)).text)
329             return hd(nms);
330     }
331     return NIL;
332 }
333
334 static List local checkSubentities(imports,named,wanted,description,textParent)
335 List   imports;
336 List   named;       /* :: [ Q?(Var|Con)(Id|Op) ]                  */
337 List   wanted;      /* :: [Name]                                  */
338 String description; /* "<constructor>|<member> of <type>|<class>" */
339 Text   textParent; {
340     for(; nonNull(named); named=tl(named)) {
341         Pair x = hd(named);
342         /* ToDo: ignores qualifier; doesn't check that entity is in scope */
343         Text t = isPair(snd(x)) ? qtextOf(x) : textOf(x);
344         Name n = lookupName(t,wanted);
345         if (isNull(n)) {
346             ERRMSG(0) "Entity \"%s\" is not a %s \"%s\"",
347                       textToStr(t),
348                       description,
349                       textToStr(textParent)
350             EEND;
351         }
352         imports = cons(n,imports);
353     }
354     return imports;
355 }
356
357 static List local checkImportEntity(imports,exporter,entity)
358 List   imports; /* Accumulated list of things to import */
359 Module exporter;
360 Cell   entity; { /* Entry from import list */
361     List oldImports = imports;
362     Text t  = isIdent(entity) ? textOf(entity) : textOf(fst(entity));
363     List es = module(exporter).exports; 
364     for(; nonNull(es); es=tl(es)) {
365         Cell e = hd(es); /* :: Entity | (Entity, NIL|DOTDOT) */
366         if (isPair(e)) {
367             Cell f = fst(e);
368             if (isTycon(f)) {
369                 if (tycon(f).text == t) {
370                     imports = cons(f,imports);
371                     if (!isIdent(entity)) {
372                         switch (tycon(f).what) {
373                         case NEWTYPE:
374                         case DATATYPE:
375                             if (DOTDOT == snd(entity)) {
376                                 imports=dupOnto(tycon(f).defn,imports);
377                             } else {
378                                 imports=checkSubentities(imports,snd(entity),tycon(f).defn,
379                                                          "constructor of type",t);
380                             }
381                             break;
382                         default:;
383                           /* deliberate fall thru */
384                         }
385                     }
386                 }
387             } else if (isClass(f)) {
388                 if (cclass(f).text == t) {
389                     imports = cons(f,imports);
390                     if (!isIdent(entity)) {
391                         if (DOTDOT == snd(entity)) {
392                             return dupOnto(cclass(f).members,imports);
393                         } else {
394                             return checkSubentities(imports,snd(entity),cclass(f).members,
395                                    "member of class",t);
396                         }
397                     }
398                 }
399             } else {
400                 internal("checkImportEntity2");
401             }
402         } else if (isName(e)) {
403             if (isIdent(entity) && name(e).text == t) {
404                 imports = cons(e,imports);
405             }
406         } else {
407             internal("checkImportEntity3");
408         }
409     }
410     if (imports == oldImports) {
411         ERRMSG(0) "Unknown entity \"%s\" imported from module \"%s\"",
412                   textToStr(t),
413                   textToStr(module(exporter ).text)
414         EEND;
415     }
416     return imports;
417 }
418
419 static List local resolveImportList(m,impList)
420 Module m;  /* exporting module */
421 Cell   impList; {
422     List imports = NIL;
423     if (DOTDOT == impList) {
424         List es = module(m).exports;
425         for(; nonNull(es); es=tl(es)) {
426             Cell e = hd(es);
427             if (isName(e)) {
428                 imports = cons(e,imports);
429             } else {
430                 Cell c = fst(e);
431                 List subentities = NIL;
432                 imports = cons(c,imports);
433                 if (isTycon(c)
434                     && (tycon(c).what == DATATYPE 
435                         || tycon(c).what == NEWTYPE))
436                     subentities = tycon(c).defn;
437                 else if (isClass(c))
438                     subentities = cclass(c).members;
439                 if (DOTDOT == snd(e)) {
440                     imports = dupOnto(subentities,imports);
441                 }
442             }
443         }
444     } else {
445         map1Accum(checkImportEntity,imports,m,impList);
446     }
447     return imports;
448 }
449
450 static Void local checkImportList(importSpec) /*Import a module unqualified*/
451 Pair importSpec; {
452     Module m       = fst(importSpec);
453     Cell   impList = snd(importSpec);
454
455     List   imports = NIL; /* entities we want to import */
456     List   hidden  = NIL; /* entities we want to hide   */
457
458     if (moduleThisScript(m)) { 
459         ERRMSG(0) "Module \"%s\" recursively imports itself",
460                   textToStr(module(m).text)
461         EEND;
462     }
463     if (isPair(impList) && HIDDEN == fst(impList)) {
464         /* Somewhat inefficient - but obviously correct:
465          * imports = importsOf("module Foo") `setDifference` hidden;
466          */
467         hidden  = resolveImportList(m, snd(impList));
468         imports = resolveImportList(m, DOTDOT);
469     } else {
470         imports = resolveImportList(m, impList);
471     }
472     for(; nonNull(imports); imports=tl(imports)) {
473         Cell e = hd(imports);
474         if (!cellIsMember(e,hidden))
475             importEntity(m,e);
476     }
477     /* ToDo: hang onto the imports list for processing export list entries
478      * of the form "module Foo"
479      */
480 }
481
482 static Void local importEntity(source,e)
483 Module source;
484 Cell e; {
485     switch (whatIs(e)) {
486       case NAME  : importName(source,e); 
487                    break;
488       case TYCON : importTycon(source,e); 
489                    break;
490       case CLASS : importClass(source,e);
491                    break;
492       default: internal("importEntity");
493     }
494 }
495
496 static Void local importName(source,n)
497 Module source;
498 Name n; {
499     Name clash = addName(n);
500     if (nonNull(clash) && clash!=n) {
501         ERRMSG(0) "Entity \"%s\" imported from module \"%s\" already defined in module \"%s\"",
502                   textToStr(name(n).text), 
503                   textToStr(module(source).text),
504                   textToStr(module(name(clash).mod).text)
505         EEND;
506     }
507 }
508
509 static Void local importTycon(source,tc)
510 Module source;
511 Tycon tc; {
512     Tycon clash=addTycon(tc);
513     if (nonNull(clash) && clash!=tc) {
514         ERRMSG(0) "Tycon \"%s\" imported from \"%s\" already defined in module \"%s\"",
515                   textToStr(tycon(tc).text),
516                   textToStr(module(source).text),
517                   textToStr(module(tycon(clash).mod).text)      
518         EEND;
519     }
520     if (nonNull(findClass(tycon(tc).text))) {
521         ERRMSG(0) "Import of type constructor \"%s\" clashes with class in module \"%s\"",
522                   textToStr(tycon(tc).text),
523                   textToStr(module(tycon(tc).mod).text) 
524         EEND;
525     }
526 }
527
528 static Void local importClass(source,c)
529 Module source;
530 Class c; {
531     Class clash=addClass(c);
532     if (nonNull(clash) && clash!=c) {
533         ERRMSG(0) "Class \"%s\" imported from \"%s\" already defined in module \"%s\"",
534                   textToStr(cclass(c).text),
535                   textToStr(module(source).text),
536                   textToStr(module(cclass(clash).mod).text)     
537         EEND;
538     }
539     if (nonNull(findTycon(cclass(c).text))) {
540         ERRMSG(0) "Import of class \"%s\" clashes with type constructor in module \"%s\"",
541                   textToStr(cclass(c).text),
542                   textToStr(module(source).text)        
543         EEND;
544     }
545 }
546
547 static List local checkExportTycon(exports,mt,spec,tc)
548 List  exports;
549 Text  mt;
550 Cell  spec; 
551 Tycon tc; {
552     if (DOTDOT == spec || SYNONYM == tycon(tc).what) {
553         return cons(pair(tc,DOTDOT), exports);
554     } else {
555         return cons(pair(tc,NIL), exports);
556     }
557 }
558
559 static List local checkExportClass(exports,mt,spec,cl)
560 List  exports;
561 Text  mt;
562 Class cl;
563 Cell  spec; {
564     if (DOTDOT == spec) {
565         return cons(pair(cl,DOTDOT), exports);
566     } else {
567         return cons(pair(cl,NIL), exports);
568     }
569 }
570
571 static List local checkExport(exports,mt,e) /* Process entry in export list*/
572 List exports;
573 Text mt; 
574 Cell e; {
575     if (isIdent(e)) {
576         Cell export = NIL;
577         List origExports = exports;
578         if (nonNull(export=findQualName(e))) {
579             exports=cons(export,exports);
580         } 
581         if (isQCon(e) && nonNull(export=findQualTycon(e))) {
582             exports = checkExportTycon(exports,mt,NIL,export);
583         } 
584         if (isQCon(e) && nonNull(export=findQualClass(e))) {
585             /* opaque class export */
586             exports = checkExportClass(exports,mt,NIL,export);
587         }
588         if (exports == origExports) {
589             ERRMSG(0) "Unknown entity \"%s\" exported from module \"%s\"",
590                       identToStr(e),
591                       textToStr(mt)
592             EEND;
593         }
594         return exports;
595     } else if (MODULEENT == fst(e)) {
596         Module m = findModid(snd(e));
597         /* ToDo: shouldn't allow export of module we didn't import */
598         if (isNull(m)) {
599             ERRMSG(0) "Unknown module \"%s\" exported from module \"%s\"",
600                       textToStr(textOf(snd(e))),
601                       textToStr(mt)
602             EEND;
603         }
604         if (m == currentModule) {
605             /* Exporting the current module exports local definitions */
606             List xs;
607             for(xs=module(m).classes; nonNull(xs); xs=tl(xs)) {
608                 if (cclass(hd(xs)).mod==m) 
609                     exports = checkExportClass(exports,mt,DOTDOT,hd(xs));
610             }
611             for(xs=module(m).tycons; nonNull(xs); xs=tl(xs)) {
612                 if (tycon(hd(xs)).mod==m) 
613                     exports = checkExportTycon(exports,mt,DOTDOT,hd(xs));
614             }
615             for(xs=module(m).names; nonNull(xs); xs=tl(xs)) {
616                 if (name(hd(xs)).mod==m) 
617                     exports = cons(hd(xs),exports);
618             }
619         } else {
620             /* Exporting other modules imports all things imported 
621              * unqualified from it.  
622              * ToDo: we reexport everything exported by a module -
623              * whether we imported it or not.  This gives the wrong
624              * result for "module M(module N) where import N(x)"
625              */
626             exports = dupOnto(module(m).exports,exports);
627         }
628         return exports;
629     } else {
630         Cell ident = fst(e); /* class name or type name */
631         Cell parts = snd(e); /* members or constructors */
632         Cell nm;
633         if (isQCon(ident) && nonNull(nm=findQualTycon(ident))) {
634             switch (tycon(nm).what) {
635             case SYNONYM:
636                 if (DOTDOT!=parts) {
637                     ERRMSG(0) "Explicit constructor list given for type synonym"
638                               " \"%s\" in export list of module \"%s\"",
639                               identToStr(ident),
640                               textToStr(mt)
641                     EEND;
642                 }
643                 return cons(pair(nm,DOTDOT),exports);
644             case RESTRICTSYN:   
645                 ERRMSG(0) "Transparent export of restricted type synonym"
646                           " \"%s\" in export list of module \"%s\"",
647                           identToStr(ident),
648                           textToStr(mt)
649                 EEND;
650                 return exports; /* Not reached */
651             case NEWTYPE:
652             case DATATYPE:
653                 if (DOTDOT==parts) {
654                     return cons(pair(nm,DOTDOT),exports);
655                 } else {
656                     exports = checkSubentities(exports,parts,tycon(nm).defn,
657                                                "constructor of type",
658                                                tycon(nm).text);
659                     return cons(pair(nm,DOTDOT), exports);
660                 }
661             default:
662                 internal("checkExport1");
663             }
664         } else if (isQCon(ident) && nonNull(nm=findQualClass(ident))) {
665             if (DOTDOT == parts) {
666                 return cons(pair(nm,DOTDOT),exports);
667             } else {
668                 exports = checkSubentities(exports,parts,cclass(nm).members,
669                                            "member of class",cclass(nm).text);
670                 return cons(pair(nm,DOTDOT), exports);
671             }
672         } else {
673             ERRMSG(0) "Explicit export list given for non-class/datatype \"%s\" in export list of module \"%s\"",
674                       identToStr(ident),
675                       textToStr(mt)
676             EEND;
677         }
678     }
679     return exports; /* NOTUSED */
680 }
681
682 static List local checkExports(exports)
683 List exports; {
684     Module m  = lastModule();
685     Text   mt = module(m).text;
686     List   es = NIL;
687
688     map1Accum(checkExport,es,mt,exports);
689
690 #if DEBUG_MODULES
691     for(xs=es; nonNull(xs); xs=tl(xs)) {
692         Printf(" %s", textToStr(textOfEntity(hd(xs))));
693     }
694 #endif
695     return es;
696 }
697
698
699 /* --------------------------------------------------------------------------
700  * Static analysis of type declarations:
701  *
702  * Type declarations come in two forms:
703  * - data declarations - define new constructed data types
704  * - type declarations - define new type synonyms
705  *
706  * A certain amount of work is carried out as the declarations are
707  * read during parsing.  In particular, for each type constructor
708  * definition encountered:
709  * - check that there is no previous definition of constructor
710  * - ensure type constructor not previously used as a class name
711  * - make a new entry in the type constructor table
712  * - record line number of declaration
713  * - Build separate lists of newly defined constructors for later use.
714  * ------------------------------------------------------------------------*/
715
716 Void tyconDefn(line,lhs,rhs,what)       /* process new type definition     */
717 Int  line;                              /* definition line number          */
718 Cell lhs;                               /* left hand side of definition    */
719 Cell rhs;                               /* right hand side of definition   */
720 Cell what; {                            /* SYNONYM/DATATYPE/etc...         */
721     Text t = textOf(getHead(lhs));
722
723     if (nonNull(findTycon(t))) {
724         ERRMSG(line) "Repeated definition of type constructor \"%s\"",
725                      textToStr(t)
726         EEND;
727     }
728     else if (nonNull(findClass(t))) {
729         ERRMSG(line) "\"%s\" used as both class and type constructor",
730                      textToStr(t)
731         EEND;
732     }
733     else {
734         Tycon nw        = newTycon(t);
735         tyconDefns      = cons(nw,tyconDefns);
736         tycon(nw).line  = line;
737         tycon(nw).arity = argCount;
738         tycon(nw).what  = what;
739         if (what==RESTRICTSYN) {
740             h98DoesntSupport(line,"restricted type synonyms");
741             typeInDefns = cons(pair(nw,snd(rhs)),typeInDefns);
742             rhs         = fst(rhs);
743         }
744         tycon(nw).defn  = pair(lhs,rhs);
745     }
746 }
747
748 Void setTypeIns(bs)                     /* set local synonyms for given    */
749 List bs; {                              /* binding group                   */
750     List cvs = typeInDefns;
751     for (; nonNull(cvs); cvs=tl(cvs)) {
752         Tycon c  = fst(hd(cvs));
753         List  vs = snd(hd(cvs));
754         for (tycon(c).what = RESTRICTSYN; nonNull(vs); vs=tl(vs)) {
755             if (nonNull(findBinding(textOf(hd(vs)),bs))) {
756                 tycon(c).what = SYNONYM;
757                 break;
758             }
759         }
760     }
761 }
762
763 Void clearTypeIns() {                   /* clear list of local synonyms    */
764     for (; nonNull(typeInDefns); typeInDefns=tl(typeInDefns))
765         tycon(fst(hd(typeInDefns))).what = RESTRICTSYN;
766 }
767
768 /* --------------------------------------------------------------------------
769  * Further analysis of Type declarations:
770  *
771  * In order to allow the definition of mutually recursive families of
772  * data types, the static analysis of the right hand sides of type
773  * declarations cannot be performed until all of the type declarations
774  * have been read.
775  *
776  * Once parsing is complete, we carry out the following:
777  *
778  * - check format of lhs, extracting list of bound vars and ensuring that
779  *   there are no repeated variables and no Skolem variables.
780  * - run dependency analysis on rhs to check that only bound type vars
781  *   appear in type and that all constructors are defined.
782  *   Replace type variables by offsets, constructors by Tycons.
783  * - use list of dependents to sort into strongly connected components.
784  * - ensure that there is not more than one synonym in each group.
785  * - kind-check each group of type definitions.
786  *
787  * - check that there are no previous definitions for constructor
788  *   functions in data type definitions.
789  * - install synonym expansions and constructor definitions.
790  * ------------------------------------------------------------------------*/
791
792 static List tcDeps = NIL;               /* list of dependent tycons/classes*/
793
794 static Void local checkTyconDefn(d)     /* validate type constructor defn  */
795 Tycon d; {
796     Cell lhs    = fst(tycon(d).defn);
797     Cell rhs    = snd(tycon(d).defn);
798     Int  line   = tycon(d).line;
799     List tyvars = getArgs(lhs);
800     List temp;
801                                         /* check for repeated tyvars on lhs*/
802     for (temp=tyvars; nonNull(temp); temp=tl(temp))
803         if (nonNull(varIsMember(textOf(hd(temp)),tl(temp)))) {
804             ERRMSG(line) "Repeated type variable \"%s\" on left hand side",
805                          textToStr(textOf(hd(temp)))
806             EEND;
807         }
808
809     tcDeps = NIL;                       /* find dependents                 */
810     switch (whatIs(tycon(d).what)) {
811         case RESTRICTSYN :
812         case SYNONYM     : rhs = depTypeExp(line,tyvars,rhs);
813                            if (cellIsMember(d,tcDeps)) {
814                                ERRMSG(line) "Recursive type synonym \"%s\"",
815                                             textToStr(tycon(d).text)
816                                EEND;
817                            }
818                            break;
819
820         case DATATYPE    :
821         case NEWTYPE     : depConstrs(d,tyvars,rhs);
822                            rhs = fst(rhs);
823                            break;
824
825         default          : internal("checkTyconDefn");
826                            break;
827     }
828
829     tycon(d).defn = rhs;
830     tycon(d).kind = tcDeps;
831     tcDeps        = NIL;
832 }
833
834 static Void local depConstrs(t,tyvars,cd)
835 Tycon t;                                /* Define constructor functions and*/
836 List  tyvars;                           /* do dependency analysis for data */
837 Cell  cd; {                             /* definitions (w or w/o deriving) */
838     Int  line      = tycon(t).line;
839     List ctxt      = NIL;
840     Int  conNo     = 1;
841     Type lhs       = t;
842     List cs        = fst(cd);
843     List derivs    = snd(cd);
844     List compTypes = NIL;
845     List sels      = NIL;
846     Int  i;
847
848     for (i=0; i<tycon(t).arity; ++i)    /* build representation for tycon  */
849         lhs = ap(lhs,mkOffset(i));      /* applied to full comp. of args   */
850
851     if (isQualType(cs)) {               /* allow for possible context      */
852         ctxt = fst(snd(cs));
853         cs   = snd(snd(cs));
854         map2Over(depPredExp,line,tyvars,ctxt);
855         h98CheckCtxt(line,"context",TRUE,ctxt,NIL);
856     }
857
858     if (nonNull(cs) && isNull(tl(cs)))  /* Single constructor datatype?    */
859         conNo = 0;
860
861     for (; nonNull(cs); cs=tl(cs)) {    /* For each constructor function:  */
862         Cell con   = hd(cs);
863         List sig   = dupList(tyvars);
864         List evs   = NIL;               /* locally quantified vars         */
865         List lps   = NIL;               /* locally bound predicates        */
866         List ctxt1 = ctxt;              /* constructor function context    */
867         List scs   = NIL;               /* strict components               */
868         List fs    = NONE;              /* selector names                  */
869         Type type  = lhs;               /* constructor function type       */
870         Int  arity = 0;                 /* arity of constructor function   */
871         Int  nr2   = 0;                 /* Number of rank 2 args           */
872         Name n;                         /* name for constructor function   */
873
874         if (whatIs(con)==POLYTYPE) {    /* Locally quantified vars         */
875             evs = fst(snd(con));
876             con = snd(snd(con));
877             sig = checkQuantVars(line,evs,sig,con);
878         }
879
880         if (isQualType(con)) {          /* Local predicates                */
881             List us;
882             lps     = fst(snd(con));
883             for (us = typeVarsIn(lps,NIL,NIL,NIL); nonNull(us); us=tl(us))
884                 if (!varIsMember(textOf(hd(us)),evs)) {
885                     ERRMSG(line)
886                         "Variable \"%s\" in constraint is not locally bound",
887                         textToStr(textOf(hd(us)))
888                     EEND;
889                 }
890             map2Over(depPredExp,line,sig,lps);
891             con     = snd(snd(con));
892             arity   = length(lps);
893         }
894
895         if (whatIs(con)==LABC) {        /* Skeletize constr components     */
896             Cell fls = snd(snd(con));   /* get field specifications        */
897             con      = fst(snd(con));
898             fs       = NIL;
899             for (; nonNull(fls); fls=tl(fls)) { /* for each field spec:    */
900                 List vs     = fst(hd(fls));
901                 Type t      = snd(hd(fls));     /* - scrutinize type       */
902                 Bool banged = whatIs(t)==BANG;
903                 t           = depCompType(line,sig,(banged ? arg(t) : t));
904                 while (nonNull(vs)) {           /* - add named components  */
905                     Cell us = tl(vs);
906                     tl(vs)  = fs;
907                     fs      = vs;
908                     vs      = us;
909                     con     = ap(con,t);
910                     arity++;
911                     if (banged)
912                         scs = cons(mkInt(arity),scs);
913                 }
914             }
915             fs  = rev(fs);
916             scs = rev(scs);             /* put strict comps in ascend ord  */
917         }
918         else {                          /* Non-labelled constructor        */
919             Cell c = con;
920             Int  compNo;
921             for (; isAp(c); c=fun(c))
922                 arity++;
923             for (compNo=arity, c=con; isAp(c); c=fun(c)) {
924                 Type t = arg(c);
925                 if (whatIs(t)==BANG) {
926                     scs = cons(mkInt(compNo),scs);
927                     t   = arg(t);
928                 }
929                 compNo--;
930                 arg(c) = depCompType(line,sig,t);
931             }
932         }
933
934         if (nonNull(ctxt1))             /* Extract relevant part of context*/
935             ctxt1 = selectCtxt(ctxt1,offsetTyvarsIn(con,NIL));
936
937         for (i=arity; isAp(con); i--) { /* Calculate type of constructor   */
938             Type ty  = fun(con);
939             Type cmp = arg(con);
940             fun(con) = typeArrow;
941             if (isPolyOrQualType(cmp)) {
942                 if (nonNull(derivs)) {
943                     ERRMSG(line) "Cannot derive instances for types" ETHEN
944                     ERRTEXT      " with polymorphic or qualified components"
945                     EEND;
946                 }
947                 if (nr2==0)
948                     nr2 = i;
949             }
950             if (nonNull(derivs))        /* and build list of components    */
951                 compTypes = cons(cmp,compTypes);
952             type     = ap(con,type);
953             con      = ty;
954         }
955
956         if (nr2>0) {                    /* Add rank 2 annotation           */
957             type = ap(RANK2,pair(mkInt(nr2-length(lps)),type));
958         }
959
960         if (nonNull(evs)) {             /* Add existential annotation      */
961             if (nonNull(derivs)) {
962                 ERRMSG(line) "Cannot derive instances for types" ETHEN
963                 ERRTEXT      " with existentially typed components"
964                 EEND;
965             }
966             if (fs!=NONE) {
967                 ERRMSG(line)
968                    "Cannot use selectors with existentially typed components"
969                 EEND;
970             }
971             type = ap(EXIST,pair(mkInt(length(evs)),type));
972         }
973
974         if (nonNull(lps)) {             /* Add local preds part to type    */
975             type = ap(CDICTS,pair(lps,type));
976         }
977
978         if (nonNull(ctxt1)) {           /* Add context part to type        */
979             type = ap(QUAL,pair(ctxt1,type));
980         }
981
982         if (nonNull(sig)) {             /* Add quantifiers to type         */
983             List ts1 = sig;
984             for (; nonNull(ts1); ts1=tl(ts1)) {
985                 hd(ts1) = NIL;
986             }
987             type = mkPolyType(sig,type);
988         }
989
990         n = findName(textOf(con));      /* Allocate constructor fun name   */
991         if (isNull(n)) {
992             n = newName(textOf(con),NIL);
993         } else if (name(n).defn!=PREDEFINED) {
994             duplicateError(line,name(n).mod,name(n).text,
995                            "constructor function");
996         }
997         name(n).arity  = arity;         /* Save constructor fun details    */
998         name(n).line   = line;
999         name(n).parent = t;
1000         name(n).number = cfunNo(conNo++);
1001         name(n).type   = type;
1002         if (tycon(t).what==NEWTYPE) {
1003             if (nonNull(lps)) {
1004                 ERRMSG(line)
1005                    "A newtype constructor cannot have class constraints"
1006                 EEND;
1007             }
1008             if (arity!=1) {
1009                 ERRMSG(line)
1010                    "A newtype constructor must have exactly one argument"
1011                 EEND;
1012             }
1013             if (nonNull(scs)) {
1014                 ERRMSG(line)
1015                    "Illegal strictess annotation for newtype constructor"
1016                 EEND;
1017             }
1018             name(n).defn = nameId;
1019         } else {
1020             implementCfun(n,scs);
1021         }
1022
1023         hd(cs) = n;
1024         if (fs!=NONE) {
1025             sels = addSels(line,n,fs,sels);
1026         }
1027     }
1028
1029     if (nonNull(sels)) {
1030         sels     = rev(sels);
1031         fst(cd)  = appendOnto(fst(cd),sels);
1032         selDefns = cons(sels,selDefns);
1033     }
1034
1035     if (nonNull(derivs)) {              /* Generate derived instances      */
1036         map3Proc(checkDerive,t,ctxt,compTypes,derivs);
1037     }
1038 }
1039
1040 Int userArity(c)                        /* Find arity for cfun, ignoring   */
1041 Name c; {                               /* CDICTS parameters               */
1042     Int  a = name(c).arity;
1043     Type t = name(c).type;
1044     Int  w;
1045     if (isPolyType(t)) {
1046         t = monotypeOf(t);
1047     }
1048     if ((w=whatIs(t))==QUAL) {
1049         w = whatIs(t=snd(snd(t)));
1050     }
1051     if (w==CDICTS) {
1052         a -= length(fst(snd(t)));
1053     }
1054     return a;
1055 }
1056
1057
1058 static List local addSels(line,c,fs,ss) /* Add fields to selector list     */
1059 Int  line;                              /* line number of constructor      */
1060 Name c;                                 /* corresponding constr function   */
1061 List fs;                                /* list of fields (varids)         */
1062 List ss; {                              /* list of existing selectors      */
1063     Int sn    = 1;
1064     cfunSfuns = cons(pair(c,fs),cfunSfuns);
1065     for (; nonNull(fs); fs=tl(fs), ++sn) {
1066         List ns = ss;
1067         Text t  = textOf(hd(fs));
1068
1069         if (nonNull(varIsMember(t,tl(fs)))) {
1070             ERRMSG(line) "Repeated field name \"%s\" for constructor \"%s\"",
1071                          textToStr(t), textToStr(name(c).text)
1072             EEND;
1073         }
1074
1075         while (nonNull(ns) && t!=name(hd(ns)).text) {
1076             ns = tl(ns);
1077         }
1078
1079         if (nonNull(ns)) {
1080             name(hd(ns)).defn = cons(pair(c,mkInt(sn)),name(hd(ns)).defn);
1081         } else {
1082             Name n = findName(t);
1083             if (nonNull(n)) {
1084                 ERRMSG(line) "Repeated definition for selector \"%s\"",
1085                              textToStr(t)
1086                 EEND;
1087             }
1088             n              = newName(t,c);
1089             name(n).line   = line;
1090             name(n).number = SELNAME;
1091             name(n).defn   = singleton(pair(c,mkInt(sn)));
1092             ss             = cons(n,ss);
1093         }
1094     }
1095     return ss;
1096 }
1097
1098 static List local selectCtxt(ctxt,vs)   /* calculate subset of context     */
1099 List ctxt;
1100 List vs; {
1101     if (isNull(vs)) {
1102         return NIL;
1103     } else {
1104         List ps = NIL;
1105         for (; nonNull(ctxt); ctxt=tl(ctxt)) {
1106             List us = offsetTyvarsIn(hd(ctxt),NIL);
1107             for (; nonNull(us) && cellIsMember(hd(us),vs); us=tl(us)) {
1108             }
1109             if (isNull(us)) {
1110                 ps = cons(hd(ctxt),ps);
1111             }
1112         }
1113         return rev(ps);
1114     }
1115 }
1116
1117 static Void local checkSynonyms(ts)     /* Check for mutually recursive    */
1118 List ts; {                              /* synonyms                        */
1119     List syns = NIL;
1120     for (; nonNull(ts); ts=tl(ts)) {    /* build list of all synonyms      */
1121         Tycon t = hd(ts);
1122         switch (whatIs(tycon(t).what)) {
1123             case SYNONYM     :
1124             case RESTRICTSYN : syns = cons(t,syns);
1125                                break;
1126         }
1127     }
1128     while (nonNull(syns)) {             /* then visit each synonym         */
1129         syns = visitSyn(NIL,hd(syns),syns);
1130     }
1131 }
1132
1133 static List local visitSyn(path,t,syns) /* visit synonym definition to look*/
1134 List  path;                             /* for cycles                      */
1135 Tycon t;
1136 List  syns; {
1137     if (cellIsMember(t,path)) {         /* every elt in path depends on t  */
1138         ERRMSG(tycon(t).line)
1139             "Type synonyms \"%s\" and \"%s\" are mutually recursive",
1140             textToStr(tycon(t).text), textToStr(tycon(hd(path)).text)
1141         EEND;
1142     } else {
1143         List ds    = tycon(t).kind;
1144         List path1 = NIL;
1145         for (; nonNull(ds); ds=tl(ds)) {
1146             if (cellIsMember(hd(ds),syns)) {
1147                 if (isNull(path1)) {
1148                     path1 = cons(t,path);
1149                 }
1150                 syns = visitSyn(path1,hd(ds),syns);
1151             }
1152         }
1153     }
1154     tycon(t).defn = fullExpand(tycon(t).defn);
1155     return removeCell(t,syns);
1156 }
1157
1158 /* --------------------------------------------------------------------------
1159  * Expanding out all type synonyms in a type expression:
1160  * ------------------------------------------------------------------------*/
1161
1162 Type fullExpand(t)                      /* find full expansion of type exp */
1163 Type t; {                               /* assuming that all relevant      */
1164     Cell h = t;                         /* synonym defns of lower rank have*/
1165     Int  n = 0;                         /* already been fully expanded     */
1166     List args;
1167     for (args=NIL; isAp(h); h=fun(h), n++) {
1168         args = cons(fullExpand(arg(h)),args);
1169     }
1170     t = applyToArgs(h,args);
1171     if (isSynonym(h) && n>=tycon(h).arity) {
1172         if (n==tycon(h).arity) {
1173             t = instantiateSyn(tycon(h).defn,t);
1174         } else {
1175             Type p = t;
1176             while (--n > tycon(h).arity) {
1177                 p = fun(p);
1178             }
1179             fun(p) = instantiateSyn(tycon(h).defn,fun(p));
1180         }
1181     }
1182     return t;
1183 }
1184
1185 static Type local instantiateSyn(t,env) /* instantiate type according using*/
1186 Type t;                                 /* env to determine appropriate    */
1187 Type env; {                             /* values for OFFSET type vars     */
1188     switch (whatIs(t)) {
1189         case AP      : return ap(instantiateSyn(fun(t),env),
1190                                  instantiateSyn(arg(t),env));
1191
1192         case OFFSET  : return nthArg(offsetOf(t),env);
1193
1194         default      : return t;
1195     }
1196 }
1197
1198 /* --------------------------------------------------------------------------
1199  * Static analysis of class declarations:
1200  *
1201  * Performed in a similar manner to that used for type declarations.
1202  *
1203  * The first part of the static analysis is performed as the declarations
1204  * are read during parsing.  The parser ensures that:
1205  * - the class header and all superclass predicates are of the form
1206  *   ``Class var''
1207  *
1208  * The classDefn() function:
1209  * - ensures that there is no previous definition for class
1210  * - checks that class name has not previously been used as a type constr.
1211  * - make new entry in class table
1212  * - record line number of declaration
1213  * - build list of classes defined in current script for use in later
1214  *   stages of static analysis.
1215  * ------------------------------------------------------------------------*/
1216
1217 Void classDefn(line,head,ms,fds)       /* process new class definition     */
1218 Int  line;                             /* definition line number           */
1219 Cell head;                             /* class header :: ([Supers],Class) */
1220 List ms;                               /* class definition body            */
1221 List fds; {                            /* functional dependencies          */
1222     Text ct    = textOf(getHead(snd(head)));
1223     Int  arity = argCount;
1224
1225     if (nonNull(findClass(ct))) {
1226         ERRMSG(line) "Repeated definition of class \"%s\"",
1227                      textToStr(ct)
1228         EEND;
1229     } else if (nonNull(findTycon(ct))) {
1230         ERRMSG(line) "\"%s\" used as both class and type constructor",
1231                      textToStr(ct)
1232         EEND;
1233     } else {
1234         Class nw           = newClass(ct);
1235         cclass(nw).line    = line;
1236         cclass(nw).arity   = arity;
1237         cclass(nw).head    = snd(head);
1238         cclass(nw).supers  = fst(head);
1239         cclass(nw).members = ms;
1240         cclass(nw).level   = 0;
1241         cclass(nw).fds     = fds;
1242         cclass(nw).xfds    = NIL;
1243         classDefns         = cons(nw,classDefns);
1244         if (arity!=1)
1245             h98DoesntSupport(line,"multiple parameter classes");
1246     }
1247 }
1248
1249 /* --------------------------------------------------------------------------
1250  * Further analysis of class declarations:
1251  *
1252  * Full static analysis of class definitions must be postponed until the
1253  * complete script has been read and all static analysis on type definitions
1254  * has been completed.
1255  *
1256  * Once this has been achieved, we carry out the following checks on each
1257  * class definition:
1258  * - check that variables in header are distinct
1259  * - replace head by skeleton
1260  * - check superclass declarations, replace by skeletons
1261  * - split body of class into members and declarations
1262  * - make new name entry for each member function
1263  * - record member function number (eventually an offset into dictionary!)
1264  * - no member function has a previous definition ...
1265  * - no member function is mentioned more than once in the list of members
1266  * - each member function type is valid, replace vars by offsets
1267  * - qualify each member function type by class header
1268  * - only bindings for members appear in defaults
1269  * - only function bindings appear in defaults
1270  * - check that extended class hierarchy does not contain any cycles
1271  * ------------------------------------------------------------------------*/
1272
1273 static Void local checkClassDefn(c)    /* validate class definition        */
1274 Class c; {
1275     List tyvars = NIL;
1276     Int  args   = cclass(c).arity - 1;
1277     Cell temp   = cclass(c).head;
1278     List fs     = NIL;
1279     List ss     = NIL;
1280
1281     for (; isAp(temp); temp=fun(temp)) {
1282         if (!isVar(arg(temp))) {
1283             ERRMSG(cclass(c).line) "Type variable required in class head"
1284             EEND;
1285         }
1286         if (nonNull(varIsMember(textOf(arg(temp)),tyvars))) {
1287             ERRMSG(cclass(c).line)
1288                 "Repeated type variable \"%s\" in class head",
1289                 textToStr(textOf(arg(temp)))
1290             EEND;
1291         }
1292         tyvars = cons(arg(temp),tyvars);
1293     }
1294
1295     for (fs=cclass(c).fds; nonNull(fs); fs=tl(fs)) {
1296         Pair fd = hd(fs);
1297         List vs = snd(fd);
1298
1299         /* Check for trivial dependency
1300          */
1301         if (isNull(vs)) {
1302             ERRMSG(cclass(c).line) "Functional dependency is trivial"
1303             EEND;
1304         }
1305
1306         /* Check for duplicated vars on right hand side, and for vars on
1307          * right that also appear on the left:
1308          */
1309         for (vs=snd(fd); nonNull(vs); vs=tl(vs)) {
1310             if (varIsMember(textOf(hd(vs)),fst(fd))) {
1311                 ERRMSG(cclass(c).line)
1312                     "Trivial dependency for variable \"%s\"",
1313                     textToStr(textOf(hd(vs)))
1314                 EEND;
1315             }
1316             if (varIsMember(textOf(hd(vs)),tl(vs))) {
1317                 ERRMSG(cclass(c).line)
1318                     "Repeated variable \"%s\" in functional dependency",
1319                     textToStr(textOf(hd(vs)))
1320                 EEND;
1321             }
1322             hd(vs) = depTypeVar(cclass(c).line,tyvars,textOf(hd(vs)));
1323         }
1324
1325         /* Check for duplicated vars on left hand side:
1326          */
1327         for (vs=fst(fd); nonNull(vs); vs=tl(vs)) {
1328             if (varIsMember(textOf(hd(vs)),tl(vs))) {
1329                 ERRMSG(cclass(c).line)
1330                     "Repeated variable \"%s\" in functional dependency",
1331                     textToStr(textOf(hd(vs)))
1332                 EEND;
1333             }
1334             hd(vs) = depTypeVar(cclass(c).line,tyvars,textOf(hd(vs)));
1335         }
1336     }
1337
1338     if (cclass(c).arity==0) {
1339         cclass(c).head = c;
1340     } else {
1341         Int args = cclass(c).arity - 1;
1342         for (temp=cclass(c).head; args>0; temp=fun(temp), args--) {
1343             arg(temp) = mkOffset(args);
1344         }
1345         arg(temp) = mkOffset(0);
1346         fun(temp) = c;
1347     }
1348
1349     tcDeps              = NIL;          /* find dependents                 */
1350     map2Over(depPredExp,cclass(c).line,tyvars,cclass(c).supers);
1351     h98CheckCtxt(cclass(c).line,"class definition",FALSE,cclass(c).supers,NIL);
1352     cclass(c).numSupers = length(cclass(c).supers);
1353     cclass(c).defaults  = extractBindings(cclass(c).members);   /* defaults*/
1354     ss                  = extractSigdecls(cclass(c).members);
1355     fs                  = extractFixdecls(cclass(c).members);
1356     cclass(c).members   = pair(ss,fs);
1357     map2Proc(checkMems,c,tyvars,ss);
1358
1359     cclass(c).kinds     = tcDeps;
1360     tcDeps              = NIL;
1361 }
1362
1363
1364 /* --------------------------------------------------------------------------
1365  * Functional dependencies are inherited from superclasses.
1366  * For example, if I've got the following classes:
1367  *
1368  * class C a b | a -> b
1369  * class C [b] a => D a b
1370  *
1371  * then C will have the dependency ([a], [b]) as expected, and D will inherit
1372  * the dependency ([b], [a]) from C.
1373  * When doing pairwise improvement, we have to consider not just improving
1374  * when we see a pair of Cs or a pair of Ds in the context, but when we've
1375  * got a C and a D as well.  In this case, we only improve when the
1376  * predicate in question matches the type skeleton in the relevant superclass
1377  * constraint.  E.g., we improve the pair (C [Int] a, D b Int) (unifying
1378  * a and b), but we don't improve the pair (C Int a, D b Int).
1379  * To implement functional dependency inheritance, we calculate
1380  * the closure of all functional dependencies, and store the result
1381  * in an additional field `xfds' (extended functional dependencies).
1382  * The `xfds' field is a list of functional dependency lists, annotated
1383  * with a list of predicate skeletons constraining when improvement can
1384  * happen against this dependency list.  For example, the xfds field
1385  * for C above would be:
1386  *     [([C a b], [([a], [b])])]
1387  * and the xfds field for D would be:
1388  *     [([C [b] a, D a b], [([b], [a])])]
1389  * Self-improvement (of a C with a C, or a D with a D) is treated as a
1390  * special case of an inherited dependency.
1391  * ------------------------------------------------------------------------*/
1392 static List local inheritFundeps ( Class c, Cell pi, Int o )
1393 {
1394     Int alpha = newKindedVars(cclass(c).kinds);
1395     List scs = cclass(c).supers;
1396     List xfds = NIL;
1397     Cell this = NIL;
1398     /* better not fail ;-) */
1399     if (!matchPred(pi,o,cclass(c).head,alpha))
1400         internal("inheritFundeps - predicate failed to match it's own head!");
1401     this = copyPred(pi,o);
1402     for (; nonNull(scs); scs=tl(scs)) {
1403         Class s = getHead(hd(scs));
1404         if (isClass(s)) {
1405             List sfds = inheritFundeps(s,hd(scs),alpha);
1406             for (; nonNull(sfds); sfds=tl(sfds)) {
1407                 Cell h = hd(sfds);
1408                 xfds = cons(pair(cons(this,fst(h)),snd(h)),xfds);
1409             }
1410         }
1411     }
1412     if (nonNull(cclass(c).fds)) {
1413         List fds = NIL, fs = cclass(c).fds;
1414         for (; nonNull(fs); fs=tl(fs)) {
1415             fds = cons(pair(otvars(this,fst(hd(fs))),
1416                             otvars(this,snd(hd(fs)))),fds);
1417         }
1418         xfds = cons(pair(cons(this,NIL),fds),xfds);
1419     }
1420     return xfds;
1421 }
1422
1423 static Void local extendFundeps ( Class c )
1424
1425     Int alpha;
1426     emptySubstitution();
1427     alpha = newKindedVars(cclass(c).kinds);
1428     cclass(c).xfds = inheritFundeps(c,cclass(c).head,alpha);
1429
1430     /* we can now check for ambiguity */
1431     map1Proc(checkMems2,c,fst(cclass(c).members));
1432 }
1433
1434
1435 static Cell local depPredExp(line,tyvars,pred)
1436 Int  line;
1437 List tyvars;
1438 Cell pred; {
1439     Int  args = 0;
1440     Cell prev = NIL;
1441     Cell h    = pred;
1442     for (; isAp(h); args++) {
1443         arg(h) = depTypeExp(line,tyvars,arg(h));
1444         prev   = h;
1445         h      = fun(h);
1446     }
1447
1448     if (args==0) {
1449         h98DoesntSupport(line,"tag classes");
1450     } else if (args!=1) {
1451         h98DoesntSupport(line,"multiple parameter classes");
1452     }
1453
1454     if (isQCon(h)) {                    /* standard class constraint       */
1455         Class c = findQualClass(h);
1456         if (isNull(c)) {
1457             ERRMSG(line) "Undefined class \"%s\"", identToStr(h)
1458             EEND;
1459         }
1460         if (isNull(prev)) {
1461             pred = c;
1462         } else {
1463             fun(prev) = c;
1464         }
1465         if (args!=cclass(c).arity) {
1466             ERRMSG(line) "Wrong number of arguments for class \"%s\"",
1467                         textToStr(cclass(c).text)
1468             EEND;
1469         }
1470         if (cellIsMember(c,classDefns) && !cellIsMember(c,tcDeps)) {
1471             tcDeps = cons(c,tcDeps);
1472         }
1473     }
1474 #if TREX
1475     else if (isExt(h)) {                /* Lacks predicate                 */
1476         if (args!=1) {                  /* parser shouldn't let this happen*/
1477             ERRMSG(line) "Wrong number of arguments for lacks predicate"
1478             EEND;
1479         }
1480     }
1481 #endif
1482     else 
1483 #if IPARAM
1484          if (whatIs(h) != IPCELL)
1485 #endif
1486     {
1487         internal("depPredExp");
1488     }
1489     return pred;
1490 }
1491
1492 static Void local checkMems(c,tyvars,m) /* check member function details   */
1493 Class c;
1494 List  tyvars;
1495 Cell  m; {
1496     Int  line = intOf(fst3(m));
1497     List vs   = snd3(m);
1498     Type t    = thd3(m);
1499     List sig  = NIL;
1500     List tvs  = NIL;
1501     List xtvs = NIL;
1502
1503     if (isPolyType(t)) {
1504         xtvs = fst(snd(t));
1505         t    = monotypeOf(t);
1506     }
1507   
1508
1509     tyvars    = typeVarsIn(t,NIL,xtvs,tyvars);
1510                                         /* Look for extra type vars.       */
1511     checkOptQuantVars(line,xtvs,tyvars);
1512
1513     if (isQualType(t)) {                /* Overloaded member signatures?   */
1514         map2Over(depPredExp,line,tyvars,fst(snd(t)));
1515     } else {
1516         t = ap(QUAL,pair(NIL,t));
1517     }
1518
1519     fst(snd(t)) = cons(cclass(c).head,fst(snd(t)));/* Add main predicate   */
1520     snd(snd(t)) = depTopType(line,tyvars,snd(snd(t)));
1521
1522     for (tvs=tyvars; nonNull(tvs); tvs=tl(tvs)){/* Quantify                */
1523         sig = ap(NIL,sig);
1524     }
1525     if (nonNull(sig)) {
1526         t = mkPolyType(sig,t);
1527     }
1528     thd3(m) = t;                                /* Save type               */
1529     take(cclass(c).arity,tyvars);               /* Delete extra type vars  */
1530
1531     if (isAmbiguous(t)) {
1532         ambigError(line,"class declaration",hd(vs),t);
1533     }
1534     h98CheckType(line,"member type",hd(vs),t);
1535 }
1536
1537 static Void local checkMems2(c,m) /* check member function details   */
1538 Class c;
1539 Cell  m; {
1540     Int  line = intOf(fst3(m));
1541     List vs   = snd3(m);
1542     Type t    = thd3(m);
1543 }
1544
1545 static Void local addMembers(c)         /* Add definitions of member funs  */
1546 Class c; {                              /* and other parts of class struct.*/
1547     List ms  = fst(cclass(c).members);
1548     List fs  = snd(cclass(c).members);
1549     List ns  = NIL;                     /* List of names                   */
1550     Int  mno;                           /* Member function number          */
1551
1552     for (mno=0; mno<cclass(c).numSupers; mno++) {
1553         ns = cons(newDSel(c,mno),ns);
1554     }
1555     cclass(c).dsels = rev(ns);          /* Save dictionary selectors       */
1556
1557     for (mno=1, ns=NIL; nonNull(ms); ms=tl(ms)) {
1558         Int  line = intOf(fst3(hd(ms)));
1559         List vs   = rev(snd3(hd(ms)));
1560         Type t    = thd3(hd(ms));
1561         for (; nonNull(vs); vs=tl(vs)) {
1562             ns = cons(newMember(line,mno++,hd(vs),t,c),ns);
1563         }
1564     }
1565     cclass(c).members    = rev(ns);     /* Save list of members            */
1566     cclass(c).numMembers = length(cclass(c).members);
1567
1568     for (; nonNull(fs); fs=tl(fs)) {    /* fixity declarations             */
1569         Int    line = intOf(fst3(hd(fs)));
1570         List   ops  = snd3(hd(fs));
1571         Syntax s    = intOf(thd3(hd(fs)));
1572         for (; nonNull(ops); ops=tl(ops)) {
1573             Name n = nameIsMember(textOf(hd(ops)),cclass(c).members);
1574             if (isNull(n)) {
1575                 missFixity(line,textOf(hd(ops)));
1576             } else if (name(n).syntax!=NO_SYNTAX) {
1577                 dupFixity(line,textOf(hd(ops)));
1578             }
1579             name(n).syntax = s;
1580         }
1581     }
1582
1583 /*  Not actually needed just yet; for the time being, dictionary code will
1584     not be passed through the type checker.
1585
1586     cclass(c).dtycon    = addPrimTycon(generateText("Dict.%s",c),
1587                                        NIL,
1588                                        cclass(c).arity,
1589                                        DATATYPE,
1590                                        NIL);
1591 */
1592
1593     mno                  = cclass(c).numSupers + cclass(c).numMembers;
1594     /* cclass(c).dcon       = addPrimCfun(generateText("Make.%s",c),mno,0,NIL); */
1595     cclass(c).dcon       = addPrimCfun(generateText(":D%s",c),mno,0,NIL);
1596     /* implementCfun(cclass(c).dcon,NIL);
1597        Don't manufacture a wrapper fn for dictionary constructors.
1598        Applications of dictionary constructors are always saturated,
1599        and translate.c:stgExpr() special-cases saturated constructor apps.
1600     */
1601
1602     if (mno==1) {                       /* Single entry dicts use newtype  */
1603         name(cclass(c).dcon).defn = nameId;
1604         if (nonNull(cclass(c).members)) {
1605             name(hd(cclass(c).members)).number = mfunNo(0);
1606         }
1607     }
1608     cclass(c).defaults   = classBindings("class",c,cclass(c).defaults);
1609 }
1610
1611 static Name local newMember(l,no,v,t,parent)
1612 Int   l;                                /* Make definition for member fn   */
1613 Int   no;
1614 Cell  v;
1615 Type  t; 
1616 Class parent; {
1617     Name m = findName(textOf(v));
1618
1619     if (isNull(m)) {
1620         m = newName(textOf(v),parent);
1621     } else if (name(m).defn!=PREDEFINED) {
1622         ERRMSG(l) "Repeated definition for member function \"%s\"",
1623                   textToStr(name(m).text)
1624         EEND;
1625     }
1626
1627     name(m).line     = l;
1628     name(m).arity    = 1;
1629     name(m).number   = mfunNo(no);
1630     name(m).type     = t;
1631     return m;
1632 }
1633
1634 static Name local newDSel(c,no)         /* Make definition for dict selectr*/
1635 Class c;
1636 Int   no; {
1637     Name s;
1638     char buf[16];
1639
1640     /* sprintf(buf,"sc%d.%s",no,"%s"); */
1641     sprintf(buf,"$p%d%s",no+1,"%s");
1642     s                = newName(generateText(buf,c),c);
1643     name(s).line     = cclass(c).line;
1644     name(s).arity    = 1;
1645     name(s).number   = DFUNNAME;
1646     return s;
1647 }
1648
1649 #define MAX_GEN  128
1650
1651 static Text local generateText(sk,c)    /* We need to generate names for   */
1652 String sk;                              /* certain objects corresponding   */
1653 Class  c; {                             /* to each class.                  */
1654     String cname = textToStr(cclass(c).text);
1655     char buffer[MAX_GEN+1];
1656
1657     if ((strlen(sk)+strlen(cname))>=MAX_GEN) {
1658         ERRMSG(0) "Please use a shorter name for class \"%s\"", cname
1659         EEND;
1660     }
1661     sprintf(buffer,sk,cname);
1662     return findText(buffer);
1663 }
1664
1665 static Int local visitClass(c)          /* visit class defn to check that  */
1666 Class c; {                              /* class hierarchy is acyclic      */
1667 #if TREX
1668     if (isExt(c)) {                     /* special case for lacks preds    */
1669         return 0;
1670     }
1671 #endif
1672     if (cclass(c).level < 0) {          /* already visiting this class?    */
1673         ERRMSG(cclass(c).line) "Class hierarchy for \"%s\" is not acyclic",
1674                                textToStr(cclass(c).text)
1675         EEND;
1676     } else if (cclass(c).level == 0) {  /* visiting class for first time   */
1677         List scs = cclass(c).supers;
1678         Int  lev = 0;
1679         cclass(c).level = (-1);
1680         for (; nonNull(scs); scs=tl(scs)) {
1681             Int l = visitClass(getHead(hd(scs)));
1682             if (l>lev) lev=l;
1683         }
1684         cclass(c).level = 1+lev;        /* level = 1 + max level of supers */
1685     }
1686     return cclass(c).level;
1687 }
1688
1689 /* --------------------------------------------------------------------------
1690  * Process class and instance declaration binding groups:
1691  * ------------------------------------------------------------------------*/
1692
1693 static List local classBindings(where,c,bs)
1694 String where;                           /* Check validity of bindings bs   */
1695 Class  c;                               /* for class c (or an inst of c)   */
1696 List   bs; {                            /* sort into approp. member order  */
1697     List nbs = NIL;
1698
1699     for (; nonNull(bs); bs=tl(bs)) {
1700         Cell b    = hd(bs);
1701         Cell body = snd(snd(b));
1702         Name mnm;
1703
1704         if (!isVar(fst(b))) {           /* Only allow function bindings    */
1705             ERRMSG(rhsLine(snd(body)))
1706                 "Pattern binding illegal in %s declaration", where
1707             EEND;
1708         }
1709
1710         if (isNull(mnm=memberName(c,textOf(fst(b))))) {
1711             ERRMSG(rhsLine(snd(hd(body))))
1712                 "No member \"%s\" in class \"%s\"",
1713                 textToStr(textOf(fst(b))), textToStr(cclass(c).text)
1714             EEND;
1715         }
1716         snd(b) = body;
1717         nbs    = numInsert(mfunOf(mnm)-1,b,nbs);
1718     }
1719     return nbs;
1720 }
1721
1722 static Name local memberName(c,t)       /* return name of member function  */
1723 Class c;                                /* with name t in class c          */
1724 Text  t; {                              /* return NIL if not a member      */
1725     List ms = cclass(c).members;
1726     for (; nonNull(ms); ms=tl(ms)) {
1727         if (t==name(hd(ms)).text) {
1728             return hd(ms);
1729         }
1730     }
1731     return NIL;
1732 }
1733
1734 static List local numInsert(n,x,xs)    /* insert x at nth position in xs,  */
1735 Int  n;                                /* filling gaps with NIL            */
1736 Cell x;
1737 List xs; {
1738     List start = isNull(xs) ? cons(NIL,NIL) : xs;
1739
1740     for (xs=start; 0<n--; xs=tl(xs)) {
1741         if (isNull(tl(xs))) {
1742             tl(xs) = cons(NIL,NIL);
1743         }
1744     }
1745     hd(xs) = x;
1746     return start;
1747 }
1748
1749 /* --------------------------------------------------------------------------
1750  * Calculate set of variables appearing in a given type expression (possibly
1751  * qualified) as a list of distinct values.  The order in which variables
1752  * appear in the list is the same as the order in which those variables
1753  * occur in the type expression when read from left to right.
1754  * ------------------------------------------------------------------------*/
1755
1756 List local typeVarsIn(ty,us,ws,vs)      /*Calculate list of type variables*/
1757 Cell ty;                                /* used in type expression, reading*/
1758 List us;                                /* from left to right ignoring any */
1759 List ws;                                /* listed in us.                   */
1760 List vs; {                              /* ws = explicitly quantified vars */
1761     switch (whatIs(ty)) {
1762         case AP        : return typeVarsIn(snd(ty),us,ws,
1763                                            typeVarsIn(fst(ty),us,ws,vs));
1764
1765         case VARIDCELL :
1766         case VAROPCELL : if ((nonNull(findBtyvs(textOf(ty)))
1767                               && !varIsMember(textOf(ty),ws))
1768                              || varIsMember(textOf(ty),us)) {
1769                              return vs;
1770                          } else {
1771                              return maybeAppendVar(ty,vs);
1772                          }
1773
1774         case POLYTYPE  : return typeVarsIn(monotypeOf(ty),polySigOf(ty),ws,vs);
1775
1776         case QUAL      : {   vs = typeVarsIn(fst(snd(ty)),us,ws,vs);
1777                              return typeVarsIn(snd(snd(ty)),us,ws,vs);
1778                          }
1779
1780         case BANG      : return typeVarsIn(snd(ty),us,ws,vs);
1781
1782         case LABC      : {   List fs = snd(snd(ty));
1783                              for (; nonNull(fs); fs=tl(fs)) {
1784                                 vs = typeVarsIn(snd(hd(fs)),us,ws,vs);
1785                              }
1786                              return vs;
1787                          }
1788     }
1789     return vs;
1790 }
1791
1792 static List local maybeAppendVar(v,vs) /* append variable to list if not   */
1793 Cell v;                                /* already included                 */
1794 List vs; {
1795     Text t = textOf(v);
1796     List p = NIL;
1797     List c = vs;
1798
1799     while (nonNull(c)) {
1800         if (textOf(hd(c))==t) {
1801             return vs;
1802         }
1803         p = c;
1804         c = tl(c);
1805     }
1806
1807     if (nonNull(p)) {
1808         tl(p) = cons(v,NIL);
1809     } else {
1810         vs    = cons(v,NIL);
1811     }
1812
1813     return vs;
1814 }
1815
1816 /* --------------------------------------------------------------------------
1817  * Static analysis for type expressions is required to:
1818  *   - ensure that each type constructor or class used has been defined.
1819  *   - replace type variables by offsets, constructor names by Tycons.
1820  *   - ensure that the type is well-kinded.
1821  * ------------------------------------------------------------------------*/
1822
1823 static Type local checkSigType(line,where,e,type)
1824 Int    line;                            /* Check validity of type expr in  */
1825 String where;                           /* explicit type signature         */
1826 Cell   e;
1827 Type   type; {
1828     List tvs  = NIL;
1829     List sunk = NIL;
1830     List xtvs = NIL;
1831
1832     if (isPolyType(type)) {
1833         xtvs = fst(snd(type));
1834         type = monotypeOf(type);
1835     }
1836     tvs  = typeVarsIn(type,NIL,xtvs,NIL);
1837     sunk = unkindTypes;
1838     checkOptQuantVars(line,xtvs,tvs);
1839
1840     if (isQualType(type)) {
1841         map2Over(depPredExp,line,tvs,fst(snd(type)));
1842         snd(snd(type)) = depTopType(line,tvs,snd(snd(type)));
1843
1844         if (isAmbiguous(type)) {
1845             ambigError(line,where,e,type);
1846         }
1847     } else {
1848         type = depTopType(line,tvs,type);
1849     }
1850
1851     if (nonNull(tvs)) {
1852         if (length(tvs)>=NUM_OFFSETS) {
1853             ERRMSG(line) "Too many type variables in %s\n", where
1854             EEND;
1855         } else {
1856             List ts = tvs;
1857             for (; nonNull(ts); ts=tl(ts)) {
1858                 hd(ts) = NIL;
1859             }
1860             type    = mkPolyType(tvs,type);
1861         }
1862     }
1863
1864     unkindTypes = NIL;
1865     kindType(line,"type expression",type);
1866     fixKinds();
1867     unkindTypes = sunk;
1868
1869     h98CheckType(line,where,e,type);
1870     return type;
1871 }
1872
1873 static Void local checkOptQuantVars(line,xtvs,tvs)
1874 Int  line;
1875 List xtvs;                              /* Explicitly quantified vars      */
1876 List tvs; {                             /* Implicitly quantified vars      */
1877     if (nonNull(xtvs)) {
1878         List vs = tvs;
1879         for (; nonNull(vs); vs=tl(vs)) {
1880             if (!varIsMember(textOf(hd(vs)),xtvs)) {
1881                 ERRMSG(line) "Quantifier does not mention type variable \"%s\"",
1882                              textToStr(textOf(hd(vs)))
1883                 EEND;
1884             }
1885         }
1886         for (vs=xtvs; nonNull(vs); vs=tl(vs)) {
1887             if (!varIsMember(textOf(hd(vs)),tvs)) {
1888                 ERRMSG(line) "Quantified type variable \"%s\" is not used",
1889                              textToStr(textOf(hd(vs)))
1890                 EEND;
1891             }
1892             if (varIsMember(textOf(hd(vs)),tl(vs))) {
1893                 ERRMSG(line) "Quantified type variable \"%s\" is repeated",
1894                              textToStr(textOf(hd(vs)))
1895                 EEND;
1896             }
1897         }
1898     }
1899 }
1900
1901 static Type local depTopType(l,tvs,t)   /* Check top-level of type sig     */
1902 Int  l;
1903 List tvs;
1904 Type t; {
1905     Type prev = NIL;
1906     Type t1   = t;
1907     Int  nr2  = 0;
1908     Int  i    = 1;
1909     for (; getHead(t1)==typeArrow && argCount==2; ++i) {
1910         arg(fun(t1)) = depCompType(l,tvs,arg(fun(t1)));
1911         if (isPolyOrQualType(arg(fun(t1)))) {
1912             nr2 = i;
1913         }
1914         prev = t1;
1915         t1   = arg(t1);
1916     }
1917     if (nonNull(prev)) {
1918         arg(prev) = depTypeExp(l,tvs,t1);
1919     } else {
1920         t = depTypeExp(l,tvs,t1);
1921     }
1922     if (nr2>0) {
1923         t = ap(RANK2,pair(mkInt(nr2),t));
1924     }
1925     return t;
1926 }
1927
1928 static Type local depCompType(l,tvs,t)  /* Check component type for constr */
1929 Int  l;
1930 List tvs;
1931 Type t; {
1932   Int  ntvs = length(tvs);
1933   List nfr  = NIL;
1934   if (isPolyType(t)) {
1935     List vs  = fst(snd(t));
1936     t        = monotypeOf(t);
1937     tvs      = checkQuantVars(l,vs,tvs,t);
1938     nfr      = replicate(length(vs),NIL);
1939   }
1940   if (isQualType(t)) {
1941     map2Over(depPredExp,l,tvs,fst(snd(t)));
1942     snd(snd(t)) = depTypeExp(l,tvs,snd(snd(t)));
1943     if (isAmbiguous(t)) {
1944       ambigError(l,"type component",NIL,t);
1945     }
1946   } else {
1947     t = depTypeExp(l,tvs,t);
1948   }
1949   if (isNull(nfr)) {
1950     return t;
1951   }
1952   take(ntvs,tvs);
1953   return mkPolyType(nfr,t);
1954 }
1955
1956 static Type local depTypeExp(line,tyvars,type)
1957 Int  line;
1958 List tyvars;
1959 Type type; {
1960     switch (whatIs(type)) {
1961         case AP         : fst(type) = depTypeExp(line,tyvars,fst(type));
1962                           snd(type) = depTypeExp(line,tyvars,snd(type));
1963                           break;
1964
1965         case VARIDCELL  : return depTypeVar(line,tyvars,textOf(type));
1966
1967         case QUALIDENT  : if (isQVar(type)) {
1968                               ERRMSG(line) "Qualified type variables not allowed"
1969                               EEND;
1970                           }
1971                           /* deliberate fall through */
1972         case CONIDCELL  : {   Tycon tc = findQualTycon(type);
1973                               if (isNull(tc)) {
1974                                   ERRMSG(line)
1975                                       "Undefined type constructor \"%s\"",
1976                                       identToStr(type)
1977                                   EEND;
1978                               }
1979                               if (cellIsMember(tc,tyconDefns) &&
1980                                   !cellIsMember(tc,tcDeps)) {
1981                                   tcDeps = cons(tc,tcDeps);
1982                               }
1983                               return tc;
1984                           }
1985
1986 #if TREX
1987         case EXT        : h98DoesntSupport(line,"extensible records");
1988 #endif
1989         case TYCON      :
1990         case TUPLE      : break;
1991
1992         default         : internal("depTypeExp");
1993     }
1994     return type;
1995 }
1996
1997 static Type local depTypeVar(line,tyvars,tv)
1998 Int  line;
1999 List tyvars;
2000 Text tv; {
2001     Int offset = 0;
2002     Int found  = (-1);
2003
2004     for (; nonNull(tyvars); offset++) {
2005         if (tv==textOf(hd(tyvars))) {
2006             found = offset;
2007         }
2008         tyvars = tl(tyvars);
2009     }
2010     if (found<0) {
2011         Cell vt = findBtyvs(tv);
2012         if (nonNull(vt)) {
2013             return fst(vt);
2014         }
2015         ERRMSG(line) "Undefined type variable \"%s\"", textToStr(tv)
2016         EEND;
2017     }
2018     return mkOffset(found);
2019 }
2020
2021 static List local checkQuantVars(line,vs,tvs,body)
2022 Int  line;
2023 List vs;                                /* variables to quantify over      */
2024 List tvs;                               /* variables already in scope      */
2025 Cell body; {                            /* type/constr for scope of vars   */
2026     if (nonNull(vs)) {
2027         List bvs = typeVarsIn(body,NIL,NIL,NIL);
2028         List us  = vs;
2029         for (; nonNull(us); us=tl(us)) {
2030             Text u = textOf(hd(us));
2031             if (varIsMember(u,tl(us))) {
2032                 ERRMSG(line) "Duplicated quantified variable %s",
2033                              textToStr(u)
2034                 EEND;
2035             }
2036 #if 0
2037             if (varIsMember(u,tvs)) {
2038                 ERRMSG(line) "Local quantifier for %s hides an outer use",
2039                              textToStr(u)
2040                 EEND;
2041             }
2042 #endif
2043             if (!varIsMember(u,bvs)) {
2044                 ERRMSG(line) "Locally quantified variable %s is not used",
2045                              textToStr(u)
2046                 EEND;
2047             }
2048         }
2049         tvs = appendOnto(tvs,vs);
2050     }
2051     return tvs;
2052 }
2053
2054 /* --------------------------------------------------------------------------
2055  * Check for ambiguous types:
2056  * A type  Preds => type  is ambiguous if not (TV(P) `subset` TV(type))
2057  * ------------------------------------------------------------------------*/
2058
2059 List offsetTyvarsIn(t,vs)               /* add list of offset tyvars in t  */
2060 Type t;                                 /* to list vs                      */
2061 List vs; {
2062     switch (whatIs(t)) {
2063         case AP       : return offsetTyvarsIn(fun(t),
2064                                 offsetTyvarsIn(arg(t),vs));
2065
2066         case OFFSET   : if (cellIsMember(t,vs))
2067                             return vs;
2068                         else
2069                             return cons(t,vs);
2070
2071         case QUAL     : return offsetTyvarsIn(snd(t),vs);
2072
2073         case POLYTYPE : return offsetTyvarsIn(monotypeOf(t),vs);
2074                         /* slightly inaccurate, but won't matter here      */
2075
2076         case EXIST    :
2077         case RANK2    : return offsetTyvarsIn(snd(snd(t)),vs);
2078
2079         default       : return vs;
2080     }
2081 }
2082
2083 List zonkTyvarsIn(t,vs)
2084 Type t;
2085 List vs; {
2086     switch (whatIs(t)) {
2087         case AP       : return zonkTyvarsIn(fun(t),
2088                                  zonkTyvarsIn(arg(t),vs));
2089
2090         case INTCELL  : if (cellIsMember(t,vs))
2091                             return vs;
2092                         else
2093                             return cons(t,vs);
2094
2095         /* this case will lead to a type error --
2096            much better than reporting an internal error ;-) */
2097         /* case OFFSET   : internal("zonkTyvarsIn"); */
2098
2099         default       : return vs;
2100     }
2101 }
2102
2103 static List local otvars(pi,os)         /* os is a list of offsets that    */
2104 Cell pi;                                /* refer to the arguments of pi;   */
2105 List os; {                              /* find list of offsets in those   */
2106     List us = NIL;                      /* positions                       */
2107     for (; nonNull(os); os=tl(os)) {
2108         us = offsetTyvarsIn(nthArg(offsetOf(hd(os)),pi),us);
2109     }
2110     return us;
2111 }
2112
2113 static List local otvarsZonk(pi,os,o)   /* same as above, but zonks        */
2114 Cell pi;
2115 List os; {
2116     List us = NIL;
2117     for (; nonNull(os); os=tl(os)) {
2118         Type t = zonkType(nthArg(offsetOf(hd(os)),pi),o);
2119         us = zonkTyvarsIn(t,us);
2120     }
2121     return us;
2122 }
2123
2124 static Bool local odiff(us,vs)
2125 List us, vs; {
2126     while (nonNull(us) && cellIsMember(hd(us),vs)) {
2127         us = tl(us);
2128     }
2129     return us;
2130 }
2131
2132 static Bool local osubset(us,vs)        /* Determine whether us is subset  */
2133 List us, vs; {                          /* of vs                           */
2134     while (nonNull(us) && cellIsMember(hd(us),vs)) {
2135         us = tl(us);
2136     }
2137     return isNull(us);
2138 }
2139
2140 List oclose(fds,vs)     /* Compute closure of vs wrt to fds*/
2141 List fds;
2142 List vs; {
2143     Bool changed = TRUE;
2144     while (changed) {
2145         List fds1 = NIL;
2146         changed = FALSE;
2147         while (nonNull(fds)) {
2148             Cell fd   = hd(fds);
2149             List next = tl(fds);
2150             if (osubset(fst(fd),vs)) {  /* Test if fd applies              */
2151                 List os = snd(fd);
2152                 for (; nonNull(os); os=tl(os)) {
2153                     if (!cellIsMember(hd(os),vs)) {
2154                         vs      = cons(hd(os),vs);
2155                         changed = TRUE;
2156                     }
2157                 }
2158             } else {                    /* Didn't apply this time, so keep */
2159                 tl(fds) = fds1;
2160                 fds1    = fds;
2161             }
2162             fds = next;
2163         }
2164         fds = fds1;
2165     }
2166     return vs;
2167 }
2168
2169 Bool isAmbiguous(type)                  /* Determine whether type is       */
2170 Type type; {                            /* ambiguous                       */
2171     if (isPolyType(type)) {
2172         type = monotypeOf(type);
2173     }
2174     if (isQualType(type)) {             /* only qualified types can be     */
2175         List ps   = fst(snd(type));     /* ambiguous                       */
2176         List tvps = offsetTyvarsIn(ps,NIL);
2177         List tvts = offsetTyvarsIn(snd(snd(type)),NIL);
2178         List fds  = calcFunDeps(ps);
2179
2180         tvts = oclose(fds,tvts);        /* Close tvts under fds            */
2181         return !osubset(tvps,tvts);
2182     }
2183     return FALSE;
2184 }
2185
2186 List calcFunDeps(ps)
2187 List ps; {
2188     List fds  = NIL;
2189     for (; nonNull(ps); ps=tl(ps)) {/* Calc functional dependencies        */
2190         Cell pi = hd(ps);
2191         Cell c  = getHead(pi);
2192         if (isClass(c)) {
2193             List xfs = cclass(c).xfds;
2194             for (; nonNull(xfs); xfs=tl(xfs)) {
2195                 List fs = snd(hd(xfs));
2196                 for (; nonNull(fs); fs=tl(fs)) {
2197                     fds = cons(pair(otvars(pi,fst(hd(fs))),
2198                                     otvars(pi,snd(hd(fs)))),fds);
2199                 }
2200             }
2201         }
2202 #if IPARAM
2203         else if (isIP(c)) {
2204             fds = cons(pair(NIL,offsetTyvarsIn(arg(pi),NIL)),fds);
2205         }
2206 #endif
2207     }
2208     return fds;
2209 }
2210
2211 List calcFunDepsPreds(ps)
2212 List ps; {
2213     List fds  = NIL;
2214     for (; nonNull(ps); ps=tl(ps)) {/* Calc functional dependencies        */
2215         Cell pi3 = hd(ps);
2216         Cell pi = fst3(pi3);
2217         Cell c  = getHead(pi);
2218         Int o = intOf(snd3(pi3));
2219         if (isClass(c)) {
2220             List xfs = cclass(c).xfds;
2221             for (; nonNull(xfs); xfs=tl(xfs)) {
2222                 List fs = snd(hd(xfs));
2223                 for (; nonNull(fs); fs=tl(fs)) {
2224                     fds = cons(pair(otvarsZonk(pi,fst(hd(fs)),o),
2225                                     otvarsZonk(pi,snd(hd(fs)),o)),fds);
2226                 }
2227             }
2228         }
2229 #if IPARAM
2230         else if (isIP(c)) {
2231             fds = cons(pair(NIL,zonkTyvarsIn(arg(pi),NIL)),fds);
2232         }
2233 #endif
2234     }
2235     return fds;
2236 }
2237
2238 Void ambigError(line,where,e,type)      /* produce error message for       */
2239 Int    line;                            /* ambiguity                       */
2240 String where;
2241 Cell   e;
2242 Type   type; {
2243     ERRMSG(line) "Ambiguous type signature in %s", where ETHEN
2244     ERRTEXT      "\n*** ambiguous type : " ETHEN ERRTYPE(type);
2245     if (nonNull(e)) {
2246         ERRTEXT  "\n*** assigned to    : " ETHEN ERREXPR(e);
2247     }
2248     ERRTEXT      "\n"
2249     EEND;
2250 }
2251
2252 /* --------------------------------------------------------------------------
2253  * Kind inference for simple types:
2254  * ------------------------------------------------------------------------*/
2255
2256 static Void local kindConstr(line,alpha,m,c)
2257 Int  line;                              /* Determine kind of constructor   */
2258 Int  alpha;
2259 Int  m;
2260 Cell c; {
2261     Cell h = getHead(c);
2262     Int  n = argCount;
2263
2264 #ifdef DEBUG_KINDS
2265     Printf("kindConstr: alpha=%d, m=%d, c=",alpha,m);
2266     printType(stdout,c);
2267     Printf("\n");
2268 #endif
2269
2270     switch (whatIs(h)) {
2271         case POLYTYPE : if (n!=0) {
2272                             internal("kindConstr1");
2273                         } else {
2274                             static String pt = "polymorphic type";
2275                             Type  t  = dropRank1(c,alpha,m);
2276                             Kinds ks = polySigOf(t);
2277                             Int   m1 = 0;
2278                             Int   beta;
2279                             for (; isAp(ks); ks=tl(ks)) {
2280                                 m1++;
2281                             }
2282                             beta        = newKindvars(m1);
2283                             unkindTypes = cons(pair(mkInt(beta),t),unkindTypes);
2284                             checkKind(line,beta,m1,monotypeOf(t),NIL,pt,STAR,0);
2285                         }
2286                         return;
2287
2288         case CDICTS   :
2289         case QUAL     : if (n!=0) {
2290                             internal("kindConstr2");
2291                         }
2292                         map3Proc(kindPred,line,alpha,m,fst(snd(c)));
2293                         kindConstr(line,alpha,m,snd(snd(c)));
2294                         return;
2295
2296         case EXIST    :
2297         case RANK2    : kindConstr(line,alpha,m,snd(snd(c)));
2298                         return;
2299
2300 #if TREX
2301         case EXT      : if (n!=2) {
2302                             ERRMSG(line)
2303                                 "Illegal use of row in " ETHEN ERRTYPE(c);
2304                             ERRTEXT "\n"
2305                             EEND;
2306                         }
2307                         break;
2308 #endif
2309
2310         case TYCON    : if (isSynonym(h) && n<tycon(h).arity) {
2311                             ERRMSG(line)
2312                               "Not enough arguments for type synonym \"%s\"",
2313                               textToStr(tycon(h).text)
2314                             EEND;
2315                         }
2316                         break;
2317     }
2318
2319     if (n==0) {                         /* trivial case, no arguments      */
2320         typeIs = kindAtom(alpha,c);
2321     } else {                            /* non-trivial application         */
2322         static String app = "constructor application";
2323         Cell   a = c;
2324         Int    i;
2325         Kind   k;
2326         Int    beta;
2327
2328         varKind(n);
2329         beta   = typeOff;
2330         k      = typeIs;
2331
2332         typeIs = kindAtom(alpha,h);     /* h  :: v1 -> ... -> vn -> w      */
2333         shouldKind(line,h,c,app,k,beta);
2334
2335         for (i=n; i>0; --i) {           /* ci :: vi for each 1 <- 1..n     */
2336             checkKind(line,alpha,m,arg(a),c,app,aVar,beta+i-1);
2337             a = fun(a);
2338         }
2339         tyvarType(beta+n);              /* inferred kind is w              */
2340     }
2341 }
2342
2343 static Kind local kindAtom(alpha,c)     /* Find kind of atomic constructor */
2344 Int  alpha;
2345 Cell c; {
2346     switch (whatIs(c)) {
2347         case TUPLE     : return simpleKind(tupleOf(c)); /*(,)::* -> * -> * */
2348         case OFFSET    : return mkInt(alpha+offsetOf(c));
2349         case TYCON     : return tycon(c).kind;
2350         case INTCELL   : return c;
2351         case VARIDCELL :
2352         case VAROPCELL : {   Cell vt = findBtyvs(textOf(c));
2353                              if (nonNull(vt)) {
2354                                  return snd(vt);
2355                              }
2356                          }
2357 #if TREX
2358         case EXT       : return extKind;
2359 #endif
2360     }
2361 #if DEBUG_KINDS
2362     Printf("kindAtom(%d,whatIs(%d)) on ",alpha,whatIs(c));
2363     printType(stdout,c);
2364     Printf("\n");
2365 #endif
2366     internal("kindAtom");
2367     return STAR;/* not reached */
2368 }
2369
2370 static Void local kindPred(l,alpha,m,pi)/* Check kinds of arguments in pred*/
2371 Int  l;
2372 Int  alpha;
2373 Int  m;
2374 Cell pi; {
2375 #if TREX
2376     if (isAp(pi) && isExt(fun(pi))) {
2377         static String lackspred = "lacks predicate";
2378         checkKind(l,alpha,m,arg(pi),NIL,lackspred,ROW,0);
2379         return;
2380     }
2381 #endif
2382 #if IPARAM
2383     if (isAp(pi) && whatIs(fun(pi)) == IPCELL) {
2384         static String ippred = "iparam predicate";
2385         checkKind(l,alpha,m,arg(pi),NIL,ippred,STAR,0);
2386         return;
2387     }
2388 #endif
2389     {   static String predicate = "class constraint";
2390         Class c  = getHead(pi);
2391         List  as = getArgs(pi);
2392         Kinds ks = cclass(c).kinds;
2393
2394         while (nonNull(ks)) {
2395             checkKind(l,alpha,m,hd(as),NIL,predicate,hd(ks),0);
2396             ks = tl(ks);
2397             as = tl(as);
2398         }
2399     }
2400 }
2401
2402 static Void local kindType(line,wh,type)/* check that (poss qualified) type*/
2403 Int    line;                            /* is well-kinded                  */
2404 String wh;
2405 Type   type; {
2406     checkKind(line,0,0,type,NIL,wh,STAR,0);
2407 }
2408
2409 static Void local fixKinds() {          /* add kind annotations to types   */
2410     for (; nonNull(unkindTypes); unkindTypes=tl(unkindTypes)) {
2411         Pair pr   = hd(unkindTypes);
2412         Int  beta = intOf(fst(pr));
2413         Cell qts  = polySigOf(snd(pr));
2414         for (;;) {
2415             if (isNull(hd(qts))) {
2416                 hd(qts) = copyKindvar(beta++);
2417             } else {
2418                 internal("fixKinds");
2419             }
2420             if (nonNull(tl(qts))) {
2421                 qts = tl(qts);
2422             } else {
2423                 tl(qts) = STAR;
2424                 break;
2425             }
2426         }
2427 #ifdef DEBUG_KINDS
2428         Printf("Type expression: ");
2429         printType(stdout,snd(pr));
2430         Printf(" :: ");
2431         printKind(stdout,polySigOf(snd(pr)));
2432         Printf("\n");
2433 #endif
2434     }
2435 }
2436
2437 /* --------------------------------------------------------------------------
2438  * Kind checking of groups of type constructors and classes:
2439  * ------------------------------------------------------------------------*/
2440
2441 static Void local kindTCGroup(tcs)      /* find kinds for mutually rec. gp */
2442 List tcs; {                             /* of tycons and classes           */
2443     emptySubstitution();
2444     unkindTypes = NIL;
2445     mapProc(initTCKind,tcs);
2446     mapProc(kindTC,tcs);
2447     mapProc(genTC,tcs);
2448     fixKinds();
2449     emptySubstitution();
2450 }
2451     
2452 static Void local initTCKind(c)         /* build initial kind/arity for c  */
2453 Cell c; {
2454     if (isTycon(c)) {                   /* Initial kind of tycon is:       */
2455         Int beta = newKindvars(1);      /*    v1 -> ... -> vn -> vn+1      */
2456         varKind(tycon(c).arity);        /* where n is the arity of c.      */
2457         bindTv(beta,typeIs,typeOff);    /* For data definitions, vn+1 == * */
2458         switch (whatIs(tycon(c).what)) {
2459             case NEWTYPE  :
2460             case DATATYPE : bindTv(typeOff+tycon(c).arity,STAR,0);
2461         }
2462         tycon(c).kind = mkInt(beta);
2463     } else {
2464         Int n    = cclass(c).arity;
2465         Int beta = newKindvars(n);
2466         cclass(c).kinds = NIL;
2467         while (n>0) {
2468             n--;
2469             cclass(c).kinds = pair(mkInt(beta+n),cclass(c).kinds);
2470         }
2471     }
2472 }
2473
2474 static Void local kindTC(c)             /* check each part of a tycon/class*/
2475 Cell c; {                               /* is well-kinded                  */
2476     if (isTycon(c)) {
2477         static String cfun = "constructor function";
2478         static String tsyn = "synonym definition";
2479         Int line = tycon(c).line;
2480         Int beta = tyvar(intOf(tycon(c).kind))->offs;
2481         Int m    = tycon(c).arity;
2482         switch (whatIs(tycon(c).what)) {
2483             case NEWTYPE     :
2484             case DATATYPE    : {   List cs = tycon(c).defn;
2485                                    if (isQualType(cs)) {
2486                                        map3Proc(kindPred,line,beta,m,
2487                                                                 fst(snd(cs)));
2488                                        tycon(c).defn = cs = snd(snd(cs));
2489                                    }
2490                                    for (; hasCfun(cs); cs=tl(cs)) {
2491                                        kindType(line,cfun,name(hd(cs)).type);
2492                                    }
2493                                    break;
2494                                }
2495
2496             default          : checkKind(line,beta,m,tycon(c).defn,NIL,
2497                                                         tsyn,aVar,beta+m);
2498         }
2499     }
2500     else {                              /* scan type exprs in class defn to*/
2501         List ms   = fst(cclass(c).members);
2502         Int  m    = cclass(c).arity;    /* determine the class signature   */
2503         Int  beta = newKindvars(m);
2504         kindPred(cclass(c).line,beta,m,cclass(c).head);
2505         map3Proc(kindPred,cclass(c).line,beta,m,cclass(c).supers);
2506         for (; nonNull(ms); ms=tl(ms)) {
2507             Int  line = intOf(fst3(hd(ms)));
2508             Type type = thd3(hd(ms));
2509             kindType(line,"member function type signature",type);
2510         }
2511     }
2512 }
2513
2514 static Void local genTC(c)              /* generalise kind inferred for    */
2515 Cell c; {                               /* given tycon/class               */
2516     if (isTycon(c)) {
2517         tycon(c).kind = copyKindvar(intOf(tycon(c).kind));
2518 #ifdef DEBUG_KINDS
2519         Printf("%s :: ",textToStr(tycon(c).text));
2520         printKind(stdout,tycon(c).kind);
2521         Putchar('\n');
2522 #endif
2523     } else {
2524         Kinds ks = cclass(c).kinds;
2525         for (; nonNull(ks); ks=tl(ks)) {
2526             hd(ks) = copyKindvar(intOf(hd(ks)));
2527         }
2528 #ifdef DEBUG_KINDS
2529         Printf("%s :: ",textToStr(cclass(c).text));
2530         printKinds(stdout,cclass(c).kinds);
2531         Putchar('\n');
2532 #endif
2533     }
2534 }
2535
2536 /* --------------------------------------------------------------------------
2537  * Static analysis of instance declarations:
2538  *
2539  * The first part of the static analysis is performed as the declarations
2540  * are read during parsing:
2541  * - make new entry in instance table
2542  * - record line number of declaration
2543  * - build list of instances defined in current script for use in later
2544  *   stages of static analysis.
2545  * ------------------------------------------------------------------------*/
2546
2547 Void instDefn(line,head,ms)            /* process new instance definition  */
2548 Int  line;                             /* definition line number           */
2549 Cell head;                             /* inst header :: (context,Class)   */
2550 List ms; {                             /* instance members                 */
2551     Inst nw             = newInst();
2552     inst(nw).line       = line;
2553     inst(nw).specifics  = fst(head);
2554     inst(nw).head       = snd(head);
2555     inst(nw).implements = ms;
2556     instDefns           = cons(nw,instDefns);
2557 }
2558
2559 /* --------------------------------------------------------------------------
2560  * Further static analysis of instance declarations:
2561  *
2562  * Makes the following checks:
2563  * - Class part of header has form C (T a1 ... an) where C is a known
2564  *   class, and T is a known datatype constructor (or restricted synonym),
2565  *   and there is no previous C-T instance, and (T a1 ... an) has a kind
2566  *   appropriate for the class C.
2567  * - Each element of context is a valid class expression, with type vars
2568  *   drawn from a1, ..., an.
2569  * - All bindings are function bindings
2570  * - All bindings define member functions for class C
2571  * - Arrange bindings into appropriate order for member list
2572  * - No top level type signature declarations
2573  * ------------------------------------------------------------------------*/
2574
2575 Bool allowOverlap = FALSE;              /* TRUE => allow overlapping insts */
2576 Name nameListMonad = NIL;               /* builder function for List Monad */
2577
2578 static Void local checkInstDefn(in)     /* Validate instance declaration   */
2579 Inst in; {
2580     Int  line   = inst(in).line;
2581     List tyvars = typeVarsIn(inst(in).head,NIL,NIL,NIL);
2582     List tvps = NIL, tvts = NIL;
2583     List fds = NIL;
2584
2585     if (haskell98) {                    /* Check for `simple' type         */
2586         List tvs = NIL;
2587         Cell t   = arg(inst(in).head);
2588         for (; isAp(t); t=fun(t)) {
2589             if (!isVar(arg(t))) {
2590                 ERRMSG(line)
2591                    "syntax error in instance head (variable expected)"
2592                 EEND;
2593             }
2594             if (varIsMember(textOf(arg(t)),tvs)) {
2595                 ERRMSG(line) "repeated type variable \"%s\" in instance head",
2596                              textToStr(textOf(arg(t)))
2597                 EEND;
2598             }
2599             tvs = cons(arg(t),tvs);
2600         }
2601         if (isVar(t)) {
2602             ERRMSG(line)
2603                 "syntax error in instance head (constructor expected)"
2604             EEND;
2605         }
2606     }
2607
2608     /* add in the tyvars from the `specifics' so that we don't
2609        prematurely complain about undefined tyvars */
2610     tyvars = typeVarsIn(inst(in).specifics,NIL,NIL,tyvars);
2611     inst(in).head = depPredExp(line,tyvars,inst(in).head);
2612
2613     if (haskell98) {
2614         Type h = getHead(arg(inst(in).head));
2615         if (isSynonym(h)) {
2616             ERRMSG(line) "Cannot use type synonym in instance head"
2617             EEND;
2618         }
2619     }
2620
2621     map2Over(depPredExp,line,tyvars,inst(in).specifics);
2622
2623     /* OK, now we start over, and test for ambiguity */
2624     tvts = offsetTyvarsIn(inst(in).head,NIL);
2625     tvps = offsetTyvarsIn(inst(in).specifics,NIL);
2626     fds  = calcFunDeps(inst(in).specifics);
2627     tvts = oclose(fds,tvts);
2628     tvts = odiff(tvps,tvts);
2629     if (!isNull(tvts)) {
2630         ERRMSG(line) "Undefined type variable \"%s\"",
2631           textToStr(textOf(nth(offsetOf(hd(tvts)),tyvars)))
2632         EEND;
2633     }
2634
2635     h98CheckCtxt(line,"instance definition",FALSE,inst(in).specifics,NIL);
2636     inst(in).numSpecifics = length(inst(in).specifics);
2637     inst(in).c            = getHead(inst(in).head);
2638     if (!isClass(inst(in).c)) {
2639         ERRMSG(line) "Illegal predicate in instance declaration"
2640         EEND;
2641     }
2642
2643     if (nonNull(cclass(inst(in).c).fds)) {
2644         List fds = cclass(inst(in).c).fds;
2645         for (; nonNull(fds); fds=tl(fds)) {
2646             List as = otvars(inst(in).head, fst(hd(fds)));
2647             List bs = otvars(inst(in).head, snd(hd(fds)));
2648             List fs = calcFunDeps(inst(in).specifics);
2649             as = oclose(fs,as);
2650             if (!osubset(bs,as)) {
2651                 ERRMSG(inst(in).line)
2652                    "Instance is more general than a dependency allows"
2653                 ETHEN
2654                 ERRTEXT "\n*** Instance         : "
2655                 ETHEN ERRPRED(inst(in).head);
2656                 ERRTEXT "\n*** For class        : "
2657                 ETHEN ERRPRED(cclass(inst(in).c).head);
2658                 ERRTEXT "\n*** Under dependency : "
2659                 ETHEN ERRFD(hd(fds));
2660                 ERRTEXT "\n"
2661                 EEND;
2662             }
2663         }
2664     }
2665
2666     kindInst(in,length(tyvars));
2667     insertInst(in);
2668
2669     if (nonNull(extractSigdecls(inst(in).implements))) {
2670         ERRMSG(line)
2671           "Type signature declarations not permitted in instance declaration"
2672         EEND;
2673     }
2674     if (nonNull(extractFixdecls(inst(in).implements))) {
2675         ERRMSG(line)
2676           "Fixity declarations not permitted in instance declaration"
2677         EEND;
2678     }
2679     inst(in).implements = classBindings("instance",
2680                                         inst(in).c,
2681                                         extractBindings(inst(in).implements));
2682     inst(in).builder    = newInstImp(in);
2683     if (!preludeLoaded && isNull(nameListMonad) && isAp(inst(in).head)
2684         && fun(inst(in).head)==classMonad && arg(inst(in).head)==typeList) {
2685         nameListMonad = inst(in).builder;
2686     }
2687 }
2688
2689 static Void local insertInst(in)        /* Insert instance into class      */
2690 Inst in; {
2691     Class c    = inst(in).c;
2692     List  ins  = cclass(c).instances;
2693     List  prev = NIL;
2694
2695     if (nonNull(cclass(c).fds)) {       /* Check for conflicts with fds    */
2696         List ins1 = cclass(c).instances;
2697         for (; nonNull(ins1); ins1=tl(ins1)) {
2698             List fds = cclass(c).fds;
2699             substitution(RESET);
2700             for (; nonNull(fds); fds=tl(fds)) {
2701                 Int  alpha = newKindedVars(inst(in).kinds);
2702                 Int  beta  = newKindedVars(inst(hd(ins1)).kinds);
2703                 List as    = fst(hd(fds));
2704                 Bool same  = TRUE;
2705                 for (; same && nonNull(as); as=tl(as)) {
2706                     Int n = offsetOf(hd(as));
2707                     same &= unify(nthArg(n,inst(in).head),alpha,
2708                                   nthArg(n,inst(hd(ins1)).head),beta);
2709                 }
2710                 if (isNull(as) && same) {
2711                     for (as=snd(hd(fds)); same && nonNull(as); as=tl(as)) {
2712                         Int n = offsetOf(hd(as));
2713                         same &= sameType(nthArg(n,inst(in).head),alpha,
2714                                          nthArg(n,inst(hd(ins1)).head),beta);
2715                     }
2716                     if (!same) {
2717                         ERRMSG(inst(in).line)
2718                            "Instances are not consistent with dependencies"
2719                         ETHEN
2720                         ERRTEXT "\n*** This instance    : "
2721                         ETHEN ERRPRED(inst(in).head);
2722                         ERRTEXT "\n*** Conflicts with   : "
2723                         ETHEN ERRPRED(inst(hd(ins)).head);
2724                         ERRTEXT "\n*** For class        : "
2725                         ETHEN ERRPRED(cclass(c).head);
2726                         ERRTEXT "\n*** Under dependency : "
2727                         ETHEN ERRFD(hd(fds));
2728                         ERRTEXT "\n"
2729                         EEND;
2730                     }
2731                 }
2732             }
2733         }
2734     }
2735
2736
2737     substitution(RESET);
2738     while (nonNull(ins)) {              /* Look for overlap w/ other insts */
2739         Int alpha = newKindedVars(inst(in).kinds);
2740         Int beta  = newKindedVars(inst(hd(ins)).kinds);
2741         if (unifyPred(inst(in).head,alpha,inst(hd(ins)).head,beta)) {
2742             Cell pi  = copyPred(inst(in).head,alpha);
2743             if (allowOverlap && !haskell98) {
2744                 Bool bef = instCompare(in,hd(ins));
2745                 Bool aft = instCompare(hd(ins),in);
2746                 if (bef && !aft) {      /* in comes strictly before hd(ins)*/
2747                     break;
2748                 }
2749                 if (aft && !bef) {      /* in comes strictly after hd(ins) */
2750                     prev = ins;
2751                     ins  = tl(ins);
2752                     continue;
2753                 }
2754             }
2755 #if MULTI_INST
2756             if (multiInstRes && nonNull(inst(in).specifics)) {
2757                 break;
2758             } else {
2759 #endif
2760             ERRMSG(inst(in).line) "Overlapping instances for class \"%s\"",
2761                                   textToStr(cclass(c).text)
2762             ETHEN
2763             ERRTEXT "\n*** This instance   : " ETHEN ERRPRED(inst(in).head);
2764             ERRTEXT "\n*** Overlaps with   : " ETHEN
2765                                                ERRPRED(inst(hd(ins)).head);
2766             ERRTEXT "\n*** Common instance : " ETHEN
2767                                                ERRPRED(pi);
2768             ERRTEXT "\n"
2769             EEND;
2770         }
2771 #if MULTI_INST
2772             }
2773 #endif
2774         prev = ins;                     /* No overlap detected, so move on */
2775         ins  = tl(ins);                 /* to next instance                */
2776     }
2777     substitution(RESET);
2778
2779     if (nonNull(prev)) {                /* Insert instance at this point   */
2780         tl(prev) = cons(in,ins);
2781     } else {
2782         cclass(c).instances = cons(in,ins);
2783     }
2784 }
2785
2786 static Bool local instCompare(ia,ib)    /* See if ia is an instance of ib  */
2787 Inst ia, ib;{
2788     Int alpha = newKindedVars(inst(ia).kinds);
2789     Int beta  = newKindedVars(inst(ib).kinds);
2790     return matchPred(inst(ia).head,alpha,inst(ib).head,beta);
2791 }
2792
2793 static Name local newInstImp(in)        /* Make definition for inst builder*/
2794 Inst in; {
2795     Name b         = newName(inventText(),in);
2796     name(b).line   = inst(in).line;
2797     name(b).arity  = inst(in).numSpecifics;
2798     name(b).number = DFUNNAME;
2799     return b;
2800 }
2801
2802 /* --------------------------------------------------------------------------
2803  * Kind checking of instance declaration headers:
2804  * ------------------------------------------------------------------------*/
2805
2806 static Void local kindInst(in,freedom)  /* check predicates in instance    */
2807 Inst in;
2808 Int  freedom; {
2809     Int beta;
2810
2811     emptySubstitution();
2812     beta = newKindvars(freedom);
2813     kindPred(inst(in).line,beta,freedom,inst(in).head);
2814     if (whatIs(inst(in).specifics)!=DERIVE) {
2815         map3Proc(kindPred,inst(in).line,beta,freedom,inst(in).specifics);
2816     }
2817     for (inst(in).kinds = NIL; 0<freedom--; ) {
2818         inst(in).kinds = cons(copyKindvar(beta+freedom),inst(in).kinds);
2819     }
2820 #ifdef DEBUG_KINDS
2821     Printf("instance ");
2822     printPred(stdout,inst(in).head);
2823     Printf(" :: ");
2824     printKinds(stdout,inst(in).kinds);
2825     Putchar('\n');
2826 #endif
2827     emptySubstitution();
2828 }
2829
2830 /* --------------------------------------------------------------------------
2831  * Process derived instance requests:
2832  * ------------------------------------------------------------------------*/
2833
2834 static List derivedInsts;               /* list of derived instances       */
2835
2836 static Void local checkDerive(t,p,ts,ct)/* verify derived instance request */
2837 Tycon t;                                /* for tycon t, with explicit      */
2838 List  p;                                /* context p, component types ts   */
2839 List  ts;                               /* and named class ct              */
2840 Cell  ct; {
2841     Int   line = tycon(t).line;
2842     Class c    = findQualClass(ct);
2843     if (isNull(c)) {
2844         ERRMSG(line) "Unknown class \"%s\" in derived instance",
2845                      identToStr(ct)
2846         EEND;
2847     }
2848     addDerInst(line,c,p,dupList(ts),t,tycon(t).arity);
2849 }
2850
2851 static Void local addDerInst(line,c,p,cts,t,a)  /* Add a derived instance  */
2852 Int   line;
2853 Class c;
2854 List  p, cts;
2855 Type  t;
2856 Int   a; {
2857     Inst in;
2858     Cell head = t;                              /* Build instance head     */
2859     Int  i    = 0;
2860
2861     for (; i<a; i++) {
2862         head = ap(head,mkOffset(i));
2863     }
2864     head = ap(c,head);
2865
2866     in                  = newInst();
2867     inst(in).c          = c;
2868     inst(in).line       = line;
2869     inst(in).head       = head;
2870     inst(in).specifics  = ap(DERIVE,pair(dupList(p),cts));
2871     inst(in).implements = NIL;
2872     inst(in).kinds      = mkInt(a);
2873     derivedInsts        = cons(in,derivedInsts);
2874 }
2875
2876 Void addTupInst(c,n)                    /* Request derived instance of c   */
2877 Class c;                                /* for mkTuple(n) constructor      */
2878 Int   n; {
2879     Int  m   = n;
2880     List cts = NIL;
2881     while (0<m--) {
2882         cts = cons(mkOffset(m),cts);
2883     }
2884     cts = rev(cts);
2885     addDerInst(0,c,NIL,cts,mkTuple(n),n);
2886 }
2887
2888 #if TREX
2889 Inst addRecShowInst(c,e)                /* Generate instance for ShowRecRow*/
2890 Class c;                                /* c *must* be ShowRecRow          */
2891 Ext   e; {
2892     Inst in               = newInst();
2893     inst(in).c            = c;
2894     inst(in).head         = ap(c,ap2(e,aVar,bVar));
2895     inst(in).kinds        = extKind;
2896     inst(in).specifics    = cons(ap(classShow,aVar),
2897                                  cons(ap(e,bVar),
2898                                       cons(ap(c,bVar),NIL)));
2899     inst(in).numSpecifics = 3;
2900     inst(in).builder      = implementRecShw(extText(e),in);
2901     cclass(c).instances   = appendOnto(cclass(c).instances,singleton(in));
2902     return in;
2903 }
2904
2905 Inst addRecEqInst(c,e)                  /* Generate instance for EqRecRow  */
2906 Class c;                                /* c *must* be EqRecRow            */
2907 Ext   e; {
2908     Inst in               = newInst();
2909     inst(in).c            = c;
2910     inst(in).head         = ap(c,ap2(e,aVar,bVar));
2911     inst(in).kinds        = extKind;
2912     inst(in).specifics    = cons(ap(classEq,aVar),
2913                                  cons(ap(e,bVar),
2914                                       cons(ap(c,bVar),NIL)));
2915     inst(in).numSpecifics = 3;
2916     inst(in).builder      = implementRecEq(extText(e),in);
2917     cclass(c).instances   = appendOnto(cclass(c).instances,singleton(in));
2918     return in;
2919 }
2920 #endif
2921
2922 /* --------------------------------------------------------------------------
2923  * Calculation of contexts for derived instances:
2924  *
2925  * Allowing arbitrary types to appear in contexts makes it rather harder
2926  * to decide what the context for a derived instance should be.  For
2927  * example, given:
2928  *
2929  *    data T a = MkT [a] deriving Show,
2930  *
2931  * we could have either of the following:
2932  *
2933  *    instance (Show [a]) => Show (T a) where ...
2934  *    instance (Show a) => Show (T a) where ...
2935  *
2936  * (assuming, of course, that instance (Show a) => Show [a]).  For now, we
2937  * choose to reduce contexts in the hope of detecting errors at an earlier
2938  * stage---in contrast with value definitions, there is no way for a user
2939  * to provide something analogous to a `type signature' by which they might
2940  * be able to control this behaviour themselves.  We eliminate tautological
2941  * predicates, but only allow predicates to appear in the final result if
2942  * they have at least one argument with a variable at its head.
2943  *
2944  * In general, we have to deal with mutually recursive instance declarations.
2945  * We find a solution in the obvious way by iterating to find a fixed point.
2946  * Of course, without restrictions on the form of instance declarations, we
2947  * cannot be sure that this will always terminate!
2948  *
2949  * For each instance we maintain a pair of the form DERIVE (ctxt,ps).
2950  * Ctxt is a list giving the parts of the context that have been produced
2951  * so far in the form of predicate skeletons.  During the calculation of
2952  * derived instances, we attach a dummy NIL value to the end of the list
2953  * which acts as a kind of `variable': other parts of the system maintain
2954  * pointers to this variable, and use it to detect when the context has
2955  * been extended with new elements.  Meanwhile, ps is a list containing
2956  * predicates (pi,o) together with (delayed) substitutions of the form
2957  * (o,xs) where o is an offset and xs is one of the context variables
2958  * described above, which may have been partially instantiated.
2959  * ------------------------------------------------------------------------*/
2960
2961 static Bool instsChanged;
2962
2963 static Void local deriveContexts(is)    /* Calc contexts for derived insts */
2964 List is; {
2965     emptySubstitution();
2966     mapProc(initDerInst,is);            /* Prepare derived instances       */
2967
2968     do {                                /* Main calculation of contexts    */
2969         instsChanged = FALSE;
2970         mapProc(calcInstPreds,is);
2971     } while (instsChanged);
2972
2973     mapProc(tidyDerInst,is);            /* Tidy up results                 */
2974 }
2975
2976 static Void local initDerInst(in)       /* Prepare instance for calculation*/
2977 Inst in; {                              /* of derived instance context     */
2978     Cell spcs = inst(in).specifics;
2979     Int  beta = newKindedVars(inst(in).kinds);
2980     if (whatIs(spcs)!=DERIVE) {
2981         internal("initDerInst");
2982     }
2983     fst(snd(spcs)) = appendOnto(fst(snd(spcs)),singleton(NIL));
2984     for (spcs=snd(snd(spcs)); nonNull(spcs); spcs=tl(spcs)) {
2985         hd(spcs) = ap2(inst(in).c,hd(spcs),mkInt(beta));
2986     }
2987     inst(in).numSpecifics = beta;
2988
2989 #ifdef DEBUG_DERIVING
2990     Printf("initDerInst: ");
2991     printPred(stdout,inst(in).head);
2992     Printf("\n");
2993     printContext(stdout,snd(snd(inst(in).specifics)));
2994     Printf("\n");
2995 #endif
2996 }
2997
2998 static Void local calcInstPreds(in)     /* Calculate next approximation    */
2999 Inst in; {                              /* of the context for a derived    */
3000     List retain = NIL;                  /* instance                        */
3001     List ps     = snd(snd(inst(in).specifics));
3002     List spcs   = fst(snd(inst(in).specifics));
3003     Int  beta   = inst(in).numSpecifics;
3004     Int  its    = 1;
3005     Int  factor = 1+length(ps);
3006
3007 #ifdef DEBUG_DERIVING
3008     Printf("calcInstPreds: ");
3009     printPred(stdout,inst(in).head);
3010     Printf("\n");
3011 #endif
3012
3013     while (nonNull(ps)) {
3014         Cell p = hd(ps);
3015         ps     = tl(ps);
3016         if (its++ >= factor*cutoff) {
3017             Cell bpi = inst(in).head;
3018             Cell pi  = copyPred(fun(p),intOf(snd(p)));
3019             ERRMSG(inst(in).line) "\n*** Cannot derive " ETHEN ERRPRED(bpi);
3020             ERRTEXT " after %d iterations.", its-1   ETHEN
3021             ERRTEXT
3022                 "\n*** This may indicate that the problem is undecidable.  However,\n"
3023             ETHEN ERRTEXT
3024                 "*** you may still try to increase the cutoff limit using the -c\n"
3025             ETHEN ERRTEXT
3026                 "*** option and then try again.  (The current setting is -c%d)\n",
3027                 cutoff
3028             EEND;
3029         }
3030         if (isInt(fst(p))) {                    /* Delayed substitution?   */
3031             List qs = snd(p);
3032             for (; nonNull(hd(qs)); qs=tl(qs)) {
3033                 ps = cons(pair(hd(qs),fst(p)),ps);
3034             }
3035             retain = cons(pair(fst(p),qs),retain);
3036         }
3037 #if TREX
3038         else if (isExt(fun(fst(p)))) {          /* Lacks predicate         */
3039             Text   l = extText(fun(fst(p)));
3040             Type   t = arg(fst(p));
3041             Int    o = intOf(snd(p));
3042             Type   h;
3043             Tyvar *tyv;
3044
3045             deRef(tyv,t,o);
3046             h = getDerefHead(t,o);
3047             while (isExt(h) && argCount==2 && l!=extText(h)) {
3048                 t = arg(t);
3049                 deRef(tyv,t,o);
3050                 h = getDerefHead(t,o);
3051             }
3052             if (argCount==0 && isOffset(h)) {
3053                 maybeAddPred(ap(fun(fun(p)),h),o,beta,spcs);
3054             } else if (argCount!=0 || h!=typeNoRow) {
3055                 Cell bpi = inst(in).head;
3056                 Cell pi  = copyPred(fun(p),intOf(snd(p)));
3057                 ERRMSG(inst(in).line) "Cannot derive " ETHEN ERRPRED(bpi);
3058                 ERRTEXT " because predicate " ETHEN ERRPRED(pi);
3059                 ERRTEXT " does not hold\n"
3060                 EEND;
3061             }
3062         }
3063 #endif
3064         else {                                  /* Class predicate         */
3065             Cell pi  = fst(p);
3066             Int  o   = intOf(snd(p));
3067             Inst in1 = findInstFor(pi,o);
3068             if (nonNull(in1)) {
3069                 List qs  = inst(in1).specifics;
3070                 Int  off = mkInt(typeOff);
3071                 if (whatIs(qs)==DERIVE) {       /* Still being derived     */
3072                     for (qs=fst(snd(qs)); nonNull(hd(qs)); qs=tl(qs)) {
3073                         ps = cons(pair(hd(qs),off),ps);
3074                     }
3075                     retain = cons(pair(off,qs),retain);
3076                 } else {                        /* Previously def'd inst   */
3077                     for (; nonNull(qs); qs=tl(qs)) {
3078                         ps = cons(pair(hd(qs),off),ps);
3079                     }
3080                 }
3081             } else {                            /* No matching instance    */
3082                 Cell qi = pi;
3083                 while (isAp(qi) && isOffset(getDerefHead(arg(qi),o))) {
3084                     qi = fun(qi);
3085                 }
3086                 if (isAp(qi)) {
3087                     Cell bpi = inst(in).head;
3088                     pi       = copyPred(pi,o);
3089                     ERRMSG(inst(in).line) "An instance of " ETHEN ERRPRED(pi);
3090                     ERRTEXT " is required to derive "       ETHEN ERRPRED(bpi);
3091                     ERRTEXT "\n"
3092                     EEND;
3093                 } else {
3094                     maybeAddPred(pi,o,beta,spcs);
3095                 }
3096             }
3097         }
3098     }
3099     snd(snd(inst(in).specifics)) = retain;
3100 }
3101
3102 static Void local maybeAddPred(pi,o,beta,ps)
3103 Cell pi;                                /* Add predicate pi to the list ps,*/
3104 Int  o;                                 /* setting the instsChanged flag if*/
3105 Int  beta;                              /* pi is not already a member and  */
3106 List ps; {                              /* using beta to adjust vars       */
3107     Cell c = getHead(pi);
3108     for (; nonNull(ps); ps=tl(ps)) {
3109         if (isNull(hd(ps))) {           /* reached the `dummy' end of list?*/
3110             hd(ps)       = copyAdj(pi,o,beta);
3111             tl(ps)       = pair(NIL,NIL);
3112             instsChanged = TRUE;
3113             return;
3114         } else if (c==getHead(hd(ps)) && samePred(pi,o,hd(ps),beta)) {
3115             return;
3116         }
3117     }
3118 }
3119
3120 static Cell local copyAdj(c,o,beta)     /* Copy (c,o), replacing vars with */
3121 Cell c;                                 /* offsets relative to beta.       */
3122 Int  o;
3123 Int  beta; {
3124     switch (whatIs(c)) {
3125         case AP     : {   Cell l = copyAdj(fst(c),o,beta);
3126                           Cell r = copyAdj(snd(c),o,beta);
3127                           return ap(l,r);
3128                       }
3129
3130         case OFFSET : {   Int   vn   = o+offsetOf(c);
3131                           Tyvar *tyv = tyvar(vn);
3132                           if (isBound(tyv)) {
3133                               return copyAdj(tyv->bound,tyv->offs,beta);
3134                           }
3135                           vn -= beta;
3136                           if (vn<0 || vn>=NUM_OFFSETS) {
3137                               internal("copyAdj");
3138                           }
3139                           return mkOffset(vn);
3140                       }
3141     }
3142     return c;
3143 }
3144
3145 static Void local tidyDerInst(in)       /* Tidy up results of derived inst */
3146 Inst in; {                              /* calculations                    */
3147     Int  o  = inst(in).numSpecifics;
3148     List ps = tl(rev(fst(snd(inst(in).specifics))));
3149     clearMarks();
3150     copyPred(inst(in).head,o);
3151     inst(in).specifics    = simpleContext(ps,o);
3152     h98CheckCtxt(inst(in).line,"derived instance",FALSE,inst(in).specifics,in);
3153     inst(in).numSpecifics = length(inst(in).specifics);
3154
3155 #ifdef DEBUG_DERIVING
3156     Printf("Derived instance: ");
3157     printContext(stdout,inst(in).specifics);
3158     Printf(" ||- ");
3159     printPred(stdout,inst(in).head);
3160     Printf("\n");
3161 #endif
3162 }
3163
3164 /* --------------------------------------------------------------------------
3165  * Generate code for derived instances:
3166  * ------------------------------------------------------------------------*/
3167
3168 static Void local addDerivImp(in)
3169 Inst in; {
3170     List  imp = NIL;
3171     Type  t   = getHead(arg(inst(in).head));
3172     Class c   = inst(in).c;
3173     if (c==classEq) {
3174         imp = deriveEq(t);
3175     } else if (c==classOrd) {
3176         imp = deriveOrd(t);
3177     } else if (c==classEnum) {
3178         imp = deriveEnum(t);
3179     } else if (c==classIx) {
3180         imp = deriveIx(t);
3181     } else if (c==classShow) {
3182         imp = deriveShow(t);
3183     } else if (c==classRead) {
3184         imp = deriveRead(t);
3185     } else if (c==classBounded) {
3186         imp = deriveBounded(t);
3187     } else {
3188         ERRMSG(inst(in).line) "Cannot derive instances of class \"%s\"",
3189                               textToStr(cclass(inst(in).c).text)
3190         EEND;
3191     }
3192
3193     kindInst(in,intOf(inst(in).kinds));
3194     insertInst(in);
3195     inst(in).builder    = newInstImp(in);
3196     inst(in).implements = classBindings("derived instance",
3197                                         inst(in).c,
3198                                         imp);
3199 }
3200
3201
3202 /* --------------------------------------------------------------------------
3203  * Default definitions; only one default definition is permitted in a
3204  * given script file.  If no default is supplied, then a standard system
3205  * default will be used where necessary.
3206  * ------------------------------------------------------------------------*/
3207
3208 Void defaultDefn(line,defs)             /* Handle default types definition */
3209 Int  line;
3210 List defs; {
3211     if (defaultLine!=0) {
3212         ERRMSG(line) "Multiple default declarations are not permitted in" ETHEN
3213         ERRTEXT     "a single script file.\n"
3214         EEND;
3215     }
3216     defaultDefns = defs;
3217     defaultLine  = line;
3218 }
3219
3220 static Void local checkDefaultDefns() { /* check that default types are    */
3221     List ds = NIL;                      /* well-kinded instances of Num    */
3222
3223     if (defaultLine!=0) {
3224         map2Over(depTypeExp,defaultLine,NIL,defaultDefns);
3225         emptySubstitution();
3226         unkindTypes = NIL;
3227         map2Proc(kindType,defaultLine,"default type",defaultDefns);
3228         fixKinds();
3229         emptySubstitution();
3230         mapOver(fullExpand,defaultDefns);
3231     } else {
3232         defaultDefns = stdDefaults;
3233     }
3234
3235     if (isNull(classNum)) {
3236         classNum = findClass(findText("Num"));
3237     }
3238
3239     for (ds=defaultDefns; nonNull(ds); ds=tl(ds)) {
3240         if (isNull(provePred(NIL,NIL,ap(classNum,hd(ds))))) {
3241             ERRMSG(defaultLine)
3242                 "Default types must be instances of the Num class"
3243             EEND;
3244         }
3245     }
3246 }
3247
3248
3249 /* --------------------------------------------------------------------------
3250  * Foreign import declarations are Hugs' equivalent of GHC's ccall mechanism.
3251  * They are used to "import" C functions into a module.
3252  * They are usually not written by hand but, rather, generated automatically
3253  * by GreenCard, IDL compilers or whatever.  We support foreign import 
3254  * (static) and foreign import dynamic.  In the latter case, extName==NIL.
3255  *
3256  * Foreign export declarations generate C wrappers for Hugs functions.
3257  * Hugs only provides "foreign export dynamic" because it's not obvious
3258  * what "foreign export static" would mean in an interactive setting.
3259  * ------------------------------------------------------------------------*/
3260
3261 Void foreignImport(line,callconv,extName,intName,type) 
3262                                               /* Handle foreign imports    */
3263 Cell line;
3264 Text callconv;
3265 Pair extName;
3266 Cell intName;
3267 Cell type; {
3268     Text t = textOf(intName);
3269     Name n = findName(t);
3270     Int  l = intOf(line);
3271
3272     if (isNull(n)) {
3273         n = newName(t,NIL);
3274     } else if (name(n).defn!=PREDEFINED) {
3275         ERRMSG(l) "Redeclaration of foreign \"%s\"", textToStr(t)
3276         EEND;
3277     }
3278     name(n).line     = l;
3279     name(n).defn     = extName;
3280     name(n).type     = type;
3281     name(n).callconv = callconv;
3282     foreignImports   = cons(n,foreignImports);
3283 }
3284
3285 static Void local checkForeignImport(p)   /* Check foreign import          */
3286 Name p; {
3287     emptySubstitution();
3288     name(p).type = checkSigType(name(p).line,
3289                                 "foreign import declaration",
3290                                 p,
3291                                 name(p).type);
3292     /* We don't expand synonyms here because we don't want the IO
3293      * part to be expanded.
3294      * name(p).type = fullExpand(name(p).type);
3295      */
3296     implementForeignImport(p);
3297 }
3298
3299 Void foreignExport(line,callconv,extName,intName,type)
3300                                               /* Handle foreign exports    */
3301 Cell line;
3302 Text callconv;
3303 Cell extName;
3304 Cell intName;
3305 Cell type; {
3306     Text t = textOf(intName);
3307     Name n = findName(t);
3308     Int  l = intOf(line);
3309
3310     if (isNull(n)) {
3311         n = newName(t,NIL);
3312     } else if (name(n).defn!=PREDEFINED) {
3313         ERRMSG(l) "Redeclaration of foreign \"%s\"", textToStr(t)
3314         EEND;
3315     }
3316     name(n).line     = l;
3317     name(n).defn     = NIL;  /* nothing to say */
3318     name(n).type     = type;
3319     name(n).callconv = callconv;
3320     foreignExports   = cons(n,foreignExports);
3321 }
3322
3323 static Void local checkForeignExport(p)       /* Check foreign export      */
3324 Name p; {
3325     emptySubstitution();
3326     name(p).type = checkSigType(name(p).line,
3327                                 "foreign export declaration",
3328                                 p,
3329                                 name(p).type);
3330     implementForeignExport(p);
3331 }
3332
3333
3334
3335 /* --------------------------------------------------------------------------
3336  * Static analysis of patterns:
3337  *
3338  * Patterns are parsed as ordinary (atomic) expressions.  Static analysis
3339  * makes the following checks:
3340  *  - Patterns are well formed (according to pattern syntax), including the
3341  *    special case of (n+k) patterns.
3342  *  - All constructor functions have been defined and are used with the
3343  *    correct number of arguments.
3344  *  - No variable name is used more than once in a pattern.
3345  *
3346  * The list of pattern variables occuring in each pattern is accumulated in
3347  * a global list `patVars', which must be initialised to NIL at appropriate
3348  * points before using these routines to check for valid patterns.  This
3349  * mechanism enables the pattern checking routine to be mapped over a list
3350  * of patterns, ensuring that no variable occurs more than once in the
3351  * complete pattern list (as is required on the lhs of a function defn).
3352  * ------------------------------------------------------------------------*/
3353
3354 static List patVars;                   /* List of vars bound in pattern    */
3355
3356 static Cell local checkPat(line,p)     /* Check valid pattern syntax       */
3357 Int  line;
3358 Cell p; {
3359     switch (whatIs(p)) {
3360         case VARIDCELL :
3361         case VAROPCELL : addToPatVars(line,p);
3362                          break;
3363
3364         case INFIX     : return checkPat(line,tidyInfix(line,snd(p)));
3365
3366         case AP        : return checkMaybeCnkPat(line,p);
3367
3368         case NAME      :
3369         case QUALIDENT : 
3370         case CONIDCELL : 
3371         case CONOPCELL : return checkApPat(line,0,p);
3372
3373         case WILDCARD  :
3374         case STRCELL   :
3375         case CHARCELL  :
3376         case FLOATCELL : break;
3377         case INTCELL   : break;
3378
3379         case ASPAT     : addToPatVars(line,fst(snd(p)));
3380                          snd(snd(p)) = checkPat(line,snd(snd(p)));
3381                          break;
3382
3383         case LAZYPAT   : snd(p) = checkPat(line,snd(p));
3384                          break;
3385
3386         case FINLIST   : map1Over(checkPat,line,snd(p));
3387                          break;
3388
3389         case CONFLDS   : depConFlds(line,p,TRUE);
3390                          break;
3391
3392         case ESIGN     : snd(snd(p)) = checkPatType(line,
3393                                                     "pattern",
3394                                                     fst(snd(p)),
3395                                                     snd(snd(p)));
3396                          fst(snd(p)) = checkPat(line,fst(snd(p)));
3397                          break;
3398
3399         default        : ERRMSG(line) "Illegal pattern syntax"
3400                          EEND;
3401     }
3402     return p;
3403 }
3404
3405 static Cell local checkMaybeCnkPat(l,p)/* Check applicative pattern with   */
3406 Int  l;                                /* the possibility of n+k pattern   */
3407 Cell p; {
3408 #if NPLUSK
3409     Cell h = getHead(p);
3410
3411     if (argCount==2 && isVar(h) && textOf(h)==textPlus) {       /* n+k     */
3412         Cell v = arg(fun(p));
3413         if (!isInt(arg(p))) {
3414             ERRMSG(l) "Second argument in (n+k) pattern must be an integer"
3415             EEND;
3416         }
3417         if (intOf(arg(p))<=0) {
3418             ERRMSG(l) "Integer k in (n+k) pattern must be > 0"
3419             EEND;
3420         }
3421         fst(fun(p))      = ADDPAT;
3422         intValOf(fun(p)) = intOf(arg(p));
3423         arg(p)           = checkPat(l,v);
3424         return p;
3425     }
3426 #endif
3427     return checkApPat(l,0,p);
3428 }
3429
3430 static Cell local checkApPat(line,args,p)
3431 Int  line;                             /* check validity of application    */
3432 Int  args;                             /* of constructor to arguments      */
3433 Cell p; {
3434     switch (whatIs(p)) {
3435         case AP        : fun(p) = checkApPat(line,args+1,fun(p));
3436                          arg(p) = checkPat(line,arg(p));
3437                          break;
3438
3439         case TUPLE     : if (tupleOf(p)!=args) {
3440                              ERRMSG(line) "Illegal tuple pattern"
3441                              EEND;
3442                          }
3443                          break;
3444
3445 #if TREX
3446         case EXT       : h98DoesntSupport(line,"extensible records");
3447                          if (args!=2) {
3448                              ERRMSG(line) "Illegal record pattern"
3449                              EEND;
3450                          }
3451                          break;
3452 #endif
3453
3454         case QUALIDENT : if (!isQCon(p)) {
3455                             ERRMSG(line)
3456                                 "Illegal use of qualified variable in pattern"
3457                             EEND;
3458                          }
3459                          /* deliberate fall through */
3460         case CONIDCELL :
3461         case CONOPCELL : p = conDefined(line,p);
3462                          checkCfunArgs(line,p,args);
3463                          break;
3464
3465         case NAME      : checkIsCfun(line,p);
3466                          checkCfunArgs(line,p,args);
3467                          break;
3468
3469         default        : ERRMSG(line) "Illegal pattern syntax"
3470                          EEND;
3471     }
3472     return p;
3473 }
3474
3475 static Void local addToPatVars(line,v)  /* Add variable v to list of vars  */
3476 Int  line;                              /* in current pattern, checking    */
3477 Cell v; {                               /* for repeated variables.         */
3478     Text t = textOf(v);
3479     List p = NIL;
3480     List n = patVars;
3481
3482     for (; nonNull(n); p=n, n=tl(n)) {
3483         if (textOf(hd(n))==t) {
3484             ERRMSG(line) "Repeated variable \"%s\" in pattern",
3485                          textToStr(t)
3486             EEND;
3487         }
3488     }
3489
3490     if (isNull(p)) {
3491          patVars = cons(v,NIL);
3492     } else {
3493          tl(p)   = cons(v,NIL);
3494     }
3495 }
3496
3497 static Name local conDefined(line,nm)  /* check that nm is the name of a   */
3498 Int  line;                             /* previously defined constructor   */
3499 Cell nm; {                             /* function.                        */
3500     Name n = findQualName(nm);
3501     if (isNull(n)) {
3502         ERRMSG(line) "Undefined constructor function \"%s\"", identToStr(nm)
3503         EEND;
3504     }
3505     checkIsCfun(line,n);
3506     return n;
3507 }
3508
3509 static Void local checkIsCfun(line,c)  /* Check that c is a constructor fn */
3510 Int  line;
3511 Name c; {
3512     if (!isCfun(c)) {
3513         ERRMSG(line) "\"%s\" is not a constructor function",
3514                      textToStr(name(c).text)
3515         EEND;
3516     }
3517 }
3518
3519 static Void local checkCfunArgs(line,c,args)
3520 Int  line;                             /* Check constructor applied with   */
3521 Cell c;                                /* correct number of arguments      */
3522 Int  args; {
3523     Int a = userArity(c);
3524     if (a!=args) {
3525         ERRMSG(line)
3526           "Constructor \"%s\" must have exactly %d argument%s in pattern",
3527           textToStr(name(c).text), a, ((a==1)?"":"s")
3528         EEND;
3529     }
3530 }
3531
3532 static Cell local checkPatType(l,wh,e,t)/* Check type appearing in pattern */
3533 Int    l;
3534 String wh;
3535 Cell   e;
3536 Type   t; {
3537     List tvs = typeVarsIn(t,NIL,NIL,NIL);
3538     h98DoesntSupport(l,"pattern type annotations");
3539     for (; nonNull(tvs); tvs=tl(tvs)) {
3540         Int beta    = newKindvars(1);
3541         hd(btyvars) = cons(pair(hd(tvs),mkInt(beta)), hd(btyvars));
3542     }
3543     t = checkSigType(l,"pattern type",e,t);
3544     if (isPolyOrQualType(t) || whatIs(t)==RANK2) {
3545         ERRMSG(l) "Illegal syntax in %s type annotation", wh
3546         EEND;
3547     }
3548     return t;
3549 }
3550
3551 static Cell local applyBtyvs(pat)       /* Record bound type vars in pat   */
3552 Cell pat; {
3553     List bts = hd(btyvars);
3554     leaveBtyvs();
3555     if (nonNull(bts)) {
3556         pat = ap(BIGLAM,pair(bts,pat));
3557         for (; nonNull(bts); bts=tl(bts)) {
3558             snd(hd(bts)) = copyKindvar(intOf(snd(hd(bts))));
3559         }
3560     }
3561     return pat;
3562 }
3563
3564 /* --------------------------------------------------------------------------
3565  * Maintaining lists of bound variables and local definitions, for
3566  * dependency and scope analysis.
3567  * ------------------------------------------------------------------------*/
3568
3569 static List bounds;                    /* list of lists of bound vars      */
3570 static List bindings;                  /* list of lists of binds in scope  */
3571 static List depends;                   /* list of lists of dependents      */
3572
3573 /* bounds   :: [[Var]]        -- var equality used on Vars     */
3574 /* bindings :: [[([Var],?)]]  -- var equality used on Vars     */
3575 /* depends  :: [[Var]]        -- pointer equality used on Vars */
3576
3577 #define saveBvars()      hd(bounds)    /* list of bvars in current scope   */
3578 #define restoreBvars(bs) hd(bounds)=bs /* restore list of bound variables  */
3579
3580 static Cell local bindPat(line,p)      /* add new bound vars for pattern   */
3581 Int  line;
3582 Cell p; {
3583     patVars    = NIL;
3584     p          = checkPat(line,p);
3585     hd(bounds) = revOnto(patVars,hd(bounds));
3586     return p;
3587 }
3588
3589 static Void local bindPats(line,ps)    /* add new bound vars for patterns  */
3590 Int  line;
3591 List ps; {
3592     patVars    = NIL;
3593     map1Over(checkPat,line,ps);
3594     hd(bounds) = revOnto(patVars,hd(bounds));
3595 }
3596
3597 /* --------------------------------------------------------------------------
3598  * Before processing value and type signature declarations, all data and
3599  * type definitions have been processed so that:
3600  * - all valid type constructors (with their arities) are known.
3601  * - all valid constructor functions (with their arities and types) are
3602  *   known.
3603  *
3604  * The result of parsing a list of value declarations is a list of Eqns:
3605  *       Eqn ::= (SIGDECL,(Line,[Var],type))
3606  *            |  (FIXDECL,(Line,[Op],SyntaxInt))
3607  *            |  (Expr,Rhs)
3608  * The ordering of the equations in this list is the reverse of the original
3609  * ordering in the script parsed.  This is a consequence of the structure of
3610  * the parser ... but also turns out to be most convenient for the static
3611  * analysis.
3612  *
3613  * As the first stage of the static analysis of value declarations, each
3614  * list of Eqns is converted to a list of Bindings.  As part of this
3615  * process:
3616  * - The ordering of the list of Bindings produced is the same as in the
3617  *   original script.
3618  * - When a variable (function) is defined over a number of lines, all
3619  *   of the definitions should appear together and each should give the
3620  *   same arity to the variable being defined.
3621  * - No variable can have more than one definition.
3622  * - For pattern bindings:
3623  *   - Each lhs is a valid pattern/function lhs, all constructor functions
3624  *     have been defined and are used with the correct number of arguments.
3625  *   - Each lhs contains no repeated pattern variables.
3626  *   - Each equation defines at least one variable (e.g. True = False is
3627  *     not allowed).
3628  * - Types appearing in type signatures are well formed:
3629  *    - Type constructors used are defined and used with correct number
3630  *      of arguments.
3631  *    - type variables are replaced by offsets, type constructor names
3632  *      by Tycons.
3633  * - Every variable named in a type signature declaration is defined by
3634  *   one or more equations elsewhere in the script.
3635  * - No variable has more than one type declaration.
3636  * - Similar properties for fixity declarations.
3637  *
3638  * ------------------------------------------------------------------------*/
3639
3640 #define bindingAttr(b) fst(snd(b))     /* type(s)/fixity(ies) for binding  */
3641 #define fbindAlts(b)   snd(snd(b))     /* alternatives for function binding*/
3642
3643 static List local extractSigdecls(es)  /* Extract the SIGDECLS from list   */
3644 List es; {                             /* of equations                     */
3645     List sigdecls = NIL;               /* :: [(Line,[Var],Type)]           */
3646
3647     for(; nonNull(es); es=tl(es)) {
3648         if (fst(hd(es))==SIGDECL) {                  /* type-declaration?  */
3649             Pair sig  = snd(hd(es));
3650             Int  line = intOf(fst3(sig));
3651             List vs   = snd3(sig);
3652             for(; nonNull(vs); vs=tl(vs)) {
3653                 if (isQualIdent(hd(vs))) {
3654                     ERRMSG(line) "Type signature for qualified variable \"%s\" is not allowed",
3655                                  identToStr(hd(vs))
3656                     EEND;
3657                 }
3658             }
3659             sigdecls = cons(sig,sigdecls);           /* discard SIGDECL tag*/
3660         }
3661     }
3662     return sigdecls;
3663 }
3664
3665 static List local extractFixdecls(es)   /* Extract the FIXDECLS from list  */
3666 List es; {                              /* of equations                    */
3667     List fixdecls = NIL;                /* :: [(Line,SyntaxInt,[Op])]      */
3668
3669     for(; nonNull(es); es=tl(es)) {
3670         if (fst(hd(es))==FIXDECL) {                  /* fixity declaration?*/
3671             fixdecls = cons(snd(hd(es)),fixdecls);   /* discard FIXDECL tag*/
3672         }
3673     }
3674     return fixdecls;
3675 }
3676
3677 static List local extractBindings(ds)   /* extract untyped bindings from   */
3678 List ds; {                              /* given list of equations         */
3679     Cell lastVar   = NIL;               /* = var def'd in last eqn (if any)*/
3680     Int  lastArity = 0;                 /* = number of args in last defn   */
3681     List bs        = NIL;               /* :: [Binding]                    */
3682
3683     for(; nonNull(ds); ds=tl(ds)) {
3684         Cell d = hd(ds);
3685         if (fst(d)==FUNBIND) {          /* Function bindings               */
3686             Cell rhs    = snd(snd(d));
3687             Int  line   = rhsLine(rhs);
3688             Cell lhs    = fst(snd(d));
3689             Cell v      = getHead(lhs);
3690             Cell newAlt = pair(getArgs(lhs),rhs);
3691             if (!isVar(v)) {
3692                 internal("FUNBIND");
3693             }
3694             if (nonNull(lastVar) && textOf(v)==textOf(lastVar)) {
3695                 if (argCount!=lastArity) {
3696                     ERRMSG(line) "Equations give different arities for \"%s\"",
3697                                  textToStr(textOf(v))
3698                     EEND;
3699                 }
3700                 fbindAlts(hd(bs)) = cons(newAlt,fbindAlts(hd(bs)));
3701             }
3702             else {
3703                 lastVar   = v;
3704                 lastArity = argCount;
3705                 notDefined(line,bs,v);
3706                 bs        = cons(pair(v,pair(NIL,singleton(newAlt))),bs);
3707             }
3708
3709         } else if (fst(d)==PATBIND) {   /* Pattern bindings                */
3710             Cell rhs  = snd(snd(d));
3711             Int  line = rhsLine(rhs);
3712             Cell pat  = fst(snd(d));
3713             while (whatIs(pat)==ESIGN) {/* Move type annotations to rhs   */
3714                 Cell p        = fst(snd(pat));
3715                 fst(snd(pat)) = rhs;
3716                 snd(snd(d))   = rhs = pat;
3717                 fst(snd(d))   = pat = p;
3718                 fst(rhs)      = RSIGN;
3719             }
3720             if (isVar(pat)) {           /* Convert simple pattern bind to */
3721                 notDefined(line,bs,pat);/* a function binding             */
3722                 bs = cons(pair(pat,pair(NIL,singleton(pair(NIL,rhs)))),bs);
3723             } else {
3724                 List vs = getPatVars(line,pat,NIL);
3725                 if (isNull(vs)) {
3726                     ERRMSG(line) "No variables defined in lhs pattern"
3727                     EEND;
3728                 }
3729                 map2Proc(notDefined,line,bs,vs);
3730                 bs          = cons(pair(vs,pair(NIL,snd(d))),bs);
3731             }
3732             lastVar = NIL;
3733         }
3734     }
3735     return bs;
3736 }
3737
3738 static List local getPatVars(line,p,vs) /* Find list of variables bound in */
3739 Int  line;                              /* pattern p                       */
3740 Cell p;
3741 List vs; {
3742     switch (whatIs(p)) {
3743         case AP         : do {
3744                               vs = getPatVars(line,arg(p),vs);
3745                               p  = fun(p);
3746                           } while (isAp(p));
3747                           return vs;    /* Ignore head of application      */
3748
3749         case CONFLDS    : {   List pfs = snd(snd(p));
3750                               for (; nonNull(pfs); pfs=tl(pfs)) {
3751                                   if (isVar(hd(pfs))) {
3752                                       vs = addPatVar(line,hd(pfs),vs);
3753                                   } else {
3754                                       vs = getPatVars(line,snd(hd(pfs)),vs);
3755                                   }
3756                               }
3757                           }
3758                           return vs;
3759
3760         case FINLIST    : {   List ps = snd(p);
3761                               for (; nonNull(ps); ps=tl(ps)) {
3762                                   vs = getPatVars(line,hd(ps),vs);
3763                               }
3764                           }
3765                           return vs;
3766
3767         case ESIGN      : return getPatVars(line,fst(snd(p)),vs);
3768
3769         case LAZYPAT    :
3770         case NEG        :
3771         case ONLY       :
3772         case INFIX      : return getPatVars(line,snd(p),vs);
3773
3774         case ASPAT      : return addPatVar(line,fst(snd(p)),
3775                                              getPatVars(line,snd(snd(p)),vs));
3776
3777         case VARIDCELL  :
3778         case VAROPCELL  : return addPatVar(line,p,vs);
3779
3780         case CONIDCELL  :
3781         case CONOPCELL  :
3782         case QUALIDENT  :
3783         case INTCELL    :
3784         case FLOATCELL  :
3785         case CHARCELL   :
3786         case STRCELL    :
3787         case NAME       :
3788         case WILDCARD   : return vs;
3789
3790         default         : internal("getPatVars");
3791     }
3792     return vs;
3793 }
3794
3795 static List local addPatVar(line,v,vs)  /* Add var to list of previously   */
3796 Int  line;                              /* encountered variables           */
3797 Cell v;
3798 List vs; {
3799     if (varIsMember(textOf(v),vs)) {
3800         ERRMSG(line) "Repeated use of variable \"%s\" in pattern binding",
3801                      textToStr(textOf(v))
3802         EEND;
3803     }
3804     return cons(v,vs);
3805 }
3806
3807 static List local eqnsToBindings(es,ts,cs,ps)
3808 List es;                                /* Convert list of equations to    */
3809 List ts;                                /* list of typed bindings          */
3810 List cs;
3811 List ps; {
3812     List bs = extractBindings(es);
3813     map1Proc(addSigdecl,bs,extractSigdecls(es));
3814     map4Proc(addFixdecl,bs,ts,cs,ps,extractFixdecls(es));
3815     return bs;
3816 }
3817
3818 static Void local notDefined(line,bs,v)/* check if name already defined in */
3819 Int  line;                             /* list of bindings                 */
3820 List bs;
3821 Cell v; {
3822     if (nonNull(findBinding(textOf(v),bs))) {
3823         ERRMSG(line) "\"%s\" multiply defined", textToStr(textOf(v))
3824         EEND;
3825     }
3826 }
3827
3828 static Cell local findBinding(t,bs)    /* look for binding for variable t  */
3829 Text t;                                /* in list of bindings bs           */
3830 List bs; {
3831     for (; nonNull(bs); bs=tl(bs)) {
3832         if (isVar(fst(hd(bs)))) {                     /* function-binding? */
3833             if (textOf(fst(hd(bs)))==t) {
3834                 return hd(bs);
3835             }
3836         } else if (nonNull(varIsMember(t,fst(hd(bs))))){/* pattern-binding?*/
3837             return hd(bs);
3838         }
3839     }
3840     return NIL;
3841 }
3842
3843 static Cell local getAttr(bs,v)         /* Locate type/fixity attribute    */
3844 List bs;                                /* for variable v in bindings bs   */
3845 Cell v; {
3846     Text t = textOf(v);
3847     Cell b = findBinding(t,bs);
3848
3849     if (isNull(b)) {                                    /* No binding      */
3850         return NIL;
3851     } else if (isVar(fst(b))) {                         /* func binding?   */
3852         if (isNull(bindingAttr(b))) {
3853             bindingAttr(b) = pair(NIL,NIL);
3854         }
3855         return bindingAttr(b);
3856     } else {                                            /* pat binding?    */
3857         List vs = fst(b);
3858         List as = bindingAttr(b);
3859
3860         if (isNull(as)) {
3861             bindingAttr(b) = as = replicate(length(vs),NIL);
3862         }
3863
3864         while (nonNull(vs) && t!=textOf(hd(vs))) {
3865             vs = tl(vs);
3866             as = tl(as);
3867         }
3868
3869         if (isNull(vs)) {
3870             internal("getAttr");
3871         } else if (isNull(hd(as))) {
3872             hd(as) = pair(NIL,NIL);
3873         }
3874         return hd(as);
3875     }
3876 }
3877
3878 static Void local addSigdecl(bs,sigdecl)/* add type information to bindings*/
3879 List bs;                               /* :: [Binding]                     */
3880 Cell sigdecl; {                        /* :: (Line,[Var],Type)             */
3881     Int  l    = intOf(fst3(sigdecl));
3882     List vs   = snd3(sigdecl);
3883     Type type = checkSigType(l,"type declaration",hd(vs),thd3(sigdecl));
3884
3885     for (; nonNull(vs); vs=tl(vs)) {
3886         Cell v    = hd(vs);
3887         Pair attr = getAttr(bs,v);
3888         if (isNull(attr)) {
3889             ERRMSG(l) "Missing binding for variable \"%s\" in type signature",
3890                       textToStr(textOf(v))
3891             EEND;
3892         } else if (nonNull(fst(attr))) {
3893             ERRMSG(l) "Repeated type signature for \"%s\"",
3894                       textToStr(textOf(v))
3895             EEND;
3896         }
3897         fst(attr) = type;
3898     }
3899 }
3900
3901 static Void local addFixdecl(bs,ts,cs,ps,fixdecl)
3902 List   bs;
3903 List   ts;
3904 List   cs;
3905 List   ps;
3906 Triple fixdecl; {
3907     Int  line = intOf(fst3(fixdecl));
3908     List ops  = snd3(fixdecl);
3909     Cell sy   = thd3(fixdecl);
3910
3911     for (; nonNull(ops); ops=tl(ops)) {
3912         Cell op   = hd(ops);
3913         Text t    = textOf(op);
3914         Cell attr = getAttr(bs,op);
3915         if (nonNull(attr)) {            /* Found name in binding?          */
3916             if (nonNull(snd(attr))) {
3917                 dupFixity(line,t);
3918             }
3919             snd(attr) = sy;
3920         } else {                        /* Look in tycons, classes, prims  */
3921             Name n   = NIL;
3922             List ts1 = ts;
3923             List cs1 = cs;
3924             List ps1 = ps;
3925             for (; isNull(n) && nonNull(ts1); ts1=tl(ts1)) {    /* tycons  */
3926                 Tycon tc = hd(ts1);
3927                 if (tycon(tc).what==DATATYPE || tycon(tc).what==NEWTYPE) {
3928                     n = nameIsMember(t,tycon(tc).defn);
3929                 }
3930             }
3931             for (; isNull(n) && nonNull(cs1); cs1=tl(cs1)) {    /* classes */
3932                 n = nameIsMember(t,cclass(hd(cs1)).members);
3933             }
3934             for (; isNull(n) && nonNull(ps1); ps1=tl(ps1)) {    /* prims   */
3935                 n = nameIsMember(t,hd(ps1));
3936             }
3937
3938             if (isNull(n)) {
3939                 missFixity(line,t);
3940             } else if (name(n).syntax!=NO_SYNTAX) {
3941                 dupFixity(line,t);
3942             }
3943             name(n).syntax = intOf(sy);
3944         }
3945     }
3946 }
3947
3948 static Void local dupFixity(line,t)     /* Report repeated fixity decl     */
3949 Int  line;
3950 Text t; {
3951     ERRMSG(line)
3952         "Repeated fixity declaration for operator \"%s\"", textToStr(t)
3953     EEND;
3954 }
3955
3956 static Void local missFixity(line,t)    /* Report missing op for fixity    */
3957 Int  line;
3958 Text t; {
3959     ERRMSG(line)
3960         "Cannot find binding for operator \"%s\" in fixity declaration",
3961         textToStr(t)
3962     EEND;
3963 }
3964
3965 /* --------------------------------------------------------------------------
3966  * Dealing with infix operators:
3967  *
3968  * Expressions involving infix operators or unary minus are parsed as
3969  * elements of the following type:
3970  *
3971  *     data InfixExp = Only Exp | Neg InfixExp | Infix InfixExp Op Exp
3972  *
3973  * (The algorithms here do not assume that negation can be applied only once,
3974  * i.e., that - - x is a syntax error, as required by the Haskell report.
3975  * Instead, that restriction is captured by the grammar itself, given above.)
3976  *
3977  * There are rules of precedence and grouping, expressed by two functions:
3978  *
3979  *     prec :: Op -> Int;   assoc :: Op -> Assoc    (Assoc = {L, N, R})
3980  *
3981  * InfixExp values are rearranged accordingly when a complete expression
3982  * has been read using a simple shift-reduce parser whose result may be taken
3983  * to be a value of the following type:
3984  *
3985  *     data Exp = Atom Int | Negate Exp | Apply Op Exp Exp | Error String
3986  *
3987  * The machine on which this parser is based can be defined as follows:
3988  *
3989  *     tidy                         :: InfixExp -> [(Op,Exp)] -> Exp
3990  *     tidy (Only a)      []         = a
3991  *     tidy (Only a)      ((o,b):ss) = tidy (Only (Apply o a b)) ss
3992  *     tidy (Infix a o b) []         = tidy a [(o,b)]
3993  *     tidy (Infix a o b) ((p,c):ss)
3994  *                      | shift  o p = tidy a ((o,b):(p,c):ss)
3995  *                      | red    o p = tidy (Infix a o (Apply p b c)) ss
3996  *                      | ambig  o p = Error "ambiguous use of operators"
3997  *     tidy (Neg e)       []         = tidy (tidyNeg e) []
3998  *     tidy (Neg e)       ((o,b):ss)
3999  *                      | nshift o   = tidy (Neg (underNeg o b e)) ss
4000  *                      | nred   o   = tidy (tidyNeg e) ((o,b):ss)
4001  *                      | nambig o   = Error "illegal use of negation"
4002  *
4003  * At each stage, the parser can either shift, reduce, accept, or error.
4004  * The transitions when dealing with juxtaposed operators o and p are
4005  * determined by the following rules:
4006  *
4007  *     shift o p  = (prec o > prec p)
4008  *               || (prec o == prec p && assoc o == L && assoc p == L)
4009  *
4010  *     red o p    = (prec o < prec p)
4011  *               || (prec o == prec p && assoc o == R && assoc p == R)
4012  *
4013  *     ambig o p  = (prec o == prec p)
4014  *               && (assoc o == N || assoc p == N || assoc o /= assoc p)
4015  *
4016  * The transitions when dealing with juxtaposed unary minus and infix
4017  * operators are as follows.  The precedence of unary minus (infixl 6) is
4018  * hardwired in to these definitions, as it is to the definitions of the
4019  * Haskell grammar in the official report.
4020  *
4021  *     nshift o   = (prec o > 6)
4022  *     nred   o   = (prec o < 6) || (prec o == 6 && assoc o == L)
4023  *     nambig o   = prec o == 6 && (assoc o == R || assoc o == N)
4024  *
4025  * An InfixExp of the form (Neg e) means negate the last thing in
4026  * the InfixExp e; we can force this negation using:
4027  *
4028  *     tidyNeg              :: OpExp -> OpExp
4029  *     tidyNeg (Only e)      = Only (Negate e)
4030  *     tidyNeg (Infix a o b) = Infix a o (Negate b)
4031  *     tidyNeg (Neg e)       = tidyNeg (tidyNeg e)
4032  * 
4033  * On the other hand, if we want to sneak application of an infix operator
4034  * under a negation, then we use:
4035  *
4036  *     underNeg                  :: Op -> Exp -> OpExp -> OpExp
4037  *     underNeg o b (Only e)      = Only (Apply o e b)
4038  *     underNeg o b (Neg e)       = Neg (underNeg o b e)
4039  *     underNeg o b (Infix e p f) = Infix e p (Apply o f b)
4040  *
4041  * As a concession to efficiency, we lower the number of calls to syntaxOf
4042  * by keeping track of the values of sye, sys throughout the process.  The
4043  * value APPLIC is used to indicate that the syntax value is unknown.
4044  * ------------------------------------------------------------------------*/
4045
4046 static Cell local tidyInfix(line,e)     /* Convert infixExp to Exp         */
4047 Int  line;
4048 Cell e; {                               /* :: OpExp                        */
4049     Cell   s   = NIL;                   /* :: [(Op,Exp)]                   */
4050     Syntax sye = APPLIC;                /* Syntax of op in e (init unknown)*/
4051     Syntax sys = APPLIC;                /* Syntax of op in s (init unknown)*/
4052     Cell   d   = e;
4053
4054     while (fst(d)!=ONLY) {              /* Attach fixities to operators    */
4055         if (fst(d)==NEG) {
4056             d = snd(d);
4057         } else {
4058             fun(fun(d)) = attachFixity(line,fun(fun(d)));
4059             d           = arg(fun(d));
4060         }
4061     }
4062
4063     for (;;)
4064         switch (whatIs(e)) {
4065             case ONLY : e = snd(e);
4066                         while (nonNull(s)) {
4067                             Cell next   = arg(fun(s));
4068                             arg(fun(s)) = e;
4069                             fun(fun(s)) = snd(fun(fun(s)));
4070                             e           = s;
4071                             s           = next;
4072                         }
4073                         return e;
4074
4075             case NEG  : if (nonNull(s)) {
4076                             if (sys==APPLIC) {  /* calculate sys           */
4077                                 sys = intOf(fst(fun(fun(s))));
4078                             }
4079
4080                             if (precOf(sys)==UMINUS_PREC &&     /* nambig  */
4081                                 assocOf(sys)!=UMINUS_ASSOC) {
4082                                 ERRMSG(line)
4083                                  "Ambiguous use of unary minus with \""
4084                                 ETHEN ERREXPR(snd(fun(fun(s))));
4085                                 ERRTEXT "\""
4086                                 EEND;
4087                             }
4088
4089                             if (precOf(sys)>UMINUS_PREC) {      /* nshift  */
4090                                 Cell e1    = snd(e);
4091                                 Cell t     = s;
4092                                 s          = arg(fun(s));
4093                                 while (whatIs(e1)==NEG)
4094                                     e1 = snd(e1);
4095                                 arg(fun(t)) = arg(e1);
4096                                 fun(fun(t)) = snd(fun(fun(t)));
4097                                 arg(e1)     = t;
4098                                 sys         = APPLIC;
4099                                 continue;
4100                             }
4101                         }
4102
4103                         /* Intentional fall-thru for nreduce and isNull(s) */
4104
4105                         {   Cell prev = e;              /* e := tidyNeg e  */
4106                             Cell temp = arg(prev);
4107                             Int  nneg = 1;
4108                             for (; whatIs(temp)==NEG; nneg++) {
4109                                 fun(prev) = nameNegate;
4110                                 prev      = temp;
4111                                 temp      = arg(prev);
4112                             }
4113                             if (isInt(arg(temp))) {     /* special cases   */
4114                                 if (nneg&1)             /* for literals    */
4115                                     arg(temp) = mkInt(-intOf(arg(temp)));
4116                             }
4117                             else if (isFloat(arg(temp))) {
4118                                 if (nneg&1)
4119                                     arg(temp) = floatNegate(arg(temp));
4120                                                 //mkFloat(-floatOf(arg(temp)));
4121                             }
4122                             else {
4123                                 fun(prev) = nameNegate;
4124                                 arg(prev) = arg(temp);
4125                                 arg(temp) = e;
4126                             }
4127                             e = temp;
4128                         }
4129                         continue;
4130
4131             default   : if (isNull(s)) {/* Move operation onto empty stack */
4132                             Cell next   = arg(fun(e));
4133                             s           = e;
4134                             arg(fun(s)) = NIL;
4135                             e           = next;
4136                             sys         = sye;
4137                             sye         = APPLIC;
4138                         }
4139                         else {          /* deal with pair of operators     */
4140
4141                             if (sye==APPLIC) {  /* calculate sys and sye   */
4142                                 sye = intOf(fst(fun(fun(e))));
4143                             }
4144                             if (sys==APPLIC) {
4145                                 sys = intOf(fst(fun(fun(s))));
4146                             }
4147
4148                             if (precOf(sye)==precOf(sys) &&     /* ambig   */
4149                                 (assocOf(sye)!=assocOf(sys) ||
4150                                  assocOf(sye)==NON_ASS)) {
4151                                 ERRMSG(line) "Ambiguous use of operator \""
4152                                 ETHEN ERREXPR(snd(fun(fun(e))));
4153                                 ERRTEXT "\" with \""
4154                                 ETHEN ERREXPR(snd(fun(fun(s))));
4155                                 ERRTEXT "\""
4156                                 EEND;
4157                             }
4158
4159                             if (precOf(sye)>precOf(sys) ||      /* shift   */
4160                                 (precOf(sye)==precOf(sys) &&
4161                                  assocOf(sye)==LEFT_ASS &&
4162                                  assocOf(sys)==LEFT_ASS)) {
4163                                 Cell next   = arg(fun(e));
4164                                 arg(fun(e)) = s;
4165                                 s           = e;
4166                                 e           = next;
4167                                 sys         = sye;
4168                                 sye         = APPLIC;
4169                             }
4170                             else {                              /* reduce  */
4171                                 Cell next   = arg(fun(s));
4172                                 arg(fun(s)) = arg(e);
4173                                 fun(fun(s)) = snd(fun(fun(s)));
4174                                 arg(e)      = s;
4175                                 s           = next;
4176                                 sys         = APPLIC;
4177                                 /* sye unchanged */
4178                             }
4179                         }
4180                         continue;
4181         }
4182 }
4183
4184 static Pair local attachFixity(line,op) /* Attach fixity to operator in an */
4185 Int  line;                              /* infix expression                */
4186 Cell op; {
4187     Syntax sy = DEF_OPSYNTAX;
4188
4189     switch (whatIs(op)) {
4190         case VAROPCELL :
4191         case VARIDCELL : if ((sy=lookupSyntax(textOf(op)))==NO_SYNTAX) {
4192                              Name n = findName(textOf(op));
4193                              if (isNull(n)) {
4194                                 ERRMSG(line) "Undefined variable \"%s\"",
4195                                              textToStr(textOf(op))
4196                                 EEND;
4197                              }
4198                              sy = syntaxOf(n);
4199                              op = n;
4200                          }
4201                          break;
4202
4203         case CONOPCELL :
4204         case CONIDCELL : sy = syntaxOf(op = conDefined(line,op));
4205                          break;
4206
4207         case QUALIDENT : {   Name n = findQualName(op);
4208                              if (nonNull(n)) {
4209                                  op = n;
4210                                  sy = syntaxOf(n);
4211                              } else {
4212                                  ERRMSG(line)
4213                                    "Undefined qualified variable \"%s\"",
4214                                    identToStr(op)
4215                                  EEND;
4216                              }
4217                          }
4218                          break;
4219     }
4220     if (sy==APPLIC) {
4221         sy = DEF_OPSYNTAX;
4222     }
4223     return pair(mkInt(sy),op);          /* Pair fixity with (possibly)     */
4224                                         /* translated operator             */
4225 }
4226
4227 static Syntax local lookupSyntax(t)     /* Try to find fixity for var in   */
4228 Text t; {                               /* enclosing bindings              */
4229     List bounds1   = bounds;
4230     List bindings1 = bindings;
4231
4232     while (nonNull(bindings1)) {
4233         if (nonNull(varIsMember(t,hd(bounds1)))) {
4234             return DEF_OPSYNTAX;
4235         } else {
4236             Cell b = findBinding(t,hd(bindings1));
4237             if (nonNull(b)) {
4238                 Cell a = fst(snd(b));
4239                 if (isVar(fst(b))) {    /* Function binding                */
4240                     if (nonNull(a) && nonNull(snd(a))) {
4241                         return intOf(snd(a));
4242                     }
4243                 } else {                /* Pattern binding                 */
4244                     List vs = fst(b);
4245                     while (nonNull(vs) && nonNull(a)) {
4246                         if (t==textOf(hd(vs))) {
4247                             if (nonNull(hd(a)) && isInt(snd(hd(a)))) {
4248                                 return intOf(snd(hd(a)));
4249                             }
4250                             break;
4251                         }
4252                         vs = tl(vs);
4253                         a  = tl(a);
4254                     }
4255                 }
4256                 return DEF_OPSYNTAX;
4257             }
4258         }
4259         bounds1   = tl(bounds1);
4260         bindings1 = tl(bindings1);
4261     }
4262     return NO_SYNTAX;
4263 }
4264
4265 /* --------------------------------------------------------------------------
4266  * To facilitate dependency analysis, lists of bindings are temporarily
4267  * augmented with an additional field, which is used in two ways:
4268  * - to build the `adjacency lists' for the dependency graph. Represented by
4269  *   a list of pointers to other bindings in the same list of bindings.
4270  * - to hold strictly positive integer values (depth first search numbers) of
4271  *   elements `on the stack' during the strongly connected components search
4272  *   algorithm, or a special value mkInt(0), once the binding has been added
4273  *   to a particular strongly connected component.
4274  *
4275  * Using this extra field, the type of each list of declarations during
4276  * dependency analysis is [Binding'] where:
4277  *
4278  *    Binding' ::= (Var, (Attr, (Dep, [Alt])))         -- function binding
4279  *              |  ([Var], ([Attr], (Dep, (Pat,Rhs)))) -- pattern binding
4280  *
4281  * ------------------------------------------------------------------------*/
4282
4283 #define depVal(d) (fst(snd(snd(d))))    /* Access to dependency information*/
4284
4285 static List local dependencyAnal(bs)    /* Separate lists of bindings into */
4286 List bs; {                              /* mutually recursive groups in    */
4287                                         /* order of dependency             */
4288     mapProc(addDepField,bs);            /* add extra field for dependents  */
4289     mapProc(depBinding,bs);             /* find dependents of each binding */
4290     bs = bscc(bs);                      /* sort to strongly connected comps*/
4291     mapProc(remDepField,bs);            /* remove dependency info field    */
4292     return bs;
4293 }
4294
4295 static List local topDependAnal(bs)     /* Like dependencyAnal(), but at   */
4296 List bs; {                              /* top level, reporting on progress*/
4297     List xs;
4298     Int  i = 0;
4299
4300     setGoal("Dependency analysis",(Target)(length(bs)));
4301
4302     mapProc(addDepField,bs);           /* add extra field for dependents   */
4303     for (xs=bs; nonNull(xs); xs=tl(xs)) {
4304         emptySubstitution();
4305         depBinding(hd(xs));
4306         soFar((Target)(i++));
4307     }
4308     bs = bscc(bs);                     /* sort to strongly connected comps */
4309     mapProc(remDepField,bs);           /* remove dependency info field     */
4310     done();
4311     return bs;
4312 }
4313
4314 static Void local addDepField(b)       /* add extra field to binding to    */
4315 Cell b; {                              /* hold list of dependents          */
4316     snd(snd(b)) = pair(NIL,snd(snd(b)));
4317 }
4318
4319 static Void local remDepField(bs)      /* remove dependency field from     */
4320 List bs; {                             /* list of bindings                 */
4321     mapProc(remDepField1,bs);
4322 }
4323
4324 static Void local remDepField1(b)      /* remove dependency field from     */
4325 Cell b; {                              /* single binding                   */
4326     snd(snd(b)) = snd(snd(snd(b)));
4327 }
4328
4329 static Void local clearScope() {       /* initialise dependency scoping    */
4330     bounds   = NIL;
4331     bindings = NIL;
4332     depends  = NIL;
4333 }
4334
4335 static Void local withinScope(bs)       /* Enter scope of bindings bs      */
4336 List bs; {
4337     bounds   = cons(NIL,bounds);
4338     bindings = cons(bs,bindings);
4339     depends  = cons(NIL,depends);
4340 }
4341
4342 static Void local leaveScope() {        /* Leave scope of last withinScope */
4343     List bs       = hd(bindings);       /* Remove fixity info from binds   */
4344     Bool toplevel = isNull(tl(bindings));
4345     for (; nonNull(bs); bs=tl(bs)) {
4346         Cell b = hd(bs);
4347         if (isVar(fst(b))) {            /* Variable binding                */
4348             Cell a = fst(snd(b));
4349             if (isPair(a)) {
4350                 if (toplevel) {
4351                     saveSyntax(fst(b),snd(a));
4352                 }
4353                 fst(snd(b)) = fst(a);
4354             }
4355         } else {                        /* Pattern binding                 */
4356             List vs = fst(b);
4357             List as = fst(snd(b));
4358             while (nonNull(vs) && nonNull(as)) {
4359                 if (isPair(hd(as))) {
4360                     if (toplevel) {
4361                         saveSyntax(hd(vs),snd(hd(as)));
4362                     }
4363                     hd(as) = fst(hd(as));
4364                 }
4365                 vs = tl(vs);
4366                 as = tl(as);
4367             }
4368         }
4369     }
4370     bounds   = tl(bounds);
4371     bindings = tl(bindings);
4372     depends  = tl(depends);
4373 }
4374
4375 static Void local saveSyntax(v,sy)      /* Save syntax of top-level var    */
4376 Cell v;                                 /* in corresponding Name           */
4377 Cell sy; {
4378     Name n = findName(textOf(v));
4379     if (isNull(n) || name(n).syntax!=NO_SYNTAX) {
4380         internal("saveSyntax");
4381     }
4382     if (nonNull(sy)) {
4383         name(n).syntax = intOf(sy);
4384     }
4385 }
4386
4387 /* --------------------------------------------------------------------------
4388  * As a side effect of the dependency analysis we also make the following
4389  * checks:
4390  * - Each lhs is a valid pattern/function lhs, all constructor functions
4391  *   have been defined and are used with the correct number of arguments.
4392  * - No lhs contains repeated pattern variables.
4393  * - Expressions used on the rhs of an eqn should be well formed.  This
4394  *   includes:
4395  *   - Checking for valid patterns (including repeated vars) in lambda,
4396  *     case, and list comprehension expressions.
4397  *   - Recursively checking local lists of equations.
4398  * - No free (i.e. unbound) variables are used in the declaration list.
4399  * ------------------------------------------------------------------------*/
4400
4401 static Void local depBinding(b)        /* find dependents of binding       */
4402 Cell b; {
4403     Cell defpart = snd(snd(snd(b)));   /* definition part of binding       */
4404
4405     hd(depends) = NIL;
4406
4407     if (isVar(fst(b))) {               /* function-binding?                */
4408         mapProc(depAlt,defpart);
4409         if (isNull(fst(snd(b)))) {      /* Save dep info if no type sig    */
4410             fst(snd(b)) = pair(ap(IMPDEPS,hd(depends)),NIL);
4411         } else if (isNull(fst(fst(snd(b))))) {
4412             fst(fst(snd(b))) = ap(IMPDEPS,hd(depends));
4413         }
4414     } else {                           /* pattern-binding?                 */
4415         Int line = rhsLine(snd(defpart));
4416         enterBtyvs();
4417         patVars = NIL;
4418         fst(defpart) = checkPat(line,fst(defpart));
4419         depRhs(snd(defpart));
4420 #if 0
4421         if (nonNull(hd(btyvars))) {
4422             ERRMSG(line)
4423               "Sorry, no type variables are allowed in pattern binding type annotations"
4424             EEND;
4425         }
4426 #endif
4427         fst(defpart) = applyBtyvs(fst(defpart));
4428     }
4429     depVal(b) = hd(depends);
4430 }
4431
4432 static Void local depDefaults(c)       /* dependency analysis on defaults  */
4433 Class c; {                             /* from class definition            */
4434     depClassBindings(cclass(c).defaults);
4435 }
4436
4437 static Void local depInsts(in)         /* dependency analysis on instance  */
4438 Inst in; {                             /* bindings                         */
4439     depClassBindings(inst(in).implements);
4440 }
4441
4442 static Void local depClassBindings(bs) /* dependency analysis on list of   */
4443 List bs; {                             /* bindings, possibly containing    */
4444     for (; nonNull(bs); bs=tl(bs)) {   /* NIL bindings ...                 */
4445         if (nonNull(hd(bs))) {         /* No need to add extra field for   */
4446            mapProc(depAlt,snd(hd(bs)));/* dependency information...        */
4447         }
4448     }
4449 }
4450
4451 static Void local depAlt(a)             /* Find dependents of alternative  */
4452 Cell a; {
4453     List obvs = saveBvars();            /* Save list of bound variables    */
4454     enterBtyvs();
4455     bindPats(rhsLine(snd(a)),fst(a));   /* add new bound vars for patterns */
4456     depRhs(snd(a));                     /* find dependents of rhs          */
4457     fst(a)    = applyBtyvs(fst(a));
4458     restoreBvars(obvs);                 /* restore original list of bvars  */
4459 }
4460
4461 static Void local depRhs(r)             /* Find dependents of rhs          */
4462 Cell r; {
4463     switch (whatIs(r)) {
4464         case GUARDED : mapProc(depGuard,snd(r));
4465                        break;
4466
4467         case LETREC  : fst(snd(r)) = eqnsToBindings(fst(snd(r)),NIL,NIL,NIL);
4468                        withinScope(fst(snd(r)));
4469                        fst(snd(r)) = dependencyAnal(fst(snd(r)));
4470                        hd(depends) = fst(snd(r));
4471                        depRhs(snd(snd(r)));
4472                        leaveScope();
4473                        break;
4474
4475         case RSIGN   : snd(snd(r)) = checkPatType(rhsLine(fst(snd(r))),
4476                                                   "result",
4477                                                   rhsExpr(fst(snd(r))),
4478                                                   snd(snd(r)));
4479                        depRhs(fst(snd(r)));
4480                        break;
4481
4482         default      : snd(r) = depExpr(intOf(fst(r)),snd(r));
4483                        break;
4484     }
4485 }
4486
4487 static Void local depGuard(g)          /* find dependents of single guarded*/
4488 Cell g; {                              /* expression                       */
4489     depPair(intOf(fst(g)),snd(g));
4490 }
4491
4492 static Cell local depExpr(line,e)      /* find dependents of expression    */
4493 Int  line;
4494 Cell e; {
4495   //    Printf( "\n\n"); print(e,100); Printf("\n");
4496   //printExp(stdout,e);
4497     switch (whatIs(e)) {
4498
4499         case VARIDCELL  :
4500         case VAROPCELL  : return depVar(line,e);
4501
4502         case CONIDCELL  :
4503         case CONOPCELL  : return conDefined(line,e);
4504
4505         case QUALIDENT  : if (isQVar(e)) {
4506                               return depQVar(line,e);
4507                           } else { /* QConOrConOp */
4508                               return conDefined(line,e);
4509                           }
4510
4511         case INFIX     : return depExpr(line,tidyInfix(line,snd(e)));
4512
4513 #if TREX
4514         case RECSEL     : break;
4515
4516         case AP         : if (isAp(e) && isAp(fun(e)) && isExt(fun(fun(e)))) {
4517                               return depRecord(line,e);
4518                           } else {
4519                               Cell nx = e;
4520                               Cell a;
4521                               do {
4522                                   a      = nx;
4523                                   arg(a) = depExpr(line,arg(a));
4524                                   nx     = fun(a);
4525                               } while (isAp(nx));
4526                               fun(a) = depExpr(line,fun(a));
4527                           }
4528                           break;
4529 #else
4530         case AP         : depPair(line,e);
4531                           break;
4532 #endif
4533
4534 #if IPARAM
4535         case IPVAR      :
4536 #endif
4537
4538         case NAME       :
4539         case TUPLE      :
4540         case STRCELL    :
4541         case CHARCELL   :
4542         case FLOATCELL  :
4543         case BIGCELL    :
4544         case INTCELL    : break;
4545
4546         case COND       : depTriple(line,snd(e));
4547                           break;
4548
4549         case FINLIST    : map1Over(depExpr,line,snd(e));
4550                           break;
4551
4552         case LETREC     : fst(snd(e)) = eqnsToBindings(fst(snd(e)),NIL,NIL,NIL);
4553                           withinScope(fst(snd(e)));
4554                           fst(snd(e)) = dependencyAnal(fst(snd(e)));
4555                           hd(depends) = fst(snd(e));
4556                           snd(snd(e)) = depExpr(line,snd(snd(e)));
4557                           leaveScope();
4558                           break;
4559
4560         case LAMBDA     : depAlt(snd(e));
4561                           break;
4562
4563         case DOCOMP     : /* fall-thru */
4564         case COMP       : depComp(line,snd(e),snd(snd(e)));
4565                           break;
4566
4567         case ESIGN      : fst(snd(e)) = depExpr(line,fst(snd(e)));
4568                           snd(snd(e)) = checkSigType(line,
4569                                                      "expression",
4570                                                      fst(snd(e)),
4571                                                      snd(snd(e)));
4572                           break;
4573
4574         case CASE       : fst(snd(e)) = depExpr(line,fst(snd(e)));
4575                           map1Proc(depCaseAlt,line,snd(snd(e)));
4576                           break;
4577
4578         case CONFLDS    : depConFlds(line,e,FALSE);
4579                           break;
4580
4581         case UPDFLDS    : depUpdFlds(line,e);
4582                           break;
4583
4584 #if IPARAM
4585         case WITHEXP    : depWith(line,e);
4586                           break;
4587 #endif
4588
4589         case ASPAT      : ERRMSG(line) "Illegal `@' in expression"
4590                           EEND;
4591
4592         case LAZYPAT    : ERRMSG(line) "Illegal `~' in expression"
4593                           EEND;
4594
4595         case WILDCARD   : ERRMSG(line) "Illegal `_' in expression"
4596                           EEND;
4597
4598 #if TREX
4599         case EXT        : ERRMSG(line) "Illegal application of record"
4600                           EEND;
4601 #endif
4602
4603         default         : internal("depExpr");
4604    }
4605    return e;
4606 }
4607
4608 static Void local depPair(line,e)       /* find dependents of pair of exprs*/
4609 Int  line;
4610 Cell e; {
4611     fst(e) = depExpr(line,fst(e));
4612     snd(e) = depExpr(line,snd(e));
4613 }
4614
4615 static Void local depTriple(line,e)     /* find dependents of triple exprs */
4616 Int  line;
4617 Cell e; {
4618     fst3(e) = depExpr(line,fst3(e));
4619     snd3(e) = depExpr(line,snd3(e));
4620     thd3(e) = depExpr(line,thd3(e));
4621 }
4622
4623 static Void local depComp(l,e,qs)       /* find dependents of comprehension*/
4624 Int  l;
4625 Cell e;
4626 List qs; {
4627     if (isNull(qs)) {
4628         fst(e) = depExpr(l,fst(e));
4629     } else {
4630         Cell q   = hd(qs);
4631         List qs1 = tl(qs);
4632         switch (whatIs(q)) {
4633             case FROMQUAL : {   List obvs   = saveBvars();
4634                                 snd(snd(q)) = depExpr(l,snd(snd(q)));
4635                                 enterBtyvs();
4636                                 fst(snd(q)) = bindPat(l,fst(snd(q)));
4637                                 depComp(l,e,qs1);
4638                                 fst(snd(q)) = applyBtyvs(fst(snd(q)));
4639                                 restoreBvars(obvs);
4640                             }
4641                             break;
4642
4643             case QWHERE   : snd(q)      = eqnsToBindings(snd(q),NIL,NIL,NIL);
4644                             withinScope(snd(q));
4645                             snd(q)      = dependencyAnal(snd(q));
4646                             hd(depends) = snd(q);
4647                             depComp(l,e,qs1);
4648                             leaveScope();
4649                             break;
4650
4651             case DOQUAL   : /* fall-thru */
4652             case BOOLQUAL : snd(q) = depExpr(l,snd(q));
4653                             depComp(l,e,qs1);
4654                             break;
4655         }
4656     }
4657 }
4658
4659 static Void local depCaseAlt(line,a)    /* Find dependents of case altern. */
4660 Int  line;
4661 Cell a; {
4662     List obvs = saveBvars();            /* Save list of bound variables    */
4663     enterBtyvs();
4664     fst(a)    = bindPat(line,fst(a));   /* Add new bound vars for pats     */
4665     depRhs(snd(a));                     /* Find dependents of rhs          */
4666     fst(a)    = applyBtyvs(fst(a));
4667     restoreBvars(obvs);                 /* Restore original list of bvars  */
4668 }
4669
4670 static Cell local depVar(line,e)        /* Register occurrence of variable */
4671 Int line;
4672 Cell e; {
4673     List bounds1   = bounds;
4674     List bindings1 = bindings;
4675     List depends1  = depends;
4676     Text t         = textOf(e);
4677     Cell n;
4678
4679     while (nonNull(bindings1)) {
4680         n = varIsMember(t,hd(bounds1));   /* look for t in bound variables */
4681         if (nonNull(n)) {
4682             return n;
4683         }
4684         n = findBinding(t,hd(bindings1)); /* look for t in var bindings    */
4685         if (nonNull(n)) {
4686             if (!cellIsMember(n,hd(depends1))) {
4687                 hd(depends1) = cons(n,hd(depends1));
4688             }
4689            return (isVar(fst(n)) ? fst(n) : e);
4690         }
4691
4692         bounds1   = tl(bounds1);
4693         bindings1 = tl(bindings1);
4694         depends1  = tl(depends1);
4695     }
4696
4697     if (isNull(n=findName(t))) {               /* check global definitions */
4698         ERRMSG(line) "Undefined variable \"%s\"", textToStr(t)
4699         EEND;
4700     }
4701
4702     if (!moduleThisScript(name(n).mod)) {
4703         return n;
4704     }
4705     /* Later phases of the system cannot cope if we resolve references
4706      * to unprocessed objects too early.  This is the main reason that
4707      * we cannot cope with recursive modules at the moment.
4708      */
4709     return e;
4710 }
4711
4712 static Cell local depQVar(line,e)/* register occurrence of qualified variable */
4713 Int line;
4714 Cell e; {
4715     Name n = findQualName(e);
4716     if (isNull(n)) {                            /* check global definitions */
4717         ERRMSG(line) "Undefined qualified variable \"%s\"", identToStr(e)
4718         EEND;
4719     }
4720     if (name(n).mod != currentModule) {
4721         return n;
4722     }
4723     if (fst(e) == VARIDCELL) {
4724         e = mkVar(qtextOf(e));
4725     } else {
4726         e = mkVarop(qtextOf(e));
4727     }
4728     return depVar(line,e);
4729 }
4730
4731 static Void local depConFlds(line,e,isP)/* check construction using fields */
4732 Int  line;
4733 Cell e;
4734 Bool isP; {
4735     Name c = conDefined(line,fst(snd(e)));
4736     if (isNull(snd(snd(e))) ||
4737         nonNull(cellIsMember(c,depFields(line,e,snd(snd(e)),isP)))) {
4738         fst(snd(e)) = c;
4739     } else {
4740         ERRMSG(line) "Constructor \"%s\" does not have selected fields in ",
4741                      textToStr(name(c).text)
4742         ETHEN ERREXPR(e);
4743         ERRTEXT "\n"
4744         EEND;
4745     }
4746     if (!isP && isPair(name(c).defn)) { /* Check that banged fields defined*/
4747         List scs = fst(name(c).defn);   /* List of strict components       */
4748         Type t   = name(c).type;
4749         Int  a   = userArity(c);
4750         List fs  = snd(snd(e));
4751         List ss;
4752         if (isPolyType(t)) {            /* Find tycon that c belongs to    */
4753             t = monotypeOf(t);
4754         }
4755         if (isQualType(t)) {
4756             t = snd(snd(t));
4757         }
4758         if (whatIs(t)==CDICTS) {
4759             t = snd(snd(t));
4760         }
4761         while (0<a--) {
4762             t = arg(t);
4763         }
4764         while (isAp(t)) {
4765             t = fun(t);
4766         }
4767         for (ss=tycon(t).defn; hasCfun(ss); ss=tl(ss)) {
4768         }
4769         /* Now we know the tycon t that c belongs to, and the corresponding
4770          * list of selectors for that type, ss.  Now we have to check that
4771          * each of the fields identified by scs appears in fs, using ss to
4772          * cross reference, and convert integers to selector names.
4773          */
4774         for (; nonNull(scs); scs=tl(scs)) {
4775             Int  i   = intOf(hd(scs));
4776             List ss1 = ss;
4777             for (; nonNull(ss1); ss1=tl(ss1)) {
4778                 List cns = name(hd(ss1)).defn;
4779                 for (; nonNull(cns); cns=tl(cns)) {
4780                     if (fst(hd(cns))==c) {
4781                         break;
4782                     }
4783                 }
4784                 if (nonNull(cns) && intOf(snd(hd(cns)))==i) {
4785                     break;
4786                 }
4787             }
4788             if (isNull(ss1)) {
4789                 internal("depConFlds");
4790             } else {
4791                 Name s   = hd(ss1);
4792                 List fs1 = fs;
4793                 for (; nonNull(fs1) && s!=fst(hd(fs1)); fs1=tl(fs1)) {
4794                 }
4795                 if (isNull(fs1)) {
4796                     ERRMSG(line) "Construction does not define strict field"
4797                     ETHEN
4798                     ERRTEXT      "\nExpression : " ETHEN ERREXPR(e);
4799                     ERRTEXT      "\nField      : " ETHEN ERREXPR(s);
4800                     ERRTEXT      "\n"
4801                     EEND;
4802                 }
4803             }
4804         }
4805     }
4806 }
4807
4808 static Void local depUpdFlds(line,e)    /* check update using fields       */
4809 Int  line;
4810 Cell e; {
4811     if (isNull(thd3(snd(e)))) {
4812         ERRMSG(line) "Empty field list in update"
4813         EEND;
4814     }
4815     fst3(snd(e)) = depExpr(line,fst3(snd(e)));
4816     snd3(snd(e)) = depFields(line,e,thd3(snd(e)),FALSE);
4817 }
4818
4819 static List local depFields(l,e,fs,isP) /* check field binding list        */
4820 Int  l;
4821 Cell e;
4822 List fs;
4823 Bool isP; {
4824     List cs = NIL;
4825     List ss = NIL;
4826
4827     for (; nonNull(fs); fs=tl(fs)) {    /* for each field binding          */
4828         Cell fb = hd(fs);
4829         Name s;
4830
4831         if (isVar(fb)) {                /* expand  var  to  var = var      */
4832             h98DoesntSupport(l,"missing field bindings");
4833             fb = hd(fs) = pair(fb,fb);
4834         }
4835
4836         s = findQualName(fst(fb));      /* check for selector              */
4837         if (nonNull(s) && isSfun(s)) {
4838             fst(fb) = s;
4839         } else {
4840             ERRMSG(l) "\"%s\" is not a selector function/field name",
4841                       textToStr(textOf(fst(fb)))
4842             EEND;
4843         }
4844
4845         if (isNull(ss)) {               /* for first named selector        */
4846             List scs = name(s).defn;    /* calculate list of constructors  */
4847             for (; nonNull(scs); scs=tl(scs)) {
4848                 cs = cons(fst(hd(scs)),cs);
4849             }
4850             ss = singleton(s);          /* initialize selector list        */
4851         } else {                        /* for subsequent selectors        */
4852             List ds = cs;               /* intersect constructor lists     */
4853             for (cs=NIL; nonNull(ds); ) {
4854                 List scs = name(s).defn;
4855                 while (nonNull(scs) && fst(hd(scs))!=hd(ds)) {
4856                     scs = tl(scs);
4857                 }
4858                 if (isNull(scs)) {
4859                     ds = tl(ds);
4860                 } else {
4861                     List next = tl(ds);
4862                     tl(ds)    = cs;
4863                     cs        = ds;
4864                     ds        = next;
4865                 }
4866             }
4867
4868             if (cellIsMember(s,ss)) {   /* check for repeated uses         */
4869                 ERRMSG(l) "Repeated field name \"%s\" in field list",
4870                           textToStr(name(s).text)
4871                 EEND;
4872             }
4873             ss = cons(s,ss);
4874         }
4875
4876         if (isNull(cs)) {               /* Are there any matching constrs? */
4877             ERRMSG(l) "No constructor has all of the fields specified in "
4878             ETHEN ERREXPR(e);
4879             ERRTEXT "\n"
4880             EEND;
4881         }
4882
4883         snd(fb) = (isP ? checkPat(l,snd(fb)) : depExpr(l,snd(fb)));
4884     }
4885     return cs;
4886 }
4887
4888 #if IPARAM
4889 static Void local depWith(line,e)       /* check with using fields         */
4890 Int  line;
4891 Cell e; {
4892     fst(snd(e)) = depExpr(line,fst(snd(e)));
4893     snd(snd(e)) = depDwFlds(line,e,snd(snd(e)));
4894 }
4895
4896 static List local depDwFlds(l,e,fs)/* check field binding list     */
4897 Int  l;
4898 Cell e;
4899 List fs;
4900 {
4901     Cell c = fs;
4902     for (; nonNull(c); c=tl(c)) {       /* for each field binding          */
4903         snd(hd(c)) = depExpr(l,snd(hd(c)));
4904     }
4905     return fs;
4906 }
4907 #endif
4908
4909 #if TREX
4910 static Cell local depRecord(line,e)     /* find dependents of record and   */
4911 Int  line;                              /* sort fields into approp. order  */
4912 Cell e; {                               /* to make construction and update */
4913     List exts = NIL;                    /* more efficient.                 */
4914     Cell r    = e;
4915
4916     h98DoesntSupport(line,"extensible records");
4917     do {                                /* build up list of extensions     */
4918         Text   t    = extText(fun(fun(r)));
4919         String s    = textToStr(t);
4920         List   prev = NIL;
4921         List   nx   = exts;
4922         while (nonNull(nx) && strcmp(textToStr(extText(fun(fun(nx)))),s)>0) {
4923             prev = nx;
4924             nx   = extRow(nx);
4925         }
4926         if (nonNull(nx) && t==extText(fun(fun(nx)))) {
4927             ERRMSG(line) "Repeated label \"%s\" in record ", s
4928             ETHEN ERREXPR(e);
4929             ERRTEXT "\n"
4930             EEND;
4931         }
4932         if (isNull(prev)) {
4933             exts = cons(fun(r),exts);
4934         } else {
4935             tl(prev) = cons(fun(r),nx);
4936         }
4937         extField(r) = depExpr(line,extField(r));
4938         r           = extRow(r);
4939     } while (isAp(r) && isAp(fun(r)) && isExt(fun(fun(r))));
4940     r = depExpr(line,r);
4941     return revOnto(exts,r);
4942 }
4943 #endif
4944
4945
4946 /* --------------------------------------------------------------------------
4947  * Several parts of this program require an algorithm for sorting a list
4948  * of values (with some added dependency information) into a list of strongly
4949  * connected components in which each value appears before its dependents.
4950  *
4951  * Each of these algorithms is obtained by parameterising a standard
4952  * algorithm in "scc.c" as shown below.
4953  * ------------------------------------------------------------------------*/
4954
4955 #define  SCC2            tcscc          /* make scc algorithm for Tycons   */
4956 #define  LOWLINK         tclowlink
4957 #define  DEPENDS(c)      (isTycon(c) ? tycon(c).kind : cclass(c).kinds)
4958 #define  SETDEPENDS(c,v) if(isTycon(c)) tycon(c).kind=v; else cclass(c).kinds=v
4959 #include "scc.c"
4960 #undef   SETDEPENDS
4961 #undef   DEPENDS
4962 #undef   LOWLINK
4963 #undef   SCC2
4964
4965 #define  SCC             bscc           /* make scc algorithm for Bindings */
4966 #define  LOWLINK         blowlink
4967 #define  DEPENDS(t)      depVal(t)
4968 #define  SETDEPENDS(c,v) depVal(c)=v
4969 #include "scc.c"
4970 #undef   SETDEPENDS
4971 #undef   DEPENDS
4972 #undef   LOWLINK
4973 #undef   SCC
4974
4975 /* --------------------------------------------------------------------------
4976  * Main static analysis:
4977  * ------------------------------------------------------------------------*/
4978
4979 Void checkExp() {                       /* Top level static check on Expr  */
4980     staticAnalysis(RESET);
4981     clearScope();                       /* Analyse expression in the scope */
4982     withinScope(NIL);                   /* of no local bindings            */
4983     inputExpr = depExpr(0,inputExpr);
4984     leaveScope();
4985     staticAnalysis(RESET);
4986 }
4987
4988 #if EXPLAIN_INSTANCE_RESOLUTION
4989 Void checkContext(void) {               /* Top level static check on Expr  */
4990     List vs, qs;
4991
4992     staticAnalysis(RESET);
4993     clearScope();                       /* Analyse expression in the scope */
4994     withinScope(NIL);                   /* of no local bindings            */
4995     qs = inputContext;
4996     for (vs = NIL; nonNull(qs); qs=tl(qs)) {
4997         vs = typeVarsIn(hd(qs),NIL,NIL,vs);
4998     }
4999     map2Proc(depPredExp,0,vs,inputContext);
5000     leaveScope();
5001     staticAnalysis(RESET);
5002 }
5003 #endif
5004
5005 Void checkDefns() {                     /* Top level static analysis       */
5006     Module thisModule = lastModule();
5007     staticAnalysis(RESET);
5008
5009     setCurrModule(thisModule);
5010
5011     /* Resolve module references */
5012     mapProc(checkQualImport,  module(thisModule).qualImports);
5013     mapProc(checkUnqualImport,unqualImports);
5014     /* Add "import Prelude" if there`s no explicit import */
5015     if (thisModule!=modulePrelude
5016         && isNull(cellAssoc(modulePrelude,unqualImports))
5017         && isNull(cellRevAssoc(modulePrelude,module(thisModule).qualImports))) {
5018         unqualImports = cons(pair(modulePrelude,DOTDOT),unqualImports);
5019     } else {
5020         /* Every module (including the Prelude) implicitly contains 
5021          * "import qualified Prelude" 
5022          */
5023         module(thisModule).qualImports=cons(pair(mkCon(textPrelude),modulePrelude),
5024                                             module(thisModule).qualImports);
5025     }
5026     mapProc(checkImportList, unqualImports);
5027
5028     linkPreludeTC();                    /* Get prelude tycons and classes  */
5029     mapProc(checkTyconDefn,tyconDefns); /* validate tycon definitions      */
5030     checkSynonyms(tyconDefns);          /* check synonym definitions       */
5031     mapProc(checkClassDefn,classDefns); /* process class definitions       */
5032     mapProc(kindTCGroup,tcscc(tyconDefns,classDefns)); /* attach kinds     */
5033     mapProc(extendFundeps,classDefns);  /* finish class definitions        */
5034     mapProc(addMembers,classDefns);     /* add definitions for member funs */
5035     mapProc(visitClass,classDefns);     /* check class hierarchy           */
5036     linkPreludeCM();                    /* Get prelude cfuns and mfuns     */
5037     
5038     instDefns = rev(instDefns);         /* process instance definitions    */
5039     mapProc(checkInstDefn,instDefns);
5040
5041     setCurrModule(thisModule);
5042     mapProc(addRSsigdecls,typeInDefns); /* add sigdecls for RESTRICTSYN    */
5043     valDefns   = eqnsToBindings(valDefns,tyconDefns,classDefns,/*primDefns*/NIL);
5044     mapProc(allNoPrevDef,valDefns);     /* check against previous defns    */
5045     mapProc(addDerivImp,derivedInsts);  /* Add impls for derived instances */
5046     deriveContexts(derivedInsts);       /* Calculate derived inst contexts */
5047     instDefns  = appendOnto(instDefns,derivedInsts);
5048     checkDefaultDefns();                /* validate default definitions    */
5049
5050     mapProc(allNoPrevDef,valDefns);     /* check against previous defns    */
5051
5052     linkPreludeNames();
5053
5054     mapProc(checkForeignImport,foreignImports); /* check foreign imports   */
5055     mapProc(checkForeignExport,foreignExports); /* check foreign exports   */
5056     foreignImports = NIL;
5057     foreignExports = NIL;
5058
5059     /* Every top-level name has now been created - so we can build the     */
5060     /* export list.  Note that this has to happen before dependency        */
5061     /* analysis so that references to Prelude.foo will be resolved         */
5062     /* when compiling the prelude.                                         */
5063     module(thisModule).exports = checkExports(module(thisModule).exports);
5064
5065     mapProc(checkTypeIn,typeInDefns);   /* check restricted synonym defns  */
5066
5067     clearScope();
5068     withinScope(valDefns);
5069     valDefns = topDependAnal(valDefns); /* top level dependency ordering   */
5070     mapProc(depDefaults,classDefns);    /* dep. analysis on class defaults */
5071     mapProc(depInsts,instDefns);        /* dep. analysis on inst defns     */
5072     leaveScope();
5073
5074     /* ToDo: evalDefaults should match current evaluation module */
5075     evalDefaults = defaultDefns;        /* Set defaults for evaluator      */
5076
5077     staticAnalysis(RESET);
5078 }
5079
5080
5081
5082
5083 static Void local addRSsigdecls(pr)     /* add sigdecls from TYPE ... IN ..*/
5084 Pair pr; {
5085     List vs = snd(pr);                  /* get list of variables           */
5086     for (; nonNull(vs); vs=tl(vs)) {
5087         if (fst(hd(vs))==SIGDECL) {     /* find a sigdecl                  */
5088             valDefns = cons(hd(vs),valDefns);   /* add to valDefns         */
5089             hd(vs)   = hd(snd3(snd(hd(vs))));   /* and replace with var    */
5090         }
5091     }
5092 }
5093
5094 static Void local allNoPrevDef(b)        /* ensure no previous bindings for*/
5095 Cell b; {                                /* variables in new binding       */
5096     if (isVar(fst(b))) {
5097         noPrevDef(rhsLine(snd(hd(snd(snd(b))))),fst(b));
5098     } else {
5099         Int line = rhsLine(snd(snd(snd(b))));
5100         map1Proc(noPrevDef,line,fst(b));
5101     }
5102 }
5103
5104 static Void local noPrevDef(line,v)      /* ensure no previous binding for */
5105 Int  line;                               /* new variable                   */
5106 Cell v; {
5107     Name n = findName(textOf(v));
5108
5109     if (isNull(n)) {
5110         n            = newName(textOf(v),NIL);
5111         name(n).defn = PREDEFINED;
5112     } else if (name(n).defn!=PREDEFINED) {
5113         duplicateError(line,name(n).mod,name(n).text,"variable");
5114     }
5115     name(n).line = line;
5116 }
5117
5118 static Void local duplicateErrorAux(line,mod,t,kind)/* report duplicate defn */
5119 Int    line;
5120 Module mod;
5121 Text   t;
5122 String kind; {
5123     if (mod == currentModule) {
5124         ERRMSG(line) "Repeated definition for %s \"%s\"", kind, 
5125                      textToStr(t)
5126         EEND;
5127     } else {
5128         ERRMSG(line) "Definition of %s \"%s\" clashes with import", kind,
5129                      textToStr(t)
5130         EEND;
5131     }
5132 }
5133
5134 static Void local checkTypeIn(cvs)      /* Check that vars in restricted   */
5135 Pair cvs; {                             /* synonym are defined             */
5136     Tycon c  = fst(cvs);
5137     List  vs = snd(cvs);
5138
5139     for (; nonNull(vs); vs=tl(vs)) {
5140         if (isNull(findName(textOf(hd(vs))))) {
5141             ERRMSG(tycon(c).line)
5142                 "No top level binding of \"%s\" for restricted synonym \"%s\"",
5143                 textToStr(textOf(hd(vs))), textToStr(tycon(c).text)
5144             EEND;
5145         }
5146     }
5147 }
5148
5149 /* --------------------------------------------------------------------------
5150  * Haskell 98 compatibility tests:
5151  * ------------------------------------------------------------------------*/
5152
5153 Bool h98Pred(allowArgs,pi)              /* Check syntax of Hask98 predicate*/
5154 Bool allowArgs;
5155 Cell pi; {
5156     return isClass(getHead(pi)) && argCount==1 &&
5157            isOffset(getHead(arg(pi))) && (argCount==0 || allowArgs);
5158 }
5159
5160 Cell h98Context(allowArgs,ps)           /* Check syntax of Hask98 context  */
5161 Bool allowArgs;
5162 List ps; {
5163     for (; nonNull(ps); ps=tl(ps)) {
5164         if (!h98Pred(allowArgs,hd(ps))) {
5165             return hd(ps);
5166         }
5167     }
5168     return NIL;
5169 }
5170
5171 Void h98CheckCtxt(line,wh,allowArgs,ps,in)
5172 Int    line;                            /* Report illegal context/predicate*/
5173 String wh;
5174 Bool   allowArgs;
5175 List   ps;
5176 Inst   in; {
5177     if (haskell98) {
5178         Cell pi = h98Context(allowArgs,ps);
5179         if (nonNull(pi)) {
5180             ERRMSG(line) "Illegal Haskell 98 class constraint in %s",wh ETHEN
5181             if (nonNull(in)) {
5182                 ERRTEXT  "\n*** Instance   : " ETHEN ERRPRED(inst(in).head);
5183             }
5184             ERRTEXT      "\n*** Constraint : " ETHEN ERRPRED(pi);
5185             if (nonNull(ps) && nonNull(tl(ps))) {
5186                 ERRTEXT  "\n*** Context    : " ETHEN ERRCONTEXT(ps);
5187             }
5188             ERRTEXT      "\n"
5189             EEND;
5190         }
5191     }
5192 }
5193
5194 Void h98CheckType(line,wh,e,t)          /* Check for Haskell 98 type       */
5195 Int    line;
5196 String wh;
5197 Cell   e;
5198 Type   t; {
5199     if (haskell98) {
5200         Type ty = t;
5201         if (isPolyType(t))
5202             t = monotypeOf(t);
5203         if (isQualType(t)) {
5204             Cell pi = h98Context(TRUE,fst(snd(t)));
5205             if (nonNull(pi)) {
5206                 ERRMSG(line) "Illegal Haskell 98 class constraint in %s",wh
5207                 ETHEN
5208                 ERRTEXT  "\n*** Expression : " ETHEN ERREXPR(e);
5209                 ERRTEXT  "\n*** Type       : " ETHEN ERRTYPE(ty);
5210                 ERRTEXT  "\n"
5211                 EEND;
5212             }
5213         }
5214     }
5215 }
5216
5217 Void h98DoesntSupport(line,wh)          /* Report feature missing in H98   */
5218 Int    line;
5219 String wh; {
5220     if (haskell98) {
5221         ERRMSG(line) "Haskell 98 does not support %s", wh
5222         EEND;
5223     }
5224 }
5225
5226 /* --------------------------------------------------------------------------
5227  * Static Analysis control:
5228  * ------------------------------------------------------------------------*/
5229
5230 Void staticAnalysis(what)
5231 Int what; {
5232     switch (what) {
5233         case RESET   : cfunSfuns    = NIL;
5234                        daSccs       = NIL;
5235                        patVars      = NIL;
5236                        bounds       = NIL;
5237                        bindings     = NIL;
5238                        depends      = NIL;
5239                        tcDeps       = NIL;
5240                        derivedInsts = NIL;
5241                        diVars       = NIL;
5242                        diNum        = 0;
5243                        unkindTypes  = NIL;
5244                        break;
5245
5246         case MARK    : mark(daSccs);
5247                        mark(patVars);
5248                        mark(bounds);
5249                        mark(bindings);
5250                        mark(depends);
5251                        mark(tcDeps);
5252                        mark(derivedInsts);
5253                        mark(diVars);
5254                        mark(cfunSfuns);
5255                        mark(unkindTypes);
5256 #if TREX
5257                        mark(extKind);
5258 #endif
5259                        break;
5260
5261         case INSTALL : staticAnalysis(RESET);
5262 #if TREX
5263                        extKind = pair(STAR,pair(ROW,ROW));
5264 #endif
5265                        break;
5266     }
5267 }
5268
5269 /*-------------------------------------------------------------------------*/