Remove some unneeded semicolons across the tree.
[dragonfly.git] / usr.bin / xlint / lint1 / func.c
1 /*      $NetBSD: func.c,v 1.7 1995/10/02 17:31:40 jpo Exp $     */
2
3 /*
4  * Copyright (c) 1994, 1995 Jochen Pohl
5  * All Rights Reserved.
6  *
7  * Redistribution and use in source and binary forms, with or without
8  * modification, are permitted provided that the following conditions
9  * are met:
10  * 1. Redistributions of source code must retain the above copyright
11  *    notice, this list of conditions and the following disclaimer.
12  * 2. Redistributions in binary form must reproduce the above copyright
13  *    notice, this list of conditions and the following disclaimer in the
14  *    documentation and/or other materials provided with the distribution.
15  * 3. All advertising materials mentioning features or use of this software
16  *    must display the following acknowledgement:
17  *      This product includes software developed by Jochen Pohl for
18  *      The NetBSD Project.
19  * 4. The name of the author may not be used to endorse or promote products
20  *    derived from this software without specific prior written permission.
21  *
22  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
23  * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
24  * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
25  * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
26  * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
27  * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
28  * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
29  * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
30  * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
31  * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
32  */
33
34 #include <stdlib.h>
35 #include <string.h>
36
37 #include "lint1.h"
38 #include "y.tab.h"
39
40 /*
41  * Contains a pointer to the symbol table entry of the current function
42  * definition.
43  */
44 sym_t   *funcsym;
45
46 /* Is set as long as a statement can be reached. Must be set at level 0. */
47 int     reached = 1;
48
49 /*
50  * Is set as long as NOTREACHED is in effect.
51  * Is reset everywhere where reached can become 0.
52  */
53 int     rchflg;
54
55 /*
56  * In conjunction with reached ontrols printing of "fallthrough on ..."
57  * warnings.
58  * Reset by each statement and set by FALLTHROUGH, switch (switch1())
59  * and case (label()).
60  *
61  * Control statements if, for, while and switch do not reset ftflg because
62  * this must be done by the controled statement. At least for if this is
63  * important because ** FALLTHROUGH ** after "if (expr) stmnt" is evaluated
64  * befor the following token, wich causes reduction of above, is read.
65  * This means that ** FALLTHROUGH ** after "if ..." would always be ignored.
66  */
67 int     ftflg;
68
69 /* Top element of stack for control statements */
70 cstk_t  *cstk;
71
72 /*
73  * Number of arguments which will be checked for usage in following
74  * function definition. -1 stands for all arguments.
75  *
76  * The position of the last ARGSUSED comment is stored in aupos.
77  */
78 int     nargusg = -1;
79 pos_t   aupos;
80
81 /*
82  * Number of arguments of the following function definition whose types
83  * shall be checked by lint2. -1 stands for all arguments.
84  *
85  * The position of the last VARARGS comment is stored in vapos.
86  */
87 int     nvararg = -1;
88 pos_t   vapos;
89
90 /*
91  * Both prflstr and scflstrg contain the number of the argument which
92  * shall be used to check the types of remaining arguments (for PRINTFLIKE
93  * and SCANFLIKE).
94  *
95  * prflpos and scflpos are the positions of the last PRINTFLIKE or
96  * SCANFLIKE comment.
97  */
98 int     prflstrg = -1;
99 int     scflstrg = -1;
100 pos_t   prflpos;
101 pos_t   scflpos;
102
103 /*
104  * Are both plibflg and llibflg set, prototypes are writen as function
105  * definitions to the output file.
106  */
107 int     plibflg;
108
109 /*
110  * Nonzero means that no warnings about constands in conditional
111  * context are printed.
112  */
113 int     ccflg;
114
115 /*
116  * llibflg is set if a lint library shall be created. The effect of
117  * llibflg is that all defined symbols are treated as used.
118  * (The LINTLIBRARY comment also resets vflag.)
119  */
120 int     llibflg;
121
122 /*
123  * Nonzero if warnings are suppressed by a LINTED directive
124  */
125 int     nowarn;
126
127 /*
128  * Nonzero if complaints about use of "long long" are suppressed in
129  * the next statement or declaration.
130  */
131 int     quadflg;
132
133 /*
134  * Puts a new element at the top of the stack used for control statements.
135  */
136 void
137 pushctrl(int env)
138 {
139         cstk_t  *ci;
140
141         ci = xcalloc(1, sizeof (cstk_t));
142         ci->c_env = env;
143         ci->c_nxt = cstk;
144         cstk = ci;
145 }
146
147 /*
148  * Removes the top element of the stack used for control statements.
149  */
150 void
151 popctrl(int env)
152 {
153         cstk_t  *ci;
154         clst_t  *cl;
155
156         if (cstk == NULL || cstk->c_env != env)
157                 lerror("popctrl() 1");
158
159         cstk = (ci = cstk)->c_nxt;
160
161         while ((cl = ci->c_clst) != NULL) {
162                 ci->c_clst = cl->cl_nxt;
163                 free(cl);
164         }
165
166         if (ci->c_swtype != NULL)
167                 free(ci->c_swtype);
168
169         free(ci);
170 }
171
172 /*
173  * Prints a warning if a statement cannot be reached.
174  */
175 void
176 chkreach(void)
177 {
178         if (!reached && !rchflg) {
179                 /* statement not reached */
180                 warning(193);
181                 reached = 1;
182         }
183 }
184
185 /*
186  * Called after a function declaration which introduces a function definition
187  * and before an (optional) old style argument declaration list.
188  *
189  * Puts all symbols declared in the Prototype or in an old style argument
190  * list back to the symbol table.
191  *
192  * Does the usual checking of storage class, type (return value),
193  * redeclaration etc..
194  */
195 void
196 funcdef(sym_t *fsym)
197 {
198         int     n, warn;
199         sym_t   *arg, *sym, *rdsym;
200
201         funcsym = fsym;
202
203         /*
204          * Put all symbols declared in the argument list back to the
205          * symbol table.
206          */
207         for (sym = dcs->d_fpsyms; sym != NULL; sym = sym->s_dlnxt) {
208                 if (sym->s_blklev != -1) {
209                         if (sym->s_blklev != 1)
210                                 lerror("funcdef() 1");
211                         inssym(1, sym);
212                 }
213         }
214
215         /*
216          * In osfunc() we did not know whether it is an old style function
217          * definition or only an old style declaration, if there are no
218          * arguments inside the argument list ("f()").
219          */
220         if (!fsym->s_type->t_proto && fsym->s_args == NULL)
221                 fsym->s_osdef = 1;
222
223         chktyp(fsym);
224
225         /*
226          * chktyp() checks for almost all possible errors, but not for
227          * incomplete return values (these are allowed in declarations)
228          */
229         if (fsym->s_type->t_subt->t_tspec != VOID &&
230             incompl(fsym->s_type->t_subt)) {
231                 /* cannot return incomplete type */
232                 error(67);
233         }
234
235         fsym->s_def = DEF;
236
237         if (fsym->s_scl == TYPEDEF) {
238                 fsym->s_scl = EXTERN;
239                 /* illegal storage class */
240                 error(8);
241         }
242
243         if (dcs->d_inline)
244                 fsym->s_inline = 1;
245
246         /*
247          * Arguments in new style function declarations need a name.
248          * (void is already removed from the list of arguments)
249          */
250         n = 1;
251         for (arg = fsym->s_type->t_args; arg != NULL; arg = arg->s_nxt) {
252                 if (arg->s_scl == ABSTRACT) {
253                         if (arg->s_name != unnamed)
254                                 lerror("funcdef() 2");
255                         /* formal parameter lacks name: param #%d */
256                         error(59, n);
257                 } else {
258                         if (arg->s_name == unnamed)
259                                 lerror("funcdef() 3");
260                 }
261                 n++;
262         }
263
264         /*
265          * We must also remember the position. s_dpos is overwritten
266          * if this is an old style definition and we had already a
267          * prototype.
268          */
269         STRUCT_ASSIGN(dcs->d_fdpos, fsym->s_dpos);
270
271         if ((rdsym = dcs->d_rdcsym) != NULL) {
272
273                 if (!isredec(fsym, (warn = 0, &warn))) {
274
275                         /*
276                          * Print nothing if the newly defined function
277                          * is defined in old style. A better warning will
278                          * be printed in cluparg().
279                          */
280                         if (warn && !fsym->s_osdef) {
281                                 /* redeclaration of %s */
282                                 (*(sflag ? error : warning))(27, fsym->s_name);
283                                 prevdecl(-1, rdsym);
284                         }
285
286                         /* copy usage information */
287                         cpuinfo(fsym, rdsym);
288
289                         /*
290                          * If the old symbol was a prototype and the new
291                          * one is none, overtake the position of the
292                          * declaration of the prototype.
293                          */
294                         if (fsym->s_osdef && rdsym->s_type->t_proto)
295                                 STRUCT_ASSIGN(fsym->s_dpos, rdsym->s_dpos);
296
297                         /* complete the type */
298                         compltyp(fsym, rdsym);
299
300                         /* once a function is inline it remains inline */
301                         if (rdsym->s_inline)
302                                 fsym->s_inline = 1;
303
304                 }
305
306                 /* remove the old symbol from the symbol table */
307                 rmsym(rdsym);
308
309         }
310
311         if (fsym->s_osdef && !fsym->s_type->t_proto) {
312                 if (sflag && hflag && strcmp(fsym->s_name, "main") != 0)
313                         /* function definition is not a prototyp */
314                         warning(286);
315         }
316
317         if (dcs->d_notyp)
318                 /* return value is implizitly declared to be int */
319                 fsym->s_rimpl = 1;
320
321         reached = 1;
322 }
323
324 /*
325  * Called at the end of a function definition.
326  */
327 void
328 funcend(void)
329 {
330         sym_t   *arg;
331         int     n;
332
333         if (reached) {
334                 cstk->c_noretval = 1;
335                 if (funcsym->s_type->t_subt->t_tspec != VOID &&
336                     !funcsym->s_rimpl) {
337                         /* func. %s falls off bottom without returning value */
338                         warning(217, funcsym->s_name);
339                 }
340         }
341
342         /*
343          * This warning is printed only if the return value was implizitly
344          * declared to be int. Otherwise the wrong return statement
345          * has already printed a warning.
346          */
347         if (cstk->c_noretval && cstk->c_retval && funcsym->s_rimpl)
348                 /* function %s has return (e); and return; */
349                 warning(216, funcsym->s_name);
350
351         /* Print warnings for unused arguments */
352         arg = dcs->d_fargs;
353         n = 0;
354         while (arg != NULL && (nargusg == -1 || n < nargusg)) {
355                 chkusg1(dcs->d_asm, arg);
356                 arg = arg->s_nxt;
357                 n++;
358         }
359         nargusg = -1;
360
361         /*
362          * write the information about the function definition to the
363          * output file
364          * inline functions explicitely declared extern are written as
365          * declarations only.
366          */
367         if (dcs->d_scl == EXTERN && funcsym->s_inline) {
368                 outsym(funcsym, funcsym->s_scl, DECL);
369         } else {
370                 outfdef(funcsym, &dcs->d_fdpos, cstk->c_retval,
371                         funcsym->s_osdef, dcs->d_fargs);
372         }
373
374         /*
375          * remove all symbols declared during argument declaration from
376          * the symbol table
377          */
378         if (dcs->d_nxt != NULL || dcs->d_ctx != EXTERN)
379                 lerror("funcend() 1");
380         rmsyms(dcs->d_fpsyms);
381
382         /* must be set on level 0 */
383         reached = 1;
384 }
385
386 /*
387  * Process a label.
388  *
389  * typ          type of the label (T_NAME, T_DEFAULT or T_CASE).
390  * sym          symbol table entry of label if typ == T_NAME
391  * tn           expression if typ == T_CASE
392  */
393 void
394 label(int typ, sym_t *sym, tnode_t *tn)
395 {
396         cstk_t  *ci;
397         clst_t  *cl;
398         val_t   *v, *nv;
399         tspec_t t;
400
401         switch (typ) {
402
403         case T_NAME:
404                 if (sym->s_set) {
405                         /* label %s redefined */
406                         error(194, sym->s_name);
407                 } else {
408                         setsflg(sym);
409                 }
410                 break;
411
412         case T_CASE:
413
414                 /* find the stack entry for the innermost switch statement */
415                 for (ci = cstk; ci != NULL && !ci->c_switch; ci = ci->c_nxt) ;
416
417                 if (ci == NULL) {
418                         /* case not in switch */
419                         error(195);
420                         tn = NULL;
421                 } else if (tn != NULL && tn->tn_op != CON) {
422                         /* non-constant case expression */
423                         error(197);
424                         tn = NULL;
425                 } else if (tn != NULL && !isityp(tn->tn_type->t_tspec)) {
426                         /* non-integral case expression */
427                         error(198);
428                         tn = NULL;
429                 }
430
431                 if (tn != NULL) {
432
433                         if (ci->c_swtype == NULL)
434                                 lerror("label() 1");
435
436                         if (reached && !ftflg) {
437                                 if (hflag)
438                                         /* fallthrough on case statement */
439                                         warning(220);
440                         }
441
442                         t = tn->tn_type->t_tspec;
443                         if (t == LONG || t == ULONG ||
444                             t == QUAD || t == UQUAD) {
445                                 if (tflag)
446                                         /* case label must be of type ... */
447                                         warning(203);
448                         }
449
450                         /*
451                          * get the value of the expression and convert it
452                          * to the type of the switch expression
453                          */
454                         v = constant(tn);
455                         nv = xcalloc(1, sizeof (val_t));
456                         cvtcon(CASE, 0, ci->c_swtype, nv, v);
457                         free(v);
458
459                         /* look if we had this value already */
460                         for (cl = ci->c_clst; cl != NULL; cl = cl->cl_nxt) {
461                                 if (cl->cl_val.v_quad == nv->v_quad)
462                                         break;
463                         }
464                         if (cl != NULL && isutyp(nv->v_tspec)) {
465                                 /* duplicate case in switch, %lu */
466                                 error(200, (u_long)nv->v_quad);
467                         } else if (cl != NULL) {
468                                 /* duplicate case in switch, %ld */
469                                 error(199, (long)nv->v_quad);
470                         } else {
471                                 /*
472                                  * append the value to the list of
473                                  * case values
474                                  */
475                                 cl = xcalloc(1, sizeof (clst_t));
476                                 STRUCT_ASSIGN(cl->cl_val, *nv);
477                                 cl->cl_nxt = ci->c_clst;
478                                 ci->c_clst = cl;
479                         }
480                 }
481                 tfreeblk();
482                 break;
483
484         case T_DEFAULT:
485
486                 /* find the stack entry for the innermost switch statement */
487                 for (ci = cstk; ci != NULL && !ci->c_switch; ci = ci->c_nxt) ;
488
489                 if (ci == NULL) {
490                         /* default outside switch */
491                         error(201);
492                 } else if (ci->c_default) {
493                         /* duplicate default in switch */
494                         error(202);
495                 } else {
496                         if (reached && !ftflg) {
497                                 if (hflag)
498                                         /* fallthrough on default statement */
499                                         warning(284);
500                         }
501                         ci->c_default = 1;
502                 }
503                 break;
504         }
505         reached = 1;
506 }
507
508 /*
509  * T_IF T_LPARN expr T_RPARN
510  */
511 void
512 if1(tnode_t *tn)
513 {
514         if (tn != NULL)
515                 tn = cconv(tn);
516         if (tn != NULL)
517                 tn = promote(NOOP, 0, tn);
518         expr(tn, 0, 1);
519         pushctrl(T_IF);
520 }
521
522 /*
523  * if_without_else
524  * if_without_else T_ELSE
525  */
526 void
527 if2(void)
528 {
529         cstk->c_rchif = reached ? 1 : 0;
530         reached = 1;
531 }
532
533 /*
534  * if_without_else
535  * if_without_else T_ELSE stmnt
536  */
537 void
538 if3(int els)
539 {
540         if (els) {
541                 reached |= cstk->c_rchif;
542         } else {
543                 reached = 1;
544         }
545         popctrl(T_IF);
546 }
547
548 /*
549  * T_SWITCH T_LPARN expr T_RPARN
550  */
551 void
552 switch1(tnode_t *tn)
553 {
554         tspec_t t;
555         type_t  *tp;
556
557         if (tn != NULL)
558                 tn = cconv(tn);
559         if (tn != NULL)
560                 tn = promote(NOOP, 0, tn);
561         if (tn != NULL && !isityp(tn->tn_type->t_tspec)) {
562                 /* switch expression must have integral type */
563                 error(205);
564                 tn = NULL;
565         }
566         if (tn != NULL && tflag) {
567                 t = tn->tn_type->t_tspec;
568                 if (t == LONG || t == ULONG || t == QUAD || t == UQUAD) {
569                         /* switch expr. must be of type `int' in trad. C */
570                         warning(271);
571                 }
572         }
573
574         /*
575          * Remember the type of the expression. Because its possible
576          * that (*tp) is allocated on tree memory the type must be
577          * duplicated. This is not too complicated because it is
578          * only an integer type.
579          */
580         tp = xcalloc(1, sizeof (type_t));
581         if (tn != NULL) {
582                 tp->t_tspec = tn->tn_type->t_tspec;
583                 if ((tp->t_isenum = tn->tn_type->t_isenum) != 0)
584                         tp->t_enum = tn->tn_type->t_enum;
585         } else {
586                 tp->t_tspec = INT;
587         }
588
589         expr(tn, 1, 0);
590
591         pushctrl(T_SWITCH);
592         cstk->c_switch = 1;
593         cstk->c_swtype = tp;
594
595         reached = rchflg = 0;
596         ftflg = 1;
597 }
598
599 /*
600  * switch_expr stmnt
601  */
602 void
603 switch2(void)
604 {
605         int     nenum, nclab;
606         sym_t   *esym;
607         clst_t  *cl;
608
609         if (cstk->c_swtype == NULL)
610                 lerror("switch2() 1");
611
612         /*
613          * If the switch expression was of type enumeration, count the case
614          * labels and the number of enumerators. If both counts are not
615          * equal print a warning.
616          */
617         if (cstk->c_swtype->t_isenum) {
618                 nenum = nclab = 0;
619                 if (cstk->c_swtype->t_enum == NULL)
620                         lerror("switch2() 2");
621                 for (esym = cstk->c_swtype->t_enum->elem;
622                      esym != NULL; esym = esym->s_nxt) {
623                         nenum++;
624                 }
625                 for (cl = cstk->c_clst; cl != NULL; cl = cl->cl_nxt)
626                         nclab++;
627                 if (hflag && eflag && nenum != nclab && !cstk->c_default) {
628                         /* enumeration value(s) not handled in switch */
629                         warning(206);
630                 }
631         }
632
633         if (cstk->c_break) {
634                 /*
635                  * end of switch alway reached (c_break is only set if the
636                  * break statement can be reached).
637                  */
638                 reached = 1;
639         } else if (!cstk->c_default &&
640                    (!hflag || !cstk->c_swtype->t_isenum || nenum != nclab)) {
641                 /*
642                  * there are possible values which are not handled in
643                  * switch
644                  */
645                 reached = 1;
646         }       /*
647                  * otherwise the end of the switch expression is reached
648                  * if the end of the last statement inside it is reached.
649                  */
650
651         popctrl(T_SWITCH);
652 }
653
654 /*
655  * T_WHILE T_LPARN expr T_RPARN
656  */
657 void
658 while1(tnode_t *tn)
659 {
660         if (!reached) {
661                 /* loop not entered at top */
662                 warning(207);
663                 reached = 1;
664         }
665
666         if (tn != NULL)
667                 tn = cconv(tn);
668         if (tn != NULL)
669                 tn = promote(NOOP, 0, tn);
670         if (tn != NULL && !issclt(tn->tn_type->t_tspec)) {
671                 /* controlling expressions must have scalar type */
672                 error(204);
673                 tn = NULL;
674         }
675
676         pushctrl(T_WHILE);
677         cstk->c_loop = 1;
678         if (tn != NULL && tn->tn_op == CON) {
679                 if (isityp(tn->tn_type->t_tspec)) {
680                         cstk->c_infinite = tn->tn_val->v_quad != 0;
681                 } else {
682                         cstk->c_infinite = tn->tn_val->v_ldbl != 0.0;
683                 }
684         }
685
686         expr(tn, 0, 1);
687 }
688
689 /*
690  * while_expr stmnt
691  * while_expr error
692  */
693 void
694 while2(void)
695 {
696         /*
697          * The end of the loop can be reached if it is no endless loop
698          * or there was a break statement which was reached.
699          */
700         reached = !cstk->c_infinite || cstk->c_break;
701         rchflg = 0;
702
703         popctrl(T_WHILE);
704 }
705
706 /*
707  * T_DO
708  */
709 void
710 do1(void)
711 {
712         if (!reached) {
713                 /* loop not entered at top */
714                 warning(207);
715                 reached = 1;
716         }
717
718         pushctrl(T_DO);
719         cstk->c_loop = 1;
720 }
721
722 /*
723  * do stmnt do_while_expr
724  * do error
725  */
726 void
727 do2(tnode_t *tn)
728 {
729         /*
730          * If there was a continue statement the expression controlling the
731          * loop is reached.
732          */
733         if (cstk->c_cont)
734                 reached = 1;
735
736         if (tn != NULL)
737                 tn = cconv(tn);
738         if (tn != NULL)
739                 tn = promote(NOOP, 0, tn);
740         if (tn != NULL && !issclt(tn->tn_type->t_tspec)) {
741                 /* controlling expressions must have scalar type */
742                 error(204);
743                 tn = NULL;
744         }
745
746         if (tn != NULL && tn->tn_op == CON) {
747                 if (isityp(tn->tn_type->t_tspec)) {
748                         cstk->c_infinite = tn->tn_val->v_quad != 0;
749                 } else {
750                         cstk->c_infinite = tn->tn_val->v_ldbl != 0.0;
751                 }
752         }
753
754         expr(tn, 0, 1);
755
756         /*
757          * The end of the loop is only reached if it is no endless loop
758          * or there was a break statement which could be reached.
759          */
760         reached = !cstk->c_infinite || cstk->c_break;
761         rchflg = 0;
762
763         popctrl(T_DO);
764 }
765
766 /*
767  * T_FOR T_LPARN opt_expr T_SEMI opt_expr T_SEMI opt_expr T_RPARN
768  */
769 void
770 for1(tnode_t *tn1, tnode_t *tn2, tnode_t *tn3)
771 {
772         /*
773          * If there is no initialisation expression it is possible that
774          * it is intended not to enter the loop at top.
775          */
776         if (tn1 != NULL && !reached) {
777                 /* loop not entered at top */
778                 warning(207);
779                 reached = 1;
780         }
781
782         pushctrl(T_FOR);
783         cstk->c_loop = 1;
784
785         /*
786          * Store the tree memory for the reinitialisation expression.
787          * Also remember this expression itself. We must check it at
788          * the end of the loop to get "used but not set" warnings correct.
789          */
790         cstk->c_fexprm = tsave();
791         cstk->c_f3expr = tn3;
792         STRUCT_ASSIGN(cstk->c_fpos, curr_pos);
793         STRUCT_ASSIGN(cstk->c_cfpos, csrc_pos);
794
795         if (tn1 != NULL)
796                 expr(tn1, 0, 0);
797
798         if (tn2 != NULL)
799                 tn2 = cconv(tn2);
800         if (tn2 != NULL)
801                 tn2 = promote(NOOP, 0, tn2);
802         if (tn2 != NULL && !issclt(tn2->tn_type->t_tspec)) {
803                 /* controlling expressions must have scalar type */
804                 error(204);
805                 tn2 = NULL;
806         }
807         if (tn2 != NULL)
808                 expr(tn2, 0, 1);
809
810         if (tn2 == NULL) {
811                 cstk->c_infinite = 1;
812         } else if (tn2->tn_op == CON) {
813                 if (isityp(tn2->tn_type->t_tspec)) {
814                         cstk->c_infinite = tn2->tn_val->v_quad != 0;
815                 } else {
816                         cstk->c_infinite = tn2->tn_val->v_ldbl != 0.0;
817                 }
818         }
819
820         /* Checking the reinitialisation expression is done in for2() */
821
822         reached = 1;
823 }
824
825 /*
826  * for_exprs stmnt
827  * for_exprs error
828  */
829 void
830 for2(void)
831 {
832         pos_t   cpos, cspos;
833         tnode_t *tn3;
834
835         if (cstk->c_cont)
836                 reached = 1;
837
838         STRUCT_ASSIGN(cpos, curr_pos);
839         STRUCT_ASSIGN(cspos, csrc_pos);
840
841         /* Restore the tree memory for the reinitialisation expression */
842         trestor(cstk->c_fexprm);
843         tn3 = cstk->c_f3expr;
844         STRUCT_ASSIGN(curr_pos, cstk->c_fpos);
845         STRUCT_ASSIGN(csrc_pos, cstk->c_cfpos);
846
847         /* simply "statement not reached" would be confusing */
848         if (!reached && !rchflg) {
849                 /* end-of-loop code not reached */
850                 warning(223);
851                 reached = 1;
852         }
853
854         if (tn3 != NULL) {
855                 expr(tn3, 0, 0);
856         } else {
857                 tfreeblk();
858         }
859
860         STRUCT_ASSIGN(curr_pos, cpos);
861         STRUCT_ASSIGN(csrc_pos, cspos);
862
863         /* An endless loop without break will never terminate */
864         reached = cstk->c_break || !cstk->c_infinite;
865         rchflg = 0;
866
867         popctrl(T_FOR);
868 }
869
870 /*
871  * T_GOTO identifier T_SEMI
872  * T_GOTO error T_SEMI
873  */
874 void
875 dogoto(sym_t *lab)
876 {
877         setuflg(lab, 0, 0);
878
879         chkreach();
880
881         reached = rchflg = 0;
882 }
883
884 /*
885  * T_BREAK T_SEMI
886  */
887 void
888 dobreak(void)
889 {
890         cstk_t  *ci;
891
892         ci = cstk;
893         while (ci != NULL && !ci->c_loop && !ci->c_switch)
894                 ci = ci->c_nxt;
895
896         if (ci == NULL) {
897                 /* break outside loop or switch */
898                 error(208);
899         } else {
900                 if (reached)
901                         ci->c_break = 1;
902         }
903
904         if (bflag)
905                 chkreach();
906
907         reached = rchflg = 0;
908 }
909
910 /*
911  * T_CONTINUE T_SEMI
912  */
913 void
914 docont(void)
915 {
916         cstk_t  *ci;
917
918         for (ci = cstk; ci != NULL && !ci->c_loop; ci = ci->c_nxt) ;
919
920         if (ci == NULL) {
921                 /* continue outside loop */
922                 error(209);
923         } else {
924                 ci->c_cont = 1;
925         }
926
927         chkreach();
928
929         reached = rchflg = 0;
930 }
931
932 /*
933  * T_RETURN T_SEMI
934  * T_RETURN expr T_SEMI
935  */
936 void
937 doreturn(tnode_t *tn)
938 {
939         tnode_t *ln, *rn;
940         cstk_t  *ci;
941         op_t    op;
942
943         for (ci = cstk; ci->c_nxt != NULL; ci = ci->c_nxt) ;
944
945         if (tn != NULL) {
946                 ci->c_retval = 1;
947         } else {
948                 ci->c_noretval = 1;
949         }
950
951         if (tn != NULL && funcsym->s_type->t_subt->t_tspec == VOID) {
952                 /* void function %s cannot return value */
953                 error(213, funcsym->s_name);
954                 tfreeblk();
955                 tn = NULL;
956         } else if (tn == NULL && funcsym->s_type->t_subt->t_tspec != VOID) {
957                 /*
958                  * Assume that the function has a return value only if it
959                  * is explicitly declared.
960                  */
961                 if (!funcsym->s_rimpl)
962                         /* function %s expects to return value */
963                         warning(214, funcsym->s_name);
964         }
965
966         if (tn != NULL) {
967
968                 /* Create a temporary node for the left side */
969                 ln = tgetblk(sizeof (tnode_t));
970                 ln->tn_op = NAME;
971                 ln->tn_type = tduptyp(funcsym->s_type->t_subt);
972                 ln->tn_type->t_const = 0;
973                 ln->tn_lvalue = 1;
974                 ln->tn_sym = funcsym;           /* better than nothing */
975
976                 tn = build(RETURN, ln, tn);
977
978                 if (tn != NULL) {
979                         rn = tn->tn_right;
980                         while ((op = rn->tn_op) == CVT || op == PLUS)
981                                 rn = rn->tn_left;
982                         if (rn->tn_op == AMPER && rn->tn_left->tn_op == NAME &&
983                             rn->tn_left->tn_sym->s_scl == AUTO) {
984                                 /* %s returns pointer to automatic object */
985                                 warning(302, funcsym->s_name);
986                         }
987                 }
988
989                 expr(tn, 1, 0);
990
991         } else {
992
993                 chkreach();
994
995         }
996
997         reached = rchflg = 0;
998 }
999
1000 /*
1001  * Do some cleanup after a global declaration or definition.
1002  * Especially remove informations about unused lint comments.
1003  */
1004 void
1005 glclup(int silent)
1006 {
1007         pos_t   cpos;
1008
1009         STRUCT_ASSIGN(cpos, curr_pos);
1010
1011         if (nargusg != -1) {
1012                 if (!silent) {
1013                         STRUCT_ASSIGN(curr_pos, aupos);
1014                         /* must precede function definition: %s */
1015                         warning(282, "ARGSUSED");
1016                 }
1017                 nargusg = -1;
1018         }
1019         if (nvararg != -1) {
1020                 if (!silent) {
1021                         STRUCT_ASSIGN(curr_pos, vapos);
1022                         /* must precede function definition: %s */
1023                         warning(282, "VARARGS");
1024                 }
1025                 nvararg = -1;
1026         }
1027         if (prflstrg != -1) {
1028                 if (!silent) {
1029                         STRUCT_ASSIGN(curr_pos, prflpos);
1030                         /* must precede function definition: %s */
1031                         warning(282, "PRINTFLIKE");
1032                 }
1033                 prflstrg = -1;
1034         }
1035         if (scflstrg != -1) {
1036                 if (!silent) {
1037                         STRUCT_ASSIGN(curr_pos, scflpos);
1038                         /* must precede function definition: %s */
1039                         warning(282, "SCANFLIKE");
1040                 }
1041                 scflstrg = -1;
1042         }
1043
1044         STRUCT_ASSIGN(curr_pos, cpos);
1045
1046         dcs->d_asm = 0;
1047 }
1048
1049 /*
1050  * ARGSUSED comment
1051  *
1052  * Only the first n arguments of the following function are checked
1053  * for usage. A missing argument is taken to be 0.
1054  */
1055 void
1056 argsused(int n)
1057 {
1058         if (n == -1)
1059                 n = 0;
1060
1061         if (dcs->d_ctx != EXTERN) {
1062                 /* must be outside function: ** %s ** */
1063                 warning(280, "ARGSUSED");
1064                 return;
1065         }
1066         if (nargusg != -1) {
1067                 /* duplicate use of ** %s ** */
1068                 warning(281, "ARGSUSED");
1069         }
1070         nargusg = n;
1071         STRUCT_ASSIGN(aupos, curr_pos);
1072 }
1073
1074 /*
1075  * VARARGS comment
1076  *
1077  * Makes that lint2 checks only the first n arguments for compatibility
1078  * to the function definition. A missing argument is taken to be 0.
1079  */
1080 void
1081 varargs(int n)
1082 {
1083         if (n == -1)
1084                 n = 0;
1085
1086         if (dcs->d_ctx != EXTERN) {
1087                 /* must be outside function: ** %s ** */
1088                 warning(280, "VARARGS");
1089                 return;
1090         }
1091         if (nvararg != -1) {
1092                 /* duplicate use of  ** %s ** */
1093                 warning(281, "VARARGS");
1094         }
1095         nvararg = n;
1096         STRUCT_ASSIGN(vapos, curr_pos);
1097 }
1098
1099 /*
1100  * PRINTFLIKE comment
1101  *
1102  * Check all arguments until the (n-1)-th as usual. The n-th argument is
1103  * used the check the types of remaining arguments.
1104  */
1105 void
1106 printflike(int n)
1107 {
1108         if (n == -1)
1109                 n = 0;
1110
1111         if (dcs->d_ctx != EXTERN) {
1112                 /* must be outside function: ** %s ** */
1113                 warning(280, "PRINTFLIKE");
1114                 return;
1115         }
1116         if (prflstrg != -1) {
1117                 /* duplicate use of ** %s ** */
1118                 warning(281, "PRINTFLIKE");
1119         }
1120         prflstrg = n;
1121         STRUCT_ASSIGN(prflpos, curr_pos);
1122 }
1123
1124 /*
1125  * SCANFLIKE comment
1126  *
1127  * Check all arguments until the (n-1)-th as usual. The n-th argument is
1128  * used the check the types of remaining arguments.
1129  */
1130 void
1131 scanflike(int n)
1132 {
1133         if (n == -1)
1134                 n = 0;
1135
1136         if (dcs->d_ctx != EXTERN) {
1137                 /* must be outside function: ** %s ** */
1138                 warning(280, "SCANFLIKE");
1139                 return;
1140         }
1141         if (scflstrg != -1) {
1142                 /* duplicate use of ** %s ** */
1143                 warning(281, "SCANFLIKE");
1144         }
1145         scflstrg = n;
1146         STRUCT_ASSIGN(scflpos, curr_pos);
1147 }
1148
1149 /*
1150  * Set the linenumber for a CONSTCOND comment. At this and the following
1151  * line no warnings about constants in conditional contexts are printed.
1152  */
1153 /* ARGSUSED */
1154 void
1155 constcond(int n)
1156 {
1157         ccflg = 1;
1158 }
1159
1160 /*
1161  * Suppress printing of "fallthrough on ..." warnings until next
1162  * statement.
1163  */
1164 /* ARGSUSED */
1165 void
1166 fallthru(int n)
1167 {
1168         ftflg = 1;
1169 }
1170
1171 /*
1172  * Stop warnings about statements which cannot be reached. Also tells lint
1173  * that the following statements cannot be reached (e.g. after exit()).
1174  */
1175 /* ARGSUSED */
1176 void
1177 notreach(int n)
1178 {
1179         reached = 0;
1180         rchflg = 1;
1181 }
1182
1183 /* ARGSUSED */
1184 void
1185 lintlib(int n)
1186 {
1187         if (dcs->d_ctx != EXTERN) {
1188                 /* must be outside function: ** %s ** */
1189                 warning(280, "LINTLIBRARY");
1190                 return;
1191         }
1192         llibflg = 1;
1193         vflag = 0;
1194 }
1195
1196 /*
1197  * Suppress most warnings at the current and the following line.
1198  */
1199 /* ARGSUSED */
1200 void
1201 linted(int n)
1202 {
1203         nowarn = 1;
1204 }
1205
1206 /*
1207  * PROTOTLIB in conjunction with LINTLIBRARY can be used to handle
1208  * prototypes like function definitions. This is done if the argument
1209  * to PROTOLIB is nonzero. Otherwise prototypes are handled normaly.
1210  */
1211 void
1212 protolib(int n)
1213 {
1214         if (dcs->d_ctx != EXTERN) {
1215                 /* must be outside function: ** %s ** */
1216                 warning(280, "PROTOLIB");
1217                 return;
1218         }
1219         plibflg = n == 0 ? 0 : 1;
1220 }
1221
1222 /*
1223  * Set quadflg to nonzero which means that the next statement/declaration
1224  * may use "long long" without an error or warning.
1225  */
1226 /* ARGSUSED */
1227 void
1228 longlong(int n)
1229 {
1230         quadflg = 1;
1231 }