Add tests, fixes for tests, reinstate and type-convert stuff marked "bitrot"
[ccom.git] / c02.c
1 /*
2  * C compiler
3  */
4
5 #include <string.h>
6 #include "c0.h"
7 #include "c1.h" /* pswitch0() one-pass version */
8 /*
9  * Process a single external definition
10  */
11 void extdef() {
12         register int o;
13         int sclass, scflag;
14  /*     struct nmlist typer;*/
15  struct type *dtype;
16  static struct type t_int = {INT};
17         register struct nmlist *ds;
18  struct tdim dim;
19  int a;
20
21         if(((o=symbol())==EOFC) || o==SEMI)
22                 return;
23         peeksym = o;
24         sclass = 0;
25         blklev = 0;
26         if (/*getkeywords(&sclass, &typer)==0*/(dtype = getkeywords(&sclass)) == NULL) {
27                 sclass = EXTERN;
28                 if (peeksym!=NAME)
29                         goto syntax;
30  dtype = &t_int;
31         }
32         scflag = 0;
33         if (sclass==DEFXTRN) {
34                 scflag++;
35                 sclass = EXTERN;
36         }
37         if (sclass!=EXTERN && sclass!=STATIC && sclass!=TYPEDEF)
38                 error0("Illegal storage class");
39         do {
40                 defsym = 0;
41                 paraml = NULL;
42                 parame = NULL;
43                 if (sclass==TYPEDEF) {
44                         decl1(TYPEDEF, /*&typer*/dtype, 0, (struct nmlist *)NULL);
45                         continue;
46                 }
47                 decl1(EXTERN, /*&typer*/dtype, 0, (struct nmlist *)NULL);
48                 if ((ds=defsym)==0)
49                         return;
50                 funcsym = ds;
51                 if (/*(ds->nl_type&XTYPE)==FUNC*/ds->nl_dtype->t_id==(REF|FUNC)) {
52                         if ((peeksym=symbol())==LBRACE || peeksym==KEYW
53                          || (peeksym==NAME && csym->nl_class==TYPEDEF)) {
54  /* create a fake local variable of same type as function's return type */
55  /*                             funcblk.locnn_type = decref0(ds->nl_type);
56                                 funcblk.locnn_strp = ds->nl_strp;*/
57  dim.rank = 0;
58  funcblk.locnn_type = XXXoldtype(((struct ftype *)ds->nl_dtype)->ft_reftype, &dim, (struct SS **)&funcblk.locnn_strp);
59  funcblk.locnn_subsp = dim.rank ? (int *)Tblock(dim.rank*sizeof(dim.rank)) : NULL;
60  for (a=0; a<dim.rank; a++)
61   funcblk.locnn_subsp[a] = dim.dimens[a];
62                                 setinit(ds);
63                                 outcode("BS", SYMDEF, sclass==EXTERN?ds->nl_name:"");
64                                 cfunc();
65                                 return;
66                         }
67                         if (paraml)
68                                 error0("Inappropriate parameters");
69                 } else if ((o=symbol())==COMMA || o==SEMI) {
70                         peeksym = o;
71                         o = (length(/*(struct node *)ds*/ds->nl_dtype)+ALIGN) & ~ALIGN;
72                         if (sclass==STATIC) {
73                                 setinit(ds);
74                                 outcode("BSBBSBN", SYMDEF, "", BSS, NLABEL, ds->nl_name, SSPACE, o);
75                         } else if (scflag)
76                                 outcode("BSN", CSPACE, ds->nl_name, o);
77                 } else {
78                         if (o!=ASSIGN) {
79                                 error0("Declaration syntax");
80                                 peeksym = o;
81                         }
82                         setinit(ds);
83                         if (sclass==EXTERN)
84                                 outcode("BS", SYMDEF, ds->nl_name);
85                         outcode("BBS", DATA, NLABEL, ds->nl_name);
86                         if (cinit(ds, 1, sclass) & ALIGN)
87                                 outcode("B", EVEN);
88                 }
89         } while ((o=symbol())==COMMA);
90         if (o==SEMI)
91                 return;
92 syntax:
93         if (o==RBRACE) {
94                 error0("Too many }'s");
95                 peeksym = 0;
96                 return;
97         }
98         error0("External definition syntax");
99         errflush(o);
100         statement();
101 }
102
103 /*
104  * Process a function definition.
105  */
106 void cfunc() {
107         register char *cb;
108         register int sloc;
109
110         sloc = isn0;
111         isn0 += 2;
112         outcode("BBS", PROG, RLABEL, funcsym->nl_name);
113         regvar = 5;
114         autolen = STAUTO;
115         maxauto = STAUTO;
116         blklev = 1;
117         cb = locbase;
118         declist(ARG);
119         outcode("B", SAVE);
120         if (proflg)
121                 outcode("BNS", PROFIL, isn0++, funcsym->nl_name);
122         funchead();
123         branch0(sloc);
124         label0(sloc+1);
125         retlab = isn0++;
126         blklev = 0;
127         if ((peeksym = symbol()) != LBRACE)
128                 error0("Compound statement required");
129         statement();
130         outcode("BNB", LABEL, retlab, RETRN);
131         label0(sloc);
132 /* add STAUTO; overlay bug fix, coupled with section in c11.c */
133         outcode("BN", SETSTK, -maxauto+STAUTO);
134         branch0(sloc+1);
135  /*fprintf(stderr, "cb=%p\n", cp);*/
136         locbase = cb;
137 }
138
139 /*
140  * Process the initializers for an external definition.
141  */
142 int cinit(anp, flex, sclass) struct nmlist *anp; int flex; int sclass; {
143         struct nmlist np;
144         register int nel, ninit;
145         int width, isarray, o, brace/*, realtype*/;
146  struct type *realtype;
147         struct node *s;
148  struct tdim dim;
149  int type;
150  union str *strp;
151  int *subsp, a;
152
153         np = *anp;
154         realtype = /*np.nl_type*/np.nl_dtype;
155         isarray = 0;
156         if (/*(realtype&XTYPE) == ARRAY*/realtype->t_id == (REF | ARRAY))
157                 isarray++;
158         else
159                 flex = 0;
160         width = length(/*(struct node *)&np*/np.nl_dtype);
161         nel = 1;
162         /*
163          * If it's an array, find the number of elements.
164          * temporarily modify to look like kind of thing it's
165          * an array of.
166          */
167         if (sclass==AUTO)
168                 if (isarray || /*realtype*/realtype->t_id==STRUCT)
169                         error0("No auto. aggregate initialization");
170         if (isarray) {
171  /*             np.nl_type = decref0(realtype);
172                 np.nl_subsp++;*/
173  np.nl_dtype = ((struct atype *)realtype)->at_reftype;
174                 if (width==0 && flex==0)
175                         error0("0-length row: %s", anp->nl_name);
176                 o = length(/*(struct node *)&np*/np.nl_dtype);
177                 nel = (unsigned)width/o;
178                 width = o;
179         }
180         brace = 0;
181         if ((peeksym=symbol())==LBRACE && (isarray || /*np.nl_type*/np.nl_dtype->t_id!=STRUCT)) {
182                 peeksym = -1;
183                 brace++;
184         }
185         ninit = 0;
186         do {
187                 if ((o=symbol())==RBRACE)
188                         break;
189                 peeksym = o;
190                 if (o==STRING && /*(realtype==ARRAY+CHAR || realtype==ARRAY+UNCHAR)*/realtype->t_id == (REF | ARRAY) && (((struct atype *)realtype)->at_reftype->t_id == CHAR || ((struct atype *)realtype)->at_reftype->t_id == UNCHAR)) {
191                         if (sclass==AUTO)
192                                 error0("No strings in automatic");
193                         peeksym = -1;
194                         putstr(0, flex?10000:nel);
195                         ninit += nchstr;
196                         o = symbol();
197                         break;
198                 } else if (/*np.nl_type*/np.nl_dtype->t_id==STRUCT) {
199                         strinit(&np, sclass);
200                 } else if (/*(np.nl_type&ARRAY)==ARRAY*/np.nl_dtype->t_id==(REF|ARRAY) || peeksym==LBRACE)
201                         cinit(&np, 0, sclass);
202                 else {
203                         char *st;
204                         initflg++;
205                         st = starttree();
206                         s = tree(/*0*/);
207                         initflg = 0;
208                         if (np./*nl_flag&FFIELD*/nl_dtype->t_id==BITFLD)
209                                 error0("No field initialization");
210                         *cp++ = (struct node *)nblock(&np);
211                         *cp++ = s;
212                         build(ASSIGN);
213                         if (sclass==AUTO||sclass==REG)
214                                 rcexpr0(*--cp);
215                         else if (sclass==ENUMCON) {
216                                 if (s->n_op!=CON)
217                                         error0("Illegal enum constant for %s", anp->nl_name);
218                                 anp->nl_offset = ((struct cnode *)s)->cn_value;
219                         } else
220  {
221   dim.rank = 0;
222   type = XXXoldtype(np.nl_dtype, &dim, (struct SS **)&strp);
223   subsp = dim.rank ? (int *)Tblock(dim.rank*sizeof(dim.rank)) : NULL;
224   for (a=0; a<dim.rank; a++)
225    subsp[a] = dim.dimens[a];
226                                 rcexpr0((struct node *)block(INIT,/*np.nl_type*/type,/*(int *)NULL*/subsp,
227                                   /*(union str *)NULL*/strp, ((struct tnode *)(*--cp))->tn_tr2, (struct node *)NULL));
228  }
229                         endtree(st);
230                 }
231                 ninit++;
232                 if ((ninit&077)==0 && sclass==EXTERN)
233                         outcode("BS", SYMDEF, "");
234         } while ((o=symbol())==COMMA && (ninit<nel || brace || flex));
235         if (brace==0 || o!=RBRACE)
236                 peeksym = o;
237         /*
238          * If there are too few initializers, allocate
239          * more storage.
240          * If there are too many initializers, extend
241          * the declared size for benefit of "sizeof"
242          */
243         if (ninit<nel && sclass!=AUTO)
244                 outcode("BN", SSPACE, (nel-ninit)*width);
245         else if (ninit>nel) {
246                 if (flex && nel==0) {
247  /* note: nel==0 implies isarray, since otherwise nel must be 1 */
248  /*                     np.nl_subsp[-1] = ninit;*/
249 #define arealtype (*(struct atype **)&realtype)
250  arealtype = (struct atype *)Dblock(sizeof(struct atype));
251  arealtype->at_id = REF | ARRAY;
252  arealtype->at_reftype = np.nl_dtype;
253  arealtype->at_nelt = ninit;
254  anp->nl_dtype = (struct type *)arealtype;
255 #undef arealtype
256                 } else
257                         error0("Too many initializers: %s", anp->nl_name);
258                 nel = ninit;
259         }
260         return(nel*width);
261 }
262
263 /*
264  * Initialize a structure
265  */
266 void strinit(np, sclass) struct nmlist *np; int sclass; {
267  /*     static*/ struct nmlist junk;
268  static struct type t_int = {INT};
269         register struct nmlist **mlp;
270         static struct nmlist *zerloc = NULL;
271         register int o, brace;
272
273         if ((mlp = /*np->nl_strp->S.memlist*/((struct stype *)np->nl_dtype)->st_memlist)==NULL) {
274                 mlp = &zerloc;
275                 error0("Undefined structure initialization");
276         }
277         brace = 0;
278         if ((o = symbol()) == LBRACE)
279                 brace++;
280         else
281                 peeksym = o;
282         do {
283                 if ((o=symbol()) == RBRACE)
284                         break;
285                 peeksym = o;
286                 if (*mlp==0) {
287  /* change this to a static struct nmlist later when nmlist has stabilized */
288  bzero(&junk, sizeof(struct nmlist));
289  junk.nl_dtype = &t_int;
290                         error0("Too many structure initializers");
291                         cinit(&junk, 0, sclass);
292                 } else
293                         cinit(*mlp++, 0, sclass);
294                 if (*mlp ==  &structhole) {
295                         outcode("B", EVEN);
296                         mlp++;
297                 }
298                                 /* DAG -- union initialization bug fix */
299                 if (*mlp && mlp[-1]->nl_offset == (*mlp)->nl_offset) {
300                         werror0("union initialization non-portable");
301                         while (*mlp)    /* will NOT be &structhole */
302                                 mlp++;  /* skip other members of union */
303                 }
304         } while ((o=symbol())==COMMA && (*mlp || brace));
305         if (sclass!=AUTO && sclass!=REG) {
306                 if (*mlp)
307                         outcode("BN", SSPACE, /*np->nl_strp->S.ssize*/((struct stype *)np->nl_dtype)->st_ssize - (*mlp)->nl_offset);
308                 outcode("B", EVEN);
309         }
310         if (o!=RBRACE || brace==0)
311                 peeksym = o;
312 }
313
314 /*
315  * Mark already initialized
316  */
317 void setinit(np) register struct nmlist *np; {
318
319         if (np->nl_flag&FINIT)
320                 error0("%s multiply defined", np->nl_name);
321         np->nl_flag |= FINIT;
322 }
323
324 /*
325  * Process one statement in a function.
326  */
327 struct type gototype = {0}; /* dummy type distinguished by its address */
328 void statement() {
329         register int o, o1;
330         int sauto, sreg;
331
332 stmt:
333         switch(o=symbol()) {
334
335         case EOFC:
336                 error0("Unexpected EOF");
337         case SEMI:
338                 return;
339
340         case LBRACE:
341                 sauto = autolen;
342                 sreg = regvar;
343                 blockhead();
344                 while (!eof) {
345                         if ((o=symbol())==RBRACE) {
346                                 autolen = sauto;
347                                 if (sreg!=regvar)
348                                         outcode("BN", SETREG, sreg);
349                                 regvar = sreg;
350                                 blkend();
351                                 return;
352                         }
353                         peeksym = o;
354                         statement();
355                 }
356                 error0("Missing '}'");
357                 return;
358
359         case KEYW:
360                 switch(cval) {
361
362                 case GOTO:
363                         if (o1 = simplegoto())
364                                 branch0(o1);
365                         else 
366                                 dogoto();
367                         goto semi;
368
369                 case RETURN:
370                         doret();
371                         goto semi;
372
373                 case ASM:
374                 {
375                         char    tmp[80],        /* tmp for line buffer */
376                                 *p;
377
378                         if (symbol() != LPARN || (o1 = symbol()) != STRING)
379                                 goto syntax;
380                         for (p = tmp; (o1 = mapch('"')) >= 0; )
381                                 *p++ = o1&0177;
382                         *p = '\0';
383                         if (symbol() != RPARN)
384                                 goto syntax;
385                         outcode("BF", ASSEM, tmp);
386                         goto semi;
387                 }
388
389                 case IF: {
390                         register int o2;
391                         register struct node *np;
392
393  char *st = starttree();
394                         np = pexpr(/*1*/);
395                         o2 = 0;
396                         if ((o1=symbol())==KEYW) switch (cval) {
397                         case GOTO:
398                                 if (o2=simplegoto())
399                                         goto simpif;
400                                 cbranch0(np, o2=isn0++, 0);
401                                 dogoto();
402                                 label0(o2);
403                                 goto hardif;
404
405                         case RETURN:
406                                 if (nextchar()==';') {
407                                         o2 = retlab;
408                                         goto simpif;
409                                 }
410                                 cbranch0(np, o1=isn0++, 0);
411                                 doret();
412                                 label0(o1);
413                                 o2++;
414                                 goto hardif;
415
416                         case BREAK:
417                                 o2 = brklab;
418                                 goto simpif;
419
420                         case CONTIN:
421                                 o2 = contlab;
422                         simpif:
423                                 chconbrk(o2);
424                                 cbranch0(np, o2, 1);
425                         hardif:
426  endtree(st);
427                                 if ((o=symbol())!=SEMI)
428                                         goto syntax;
429                                 if ((o1=symbol())==KEYW && cval==ELSE) 
430                                         goto stmt;
431                                 peeksym = o1;
432                                 return;
433                         }
434                         peeksym = o1;
435                         cbranch0(np, o1=isn0++, 0);
436  endtree(st);
437                         statement();
438                         if ((o=symbol())==KEYW && cval==ELSE) {
439                                 o2 = isn0++;
440                                 branch0(o2);
441                                 label0(o1);
442                                 statement();
443                                 label0(o2);
444                                 return;
445                         }
446                         peeksym = o;
447                         label0(o1);
448                         return;
449                 }
450
451                 case WHILE: {
452  char *st;
453                         register int o2;
454                         o1 = contlab;
455                         o2 = brklab;
456                         label0(contlab = isn0++);
457  st = starttree();
458                         cbranch0(pexpr(/*1*/), brklab=isn0++, 0);
459  endtree(st);
460                         statement();
461                         branch0(contlab);
462                         label0(brklab);
463                         contlab = o1;
464                         brklab = o2;
465                         return;
466                 }
467
468                 case BREAK:
469                         chconbrk(brklab);
470                         branch0(brklab);
471                         goto semi;
472
473                 case CONTIN:
474                         chconbrk(contlab);
475                         branch0(contlab);
476                         goto semi;
477
478                 case DO: {
479                         register int o2, o3;
480                         o1 = contlab;
481                         o2 = brklab;
482                         contlab = isn0++;
483                         brklab = isn0++;
484                         label0(o3 = isn0++);
485                         statement();
486                         label0(contlab);
487                         contlab = o1;
488                         if ((o=symbol())==KEYW && cval==WHILE) {
489  char *st = starttree();
490                                 cbranch0(tree(/*1*/), o3, 1);
491  endtree(st);
492                                 label0(brklab);
493                                 brklab = o2;
494                                 goto semi;
495                         }
496                         goto syntax;
497                 }
498
499                 case CASE:
500                         o1 = conexp();
501                         if ((o=symbol())!=COLON)
502                                 goto syntax;
503                         if (swp==0) {
504                                 error0("Case not in switch");
505                                 goto stmt;
506                         }
507                         if(swp>=swtab+SWSIZ) {
508                                 error0("Switch table overflow");
509                         } else {
510                                 swp->swlab = isn0;
511                                 (swp++)->swval = o1;
512                                 label0(isn0++);
513                         }
514                         goto stmt;
515
516                 case SWITCH: {
517                         register struct node *np;
518                         register char *st;
519
520                         o1 = brklab;
521                         brklab = isn0++;
522                         st = starttree();
523                         np = pexpr(/*0*/);
524                         chkw(np, -1);
525                         rcexpr0((struct node *)block(RFORCE,0,(int *)NULL,(union str *)NULL,np,(struct node *)NULL));
526                         endtree(st);
527                         pswitch0();
528                         brklab = o1;
529                         return;
530                 }
531
532                 case DEFAULT:
533                         if (swp==0)
534                                 error0("Default not in switch");
535                         if (deflab)
536                                 error0("More than 1 'default'");
537                         if ((o=symbol())!=COLON)
538                                 goto syntax;
539                         label0(deflab = isn0++);
540                         goto stmt;
541
542                 case FOR: {
543                         register int o2;
544                         o1 = contlab;
545                         o2 = brklab;
546                         contlab = isn0++;
547                         brklab = isn0++;
548                         if (o=forstmt())
549                                 goto syntax;
550                         contlab = o1;
551                         brklab = o2;
552                         return;
553                 }
554
555                 case ELSE:
556                         error0("Inappropriate 'else'");
557                         statement();
558                         return;
559                 }
560                 error0("Unknown keyword");
561                 goto syntax;
562
563         case NAME: {
564                 register struct nmlist *np;
565                 if (nextchar()==':') {
566                         peekc = 0;
567                         np = csym;
568                         if (np->nl_class>0) {
569                                 if (np->nl_blklev==0) {
570                                         np = pushdecl(np);
571                                         np->nl_offset = 0;
572                                 } else {
573                                         defsym = np;
574                                         redec();
575                                         goto stmt;
576                                 }
577                         }
578                         np->nl_class = STATIC;
579  /*                     np->nl_type = ARRAY;*/
580  np->nl_dtype = &gototype;
581                         np->nl_flag |= FLABL;
582                         if (np->nl_offset==0)
583                                 np->nl_offset = isn0++;
584                         label0(np->nl_offset);
585                         goto stmt;
586                 }
587         }
588         }
589         peeksym = o;
590  {
591   char *st = starttree();
592         rcexpr0(tree(/*1*/));
593   endtree(st);
594  }
595
596 semi:
597         if ((o=symbol())==SEMI)
598                 return;
599 syntax:
600         error0("Statement syntax");
601         errflush(o);
602 }
603
604 /*
605  * Process a for statement.
606  */
607 int forstmt() {
608         register int o;
609         register struct node *st;
610         register int l;
611         char *ss;
612
613         if ((o=symbol()) != LPARN)
614                 return(o);
615  ss = starttree();
616         if ((o=symbol()) != SEMI) {             /* init part */
617                 peeksym = o;
618                 rcexpr0(tree(/*1*/));
619                 if ((o=symbol()) != SEMI)
620  {
621   endtree(ss);
622                         return(o);
623  }
624         }
625         l = isn0;
626         isn0 += 3;
627         branch0(l+0);
628         label0(l+1);
629         branch0(l+2);
630         label0(contlab);
631         st = NULL;
632         if ((o=symbol()) != SEMI) {             /* test part */
633                 peeksym = o;
634  /*             ss = starttree();*/
635                 st = tree(0);
636                 if ((o=symbol()) != SEMI) {
637                         endtree(ss);
638                         return(o);
639                 }
640         }
641         if ((o=symbol()) != RPARN) {    /* incr part */
642                 peeksym = o;
643                 rcexpr0(tree(/*1*/));
644                 if ((o=symbol()) != RPARN) {
645  /*                     if (st)*/
646                                 endtree(ss);
647                         return(o);
648                 }
649         }
650         label0(l+0);
651         if (st) {
652                 cbranch0(st, l+1, 1);
653  /*             endtree(ss);*/
654         } else
655                 branch0(l+1);
656  endtree(ss);
657         branch0(brklab);
658         label0(l+2);
659         statement();
660         branch0(contlab);
661         label0(brklab);
662         return(0);
663 }
664
665 /*
666  * A parenthesized expression,
667  * as after "if".
668  */
669 struct node *pexpr(/*eflag*/) /*int eflag;*/ {
670         register int o;
671         register struct node *t;
672
673         if ((o=symbol())!=LPARN)
674                 goto syntax;
675         t = tree(/*eflag*/);
676         if ((o=symbol())!=RPARN)
677                 goto syntax;
678         if (t->n_type==VOID)
679                 error0("Illegal use of void");
680         return(t);
681 syntax:
682         error0("Statement syntax");
683         errflush(o);
684         return(0);
685 }
686
687 /*
688  * The switch statement, which involves collecting the
689  * constants and labels for the cases.
690  */
691 void pswitch0() {
692         register struct swtab *cswp, *sswp;
693         int dl, swlab;
694 #if 1 /* one-pass version */
695         char *svtree;
696 #endif
697
698         cswp = sswp = swp;
699         if (swp==0)
700                 cswp = swp = swtab;
701         branch0(swlab=isn0++);
702         dl = deflab;
703         deflab = 0;
704         statement();
705         branch0(brklab);
706         label0(swlab);
707         if (deflab==0)
708                 deflab = brklab;
709 #if 1 /* one-pass version */
710         svtree = starttree();
711         pswitch1(cswp, swp, deflab);
712         endtree(svtree);
713 #else
714         outcode("BNN", SWIT, deflab, line);
715         for (; cswp < swp; cswp++)
716                 outcode("NN", cswp->swlab, cswp->swval);
717         outcode("0");
718 #endif
719         label0(brklab);
720         deflab = dl;
721         swp = sswp;
722 }
723
724 /*
725  * funchead is called at the start of each function
726  * to process the arguments, which have been linked in a list.
727  * This list is necessary because in
728  * f(a, b) float b; int a; ...
729  * the names are seen before the types.
730  */
731 /*
732  * Structure resembling a block for a register variable.
733  */
734 struct  nmlist  hreg    = { REG, 0, /*0, (int *)NULL, (union str *)NULL,*/ (struct type *)NULL, 0/*nl_offset*/ }; /* note: remaining fields not initialized */
735 struct  locnnode areg   = { { { NAME, 0, (int *)NULL, (union str *)NULL }, &hreg/*nn_nmlist*/, REG/*nn_class*/, 0/*nn_regno*/, 0/*nn_offset*/}, 0/*locnn_nloc*/ };
736 void funchead() {
737         register int pl;
738         register struct nmlist *cs;
739         register char *st;
740  static struct type t_double = {DOUBLE};
741  struct tdim dim;
742  int a;
743
744         pl = STARG;
745         while(paraml) {
746                 parame->nl_sparent = NULL;
747                 cs = paraml;
748                 paraml = &paraml->nl_sparent->P;
749                 if (cs->/*nl_type*/nl_dtype->t_id==FLOAT)
750                         cs->/*nl_type*/nl_dtype = /*DOUBLE*/&t_double;
751                 cs->nl_offset = pl;
752                 if (/*(cs->nl_type&XTYPE) == ARRAY*/cs->nl_dtype->t_id == (REF | ARRAY)) {
753 /*                      cs->nl_type -= (ARRAY-PTR);     *//* set ptr *//*
754                         cs->nl_subsp++;*/               /* pop dims */
755  struct rtype *rt = (struct rtype *)Dblock(sizeof(struct rtype));
756  rt->rt_id = REF | PTR;
757  rt->rt_reftype = ((struct rtype *)cs->nl_dtype)->rt_reftype;
758  cs->nl_dtype = (struct type *)rt;
759                 }
760                 pl += rlength(/*(struct node *)cs*/cs->nl_dtype);
761                 if (cs->nl_class==AREG && (hreg.nl_offset=goodreg(cs))>=0) {
762  /* make hreg = *cs but in the chosen register */
763  /*hreg.nl_type = cs->nl_type;
764  hreg.nl_subsp = cs->nl_subsp;
765  hreg.nl_strp = cs->nl_strp;*/
766  hreg.nl_dtype = cs->nl_dtype;
767                         st = starttree();
768  /* make areg look like result of nblock(&hreg) */
769  areg.locnn_nloc = hreg.nl_offset;
770  /*areg.locnn_op = NAME;
771  areg.locnn_type = hreg.nl_type;
772  areg.locnn_subsp = hreg.nl_subsp;
773  areg.nocnn_strp = hreg.nl_strp;*/
774  dim.rank = 0;
775  areg.locnn_type = XXXoldtype(cs->nl_dtype, &dim, (struct SS **)&areg.locnn_strp);
776  areg.locnn_subsp = dim.rank ? (int *)Tblock(dim.rank*sizeof(dim.rank)) : NULL;
777  for (a=0; a<dim.rank; a++)
778   areg.locnn_subsp[a] = dim.dimens[a];
779  /*areg.locnn_nmlist = &hreg;
780  areg.locnn_class = hreg.nl_class==0?STATIC:hreg.nl_class;
781  areg.locnn_regno = 0;
782  areg.locnn_offset = 0;*/
783                         *cp++ = (struct node *)&areg;
784  /* formerly rcexpr0() would have translated struct nmlist * to class, regno, */
785  /* offset, but now this happens in nblock, so we have to set class earlier */
786  cs->nl_class = AUTO;
787                         *cp++ = (struct node *)nblock(cs);
788  /*                     areg.locnn_type = cs->nl_type;
789                         areg.locnn_strp = cs->nl_strp;*/
790  /*                     cs->nl_class = AUTO;*/
791                         build(ASSIGN);
792                         rcexpr0(*--cp);
793                         cs->nl_offset = hreg.nl_offset;
794                         cs->nl_class = REG;
795                         endtree(st);
796                 } else
797                         cs->nl_class = AUTO;
798                 prste(cs);
799         }
800         for (pl=0; pl<HSHSIZ; pl++) {
801                 for (cs = hshtab[pl]; cs!=NULL; cs = cs->nl_nextnm) {
802                         if (cs->nl_class == ARG || cs->nl_class==AREG)
803                                 error0("Not an argument: %s", cs->nl_name);
804                 }
805         }
806         outcode("BN", SETREG, regvar);
807 }
808
809 void blockhead() {
810         register int r;
811
812         r = regvar;
813         blklev++;
814         declist(0);
815         if (r != regvar)
816                 outcode("BN", SETREG, regvar);
817 }
818
819 /*
820  * After the end of a block, delete local
821  * symbols;
822  * Also complain about undefined labels.
823  */
824 void blkend() {
825         register struct nmlist *cs, **lcs;
826         register int i;
827
828         blklev--;
829         for (i = 0; i < HSHSIZ; i++) {
830                 lcs = &hshtab[i];
831                 cs = *lcs;
832                 while (cs) {
833                         if (cs->nl_blklev > blklev
834                          && (((cs->nl_flag&FLABL)==0 && cs->nl_class!=EXTERN) || blklev<=0)) {
835                                 if (cs->nl_class==0)
836                                         error0("%s undefined", cs->nl_name);
837                                 if (cs->nl_class==EXTERN)
838                                         nameconflict(hshtab[i], cs);
839                                 *lcs = cs->nl_nextnm;
840                         } else
841                                 lcs = &cs->nl_nextnm;
842                         cs = cs->nl_nextnm;
843                 }
844         }
845 }
846
847 void nameconflict(ocs, cs) register struct nmlist *ocs; register struct nmlist *cs; {
848
849         for (; ocs!=NULL; ocs = ocs->nl_nextnm) 
850                 if (ocs!=cs && ocs->nl_class==EXTERN && 
851                     strncmp(cs->nl_name, ocs->nl_name, MAXCPS-1) == 0)
852                         error0("names %s and %s conflict", cs->nl_name, ocs->nl_name);
853 }
854
855 /*
856  * write out special definitions of local symbols for
857  * benefit of the debugger.  None of these are used
858  * by the assembler except to save them.
859  */
860 void prste(cs) struct nmlist *cs; {
861         register int nkind;
862
863         switch (cs->nl_class) {
864         case REG:
865                 nkind = RNAME;
866                 break;
867
868         case AUTO:
869                 nkind = ANAME;
870                 break;
871
872         case STATIC:
873                 nkind = SNAME;
874                 break;
875
876         default:
877                 return;
878
879         }
880         outcode("BSN", nkind, cs->nl_name, cs->nl_offset);
881 }
882
883 /*
884  * In case of error, skip to the next
885  * statement delimiter.
886  */
887 void errflush(ao) int ao; {
888         register int o;
889
890         o = ao;
891         while(o>RBRACE) {       /* ; { } */
892                 if (o==STRING)
893                         putstr(0, 0);
894                 o = symbol();
895         }
896         peeksym  = o;
897 }