]> andersk Git - splint.git/blob - src/exprNode.c
Making changes to try to support loops.
[splint.git] / src / exprNode.c
1 /*
2 ** LCLint - annotation-assisted static program checker
3 ** Copyright (C) 1994-2000 University of Virginia,
4 **         Massachusetts Institute of Technology
5 **
6 ** This program is free software; you can redistribute it and/or modify it
7 ** under the terms of the GNU General Public License as published by the
8 ** Free Software Foundation; either version 2 of the License, or (at your
9 ** option) any later version.
10 ** 
11 ** This program is distributed in the hope that it will be useful, but
12 ** WITHOUT ANY WARRANTY; without even the implied warranty of
13 ** MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
14 ** General Public License for more details.
15 ** 
16 ** The GNU General Public License is available from http://www.gnu.org/ or
17 ** the Free Software Foundation, Inc., 59 Temple Place - Suite 330, Boston,
18 ** MA 02111-1307, USA.
19 **
20 ** For information on lclint: lclint-request@cs.virginia.edu
21 ** To report a bug: lclint-bug@cs.virginia.edu
22 ** For more information: http://lclint.cs.virginia.edu
23 */
24 /*
25 ** exprNode.c
26 */
27
28 # include <ctype.h> /* for isdigit */
29 # include "lclintMacros.nf"
30 # include "basic.h"
31 # include "cgrammar.h"
32 # include "cgrammar_tokens.h"
33
34 # include "exprChecks.h"
35 # include "aliasChecks.h"
36 # include "exprNodeSList.h"
37 # include "exprData.i"
38
39 static bool exprNode_isEmptyStatement (exprNode p_e);
40 static /*@exposed@*/ exprNode exprNode_firstStatement (/*@returned@*/ exprNode p_e);
41 static bool exprNode_isFalseConstant (exprNode p_e) /*@*/ ;
42 static bool exprNode_isBlock (exprNode p_e);
43 static void checkGlobUse (uentry p_glob, bool p_isCall, /*@notnull@*/ exprNode p_e);
44 static void exprNode_addUse (exprNode p_e, sRef p_s);
45 static bool exprNode_matchArgType (ctype p_ct, exprNode p_e);
46  exprNode exprNode_fakeCopy (exprNode p_e) /*@*/ ;
47 static exprNode exprNode_statementError (/*@only@*/ exprNode p_e, /*@only@*/ lltok p_t);
48 static bool exprNode_matchTypes (exprNode p_e1, exprNode p_e2);
49 static void checkUniqueParams (exprNode p_fcn,
50                                /*@notnull@*/ exprNode p_current, exprNodeList p_args, 
51                                int p_paramno, uentry p_ucurrent);
52 static void updateAliases (/*@notnull@*/ exprNode p_e1, /*@notnull@*/ exprNode p_e2);
53 static void abstractOpError (ctype p_tr1, ctype p_tr2, lltok p_op, 
54                              /*@notnull@*/ exprNode p_e1, /*@notnull@*/ exprNode p_e2, 
55                              fileloc p_loc1, fileloc p_loc2);
56 static ctype checkNumerics (ctype p_tr1, ctype p_tr2, ctype p_te1, ctype p_te2,
57                             /*@notnull@*/ exprNode p_e1, /*@notnull@*/ exprNode p_e2, lltok p_op);
58 static void doAssign (/*@notnull@*/ exprNode p_e1, /*@notnull@*/ exprNode p_e2, bool p_isInit);
59 static void checkSafeUse (exprNode p_e, sRef p_s);
60 static void reflectNullTest (/*@notnull@*/ exprNode p_e, bool p_isnull);
61 static void checkMacroParen (exprNode p_e);
62 static exprNodeSList exprNode_flatten (/*@dependent@*/ exprNode p_e);
63 static void exprNode_checkSetAny (exprNode p_e, /*@dependent@*/ cstring p_name);
64 static void exprNode_checkUse (exprNode p_e, sRef p_s, fileloc p_loc);
65 static void exprNode_mergeUSs (exprNode p_res, exprNode p_other);
66 static void exprNode_mergeCondUSs (exprNode p_res, exprNode p_other1, exprNode p_other2);
67 static /*@only@*/ /*@notnull@*/ exprNode exprNode_fromIdentifierAux (/*@observer@*/ uentry p_c);
68 static void checkAnyCall (/*@notnull@*/ /*@dependent@*/ exprNode p_fcn, 
69                           /*@dependent@*/ cstring p_fname,
70                           uentryList p_pn, exprNodeList p_args, 
71                           bool p_hasMods, sRefSet p_mods, bool p_isSpec,
72                           int p_specialArgs);
73 static void checkOneArg (uentry p_ucurrent, /*@notnull@*/ exprNode p_current, 
74                          /*@dependent@*/ exprNode p_fcn, bool p_isSpec, int p_argno, int p_totargs);
75 static void 
76   checkUnspecCall (/*@notnull@*/ /*@dependent@*/ exprNode p_fcn, uentryList p_params, exprNodeList p_args);
77
78 static /*@only@*/ exprNode exprNode_effect (exprNode p_e)
79   /*@globals internalState@*/ ;
80 static /*@only@*/ cstring exprNode_doUnparse (exprNode p_e);
81 static /*@observer@*/ cstring exprNode_rootVarName (exprNode p_e);
82 static /*@exposed@*/ exprNode 
83   exprNode_lastStatement (/*@returned@*/ exprNode p_e);
84
85 static /*@null@*/ sRef defref = sRef_undefined;
86 static /*@only@*/ exprNode mustExitNode = exprNode_undefined;
87
88 static int checkArgsReal (uentry p_fcn, /*@dependent@*/ exprNode p_f, 
89                           uentryList p_cl, 
90                           exprNodeList p_args, bool p_isIter, exprNode p_ret);
91
92 static bool inEffect = FALSE;
93 static int nowalloc = 0;
94 static int totalloc = 0;
95 static int maxalloc = 0;
96
97 static /*@only@*/ uentry regArg;
98 static /*@only@*/ uentry outArg;
99 static /*@only@*/ uentry outStringArg;
100 static /*@exposed@*/ sRef stdinRef;
101 static /*@exposed@*/ sRef stdoutRef;
102 static /*@only@*/ uentry csArg;
103 static /*@only@*/ uentry csOnlyArg; 
104 static ctype cstringType;
105 static ctype ctypeType;
106 static ctype filelocType; 
107 static bool initMod = FALSE;
108
109 /*
110 ** must occur after library has been read
111 */
112
113 void exprNode_initMod (void)
114   /*@globals undef regArg, undef outArg, undef outStringArg, 
115              undef csOnlyArg, undef csArg; 
116    @*/
117 {
118   uentry ue;
119   idDecl tmp;
120   
121   initMod = TRUE;
122   cstringType = ctype_unknown;
123   ctypeType = ctype_unknown;
124   filelocType = ctype_unknown;
125
126   defref = sRef_undefined;
127   
128   if (usymtab_existsType (cstring_makeLiteralTemp ("cstring")))
129     {
130       cstringType = usymtab_lookupAbstractType (cstring_makeLiteralTemp ("cstring"));
131     }
132  
133   if (usymtab_existsType (cstring_makeLiteralTemp ("ctype")))
134     {
135       ctypeType = usymtab_lookupAbstractType (cstring_makeLiteralTemp ("ctype"));
136     }
137
138   if (usymtab_existsType (cstring_makeLiteralTemp ("fileloc")))
139     {
140       filelocType = usymtab_lookupAbstractType (cstring_makeLiteralTemp ("fileloc"));
141     }
142
143   if (usymtab_existsGlob (cstring_makeLiteralTemp ("stdin")))
144     {
145       ue = usymtab_lookupGlob (cstring_makeLiteralTemp ("stdin"));
146     }
147   else /* define stdin */
148     {
149       ue = uentry_makeVariable (cstring_makeLiteralTemp ("stdin"), 
150                                 ctype_unknown, 
151                                 fileloc_getBuiltin (), 
152                                 FALSE);
153       uentry_setHasNameError (ue); 
154       ue = usymtab_supGlobalEntryReturn (ue);
155     }
156
157   stdinRef = sRef_makePointer (uentry_getSref (ue));
158   
159   if (usymtab_existsGlob (cstring_makeLiteralTemp ("stdout")))
160     {
161       ue = usymtab_lookupGlob (cstring_makeLiteralTemp ("stdout"));
162     }
163   else
164     {
165       ue = uentry_makeVariable (cstring_makeLiteralTemp ("stdout"), 
166                                 ctype_unknown, 
167                                 fileloc_getBuiltin (), 
168                                 FALSE);
169       uentry_setHasNameError (ue); 
170       ue = usymtab_supGlobalEntryReturn (ue);
171     }
172   
173   stdoutRef = sRef_makePointer (uentry_getSref (ue));
174
175   tmp = idDecl_create (cstring_undefined, qtype_create (ctype_unknown));
176
177   regArg = uentry_makeParam (tmp, PARAMUNKNOWN);
178
179   idDecl_setTyp (tmp, 
180                  qtype_addQual (qtype_create (ctype_makePointer (ctype_unknown)),
181                                 qual_createOut ()));
182
183   outArg = uentry_makeParam (tmp, PARAMUNKNOWN);
184
185   idDecl_setTyp (tmp, qtype_addQual (qtype_create (ctype_string), 
186                                      qual_createOut ()));
187   
188   outStringArg = uentry_makeParam (tmp, PARAMUNKNOWN);
189   
190   idDecl_setTyp (tmp, qtype_addQual (qtype_addQual (qtype_create (cstringType), 
191                                                     qual_createOnly ()),
192                                      qual_createNull ()));
193   
194   csOnlyArg = uentry_makeParam (tmp, PARAMUNKNOWN);
195   
196   idDecl_setTyp (tmp, qtype_addQual (qtype_create (cstringType), qual_createNull ()));
197   csArg = uentry_makeParam (tmp, PARAMUNKNOWN);
198   
199   idDecl_free (tmp);
200 }
201
202 void
203 exprNode_destroyMod (void) 
204    /*@globals killed regArg, killed outArg, killed outStringArg,
205               killed mustExitNode, initMod @*/
206 {
207   if (initMod)
208     {
209       uentry_free (regArg);
210       uentry_free (outArg);
211       uentry_free (outStringArg);
212       
213       exprNode_free (mustExitNode);
214       initMod = FALSE;
215     /*@-branchstate@*/ 
216     } 
217   /*@=branchstate@*/
218 }
219
220 static void exprNode_resetSref (/*@notnull@*/ exprNode e)
221 {
222   e->sref = defref;
223 }
224
225 exprNode exprNode_fakeCopy (exprNode e)
226 {
227   /*@-temptrans@*/ /*@-retalias@*/
228   return e;
229   /*@=temptrans@*/ /*@=retalias@*/
230 }
231
232 static bool isFlagKey (char key)
233 {
234   return (key == '-' || key == '+' || key == ' ' || key == '#');
235 }
236
237 static void exprNode_combineControl (/*@notnull@*/ exprNode ret,
238                                      /*@notnull@*/ exprNode ifclause,
239                                      /*@notnull@*/ exprNode elseclause)
240 {
241   ret->canBreak = ifclause->canBreak || elseclause->canBreak;
242
243   ret->mustBreak =
244     (ifclause->mustBreak || exprNode_mustEscape (ifclause))
245       && (elseclause->mustBreak || exprNode_mustEscape (elseclause));
246
247   ret->exitCode = exitkind_combine (ifclause->exitCode,
248                                     elseclause->exitCode);
249
250 }
251
252 /*
253 ** For exprNode's returned by exprNode_effect.
254 */
255
256 static bool shallowKind (exprKind kind)
257 {
258   return (kind == XPR_STRINGLITERAL
259           || kind == XPR_NUMLIT
260           || kind == XPR_EMPTY
261           || kind == XPR_BODY
262           || kind == XPR_NODE);
263 }
264
265 static void 
266 exprNode_freeIniter (/*@only@*/ exprNode e)
267 {
268   if (!exprNode_isError (e))
269     {
270       switch (e->kind)
271         {
272         case XPR_FACCESS:
273           sfree (e->edata->field);
274           sfree (e->edata);
275           break;
276         case XPR_FETCH:
277           exprNode_free (e->edata->op->b);
278           /*@-compdestroy@*/ sfree (e->edata->op); /*@=compdestroy@*/
279           sfree (e->edata);
280           break;
281         default:
282           llbug (message ("other: %s", exprNode_unparse (e)));
283         }
284
285       multiVal_free (e->val);
286       cstring_free (e->etext);
287       fileloc_free (e->loc);
288       sRefSet_free (e->uses);
289       sRefSet_free (e->sets);
290       sRefSet_free (e->msets);
291       guardSet_free (e->guards);
292       sfree (e);
293     }
294 }
295
296 void 
297 exprNode_freeShallow (/*@only@*/ exprNode e)
298 {
299   if (!exprNode_isError (e))
300     {
301       if (shallowKind (e->kind))
302         {
303                 }
304       else
305         {
306           if (!inEffect)
307             {
308               if (e->kind == XPR_EMPTY
309                   || e->kind == XPR_BODY
310                   || e->kind == XPR_STRINGLITERAL
311                   || e->kind == XPR_NUMLIT
312                   || e->kind == XPR_NODE
313                   || e->kind == XPR_OFFSETOF
314                   || e->kind == XPR_ALIGNOFT
315                   || e->kind == XPR_ALIGNOF
316                   || e->kind == XPR_SIZEOFT
317                   || e->kind == XPR_SIZEOF)
318                 {
319                   /* don't free anything */
320                 }
321               else
322                 {
323                   /* multiVal_free (e->val);  */
324                   cstring_free (e->etext);
325                   fileloc_free (e->loc);
326                   sRefSet_free (e->uses);
327                   sRefSet_free (e->sets);
328                   sRefSet_free (e->msets);
329                   guardSet_free (e->guards);
330                   exprData_freeShallow (e->edata, e->kind); 
331                   nowalloc--;
332                   /*@-compdestroy@*/ sfree (e); /*@=compdestroy@*/
333                   /*@-branchstate@*/
334                 }
335             }
336         } /*@=branchstate@*/
337     }
338   }
339
340 void
341 exprNode_free (exprNode e)
342 {
343   if (!exprNode_isError (e))
344     {
345       if (!inEffect)
346         {
347           multiVal_free (e->val);
348           cstring_free (e->etext);
349           fileloc_free (e->loc);
350           sRefSet_free (e->uses);
351           sRefSet_free (e->sets);
352           sRefSet_free (e->msets);
353           guardSet_free (e->guards);
354           exprData_free (e->edata, e->kind);
355           
356           nowalloc--;
357           sfree (e);
358           /*@-branchstate@*/ 
359         } /*@=branchstate@*/
360     }
361 }
362
363 exprNode
364 exprNode_makeError ()
365 {
366   return exprNode_undefined;
367 }
368
369 static /*@out@*/ /*@only@*/ /*@notnull@*/ exprNode
370 exprNode_new (void)
371 {
372   exprNode ret = (exprNode) dmalloc (sizeof (*ret));
373   /* static int lastexpnodes = 0; */
374
375   nowalloc++;
376   totalloc++;
377
378   if (nowalloc > maxalloc)
379     {
380       maxalloc = nowalloc;
381     }
382
383   return ret;
384 }
385
386 static /*@notnull@*/ /*@special@*/ exprNode
387   exprNode_createPlain (ctype c) 
388   /*@defines result@*/
389   /*@post:isnull result->edata, result->loc, result->val, result->guards,
390                  result->uses, result->sets, result->msets, result->etext @*/
391   /*@*/
392 {
393   exprNode e = exprNode_new ();
394
395   e->typ = c;
396   e->kind = XPR_EMPTY;
397   e->val = multiVal_undefined;
398   e->sref = defref;
399   e->etext = cstring_undefined;
400   e->loc = fileloc_undefined;
401   e->guards = guardSet_undefined;
402   e->uses = sRefSet_undefined;
403   e->sets = sRefSet_undefined;
404   e->msets = sRefSet_undefined;
405   e->edata = exprData_undefined;
406   e->exitCode = XK_NEVERESCAPE;
407   e->canBreak = FALSE;
408   e->mustBreak = FALSE;
409   e->isJumpPoint = FALSE;
410   e->environment =  environmentTable_undefined;
411   e->requiresConstraints = constraintList_new();
412   e->ensuresConstraints  = constraintList_new();
413   
414   return (e);
415 }
416
417 /*@observer@*/ exprNode exprNode_makeMustExit (void)
418 {
419   if (exprNode_isUndefined (mustExitNode))
420     {
421       mustExitNode = exprNode_createPlain (ctype_unknown);
422       mustExitNode->exitCode = XK_MUSTEXIT;
423     }
424
425   return mustExitNode;
426 }
427
428
429 static /*@notnull@*/ /*@special@*/ exprNode exprNode_create (ctype c)
430   /*@defines result@*/
431   /*@post:isnull result->edata, result->guards, result->val,
432                  result->uses, result->sets, result->msets@*/
433   /*@*/
434 {
435   exprNode e = exprNode_createPlain (c);
436   e->loc = fileloc_copy (g_currentloc);
437   return (e);
438 }
439
440 static /*@notnull@*/ /*@special@*/ exprNode exprNode_createUnknown (void)
441   /*@defines result@*/
442   /*@post:isnull result->edata, result->guards,
443                  result->uses, result->sets, result->msets@*/
444   /*@*/
445 {
446   return (exprNode_create (ctype_unknown));
447 }
448
449 static /*@notnull@*/ /*@special@*/ exprNode
450   exprNode_createLoc (ctype c, /*@keep@*/ fileloc loc)
451   /*@defines result@*/
452   /*@post:isnull result->edata, result->guards, result->val,
453                  result->uses, result->sets, result->msets@*/
454   /*@*/
455 {
456   exprNode e = exprNode_createPlain (c);
457   e->loc = loc;
458   return (e);
459 }
460
461 static void 
462   exprNode_copySets (/*@special@*/ /*@notnull@*/ exprNode ret, exprNode e)
463   /*@defines ret->guards, ret->uses, ret->sets, ret->msets@*/
464 {
465   if (exprNode_isDefined (e))
466     {
467       ret->guards = guardSet_copy (e->guards);
468       ret->uses = sRefSet_newCopy (e->uses);
469       ret->sets = sRefSet_newCopy (e->sets);
470       ret->msets = sRefSet_newCopy (e->msets); 
471     }
472   else
473     {
474       ret->guards = guardSet_undefined;
475       ret->uses = sRefSet_undefined;
476       ret->sets = sRefSet_undefined;
477       ret->msets = sRefSet_undefined;
478     }
479 }
480
481 static /*@notnull@*/ /*@special@*/ exprNode
482   exprNode_createPartialLocCopy (exprNode e, /*@only@*/ fileloc loc)
483   /*@defines result@*/
484   /*@post:isnull result->edata, result->etext@*/
485   /*@*/
486 {
487   exprNode ret = exprNode_new ();
488
489   if (exprNode_isError (e))
490     {
491       ret->typ = ctype_unknown;
492       ret->val = multiVal_undefined;
493       ret->loc = loc;
494       ret->guards = guardSet_undefined;
495       ret->uses = sRefSet_undefined;
496       ret->sets = sRefSet_undefined;
497       ret->msets = sRefSet_undefined;
498     }
499   else
500     {
501       ret->typ = e->typ;
502       ret->val = multiVal_copy (e->val);
503       ret->loc = loc;
504       ret->guards = guardSet_copy (e->guards);
505       ret->uses = sRefSet_newCopy (e->uses);
506       ret->sets = sRefSet_newCopy (e->sets);
507       ret->msets = sRefSet_newCopy (e->msets); 
508     }
509
510   ret->kind = XPR_EMPTY;
511   ret->sref = defref;
512   ret->etext = cstring_undefined;
513   ret->exitCode = XK_NEVERESCAPE;
514   ret->canBreak = FALSE;
515   ret->mustBreak = FALSE;
516   ret->isJumpPoint = FALSE;
517   ret->edata = exprData_undefined;
518
519   return (ret);
520 }
521
522
523 static /*@notnull@*/ /*@special@*/ exprNode
524   exprNode_createPartialCopy (exprNode e)
525   /*@defines result@*/
526   /*@post:isnull result->edata, result->etext@*/
527   /*@*/
528 {
529   return (exprNode_createPartialLocCopy (e, fileloc_copy (exprNode_loc (e))));
530 }
531
532 static /*@notnull@*/ /*@special@*/ exprNode
533   exprNode_createPartialNVCopy (exprNode e)
534   /*@defines result@*/
535   /*@post:isnull result->edata, result->etext, result->val @*/
536   /*@*/
537 {
538   exprNode ret = exprNode_new ();
539
540   if (exprNode_isError (e))
541     {
542       ret->typ = ctype_unknown;
543       ret->loc = fileloc_undefined;
544       ret->guards = guardSet_undefined;
545       ret->uses = sRefSet_undefined;
546       ret->sets = sRefSet_undefined;
547       ret->msets = sRefSet_undefined;
548     }
549   else
550     {
551       ret->typ = e->typ;
552       ret->loc = fileloc_copy (e->loc);
553       ret->guards = guardSet_copy (e->guards);
554       ret->uses = sRefSet_newCopy (e->uses);
555       ret->sets = sRefSet_newCopy (e->sets);
556       ret->msets = sRefSet_newCopy (e->msets); 
557     }
558   
559   ret->val = multiVal_undefined;
560   ret->kind = XPR_EMPTY;
561   ret->sref = defref;
562   ret->etext = cstring_undefined;
563   ret->exitCode = XK_NEVERESCAPE;
564   ret->canBreak = FALSE;
565   ret->mustBreak = FALSE;
566   ret->isJumpPoint = FALSE;
567   ret->edata = exprData_undefined;
568
569   return (ret);
570 }
571
572 static /*@notnull@*/ /*@special@*/ exprNode
573   exprNode_createSemiCopy (exprNode e)
574   /*@defines result@*/
575   /*@post:isnull result->edata, result->etext, result->sets,
576                  result->msets, result->uses, result->guards@*/
577   /*@*/
578 {
579   if (exprNode_isError (e))
580     {
581       return exprNode_createPlain (ctype_unknown);
582     }
583   else
584     {
585       exprNode ret = exprNode_new ();
586
587       ret->typ = e->typ;
588       ret->val = multiVal_copy (e->val);
589       ret->loc = fileloc_copy (e->loc);
590       ret->guards = guardSet_undefined;
591       ret->uses = sRefSet_undefined;
592       ret->sets = sRefSet_undefined;
593       ret->msets = sRefSet_undefined;
594
595       ret->kind = XPR_EMPTY;
596       ret->sref = defref;
597       ret->etext = cstring_undefined;
598       ret->exitCode = XK_NEVERESCAPE;
599       ret->canBreak = FALSE;
600       ret->mustBreak = FALSE;
601       ret->isJumpPoint = FALSE;
602       ret->edata = exprData_undefined;
603       
604       return (ret);
605     }
606 }
607
608 bool
609 exprNode_isNullValue (exprNode e)
610 {
611   if (exprNode_isDefined (e))
612     {
613       multiVal m = exprNode_getValue (e);
614       
615       if (multiVal_isInt (m))
616         {
617           return (multiVal_forceInt (m) == 0);
618         }
619     }
620   
621   return FALSE;
622 }
623
624 static bool
625 exprNode_isUnknownConstant (/*@notnull@*/ exprNode e)
626 {
627   while (e->kind == XPR_PARENS)
628     {
629       e = exprData_getUopNode (e->edata);
630       llassert (exprNode_isDefined (e));
631     }
632
633   if (e->kind == XPR_CONST)
634     {
635       multiVal m = exprNode_getValue (e);
636
637       if (multiVal_isUnknown (m)) 
638         {
639           return TRUE;
640         }
641     }
642   
643   return FALSE;
644 }
645
646 /*@only@*/ exprNode
647   exprNode_numLiteral (ctype c, /*@temp@*/ cstring t, 
648                        /*@only@*/ fileloc loc, long val)
649 {
650   exprNode e = exprNode_createLoc (c, loc);
651
652   e->kind = XPR_NUMLIT;
653   
654   llassert (multiVal_isUndefined (e->val));
655   e->val = multiVal_makeInt (val);
656   e->edata = exprData_makeLiteral (cstring_copy (t));
657
658   if (val == 0)
659     {
660       e->sref = sRef_makeUnknown ();
661       sRef_setDefNull (e->sref, e->loc);
662     }
663
664   DPRINTF (("Num lit: %s / %s", exprNode_unparse (e), ctype_unparse (exprNode_getType (e))));
665   return (e);
666 }
667
668 /*@only@*/ exprNode
669 exprNode_charLiteral (char c, cstring text, /*@only@*/ fileloc loc)
670 {
671   exprNode e = exprNode_createLoc (ctype_char, loc);
672
673   if (context_getFlag (FLG_CHARINTLITERAL))
674     {
675       e->typ = ctype_makeConj (ctype_char, ctype_int);
676     }
677
678   e->kind = XPR_NUMLIT;
679   e->val = multiVal_makeChar (c);
680
681   e->edata = exprData_makeLiteral (cstring_copy (text));
682   return (e);
683 }
684
685 /*@only@*/ exprNode
686 exprNode_floatLiteral (double d, ctype ct, cstring text, /*@only@*/ fileloc loc)
687 {
688   exprNode e = exprNode_createLoc (ct, loc);
689
690   e->kind = XPR_NUMLIT;
691     e->val = multiVal_makeDouble (d);
692   e->edata = exprData_makeLiteral (cstring_copy (text));
693   return (e);
694 }
695
696 multiVal exprNode_getValue (exprNode e) 
697 {
698   while (exprNode_isInParens (e)) {
699     if (e->edata != NULL) {
700       e = exprData_getUopNode (e->edata);
701     } else {
702       break;
703     }
704   }
705
706   if (exprNode_isDefined (e)) {
707     return e->val; 
708   } else {
709     return multiVal_undefined;
710   }
711 }
712
713 /*@only@*/ exprNode
714 exprNode_stringLiteral (/*@only@*/ cstring t, /*@only@*/ fileloc loc)
715 {
716   exprNode e = exprNode_createLoc (ctype_string, loc);
717   int len = cstring_length (t) - 2;
718   char *ts = cstring_toCharsSafe (t);
719   char *s = cstring_toCharsSafe (cstring_create (len + 1));
720
721   if (context_getFlag (FLG_STRINGLITERALLEN))
722     {
723       if (len > context_getValue (FLG_STRINGLITERALLEN))
724         {
725           voptgenerror (FLG_STRINGLITERALLEN,
726                         message
727                         ("String literal length (%d) exceeds maximum "
728                          "length (%d): %s",
729                          len,
730                          context_getValue (FLG_STRINGLITERALLEN),
731                          t),
732                         e->loc);
733         }
734     }
735
736   strncpy (s, ts+1, size_fromInt (len));
737   *(s + len) = '\0';
738
739   
740   e->kind = XPR_STRINGLITERAL;
741   e->val = multiVal_makeString (cstring_fromCharsO (s));
742   e->edata = exprData_makeLiteral (t);
743   e->sref = sRef_makeType (ctype_string);
744   /* Start modifications */
745   /* This expr is null terminated, so we set the len and size */
746   sRef_setNullTerminatedState(e->sref);
747   /*
748   TPRINTF("Len is set to : %d\n\n", strlen((char *)multiVal_forceString(e->val)));
749   TPRINTF("Size is set to : %d\n\n", strlen((char *)multiVal_forceString(e->val)));
750   TPRINTF("State is set to: %d\n\n", e->sref->bufinfo.bufstate);
751   */
752   sRef_setLen(e->sref, strlen((char *)multiVal_forceString(e->val)));
753   sRef_setSize(e->sref, strlen((char *)multiVal_forceString(e->val)));
754
755   if (context_getFlag (FLG_READONLYSTRINGS))
756     {
757       sRef_setAliasKind (e->sref, AK_STATIC, fileloc_undefined);
758       sRef_setExKind (e->sref, XO_OBSERVER, loc);
759     }
760   else
761     {
762       sRef_setAliasKind (e->sref, AK_ERROR, fileloc_undefined);
763     }
764
765   return (e); /* s released */
766 }
767
768 exprNode exprNode_fromUIO (cstring c)
769 {
770   fileloc loc = context_getSaveLocation ();
771   exprNode e  = exprNode_createPlain (ctype_unknown);
772
773   e->kind = XPR_VAR;
774
775   if (fileloc_isUndefined (loc))
776     {
777       loc = fileloc_copy (g_currentloc);
778     }
779
780   e->loc = loc; /* save loc was mangled */
781   e->sref = defref;
782
783   if (usymtab_exists (c))
784     {
785       uentry ue = usymtab_lookupEither (c);
786
787       if (uentry_isDatatype (ue) 
788           && uentry_isSpecified (ue))
789         {
790           llfatalerror
791             (message ("%q: Specified datatype %s used in code, but not defined. "
792                       "(Cannot continue reasonably from this error.)",
793                       fileloc_unparse (e->loc), c));
794         }
795       else
796         {
797           BADBRANCH; 
798         }
799     }
800   
801   llassertprint (!usymtab_exists (c), ("Entry exists: %s", c));
802
803   /*
804   ** was supercedeGlobalEntry...is this better?
805   */
806
807   if (!context_inIterEnd ())
808     {
809       if (context_inMacro ())
810         {
811           if (context_getFlag (FLG_UNRECOG))
812             {
813               voptgenerror 
814                 (FLG_MACROUNDEF, 
815                  message ("Unrecognized identifier in macro definition: %s", c), e->loc);
816             }
817           else
818             {
819               flagcode_recordSuppressed (FLG_UNRECOG);
820             }
821         }
822       else
823         {
824           voptgenerror 
825             (FLG_UNRECOG, message ("Unrecognized identifier: %s", c),
826              e->loc);
827         }
828     }
829   
830   e->edata = exprData_makeId (uentry_makeUnrecognized (c, fileloc_copy (loc)));
831
832   /* No alias errors for unrecognized identifiers */
833   sRef_setAliasKind (e->sref, AK_ERROR, loc); 
834
835   return (e);
836 }
837
838 exprNode exprNode_createId (/*@observer@*/ uentry c)
839 {
840   if (uentry_isValid (c))
841     {
842       exprNode e = exprNode_new ();
843       
844       e->typ = uentry_getType (c);
845
846       if (uentry_isFunction (c)
847           && !sRef_isLocalVar (uentry_getSref (c)))
848         {
849           e->sref = sRef_undefined;
850         }
851       else
852         {
853           e->sref = uentry_getSref (c); 
854         }
855
856       if (sRef_isStateUnknown (e->sref) && uentry_isNonLocal (c))
857         {
858           sRef_setDefined (e->sref, fileloc_undefined);
859         }
860       
861       /*
862       ** yoikes!  leaving this out was a heinous bug...that would have been
863       ** caught if i had lclint working first.  gag!
864       */
865       
866       e->etext = cstring_undefined;
867       
868       if (uentry_isEitherConstant (c))
869         {
870           e->kind = XPR_CONST;
871           e->val = multiVal_copy (uentry_getConstantValue (c));
872         }
873       else
874         {
875           e->kind = XPR_VAR;
876           e->val = multiVal_unknown ();
877         }
878       
879       e->edata = exprData_makeId (c);
880       e->loc = context_getSaveLocation ();
881       
882       if (fileloc_isUndefined (e->loc))
883         {
884           fileloc_free (e->loc);
885           e->loc = fileloc_copy (g_currentloc);
886         }
887
888       e->guards = guardSet_new ();
889       e->sets = sRefSet_new ();
890       e->msets = sRefSet_new ();
891       e->uses = sRefSet_new ();
892       
893       /*> missing fields, detected by lclint <*/
894       e->exitCode = XK_NEVERESCAPE;
895       e->isJumpPoint = FALSE;
896       e->canBreak = FALSE;
897       e->mustBreak = FALSE;
898       
899       return e;
900     }
901   else
902     {
903             return exprNode_createUnknown ();
904     }
905 }
906
907 /*@notnull@*/ exprNode
908 exprNode_fromIdentifier (/*@observer@*/ uentry c)
909 {
910   exprNode ret;
911
912   if (context_justPopped ()) /* watch out! c could be dead */
913     { 
914       uentry ce = usymtab_lookupSafe (LastIdentifier ());
915
916       if (uentry_isValid (ce)) 
917         {
918           c = ce;
919         }
920       else
921         {
922           llbuglit ("Looks like Aunt Millie forgot to walk to dog again.");
923         }
924     }
925
926   ret = exprNode_fromIdentifierAux (c);
927   
928   return ret;
929 }
930
931
932 static /*@only@*/ /*@notnull@*/ exprNode
933 exprNode_fromIdentifierAux (/*@observer@*/ uentry c)
934 {
935   exprNode e = exprNode_createId (c);
936   sRef sr = e->sref;
937
938   uentry_setUsed (c, e->loc);
939
940   if (uentry_isVar (c) && sRef_isGlobal (sr))
941     {
942       checkGlobUse (c, FALSE, e);
943     }
944
945   return (e);
946 }
947
948 static bool
949 exprNode_isZero (exprNode e)
950 {
951   if (exprNode_isDefined (e))
952     {
953       multiVal m = exprNode_getValue (e);
954       
955       if (multiVal_isInt (m))
956         {
957           return (multiVal_forceInt (m) == 0);
958         }
959     }
960
961   return FALSE;
962 }
963
964 static bool
965 exprNode_isNonNegative (exprNode e)
966 {
967   if (exprNode_isDefined (e))
968     {
969       multiVal m = exprNode_getValue (e);
970       
971       if (multiVal_isInt (m))
972         {
973           return (multiVal_forceInt (m) >= 0);
974         }
975     }
976
977   return FALSE;
978 }
979
980 /*
981 ** a[x]  - uses a but NOT a[] 
982 **         result sref = a[]  (set/use in assignment)
983 ** 
984 ** The syntax x[a] is also legal in C, and has the same 
985 ** semantics.  If ind is an array, and arr is an int, flip
986 ** the arguments.
987 */
988
989 /*@only@*/ exprNode
990 exprNode_arrayFetch (/*@only@*/ exprNode e1, /*@only@*/ exprNode e2)
991 {
992   /*
993   ** error in arr, error propagates (no new messages)
994   ** error in ind, assume valid and continue
995   */
996
997   if (exprNode_isError (e1))
998     {
999       exprNode_free (e2);
1000       return (exprNode_makeError ());
1001     }
1002   else
1003     {
1004       exprNode arr;
1005       exprNode ind;
1006       ctype carr = exprNode_getType (e1);
1007       ctype crarr = ctype_realType (carr);
1008  
1009       /*
1010       ** this sets up funny aliasing, that leads to spurious
1011       ** lclint errors.  Hence, the i2 comments.
1012       */
1013
1014       if (!ctype_isRealArray (crarr) 
1015           && ctype_isRealNumeric (crarr) 
1016           && !exprNode_isError (e2)
1017           && ctype_isRealAP (exprNode_getType (e2)))  /* fetch like 3[a] */
1018         {
1019           arr = e2;
1020           ind = e1;
1021
1022           carr = exprNode_getType (arr);
1023           crarr = ctype_realType (carr);
1024         }
1025       else
1026         {
1027           arr = e1;
1028           ind = e2;
1029         }
1030
1031       if (sRef_possiblyNull (arr->sref))
1032         {
1033           if (!usymtab_isGuarded (arr->sref))
1034             {
1035               if (optgenerror (FLG_NULLDEREF,
1036                                message ("Index of %s pointer %q: %s", 
1037                                         sRef_nullMessage (arr->sref),
1038                                         sRef_unparse (arr->sref),
1039                                         exprNode_unparse (arr)),
1040                                arr->loc))
1041                 {
1042                   sRef_showNullInfo (arr->sref);
1043
1044                   /* suppress future messages */
1045                   sRef_setNullError (arr->sref); 
1046                 }
1047             }
1048         }
1049
1050       if (exprNode_isError (ind))
1051         {
1052           if ((ctype_isArrayPtr (crarr) 
1053                && !ctype_isFunction (crarr))
1054               || ctype_isUnknown (carr))
1055             {
1056               exprNode ret = exprNode_createPartialCopy (arr);
1057
1058               if (ctype_isKnown (carr))
1059                 {
1060                   ret->typ = ctype_baseArrayPtr (crarr);
1061                 }
1062               else
1063                 {
1064                   ret->typ = ctype_unknown;
1065                 }
1066               
1067               ret->sref = sRef_makeArrayFetch (arr->sref);
1068               
1069               ret->kind = XPR_FETCH;
1070
1071               /*
1072               ** Because of funny aliasing (when arr and ind are
1073               ** flipped) spurious errors would be reported here.
1074               */
1075          
1076               /*@i2@*/ ret->edata = exprData_makePair (arr, ind);             
1077               checkSafeUse (ret, arr->sref);
1078               return (ret);
1079             }
1080           else
1081             {
1082               voptgenerror (FLG_TYPE,
1083                             message ("Array fetch from non-array (%t): %s[%s]", carr, 
1084                                      exprNode_unparse (e1), exprNode_unparse (e2)),
1085                             arr->loc);
1086               exprNode_free (arr);
1087               return (exprNode_makeError ());
1088             }
1089         }
1090       else
1091         {
1092           if (!ctype_isForceRealInt (&(ind->typ)))
1093             {
1094               ctype rt = ctype_realType (ind->typ);
1095
1096               if (ctype_isChar (rt))
1097                 {
1098                   vnoptgenerror
1099                     (FLG_CHARINDEX,
1100                      message ("Array fetch using non-integer, %t: %s[%s]",
1101                               ind->typ, 
1102                               exprNode_unparse (e1), exprNode_unparse (e2)),
1103                      arr->loc);
1104                 }
1105               else if (ctype_isEnum (rt))
1106                 {
1107                   vnoptgenerror
1108                     (FLG_ENUMINDEX,
1109                      message ("Array fetch using non-integer, %t: %s[%s]",
1110                               ind->typ, 
1111                               exprNode_unparse (e1), exprNode_unparse (e2)),
1112                      arr->loc);
1113                 }
1114               else
1115                 {
1116                   voptgenerror 
1117                     (FLG_TYPE,
1118                      message ("Array fetch using non-integer, %t: %s[%s]",
1119                               ind->typ, 
1120                               exprNode_unparse (e1), exprNode_unparse (e2)),
1121                      arr->loc);
1122                 }
1123
1124               multiVal_free (ind->val);
1125               ind->val = multiVal_unknown ();
1126             }
1127           
1128           if (ctype_isArrayPtr (crarr) && !ctype_isFunction (crarr))
1129             {
1130               exprNode ret = exprNode_createSemiCopy (arr);
1131               multiVal m = exprNode_getValue (ind);
1132               
1133               ret->typ = ctype_baseArrayPtr (crarr);
1134               ret->kind = XPR_FETCH;
1135               
1136               if (multiVal_isInt (m))
1137                 {
1138                   int i = (int) multiVal_forceInt (m);
1139                   
1140                   if (sRef_isValid (arr->sref)) {
1141                     ret->sref = sRef_makeArrayFetchKnown (arr->sref, i);
1142                   } else {
1143                     ret->sref = sRef_undefined;
1144                   }
1145                 }
1146               else
1147                 {
1148                                   ret->sref = sRef_makeArrayFetch (arr->sref);
1149                 }
1150               
1151               ret->sets = sRefSet_realNewUnion (arr->sets, ind->sets);
1152               ret->msets = sRefSet_realNewUnion (arr->msets, ind->msets);
1153               ret->uses = sRefSet_realNewUnion (arr->uses, ind->uses);
1154               
1155               /* (see comment on spurious errors above) */
1156               /*@i2@*/ ret->edata = exprData_makePair (arr, ind);
1157               
1158               exprNode_checkUse (ret, ind->sref, ind->loc);
1159               exprNode_checkUse (ret, arr->sref, arr->loc);
1160               
1161               return (ret);
1162             }
1163           else
1164             {
1165               if (ctype_isUnknown (carr))
1166                 {
1167                   exprNode ret = exprNode_createPartialCopy (arr);
1168                   
1169                   ret->kind = XPR_FETCH;
1170                   ret->typ = ctype_unknown;
1171                   ret->sets = sRefSet_union (ret->sets, ind->sets);
1172                   ret->msets = sRefSet_union (ret->msets, ind->msets);
1173                   ret->uses = sRefSet_union (ret->uses, ind->uses);
1174
1175                   /* (see comment on spurious errors above) */            
1176                   /*@i2@*/ ret->edata = exprData_makePair (arr, ind);
1177                   
1178                   exprNode_checkUse (ret, ind->sref, ind->loc);
1179                   exprNode_checkUse (ret, arr->sref, arr->loc);
1180                   return (ret);
1181                 }
1182               else
1183                 {
1184                   voptgenerror
1185                     (FLG_TYPE,
1186                      message ("Array fetch from non-array (%t): %s[%s]", carr, 
1187                               exprNode_unparse (e1), exprNode_unparse (e2)),
1188                      arr->loc);
1189
1190                   exprNode_free (arr);
1191                   exprNode_free (ind);
1192
1193                   return (exprNode_makeError ());
1194                 }
1195             }
1196         }
1197     }
1198   BADEXIT;
1199 }
1200
1201
1202 static int
1203 checkArgs (uentry fcn, /*@dependent@*/ exprNode f, ctype t, 
1204            exprNodeList args, exprNode ret)
1205 {
1206   return (checkArgsReal (fcn, f, ctype_argsFunction (t), args, FALSE, ret));
1207 }
1208
1209 /*
1210 ** checkPrintfArgs --- checks arguments for printf-like functions
1211 **    Arguments before ... have already been checked.
1212 **    The argument before the ... is a char *.  
1213 **    argno is the format string argument.
1214 */
1215
1216 static void
1217 checkPrintfArgs (/*@notnull@*/ /*@dependent@*/ exprNode f, uentry fcn, 
1218                  exprNodeList args, exprNode ret, int argno)
1219 {
1220   /*
1221   ** the last argument before the elips is the format string 
1222   */
1223
1224   int i = argno;
1225   fileloc formatloc;
1226   int nargs = exprNodeList_size (args);
1227   uentryList params = uentry_getParams (fcn);
1228   exprNode a; 
1229
1230   /*
1231   ** These should be ensured by checkSpecialFunction
1232   */
1233
1234   llassert (uentryList_size (params) == argno + 1);
1235   llassert (uentry_isElipsisMarker (uentryList_getN (params, argno)));
1236
1237   a = exprNodeList_getN (args, argno - 1);
1238   formatloc = fileloc_copy (exprNode_loc (a));
1239
1240   if (exprNode_isDefined (a) && exprNode_isStringLiteral (a) 
1241       && exprNode_knownStringValue (a))
1242     {
1243       char *format = cstring_toCharsSafe (multiVal_forceString (exprNode_getValue (a)));
1244       char *code = format;
1245       char *ocode = code;
1246
1247       nargs = exprNodeList_size (args);
1248
1249       while ((code = strchr (code, '%')) != NULL)
1250         {
1251           char *origcode = code;
1252           char key = *(++code);                 
1253           ctype modtype = ctype_int;
1254           bool modified = FALSE;
1255
1256           fileloc_addColumn (formatloc, code - ocode);
1257
1258           /* ignore flags */
1259           while (isFlagKey (key)) 
1260             {
1261               key = *(++code);
1262               fileloc_incColumn (formatloc);
1263             }
1264
1265           if (key == 'm') /* skipped in syslog */
1266             {
1267               continue; 
1268             }
1269           
1270           /* ignore field width */
1271           while (isdigit ((int) key) != 0) 
1272             {
1273               key = *(++code);
1274               fileloc_incColumn (formatloc);
1275             }
1276           
1277           /* ignore precision */
1278           if (key == '.')
1279             {
1280               key = *(++code);
1281               fileloc_incColumn (formatloc);
1282
1283               /*
1284               ** In printf, '*' means: read the next arg as an int for the
1285               ** field width.  This seems to be missing from my copy of the 
1286               ** standard x3.159-1989.  Setion 4.9.6.1 refers to * (described
1287               ** later) but never does.
1288               */
1289               
1290               if (key == '*') 
1291                 {
1292                   ; /* don't do anything --- handle later */
1293                 }
1294               else
1295                 {
1296                   while (isdigit ((int) key) != 0)
1297                     {
1298                       key = *(++code);
1299                       fileloc_incColumn (formatloc);
1300                     }
1301                 }
1302             }
1303
1304           if (key == 'h')
1305             {
1306               modtype = ctype_sint;  /* short */
1307               key = *(++code);
1308               fileloc_incColumn (formatloc);
1309             }
1310           else if (key == 'l' || key == 'L') 
1311             {
1312               modtype = ctype_lint; /* long */
1313               key = *(++code);
1314               fileloc_incColumn (formatloc);
1315
1316               if (key == 'l' || key == 'L') { 
1317                 modtype = ctype_llint; /* long long */
1318                 key = *(++code);
1319                 fileloc_incColumn (formatloc);
1320               }
1321             }
1322           else
1323             {
1324               ; /* no modifier */
1325             }
1326           
1327           /* now, key = type of conversion to apply */
1328           ++code;
1329           fileloc_incColumn (formatloc);
1330
1331           if (key != '%') 
1332             {
1333               if (i >= nargs)
1334                 {
1335                   if (optgenerror 
1336                       (FLG_TYPE,
1337                        message ("No argument corresponding to %q format "
1338                                 "code %d (%%%h): \"%s\"",
1339                                 uentry_getName (fcn),
1340                                 i, key,
1341                                 cstring_fromChars (format)),
1342                        f->loc))
1343                     {
1344                       if (fileloc_isDefined (formatloc)
1345                           && context_getFlag (FLG_SHOWCOL))
1346                         {
1347                           llgenindentmsg (cstring_makeLiteral ("Corresponding format code"),
1348                                           formatloc);
1349                         }
1350                     }
1351                   i++;
1352                 }
1353               else
1354                 {
1355                   a = exprNodeList_getN (args, i);
1356                   i++;
1357                   
1358                   if (!exprNode_isError (a))
1359                     {
1360                       ctype expecttype;
1361
1362                       switch (key)
1363                         {
1364                         case '*': /* int argument for fieldwidth */
1365                           expecttype = ctype_int;
1366                           *(--code) = '%'; /* convert it for next code */
1367                           fileloc_subColumn (formatloc, 1);
1368                           /*@switchbreak@*/ break;              
1369                         case 'u':
1370                         case 'o':
1371                           expecttype = ctype_combine (ctype_uint, modtype);
1372                           /*@switchbreak@*/ break;
1373                           
1374                         case 'i': /* int argument */ 
1375                         case 'd':
1376                           expecttype = ctype_combine (ctype_int, modtype);
1377                           /*@switchbreak@*/ break;
1378
1379                         case 'x': /* unsigned int */
1380                         case 'X':
1381                           expecttype = ctype_combine (ctype_uint, modtype);
1382                           /*@switchbreak@*/ break;
1383                           
1384                         case 'e':
1385                         case 'E':
1386                         case 'g':
1387                         case 'G':
1388                         case 'f': /* double */
1389                           expecttype = ctype_combine (ctype_double, modtype);
1390                           /*@switchbreak@*/ break;
1391                           
1392                         case 'c': /* int converted to char (check its a char?) */
1393                           expecttype = ctype_makeConj (ctype_char, ctype_uchar);
1394                           /*@switchbreak@*/ break;
1395                               
1396                         case 's': /* string */
1397                           expecttype = ctype_string;
1398                           /*@switchbreak@*/ break;
1399                         case '[': 
1400                           /* skip to ']' */
1401                           while (((key = *(++code)) != ']') 
1402                                  && (key != '\0'))
1403                             {
1404                               fileloc_incColumn (formatloc);
1405                             }
1406                           
1407                           if (key == '\0')
1408                             {
1409                               llfatalerrorLoc
1410                                 (message ("Bad character set format: %s", 
1411                                           cstring_fromChars (origcode)));
1412                             }
1413                           
1414                           expecttype = ctype_string;
1415                           /*@switchbreak@*/ break;
1416                           
1417                         case 'p': /* pointer */
1418                           expecttype = ctype_makePointer (ctype_void);
1419                           /* really! */
1420                           /*@switchbreak@*/ break;
1421                           
1422                         case 'n': /* pointer to int, modified by call! */
1423                           expecttype = ctype_combine (ctype_makePointer (ctype_int), modtype);
1424                           modified = TRUE;
1425                           uentry_setDefState (regArg, SS_ALLOCATED); /* corresponds to out */
1426                           /*@switchbreak@*/ break;
1427
1428                         case 'm': /* in a syslog, it doesn't consume an argument */
1429                           /* should check we're really doing syslog */
1430                           
1431                           /*@switchbreak@*/ break;
1432
1433                           
1434                         default:
1435                           expecttype = ctype_unknown;
1436                           
1437                           voptgenerror
1438                             (FLG_FORMATCODE,
1439                              message ("Unrecognized format code: %s", 
1440                                       cstring_fromChars (origcode)),
1441                              fileloc_isDefined (formatloc) 
1442                              ? formatloc : g_currentloc);
1443
1444                           /*@switchbreak@*/ break;
1445                         }
1446
1447                       if (!(exprNode_matchArgType (expecttype, a)))
1448                         {
1449                           if (ctype_isVoidPointer (expecttype) 
1450                               && ctype_isRealAbstract (a->typ)
1451                               && (context_getFlag (FLG_ABSTVOIDP)))
1452                             {
1453                               ;
1454                             }
1455                           else
1456                             {
1457                               if (llgenformattypeerror 
1458                                   (expecttype, exprNode_undefined,
1459                                    a->typ, a,
1460                                    message ("Format argument %d to %q (%%%h) expects "
1461                                             "%t gets %t: %s",
1462                                             i - argno,
1463                                             uentry_getName (fcn), 
1464                                             key, expecttype,
1465                                             a->typ, exprNode_unparse (a)),
1466                                    a->loc))
1467                                 {
1468                                   if (fileloc_isDefined (formatloc)
1469                                       && context_getFlag (FLG_SHOWCOL))
1470                                     {
1471                                       llgenindentmsg
1472                                         (cstring_makeLiteral 
1473                                          ("Corresponding format code"),
1474                                          formatloc);
1475                                     }
1476                                 }
1477                             }
1478                         }
1479
1480                       uentry_setType (regArg, expecttype);
1481                       checkOneArg (regArg, a, f, FALSE, i+1, nargs);
1482                       
1483                       if (ctype_equal (expecttype, ctype_string))
1484                         {
1485                           exprNode_checkUse (a, sRef_makePointer (a->sref), a->loc);
1486                         }
1487                       
1488                       uentry_setType (regArg, ctype_unknown);
1489                       uentry_fixupSref (regArg);
1490                   
1491                       if (modified)
1492                         {
1493                           exprNode_checkCallModifyVal (a->sref, args, f, ret);
1494                         }
1495                     }
1496                   else
1497                     {
1498                       ;
1499                     }
1500                 }
1501             }
1502           ocode = code;
1503         }
1504   
1505       if (i < nargs)
1506         {
1507           voptgenerror (FLG_TYPE,
1508                         message ("Format string for %q has %d arg%p, given %d", 
1509                                  uentry_getName (fcn), i - argno, nargs - argno),
1510                         f->loc);
1511         }
1512     }
1513   else
1514     {
1515       /* no checking possible for compile-time unknown format strings */
1516     }
1517
1518   fileloc_free (formatloc);
1519 }
1520
1521 static void
1522 checkScanfArgs (/*@notnull@*/ /*@dependent@*/ exprNode f, uentry fcn, 
1523                  exprNodeList args, exprNode ret, int argno)
1524 {
1525   int i = argno;
1526   fileloc formatloc;
1527   int nargs = exprNodeList_size (args);
1528   uentryList params = uentry_getParams (fcn);
1529   exprNode a; 
1530
1531   /*
1532   ** These should be ensured by checkSpecialFunction
1533   */
1534
1535   llassert (uentryList_size (params) == argno + 1);
1536   llassert (uentry_isElipsisMarker (uentryList_getN (params, argno)));
1537
1538   a = exprNodeList_getN (args, argno - 1);
1539   formatloc = fileloc_copy (exprNode_loc (a));
1540
1541   if (exprNode_isDefined (a) && exprNode_isStringLiteral (a) 
1542       && exprNode_knownStringValue (a))
1543     {
1544       char *format = cstring_toCharsSafe (multiVal_forceString (exprNode_getValue (a)));
1545       char *code = format;
1546       char *ocode = code;
1547
1548       nargs = exprNodeList_size (args);
1549
1550       while ((code = strchr (code, '%')) != NULL)
1551         {
1552           char *origcode = code;
1553           char key = *(++code);                 
1554           ctype modtype = ctype_int;
1555           char modifier = '\0';
1556           bool modified = TRUE;
1557           bool ignore = FALSE;
1558
1559           fileloc_addColumn (formatloc, code - ocode);
1560
1561           /*
1562           ** this is based on ANSI standard library description of fscanf
1563           ** (from ANSI standard X3.159-1989, 4.9.6.1)
1564           */
1565               
1566           /* '*' suppresses assignment (does not need match argument) */
1567           
1568           if (key == '*') 
1569             {
1570               key = *(++code);
1571               modified = FALSE; 
1572               ignore = TRUE;
1573               fileloc_incColumn (formatloc);
1574             }
1575           
1576           /* ignore field width */
1577           while (isdigit ((int) key) != 0)
1578             {
1579               key = *(++code);
1580               fileloc_incColumn (formatloc);
1581             }
1582           
1583           if (key == 'h')
1584             {
1585               modtype = ctype_sint;  /* short */
1586               key = *(++code);
1587               fileloc_incColumn (formatloc);
1588             }
1589           else if (key == 'l' || key == 'L') 
1590             {
1591               modtype = ctype_lint; /* long */
1592               modifier = key;
1593
1594               key = *(++code);
1595               fileloc_incColumn (formatloc);
1596
1597               if (key == 'l' || key == 'L') { 
1598                 modtype = ctype_llint; /* long long */
1599                 key = *(++code);
1600                 fileloc_incColumn (formatloc);
1601               }
1602             }
1603           else
1604             {
1605               ; /* no modifier */
1606             }
1607           
1608           /* now, key = type of conversion to apply */
1609           ++code;
1610           fileloc_incColumn (formatloc);
1611
1612           if (key != '%') 
1613             {
1614               if (ignore)
1615                 {
1616                   ;
1617                 }
1618               else
1619                 {
1620                   if (i >= nargs)
1621                     {
1622                       if (optgenerror 
1623                           (FLG_TYPE,
1624                            message ("No argument corresponding to %q format "
1625                                     "code %d (%%%h): \"%s\"",
1626                                     uentry_getName (fcn),
1627                                     i, key,
1628                                     cstring_fromChars (format)),
1629                            f->loc))
1630                         {
1631                           if (fileloc_isDefined (formatloc)
1632                               && context_getFlag (FLG_SHOWCOL))
1633                             {
1634                               llgenindentmsg
1635                                 (cstring_makeLiteral ("Corresponding format code"),
1636                                  formatloc);
1637                             }
1638                         }
1639                       i++;
1640                     }
1641                   else
1642                     {
1643                       a = exprNodeList_getN (args, i);
1644                       i++;
1645                   
1646                       if (!exprNode_isError (a))
1647                         {
1648                           ctype expecttype;
1649
1650                           switch (key)
1651                             {
1652                             case '*': /* int argument for fieldwidth */
1653                               expecttype = ctype_makePointer (ctype_int);
1654                               *(--code) = '%'; /* convert it for next code */
1655                               fileloc_subColumn (formatloc, 1);
1656                               /*@switchbreak@*/ break;          
1657                             case 'u':
1658                             case 'o':
1659                               expecttype = ctype_makePointer (ctype_combine (ctype_uint, modtype));
1660                               /*@switchbreak@*/ break;
1661                               
1662                             case 'i': 
1663                             case 'd':
1664                             case 'x':
1665                             case 'X': /* unsigned int */
1666                               expecttype = ctype_makePointer (ctype_combine (ctype_int, modtype));
1667                               /*@switchbreak@*/ break;
1668                               
1669                             case 'e':
1670                             case 'E':
1671                             case 'g':
1672                             case 'G':
1673                             case 'f': 
1674                               /* printf is double, scanf is float! */
1675
1676                               if (modifier == 'l') 
1677                                 {
1678                                   expecttype = ctype_makePointer (ctype_double);
1679                                 }
1680                               else if (modifier == 'L')
1681                                 {
1682                                   expecttype = ctype_makePointer (ctype_ldouble);
1683                                 }
1684                               else 
1685                                 {
1686                                   llassert (modifier == '\0');
1687                                   expecttype = ctype_makePointer (ctype_float);
1688                                 }
1689                               /*@switchbreak@*/ break;
1690                               
1691                             case 'c': /* int converted to char (check its a char?) */
1692                               expecttype = ctype_makePointer (ctype_makeConj (ctype_char, ctype_uchar));
1693                               /*@switchbreak@*/ break;
1694                               
1695                             case 's': /* string */
1696                               expecttype = ctype_string;
1697                               /*@switchbreak@*/ break;
1698
1699                             case '[': 
1700                               /* skip to ']' */
1701                               while (((key = *(++code)) != ']') 
1702                                      && (key != '\0'))
1703                                 {
1704                                   fileloc_incColumn (formatloc);
1705                                 }
1706                               
1707                               if (key == '\0')
1708                                 {
1709                                   llfatalerrorLoc
1710                                     (message ("Bad character set format: %s", 
1711                                               cstring_fromChars (origcode)));
1712                                 }
1713                               
1714                               expecttype = ctype_string;
1715                               /*@switchbreak@*/ break;
1716                               
1717                             case 'p': /* pointer */
1718                               expecttype = ctype_unknown;
1719                               /* really! */
1720                               /*@switchbreak@*/ break;
1721                               
1722                             case 'n': /* pointer to int, modified by call! */
1723                               expecttype = ctype_makePointer (ctype_int);
1724                               /*@switchbreak@*/ break;
1725                           
1726                             default:
1727                               expecttype = ctype_unknown;
1728                               
1729                               voptgenerror
1730                                 (FLG_FORMATCODE,
1731                                  message ("Unrecognized format code: %s", 
1732                                           cstring_fromChars (origcode)),
1733                                  fileloc_isDefined (formatloc) 
1734                                  ? formatloc : g_currentloc);
1735                               
1736                               /*@switchbreak@*/ break;
1737                             }
1738                           
1739                           if (!(exprNode_matchArgType (expecttype, a)))
1740                             {
1741                               if (ctype_isVoidPointer (expecttype) 
1742                                   && ctype_isRealAbstract (a->typ)
1743                                   && (context_getFlag (FLG_ABSTVOIDP)))
1744                                 {
1745                                   ;
1746                                 }
1747                               else
1748                                 {
1749                                   if (modifier != '\0')
1750                                     {
1751                                       if (llgenformattypeerror 
1752                                           (expecttype, exprNode_undefined,
1753                                            a->typ, a,
1754                                            message ("Format argument %d to %q (%%%h%h) expects "
1755                                                     "%t gets %t: %s",
1756                                                     i - argno,
1757                                                     uentry_getName (fcn), 
1758                                                     modifier,
1759                                                     key, expecttype,
1760                                                     a->typ, exprNode_unparse (a)),
1761                                            a->loc))
1762                                         {
1763                                           if (fileloc_isDefined (formatloc)
1764                                               && context_getFlag (FLG_SHOWCOL))
1765                                             {
1766                                               llgenindentmsg
1767                                                 (cstring_makeLiteral 
1768                                                  ("Corresponding format code"),
1769                                                  formatloc);
1770                                             }
1771                                         }
1772
1773                                     }
1774                                   else
1775                                     {
1776                                       if (llgenformattypeerror 
1777                                           (expecttype, exprNode_undefined,
1778                                            a->typ, a,
1779                                            message ("Format argument %d to %q (%%%h) expects "
1780                                                     "%t gets %t: %s",
1781                                                     i - argno,
1782                                                     uentry_getName (fcn), 
1783                                                     key, expecttype,
1784                                                     a->typ, exprNode_unparse (a)),
1785                                            a->loc))
1786                                         {
1787                                           if (fileloc_isDefined (formatloc)
1788                                               && context_getFlag (FLG_SHOWCOL))
1789                                             {
1790                                               llgenindentmsg
1791                                                 (cstring_makeLiteral 
1792                                                  ("Corresponding format code"),
1793                                                  formatloc);
1794                                             }
1795                                         }
1796                                     }
1797                                 }
1798                             }
1799                           
1800                           uentry_setType (outArg, expecttype);
1801                           checkOneArg (outArg, a, f, FALSE, i+1, nargs);
1802                           uentry_setType (outArg, ctype_unknown);
1803                           uentry_fixupSref (outArg);
1804                           
1805                           if (modified)
1806                             {
1807                               exprNode_checkCallModifyVal (a->sref, args, f, ret);
1808                             }
1809                         }
1810                       else
1811                         {
1812                                                   /* a->sref = defref; */
1813                         }
1814                     }
1815                 }
1816             }
1817           ocode = code;
1818         }
1819
1820       if (i < nargs)
1821         {
1822           voptgenerror (FLG_TYPE,
1823                         message ("Format string for %q has %d arg%p, given %d", 
1824                                  uentry_getName (fcn), i - argno, nargs - argno),
1825                         f->loc);
1826         }
1827     }
1828   else
1829     {
1830       /* no checking possible for compile-time unknown format strings */
1831     }
1832
1833   fileloc_free (formatloc);
1834 }
1835                           
1836 static void
1837 checkMessageArgs (/*@notnull@*/ /*@dependent@*/ exprNode f,
1838                   uentry fcn,
1839                   exprNodeList args,
1840                   /*@unused@*/ int argno)
1841 {
1842   /*
1843   ** the last argument before the elips is the format string 
1844   */
1845
1846   int nargs = exprNodeList_size (args);
1847   int i = argno;
1848   fileloc formatloc;
1849   exprNode a; 
1850
1851   a = exprNodeList_getN (args, argno - 1);
1852   formatloc = fileloc_copy (exprNode_loc (a));
1853
1854   if (ctype_isUnknown (cstringType)) {
1855     if (usymtab_existsType (cstring_makeLiteralTemp ("cstring")))
1856       {
1857         cstringType = usymtab_lookupAbstractType (cstring_makeLiteralTemp ("cstring"));
1858       }
1859   }
1860  
1861   if (ctype_isUnknown (ctypeType)) {
1862     if (usymtab_existsType (cstring_makeLiteralTemp ("ctype")))
1863       {
1864         ctypeType = usymtab_lookupAbstractType (cstring_makeLiteralTemp ("ctype"));
1865       }
1866   }
1867
1868   if (ctype_isUnknown (filelocType)) {
1869     if (usymtab_existsType (cstring_makeLiteralTemp ("fileloc")))
1870       {
1871         filelocType = usymtab_lookupAbstractType (cstring_makeLiteralTemp ("fileloc"));
1872       }
1873   }
1874
1875   if (exprNode_isDefined (a) && exprNode_isStringLiteral (a) 
1876       && exprNode_knownStringValue (a))
1877     {
1878       cstring format = multiVal_forceString (exprNode_getValue (a));
1879       char *code = cstring_toCharsSafe (format);
1880       char *ocode = code;
1881
1882       nargs = exprNodeList_size (args);
1883
1884       while ((code = strchr (code, '%')) != NULL)
1885         {
1886           char *origcode = code;
1887           char key = *(++code);                 
1888           bool isOnly = FALSE;
1889
1890           fileloc_addColumn (formatloc, code - ocode);
1891
1892           while (key >= '0' && key <= '9')
1893             {
1894               key = *(++code);
1895               fileloc_incColumn (formatloc);
1896             }
1897           
1898           ++code;
1899           fileloc_incColumn (formatloc);
1900
1901           if (key != '%') 
1902             {
1903               if (key == 'p')
1904                 {
1905                   goto nextKey;
1906                 }
1907
1908               if (i >= nargs)
1909                 {
1910                   voptgenerror
1911                     (FLG_TYPE,
1912                      message ("Message missing format arg %d (%%%h): \"%s\"",
1913                               i + 1, key, format), 
1914                      f->loc);
1915                   i++;
1916                 }
1917               else
1918                 {
1919                   a = exprNodeList_getN (args, i);
1920                   i++;
1921                   
1922                 nextKey:
1923                   if (!exprNode_isError (a))
1924                     {
1925                       ctype expecttype;
1926                       
1927                       /*@-loopswitchbreak@*/
1928
1929                       switch (key)
1930                         {
1931                         case 'c':
1932                         case 'h': 
1933                           expecttype = ctype_char; break;
1934                         case 's': 
1935                           expecttype = cstringType; break;
1936                         case 'q': 
1937                           expecttype = cstringType; isOnly = TRUE; break;
1938                         case 'x': 
1939                           expecttype = cstringType; isOnly = TRUE; break;
1940                         case 'd': expecttype = ctype_int; break;
1941                         case 'u': expecttype = ctype_uint; break;
1942                         case 'w': expecttype = ctype_ulint; break;
1943                         case 'f': expecttype = ctype_float; break;
1944                         case 'b': expecttype = ctype_bool; break;
1945                         case 't': expecttype = ctypeType; break;
1946                         case 'l': expecttype = filelocType; break;
1947                         case 'p':  /* a wee bit of a hack methinks */
1948                           expecttype = ctype_int;
1949                           break;
1950                         case 'r': expecttype = ctype_bool; break;
1951                         default:  
1952                           expecttype = ctype_unknown;
1953                           voptgenerror
1954                             (FLG_FORMATCODE,
1955                              message ("Unrecognized format code: %s", 
1956                                       cstring_fromChars (origcode)),
1957                              fileloc_isDefined (formatloc) 
1958                              ? formatloc : g_currentloc);
1959                           break;
1960                         }
1961                       /*@=loopswitchbreak@*/
1962
1963                       if (!(exprNode_matchArgType (expecttype, a)))
1964                         {
1965                           if (ctype_isVoidPointer (expecttype) 
1966                               && ctype_isRealAbstract (a->typ)
1967                               && (context_getFlag (FLG_ABSTVOIDP)))
1968                             {
1969                               ;
1970                             }
1971                           else
1972                             {
1973                               if (llgenformattypeerror 
1974                                   (expecttype, exprNode_undefined,
1975                                    a->typ, a,
1976                                    message ("Format argument %d to %q (%%%h) expects "
1977                                             "%t gets %t: %s",
1978                                             i - argno,
1979                                             uentry_getName (fcn), 
1980                                             key, expecttype,
1981                                             a->typ, exprNode_unparse (a)),
1982                                    a->loc))
1983                                   {
1984                                   if (fileloc_isDefined (formatloc)
1985                                       && context_getFlag (FLG_SHOWCOL))
1986                                     {
1987                                       llgenindentmsg
1988                                         (cstring_makeLiteral 
1989                                          ("Corresponding format code"),
1990                                          formatloc);
1991                                     }
1992                                 }
1993                             }
1994                         }
1995                       
1996                       if (ctype_equal (expecttype, cstringType))
1997                         {
1998                           if (isOnly)
1999                             {
2000                               checkOneArg (csOnlyArg, a, f, FALSE, i+1, nargs);
2001                               uentry_fixupSref (csOnlyArg);
2002                             }
2003                           else
2004                             {
2005                               checkOneArg (csArg, a, f, FALSE, i+1, nargs);
2006                               uentry_fixupSref (csArg);
2007                             }
2008                         }
2009                       else
2010                         {
2011                                                   checkOneArg (regArg, a, f, FALSE, i+1, nargs);
2012                           uentry_fixupSref (regArg);
2013                         }
2014                     }
2015                 }
2016             }
2017         }
2018
2019       if (i < nargs)
2020         {
2021           voptgenerror (FLG_TYPE,
2022                         message ("Format string for %q has %d arg%p, given %d", 
2023                                  uentry_getName (fcn), i - argno, nargs -argno),
2024                         f->loc);
2025         }
2026     }
2027   else
2028     {
2029       /* no checking possible for compile-time unknown format strings */
2030     }
2031
2032   fileloc_free (formatloc);
2033 }
2034
2035 static void
2036   checkExpressionDefinedAux (/*@notnull@*/ exprNode e1, 
2037                              /*@notnull@*/ exprNode e2, 
2038                              sRefSet sets1,
2039                              sRefSet sets2, 
2040                              lltok op,
2041                              flagcode flag)
2042 {
2043   bool hadUncon = FALSE;
2044
2045   if (sRef_isGlobal (sRef_getRootBase (e1->sref)) && 
2046       sRefSet_hasUnconstrained (sets2))
2047     {
2048       voptgenerror
2049         (FLG_EVALORDERUNCON,
2050          message
2051          ("Expression may have undefined behavior (%q used in right operand "
2052           "may set global variable %q used in left operand): %s %s %s", 
2053           sRefSet_unparseUnconstrained (sets2),
2054           sRef_unparse (sRef_getRootBase (e1->sref)),
2055           exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
2056          e2->loc);
2057     }
2058
2059   if (sRef_isGlobal (sRef_getRootBase (e2->sref)) && 
2060       sRefSet_hasUnconstrained (sets1))
2061     {
2062       voptgenerror
2063         (FLG_EVALORDERUNCON,
2064          message
2065          ("Expression has undefined behavior (%q used in left operand "
2066           "may set global variable %q used in right operand): %s %s %s", 
2067           sRefSet_unparseUnconstrained (sets1),
2068           sRef_unparse (e2->sref),
2069           exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
2070          e2->loc);
2071     }
2072
2073   sRefSet_realElements (e1->uses, sr)
2074     {
2075       if (sRef_isMeaningful (sr) && sRefSet_member (sets2, sr))
2076         {
2077           voptgenerror
2078             (FLG_EVALORDER,
2079              message
2080              ("Expression has undefined behavior (left operand uses %q, "
2081               "modified by right operand): %s %s %s", 
2082               sRef_unparse (sr),
2083               exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
2084              e2->loc);
2085         }
2086     } end_sRefSet_realElements;
2087   
2088   sRefSet_realElements (sets1, sr)
2089     {
2090       if (sRef_isMeaningful (sr))
2091         {
2092           if (sRef_same (sr, e2->sref))
2093             {
2094               voptgenerror
2095                 (flag,
2096                  message
2097                  ("Expression has undefined behavior (value of right operand "
2098                   "modified by left operand): %s %s %s", 
2099                   exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
2100                  e2->loc);
2101             }
2102           else if (sRefSet_member (e2->uses, sr))
2103             {
2104               voptgenerror
2105                 (flag,
2106                  message 
2107                  ("Expression has undefined behavior (left operand modifies %q, "
2108                   "used by right operand): %s %s %s", 
2109                   sRef_unparse (sr),
2110                   exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
2111                  e2->loc);
2112             }
2113           else 
2114             {
2115               if (sRefSet_member (sets2, sr))
2116                 {
2117                   if (sRef_isUnconstrained (sr))
2118                     {
2119                       if (hadUncon)
2120                         {
2121                           ;
2122                         }
2123                       else
2124                         {
2125                           hadUncon = optgenerror
2126                             (FLG_EVALORDERUNCON,
2127                              message 
2128                              ("Expression may have undefined behavior.  Left operand "
2129                               "calls %q; right operand calls %q.  The unconstrained "
2130                               "functions may modify global state used by "
2131                               "the other operand): %s %s %s", 
2132                               sRefSet_unparseUnconstrained (sets1),
2133                               sRefSet_unparseUnconstrained (sets2),
2134                               exprNode_unparse (e1), lltok_unparse (op),
2135                               exprNode_unparse (e2)),
2136                              e2->loc);
2137                         }
2138                     }
2139                   else
2140                     {
2141                       voptgenerror
2142                         (flag,
2143                          message 
2144                          ("Expression has undefined behavior (both "
2145                           "operands modify %q): %s %s %s", 
2146                           sRef_unparse (sr), 
2147                           exprNode_unparse (e1), 
2148                           lltok_unparse (op), exprNode_unparse (e2)),
2149                          e2->loc);
2150                     }
2151                 }
2152             }
2153         }
2154     } end_sRefSet_realElements;
2155 }
2156
2157 static void checkExpressionDefined (exprNode e1, exprNode e2, lltok op)
2158 {
2159   bool hasError = FALSE;
2160   
2161   if (exprNode_isError (e1) || exprNode_isError (e2))
2162     {
2163       return;
2164     }
2165
2166   if (sRefSet_member (e2->sets, e1->sref))
2167     {
2168       if (e2->kind == XPR_CALL)
2169         {
2170          ;
2171         }
2172       else
2173         {
2174           hasError = optgenerror 
2175             (FLG_EVALORDER,
2176              message ("Expression has undefined behavior "
2177                       "(value of left operand is modified "
2178                       "by right operand): %s %s %s", 
2179                       exprNode_unparse (e1), lltok_unparse (op),
2180                       exprNode_unparse (e2)),
2181              e2->loc);
2182         }
2183     }
2184
2185   if (context_getFlag (FLG_EVALORDERUNCON))
2186     {
2187       if (sRefSet_member (e2->msets, e1->sref))
2188         {
2189           if (e2->kind == XPR_CALL)
2190             {
2191               ;
2192             }
2193           else
2194             {
2195               hasError = optgenerror 
2196                 (FLG_EVALORDER,
2197                  message 
2198                  ("Expression has undefined behavior (value of left "
2199                   "operand may be modified by right operand): %s %s %s", 
2200                   exprNode_unparse (e1), lltok_unparse (op),
2201                   exprNode_unparse (e2)),
2202                  e2->loc);
2203             }
2204         }
2205     }
2206   
2207   if (!hasError)
2208     {
2209       checkExpressionDefinedAux (e1, e2, e1->sets, e2->sets, op, FLG_EVALORDER);
2210       
2211       if (context_maybeSet (FLG_EVALORDERUNCON))
2212         {
2213           checkExpressionDefinedAux (e1, e2, e1->msets, 
2214                                      e2->msets, op, FLG_EVALORDERUNCON);
2215         }
2216     }
2217 }
2218
2219 static void checkSequencing (exprNode p_f, exprNodeList p_args); 
2220
2221 static int
2222   checkArgsReal (uentry fcn, /*@dependent@*/ exprNode f, uentryList cl, 
2223                  exprNodeList args, bool isIter, exprNode ret)
2224 {
2225   int special = 0;
2226
2227   if (!exprNode_isError (f))
2228     {
2229       if (!uentryList_isMissingParams (cl))
2230         {
2231           int nargs = exprNodeList_size (args);
2232           int expectargs = uentryList_size (cl);
2233           ctype last;
2234           int i = 0;
2235           
2236           if (expectargs == 0)
2237             {
2238               if (nargs != 0)
2239                 {
2240                   if (isIter)
2241                     {
2242                       voptgenerror
2243                         (FLG_TYPE,
2244                          message ("Iter %q invoked with %d args, "
2245                                   "declared void",
2246                                   uentry_getName (fcn),
2247                                   nargs),
2248                          f->loc);
2249                     }
2250                   else
2251                     {
2252                       voptgenerror 
2253                         (FLG_TYPE,
2254                          message ("Function %s called with %d args, "
2255                                   "declared void", 
2256                                   exprNode_unparse (f), nargs),
2257                          f->loc);
2258                     }
2259                 }
2260               return special;
2261             }
2262           
2263           last = uentry_getType (uentryList_getN (cl, expectargs - 1));
2264           
2265           exprNodeList_reset (args);
2266           
2267           uentryList_elements (cl, current)
2268             {
2269               ctype ct = uentry_getType (current);
2270               exprNode a;
2271               
2272               if (ctype_isElips (ct))
2273                 {
2274                   /*
2275                    ** do special checking for printf/scanf library functions
2276                    **
2277                    ** this is kludgey code, just for handling the special case
2278                    **
2279                    */
2280
2281                   if (uentry_isPrintfLike (fcn))
2282                     {
2283                       checkPrintfArgs (f, fcn, args, ret, i);
2284                       special = i;
2285                     }
2286                   else if (uentry_isScanfLike (fcn))
2287                     {
2288                       checkScanfArgs (f, fcn, args, ret, i); 
2289                       special = i;
2290                     }
2291                   else if (uentry_isMessageLike (fcn))
2292                     {
2293                       checkMessageArgs (f, fcn, args, i);
2294                       special = i;
2295                     }
2296                   else
2297                     {
2298                       llassert (!uentry_isSpecialFunction (fcn));
2299                     }
2300                     
2301                   nargs = expectargs; /* avoid errors */
2302                   break;
2303                 }
2304               else
2305                 {
2306                   if (i >= nargs) break;
2307                   
2308                   a = exprNodeList_current (args);
2309                   exprNodeList_advance (args);
2310                   
2311                   i++;
2312                   
2313                   if (exprNode_isError (a))
2314                     {
2315                      ;
2316                     }
2317                   else
2318                     {
2319                       /* 
2320                         probably necessary? I'm not sure about this one
2321                         checkMacroParen (a);
2322                         */
2323                       
2324                       f->guards = guardSet_union (f->guards, a->guards);
2325                       
2326                       DPRINTF (("match arg: %s / %s", ctype_unparse (ct), ctype_unparse (a->typ)));
2327
2328                       if (!(exprNode_matchArgType (ct, a)))
2329                         {
2330                           DPRINTF (("Args mismatch!"));
2331
2332                           if (ctype_isVoidPointer (ct) 
2333                               && (ctype_isPointer (a->typ) 
2334                                   && (ctype_isRealAbstract (ctype_baseArrayPtr (a->typ)))))
2335                             {
2336                               vnoptgenerror 
2337                                 (FLG_ABSTVOIDP,
2338                                  message 
2339                                  ("Pointer to abstract type (%t) used "
2340                                   "as void pointer "
2341                                   "(arg %d to %q): %s",
2342                                   a->typ, i, 
2343                                   uentry_getName (fcn), 
2344                                   exprNode_unparse (a)),
2345                                  a->loc);
2346                             }
2347                           else
2348                             {
2349                               if (isIter)
2350                                 {
2351                                   (void) gentypeerror 
2352                                     (ct, exprNode_undefined,
2353                                      a->typ, a,
2354                                      message 
2355                                      ("Iter %q expects arg %d to "
2356                                       "be %t gets %t: %s",
2357                                       uentry_getName (fcn),
2358                                       i, ct, a->typ, exprNode_unparse (a)),
2359                                      a->loc);
2360                                 }
2361                               else
2362                                 {
2363                                   if (gentypeerror  
2364                                       (ct, 
2365                                        exprNode_undefined,
2366                                        a->typ,
2367                                        a,
2368                                        message 
2369                                        ("Function %q expects arg %d to be %t gets %t: %s",
2370                                         uentry_getName (fcn),
2371                                         i, ct, a->typ, exprNode_unparse (a)),
2372                                        a->loc))
2373                                     {
2374                                       DPRINTF (("Types: %s / %s",
2375                                                 ctype_unparse (ct),
2376                                                 ctype_unparse (a->typ)));
2377                                     }
2378
2379                                   /*
2380                                   ** Clear null marker for abstract types.
2381                                   ** (It is not revealed, so suppress future messages.)
2382                                   */
2383
2384                                   if (ctype_isAbstract (a->typ))
2385                                     {
2386                                       sRef_setNullUnknown (exprNode_getSref (a), a->loc);
2387                                     }
2388                                 }
2389                             }
2390                         }
2391                     }
2392                 }
2393             } end_uentryList_elements ;
2394           
2395           
2396           if (expectargs != nargs) /* note: not != since we may have ... */
2397             {
2398               if (ctype_isElips (last))
2399                 {
2400                   voptgenerror
2401                     (FLG_TYPE,
2402                      message ("Function %s called with %d args, expects at least %d",
2403                               exprNode_unparse (f),
2404                               nargs, expectargs - 1),
2405                      f->loc);
2406                 }
2407               else
2408                 {
2409                   if (isIter)
2410                     {
2411                       voptgenerror 
2412                         (FLG_TYPE,
2413                          message ("Iter %q invoked with %d args, expects %d",
2414                                   uentry_getName (fcn), nargs, expectargs),
2415                          f->loc);
2416                     }
2417                   else
2418                     {
2419                       voptgenerror 
2420                         (FLG_TYPE,
2421                          message ("Function %s called with %d args, expects %d",
2422                                   exprNode_unparse (f),
2423                                   nargs, expectargs),
2424                          f->loc);
2425                     }
2426                 }
2427             }
2428         }
2429     }
2430
2431   return special;
2432 }
2433
2434 /*
2435 ** Check for undefined code sequences in function arguments:
2436 **
2437 **   one parameter sets something used by another parameter
2438 **   one parameter sets something set  by another parameter
2439 */
2440
2441 static void 
2442 checkSequencingOne (exprNode f, exprNodeList args, 
2443                     /*@notnull@*/ exprNode el, int argno)
2444 {
2445   /*
2446   ** Do second loop, iff +undefunspec
2447   */
2448
2449   int checkloop;
2450   int numloops = context_maybeSet (FLG_EVALORDERUNCON) ? 2 : 1;
2451   
2452   for (checkloop = 0; checkloop < numloops; checkloop++)
2453     {
2454       sRefSet thissets;
2455
2456       if (checkloop == 0)
2457         {
2458           thissets = el->sets;
2459         }
2460       else
2461         {
2462           llassert (checkloop == 1);
2463           thissets = el->msets;
2464         }
2465       
2466       sRefSet_realElements (thissets, thisset)
2467         {
2468           int j;
2469
2470           /*@access exprNodeList@*/
2471           for (j = 0; j < args->nelements; j++)
2472             {
2473               exprNode jl = args->elements[j];
2474               int thisargno = j + 1;
2475
2476               if (thisargno != argno && exprNode_isDefined (jl))
2477                 {
2478                   sRefSet otheruses = jl->uses;
2479                   
2480                   if (sRef_isGlobal (sRef_getRootBase (jl->sref)) && 
2481                       sRefSet_hasUnconstrained (thissets))
2482                     {
2483                       voptgenerror
2484                         (FLG_EVALORDERUNCON,
2485                          /*@-sefparams@*/
2486                          message
2487                          ("%q used in argument %d may set "
2488                           "global variable %q used by argument %d: %s(%q)", 
2489                           cstring_capitalizeFree (sRefSet_unparseUnconstrained (thissets)),
2490                           /*@=sefparams@*/
2491                           argno,
2492                           sRef_unparse (sRef_getRootBase (jl->sref)),
2493                           thisargno,
2494                           exprNode_unparse (f), exprNodeList_unparse (args)),
2495                          el->loc);
2496                     }
2497
2498                   if (sRefSet_member (otheruses, thisset))
2499                     {
2500                       if (sRef_isUnconstrained (thisset))
2501                         {
2502                           voptgenerror 
2503                             (FLG_EVALORDERUNCON,
2504                              message 
2505                              ("Unconstrained functions used in arguments %d (%q) "
2506                               "and %d (%s) may modify "
2507                               "or use global state in undefined way: %s(%q)",
2508                               argno,
2509                               sRefSet_unparseUnconstrainedPlain (otheruses),
2510                               thisargno, 
2511                               sRef_unconstrainedName (thisset),
2512                               exprNode_unparse (f), 
2513                               exprNodeList_unparse (args)),
2514                              el->loc);
2515                         }
2516                       else
2517                         {
2518                           voptgenerror 
2519                             (FLG_EVALORDER,
2520                              message 
2521                              ("Argument %d modifies %q, used by argument %d "
2522                               "(order of evaluation of actual parameters is "
2523                               "undefined): %s(%q)",
2524                               argno, sRef_unparse (thisset), thisargno, 
2525                               exprNode_unparse (f), exprNodeList_unparse (args)),
2526                              el->loc);
2527                         }
2528                     }
2529                   else 
2530                     {
2531                       sRefSet othersets = jl->sets;
2532                       
2533                       if (sRefSet_member (othersets, thisset))
2534                         {
2535                           if (sRef_isUnconstrained (thisset))
2536                             {
2537                               voptgenerror 
2538                                 (FLG_EVALORDERUNCON,
2539                                  message 
2540                                  ("Unconstrained functions used in "
2541                                   "arguments %d (%q) and %d (%s) may modify "
2542                                   "or use global state in undefined way: %s(%q)",
2543                                   argno, 
2544                                   sRefSet_unparseUnconstrainedPlain (othersets),
2545                                   thisargno, 
2546                                   sRef_unconstrainedName (thisset),
2547                                   exprNode_unparse (f), exprNodeList_unparse (args)),
2548                                  el->loc);
2549                             }
2550                           else
2551                             {
2552                               voptgenerror 
2553                                 (FLG_EVALORDER,
2554                                  message 
2555                                  ("Argument %d modifies %q, set by argument %d (order of"
2556                                   " evaluation of actual parameters is undefined): %s(%q)",
2557                                   argno, sRef_unparse (thisset), thisargno, 
2558                                   exprNode_unparse (f), exprNodeList_unparse (args)),
2559                                  el->loc);
2560                             }
2561                         }
2562                     }
2563                 }
2564             }
2565           /*@noaccess exprNodeList@*/
2566         } end_sRefSet_realElements;
2567     }
2568 }
2569
2570 static void
2571 checkSequencing (exprNode f, exprNodeList args)
2572 {
2573   if (exprNodeList_size (args) > 1)
2574     {
2575       int i;
2576       exprNode el;
2577       
2578       /*@access exprNodeList*/
2579       
2580       for (i = 0; i < args->nelements; i++)
2581         {
2582           el = args->elements[i];
2583           
2584           if (!exprNode_isError (el))
2585             {
2586               checkSequencingOne (f, args, el, i + 1);
2587             }
2588         }
2589       /*@noaccess exprNodeList*/
2590     }
2591 }
2592
2593 /*
2594 ** requires le = exprNode_getUentry (f) 
2595 */
2596
2597 static void
2598 checkGlobMods (/*@notnull@*/ /*@dependent@*/ exprNode f,
2599                uentry le, exprNodeList args, 
2600                /*@notnull@*/ exprNode ret, int specialArgs)
2601 {
2602   bool isSpec = FALSE;
2603   bool hasMods = FALSE;
2604   cstring fname;
2605   globSet usesGlobs = globSet_undefined;
2606   sRefSet mods = sRefSet_undefined;
2607   bool freshMods = FALSE;
2608   uentryList params = uentryList_undefined;
2609
2610   /*
2611   ** check globals and modifies
2612   */
2613
2614   setCodePoint ();
2615   
2616   if (!uentry_isValid (le))
2617     {
2618       ctype fr = ctype_realType (f->typ);
2619
2620       if (ctype_isFunction (fr))
2621         {
2622           params = ctype_argsFunction (fr);
2623         }
2624       else
2625         {
2626           params = uentryList_missingParams;
2627         }
2628
2629       if (!context_getFlag (FLG_MODNOMODS) 
2630           && !context_getFlag (FLG_GLOBUNSPEC))
2631         {
2632                     checkUnspecCall (f, params, args);
2633         }
2634       
2635       return;
2636     }
2637
2638   fname = uentry_rawName (le);
2639
2640   setCodePoint ();
2641
2642   if (uentry_isFunction (le))
2643     {
2644       params = uentry_getParams (le);
2645       mods = uentry_getMods (le);
2646       hasMods = uentry_hasMods (le);
2647       usesGlobs = uentry_getGlobs (le);
2648       isSpec = uentry_isSpecified (le);
2649     }
2650   else /* not a function */
2651     {
2652       ctype ct = ctype_realType (uentry_getType (le));
2653       
2654       llassertprint (uentry_isVar (le) && ctype_isFunction (ct),
2655                      ("checkModGlobs: uentry not a function: %s", 
2656                       uentry_unparse (le)));
2657       
2658       params = ctype_argsFunction (ct);
2659     }
2660
2661   /*
2662   ** check globals
2663   */
2664
2665   setCodePoint ();
2666
2667     
2668   globSet_allElements (usesGlobs, el)
2669     {
2670       if (sRef_isValid (el))
2671         {
2672           if (sRef_isInternalState (el) || sRef_isSystemState (el))
2673             {
2674               context_usedGlobal (el);
2675               exprNode_checkUse (f, el, f->loc);
2676
2677               if (context_checkInternalUse ())
2678                 {
2679                   if (!context_globAccess (el))
2680                     {
2681                       if (sRef_isSystemState (el)
2682                           && !context_getFlag (FLG_MODFILESYSTEM))
2683                         {
2684                           ;
2685                         }
2686                       else
2687                         {
2688                           voptgenerror
2689                             (FLG_INTERNALGLOBS,
2690                              message 
2691                              ("Called procedure %s may access %q, but "
2692                               "globals list does not include globals %s",
2693                               exprNode_unparse (f),
2694                               sRef_unparse (el),
2695                               cstring_makeLiteralTemp (sRef_isInternalState (el)
2696                                                        ? "internalState"
2697                                                        : "fileSystem")),
2698                              f->loc);
2699                         }
2700                     }
2701                 }
2702             }
2703           else if (sRef_isNothing (el) || sRef_isSpecState (el))
2704             {
2705               ;
2706             }
2707           else
2708             {
2709               uentry gle = sRef_getUentry (el);
2710               sRef sr = sRef_updateSref (el);
2711               
2712               if (sRef_isUndefGlob (el))
2713                 {
2714                   sRef_setDefined (sr, f->loc);
2715                   exprNode_checkSet (f, sr);
2716                 }
2717               else
2718                 {
2719                   /*
2720                   ** check definition
2721                   */
2722                   
2723                   if (sRef_isAllocated (el))
2724                     {
2725                       exprNode_checkSet (f, sr);
2726                     }
2727                   else
2728                     {
2729                       if (sRef_isStateUndefined (sr))
2730                         {
2731                           voptgenerror 
2732                             (FLG_GLOBSTATE,
2733                              message
2734                              ("%s %q used by function undefined before call: %s",
2735                               sRef_getScopeName (sr),
2736                               sRef_unparse (sr),
2737                               exprNode_unparse (f)),
2738                              f->loc);
2739                           sRef_setDefined (sr, f->loc);
2740                         }
2741                       exprNode_checkUse (f, sr, f->loc);
2742                     }
2743                   
2744                   checkGlobUse (gle, TRUE, f);
2745                 }
2746           
2747               if (sRef_isKilledGlob (el))
2748                 {
2749                   sRef_kill (sr, f->loc);
2750                   context_usedGlobal (sr);
2751                 }
2752             }
2753         }
2754     } end_globSet_allElements;
2755   
2756   /*
2757   ** check modifies
2758   */
2759
2760   if (context_hasMods () || context_getFlag (FLG_MODNOMODS))
2761     {
2762       sRefSet smods = sRefSet_undefined;
2763
2764       /*
2765       ** NEED to check for modifies anything
2766       */
2767
2768       /*
2769       ** check each sRef that called function modifies (ml), is
2770       ** modifiable by tl
2771       */
2772
2773       setCodePoint ();
2774
2775       sRefSet_allElements (mods, s) /* s is something which may be modified */
2776         {
2777           if (sRef_isKindSpecial (s))
2778             {
2779               if (sRef_isSpecInternalState (s))
2780                 {
2781                   if (context_getFlag (FLG_MODINTERNALSTRICT))
2782                     {
2783                       exprNode_checkCallModifyVal (s, args, f, ret);
2784                     }
2785                   else
2786                     {
2787                       sRefSet mmods = context_modList ();
2788
2789                       sRefSet_allElements (mmods, el)
2790                         {
2791                           if (sRef_isInternalState (el))
2792                             {
2793                               sRef_setModified (el);
2794                             }
2795                         } end_sRefSet_allElements ;
2796                     }
2797                 }
2798               else
2799                 {
2800                   exprNode_checkCallModifyVal (s, args, f, ret);
2801                 }
2802             }
2803           else
2804             {
2805               sRef rb = sRef_getRootBase (s);
2806               
2807               if (sRef_isGlobal (rb))
2808                 {
2809                   context_usedGlobal (rb);
2810                 }
2811               
2812               if (sRef_isFileStatic (s)
2813                   && !fileId_equal (fileloc_fileId (f->loc), 
2814                                     fileloc_fileId (uentry_whereDefined (le))))
2815                 {
2816                   smods = sRefSet_insert (smods, s);
2817                 }
2818               else
2819                 {
2820                   exprNode_checkCallModifyVal (s, args, f, ret);
2821                 }
2822             }
2823         } end_sRefSet_allElements;
2824
2825       setCodePoint ();
2826
2827       /*
2828       ** Static elements in modifies set can have nasty consequences.
2829       ** (I think...have not been able to reproduce a possible bug.)
2830       */
2831
2832       if (!sRefSet_isDefined (smods))
2833         {
2834           mods = sRefSet_newCopy (mods);
2835           freshMods = TRUE;
2836           
2837           sRefSet_allElements (smods, el)
2838             {
2839               bool res = sRefSet_delete (mods, el);
2840               
2841               llassert (res);
2842             } end_sRefSet_allElements;
2843
2844           sRefSet_free (smods);
2845         /*@-branchstate@*/
2846         } 
2847       /*@=branchstate@*/
2848     }
2849   else if (sRefSet_isDefined (mods))
2850     { /* just check observers */
2851       setCodePoint ();
2852
2853       sRefSet_allElements (mods, s) /* s is something which may be modified */
2854         {
2855           sRef rb = sRef_getRootBase (s);
2856
2857           setCodePoint ();
2858
2859           if (sRef_isParam (rb))
2860             {
2861               sRef b = sRef_fixBaseParam (s, args);
2862
2863               if (sRef_isObserver (b))
2864                 {
2865                   exprNode e = exprNodeList_nth (args, sRef_getParam (rb));
2866                   
2867                   if (optgenerror 
2868                       (FLG_MODOBSERVER,
2869                        message ("Function call may modify observer%q: %s", 
2870                                 sRef_unparsePreOpt (b), exprNode_unparse (e)),
2871                        exprNode_loc (e)))
2872                     {
2873                       sRef_showExpInfo (b);
2874                     }
2875                 }
2876             }
2877         } end_sRefSet_allElements;
2878     }
2879   else 
2880     {
2881       if (!hasMods) /* no specified modifications */
2882         {
2883           if (context_getFlag (FLG_MODOBSERVERUNCON))
2884             {
2885               exprNodeList_elements (args, e)
2886                 {
2887                   if (exprNode_isDefined (e))
2888                     {
2889                       sRef s = exprNode_getSref (e);
2890                       
2891                       if (sRef_isObserver (s) 
2892                           && ctype_isMutable (sRef_getType (s)))
2893                         {
2894                           if (optgenerror 
2895                               (FLG_MODOBSERVERUNCON,
2896                                message
2897                                ("Call to unconstrained function %s may modify observer%q: %s", 
2898                                 exprNode_unparse (f),
2899                                 sRef_unparsePreOpt (s), exprNode_unparse (e)),
2900                                exprNode_loc (e)))
2901                             {
2902                               sRef_showExpInfo (s);
2903                             }
2904                         }
2905                     }
2906                 } end_exprNodeList_elements; 
2907             }
2908         }
2909     }
2910   
2911   checkAnyCall (f, fname, params, args, hasMods, mods, isSpec, specialArgs);
2912
2913   ret->uses = sRefSet_union (ret->uses, f->uses);
2914   ret->sets = sRefSet_union (ret->sets, f->sets);
2915   ret->msets = sRefSet_union (ret->msets, f->msets);
2916
2917   if (freshMods)
2918     {
2919       /*
2920       ** Spurious errors reported, because lclint can't tell
2921       ** mods must be fresh if freshMods is true.
2922       */
2923
2924       /*@i@*/ sRefSet_free (mods);
2925     }
2926
2927   setCodePoint ();
2928 }
2929
2930 void checkGlobUse (uentry glob, bool isCall, /*@notnull@*/ exprNode e)
2931 {
2932   if (uentry_isVar (glob))
2933     {
2934       if (context_inFunctionLike ())
2935         {
2936           sRef sr = uentry_getSref (glob);
2937
2938           context_usedGlobal (sr);
2939           
2940           if (context_checkGlobUse (glob))
2941             {
2942               if (!context_globAccess (sr))
2943                 {
2944                   if (isCall)
2945                     {
2946                       voptgenerror
2947                         (FLG_GLOBALS,
2948                          message ("Called procedure %s may access %s %q",
2949                                   exprNode_unparse (e), 
2950                                   sRef_unparseScope (sr),
2951                                   uentry_getName (glob)),
2952                          e->loc);
2953                     }
2954                   else
2955                     {
2956                       voptgenerror 
2957                         (FLG_GLOBALS,
2958                          message ("Undocumented use of %s %s", 
2959                                   sRef_unparseScope (sr),
2960                                   exprNode_unparse (e)),
2961                          e->loc);
2962                     }
2963                 }
2964             }
2965         }
2966     }
2967   else
2968     {
2969       llbug (message ("Global not variable: %q", uentry_unparse (glob)));
2970     }
2971 }  
2972
2973 static /*@only@*/ exprNode
2974 functionCallSafe (/*@only@*/ /*@notnull@*/ exprNode f,
2975                   ctype t, /*@keep@*/ exprNodeList args)
2976 {
2977   /* requires f is a non-error exprNode, with type function */
2978   cstring fname = exprNode_unparse (f);
2979   uentry le = exprNode_getUentry (f);
2980   exprNode ret = exprNode_createPartialCopy (f);
2981   int special;
2982
2983   setCodePoint ();
2984         
2985   ret->typ = ctype_returnValue (t);
2986   ret->kind = XPR_CALL;
2987
2988   ret->edata = exprData_makeCall (f, args);
2989
2990   /*
2991   ** Order of these steps is very important!  
2992   **
2993   ** Must check for argument dependencies before messing up uses and sets.
2994   */
2995
2996   if (context_getFlag (FLG_EVALORDER))
2997     {
2998       exprNodeList_elements (args, current)
2999         {
3000           if (exprNode_isDefined (current))
3001             {
3002               exprNode_addUse (current, current->sref);
3003             }
3004         } end_exprNodeList_elements;
3005
3006       if (context_maybeSet (FLG_EVALORDER) || context_maybeSet (FLG_EVALORDERUNCON))
3007         {
3008           checkSequencing (f, args); 
3009         }
3010       
3011       exprNodeList_elements (args, current)
3012         {
3013           if (exprNode_isDefined (current) && sRef_isMeaningful (current->sref))
3014             {
3015               exprNode_addUse (ret, sRef_makeDerived (current->sref));
3016             }
3017         } end_exprNodeList_elements ;
3018     }
3019
3020   special = checkArgs (le, f, t, args, ret); 
3021   checkGlobMods (f, le, args, ret, special); 
3022
3023   setCodePoint ();
3024
3025   if (uentry_isValid (le)
3026       && (uentry_isFunction (le) 
3027           || (uentry_isVariable (le)
3028               && ctype_isFunction (uentry_getType (le)))))
3029     {
3030       exitkind exk = uentry_getExitCode (le);
3031
3032       /* f->typ is already set to the return type */
3033
3034       ret->sref = uentry_returnedRef (le, args);
3035
3036       if (uentry_isFunction (le) && exprNodeList_size (args) >= 1)
3037         {
3038           qual nullPred = uentry_nullPred (le);
3039
3040           if (qual_isTrueNull (nullPred))
3041             {
3042               exprNode arg = exprNodeList_head (args);
3043
3044               if (exprNode_isDefined (arg))
3045                 {
3046                   ret->guards = guardSet_addFalseGuard (ret->guards, arg->sref);
3047                 }
3048             }
3049           else if (qual_isFalseNull (nullPred))
3050             {
3051               exprNode arg = exprNodeList_head (args);
3052               
3053               if (exprNode_isDefined (arg))
3054                 {
3055                   ret->guards = guardSet_addTrueGuard (ret->guards, arg->sref);
3056                 }
3057             }
3058           else
3059             {
3060               llassert (qual_isUnknown (nullPred));
3061             }
3062         }
3063       
3064       if (exitkind_isConditionalExit (exk))
3065         {
3066           /*
3067           ** True exit is: 
3068           **    if (arg0) then { exit! } else { ; }
3069           ** False exit is:
3070           **    if (arg0) then { ; } else { exit! }
3071           */
3072
3073           exprNode firstArg;
3074
3075           llassert (!exprNodeList_isEmpty (args));
3076           firstArg = exprNodeList_head (args);
3077
3078           if (exprNode_isDefined (firstArg)
3079               && !guardSet_isEmpty (firstArg->guards))
3080             {
3081               usymtab_trueBranch (guardSet_undefined);
3082               usymtab_altBranch (guardSet_undefined);
3083               
3084               if (exitkind_isTrueExit (exk))
3085                 {
3086                   usymtab_popBranches (firstArg, 
3087                                        exprNode_makeMustExit (), 
3088                                        exprNode_undefined,
3089                                        TRUE, TRUEEXITCLAUSE);
3090                 }
3091               else
3092                 {
3093                   usymtab_popBranches (firstArg,
3094                                        exprNode_undefined,
3095                                        exprNode_makeMustExit (), 
3096                                        TRUE, FALSEEXITCLAUSE);
3097                 }
3098             }
3099
3100           ret->exitCode = XK_MAYEXIT;
3101         }
3102       else if (exitkind_mustExit (exk))
3103         {
3104           ret->exitCode = XK_MUSTEXIT;
3105         }
3106       else if (exitkind_couldExit (exk))
3107         {
3108           ret->exitCode = XK_MAYEXIT;
3109         }
3110       else
3111         {
3112           ;
3113         }
3114       
3115       if (cstring_equalLit (fname, "exit"))
3116         {
3117           if (exprNodeList_size (args) == 1)
3118             {
3119               exprNode arg = exprNodeList_head (args);
3120               
3121               if (exprNode_isDefined (arg) && exprNode_knownIntValue (arg))
3122                 {
3123                   long int val = multiVal_forceInt (exprNode_getValue (arg));
3124                   
3125                   if (val != 0)
3126                     {
3127                       voptgenerror
3128                         (FLG_EXITARG,
3129                          message 
3130                          ("Argument to exit has implementation defined behavior: %s",
3131                           exprNode_unparse (arg)),
3132                          exprNode_loc (arg));
3133                     }
3134                 }
3135             }
3136         }
3137     }
3138   else
3139     {
3140       ret->sref = defref;
3141       exprNode_checkSetAny (ret, uentry_rawName (le));
3142     }
3143
3144   return (ret);
3145 }
3146
3147 /*
3148 ** this is yucky!  should keep the uentry as part of exprNode!
3149 */
3150
3151 /*@observer@*/ uentry
3152 exprNode_getUentry (exprNode e)
3153 {
3154   if (exprNode_isError (e))
3155     {
3156       return uentry_undefined;
3157     }
3158   else
3159     {
3160       cstring s = exprNode_rootVarName (e);
3161       uentry ue = usymtab_lookupSafe (s);
3162
3163       return ue;
3164     }
3165 }
3166
3167 exprNode 
3168 exprNode_makeInitBlock (lltok brace, /*@only@*/ exprNodeList inits)
3169 {
3170   exprNode ret = exprNode_createPlain (ctype_unknown);
3171
3172   ret->kind = XPR_INITBLOCK;
3173   ret->edata = exprData_makeCall (exprNode_undefined, inits);
3174   ret->loc = fileloc_update (ret->loc, lltok_getLoc (brace));
3175
3176   return (ret);
3177 }
3178
3179 exprNode
3180 exprNode_functionCall (/*@only@*/ exprNode f, /*@only@*/ exprNodeList args)
3181 {
3182   ctype t;
3183
3184   setCodePoint ();
3185
3186   if (exprNode_isUndefined (f))
3187     {
3188       exprNode_free (f);
3189       exprNodeList_free (args);
3190       return exprNode_undefined;
3191     }
3192
3193   t = exprNode_getType (f);
3194
3195   if (sRef_isLocalVar (f->sref))
3196     {
3197       exprNode_checkUse (f, f->sref, f->loc);
3198
3199       if (sRef_possiblyNull (f->sref))
3200         {
3201           if (!usymtab_isGuarded (f->sref))
3202             {
3203               if (optgenerror (FLG_NULLDEREF,
3204                                message ("Function call using %s pointer %q", 
3205                                         sRef_nullMessage (f->sref),
3206                                         sRef_unparse (f->sref)),
3207                                f->loc))
3208                 {
3209                   sRef_showNullInfo (f->sref);
3210                   sRef_setNullError (f->sref);
3211                 }
3212             }
3213         }
3214     }
3215
3216   setCodePoint ();
3217
3218   if (ctype_isRealFunction (t))
3219     {
3220       exprNode ret = functionCallSafe (f, t, args);
3221       setCodePoint ();
3222       return ret;
3223     }
3224   else if (ctype_isUnknown (t))
3225     {
3226       exprNode ret = exprNode_createPartialCopy (f);
3227       cstring tstring;
3228
3229       setCodePoint ();
3230       
3231       ret->typ = t;
3232       exprNodeList_elements (args, current)
3233         {
3234           if (exprNode_isDefined (current))
3235             {
3236               exprNode_checkUse (ret, current->sref, ret->loc);
3237
3238               /* 
3239               ** also, anything derivable from current->sref may be used 
3240               */
3241
3242               exprNode_addUse (ret, sRef_makeDerived (current->sref));
3243               exprNode_mergeUSs (ret, current);
3244             }
3245         } end_exprNodeList_elements;
3246
3247       ret->edata = exprData_makeCall (f, args);
3248       ret->kind = XPR_CALL;
3249
3250       tstring = cstring_copy (exprNode_unparse (f));
3251
3252       cstring_markOwned (tstring);
3253       exprNode_checkSetAny (ret, tstring);
3254
3255       return (ret);
3256     }
3257   else
3258     {
3259       voptgenerror (FLG_TYPE,
3260                     message ("Call to non-function (type %t): %s", t, 
3261                              exprNode_unparse (f)),
3262                     f->loc);
3263       exprNode_free (f);
3264       exprNodeList_free (args);
3265
3266       return (exprNode_makeError ());
3267     }
3268 }
3269
3270 exprNode
3271 exprNode_fieldAccess (/*@only@*/ exprNode s, /*@only@*/ cstring f)
3272 {
3273   exprNode ret = exprNode_createPartialCopy (s);
3274
3275   ret->kind = XPR_FACCESS;
3276
3277   if (exprNode_isError (s))
3278     {
3279       ret->edata = exprData_makeField (s, f);
3280       return ret;
3281     }
3282   else
3283     {
3284       ctype t = exprNode_getType (s);
3285       ctype tr = ctype_realType (t);
3286       
3287       checkMacroParen (s);
3288
3289       ret->edata = exprData_makeField (s, f);
3290       
3291       if (ctype_isStructorUnion (tr))
3292         {
3293           uentry tf = uentryList_lookupField (ctype_getFields (tr), f);
3294
3295           if (uentry_isUndefined (tf))
3296             {
3297               voptgenerror (FLG_TYPE,
3298                             message ("Access non-existent field %s of %t: %s", f, t, 
3299                                      exprNode_unparse (ret)),
3300                             s->loc);
3301               
3302               return (ret);
3303             }
3304           else
3305             {
3306               uentry_setUsed (tf, exprNode_loc (ret));
3307
3308               ret->typ = uentry_getType (tf); 
3309               checkSafeUse (ret, s->sref);
3310               
3311               ret->sref = sRef_makeField (s->sref, uentry_rawName (tf));
3312               return (ret);
3313             }
3314         }
3315       else /* isStructorUnion */
3316         {
3317           if (ctype_isRealAbstract (tr))
3318             {
3319               voptgenerror
3320                 (FLG_ABSTRACT,
3321                  message ("Access field of abstract type (%t): %s.%s", 
3322                           t, exprNode_unparse (s), f),
3323                  s->loc);
3324               ret->typ = ctype_unknown;
3325             }
3326           else
3327             {
3328               if (ctype_isKnown (tr))
3329                 {
3330                   voptgenerror 
3331                     (FLG_TYPE,
3332                      message
3333                      ("Access field of non-struct or union (%t): %s.%s",
3334                       t, exprNode_unparse (s), f),
3335                      s->loc);
3336
3337                   ret->typ = ctype_unknown;
3338                 }
3339               else
3340                 {
3341                   cstring sn = cstring_copy (f);
3342
3343                   checkSafeUse (ret, s->sref);
3344                   cstring_markOwned (sn);
3345                   ret->sref = sRef_makeField (s->sref, sn);
3346
3347                   return (ret);
3348                 }
3349             }
3350           return (ret);
3351         }
3352     }
3353   BADEXIT;
3354 }
3355
3356 exprNode
3357 exprNode_addParens (/*@only@*/ lltok lpar, /*@only@*/ exprNode e)
3358 {
3359   exprNode ret = exprNode_createPartialCopy (e);
3360
3361   ret->loc = fileloc_update (ret->loc, lltok_getLoc (lpar));
3362   ret->kind = XPR_PARENS;
3363   ret->edata = exprData_makeUop (e, lpar);
3364
3365   if (!exprNode_isError (e))
3366     {
3367       ret->exitCode = e->exitCode;
3368       ret->canBreak = e->canBreak;
3369       ret->mustBreak = e->mustBreak;
3370       ret->isJumpPoint = e->isJumpPoint;
3371       ret->sref = e->sref;
3372     }
3373
3374   return ret;
3375 }
3376
3377 exprNode
3378 exprNode_arrowAccess (/*@only@*/ exprNode s, /*@only@*/ cstring f)
3379 {
3380   exprNode ret = exprNode_createPartialCopy (s);
3381
3382   ret->edata = exprData_makeField (s, f);
3383   ret->kind = XPR_ARROW;
3384
3385   if (exprNode_isError (s))
3386     {
3387       return (ret);
3388     }
3389   else
3390     {
3391        ctype t = exprNode_getType (s);
3392        ctype tr = ctype_realType (t);
3393
3394        checkMacroParen (s);
3395
3396        (void) ctype_fixArrayPtr (tr); /* REWRITE THIS */
3397
3398        if (ctype_isRealPointer (tr)) 
3399          {
3400            ctype b = ctype_realType (ctype_baseArrayPtr (tr));
3401            
3402            if (ctype_isStructorUnion (b))
3403              {
3404                uentry fentry = uentryList_lookupField (ctype_getFields (b), f);
3405                
3406                if (sRef_isKnown (s->sref) && sRef_possiblyNull (s->sref))
3407                  {
3408                    if (!usymtab_isGuarded (s->sref) && !context_inProtectVars ())
3409                      {
3410                        if (optgenerror 
3411                            (FLG_NULLDEREF,
3412                             message ("Arrow access from %s pointer%q: %s", 
3413                                      sRef_nullMessage (s->sref),
3414                                      sRef_unparsePreOpt (s->sref),
3415                                      exprNode_unparse (ret)),
3416                             s->loc))
3417                          {
3418                            sRef_showNullInfo (s->sref);
3419                            sRef_setNullError (s->sref);
3420                          }
3421                      }
3422                  }
3423                
3424                if (uentry_isUndefined (fentry))
3425                  {
3426                    voptgenerror 
3427                      (FLG_TYPE,
3428                       message ("Access non-existent field %s of %t: %s", 
3429                                f, t, exprNode_unparse (ret)),
3430                       s->loc);
3431                    ret->typ = ctype_unknown;
3432                    
3433                    return (ret);
3434                  }
3435                else
3436                  {
3437                    /*
3438                    ** was safeUse: shouldn't be safe!
3439                    **
3440                    ** to do rec->field
3441                    ** rec must be defined,
3442                    ** *rec must be allocated
3443                    ** rec->field need only be defined it if is an rvalue
3444                    */
3445                    
3446                    uentry_setUsed (fentry, exprNode_loc (ret));
3447                    ret->typ = uentry_getType (fentry);
3448                    
3449                    exprNode_checkUse (ret, s->sref, s->loc);
3450                    
3451                    /* exprNode_checkUse (ret, sRef_makePointer (s->sref), s->loc); */
3452                    ret->sref = sRef_makeArrow (s->sref, uentry_rawName (fentry));
3453                    return (ret);
3454                  }
3455              }
3456            else /* Pointer to something that is not a struct or union*/
3457              {
3458                if (ctype_isRealAbstract (tr))
3459                  {
3460                    ctype xrt = ctype_forceRealType (tr);
3461                    
3462                    voptgenerror 
3463                      (FLG_ABSTRACT,
3464                       message ("Arrow access field of abstract type (%t): %s->%s", 
3465                                t, exprNode_unparse (s), f),
3466                       s->loc);
3467                    
3468                    /*
3469                    ** Set the state correctly, as if the abstraction is broken.
3470                    */
3471                    
3472                    if (ctype_isRealPointer (xrt) &&
3473                        (b = ctype_realType (ctype_baseArrayPtr (xrt)),
3474                         ctype_isStructorUnion (b)))
3475                      {
3476                        uentry fentry = uentryList_lookupField (ctype_getFields (b), f);
3477                        ret->typ = uentry_getType (fentry);
3478                        ret->sref = sRef_makeArrow (s->sref, uentry_rawName (fentry));
3479                      }
3480                    else
3481                      {
3482                        ret->typ = ctype_unknown;
3483                        ret->sref = sRef_undefined;
3484                      }
3485                  }
3486                else /* not a struct, union or abstract */
3487                  {
3488                    if (ctype_isUnknown (tr)) {
3489                      cstring sn = cstring_copy (f);
3490                      
3491                      DPRINTF (("Here: %s", exprNode_unparse (s)));
3492                      
3493                      exprNode_checkUse (ret, s->sref, s->loc);
3494                      exprNode_checkUse (ret, sRef_makePointer (s->sref), s->loc);
3495                      
3496                      cstring_markOwned (sn);
3497                      ret->sref = sRef_makeArrow (s->sref, sn);
3498                      
3499                      ret->kind = XPR_ARROW;
3500                      return (ret);
3501                    } else {
3502                      voptgenerror 
3503                        (FLG_TYPE,
3504                         message ("Arrow access field of non-struct or union "
3505                                  "pointer (%t): %s->%s",
3506                                  t, exprNode_unparse (s), f),
3507                         s->loc);
3508                      
3509                      ret->typ = ctype_unknown;
3510                      ret->sref = sRef_undefined;
3511                    }
3512                  }
3513              }
3514          }
3515        else /* its not a pointer */
3516          {
3517            if (!ctype_isUnknown (tr))
3518              {
3519                voptgenerror 
3520                  (FLG_TYPE,
3521                   message ("Arrow access of non-pointer (%t): %s->%s",
3522                            t, exprNode_unparse (s), f),
3523                   s->loc);
3524                
3525                ret->typ = ctype_unknown;
3526                ret->sref = sRef_undefined;
3527              }
3528            else
3529              {
3530                cstring sn = cstring_copy (f);
3531                
3532                DPRINTF (("Here: %s", exprNode_unparse (s)));
3533                
3534                exprNode_checkUse (ret, s->sref, s->loc);
3535                exprNode_checkUse (ret, sRef_makePointer (s->sref), s->loc);
3536                
3537                cstring_markOwned (sn);
3538                ret->sref = sRef_makeArrow (s->sref, sn);
3539                
3540                ret->kind = XPR_ARROW;
3541                return (ret);
3542              }
3543          }
3544
3545       return (ret);
3546     }
3547   BADEXIT;
3548 }
3549
3550 /*
3551 ** only postOp's in C: i++ and i--
3552 */
3553
3554 exprNode
3555 exprNode_postOp (/*@only@*/ exprNode e, /*@only@*/ lltok op)
3556 {
3557   /* check modification also */
3558   /* cstring opname = lltok_unparse (op);*/
3559   ctype t;
3560   exprNode ret = exprNode_createPartialCopy (e);
3561
3562   ret->loc = fileloc_update (ret->loc, lltok_getLoc (op));
3563   ret->kind = XPR_POSTOP;
3564   ret->edata = exprData_makeUop (e, op);
3565
3566   if (!exprNode_isDefined (e))
3567     {
3568       return ret;
3569     }
3570
3571   checkMacroParen (e);
3572
3573   exprNode_checkUse (ret, e->sref, e->loc);
3574   exprNode_checkSet (ret, e->sref);
3575
3576   t = exprNode_getType (e);
3577
3578   if (sRef_isUnsafe (e->sref))
3579     {
3580       voptgenerror (FLG_MACROPARAMS,
3581                     message ("Operand of %s is macro parameter (non-functional): %s%s", 
3582                              lltok_unparse (op), exprNode_unparse (e), lltok_unparse (op)),
3583                     e->loc);
3584       sRef_makeSafe (e->sref);
3585       sRef_makeSafe (ret->sref);
3586     }
3587
3588   if (ctype_isForceRealNumeric (&t) || ctype_isRealAP (t))
3589     {
3590       ret->typ = e->typ;
3591     }
3592   else
3593     {
3594       if (ctype_isRealAbstract (t))
3595         {
3596           voptgenerror 
3597             (FLG_ABSTRACT,
3598              message ("Operand of %s is abstract type (%t): %s",
3599                       lltok_unparse (op), t, exprNode_unparse (e)),
3600              e->loc);
3601         }
3602       else
3603         {
3604           voptgenerror 
3605             (FLG_TYPE,
3606              message ("Operand of %s is non-numeric (%t): %s",
3607                       lltok_unparse (op), t, exprNode_unparse (e)),
3608              e->loc);
3609         }
3610       ret->typ = ctype_unknown;
3611     }
3612
3613   /* if (ctype_isZero (t)) e->typ = ctype_int; */
3614
3615   exprNode_checkModify (e, ret);
3616
3617   /* added 7/11/2000 D.L */
3618   
3619   updateEnvironmentForPostOp (e);
3620
3621         /* start modifications */
3622         /* added by Seejo on 4/16/2000 */
3623
3624         /* Arithmetic operations on pointers wil modify the size/len/null terminated 
3625                  status */
3626         if ((sRef_isPossiblyNullTerminated (e->sref)) || (sRef_isNullTerminated(e->sref))) {
3627
3628                 ret->sref = sRef_copy (e->sref);
3629
3630                 /* Operator : ++ */
3631                 if (lltok_getTok (op) == INC_OP) {
3632                         if (sRef_getSize(e->sref) > 0) {
3633
3634                                 sRef_setSize (ret->sref, sRef_getSize(e->sref) - 1);
3635                                 
3636                                 if (sRef_getLen(e->sref) == 1) { /* i.e. the first character is \0 */
3637                                         /* Assumption: there is only 1 \0 in the buffer */
3638                                         /* This will not be correct if there are 2 \0's in the buffer */
3639                                         sRef_setNotNullTerminatedState(ret->sref);
3640                                         sRef_resetLen(ret->sref);
3641                                 } else {
3642                                         sRef_setNullTerminatedState(ret->sref);
3643                                         sRef_setLen (ret->sref, sRef_getLen(e->sref) - 1);
3644                                 }
3645                                 if (sRef_isNullTerminated (ret->sref))
3646                                         printf ("ret->sref is Null Terminated\n");
3647                                 else if (sRef_isPossiblyNullTerminated (ret->sref))
3648                                         printf ("ret->sref is Possibly Null Terminated\n");
3649                                 else if (sRef_isNotNullTerminated (ret->sref))
3650                                         printf ("ret->sref is Not Null Terminated\n");
3651                         }
3652                 }
3653
3654                 /* Operator : -- */
3655                 if (lltok_getTok (op) == DEC_OP) {
3656                         if (sRef_getSize(e->sref) >= 0) {
3657                                 sRef_setSize (ret->sref, sRef_getSize(e->sref) + 1);
3658                                 sRef_setLen (ret->sref, sRef_getLen(e->sref) + 1);
3659                         }
3660                 }
3661         }
3662
3663         /* end modifications */
3664
3665   return ret;
3666 }
3667
3668 exprNode
3669 exprNode_preOp (/*@only@*/ exprNode e, /*@only@*/ lltok op)
3670 {
3671   bool checkMod = FALSE;
3672   ctype te, tr;
3673   int opid = lltok_getTok (op);
3674   exprNode ret = exprNode_createSemiCopy (e);
3675
3676   exprNode_copySets (ret, e);
3677
3678   multiVal_free (ret->val);
3679   ret->val = multiVal_undefined;
3680   ret->loc = fileloc_update (ret->loc, lltok_getLoc (op));
3681   ret->kind = XPR_PREOP;  
3682   ret->edata = exprData_makeUop (e, op);
3683   
3684   if (exprNode_isError (e))
3685     {
3686       return ret;
3687     }
3688   
3689   checkMacroParen (e);
3690   
3691   te = exprNode_getType (e);
3692   tr = ctype_realType (te);
3693   
3694   if (opid != TAMPERSAND)
3695     {
3696       exprNode_checkUse (ret, e->sref, e->loc);
3697       
3698       if (ctype_isRealAbstract (tr)
3699           && (!(ctype_isRealBool (te) && (opid == TEXCL))))
3700         {
3701           if (optgenerror (FLG_ABSTRACT,
3702                            message ("Operand of %s is abstract type (%t): %s",
3703                                     lltok_unparse (op), tr,
3704                                     exprNode_unparse (ret)),
3705                            e->loc))
3706             {
3707               tr = te = ctype_unknown;
3708               ret->typ = ctype_unknown;
3709               sRef_setNullError (e->sref);
3710             }
3711         }
3712     }
3713   
3714   switch (opid)
3715     {
3716     case INC_OP:
3717     case DEC_OP:                /* should also check modification! */
3718
3719       if (sRef_isMacroParamRef (e->sref))
3720         {
3721           voptgenerror 
3722             (FLG_MACROPARAMS,
3723              message ("Operand of %s is macro parameter (non-functional): %s", 
3724                       lltok_unparse (op), exprNode_unparse (ret)),
3725              e->loc);
3726         }
3727       else
3728         {
3729           exprNode_checkSet (ret, e->sref);
3730         }
3731       
3732       if (ctype_isForceRealNumeric (&tr) || ctype_isRealAP (tr))
3733         {
3734         }
3735       else
3736         {
3737           if (context_msgStrictOps ())
3738             {
3739               voptgenerror 
3740                 (FLG_STRICTOPS,
3741                  message ("Operand of %s is non-numeric (%t): %s",
3742                           lltok_unparse (op), te, exprNode_unparse (ret)),
3743                  e->loc);
3744             }
3745           ret->typ = ctype_int;
3746         }
3747
3748         /* start modifications */
3749         /* added by Seejo on 4/16/2000 */
3750
3751         /* Arithmetic operations on pointers wil modify the size/len/null terminated 
3752                  status */
3753         if ((sRef_isPossiblyNullTerminated (e->sref)) || (sRef_isNullTerminated(e->sref))) {
3754
3755                 ret->sref = sRef_copy (e->sref);
3756
3757                 /* Operator : ++ */
3758                 if (lltok_getTok (op) == INC_OP) {
3759                         if (sRef_getSize(e->sref) > 0) {
3760
3761                                 sRef_setSize (ret->sref, sRef_getSize(e->sref) - 1);
3762
3763                                 if (sRef_getLen(e->sref) == 1) { /* i.e. the first character is \0 */
3764                                         /* Assumption: there is only 1 \0 in the buffer */
3765                                         /* This will not be correct if there are 2 \0's in the buffer */
3766                                         sRef_setNotNullTerminatedState(ret->sref);
3767                                         sRef_resetLen (ret->sref);
3768                                 } else {
3769                                         sRef_setNullTerminatedState(ret->sref);
3770                                         sRef_setLen (ret->sref, sRef_getLen(e->sref) - 1);
3771                                 }
3772                         }
3773                 }
3774
3775                 /* Operator : -- */
3776                 if (lltok_getTok (op) == DEC_OP) {
3777                         if (sRef_getSize(e->sref) >= 0) {
3778                                 sRef_setSize (ret->sref, sRef_getSize(e->sref) + 1);
3779                                 sRef_setLen (ret->sref, sRef_getLen(e->sref) + 1);
3780                         }
3781                 }
3782         }
3783
3784         /* end modifications */    
3785
3786       checkMod = TRUE;
3787       break;
3788       
3789     case TMINUS:
3790     case TPLUS:
3791       if (ctype_isForceRealNumeric (&tr))
3792         {
3793           if (opid == TMINUS)
3794             {
3795               ret->val = multiVal_invert (exprNode_getValue (e));
3796             }
3797           else
3798             {
3799               ret->val = multiVal_copy (exprNode_getValue (e));
3800             }
3801         }
3802       else
3803         {
3804           if (context_msgStrictOps ())
3805             {
3806               voptgenerror 
3807                 (FLG_STRICTOPS,
3808                  message ("Operand of %s is non-numeric (%t): %s",
3809                           lltok_unparse (op), te, exprNode_unparse (ret)),
3810                  e->loc);
3811             }
3812
3813           ret->typ = ctype_int;
3814         }
3815       break;
3816       
3817     case TEXCL:         /* maybe this should be restricted */
3818       guardSet_flip (ret->guards);      
3819
3820       if (ctype_isRealBool (te))
3821         {
3822          ;
3823         }
3824       else
3825         {
3826           if (ctype_isRealPointer (tr))
3827             {
3828               if (sRef_isKnown (e->sref))
3829                 {
3830                   ret->guards = guardSet_addFalseGuard (ret->guards, e->sref);
3831                 }
3832
3833               voptgenerror2n
3834                 (FLG_BOOLOPS, FLG_PTRNEGATE,
3835                  message ("Operand of %s is non-boolean (%t): %s",
3836                           lltok_unparse (op), te, exprNode_unparse (ret)),
3837                  e->loc);
3838             }
3839           else
3840             {
3841               voptgenerror
3842                 (FLG_BOOLOPS,
3843                  message ("Operand of %s is non-boolean (%t): %s",
3844                           lltok_unparse (op), te, exprNode_unparse (ret)),
3845                  e->loc);
3846             }
3847           
3848           ret->typ = ctype_bool;
3849         }
3850       break;
3851       
3852     case TTILDE:
3853       if (ctype_isForceRealInt (&tr))
3854         {
3855         }
3856       else
3857         {
3858           if (context_msgStrictOps ())
3859             {
3860               voptgenerror 
3861                 (FLG_STRICTOPS,
3862                  message ("Operand of %s is non-integer (%t): %s",
3863                           lltok_unparse (op), te, exprNode_unparse (ret)), 
3864                  e->loc);
3865             }
3866
3867           if (ctype_isInt (e->typ))
3868             {
3869               ret->typ = e->typ;
3870             }
3871           else
3872             {
3873               ret->typ = ctype_int;
3874             }
3875         }       
3876       break;
3877       
3878     case TAMPERSAND:
3879       ret->typ = ctype_makePointer (e->typ);
3880
3881       if (sRef_isKnown (e->sref))
3882         {
3883           ret->sref = sRef_makeAddress (e->sref);
3884         }
3885       
3886       break;
3887       
3888     case TMULT:
3889       
3890       if (ctype_isAP (tr))
3891         {
3892           ret->typ = ctype_baseArrayPtr (e->typ);
3893         }
3894       else
3895         {
3896           if (ctype_isKnown (te))
3897             {
3898               if (ctype_isFunction (te))
3899                 {
3900                   ret->typ = e->typ;
3901
3902                   voptgenerror
3903                     (FLG_FCNDEREF,
3904                      message ("Dereference of function type (%t): %s",
3905                               te, exprNode_unparse (ret)),
3906                      e->loc);
3907                 }
3908               else
3909                 {
3910                   voptgenerror (FLG_TYPE,
3911                                 message ("Dereference of non-pointer (%t): %s",
3912                                          te, exprNode_unparse (ret)),
3913                                 e->loc);
3914                   ret->typ = ctype_unknown;
3915                 }
3916             }
3917           else
3918             {
3919               ret->typ = ctype_unknown;
3920             }
3921           
3922         }
3923       
3924       if (sRef_isKnown (e->sref))
3925         {
3926           if (sRef_possiblyNull (e->sref))
3927             {
3928               if (!usymtab_isGuarded (e->sref) && !context_inProtectVars ())
3929                 {
3930                   if (optgenerror 
3931                       (FLG_NULLDEREF,
3932                        message ("Dereference of %s pointer %q: %s", 
3933                                 sRef_nullMessage (e->sref),
3934                                 sRef_unparse (e->sref),
3935                                 exprNode_unparse (ret)),
3936                        e->loc))
3937                     {
3938                       sRef_showNullInfo (e->sref);
3939                       sRef_setNotNull (e->sref, e->loc); /* suppress future messages */
3940                     }
3941                 }
3942             }
3943           
3944           ret->sref = sRef_makePointer (e->sref);
3945         }
3946       break;
3947       
3948     default:
3949       llbug (message ("exprNode_preOp: unhandled op: %s", lltok_unparse (op)));
3950     }
3951
3952   if (checkMod)
3953     {
3954       exprNode_checkModify (e, ret);
3955     }
3956
3957   return ret;
3958 }
3959
3960 /*
3961 ** any reason to disallow sizeof (abstract type) ?
3962 */
3963
3964 /*
3965 ** used by both sizeof
3966 */
3967
3968 static
3969 ctype sizeof_resultType (void)
3970 {
3971   static ctype sizet = ctype_unknown;
3972
3973   if (ctype_isUnknown (sizet))
3974     {
3975       if (usymtab_existsType (cstring_makeLiteralTemp ("size_t")))
3976         {
3977           sizet = uentry_getAbstractType (usymtab_lookup (cstring_makeLiteralTemp ("size_t")));
3978         }
3979       else
3980         {
3981                   sizet = ctype_ulint;
3982         }
3983     }
3984   return sizet;
3985 }
3986
3987 exprNode
3988 exprNode_sizeofType (/*@only@*/ qtype qt)
3989 {
3990   exprNode ret = exprNode_create (sizeof_resultType ());
3991   ctype ct = qtype_getType (qt);
3992
3993   ret->kind = XPR_SIZEOFT;
3994   ret->edata = exprData_makeSizeofType (qt);
3995
3996   voptgenerror (FLG_SIZEOFTYPE,
3997                 message ("Parameter to sizeof is type %s: %s",
3998                          ctype_unparse (ct),
3999                          exprNode_unparse (ret)),
4000                 ret->loc);
4001   
4002   return (ret);
4003 }
4004
4005 exprNode
4006 exprNode_alignofType (/*@only@*/ qtype qt)
4007 {
4008   exprNode ret = exprNode_create (sizeof_resultType ());
4009   ctype ct = qtype_getType (qt);
4010
4011   ret->kind = XPR_ALIGNOFT;
4012   ret->edata = exprData_makeSizeofType (qt);
4013
4014   voptgenerror (FLG_SIZEOFTYPE,
4015                 message ("Parameter to alignof is type %s: %s",
4016                          ctype_unparse (ct),
4017                          exprNode_unparse (ret)),
4018                 ret->loc);
4019   
4020   return (ret);
4021 }
4022
4023 exprNode exprNode_offsetof (qtype qt, cstringList s)
4024 {
4025   exprNode ret = exprNode_create (sizeof_resultType ());
4026   ctype ct = qtype_getType (qt);
4027
4028   ret->kind = XPR_OFFSETOF;
4029   ret->edata = exprData_makeOffsetof (qt, s);
4030
4031   if (!ctype_isRealSU (ct))
4032     {
4033       voptgenerror (FLG_TYPE,
4034                     message ("First parameter to offsetof is not a "
4035                              "struct or union type (type %s): %s",
4036                              ctype_unparse (ct),
4037                              exprNode_unparse (ret)),
4038                     ret->loc);
4039     }
4040   else
4041     {
4042       ctype lt = ct;
4043
4044       cstringList_elements (s, el) {
4045         uentryList fields;
4046         uentry fld;
4047
4048         if (ctype_isUndefined (lt))
4049           {
4050             break;
4051           } 
4052         else if (!ctype_isRealSU (lt))
4053           {
4054             voptgenerror (FLG_TYPE,
4055                           message ("Inner offsetof type is not a "
4056                                    "struct or union type (type %s before field %s): %s",
4057                                    ctype_unparse (lt), el,
4058                                    exprNode_unparse (ret)),
4059                           ret->loc);
4060             break;
4061           }
4062         else 
4063           {
4064             fields = ctype_getFields (ctype_realType (lt));
4065             fld = uentryList_lookupField (fields, el);
4066             DPRINTF (("Try: %s / %s", ctype_unparse (lt), el));
4067             
4068             if (uentry_isUndefined (fld))
4069               {
4070                 if (ctype_equal (lt, ct)) {
4071                   voptgenerror (FLG_TYPE,
4072                                 message ("Field %s in offsetof is not the "
4073                                          "name of a field of %s: %s",
4074                                          el,
4075                                          ctype_unparse (ct),
4076                                          exprNode_unparse (ret)),
4077                                 ret->loc);
4078                 } else {
4079                   voptgenerror (FLG_TYPE,
4080                                 message ("Deep field %s in offsetof is not the "
4081                                          "name of a field of %s: %s",
4082                                          el,
4083                                          ctype_unparse (lt),
4084                                          exprNode_unparse (ret)),
4085                                 ret->loc);
4086                 }
4087               }
4088             else 
4089               {
4090                 lt = uentry_getType (fld);
4091               }
4092           }
4093       } end_cstringList_elements;
4094
4095       /* Should report error if its a bit field - behavior is undefined! */
4096     }
4097   
4098   return (ret);
4099 }
4100
4101 /*@only@*/ exprNode
4102 exprNode_sizeofExpr (/*@only@*/ exprNode e)
4103 {
4104   exprNode ret;
4105
4106   if (exprNode_isUndefined (e))
4107     {
4108       ret = exprNode_createLoc (ctype_unknown, fileloc_copy (g_currentloc));
4109       ret->edata = exprData_makeSingle (e);
4110       ret->typ = sizeof_resultType ();
4111       ret->kind = XPR_SIZEOF;
4112     }
4113   else
4114     {
4115       uentry u = exprNode_getUentry (e);
4116
4117       ret = exprNode_createPartialCopy (e);
4118       ret->edata = exprData_makeSingle (e);
4119
4120       ret->typ = sizeof_resultType ();
4121       ret->kind = XPR_SIZEOF;
4122
4123       if (uentry_isValid (u) 
4124           && uentry_isRefParam (u)
4125           && ctype_isRealArray (uentry_getType (u)))
4126         {
4127           voptgenerror
4128             (FLG_SIZEOFFORMALARRAY,
4129              message ("Parameter to sizeof is an array-type function parameter: %s",
4130                       exprNode_unparse (ret)),
4131              ret->loc);
4132         }
4133     }
4134
4135   /*
4136   ** sizeof (x) doesn't "really" use x
4137   */
4138
4139   return (ret);
4140 }
4141
4142 /*@only@*/ exprNode
4143 exprNode_alignofExpr (/*@only@*/ exprNode e)
4144 {
4145   exprNode ret;
4146
4147   if (exprNode_isUndefined (e))
4148     {
4149       ret = exprNode_createLoc (ctype_unknown, fileloc_copy (g_currentloc));
4150     }
4151   else
4152     {
4153       ret = exprNode_createPartialCopy (e);
4154     }
4155
4156   ret->edata = exprData_makeSingle (e);
4157   ret->typ = sizeof_resultType ();
4158   ret->kind = XPR_ALIGNOF;
4159   
4160   /*
4161   ** sizeof (x) doesn't "really" use x
4162   */
4163
4164   return (ret);
4165 }
4166
4167 /*@only@*/ exprNode
4168 exprNode_cast (/*@only@*/ lltok tok, /*@only@*/ exprNode e, /*@only@*/ qtype q)
4169 {
4170   ctype c;
4171   ctype t;
4172   exprNode ret;
4173
4174   if (exprNode_isError (e))
4175     {
4176       qtype_free (q);
4177       lltok_release (tok);
4178       return exprNode_undefined;
4179     }
4180
4181   checkMacroParen (e);
4182
4183   c = qtype_getType (q);
4184   t = exprNode_getType (e);
4185
4186   ret = exprNode_createPartialCopy (e);
4187   
4188   ret->loc = fileloc_update (ret->loc, lltok_getLoc (tok));
4189   ret->typ = c;
4190   ret->kind = XPR_CAST;
4191   ret->edata = exprData_makeCast (tok, e, q);
4192
4193   if (ctype_isRealSU (ctype_getBaseType (sRef_getType (e->sref))))
4194     {
4195       /* 
4196       ** This is a bit of a hack to avoid a problem
4197       ** when the code does,
4198       **          (some other struct) x
4199       **          ...
4200       **          x->field
4201       */
4202
4203       ret->sref = sRef_copy (e->sref);
4204       usymtab_addForceMustAlias (ret->sref, e->sref);
4205       sRef_setTypeFull (ret->sref, c);
4206       DPRINTF (("Cast: %s -> %s", sRef_unparseFull (e->sref),
4207                 sRef_unparseFull (ret->sref)));
4208     }
4209   else
4210     {
4211       ret->sref = e->sref;
4212       sRef_setTypeFull (ret->sref, c);
4213       DPRINTF (("Cast 2: -> %s", sRef_unparseFull (ret->sref)));
4214     }
4215
4216   /*
4217   ** we allow
4218   **       abstract  -> void
4219   **              0 <-> abstract * 
4220   **         void * <-> abstract *  (if FLG_ABSTVOIDP)
4221   **     abstract * <-> void *      (if FLG_ABSTVOIDP)
4222   */
4223
4224   if (ctype_isVoid (c)) /* cast to void is always okay --- discard value */
4225     {
4226       ;
4227     }
4228   else if (ctype_isRealAP (c)) /* casting to array or pointer */
4229     {
4230       ctype bc = ctype_getBaseType (c);
4231       ctype bt = ctype_getBaseType (t);
4232       ctype rt = ctype_realType (t);
4233
4234       if (ctype_isFunction (ctype_baseArrayPtr (ctype_realType (c)))
4235           && (ctype_isArrayPtr (rt)
4236               && !ctype_isFunction (ctype_realType (ctype_baseArrayPtr (rt)))))
4237         {
4238           voptgenerror
4239             (FLG_CASTFCNPTR,
4240              message ("Cast from function pointer type (%t) to "
4241                       "non-function pointer (%t): %s",
4242                       c, t, exprNode_unparse (ret)),
4243              e->loc);     
4244         }
4245
4246       if (!ctype_isFunction (ctype_baseArrayPtr (c))
4247           && (ctype_isArrayPtr (rt)
4248               && ctype_isFunction (ctype_realType (ctype_baseArrayPtr (rt)))))
4249         {
4250           voptgenerror
4251             (FLG_CASTFCNPTR,
4252              message ("Cast from non-function pointer type (%t) to "
4253                       "function pointer (%t): %s",
4254                       c, t, exprNode_unparse (ret)),
4255              e->loc);     
4256         }
4257
4258       if (exprNode_isZero (e) && context_getFlag (FLG_ZEROPTR) &&
4259           !(ctype_isRealAbstract (bc)
4260             && context_hasAccess (ctype_typeId (bc))))
4261         {
4262          ; /* okay to cast zero */
4263         }
4264       else
4265         {
4266           if (ctype_isRealAbstract (bc)
4267               && !context_hasAccess (ctype_typeId (bc)))
4268             {
4269               if (ctype_isVoidPointer (t) || ctype_isUnknown (t))
4270                 {
4271                   vnoptgenerror
4272                     (FLG_ABSTVOIDP,
4273                      message ("Cast to underlying abstract type %t: %s",
4274                               c, exprNode_unparse (ret)),
4275                      e->loc);
4276                 }
4277               else
4278                 {
4279                   voptgenerror
4280                     (FLG_ABSTRACT,
4281                      message ("Cast to underlying abstract type %t: %s",
4282                               c, exprNode_unparse (ret)),
4283                      e->loc);     
4284                 }
4285             }
4286
4287           if (ctype_isRealAbstract (bt)
4288               && !context_hasAccess (ctype_typeId (bt)))
4289             {
4290               if (ctype_isUnknown (c) || ctype_isVoidPointer (c))
4291                 {
4292                   vnoptgenerror
4293                     (FLG_ABSTVOIDP,
4294                      message ("Cast from underlying abstract type %t: %s",
4295                               t, exprNode_unparse (ret)),
4296                      e->loc);
4297                 }
4298               else
4299                 {
4300                   voptgenerror
4301                     (FLG_ABSTRACT,
4302                      message ("Cast from underlying abstract type %t: %s",
4303                               t, exprNode_unparse (ret)),
4304                      e->loc);
4305                 }
4306             }
4307         }
4308     }
4309   else
4310     {
4311       ctype bt = ctype_realType (ctype_getBaseType (t));
4312       ctype bc = ctype_realType (ctype_getBaseType (c));
4313
4314       if (ctype_isAbstract (bt) && !context_hasAccess (ctype_typeId (bt)))
4315         {
4316           if (ctype_match (c, t))
4317             {
4318               if (ctype_equal (c, t))
4319                 {
4320                   voptgenerror
4321                     (FLG_TYPE, 
4322                      message ("Redundant cast involving abstract type %t: %s",
4323                               bt, exprNode_unparse (ret)),
4324                      e->loc);
4325                 }
4326             }
4327           else
4328             {
4329               voptgenerror
4330                 (FLG_ABSTRACT,
4331                  message ("Cast from abstract type %t: %s", 
4332                           bt, exprNode_unparse (ret)),
4333                  e->loc);
4334             }
4335         }
4336       
4337       if (ctype_isAbstract (bc) 
4338           && !context_hasAccess (ctype_typeId (bc)))
4339         {
4340           if (ctype_match (c, t))
4341             {
4342              ;
4343             }
4344           else
4345             {
4346               voptgenerror 
4347                 (FLG_ABSTRACT,
4348                  message ("Cast to abstract type %t: %s", bc, 
4349                           exprNode_unparse (ret)),
4350                  e->loc);
4351             }
4352         }
4353     }
4354
4355   if (ctype_isAbstract (c))
4356     {
4357       if (sRef_isExposed (e->sref) || sRef_isOnly (e->sref))
4358         {
4359           /* okay, cast exposed to abstract */
4360           sRef_clearExKindComplete (ret->sref, fileloc_undefined);
4361         }
4362       else 
4363         {
4364           if (ctype_isVisiblySharable (t) 
4365               && sRef_isExternallyVisible (e->sref)
4366               && !(ctype_isAbstract (t) 
4367                    && context_hasAccess (ctype_typeId (t))))
4368             {
4369               voptgenerror 
4370                 (FLG_CASTEXPOSE,
4371                  message ("Cast to abstract type from externally visible "
4372                           "mutable storage exposes rep of %s: %s",
4373                           ctype_unparse (c),
4374                           exprNode_unparse (e)),
4375                  e->loc);
4376             }
4377         }
4378     }
4379
4380   return (ret);
4381 }
4382
4383 static bool
4384 evaluationOrderUndefined (lltok op)
4385 {
4386   int opid = lltok_getTok (op);
4387
4388   return (opid != AND_OP && opid != OR_OP);
4389 }
4390
4391 static bool checkIntegral (/*@notnull@*/ exprNode e1, 
4392                            /*@notnull@*/ exprNode e2, 
4393                            /*@notnull@*/ exprNode ret, 
4394                            lltok op)
4395 {
4396   bool error = FALSE;
4397
4398   ctype te1 = exprNode_getType (e1);
4399   ctype te2 = exprNode_getType (e2);
4400
4401   ctype tr1 = ctype_realishType (te1);
4402   ctype tr2 = ctype_realishType (te2);
4403   
4404   if (ctype_isForceRealInt (&tr1) && ctype_isForceRealInt (&tr2))
4405     {
4406       ;
4407     }
4408   else
4409     {
4410       if (context_msgStrictOps ())
4411         {
4412           if (!ctype_isInt (tr1) && !ctype_isInt (tr2))
4413             {
4414               if (ctype_sameName (te1, te2))
4415                 {
4416                   error = optgenerror 
4417                     (FLG_STRICTOPS,
4418                      message ("Operands of %s are non-integer (%t): %s",
4419                               lltok_unparse (op), te1,
4420                               exprNode_unparse (ret)),
4421                      e1->loc);
4422                 }
4423               else
4424                 {
4425                   error = optgenerror 
4426                     (FLG_STRICTOPS,
4427                      message ("Operands of %s are non-integers (%t, %t): %s",
4428                               lltok_unparse (op), te1, te2,
4429                               exprNode_unparse (ret)),
4430                      e1->loc);
4431                 }
4432             }
4433           else if (!ctype_isInt (tr1))
4434             {
4435               error = optgenerror 
4436                 (FLG_STRICTOPS,
4437                  message ("Left operand of %s is non-integer (%t): %s",
4438                           lltok_unparse (op), te1, exprNode_unparse (ret)),
4439                  e1->loc);
4440             }
4441           else
4442             /* !ctype_isInt (te2) */
4443             {
4444               error = optgenerror 
4445                 (FLG_STRICTOPS,
4446                  message ("Right operand of %s is non-integer (%t): %s",
4447                           lltok_unparse (op), te2, exprNode_unparse (ret)),
4448                  e2->loc);
4449             }
4450         }
4451     }
4452
4453   return !error;
4454 }
4455
4456 /*
4457 ** returns exprNode representing e1 op e2
4458 **
4459 ** uses msg if there are errors
4460 ** can be used for both assignment ops and regular ops
4461 **
4462 ** modifies e1
4463 */
4464
4465 static /*@only@*/ /*@notnull@*/ exprNode
4466 exprNode_makeOp (/*@keep@*/ exprNode e1, /*@keep@*/ exprNode e2, 
4467                  /*@keep@*/ lltok op)
4468 {
4469   ctype te1, te2, tr1, tr2, tret;
4470   int opid = lltok_getTok (op);
4471   bool hasError = FALSE;
4472   exprNode ret;
4473
4474   if (exprNode_isError (e1))
4475     {
4476       ret = exprNode_createPartialNVCopy (e2);
4477     }
4478   else
4479     {
4480       ret = exprNode_createPartialNVCopy (e1);    
4481     }
4482
4483   ret->val = multiVal_undefined;
4484   ret->kind = XPR_OP;
4485   ret->edata = exprData_makeOp (e1, e2, op);
4486
4487   if (exprNode_isError (e1) || exprNode_isError (e2))
4488     {
4489       if (opid == TLT || opid == TGT || opid == LE_OP || opid == GE_OP
4490           || opid == EQ_OP || opid == NE_OP 
4491           || opid == AND_OP || opid == OR_OP)
4492         {
4493           ret->typ = ctype_bool;
4494         }
4495
4496       if (exprNode_isDefined (e1))
4497         {
4498           exprNode_checkUse (ret, e1->sref, e1->loc);  
4499         }
4500
4501       if (exprNode_isDefined (e2))
4502         {
4503           exprNode_mergeUSs (ret, e2);
4504           exprNode_checkUse (ret, e2->sref, e2->loc);  
4505         }
4506
4507       return ret;
4508     }
4509
4510   tret = ctype_unknown;
4511   te1 = exprNode_getType (e1);
4512   DPRINTF (("te1 = %s / %s", exprNode_unparse (e1), ctype_unparse (te1)));
4513
4514   te2 = exprNode_getType (e2);
4515
4516   tr1 = ctype_realishType (te1);
4517   tr2 = ctype_realishType (te2);
4518
4519   if (opid == OR_OP)
4520     {
4521       ret->guards = guardSet_or (ret->guards, e2->guards);
4522     }
4523   else if (opid == AND_OP)
4524     {
4525       ret->guards = guardSet_and (ret->guards, e2->guards);
4526     }
4527   else
4528     {
4529       /* no guards */
4530     }
4531
4532   if (opid == EQ_OP || opid == NE_OP)
4533     {
4534       exprNode temp1 = e1, temp2 = e2;
4535
4536       /* could do NULL == x */
4537       
4538       if (exprNode_isNullValue (e1) || exprNode_isUnknownConstant (e1))
4539         {
4540           temp1 = e2; temp2 = e1;
4541         }
4542
4543       if (exprNode_isNullValue (temp2) || exprNode_isUnknownConstant (temp2))
4544         {
4545           reflectNullTest (temp1, (opid == NE_OP));
4546           guardSet_free (ret->guards);
4547           ret->guards = guardSet_copy (temp1->guards);
4548         }
4549     }
4550
4551   if (opid == TLT || opid == TGT || opid == LE_OP || opid == GE_OP
4552       || opid == EQ_OP || opid == NE_OP || opid == AND_OP || opid == OR_OP)
4553     {
4554       tret = ctype_bool; 
4555     }
4556   
4557   if (anyAbstract (tr1, tr2) &&
4558       (!((ctype_isRealBool (te1) || ctype_isRealBool (te2)) && 
4559          (opid == AND_OP || opid == OR_OP 
4560           || opid == EQ_OP || opid == NE_OP))))
4561     {
4562       abstractOpError (tr1, tr2, op, e1, e2, e1->loc, e2->loc);
4563     }
4564   else if (ctype_isUnknown (te1) || ctype_isUnknown (te2))
4565     {
4566       /* unknown types, no comparisons possible */
4567     }
4568   else
4569     {
4570       switch (opid)
4571         {
4572         case TMULT:             /* multiplication and division:           */
4573         case TDIV:              /*                                        */
4574         case MUL_ASSIGN:        /*    numeric, numeric -> numeric         */
4575         case DIV_ASSIGN:        /*                                        */
4576           
4577           tret = checkNumerics (tr1, tr2, te1, te2, e1, e2, op);
4578           break;
4579           
4580         case TPLUS:             /* addition and subtraction:               */
4581         case TMINUS:            /*    pointer, int     -> pointer          */
4582         case SUB_ASSIGN:        /*    int, pointer     -> pointer          */
4583         case ADD_ASSIGN:        /*    numeric, numeric -> numeric          */
4584           
4585           tr1 = ctype_fixArrayPtr (tr1);
4586
4587           if ((ctype_isRealPointer (tr1) && !exprNode_isNullValue (e1))
4588               && (!ctype_isRealPointer (tr2) && ctype_isRealInt (tr2)))
4589             {
4590               /* pointer + int */
4591
4592               if (context_msgPointerArith ())
4593                 {
4594                   voptgenerror
4595                     (FLG_POINTERARITH,
4596                      message ("Pointer arithmetic (%t, %t): %s", 
4597                               te1, te2, exprNode_unparse (ret)),
4598                      e1->loc);
4599                 }
4600
4601               if (sRef_possiblyNull (e1->sref)
4602                   && !usymtab_isGuarded (e1->sref))
4603                 {
4604                   voptgenerror
4605                     (FLG_NULLPOINTERARITH,
4606                      message ("Pointer arithmetic involving possibly "
4607                               "null pointer %s: %s", 
4608                               exprNode_unparse (e1), 
4609                               exprNode_unparse (ret)),
4610                      e1->loc);
4611                 }
4612
4613               ret->sref = sRef_copy (e1->sref);
4614
4615          /* start modifications */
4616              /* added by Seejo on 4/16/2000 */
4617
4618             /* Arithmetic operations on pointers wil modify the size/len/null terminated 
4619                         status */
4620             if ((sRef_isPossiblyNullTerminated (e1->sref)) || (sRef_isNullTerminated(e1->sref))) {
4621                                 //if (sRef_isKnown (e->sref)) {
4622                                 //ret->sref = sRef_makeAddress (e->sref);
4623                                 //}
4624
4625               int val;
4626               /*drl 1-4-2001
4627                 added ugly fixed to stop
4628                 program from crashing on point + int +int
4629                 one day I'll fix this or ask Seejo wtf the codes supposed to do. */
4630
4631               if (!multiVal_isInt (e2->val) )
4632                 break;
4633               /*end drl*/
4634               
4635               val = (int) multiVal_forceInt (e2->val);
4636
4637                         /* Operator : + or += */
4638                     if ((lltok_getTok (op) == TPLUS) || (lltok_getTok(op) == ADD_ASSIGN)) {
4639                                 if (sRef_getSize(e1->sref) >= val) {/* Incrementing the pointer by 
4640                                                                                                                                            val should not result in a 
4641                                                                                                                                                    size < 0 (size = 0 is ok !) */
4642                                         
4643                                         sRef_setSize (ret->sref, sRef_getSize(e1->sref) - val);
4644                                         
4645                                         if (sRef_getLen(e1->sref) == val) { /* i.e. the character at posn val is \0 */
4646                                                 sRef_setNotNullTerminatedState(ret->sref);
4647                                                 sRef_resetLen (ret->sref);
4648                                         } else {
4649                                                 sRef_setNullTerminatedState(ret->sref);
4650                                                 sRef_setLen (ret->sref, sRef_getLen(e1->sref) - val);
4651                                         }
4652                                 }
4653                         }
4654                         
4655                         /* Operator : - or -= */
4656                          if ((lltok_getTok (op) == TMINUS) || (lltok_getTok (op) == SUB_ASSIGN)) {
4657                                 if (sRef_getSize(e1->sref) >= 0) {
4658                                         sRef_setSize (ret->sref, sRef_getSize(e1->sref) + val);
4659                                         sRef_setLen (ret->sref, sRef_getLen(e1->sref) + val);
4660                                 }
4661                         }
4662             }
4663                         
4664              /* end modifications */  
4665
4666               sRef_setNullError (ret->sref);
4667
4668               /*
4669               ** Fixed for 2.2c: the alias state of ptr + int is dependent,
4670               ** since is points to storage that should not be deallocated
4671               ** through this pointer.
4672               */
4673
4674               if (sRef_isOnly (ret->sref) 
4675                   || sRef_isFresh (ret->sref)) 
4676                 {
4677                   sRef_setAliasKind (ret->sref, AK_DEPENDENT, exprNode_loc (ret));
4678                 }
4679               
4680               tret = e1->typ;
4681             }
4682           else if ((!ctype_isRealPointer(tr1) && ctype_isRealInt (tr1)) 
4683                    && (ctype_isRealPointer (tr2) && !exprNode_isNullValue (e2)))
4684             {
4685               if (context_msgPointerArith ())
4686                 {
4687                   voptgenerror 
4688                     (FLG_POINTERARITH,
4689                      message ("Pointer arithmetic (%t, %t): %s", 
4690                               te1, te2, exprNode_unparse (ret)),
4691                      e1->loc);
4692                 }
4693
4694               if (sRef_possiblyNull (e1->sref)
4695                   && !usymtab_isGuarded (e1->sref))
4696                 {
4697                   voptgenerror
4698                     (FLG_NULLPOINTERARITH,
4699                      message ("Pointer arithmetic involving possibly "
4700                               "null pointer %s: %s", 
4701                               exprNode_unparse (e2), 
4702                               exprNode_unparse (ret)),
4703                      e2->loc);
4704                 }
4705
4706               ret->sref = sRef_copy (e2->sref);
4707
4708                   /* start modifications */
4709                   /* added by Seejo on 4/16/2000 */
4710
4711                   /* Arithmetic operations on pointers wil modify the size/len/null terminated 
4712                                  status */
4713
4714             if ((sRef_isPossiblyNullTerminated (e2->sref)) || (sRef_isNullTerminated(e2->sref))) {
4715                                 //if (sRef_isKnown (e->sref)) {
4716                                 //ret->sref = sRef_makeAddress (e->sref);
4717                                 //}
4718
4719                          int val = (int) multiVal_forceInt (e1->val);
4720
4721                         /* Operator : + or += */
4722                     if ((lltok_getTok (op) == TPLUS) || (lltok_getTok(op) == ADD_ASSIGN)) {
4723                                 if (sRef_getSize(e2->sref) >= val) {/* Incrementing the pointer by 
4724                                                                                                                                            val should not result in a 
4725                                                                                                                                                    size < 0 (size = 0 is ok !) */
4726                                         
4727                                         sRef_setSize (ret->sref, sRef_getSize(e2->sref) - val);
4728                                         
4729                                         if (sRef_getLen(e2->sref) == val) { /* i.e. the character at posn val is \0 */
4730                                                 sRef_setNotNullTerminatedState(ret->sref);
4731                                                 sRef_resetLen (ret->sref);
4732                                         } else {
4733                                                 sRef_setNullTerminatedState(ret->sref);
4734                                                 sRef_setLen (ret->sref, sRef_getLen(e2->sref) - val);
4735                                         }
4736                                 }
4737                         }
4738                         
4739                         /* Operator : - or -= */
4740                          if ((lltok_getTok (op) == TMINUS) || (lltok_getTok (op) == SUB_ASSIGN)) {
4741                                 if (sRef_getSize(e2->sref) >= 0) {
4742                                         sRef_setSize (ret->sref, sRef_getSize(e2->sref) + val);
4743                                         sRef_setLen (ret->sref, sRef_getLen(e2->sref) + val);
4744                                 }
4745                         }
4746                  }
4747
4748             /* end modifications */
4749
4750               sRef_setNullError (ret->sref);
4751
4752               /*
4753               ** Fixed for 2.2c: the alias state of ptr + int is dependent,
4754               ** since is points to storage that should not be deallocated
4755               ** through this pointer.
4756               */
4757
4758               if (sRef_isOnly (ret->sref) 
4759                   || sRef_isFresh (ret->sref)) {
4760                 sRef_setAliasKind (ret->sref, AK_DEPENDENT, exprNode_loc (ret));
4761               }
4762
4763               tret = e2->typ;
4764               ret->sref = e2->sref;
4765             }
4766           else
4767             {
4768               tret = checkNumerics (tr1, tr2, te1, te2, e1, e2, op);
4769             }
4770           
4771           break;
4772
4773         case LEFT_ASSIGN:   /* Shifts: should be unsigned values */
4774         case RIGHT_ASSIGN:
4775         case LEFT_OP:
4776         case RIGHT_OP:
4777         case TAMPERSAND:    /* bitwise & */
4778         case AND_ASSIGN:       
4779         case TCIRC:         /* ^ (XOR) */
4780         case TBAR:
4781         case XOR_ASSIGN:
4782         case OR_ASSIGN:
4783           {
4784             bool reported = FALSE;
4785             flagcode code = FLG_BITWISEOPS;
4786             
4787             if (opid == LEFT_OP || opid == LEFT_ASSIGN
4788                 || opid == RIGHT_OP || opid == RIGHT_ASSIGN) {
4789               code = FLG_SHIFTSIGNED;
4790             }
4791
4792             if (!ctype_isUnsigned (tr1)) 
4793               {
4794                 if (exprNode_isNonNegative (e1)) {
4795                   ;
4796                 } else {
4797                   reported = optgenerror 
4798                     (code,
4799                      message ("Left operand of %s is not unsigned value (%t): %s",
4800                               lltok_unparse (op), te1,
4801                               exprNode_unparse (ret)),
4802                      e1->loc);
4803                   
4804                   if (reported) {
4805                     te1 = ctype_uint;
4806                   }
4807                 }
4808               }
4809             else 
4810               {
4811                 /* right need not be signed for shifts */
4812                 if (code != FLG_SHIFTSIGNED 
4813                     && !ctype_isUnsigned (tr2)) 
4814                   {
4815                     if (!exprNode_isNonNegative (e2)) {
4816                       reported = optgenerror 
4817                         (code,
4818                          message ("Right operand of %s is not unsigned value (%t): %s",
4819                                   lltok_unparse (op), te2,
4820                                   exprNode_unparse (ret)),
4821                          e2->loc);
4822                     }
4823                   }
4824               }
4825             
4826             if (!reported) 
4827               {
4828                 if (!checkIntegral (e1, e2, ret, op)) {
4829                   te1 = ctype_unknown;
4830                 }
4831               }
4832             
4833             DPRINTF (("Set: %s", ctype_unparse (te1)));     
4834
4835             /*
4836             ** tret is the widest type of te1 and te2 
4837             */
4838
4839             tret = ctype_widest (te1, te2);
4840             break;
4841           }
4842         case MOD_ASSIGN:
4843         case TPERCENT:          
4844           if (checkIntegral (e1, e2, ret, op)) {
4845             tret = te1;
4846           } else {
4847             tret = ctype_unknown;
4848           }
4849           break;
4850         case EQ_OP: 
4851         case NE_OP:
4852         case TLT:               /* comparisons                           */
4853         case TGT:               /*    numeric, numeric -> bool           */
4854           if ((ctype_isReal (tr1) && !ctype_isInt (tr1))
4855               || (ctype_isReal (tr2) && !ctype_isInt (tr2)))
4856             {
4857               ctype rtype = tr1;
4858               bool fepsilon = FALSE;
4859
4860               if (!ctype_isReal (rtype) || ctype_isInt (rtype))
4861                 {
4862                   rtype = tr2;
4863                 }
4864               
4865               if (opid == TLT || opid == TGT)
4866                 {
4867                   uentry ue1 = exprNode_getUentry (e1);
4868                   uentry ue2 = exprNode_getUentry (e2);
4869
4870                   /*
4871                   ** FLT_EPSILON, etc. really is a variable, not
4872                   ** a constant.
4873                   */
4874
4875                   if (uentry_isVariable (ue1))
4876                     {
4877                       cstring uname = uentry_rawName (ue1);
4878
4879                       if (cstring_equalLit (uname, "FLT_EPSILON")
4880                           || cstring_equalLit (uname, "DBL_EPSILON")
4881                           || cstring_equalLit (uname, "LDBL_EPSILON"))
4882                         {
4883                           fepsilon = TRUE;
4884                         }
4885                     }
4886
4887                   if (uentry_isVariable (ue2))
4888                     {
4889                       cstring uname = uentry_rawName (ue2);
4890
4891                       if (cstring_equalLit (uname, "FLT_EPSILON")
4892                           || cstring_equalLit (uname, "DBL_EPSILON")
4893                           || cstring_equalLit (uname, "LDBL_EPSILON"))
4894                         {
4895                           fepsilon = TRUE;
4896                         }
4897                     }
4898                 }
4899
4900               if (fepsilon)
4901                 {
4902                   ; /* Don't complain. */
4903                 }
4904               else
4905                 {
4906                   voptgenerror
4907                     (FLG_REALCOMPARE,
4908                      message ("Dangerous comparison involving %s types: %s",
4909                               ctype_unparse (rtype),
4910                               exprNode_unparse (ret)),
4911                      ret->loc);
4912                 }
4913             }
4914           /*@fallthrough@*/
4915         case LE_OP:
4916         case GE_OP:
4917
4918           /*
4919           ** Types should match.
4920           */
4921
4922           if (!exprNode_matchTypes (e1, e2))
4923             {
4924               hasError = gentypeerror 
4925                 (te1, e1, te2, e2,
4926                  message ("Operands of %s have incompatible types (%t, %t): %s",
4927                           lltok_unparse (op), te1, te2, exprNode_unparse (ret)),
4928                  e1->loc);
4929               
4930             }
4931
4932           if (hasError 
4933               || (ctype_isForceRealNumeric (&tr1)
4934                   && ctype_isForceRealNumeric (&tr2)) ||
4935               (ctype_isRealPointer (tr1) && ctype_isRealPointer (tr2)))
4936             {
4937               ; /* okay */
4938             }
4939           else
4940             {
4941               if ((ctype_isRealNumeric (tr1) && ctype_isRealPointer (tr2)) ||
4942                   (ctype_isRealPointer (tr1) && ctype_isRealNumeric (tr2)))
4943                 {
4944                   voptgenerror 
4945                     (FLG_PTRNUMCOMPARE,
4946                      message ("Comparison of pointer and numeric (%t, %t): %s",
4947                               te1, te2, exprNode_unparse (ret)),
4948                      e1->loc);
4949                 }
4950               else
4951                 {
4952                   (void) checkNumerics (tr1, tr2, te1, te2, e1, e2, op);
4953                 }
4954               tret = ctype_bool;
4955             }
4956
4957           /* EQ_OP should NOT be used with booleans (unless one is FALSE) */
4958           
4959           if ((opid == EQ_OP || opid == NE_OP) && 
4960               ctype_isDirectBool (tr1) && ctype_isDirectBool (tr2))
4961             {
4962               /*
4963               ** is one a variable?
4964               */
4965
4966               if (uentry_isVariable (exprNode_getUentry (e1))
4967                   || uentry_isVariable (exprNode_getUentry (e2)))
4968                 {
4969                   /*
4970                   ** comparisons with FALSE are okay
4971                   */
4972
4973                   if (exprNode_isFalseConstant (e1)
4974                       || exprNode_isFalseConstant (e2))
4975                     {
4976                       ;
4977                     }
4978                   else
4979                     {
4980                       voptgenerror
4981                         (FLG_BOOLCOMPARE,
4982                          message 
4983                          ("Use of %q with %s variables (risks inconsistency because "
4984                           "of multiple true values): %s",
4985                           cstring_makeLiteral ((opid == EQ_OP) ? "==" : "!="),
4986                           context_printBoolName (), exprNode_unparse (ret)),
4987                          e1->loc);
4988                     }
4989                 }
4990             }
4991           break;
4992           
4993         case AND_OP:            /* bool, bool -> bool */
4994         case OR_OP:
4995
4996           if (ctype_isForceRealBool (&tr1) && ctype_isForceRealBool (&tr2))
4997             {
4998               ; 
4999             }
5000           else
5001             {
5002               if (context_maybeSet (FLG_BOOLOPS))
5003                 {
5004                   if (!ctype_isRealBool (te1) && !ctype_isRealBool (te2))
5005                     {
5006                       if (ctype_sameName (te1, te2))
5007                         {
5008                           voptgenerror 
5009                             (FLG_BOOLOPS,
5010                              message ("Operands of %s are non-boolean (%t): %s",
5011                                       lltok_unparse (op), te1,
5012                                       exprNode_unparse (ret)),
5013                              e1->loc);
5014                         }
5015                       else
5016                         {
5017                           voptgenerror 
5018                             (FLG_BOOLOPS,
5019                              message
5020                              ("Operands of %s are non-booleans (%t, %t): %s",
5021                               lltok_unparse (op), te1, te2, exprNode_unparse (ret)),
5022                              e1->loc);
5023                         }
5024                     }
5025                   else if (!ctype_isRealBool (te1))
5026                     {
5027                       voptgenerror 
5028                         (FLG_BOOLOPS,
5029                          message ("Left operand of %s is non-boolean (%t): %s",
5030                                   lltok_unparse (op), te1, exprNode_unparse (ret)),
5031                          e1->loc);
5032                     }
5033                   else if (!ctype_isRealBool (te2))
5034                     {
5035                       voptgenerror
5036                         (FLG_BOOLOPS,
5037                          message ("Right operand of %s is non-boolean (%t): %s",
5038                                   lltok_unparse (op), te2, exprNode_unparse (ret)),
5039                          e2->loc);
5040                     }
5041                   else
5042                     {
5043                       ;
5044                     }
5045                 }
5046               tret = ctype_bool;
5047             }
5048           break;
5049         default: {
5050             llfatalbug 
5051               (cstring_makeLiteral 
5052                ("There has been a problem in the parser. This is due to a bug "
5053                 "in either lclint, bison or gcc version 2.95 optimizations, "
5054                 "but it has not been confirmed.  Please try rebuidling LCLint "
5055                 "without the -O<n> option."));
5056           }
5057         }
5058     }
5059
5060   DPRINTF (("Return type: %s", ctype_unparse (tret)));
5061   ret->typ = tret;
5062
5063   exprNode_checkUse (ret, e1->sref, e1->loc);  
5064   exprNode_mergeUSs (ret, e2);
5065   exprNode_checkUse (ret, e2->sref, e2->loc);  
5066
5067   return ret;
5068 }
5069
5070 /*@only@*/ exprNode
5071 exprNode_op (/*@only@*/ exprNode e1, /*@keep@*/ exprNode e2,
5072              /*@only@*/ lltok op)
5073 {
5074   exprNode ret;
5075
5076   checkMacroParen (e1);
5077   checkMacroParen (e2);
5078
5079   if (evaluationOrderUndefined (op) && context_maybeSet (FLG_EVALORDER))
5080     {
5081       checkExpressionDefined (e1, e2, op);
5082     }
5083
5084   ret = exprNode_makeOp (e1, e2, op);
5085   return (ret);
5086 }
5087
5088 static
5089 void exprNode_checkAssignMod (exprNode e1, exprNode ret)
5090 {
5091   /*
5092   ** This is somewhat bogus!
5093   **
5094   ** Assigning to a nested observer in a non-observer datatype
5095   ** should not produce an error.
5096   */
5097
5098   sRef ref = exprNode_getSref (e1);
5099
5100   DPRINTF (("Check assign mod: %s",
5101             sRef_unparseFull (ref)));
5102
5103   if (sRef_isObserver (ref) 
5104       || ((sRef_isFileStatic (ref) || sRef_isGlobal (ref))
5105           && ctype_isArray (ctype_realType (sRef_getType (ref)))))
5106     {
5107       sRef base = sRef_getBase (ref);
5108
5109       if (sRef_isValid (base) && sRef_isObserver (base))
5110         {
5111           exprNode_checkModify (e1, ret);
5112         }
5113       else
5114         {
5115           exprNode_checkModifyVal (e1, ret);
5116         }
5117     }
5118   else
5119     {
5120       exprNode_checkModify (e1, ret);
5121     }
5122 }
5123
5124 exprNode
5125 exprNode_assign (/*@only@*/ exprNode e1,
5126                  /*@only@*/ exprNode e2, /*@only@*/ lltok op)
5127 {
5128   bool isalloc = FALSE;
5129   bool isjustalloc = FALSE;
5130   exprNode ret;
5131
5132   DPRINTF (("%s [%s] <- %s [%s]",
5133             exprNode_unparse (e1),
5134             ctype_unparse (e1->typ),
5135             exprNode_unparse (e2),
5136             ctype_unparse (e2->typ)));
5137
5138   if (lltok_getTok (op) != TASSIGN) 
5139     {
5140       ret = exprNode_makeOp (e1, e2, op);
5141     } 
5142   else 
5143     {
5144       ret = exprNode_createPartialCopy (e1);
5145       ret->kind = XPR_ASSIGN;
5146       ret->edata = exprData_makeOp (e1, e2, op);
5147
5148       if (!exprNode_isError (e2)) 
5149         {
5150           ret->sets = sRefSet_union (ret->sets, e2->sets);
5151           ret->msets = sRefSet_union (ret->msets, e2->msets);
5152           ret->uses = sRefSet_union (ret->uses, e2->uses);
5153         }
5154     }
5155
5156   checkExpressionDefined (e1, e2, op);
5157
5158   if (exprNode_isError (e1))
5159     {
5160       if (!exprNode_isError (e2)) 
5161         {
5162           ret->loc = fileloc_update (ret->loc, e2->loc);
5163         }
5164       else
5165         {
5166           ret->loc = fileloc_update (ret->loc, g_currentloc);
5167         }
5168     }
5169
5170   if (!exprNode_isError (e2))
5171     {
5172       checkMacroParen (e2);
5173     }
5174
5175   if (exprNode_isDefined (e1))
5176     {
5177       if (sRef_isMacroParamRef (e1->sref))
5178         {
5179           if (context_inIterDef ())
5180             {
5181               uentry ue = sRef_getUentry (e1->sref);
5182               
5183               if (uentry_isYield (ue))
5184                 {
5185                   ;
5186                 }
5187               else
5188                 {
5189                   if (fileloc_isDefined (e1->loc))
5190                     {
5191                       voptgenerror
5192                         (FLG_MACROPARAMS,
5193                          message ("Assignment to non-yield iter parameter: %q", 
5194                                   sRef_unparse (e1->sref)),
5195                          e1->loc);
5196                     }
5197                   else
5198                     {
5199                       voptgenerror 
5200                         (FLG_MACROPARAMS,
5201                          message ("Assignment to non-yield iter parameter: %q", 
5202                                   sRef_unparse (e1->sref)),
5203                          g_currentloc);
5204                     }
5205                 }
5206             }
5207           else
5208             {
5209               if (fileloc_isDefined (e1->loc))
5210                 {
5211                   voptgenerror
5212                     (FLG_MACROASSIGN,
5213                      message ("Assignment to macro parameter: %q", 
5214                               sRef_unparse (e1->sref)),
5215                      e1->loc);
5216                 }
5217               else
5218                 {
5219                   voptgenerror 
5220                     (FLG_MACROASSIGN,
5221                      message ("Assignment to macro parameter: %q", 
5222                               sRef_unparse (e1->sref)),
5223                      g_currentloc);
5224                 }
5225             }
5226         }
5227       else
5228         {
5229           exprNode_checkAssignMod (e1, ret);
5230         }
5231
5232       if (exprNode_isDefined (e2))
5233         {
5234           if (lltok_getTok (op) == TASSIGN) 
5235             {
5236               ctype te1 = exprNode_getType (e1);
5237               ctype te2 = exprNode_getType (e2);
5238               
5239               if (!ctype_forceMatch (te1, te2))
5240                 {
5241                   if (exprNode_matchLiteral (te1, e2))
5242                     {
5243                       ;
5244                     }
5245                   else
5246                     {
5247                       (void) gentypeerror 
5248                         (te2, e2, te1, e1,
5249                          message ("Assignment of %t to %t: %s %s %s", 
5250                                   te2, te1, exprNode_unparse (e1),
5251                                   lltok_unparse (op), 
5252                                   exprNode_unparse (e2)),
5253                          e1->loc);
5254                     }
5255                 }
5256             }
5257          
5258           exprNode_mergeUSs (ret, e2);
5259           exprNode_checkUse (ret, e2->sref, e2->loc);
5260           
5261           doAssign (e1, e2, FALSE); 
5262           ret->sref = e1->sref;
5263         }
5264       else
5265         {
5266           if (exprNode_isDefined (e2))
5267             {
5268               exprNode_mergeUSs (ret, e2);
5269                       exprNode_checkUse (ret, e2->sref, e2->loc);
5270             }
5271         }
5272
5273       if (sRef_isPointer (e1->sref) && !sRef_isMacroParamRef (e1->sref))
5274         {
5275           exprNode_checkUse (ret, sRef_getBase (e1->sref), e1->loc);
5276         }
5277
5278       isjustalloc = sRef_isJustAllocated (e1->sref);
5279       isalloc = sRef_isAllocated (e1->sref);
5280
5281       if (sRef_isField (e1->sref))
5282         {
5283           sRef root = sRef_getRootBase (sRef_getBase (e1->sref));
5284           
5285           if (!sRef_isAllocated (root) && !sRef_isMacroParamRef (root))
5286             {
5287               exprNode_checkUse (ret, root, e1->loc);
5288             }
5289           
5290         }
5291   
5292       /*
5293       ** be careful!  this defines e1->sref.
5294       */
5295    
5296       if (!sRef_isMacroParamRef (e1->sref))
5297         {
5298           exprNode_checkSet (ret, e1->sref);
5299         }
5300       
5301       if (isjustalloc) 
5302         {
5303           sRef_setAllocatedComplete (e1->sref, exprNode_isDefined (e2)
5304                                      ? e2->loc : e1->loc);
5305         }
5306       else 
5307         {
5308           if (isalloc)
5309             {
5310               sRef_setAllocatedShallowComplete (e1->sref, exprNode_loc (e2));
5311             }
5312         }
5313     }
5314   
5315   return ret;
5316 }
5317
5318 exprNode
5319 exprNode_cond (/*@keep@*/ exprNode pred, /*@keep@*/ exprNode ifclause, 
5320                /*@keep@*/ exprNode elseclause)
5321 {
5322   exprNode ret;
5323
5324   if (!exprNode_isError (pred))
5325     {
5326       ret = exprNode_createPartialCopy (pred);
5327       checkMacroParen (pred);
5328       exprNode_checkPred (cstring_makeLiteralTemp ("conditional"), pred);
5329       
5330       if (!exprNode_isError (ifclause))
5331         {
5332           checkMacroParen (ifclause);   /* update macro counts! */
5333
5334           if (!exprNode_isError (elseclause))
5335             {
5336               checkMacroParen (elseclause);
5337               
5338               if (!exprNode_matchTypes (ifclause, elseclause))
5339                 {
5340                   if (gentypeerror 
5341                       (exprNode_getType (ifclause),
5342                        ifclause,
5343                        exprNode_getType (elseclause),
5344                        elseclause,
5345                        message ("Conditional clauses are not of same type: "
5346                                 "%s (%t), %s (%t)", 
5347                                 exprNode_unparse (ifclause), 
5348                                 exprNode_getType (ifclause),
5349                                 exprNode_unparse (elseclause), 
5350                                 exprNode_getType (elseclause)),
5351                        ifclause->loc))
5352                     {
5353                       ret->sref = sRef_undefined;
5354                       ret->typ = ctype_unknown;
5355                     }
5356                 }
5357               else
5358                 {
5359                   /* for now...should merge the states */
5360                   ret->sref = ifclause->sref;
5361                   ret->typ = ifclause->typ;
5362
5363                   if (exprNode_isNullValue (ifclause))
5364                     {
5365                       ret->typ = elseclause->typ;
5366                     }
5367                 }
5368               
5369               exprNode_checkUse (ret, pred->sref, pred->loc);
5370               exprNode_checkUse (ifclause, ifclause->sref, ifclause->loc);
5371               exprNode_checkUse (elseclause, elseclause->sref, elseclause->loc);
5372
5373               exprNode_mergeCondUSs (ret, ifclause, elseclause);
5374
5375             }
5376           else
5377             {
5378               ret->typ = ifclause->typ;
5379               
5380               exprNode_checkUse (pred, pred->sref, pred->loc);
5381               exprNode_checkUse (ifclause, ifclause->sref, ifclause->loc);
5382               
5383               exprNode_mergeCondUSs (ret, ifclause, exprNode_undefined);
5384             }
5385         }
5386       else 
5387         {
5388           if (!exprNode_isError (elseclause))
5389             {
5390               ret->typ = elseclause->typ;
5391               
5392               exprNode_checkUse (pred, pred->sref, pred->loc);
5393               exprNode_checkUse (elseclause, elseclause->sref, elseclause->loc);
5394               
5395               exprNode_mergeCondUSs (ret, exprNode_undefined, elseclause);
5396             }
5397         }
5398     }
5399   else /* pred is error */
5400     {
5401       if (!exprNode_isError (ifclause))
5402         {
5403           ret = exprNode_createSemiCopy (ifclause);
5404
5405           checkMacroParen (ifclause);   /* update macro counts! */
5406           
5407           if (!exprNode_isError (elseclause))
5408             {
5409               checkMacroParen (elseclause);
5410               
5411               ret->typ = ifclause->typ;
5412                       
5413               if (!ctype_forceMatch (ifclause->typ, elseclause->typ))
5414                 {
5415                   if (gentypeerror 
5416                       (exprNode_getType (ifclause),
5417                        ifclause,
5418                        exprNode_getType (elseclause),
5419                        elseclause,
5420                        message ("Conditional clauses are not of same type: "
5421                                 "%s (%t), %s (%t)", 
5422                                 exprNode_unparse (ifclause), 
5423                                 exprNode_getType (ifclause),
5424                                 exprNode_unparse (elseclause), 
5425                                 exprNode_getType (elseclause)),
5426                        ifclause->loc))
5427                     {
5428                       ret->typ = ctype_unknown;
5429                     }
5430                 }
5431                       
5432               exprNode_checkUse (ifclause, ifclause->sref, ifclause->loc);
5433               exprNode_checkUse (elseclause, elseclause->sref, elseclause->loc);
5434               
5435               exprNode_mergeCondUSs (ret, ifclause, elseclause);
5436             }
5437         }
5438       else if (!exprNode_isError (elseclause)) /* pred, if errors */
5439         {
5440           ret = exprNode_createSemiCopy (ifclause);
5441
5442           ret->typ = elseclause->typ;
5443           checkMacroParen (elseclause);
5444           
5445           exprNode_checkUse (elseclause, elseclause->sref, elseclause->loc);
5446           exprNode_mergeCondUSs (ret, exprNode_undefined, elseclause);
5447         }
5448       else /* all errors! */
5449         {
5450           ret = exprNode_createLoc (ctype_unknown, g_currentloc);
5451         }
5452     }
5453   
5454   ret->kind = XPR_COND;
5455   ret->edata = exprData_makeCond (pred, ifclause, elseclause);  
5456
5457   if (exprNode_isDefined (ifclause) && exprNode_isDefined (elseclause))
5458     {
5459       exprNode_combineControl (ret, ifclause, elseclause);
5460     }
5461
5462   return (ret);
5463 }
5464
5465 exprNode
5466 exprNode_vaArg (/*@only@*/ lltok tok, /*@only@*/ exprNode arg, /*@only@*/ qtype qt)
5467 {
5468   ctype totype = qtype_getType (qt);
5469   exprNode ret =
5470     exprNode_createPartialLocCopy (arg, fileloc_copy (lltok_getLoc (tok)));
5471   ctype targ;
5472
5473   /*
5474   ** check use of va_arg : <valist>, type -> type
5475   */
5476
5477   if (exprNode_isError (arg))
5478     {
5479     }
5480   else
5481     {
5482       targ = exprNode_getType (arg);
5483
5484       /*
5485       ** arg should have be a pointer
5486       */
5487
5488       if (!ctype_isUA (targ) ||
5489           (!usymId_equal (ctype_typeId (targ), 
5490                          usymtab_getTypeId (cstring_makeLiteralTemp ("va_list")))))
5491         {
5492           voptgenerror
5493             (FLG_TYPE,
5494              message ("First argument to va_arg is not a va_list (type %t): %s",
5495                       targ, exprNode_unparse (arg)),
5496              arg->loc);
5497         }
5498
5499       exprNode_checkSet (ret, arg->sref);
5500     }
5501   
5502   /*
5503   ** return type is totype
5504   */
5505
5506   ret->typ = totype;
5507   ret->kind = XPR_VAARG;
5508   ret->edata = exprData_makeCast (tok, arg, qt);
5509
5510   return (ret);
5511 }
5512
5513 exprNode exprNode_labelMarker (/*@only@*/ cstring label)
5514 {
5515   exprNode ret = exprNode_createPlain (ctype_undefined);
5516   ret->kind = XPR_LABEL;
5517   ret->edata = exprData_makeLiteral (label);
5518   ret->isJumpPoint = TRUE;
5519
5520   return (ret); /* for now, ignore label */
5521 }
5522
5523 exprNode exprNode_notReached (/*@returned@*/ exprNode stmt)
5524 {
5525   if (exprNode_isDefined (stmt))
5526     {
5527       stmt->isJumpPoint = TRUE;
5528
5529       /* This prevent stray no return path errors, etc. */
5530       stmt->exitCode = XK_MUSTEXIT;
5531     }
5532
5533   return (stmt); 
5534 }
5535
5536 bool exprNode_isDefaultMarker (exprNode e) 
5537 {
5538   if (exprNode_isDefined (e))
5539     {
5540       return (e->kind == XPR_DEFAULT || e->kind == XPR_FTDEFAULT);
5541     }
5542
5543   return FALSE;
5544 }
5545
5546 bool exprNode_isCaseMarker (exprNode e) 
5547 {
5548   if (exprNode_isDefined (e))
5549     {
5550       return (e->kind == XPR_FTCASE || e->kind == XPR_CASE);
5551     }
5552
5553   return FALSE;
5554 }
5555
5556 bool exprNode_isLabelMarker (exprNode e) 
5557 {
5558   if (exprNode_isDefined (e))
5559     {
5560       return (e->kind == XPR_LABEL);
5561     }
5562
5563   return FALSE;
5564 }
5565
5566 exprNode exprNode_caseMarker (/*@only@*/ exprNode test, bool fallThrough) 
5567 {
5568   exprNode ret = exprNode_createPartialCopy (test);
5569
5570   ret->kind = fallThrough ? XPR_FTCASE : XPR_CASE;
5571
5572   if (exprNode_isError (test)) {
5573     return ret;
5574   }
5575
5576   exprNode_checkUse (ret, test->sref, test->loc);
5577   
5578   usymtab_setExitCode (ret->exitCode);
5579   
5580   if (ret->mustBreak)
5581     {
5582       usymtab_setMustBreak ();
5583     }
5584
5585   ret->edata = exprData_makeSingle (test);
5586   ret->isJumpPoint = TRUE;
5587   
5588   return ret;
5589 }
5590
5591 # if 0
5592 exprNode exprNode_caseStatement (/*@only@*/ exprNode test, /*@only@*/ exprNode stmt, bool fallThrough)
5593 {
5594   exprNode ret = exprNode_createPartialCopy (test);
5595
5596   ret->kind = fallThrough ? XPR_FTCASE : XPR_CASE;
5597   ret->edata = exprData_makePair (test, stmt);
5598   ret->isJumpPoint = TRUE;
5599
5600   if (exprNode_isError (test))
5601     {
5602       return ret;
5603     }
5604
5605   exprNode_checkUse (ret, test->sref, test->loc);
5606   
5607   if (exprNode_isError (stmt))
5608     {
5609       return ret;
5610     }
5611   
5612   exprNode_mergeUSs (ret, stmt);
5613   
5614   ret->exitCode = stmt->exitCode;
5615   ret->mustBreak = stmt->mustBreak;
5616   ret->canBreak = stmt->canBreak;
5617
5618   usymtab_setExitCode (ret->exitCode);
5619   
5620   if (ret->mustBreak)
5621     {
5622       usymtab_setMustBreak ();
5623     }
5624   
5625   return ret;
5626 }
5627 # endif
5628
5629 /*@notnull@*/ /*@only@*/ exprNode 
5630 exprNode_defaultMarker (/*@only@*/ lltok def, bool fallThrough)
5631 {
5632   exprNode ret = exprNode_createTok (def);
5633   
5634   ret->isJumpPoint = TRUE;
5635   ret->kind = fallThrough ? XPR_FTDEFAULT : XPR_DEFAULT;
5636   return (ret);
5637 }
5638
5639 bool
5640 exprNode_mayEscape (exprNode e)
5641 {
5642   if (exprNode_isDefined (e))
5643     {
5644       return exitkind_couldEscape (e->exitCode);
5645     }
5646   return FALSE;
5647 }
5648
5649 static bool
5650 exprNode_mustBreak (exprNode e)
5651 {
5652   if (exprNode_isDefined (e))
5653     {
5654       return e->mustBreak;
5655     }
5656   return FALSE;
5657 }
5658
5659 bool
5660 exprNode_mustEscape (exprNode e)
5661 {
5662   if (exprNode_isDefined (e))
5663     {
5664       return exitkind_mustEscape (e->exitCode) || exprNode_mustBreak (e);
5665     }
5666
5667   return FALSE;
5668 }
5669
5670 bool
5671 exprNode_errorEscape (exprNode e)
5672 {
5673   if (exprNode_isDefined (e))
5674     {
5675       return exitkind_isError (e->exitCode);
5676     }
5677
5678   return FALSE;
5679 }
5680
5681 exprNode exprNode_concat (/*@only@*/ exprNode e1, /*@only@*/ exprNode e2)
5682 {
5683   exprNode ret = exprNode_createPartialCopy (e1);
5684
5685   ret->edata = exprData_makePair (e1, e2);
5686   ret->kind = XPR_STMTLIST;
5687
5688   if (exprNode_isDefined (e1))
5689     {
5690       ret->isJumpPoint = e1->isJumpPoint;
5691       ret->canBreak = e1->canBreak;
5692     }
5693   else
5694     {
5695       if (exprNode_isDefined (e2))
5696         {
5697           ret->loc = fileloc_update (ret->loc, e2->loc);
5698         }
5699     }
5700
5701   if (exprNode_isDefined (e2))
5702     {
5703       ret->exitCode = e2->exitCode;
5704       ret->mustBreak = e2->mustBreak;
5705       if (e2->canBreak) ret->canBreak = TRUE;
5706     }
5707
5708   /* 
5709   ** if e1 must return, then e2 is unreachable!
5710   */
5711
5712   if (exprNode_isDefined (e1) && exprNode_isDefined (e2))
5713     {
5714       if ((exprNode_mustEscape (e1) || exprNode_mustBreak (e1)) 
5715           && !(e2->isJumpPoint))
5716         {
5717           if (context_getFlag (FLG_UNREACHABLE))
5718             {
5719               exprNode nr = e2;
5720
5721               if (e2->kind == XPR_STMT)
5722                 {
5723                   nr = exprData_getUopNode (e2->edata);
5724                 }
5725
5726               if ((nr->kind == XPR_TOK 
5727                    && lltok_isSemi (exprData_getTok (nr->edata))))
5728                 {
5729                   /* okay to have unreachable ";" */
5730                   ret->exitCode = XK_MUSTEXIT;
5731                   ret->canBreak = TRUE;
5732                 }
5733               else
5734                 {
5735                   if (optgenerror (FLG_UNREACHABLE,
5736                                    message ("Unreachable code: %s", 
5737                                             exprNode_unparseFirst (nr)),
5738                                    exprNode_loc (nr)))
5739                     {
5740                       ret->isJumpPoint = TRUE;                
5741                       ret->mustBreak = FALSE;
5742                       ret->exitCode = XK_ERROR;
5743                       DPRINTF (("Jump point: %s", exprNode_unparse (ret)));
5744                     }
5745                   else
5746                     {
5747                       ret->exitCode = XK_MUSTEXIT;
5748                       ret->canBreak = TRUE;
5749                     }
5750
5751                 }
5752             }
5753         }
5754       else
5755         {
5756           if ((e2->kind == XPR_CASE || e2->kind == XPR_DEFAULT))
5757             {
5758               /*
5759               ** We want a warning anytime we have:
5760               **         case xxx: ...  
5761               **                   yyy;  <<<- no break or return
5762               **         case zzz: ...
5763               */
5764               
5765               exprNode lastStmt = exprNode_lastStatement (e1);
5766               
5767               if (exprNode_isDefined (lastStmt) 
5768                   && !exprNode_mustEscape (lastStmt)
5769                   && !exprNode_mustBreak (lastStmt)
5770                   && !exprNode_isCaseMarker (lastStmt)
5771                   && !exprNode_isDefaultMarker (lastStmt)
5772                   && !exprNode_isLabelMarker (lastStmt))
5773                 {
5774                   voptgenerror (FLG_CASEBREAK,
5775                                 cstring_makeLiteral 
5776                                 ("Fall through case (no preceeding break)"),
5777                                 e2->loc);
5778                 }
5779             }
5780         }
5781     }
5782
5783   exprNode_mergeUSs (ret, e2);
5784   ret = exprNode_mergeEnvironments (ret, e1, e2);
5785   usymtab_setExitCode (ret->exitCode);
5786   
5787   if (ret->mustBreak)
5788     {
5789       usymtab_setMustBreak ();
5790     }
5791
5792   return ret;
5793 }
5794
5795 exprNode exprNode_createTok (/*@only@*/ lltok t)
5796 {
5797   exprNode ret = exprNode_create (ctype_unknown);
5798   ret->kind = XPR_TOK;
5799   ret->edata = exprData_makeTok (t);
5800   return ret;
5801 }
5802
5803 exprNode exprNode_statement (/*@only@*/ exprNode e, /*@only@*/ lltok t)
5804 {
5805   if (!exprNode_isError (e))
5806     {
5807       exprNode_checkStatement(e);
5808     }
5809
5810   return (exprNode_statementError (e, t));
5811 }
5812
5813 static exprNode exprNode_statementError (/*@only@*/ exprNode e, /*@only@*/ lltok t)
5814 {
5815   exprNode ret = exprNode_createPartialCopy (e);
5816
5817   if (!exprNode_isError (e))
5818     {
5819       if (e->kind != XPR_ASSIGN)
5820         {
5821           exprNode_checkUse (ret, e->sref, e->loc);
5822         }
5823
5824       ret->exitCode = e->exitCode;
5825       ret->canBreak = e->canBreak;
5826       ret->mustBreak = e->mustBreak;
5827     }
5828   
5829   ret->edata = exprData_makeUop (e, t);
5830   ret->kind = XPR_STMT;
5831
5832   return ret;
5833 }
5834
5835 exprNode exprNode_checkExpr (/*@returned@*/ exprNode e)
5836 {
5837   if (!exprNode_isError (e))
5838     {
5839       if (e->kind != XPR_ASSIGN)
5840         {
5841           exprNode_checkUse (e, e->sref, e->loc);
5842         }
5843     }
5844
5845   return e;
5846 }
5847
5848 void exprNode_produceGuards (exprNode pred)
5849 {
5850   if (!exprNode_isError (pred))
5851     {
5852       if (ctype_isRealPointer (pred->typ))
5853         {
5854           pred->guards = guardSet_addTrueGuard (pred->guards, pred->sref);
5855         }
5856       
5857       exprNode_checkUse (pred, pred->sref, pred->loc);
5858       exprNode_resetSref (pred);
5859     }
5860 }
5861
5862 exprNode exprNode_makeBlock (/*@only@*/ exprNode e)
5863 {
5864   exprNode ret = exprNode_createPartialCopy (e);
5865
5866   if (!exprNode_isError (e))
5867     {
5868       ret->exitCode = e->exitCode;
5869       ret->canBreak = e->canBreak;
5870       ret->mustBreak = e->mustBreak;
5871     }
5872   
5873   ret->edata = exprData_makeSingle (e);
5874   ret->kind = XPR_BLOCK;
5875   return ret;
5876 }
5877
5878 bool exprNode_isBlock (exprNode e)
5879 {
5880   return (exprNode_isDefined (e) 
5881           && ((e)->kind == XPR_BLOCK));
5882 }
5883  
5884 bool exprNode_isAssign (exprNode e)
5885 {
5886   if (exprNode_isDefined (e))
5887     {
5888       return (e->kind == XPR_ASSIGN);
5889     }
5890
5891   return FALSE;
5892 }
5893
5894 bool exprNode_isEmptyStatement (exprNode e)
5895 {
5896   return (exprNode_isDefined (e) 
5897           && (e->kind == XPR_TOK)
5898           && (lltok_isSemi (exprData_getTok (e->edata))));
5899 }
5900
5901 exprNode exprNode_if (/*@only@*/ exprNode pred, /*@only@*/ exprNode tclause)
5902 {
5903   exprNode ret;
5904   bool emptyErr = FALSE;
5905
5906   if (context_maybeSet (FLG_IFEMPTY))
5907     {
5908       if (exprNode_isEmptyStatement (tclause))
5909         {
5910           emptyErr = optgenerror (FLG_IFEMPTY,
5911                                   cstring_makeLiteral
5912                                   ("Body of if statement is empty"),
5913                                   exprNode_loc (tclause));
5914         }
5915     }
5916
5917   if (!emptyErr && context_maybeSet (FLG_IFBLOCK))
5918     {
5919       if (exprNode_isDefined (tclause)
5920           && !exprNode_isBlock (tclause))
5921         {
5922           voptgenerror (FLG_IFBLOCK,
5923                         message
5924                         ("Body of if statement is not a block: %s",
5925                          exprNode_unparse (tclause)),
5926                         exprNode_loc (tclause));
5927         }
5928     }
5929
5930   if (exprNode_isError (pred))
5931     {
5932       if (exprNode_isError (tclause))
5933         {
5934           ret = exprNode_createLoc (ctype_unknown, g_currentloc);
5935         }
5936       else
5937         {
5938           ret = exprNode_createPartialCopy (tclause);
5939         }
5940     }
5941   else
5942     {
5943       if (exprNode_mustEscape (pred))
5944         {
5945           voptgenerror 
5946             (FLG_UNREACHABLE,
5947              message ("Predicate always exits: %s", exprNode_unparse (pred)),
5948              exprNode_loc (pred));
5949         }
5950
5951       exprNode_checkPred (cstring_makeLiteralTemp ("if"), pred);
5952       exprNode_checkUse (pred, pred->sref, pred->loc);
5953       
5954       if (!exprNode_isError (tclause))
5955         {
5956           exprNode_mergeCondUSs (pred, tclause, exprNode_undefined);
5957         }
5958       
5959       ret = exprNode_createPartialCopy (pred);
5960     }
5961
5962   ret->kind = XPR_IF;
5963   ret->edata = exprData_makePair (pred, tclause);
5964
5965   ret->exitCode = XK_UNKNOWN;
5966
5967   if (exprNode_isDefined (tclause))
5968     {
5969       ret->exitCode = exitkind_makeConditional (tclause->exitCode);
5970       ret->canBreak = tclause->canBreak;
5971       ret->sets = sRefSet_union (ret->sets, tclause->sets);
5972       ret->msets = sRefSet_union (ret->msets, tclause->msets);
5973       ret->uses = sRefSet_union (ret->uses, tclause->uses);
5974     }
5975
5976   ret->mustBreak = FALSE;
5977
5978   return ret;
5979 }
5980
5981 exprNode exprNode_ifelse (/*@only@*/ exprNode pred,
5982                           /*@only@*/ exprNode tclause, 
5983                           /*@only@*/ exprNode eclause)
5984 {
5985   exprNode ret;
5986   bool tEmptyErr = FALSE;
5987   bool eEmptyErr = FALSE;
5988
5989   if (context_maybeSet (FLG_IFEMPTY))
5990     {
5991       if (exprNode_isEmptyStatement (tclause))
5992         {
5993           tEmptyErr = optgenerror 
5994             (FLG_IFEMPTY,
5995              cstring_makeLiteral
5996              ("Body of if clause of if statement is empty"),
5997              exprNode_loc (tclause));
5998         }
5999
6000       if (exprNode_isEmptyStatement (eclause))
6001         {
6002           eEmptyErr = optgenerror 
6003             (FLG_IFEMPTY,
6004              cstring_makeLiteral
6005              ("Body of else clause of if statement is empty"),
6006              exprNode_loc (eclause));
6007         }
6008     }
6009
6010   if (context_maybeSet (FLG_IFBLOCK))
6011     {
6012       if (!tEmptyErr
6013           && exprNode_isDefined (tclause)
6014           && !exprNode_isBlock (tclause))
6015         {
6016           voptgenerror (FLG_IFBLOCK,
6017                         message
6018                         ("Body of if clause of if statement is not a block: %s",
6019                          exprNode_unparse (tclause)),
6020                         exprNode_loc (tclause));
6021         }
6022
6023       if (!eEmptyErr
6024           && exprNode_isDefined (eclause)
6025           && !exprNode_isBlock (eclause)
6026           && !(eclause->kind == XPR_IF)
6027           && !(eclause->kind == XPR_IFELSE))
6028         {
6029           voptgenerror
6030             (FLG_IFBLOCK,
6031              message
6032              ("Body of else clause of if statement is not a block: %s",
6033               exprNode_unparse (eclause)),
6034              exprNode_loc (eclause));
6035         }
6036     }
6037
6038   if (context_maybeSet (FLG_ELSEIFCOMPLETE))
6039     {
6040       if (exprNode_isDefined (eclause)
6041           && (eclause->kind == XPR_IF))
6042         {
6043           voptgenerror (FLG_ELSEIFCOMPLETE,
6044                         message ("Incomplete else if logic (no final else): %s",
6045                                  exprNode_unparse (eclause)),
6046                         exprNode_loc (eclause));
6047         }
6048     }
6049
6050   if (exprNode_isError (pred))
6051     {
6052       if (exprNode_isError (tclause))
6053         {
6054           if (exprNode_isError (eclause))
6055             {
6056               ret = exprNode_createLoc (ctype_unknown, g_currentloc);
6057             }
6058           else
6059             {
6060               ret = exprNode_createPartialCopy (eclause);
6061             }
6062         }
6063       else 
6064         {
6065           ret = exprNode_createPartialCopy (tclause);
6066         }
6067     }
6068   else /* pred is okay */
6069     {
6070       ret = exprNode_createPartialCopy (pred);
6071
6072       if (exprNode_mustEscape (pred))
6073         {
6074           voptgenerror
6075             (FLG_UNREACHABLE,
6076              message ("Predicate always exits: %s", exprNode_unparse (pred)),
6077              exprNode_loc (pred));
6078         }
6079       
6080       exprNode_checkPred (cstring_makeLiteralTemp ("if"), pred);
6081       exprNode_checkUse (ret, pred->sref, pred->loc);
6082       
6083       exprNode_mergeCondUSs (ret, tclause, eclause);
6084     }
6085
6086   ret->kind = XPR_IFELSE;
6087   ret->edata = exprData_makeCond (pred, tclause, eclause);
6088
6089   if (exprNode_isDefined (tclause) && exprNode_isDefined (eclause))
6090     {
6091       exprNode_combineControl (ret, tclause, eclause);
6092       ret->loc = fileloc_update (ret->loc, eclause->loc);
6093     }
6094
6095   return ret;
6096 }
6097
6098 /*
6099 ** *allpaths <- TRUE iff all executions paths must go through the switch
6100 */
6101
6102 static bool
6103 checkSwitchExpr (exprNode test, /*@dependent@*/ exprNode e, /*@out@*/ bool *allpaths)
6104 {
6105   exprNodeSList el = exprNode_flatten (e);
6106   bool mustReturn = TRUE; /* find a branch that doesn't */
6107   bool thisReturn = FALSE;
6108   bool hasDefault = FALSE;
6109   bool hasAllMembers = FALSE;
6110   bool inSwitch = FALSE;
6111   bool isEnumSwitch = FALSE;
6112   bool canBreak = FALSE;
6113   bool fallThrough = FALSE;
6114   ctype ct = ctype_unknown;
6115   enumNameSList usedEnums;
6116   enumNameList enums;
6117
6118   if (exprNode_isDefined (test))
6119     {
6120       ctype ttype;
6121
6122       ct = test->typ;
6123       ttype = ctype_realType (ct);
6124
6125       if (ctype_isEnum (ttype))
6126         {
6127           isEnumSwitch = TRUE;
6128           enums = ctype_elist (ttype);
6129           usedEnums = enumNameSList_new ();
6130         }
6131     }
6132
6133   exprNodeSList_elements (el, current)
6134     {
6135       if (exprNode_isDefined (current))
6136         {
6137           switch (current->kind)
6138             {
6139             case XPR_FTDEFAULT:
6140             case XPR_DEFAULT:
6141               if (hasDefault)
6142                 {
6143                   voptgenerror 
6144                     (FLG_CONTROL,
6145                      message ("Duplicate default cases in switch"),
6146                      exprNode_loc (current));
6147                 }          
6148             /*@fallthrough@*/
6149             case XPR_FTCASE:
6150             case XPR_CASE: 
6151               if (current->kind == XPR_DEFAULT || current->kind == XPR_FTDEFAULT)
6152                 {
6153                   hasDefault = TRUE; 
6154                 }
6155               else
6156                 {
6157                   if (isEnumSwitch)
6158                     {
6159                       exprNode st = exprData_getSingle (current->edata);
6160                       uentry ue = exprNode_getUentry (st);
6161                       
6162                       if (uentry_isValid (ue))
6163                         {
6164                           cstring cname = uentry_rawName (ue);
6165                           
6166                           if (enumNameList_member (/*@-usedef@*/enums/*@=usedef@*/, cname))
6167                             {
6168                               if (enumNameSList_member
6169                                   (/*@-usedef@*/usedEnums/*@=usedef@*/, cname))
6170                                 {
6171                                   voptgenerror
6172                                     (FLG_CONTROL,
6173                                      message ("Duplicate case in switch: %s", 
6174                                               cname),
6175                                      current->loc);
6176                                 }
6177                               else
6178                                 {
6179                                   enumNameSList_addh (usedEnums, cname);
6180                                 }
6181                             }
6182                           else
6183                             {
6184                               voptgenerror 
6185                                 (FLG_TYPE,
6186                                  message ("Case in switch not %s member: %s", 
6187                                           ctype_unparse (ct), cname),
6188                                  current->loc);
6189                             }
6190                         }
6191                     }
6192                 }
6193               
6194               if (inSwitch && !fallThrough)
6195                 {
6196                   if (!thisReturn || canBreak) 
6197                     {
6198                       mustReturn = FALSE;
6199                     }
6200                 }
6201               
6202               fallThrough = TRUE;
6203               inSwitch = TRUE;
6204               thisReturn = FALSE;
6205               canBreak = FALSE;
6206               /*@switchbreak@*/ break;
6207             default:
6208               thisReturn = thisReturn || exprNode_mustEscape (current);
6209               canBreak = canBreak || current->canBreak;
6210               if (canBreak) fallThrough = FALSE;
6211             }
6212         }
6213     } end_exprNodeSList_elements;
6214
6215   if (inSwitch) /* check the last one! */
6216     {
6217       if (!thisReturn || canBreak) 
6218         {
6219           mustReturn = FALSE;
6220         }
6221     }
6222   
6223   if (isEnumSwitch)
6224     {
6225       if (!hasDefault 
6226           && (enumNameSList_size (/*@-usedef@*/usedEnums/*@=usedef@*/) != 
6227               enumNameList_size (/*@-usedef@*/enums/*@=usedef@*/)))
6228         {
6229           enumNameSList unused = enumNameSList_subtract (enums, usedEnums);
6230           
6231           voptgenerror (FLG_MISSCASE,
6232                         message ("Missing case%s in switch: %q",
6233                                  cstring_makeLiteralTemp 
6234                                  ((enumNameSList_size (unused) > 1) ? "s" : ""),
6235                                  enumNameSList_unparse (unused)),
6236                         g_currentloc);
6237
6238           enumNameSList_free (unused);
6239         }
6240       else
6241         {
6242           hasAllMembers = TRUE;
6243           *allpaths = TRUE;
6244         }
6245
6246       enumNameSList_free (usedEnums);
6247     }
6248   else
6249     {
6250       *allpaths = hasDefault;
6251     }
6252
6253   exprNodeSList_free (el);
6254   return ((hasDefault || hasAllMembers) && mustReturn);  
6255 }
6256     
6257 exprNode exprNode_switch (/*@only@*/ exprNode e, /*@only@*/ exprNode s)
6258 {
6259   exprNode ret = exprNode_createPartialCopy (e);
6260   bool allpaths;
6261
6262   DPRINTF (("Switch: %s", exprNode_unparse (s)));
6263
6264   ret->kind = XPR_SWITCH;
6265   ret->edata = exprData_makePair (e, s);
6266   
6267   if (!exprNode_isError (s))
6268     {
6269       exprNode fs = exprNode_firstStatement (s);
6270       ret->loc = fileloc_update (ret->loc, s->loc);
6271
6272       if (exprNode_isUndefined (fs) 
6273           || exprNode_isCaseMarker (fs) || exprNode_isLabelMarker (fs)
6274           || exprNode_isDefaultMarker (fs)) {
6275         ;
6276       } else {
6277         voptgenerror (FLG_FIRSTCASE,
6278                       message
6279                       ("Statement after switch is not a case: %s", exprNode_unparse (fs)),
6280                       fs->loc);
6281       }
6282     }
6283
6284   if (!exprNode_isError (e)) 
6285     {
6286       if (checkSwitchExpr (e, s, &allpaths))
6287         {
6288           ret->exitCode = XK_MUSTRETURN;
6289         }
6290       else
6291         {
6292           ret->exitCode = e->exitCode;
6293         }
6294
6295       ret->canBreak = e->canBreak;
6296       ret->mustBreak = e->mustBreak;
6297     }
6298   /*
6299   ** forgot this!
6300   **   exprNode.c:3883,32: Variable allpaths used before definition
6301   */
6302   else 
6303     {
6304       allpaths = FALSE;
6305     }
6306   
6307   DPRINTF (("Context exit switch!"));
6308   context_exitSwitch (ret, allpaths);
6309   DPRINTF (("Context exit switch done!"));
6310
6311   return ret;
6312 }
6313
6314 static void checkInfiniteLoop (/*@notnull@*/ exprNode test,
6315                                /*@notnull@*/ exprNode body)
6316 {
6317   sRefSet tuses = test->uses;
6318   
6319   if (!sRefSet_isEmpty (test->uses))
6320     {
6321       sRefSet sets = sRefSet_newCopy (body->sets);
6322       bool hasError = TRUE;
6323       bool innerState = FALSE;
6324       sRefSet tuncon = sRefSet_undefined;
6325       
6326       sets = sRefSet_union (sets, test->sets);
6327       sets = sRefSet_union (sets, body->msets);
6328       sets = sRefSet_union (sets, test->msets);
6329
6330       sRefSet_allElements (tuses, el)
6331         {
6332           if (sRef_isUnconstrained (el))
6333             {
6334               tuncon = sRefSet_insert (tuncon, el);
6335             }
6336           else
6337             {
6338               if (sRefSet_member (sets, el))
6339                 {
6340                   hasError = FALSE;
6341                   break;
6342                 }
6343             }
6344
6345           if (sRef_isInternalState (el)
6346               || sRef_isFileStatic (sRef_getRootBase (el)))
6347             {
6348               innerState = TRUE;
6349             }
6350         } end_sRefSet_allElements ;
6351
6352       if (hasError)
6353         {
6354           sRefSet suncon = sRefSet_undefined;
6355           bool sinner = FALSE;
6356
6357           sRefSet_allElements (sets, el)
6358             {
6359               if (sRef_isUnconstrained (el))
6360                 {
6361                   suncon = sRefSet_insert (suncon, el);
6362                 }
6363               else if (sRef_isInternalState (el))
6364                 {
6365                   sinner = TRUE;
6366                 }
6367               else
6368                 {
6369                   ;
6370                 }
6371             } end_sRefSet_allElements ;
6372
6373           if (sinner && innerState)
6374             {
6375               ; 
6376             }
6377           else if (sRefSet_isEmpty (tuncon)
6378                    && sRefSet_isEmpty (suncon))
6379             {
6380               voptgenerror 
6381                 (FLG_INFLOOPS,
6382                  message
6383                  ("Suspected infinite loop.  No value used in loop test (%q) "
6384                   "is modified by test or loop body.",
6385                   sRefSet_unparsePlain (tuses)), 
6386                  test->loc);
6387             }
6388           else
6389             {
6390               if (sRefSet_isEmpty (tuncon))
6391                 {
6392                   voptgenerror 
6393                     (FLG_INFLOOPSUNCON,
6394                      message ("Suspected infinite loop.  No condition values "
6395                               "modified.  Modification possible through "
6396                               "unconstrained calls: %q",
6397                               sRefSet_unparsePlain (suncon)), 
6398                      test->loc);
6399                 }
6400               else
6401                 {
6402                   voptgenerror 
6403                     (FLG_INFLOOPSUNCON,
6404                      message ("Suspected infinite loop.  No condition values "
6405                               "modified.  Possible undetected dependency through "
6406                               "unconstrained calls in loop test: %q",
6407                               sRefSet_unparsePlain (tuncon)), 
6408                      test->loc);
6409                 }
6410             }
6411         }
6412
6413       sRefSet_free (sets);
6414     }
6415 }
6416
6417 exprNode exprNode_while (/*@keep@*/ exprNode t, /*@keep@*/ exprNode b)
6418 {
6419   exprNode ret;
6420   bool emptyErr = FALSE;
6421   char *s;
6422   //  s = exprNode_generateConstraints (t);
6423   // printf("pred: %s\n", s);
6424   // s = exprNode_generateConstraints (b);
6425   //printf ("body: %s\n", s);
6426   //constraintList_print(b->constraints);
6427   
6428   if (context_maybeSet (FLG_WHILEEMPTY))
6429     {
6430       if (exprNode_isEmptyStatement (b))
6431         {
6432           emptyErr = optgenerror 
6433             (FLG_WHILEEMPTY,
6434              cstring_makeLiteral
6435              ("Body of while statement is empty"),
6436              exprNode_loc (b));
6437         }
6438     }
6439
6440   if (!emptyErr && context_maybeSet (FLG_WHILEBLOCK))
6441     {
6442       if (exprNode_isDefined (b)
6443           && !exprNode_isBlock (b))
6444         {
6445           if (context_inIterDef ()
6446               && (b->kind == XPR_STMTLIST
6447                   || b->kind == XPR_TOK))
6448             {
6449               ; /* no error */
6450             }
6451           else
6452             {
6453               voptgenerror (FLG_WHILEBLOCK,
6454                             message
6455                             ("Body of while statement is not a block: %s",
6456                              exprNode_unparse (b)),
6457                             exprNode_loc (b));
6458             }
6459         }
6460     }
6461   
6462   if (exprNode_isError (t))
6463     {
6464       if (exprNode_isError (b))
6465         {
6466           ret = exprNode_createLoc (ctype_unknown, g_currentloc);
6467         }
6468       else
6469         {
6470           ret = exprNode_createPartialCopy (b);
6471         }
6472     }
6473   else
6474     {
6475       exprNode test;
6476
6477       ret = exprNode_createPartialCopy (t);
6478       
6479       llassert (t->kind == XPR_WHILEPRED);
6480
6481       test = exprData_getSingle (t->edata);
6482
6483       if (!exprNode_isError (b) && exprNode_isDefined (test))
6484         {
6485           if (context_maybeSet (FLG_INFLOOPS)
6486               || context_maybeSet (FLG_INFLOOPSUNCON))
6487             {
6488               /*
6489               ** check that some variable in the predicate is set by the body
6490               ** if the predicate uses any variables
6491               */
6492               
6493               checkInfiniteLoop (test, b);
6494             }
6495
6496           exprNode_mergeUSs (ret, b);
6497
6498           if (exprNode_isDefined (b))
6499             {
6500               ret->exitCode = exitkind_makeConditional (b->exitCode);
6501             }
6502         }
6503     }
6504   
6505   ret->edata = exprData_makePair (t, b);
6506   ret->kind = XPR_WHILE;
6507
6508   if (exprNode_isDefined (t) && exprNode_mustEscape (t))
6509     {
6510       voptgenerror
6511         (FLG_CONTROL,
6512          message ("Predicate always exits: %s", exprNode_unparse (t)),
6513          exprNode_loc (t));
6514     }
6515
6516   ret->exitCode = XK_NEVERESCAPE;
6517
6518   /*
6519   ** If loop is infinite, and there is no break inside, 
6520   ** exit code is never reach. 
6521   */
6522
6523   if (exprNode_knownIntValue (t))
6524     {
6525       if (!exprNode_isZero (t)) 
6526         {
6527           if (exprNode_isDefined (b)) 
6528             {
6529               if (!b->canBreak) 
6530                 {
6531                   /* Really, it means never reached. */
6532                   ret->exitCode = XK_MUSTEXIT;
6533                 }
6534             }
6535         }
6536     } 
6537   else 
6538     {
6539       ;
6540     }
6541
6542   ret->canBreak = FALSE;
6543   ret->mustBreak = FALSE;
6544
6545   return ret; 
6546 }
6547
6548 /*
6549 ** do { b } while (t);
6550 ** 
6551 ** note: body passed as first argument 
6552 */
6553
6554 exprNode exprNode_doWhile (/*@only@*/ exprNode b, /*@only@*/ exprNode t)
6555 {
6556   exprNode ret;
6557   
6558   if (exprNode_isError (t))
6559     {
6560       if (exprNode_isError (b))
6561         {
6562           ret = exprNode_createLoc (ctype_unknown, g_currentloc);
6563         }
6564       else
6565         {
6566           ret = exprNode_createPartialCopy (b);
6567
6568           ret->exitCode = exitkind_makeConditional (b->exitCode);
6569           exprNode_checkUse (ret, b->sref, b->loc);
6570           ret->exitCode = b->exitCode;
6571           ret->canBreak = b->canBreak;
6572           ret->mustBreak = b->mustBreak;
6573         }
6574     }
6575   else
6576     {
6577       ret = exprNode_createPartialCopy (t);
6578       exprNode_checkPred (cstring_makeLiteralTemp ("while"), t);
6579       
6580       if (!exprNode_isError (b)) 
6581         {
6582           /*
6583           ** forgot the copy's --- why wasn't this detected??
6584           */
6585
6586           ret->sets = sRefSet_copy (ret->sets, b->sets);
6587           ret->msets = sRefSet_copy (ret->msets, b->msets);
6588           ret->uses = sRefSet_copy (ret->uses, b->uses);  
6589
6590           /* left this out --- causes and aliasing bug (infinite loop)
6591              should be detected?? */
6592
6593           exprNode_checkUse (ret, b->sref, b->loc);
6594           exprNode_mergeUSs (ret, t);
6595           exprNode_checkUse (ret, t->sref, t->loc);
6596
6597           ret->exitCode = b->exitCode;
6598           ret->canBreak = b->canBreak;
6599           ret->mustBreak = b->mustBreak;
6600         }
6601     }
6602   
6603   context_exitDoWhileClause (t);
6604
6605   ret->kind = XPR_DOWHILE;
6606   ret->edata = exprData_makePair (t, b);
6607     return ret;
6608 }
6609
6610 exprNode exprNode_for (/*@keep@*/ exprNode inc, /*@keep@*/ exprNode body)
6611 {
6612   exprNode ret;
6613   bool emptyErr = FALSE;
6614
6615   if (context_maybeSet (FLG_FOREMPTY))
6616     {
6617       if (exprNode_isEmptyStatement (body))
6618         {
6619           emptyErr = optgenerror 
6620             (FLG_FOREMPTY,
6621              cstring_makeLiteral
6622              ("Body of for statement is empty"),
6623              exprNode_loc (body));
6624         }
6625     }
6626
6627   if (!emptyErr && context_maybeSet (FLG_FORBLOCK))
6628     {
6629       if (exprNode_isDefined (body)
6630           && !exprNode_isBlock (body))
6631         {
6632           if (context_inIterDef ()
6633               && (body->kind == XPR_STMTLIST
6634                   || body->kind == XPR_TOK))
6635             {
6636               ; /* no error */
6637             }
6638           else
6639             {
6640               voptgenerror (FLG_FORBLOCK,
6641                             message
6642                             ("Body of for statement is not a block: %s",
6643                              exprNode_unparse (body)),
6644                             exprNode_loc (body));
6645             }
6646         }
6647     }
6648
6649   /*
6650   ** for ud purposes:  (alreadly) init -> test -> (now) LOOP: body + inc + test
6651   */
6652
6653   if (exprNode_isError (body))
6654     {
6655       ret = exprNode_createPartialCopy (inc);
6656     }
6657   else
6658     {
6659       ret = exprNode_createPartialCopy (body);
6660       
6661       ret->exitCode = exitkind_makeConditional (body->exitCode);
6662
6663             exprNode_mergeUSs (inc, body);
6664       
6665       if (exprNode_isDefined (inc))
6666         {
6667           exprNode tmp;
6668
6669           context_setMessageAnnote (cstring_makeLiteral ("in post loop increment"));
6670      
6671           
6672           tmp = exprNode_effect (exprData_getTripleInc (inc->edata));
6673           exprNode_freeShallow (tmp); 
6674
6675           context_clearMessageAnnote ();
6676           context_setMessageAnnote (cstring_makeLiteral ("in post loop test"));
6677
6678           tmp = exprNode_effect (exprData_getTripleTest (inc->edata));
6679           exprNode_freeShallow (tmp);
6680
6681           context_clearMessageAnnote ();
6682
6683           ret->uses = sRefSet_copy (ret->uses, inc->uses);
6684           ret->sets = sRefSet_copy (ret->sets, inc->sets);
6685           ret->msets = sRefSet_copy (ret->msets, inc->msets);
6686         }
6687     }
6688
6689   ret->kind = XPR_FOR;
6690   ret->edata = exprData_makePair (inc, body);
6691
6692   if (exprNode_isDefined (inc)) {
6693     exprNode test = exprData_getTripleTest (inc->edata);
6694
6695     if (exprNode_isUndefined (test)) {
6696       if (exprNode_isDefined (body)) {
6697         if (!body->canBreak) {
6698           /* Really, it means never reached. */
6699           ret->exitCode = XK_MUSTEXIT;
6700         }
6701       }
6702     }
6703   }
6704
6705   return (ret);
6706 }
6707
6708 /*
6709 ** for (init; test; inc)
6710 ** ==>
6711 ** init;
6712 ** while (test) { body; inc; } 
6713 **
6714 ** Now: check use of init (may set vars for test)
6715 **      check use of test
6716 **      no checks on inc
6717 _*/
6718
6719 /*@observer@*/ guardSet exprNode_getForGuards (exprNode pred)
6720 {
6721   exprNode test;
6722
6723   if (exprNode_isError (pred)) return guardSet_undefined;
6724
6725   llassert (pred->kind == XPR_FORPRED);
6726
6727   test = exprData_getTripleTest (pred->edata);
6728
6729   if (!exprNode_isError (test))
6730     {
6731       return (test->guards);
6732     }
6733
6734   return guardSet_undefined;
6735 }
6736
6737 exprNode exprNode_whilePred (/*@only@*/ exprNode test)
6738 {
6739   exprNode ret = exprNode_createSemiCopy (test);
6740
6741   if (exprNode_isDefined (test))
6742     {
6743       exprNode_copySets (ret, test);
6744       exprNode_checkPred (cstring_makeLiteralTemp ("while"), test);
6745       exprNode_checkUse (ret, test->sref, test->loc);
6746       
6747       exprNode_produceGuards (test);
6748       
6749       ret->guards = guardSet_copy (test->guards);
6750     }
6751
6752   ret->edata = exprData_makeSingle (test);
6753   ret->kind = XPR_WHILEPRED;
6754   return ret;
6755 }
6756
6757 exprNode exprNode_forPred (/*@only@*/ exprNode init, /*@only@*/ exprNode test, 
6758                            /*@only@*/ exprNode inc)
6759 {
6760   exprNode ret;
6761   
6762   /*
6763   ** for ud purposes:  init -> test -> LOOP: [ body, inc ]
6764   */
6765   
6766   exprNode_checkPred (cstring_makeLiteralTemp ("for"), test);
6767
6768   if (!exprNode_isError (inc)) 
6769     {
6770       ret = exprNode_createPartialCopy (inc);
6771     }
6772   else 
6773     {
6774       if (!exprNode_isError (init)) 
6775         {
6776           ret = exprNode_createPartialCopy (init);
6777         }
6778       else if (!exprNode_isError (test)) 
6779         {
6780           ret = exprNode_createPartialCopy (test);
6781         }
6782       else 
6783         {
6784           ret = exprNode_createUnknown ();
6785         }
6786     }
6787
6788   exprNode_mergeUSs (ret, init);
6789
6790   if (exprNode_isDefined (init))
6791     {
6792       exprNode_checkUse (ret, init->sref, init->loc);
6793     }
6794
6795   exprNode_mergeUSs (ret, test);
6796
6797   if (exprNode_isDefined (test))
6798     {
6799       exprNode_checkUse (ret, test->sref, test->loc);
6800     }
6801
6802   ret->kind = XPR_FORPRED;
6803   ret->edata = exprData_makeFor (init, test, inc); 
6804   return (ret);
6805 }
6806
6807 /*@notnull@*/ /*@only@*/ exprNode exprNode_goto (/*@only@*/ cstring label)
6808 {
6809   exprNode ret = exprNode_createUnknown ();
6810
6811   if (context_inMacro ())
6812     {
6813       voptgenerror (FLG_MACROSTMT,
6814                     message ("Macro %s uses goto (not functional)", 
6815                              context_inFunctionName ()),
6816                     g_currentloc);
6817     }
6818   
6819   ret->kind = XPR_GOTO;
6820   ret->edata = exprData_makeLiteral (label);
6821   ret->mustBreak = TRUE;
6822   ret->exitCode = XK_GOTO;
6823   ret->canBreak = TRUE;
6824   return ret;
6825 }
6826
6827 exprNode exprNode_continue (/*@only@*/ lltok l, int qcontinue)
6828 {
6829   exprNode ret = exprNode_createLoc (ctype_unknown, fileloc_copy (lltok_getLoc (l)));
6830
6831   ret->kind = XPR_CONTINUE;
6832   ret->edata = exprData_makeTok (l);
6833   ret->canBreak = TRUE;
6834   ret->mustBreak = TRUE;
6835
6836   if (qcontinue == QSAFEBREAK)
6837     {
6838       ; /* no checking */
6839     }
6840   else if (qcontinue == QINNERCONTINUE)
6841     {
6842       if (!context_inDeepLoop ())
6843         {
6844           voptgenerror 
6845             (FLG_LOOPLOOPCONTINUE,
6846              cstring_makeLiteral ("Continue statement marked with innercontinue "
6847                                   "is not inside a nested loop"),
6848              exprNode_loc (ret));
6849         }
6850     }
6851   else if (qcontinue == BADTOK)
6852     {
6853       if (context_inDeepLoop ())
6854         {
6855           voptgenerror 
6856             (FLG_LOOPLOOPCONTINUE,
6857              cstring_makeLiteral ("Continue statement in nested loop"),
6858              exprNode_loc (ret));
6859         }
6860     }
6861   else
6862     {
6863       llbuglit ("exprNode_continue: bad qcontinue");
6864     }
6865
6866   return ret;
6867 }
6868
6869 exprNode exprNode_break (/*@only@*/ lltok l, int bqual)
6870 {
6871   exprNode ret = exprNode_createLoc (ctype_unknown, fileloc_copy (lltok_getLoc (l)));
6872   clause breakClause = context_breakClause ();
6873   
6874   ret->kind = XPR_BREAK;
6875   ret->edata = exprData_makeTok (l);
6876   ret->canBreak = TRUE;
6877   ret->mustBreak = TRUE;
6878   
6879   if (breakClause == NOCLAUSE)
6880     {
6881       voptgenerror 
6882         (FLG_SYNTAX,
6883          cstring_makeLiteral ("Break not inside while, for or switch statement"),
6884          exprNode_loc (ret));
6885     }
6886   else
6887     {
6888       if (bqual != BADTOK)
6889         {
6890           switch (bqual)
6891             {
6892             case QSAFEBREAK:
6893               break;
6894             case QINNERBREAK:
6895               if (breakClause == SWITCHCLAUSE)
6896                 {
6897                   if (!context_inDeepSwitch ())
6898                     {
6899                       voptgenerror (FLG_SYNTAX,
6900                                     cstring_makeLiteral 
6901                                     ("Break preceded by innerbreak is not in a deep switch"),
6902                                     exprNode_loc (ret));
6903                     }
6904                 }
6905               else 
6906                 {
6907                   if (!context_inDeepLoop ())
6908                     {
6909                       voptgenerror (FLG_SYNTAX,
6910                                     cstring_makeLiteral 
6911                                     ("Break preceded by innerbreak is not in a deep loop"),
6912                                     exprNode_loc (ret));
6913                     }
6914                 }
6915               break;
6916             case QLOOPBREAK:
6917               if (breakClause == SWITCHCLAUSE)
6918                 {
6919                   voptgenerror (FLG_SYNTAX,
6920                                 cstring_makeLiteral 
6921                                 ("Break preceded by loopbreak is breaking a switch"),
6922                                 exprNode_loc (ret));
6923                 }
6924               break;
6925             case QSWITCHBREAK:
6926               if (breakClause != SWITCHCLAUSE)
6927                 {
6928                   voptgenerror 
6929                     (FLG_SYNTAX,
6930                      message ("Break preceded by switchbreak is breaking %s",
6931                               cstring_makeLiteralTemp 
6932                               ((breakClause == WHILECLAUSE
6933                                 || breakClause == DOWHILECLAUSE) ? "a while loop"
6934                                : (breakClause == FORCLAUSE) ? "a for loop"
6935                                : (breakClause == ITERCLAUSE) ? "an iterator"
6936                                : "<error loop>")),
6937                      exprNode_loc (ret));
6938                 }
6939               break;
6940             BADDEFAULT;
6941             }
6942         }
6943       else
6944         {
6945           if (breakClause == SWITCHCLAUSE)
6946             {
6947               clause nextBreakClause = context_nextBreakClause ();
6948
6949               switch (nextBreakClause)
6950                 {
6951                 case NOCLAUSE: break;
6952                 case WHILECLAUSE:
6953                 case DOWHILECLAUSE:
6954                 case FORCLAUSE:
6955                 case ITERCLAUSE:
6956                   voptgenerror 
6957                     (FLG_LOOPSWITCHBREAK,
6958                      cstring_makeLiteral ("Break statement in switch inside loop"),
6959                      exprNode_loc (ret));
6960                   break;
6961                 case SWITCHCLAUSE:
6962                   voptgenerror 
6963                     (FLG_SWITCHSWITCHBREAK,
6964                      cstring_makeLiteral ("Break statement in switch inside switch"),
6965                      exprNode_loc (ret));
6966                   break;
6967                 BADDEFAULT;
6968                 }
6969             }
6970           else
6971             {
6972               if (context_inDeepLoop ())
6973                 {
6974                   voptgenerror 
6975                     (FLG_LOOPLOOPBREAK,
6976                      cstring_makeLiteral ("Break statement in nested loop"),
6977                      exprNode_loc (ret));
6978                 }
6979               else 
6980                 {
6981                   if (context_inDeepLoopSwitch ())
6982                     {
6983                       voptgenerror 
6984                         (FLG_SWITCHLOOPBREAK,
6985                          cstring_makeLiteral ("Break statement in loop inside switch"),
6986                          exprNode_loc (ret));
6987                     }
6988                 }
6989             }
6990         }
6991     }
6992
6993   return ret;
6994 }
6995
6996 exprNode exprNode_nullReturn (/*@only@*/ lltok t)
6997 {
6998   fileloc loc = lltok_getLoc (t);
6999   exprNode ret = exprNode_createLoc (ctype_unknown, fileloc_copy (loc));
7000   
7001   context_returnFunction ();
7002   exprChecks_checkNullReturn (loc);
7003
7004   ret->kind = XPR_NULLRETURN;
7005   ret->edata = exprData_makeTok (t);
7006   ret->exitCode = XK_MUSTRETURN;
7007   return ret;
7008 }
7009
7010 exprNode exprNode_return (/*@only@*/ exprNode e)
7011 {
7012   exprNode ret;
7013   
7014   if (exprNode_isError (e))
7015     {
7016       ret = exprNode_createUnknown ();
7017     }
7018   else
7019     {
7020       ret = exprNode_createLoc (ctype_unknown, fileloc_copy (e->loc));
7021
7022       exprNode_checkUse (ret, e->sref, e->loc);
7023       exprNode_checkReturn (e);
7024     }
7025
7026   context_returnFunction ();
7027   ret->kind = XPR_RETURN;
7028   ret->edata = exprData_makeSingle (e);
7029   ret->exitCode = XK_MUSTRETURN;
7030
7031   return (ret);
7032 }
7033
7034 exprNode exprNode_comma (/*@only@*/ exprNode e1, /*@only@*/ exprNode e2)
7035 {
7036   exprNode ret;
7037
7038   if (exprNode_isError (e1)) 
7039     {
7040       if (exprNode_isError (e2))
7041         {
7042           ret = exprNode_createLoc (ctype_unknown, g_currentloc);
7043         }
7044       else
7045         {
7046           ret = exprNode_createPartialCopy (e2);
7047           exprNode_checkUse (ret, e2->sref, e2->loc);
7048           ret->sref = e2->sref;
7049         }
7050     }
7051   else
7052     {
7053       ret = exprNode_createPartialCopy (e1);
7054
7055       exprNode_checkUse (ret, e1->sref, e1->loc);
7056
7057       if (!exprNode_isError (e2))
7058         {
7059           exprNode_mergeUSs (ret, e2);
7060           exprNode_checkUse (ret, e2->sref, e2->loc);
7061           ret->sref = e2->sref;
7062         }
7063     }
7064
7065   ret->kind = XPR_COMMA;
7066   ret->edata = exprData_makePair (e1, e2);
7067   
7068   if (exprNode_isDefined (e1))
7069     {
7070       if (exprNode_isDefined (e2))
7071         {
7072           ret->typ = e2->typ; 
7073
7074           if (exprNode_mustEscape (e1) || e1->mustBreak)
7075             {
7076               voptgenerror 
7077                 (FLG_UNREACHABLE,
7078                  message ("Second clause of comma expression is unreachable: %s",
7079                           exprNode_unparse (e2)), 
7080                  exprNode_loc (e2));
7081             }
7082           
7083           ret->exitCode = exitkind_combine (e1->exitCode, e2->exitCode);
7084           ret->mustBreak = e1->mustBreak || e2->mustBreak;
7085           ret->canBreak = e1->canBreak || e2->canBreak;
7086         }
7087       else
7088         {
7089           if (exprNode_mustEscape (e1) || e1->mustBreak)
7090             {
7091               voptgenerror 
7092                 (FLG_UNREACHABLE,
7093                  message ("Second clause of comma expression is unreachable: %s",
7094                           exprNode_unparse (e2)), 
7095                  exprNode_loc (e2));
7096             }
7097           
7098           ret->exitCode = e1->exitCode;
7099           ret->canBreak = e1->canBreak;
7100         }
7101     }
7102   else
7103     {
7104       if (exprNode_isDefined (e2))
7105         {
7106           ret->exitCode = e2->exitCode;
7107           ret->mustBreak = e2->mustBreak;
7108           ret->canBreak = e2->canBreak;
7109         }
7110     }
7111
7112   return (ret);
7113 }
7114
7115 static bool exprNode_checkOneInit (/*@notnull@*/ exprNode el, exprNode val)
7116 {
7117   ctype t1 = exprNode_getType (el);
7118   ctype t2 = exprNode_getType (val);
7119   bool hasError = FALSE;
7120   
7121   if (ctype_isUnknown (t1))
7122     {
7123       voptgenerror (FLG_IMPTYPE,
7124                     message ("Variable has unknown (implicitly int) type: %s",
7125                              exprNode_unparse (el)),
7126                     el->loc);
7127       
7128       t1 = ctype_int;
7129       el->typ = ctype_int;
7130     }
7131
7132   if (exprNode_isDefined (val) && val->kind == XPR_INITBLOCK)
7133     {
7134       exprNodeList vals = exprData_getArgs (val->edata);
7135
7136       if (ctype_isRealAP (t1))
7137         {
7138           int i = 0;
7139           int nerrors = 0;
7140
7141           exprNodeList_elements (vals, oneval)
7142             {
7143               cstring istring = message ("%d", i);
7144               exprNode newel =
7145                 exprNode_arrayFetch 
7146                   (exprNode_fakeCopy (el),
7147                    exprNode_numLiteral (ctype_int, istring,
7148                                         fileloc_copy (el->loc), i));
7149               
7150               if (exprNode_isDefined (newel))
7151                 {
7152                   if (exprNodeList_size (vals) == 1
7153                       && ctype_isString (exprNode_getType (oneval))
7154                       && ctype_isChar (exprNode_getType (newel)))
7155                     {
7156                       exprNode_freeIniter (newel);
7157                     }
7158                   else
7159                     {
7160                       if (exprNode_checkOneInit (newel, oneval))
7161                         {
7162                           hasError = TRUE;
7163                           nerrors++;
7164                           
7165                           if (nerrors > 3 && exprNodeList_size (vals) > 6)
7166                             {
7167                               llgenmsg 
7168                                 (message ("Additional initialization errors "
7169                                           "for %s not reported",
7170                                           exprNode_unparse (el)),
7171                                  exprNode_loc (el));
7172                               exprNode_freeIniter (newel);
7173                               break;
7174                             }
7175                           else
7176                             {
7177                               exprNode_freeIniter (newel);
7178                             }
7179                         }
7180                       else
7181                         {
7182                           exprNode_freeIniter (newel);
7183                         }
7184                     }
7185                 }
7186
7187               cstring_free (istring);
7188               i++;
7189               /*@-branchstate@*/ 
7190             } end_exprNodeList_elements;
7191           /*@=branchstate@*/
7192         }
7193       else if (ctype_isStruct (ctype_realType (t1)))
7194         {
7195           uentryList fields = ctype_getFields (t1);
7196           int i = 0;
7197
7198           if (uentryList_size (fields) != exprNodeList_size (vals))
7199             {
7200               if (uentryList_size (fields) > exprNodeList_size (vals))
7201                 {
7202                   hasError = optgenerror 
7203                     (FLG_FULLINITBLOCK,
7204                      message ("Initializer block for "
7205                               "%s has %d field%p, but %s has %d field%p: %q",
7206                               exprNode_unparse (el),
7207                               exprNodeList_size (vals),
7208                               ctype_unparse (t1),
7209                               uentryList_size (fields),
7210                               exprNodeList_unparse (vals)),
7211                      val->loc);   
7212                 }
7213               else
7214                 {
7215                   hasError = optgenerror 
7216                     (FLG_TYPE,
7217                      message ("Initializer block for "
7218                               "%s has %d field%p, but %s has %d field%p: %q",
7219                               exprNode_unparse (el),
7220                               exprNodeList_size (vals),
7221                               ctype_unparse (t1),
7222                               uentryList_size (fields),
7223                               exprNodeList_unparse (vals)),
7224                      val->loc);   
7225                 }
7226             }
7227           else
7228             {
7229               exprNodeList_elements (vals, oneval)
7230                 {
7231                   uentry thisfield = uentryList_getN (fields, i);
7232                   exprNode newel =
7233                     exprNode_fieldAccess (exprNode_fakeCopy (el),
7234                                           uentry_getName (thisfield));
7235
7236                   if (exprNode_isDefined (newel))
7237                     {
7238                       if (exprNode_checkOneInit (newel, oneval))
7239                         {
7240                           hasError = TRUE;
7241                         }
7242
7243                       exprNode_freeIniter (newel);
7244                     }
7245
7246                   i++;
7247                 } end_exprNodeList_elements;
7248             }
7249         }
7250       else
7251         {
7252           hasError = optgenerror 
7253             (FLG_TYPE,
7254              message ("Initializer block used for "
7255                       "%s where %t is expected: %s",
7256                       exprNode_unparse (el), t1, exprNode_unparse (val)),
7257              val->loc);   
7258         }
7259     }
7260   else
7261     {
7262       if (exprNode_isDefined (val))
7263         {
7264           doAssign (el, val, TRUE);
7265           
7266           if (!exprNode_matchType (t1, val))
7267             {
7268               hasError = gentypeerror 
7269                 (t1, val, t2, el,
7270                  message ("Initial value of %s is type %t, "
7271                           "expects %t: %s",
7272                           exprNode_unparse (el),
7273                           t2, t1, exprNode_unparse (val)),
7274                  val->loc);
7275             }
7276         }
7277     }
7278
7279   return hasError;
7280 }
7281
7282 exprNode exprNode_makeInitialization (/*@only@*/ idDecl t,
7283                                       /*@only@*/ exprNode e)
7284 {
7285   uentry ue = usymtab_lookup (idDecl_observeId (t));
7286   bool isUsed = uentry_isUsed (ue);
7287   exprNode ret = exprNode_fromIdentifierAux (ue);
7288   ctype ct = ctype_realishType (ret->typ);
7289   fileloc loc;
7290   
7291   if (ctype_isUnknown (ct)) 
7292     {
7293       voptgenerror (FLG_IMPTYPE,
7294                     message ("Variable has unknown (implicitly int) type: %s",
7295                              idDecl_getName (t)),
7296                     exprNode_isDefined (e) ? exprNode_loc (e) : g_currentloc);
7297       
7298       ct = ctype_int;
7299     }
7300
7301   if (exprNode_isError (e)) 
7302     {
7303       e = exprNode_createUnknown ();
7304       loc = g_currentloc;
7305
7306       /* error: assume initializer is defined */
7307       sRef_setDefined (ret->sref, loc);
7308     }
7309   else
7310     {
7311       loc = exprNode_loc (e);
7312       
7313       /*
7314       ** evs - 9 Apr 1995
7315       **
7316       ** was addSafeUse --- what's the problem?
7317       **
7318       **   int x = 3, y = x ?
7319       */
7320
7321       exprNode_checkUse (ret, e->sref, e->loc);
7322       
7323       if (ctype_isUnknown (e->typ) && uentry_isValid (ue))
7324         {
7325           exprNode lhs = exprNode_createId (ue);
7326
7327           /*
7328           ** static storage should be undefined before initializing
7329           */
7330
7331           if (uentry_isStatic (ue))
7332             {
7333               sRef_setDefState (lhs->sref, SS_PARTIAL, fileloc_undefined);
7334             }
7335
7336           (void) exprNode_checkOneInit (lhs, e);
7337
7338           if (uentry_isStatic (ue))
7339             {
7340               sRef_setDefState (lhs->sref, SS_DEFINED, fileloc_undefined);
7341             }
7342
7343           exprNode_free (lhs);
7344         }
7345       else
7346         {
7347           if (!exprNode_matchType (ct, e))
7348             {
7349               if (exprNode_isZero (e) && ctype_isArrayPtr (ct)) 
7350                 {
7351                   ;
7352                 }
7353               else
7354                 {
7355                   (void) gentypeerror 
7356                     (exprNode_getType (e), e, exprNode_getType (ret), ret,
7357                      message 
7358                      ("Variable %s initialized to type %t, expects %t: %s",
7359                       exprNode_unparse (ret), exprNode_getType (e), 
7360                       exprNode_getType (ret),
7361                       exprNode_unparse (e)),
7362                      e->loc);
7363                 }
7364             }
7365         }
7366       
7367       if (uentry_isStatic (ue))
7368         {
7369           sRef_setDefState (ret->sref, SS_PARTIAL, fileloc_undefined);
7370         }
7371
7372       doAssign (ret, e, TRUE);
7373
7374       if (uentry_isStatic (ue))
7375         {
7376           sRef_setDefState (ret->sref, SS_DEFINED, fileloc_undefined);
7377         }
7378     }
7379
7380   if (context_inIterDef ())
7381     {
7382       /* should check if it is yield */
7383       uentry_setUsed (ue, loc);
7384     }
7385   else
7386     {
7387       if (!isUsed) /* could be @unused@-qualified variable */
7388         {
7389           uentry_setNotUsed (ue);  
7390         }
7391     }
7392
7393   ret->exitCode = XK_NEVERESCAPE;
7394   ret->mustBreak = FALSE;
7395
7396   /*
7397   ** Must be before new kind is assigned!
7398   */
7399
7400   exprData_free (ret->edata, ret->kind); 
7401
7402   ret->kind = XPR_INIT;
7403   ret->edata = exprData_makeInit (t, e);
7404   exprNode_mergeUSs (ret, e);
7405   return ret;
7406 }
7407   
7408 exprNode exprNode_iter (/*@observer@*/ uentry name,
7409                         /*@only@*/ exprNodeList alist, 
7410                         /*@only@*/ exprNode body,
7411                         /*@observer@*/ uentry end)
7412 {
7413   exprNode ret;
7414   cstring iname;
7415
7416   llassert (uentry_isValid (name));
7417
7418   uentry_setUsed (name, exprNode_loc (body));
7419
7420   ret = exprNode_createPartialCopy (body);
7421   iname = uentry_getName (name);
7422
7423   if (uentry_isInvalid (end))
7424     {
7425       llerror (FLG_ITER,
7426                message ("Iter %s not balanced with end_%s", iname, iname));
7427     }
7428   else
7429     {
7430       cstring ename = uentry_getName (end);
7431
7432       if (!cstring_equalPrefix (ename, "end_"))
7433         {
7434           llerror (FLG_ITER, message ("Iter %s not balanced with end_%s: %s", 
7435                                       iname, iname, ename));
7436         }
7437       else
7438         {
7439           if (!cstring_equal (iname, cstring_suffix (ename, 4)))
7440             {
7441               llerror (FLG_ITER, 
7442                        message ("Iter %s not balanced with end_%s: %s", 
7443                                 iname, iname, ename));
7444             }
7445         }
7446
7447       cstring_free (ename);
7448     }
7449
7450   context_exitIterClause (body);
7451   
7452   ret->kind = XPR_ITER;
7453   ret->edata = exprData_makeIter (name, alist, body, end);
7454
7455   if (uentry_isIter (name))
7456     {
7457       (void) checkArgsReal (name, body, 
7458                             uentry_getParams (name), alist, TRUE, ret);
7459     }
7460
7461   cstring_free (iname);
7462
7463   return ret;
7464 }
7465
7466 exprNode
7467 exprNode_iterNewId (/*@only@*/ cstring s)
7468 {
7469   exprNode e = exprNode_new ();
7470   uentry ue = uentryList_getN (uentry_getParams (getCurrentIter ()), iterParamNo ());
7471
7472   llassert (processingIterVars ());
7473
7474   e->loc = context_getSaveLocation ();
7475
7476   if (fileloc_isUndefined (e->loc))
7477     {
7478       fileloc_free (e->loc);
7479       e->loc = fileloc_copy (g_currentloc);
7480     }
7481
7482   e->uses = sRefSet_new ();
7483   e->sets = sRefSet_new ();
7484   e->msets = sRefSet_new ();
7485   e->kind = XPR_VAR;
7486   e->val = multiVal_unknown ();
7487   e->guards = guardSet_new ();
7488   e->sref = defref;
7489   e->isJumpPoint = FALSE;
7490   e->exitCode = XK_NEVERESCAPE;
7491
7492   /*> missing fields, detected by lclint <*/
7493   e->canBreak = FALSE;
7494   e->mustBreak = FALSE;
7495   e->etext = cstring_undefined;
7496
7497   if (uentry_isYield (ue))
7498     {
7499       uentry uue = uentry_makeVariable (s, uentry_getType (ue), 
7500                                         fileloc_copy (e->loc), 
7501                                         FALSE);
7502       sRef sr;
7503
7504       uue = usymtab_supEntrySrefReturn (uue);
7505
7506       sr = uentry_getSref (uue);
7507       sRef_mergeStateQuiet (sr, uentry_getSref (ue));
7508       sr = uentry_getSref (uue);
7509       sRef_setDefined (sr, e->loc);
7510
7511       e->typ = uentry_getType (uue);      
7512       e->sref = sr;
7513       e->edata = exprData_makeId (uue);
7514       uentry_setUsed (uue, g_currentloc);
7515     }
7516   else
7517     {
7518       uentry uue;
7519
7520       sRef_setGlobalScope ();
7521       uue = uentry_makeVariableLoc (s, ctype_unknown);
7522
7523       e->typ = ctype_unknown;
7524       e->edata = exprData_makeId (uue);
7525
7526       uentry_setUsed (uue, e->loc);
7527       uentry_setHasNameError (uue); 
7528
7529       if (context_getFlag (FLG_REPEATUNRECOG))
7530         {
7531           uentry_markOwned (uue);
7532         }
7533       else
7534         {
7535           usymtab_supGlobalEntry (uue);      
7536         }
7537
7538       sRef_clearGlobalScope ();
7539
7540       voptgenerror (FLG_UNRECOG, message ("Unrecognized identifier: %s", s),
7541                     e->loc);
7542     }
7543
7544
7545   cstring_free (s);
7546   return (e);
7547 }
7548
7549 exprNode
7550 exprNode_iterExpr (/*@returned@*/ exprNode e)
7551 {
7552   if (!processingIterVars ())
7553     {
7554       llcontbuglit ("checkIterParam: not in iter");
7555       return e;
7556     }
7557   
7558   if (uentry_isYield (uentryList_getN (uentry_getParams (getCurrentIter ()), 
7559                                        iterParamNo ())))
7560     {
7561       if (exprNode_isDefined (e))
7562         {
7563           if (fileloc_isDefined (e->loc))
7564             {
7565               voptgenerror
7566                 (FLG_ITER,
7567                  message ("Yield parameter is not simple identifier: %s", 
7568                           exprNode_unparse (e)),
7569                  e->loc);
7570             }
7571           else
7572             {
7573               voptgenerror
7574                 (FLG_ITER,
7575                  message ("Yield parameter is not simple identifier: %s",
7576                           exprNode_unparse (e)),
7577                  g_currentloc);
7578               
7579             }
7580         }
7581     }
7582   return e;
7583 }
7584
7585 exprNode
7586 exprNode_iterId (/*@observer@*/ uentry c)
7587 {
7588   uentry ue;
7589
7590   llassert (processingIterVars ());
7591
7592   ue = uentryList_getN (uentry_getParams (getCurrentIter ()), 
7593                         iterParamNo ());
7594
7595   if (uentry_isYield (ue))
7596     {
7597       ctype ct = uentry_getType (ue);
7598       exprNode e = exprNode_createPlain (ct);
7599       cstring name = uentry_getName (c);
7600       uentry le = uentry_makeVariable (name, ct, fileloc_undefined, FALSE);
7601
7602       uentry_setUsed (ue, g_currentloc);
7603       uentry_setHasNameError (ue); 
7604       
7605       cstring_free (name);
7606       
7607       e->kind = XPR_VAR;
7608       e->edata = exprData_makeId (le);
7609       e->loc = context_getSaveLocation ();
7610       e->sref = uentry_getSref (le);
7611
7612       usymtab_supEntrySref (le);
7613
7614       if (!context_inHeader ())
7615         {
7616           if (optgenerror
7617               (FLG_ITER,
7618                message ("Yield parameter shadows local declaration: %q",
7619                         uentry_getName (c)),
7620                fileloc_isDefined (e->loc) ? e->loc : g_currentloc))
7621             {
7622               uentry_showWhereDeclared (c);
7623             }
7624         }
7625
7626       return e;
7627     }
7628
7629   return (exprNode_fromIdentifierAux (c));
7630 }
7631
7632 exprNode exprNode_iterStart (/*@observer@*/ uentry name, /*@only@*/ exprNodeList alist)
7633 {
7634   exprNode ret = exprNode_create (ctype_unknown);
7635
7636   ret->kind = XPR_ITERCALL;
7637   ret->edata = exprData_makeIterCall (name, alist);
7638   
7639   if (uentry_isIter (name))
7640     {
7641       uentryList params = uentry_getParams (name);
7642
7643       if (context_inIterDef () 
7644           && uentryList_size (params) == exprNodeList_size (alist))
7645         {
7646           int i = 0;
7647           
7648           exprNodeList_elements (alist, arg)
7649             {
7650               uentry parg = uentryList_getN (params, i);
7651
7652               if (uentry_isYield (parg))
7653                 {
7654                   uentry ue = exprNode_getUentry (arg);
7655
7656                   if (uentry_isValid (ue))
7657                     {
7658                       ;
7659                     }
7660                 }
7661
7662               i++;
7663             } end_exprNodeList_elements;
7664         }
7665
7666       (void) checkArgsReal (name, ret, params, alist, TRUE, ret);
7667       checkUnspecCall (ret, params, alist);
7668     }
7669
7670   return ret;
7671 }
7672
7673 /*@exposed@*/ sRef exprNode_getSref (exprNode e)
7674 {
7675   if (exprNode_isDefined (e))
7676     {
7677       /*@access sRef@*/
7678       if (e->sref == defref) /*@noaccess sRef@*/
7679         {
7680           /*@-mods@*/
7681           e->sref = sRef_makeUnknown (); 
7682           sRef_setAliasKind (e->sref, AK_ERROR, fileloc_undefined);
7683           /*@=mods@*/
7684           return e->sref;
7685         }
7686       else
7687         {
7688           return e->sref;
7689         }
7690     }
7691   else
7692     {
7693       return sRef_undefined;
7694     }
7695 }
7696
7697 /*@observer@*/ cstring
7698 exprNode_unparseFirst (exprNode e)
7699 {
7700   if (exprNode_isDefined (e))
7701     {
7702       cstring ret;
7703
7704       if (e->kind == XPR_STMTLIST
7705           || e->kind == XPR_COMMA || e->kind == XPR_COND)
7706         {
7707           exprNode first = exprData_getPairA (e->edata);
7708
7709           if (exprNode_isDefined (first))
7710             {
7711               return (exprNode_unparseFirst (exprData_getPairA (e->edata)));
7712             }
7713           else
7714             {
7715               return (cstring_makeLiteralTemp ("..."));
7716             }
7717         }
7718
7719       ret = cstring_elide (exprNode_unparse (e), 20);
7720       cstring_markOwned (ret);
7721       
7722       return (ret);
7723     }
7724   else
7725     {
7726       return cstring_makeLiteralTemp ("<error>");
7727     }
7728 }
7729
7730 /*@observer@*/ cstring
7731 exprNode_unparse (exprNode e)
7732 {
7733   if (exprNode_isError (e))
7734     {
7735       return cstring_makeLiteralTemp ("<error>");
7736     }
7737
7738   if (cstring_isDefined (e->etext))
7739     {
7740       return e->etext;
7741     }
7742   else
7743     {
7744       cstring ret = exprNode_doUnparse (e);
7745
7746       /*@-modifies@*/ /* benevolent */
7747       e->etext = ret; 
7748       /*@=modifies@*/
7749       return ret;
7750     }
7751 }
7752
7753 /*@observer@*/ fileloc
7754 exprNode_loc (exprNode e)
7755 {
7756   if (exprNode_isError (e))
7757     {
7758       return (g_currentloc);
7759     }
7760   else
7761     {
7762       return (e->loc);
7763     }
7764 }
7765
7766 /*
7767 ** executes exprNode e
7768 **    recursively rexecutes as though in original parse using
7769 **    information in e->edata
7770 */
7771
7772 static /*@only@*/ exprNodeList exprNodeList_effect (exprNodeList e)
7773 {
7774   exprNodeList ret = exprNodeList_new ();
7775
7776   exprNodeList_elements (e, current)
7777     {
7778       exprNodeList_addh (ret, exprNode_effect (current));
7779     } end_exprNodeList_elements;
7780
7781   return ret;
7782 }
7783
7784 static /*@only@*/ exprNode exprNode_effect (exprNode e) 
7785    /*@globals internalState@*/
7786 {
7787   bool innerEffect = inEffect;
7788   exprNode ret;
7789   exprData data;
7790
7791   inEffect = TRUE;
7792
7793   context_clearJustPopped ();
7794
7795   if (exprNode_isError (e))
7796     {
7797       ret = exprNode_undefined;
7798     }
7799   else
7800     {
7801       /*
7802       ** Turn off expose and dependent transfer checking.
7803       ** Need to pass exposed internal nodes,
7804       ** [ copying would be a waste! ]
7805       ** [ Actually, I think I wasted a lot more time than its worth ]
7806       ** [ trying to do this. ]
7807       */
7808
7809       /*@-exposetrans@*/
7810       /*@-observertrans@*/
7811       /*@-dependenttrans@*/
7812       
7813       data = e->edata;
7814       
7815       switch (e->kind)
7816         {
7817         case XPR_PARENS: 
7818           ret = exprNode_addParens (exprData_getUopTok (data), 
7819                                     exprNode_effect (exprData_getUopNode (data)));
7820           break;
7821         case XPR_ASSIGN:
7822           ret = exprNode_assign (exprNode_effect (exprData_getOpA (data)), 
7823                                  exprNode_effect (exprData_getOpB (data)), 
7824                                  exprData_getOpTok (data));
7825           break;
7826         case XPR_INITBLOCK:
7827           ret = exprNode_undefined;
7828           break;
7829         case XPR_CALL:
7830           ret = exprNode_functionCall (exprNode_effect (exprData_getFcn (data)),
7831                                        exprNodeList_effect (exprData_getArgs (data)));
7832           break;
7833         case XPR_EMPTY:
7834           ret = e;
7835           break;
7836
7837         case XPR_LABEL:
7838           ret = e;
7839           break;
7840
7841         case XPR_CONST:
7842         case XPR_VAR:
7843           {
7844             cstring id = exprData_getId (data);
7845             uentry ue = usymtab_lookupSafe (id);
7846
7847             ret = exprNode_fromIdentifierAux (ue);
7848             ret->loc = fileloc_update (ret->loc, e->loc);
7849             break;
7850           }
7851         case XPR_BODY:
7852           ret = e;
7853           break;
7854         case XPR_FETCH:
7855           ret = exprNode_arrayFetch (exprNode_effect (exprData_getPairA (data)), 
7856                                      exprNode_effect (exprData_getPairB (data)));
7857           break;
7858         case XPR_OP:
7859           ret = exprNode_op (exprNode_effect (exprData_getOpA (data)), 
7860                              exprNode_effect (exprData_getOpB (data)), 
7861                              exprData_getOpTok (data));
7862           break;
7863           
7864         case XPR_POSTOP:
7865           ret = exprNode_postOp (exprNode_effect (exprData_getUopNode (data)), 
7866                                  exprData_getUopTok (data));
7867           break;
7868         case XPR_PREOP:
7869           ret = exprNode_preOp (exprNode_effect (exprData_getUopNode (data)), 
7870                                 exprData_getUopTok (data));
7871           break;
7872
7873         case XPR_OFFSETOF:
7874         case XPR_SIZEOFT:
7875         case XPR_SIZEOF:
7876         case XPR_ALIGNOFT:
7877         case XPR_ALIGNOF:
7878           ret = e;
7879           break;
7880           
7881         case XPR_VAARG:
7882           ret = exprNode_vaArg (exprData_getCastTok (data),
7883                                 exprNode_effect (exprData_getCastNode (data)),
7884                                 exprData_getCastType (data));
7885           break;
7886           
7887         case XPR_CAST:
7888           ret = exprNode_cast (exprData_getCastTok (data), 
7889                                exprNode_effect (exprData_getCastNode (data)), 
7890                                exprData_getCastType (data));
7891           break;
7892         case XPR_ITERCALL:
7893           ret = exprNode_iterStart (exprData_getIterCallIter (data),
7894                                     exprNodeList_effect 
7895                                     (exprData_getIterCallArgs (data)));
7896           break;
7897           
7898         case XPR_ITER:
7899           ret = exprNode_iter (exprData_getIterSname (data),
7900                                exprNodeList_effect (exprData_getIterAlist (data)),
7901                                exprNode_effect (exprData_getIterBody (data)),
7902                                exprData_getIterEname (data));
7903           break;
7904           
7905         case XPR_FOR:
7906           ret = exprNode_for (exprNode_effect (exprData_getPairA (data)), 
7907                               exprNode_effect (exprData_getPairB (data)));
7908           break;
7909           
7910         case XPR_FORPRED:
7911           ret = exprNode_forPred (exprNode_effect (exprData_getTripleInit (data)),
7912                                   exprNode_effect (exprData_getTripleTest (data)),
7913                                   exprNode_effect (exprData_getTripleInc (data)));
7914           break;
7915           
7916         case XPR_TOK:
7917           ret = exprNode_createTok (exprData_getTok (data));
7918           break;
7919           
7920         case XPR_GOTO:
7921           ret = exprNode_goto (exprData_getLiteral (data));
7922           ret->loc = fileloc_update (ret->loc, e->loc);
7923           break;
7924           
7925         case XPR_CONTINUE:
7926           ret = exprNode_continue (exprData_getTok (data), QSAFEBREAK);
7927           break;
7928           
7929         case XPR_BREAK:
7930           ret = exprNode_break (exprData_getTok (data), QSAFEBREAK);
7931           break;
7932           
7933         case XPR_RETURN:
7934           ret = exprNode_return (exprNode_effect (exprData_getSingle (data)));
7935           break;
7936           
7937         case XPR_NULLRETURN:
7938           ret = exprNode_nullReturn (exprData_getTok (data));
7939           break;
7940           
7941         case XPR_COMMA:
7942           ret = exprNode_comma (exprNode_effect (exprData_getPairA (data)),
7943                                 exprNode_effect (exprData_getPairB (data)));
7944           break;
7945           
7946         case XPR_COND:
7947           ret = exprNode_cond (exprNode_effect (exprData_getTriplePred (data)),
7948                                exprNode_effect (exprData_getTripleTrue (data)),
7949                                exprNode_effect (exprData_getTripleFalse (data)));
7950           break;
7951         case XPR_IF:
7952           ret = exprNode_if (exprNode_effect (exprData_getPairA (data)),
7953                              exprNode_effect (exprData_getPairB (data)));
7954           break;
7955           
7956         case XPR_IFELSE:
7957           ret = exprNode_ifelse (exprNode_effect (exprData_getTriplePred (data)),
7958                                  exprNode_effect (exprData_getTripleTrue (data)),
7959                                  exprNode_effect (exprData_getTripleFalse (data)));
7960           break;
7961         case XPR_WHILEPRED:
7962           ret = exprNode_whilePred (exprData_getSingle (data));
7963           break;
7964           
7965         case XPR_WHILE:
7966           ret = exprNode_while (exprNode_effect (exprData_getPairA (data)),
7967                                 exprNode_effect (exprData_getPairB (data)));
7968           break;
7969           
7970         case XPR_DOWHILE:
7971           ret = exprNode_doWhile (exprNode_effect (exprData_getPairA (data)),
7972                                   exprNode_effect (exprData_getPairB (data)));
7973           break;
7974
7975         case XPR_BLOCK:
7976           ret = exprNode_makeBlock (exprNode_effect (exprData_getSingle (data)));
7977           break;          
7978
7979         case XPR_STMT:
7980           ret = exprNode_statement (exprNode_effect (exprData_getUopNode (data)),
7981                                     exprData_getUopTok (data));
7982           break;
7983           
7984         case XPR_STMTLIST:
7985           ret = exprNode_concat (exprNode_effect (exprData_getPairA (data)),
7986                                  exprNode_effect (exprData_getPairB (data)));
7987           break;
7988           
7989         case XPR_FTCASE:
7990         case XPR_CASE:
7991           ret = exprNode_caseMarker 
7992             (exprNode_effect (exprData_getSingle (data)),
7993              TRUE);
7994           break;
7995           
7996         case XPR_FTDEFAULT:
7997         case XPR_DEFAULT:
7998           ret = exprNode_createTok (exprData_getTok (data));
7999           break;
8000           
8001         case XPR_SWITCH:
8002           ret = exprNode_switch (exprNode_effect (exprData_getPairA (data)),
8003                                  exprNode_effect (exprData_getPairB (data)));
8004           break;
8005           
8006         case XPR_INIT:
8007           ret = exprNode_makeInitialization
8008             (exprData_getInitId (data),
8009              exprNode_effect (exprData_getInitNode (data)));
8010           break;
8011           
8012         case XPR_FACCESS:
8013           ret = exprNode_fieldAccess (exprNode_effect (exprData_getFieldNode (data)),
8014                                       cstring_copy (exprData_getFieldName (data)));
8015           break;
8016           
8017         case XPR_ARROW:
8018           ret = exprNode_arrowAccess (exprNode_effect (exprData_getFieldNode (data)),
8019                                       cstring_copy (exprData_getFieldName (data)));
8020           break;
8021           
8022         case XPR_STRINGLITERAL:
8023           ret = e;
8024           break;
8025           
8026         case XPR_NUMLIT:
8027           ret = e;
8028           break;
8029
8030         case XPR_NODE:
8031           ret = e;
8032           break;
8033           /*@-branchstate@*/ 
8034         } 
8035       /*@=branchstate@*/
8036       /*@=observertrans@*/
8037       /*@=exposetrans@*/
8038       /*@=dependenttrans@*/
8039     }
8040
8041   if (!innerEffect) 
8042     {
8043       inEffect = FALSE;
8044     }
8045
8046   return ret;
8047 }
8048
8049 static /*@observer@*/ cstring exprNode_rootVarName (exprNode e)
8050 {
8051   cstring ret;
8052   exprData data;
8053
8054   if (exprNode_isError (e))
8055     {
8056       return cstring_undefined;
8057     }
8058
8059   data = e->edata;
8060
8061   switch (e->kind)
8062     {
8063     case XPR_PARENS: 
8064       ret = exprNode_rootVarName (exprData_getUopNode (data));
8065       break;
8066     case XPR_ASSIGN:
8067       ret = exprNode_rootVarName (exprData_getOpA (data));
8068       break;
8069     case XPR_CONST:
8070     case XPR_VAR:
8071       ret = exprData_getId (data);
8072       break;
8073     case XPR_LABEL:
8074     case XPR_TOK:
8075     case XPR_ITERCALL:
8076     case XPR_EMPTY:
8077     case XPR_CALL:
8078     case XPR_INITBLOCK:
8079     case XPR_BODY:
8080     case XPR_FETCH:
8081     case XPR_OP:
8082     case XPR_POSTOP:
8083     case XPR_PREOP:
8084     case XPR_OFFSETOF:
8085     case XPR_ALIGNOFT:
8086     case XPR_ALIGNOF:
8087     case XPR_SIZEOFT:
8088     case XPR_SIZEOF:
8089     case XPR_VAARG:
8090     case XPR_CAST:
8091     case XPR_ITER:
8092     case XPR_FOR:
8093     case XPR_FORPRED:
8094     case XPR_BREAK:
8095     case XPR_RETURN:
8096     case XPR_NULLRETURN:
8097     case XPR_COMMA:
8098     case XPR_COND:
8099     case XPR_IF:
8100     case XPR_IFELSE:
8101     case XPR_WHILE:
8102     case XPR_WHILEPRED:
8103     case XPR_DOWHILE:
8104     case XPR_GOTO:
8105     case XPR_CONTINUE:
8106     case XPR_FTDEFAULT:
8107     case XPR_DEFAULT:
8108     case XPR_SWITCH:
8109     case XPR_FTCASE:
8110     case XPR_CASE:
8111     case XPR_BLOCK:
8112     case XPR_STMT:
8113     case XPR_STMTLIST:
8114     case XPR_INIT:
8115     case XPR_FACCESS:
8116     case XPR_ARROW:
8117     case XPR_NODE:
8118     case XPR_NUMLIT:
8119     case XPR_STRINGLITERAL:
8120       ret = cstring_undefined;
8121       break;
8122     }
8123
8124   return ret;
8125 }
8126
8127
8128 static /*@only@*/ cstring exprNode_doUnparse (exprNode e)
8129 {
8130   cstring ret;
8131   exprData data;
8132
8133   if (exprNode_isError (e))
8134     {
8135       static /*@only@*/ cstring error = cstring_undefined;
8136
8137       if (!cstring_isDefined (error))
8138         {
8139           error = cstring_makeLiteral ("<error>");
8140         }
8141       
8142       return error;
8143     }
8144
8145   data = e->edata;
8146
8147   switch (e->kind)
8148     {
8149     case XPR_PARENS: 
8150       ret = message ("(%s)", exprNode_unparse (exprData_getUopNode (e->edata)));
8151       break;
8152     case XPR_ASSIGN:
8153       ret = message ("%s %s %s",
8154                      exprNode_unparse (exprData_getOpA (data)), 
8155                      lltok_unparse (exprData_getOpTok (data)),
8156                      exprNode_unparse (exprData_getOpB (data)));
8157       break;
8158     case XPR_CALL:
8159       ret = message ("%s(%q)",
8160                      exprNode_unparse (exprData_getFcn (data)), 
8161                      exprNodeList_unparse (exprData_getArgs (data)));
8162       break;
8163     case XPR_INITBLOCK:
8164       ret = message ("{ %q }", exprNodeList_unparse (exprData_getArgs (data)));
8165       break;
8166     case XPR_EMPTY:
8167       ret = cstring_undefined;
8168       break;
8169     case XPR_LABEL:
8170       ret = message ("%s:", exprData_getId (data));
8171       break;
8172     case XPR_CONST:
8173     case XPR_VAR:
8174       ret = cstring_copy (exprData_getId (data));
8175       break;
8176     case XPR_FETCH:
8177       ret = message ("%s[%s]", exprNode_unparse (exprData_getPairA (data)),
8178                      exprNode_unparse (exprData_getPairB (data)));
8179       break;
8180     case XPR_BODY:
8181       ret = message ("<body>");
8182       break;
8183     case XPR_OP:
8184       ret = message ("%s %s %s",
8185                      exprNode_unparse (exprData_getOpA (data)), 
8186                      lltok_unparse (exprData_getOpTok (data)),
8187                      exprNode_unparse (exprData_getOpB (data))); 
8188       break;
8189       
8190     case XPR_PREOP: 
8191       ret = message ("%s%s",
8192                      lltok_unparse (exprData_getUopTok (data)),
8193                      exprNode_unparse (exprData_getUopNode (data))); 
8194       break;
8195
8196     case XPR_POSTOP:
8197       ret = message ("%s%s",
8198                      exprNode_unparse (exprData_getUopNode (data)),
8199                      lltok_unparse (exprData_getUopTok (data))); 
8200       break;
8201       
8202     case XPR_OFFSETOF:
8203       ret = message ("offsetof(%s,%q)", 
8204                      ctype_unparse (qtype_getType (exprData_getOffsetType (data))),
8205                      cstringList_unparseSep (exprData_getOffsetName (data), cstring_makeLiteralTemp (".")));
8206       break;
8207
8208     case XPR_SIZEOFT:
8209       ret = message ("sizeof(%s)", ctype_unparse (qtype_getType (exprData_getType (data))));
8210       break;
8211       
8212     case XPR_SIZEOF:
8213       ret = message ("sizeof(%s)", exprNode_unparse (exprData_getSingle (data)));
8214       break;
8215
8216     case XPR_ALIGNOFT:
8217       ret = message ("alignof(%s)", ctype_unparse (qtype_getType (exprData_getType (data))));
8218       break;
8219       
8220     case XPR_ALIGNOF:
8221       ret = message ("alignof(%s)", exprNode_unparse (exprData_getSingle (data)));
8222       break;
8223       
8224     case XPR_VAARG:
8225       ret = message ("va_arg(%s, %q)", 
8226                      exprNode_unparse (exprData_getCastNode (data)),
8227                      qtype_unparse (exprData_getCastType (data)));
8228       break;
8229       
8230     case XPR_ITERCALL:
8231       ret = message ("%q(%q)", 
8232                      uentry_getName (exprData_getIterCallIter (data)),
8233                      exprNodeList_unparse (exprData_getIterCallArgs (data)));
8234       break;
8235     case XPR_ITER:
8236       ret = message ("%q(%q) %s %q",
8237                      uentry_getName (exprData_getIterSname (data)),
8238                      exprNodeList_unparse (exprData_getIterAlist (data)),
8239                      exprNode_unparse (exprData_getIterBody (data)),
8240                      uentry_getName (exprData_getIterEname (data)));
8241       break;
8242     case XPR_CAST:
8243       ret = message ("(%q)%s", 
8244                      qtype_unparse (exprData_getCastType (data)),
8245                      exprNode_unparse (exprData_getCastNode (data)));
8246       break;
8247       
8248     case XPR_FOR:
8249       ret = message ("%s %s", 
8250                      exprNode_unparse (exprData_getPairA (data)), 
8251                      exprNode_unparse (exprData_getPairB (data)));
8252       break;
8253
8254     case XPR_FORPRED:
8255             ret = message ("for (%s; %s; %s)",
8256                      exprNode_unparse (exprData_getTripleInit (data)),
8257                      exprNode_unparse (exprData_getTripleTest (data)),
8258                      exprNode_unparse (exprData_getTripleInc (data)));
8259       break;
8260       
8261     case XPR_GOTO:
8262       ret = message ("goto %s", exprData_getLiteral (data));
8263       break;
8264
8265     case XPR_CONTINUE:
8266       ret = cstring_makeLiteral ("continue");
8267       break;
8268
8269     case XPR_BREAK:
8270       ret = cstring_makeLiteral ("break");
8271       break;
8272
8273     case XPR_RETURN:
8274       ret = message ("return %s", exprNode_unparse (exprData_getSingle (data)));
8275       break;
8276
8277     case XPR_NULLRETURN:
8278       ret = cstring_makeLiteral ("return");
8279       break;
8280
8281     case XPR_COMMA:
8282       ret = message ("%s, %s", 
8283                      exprNode_unparse (exprData_getPairA (data)),
8284                      exprNode_unparse (exprData_getPairB (data)));
8285       break;
8286       
8287     case XPR_COND:
8288       ret = message ("%s ? %s : %s",
8289                      exprNode_unparse (exprData_getTriplePred (data)),
8290                      exprNode_unparse (exprData_getTripleTrue (data)),
8291                      exprNode_unparse (exprData_getTripleFalse (data)));
8292       break;
8293     case XPR_IF:
8294       ret = message ("if (%s) %s", 
8295                      exprNode_unparse (exprData_getPairA (data)),
8296                      exprNode_unparse (exprData_getPairB (data)));
8297       break;
8298       
8299     case XPR_IFELSE:
8300       ret = message ("if (%s) %s else %s",
8301                      exprNode_unparse (exprData_getTriplePred (data)),
8302                      exprNode_unparse (exprData_getTripleTrue (data)),
8303                      exprNode_unparse (exprData_getTripleFalse (data)));
8304       break;
8305     case XPR_WHILE:
8306       ret = message ("while (%s) %s",
8307                      exprNode_unparse (exprData_getPairA (data)),
8308                      exprNode_unparse (exprData_getPairB (data)));
8309       break;
8310
8311     case XPR_WHILEPRED:
8312       ret = cstring_copy (exprNode_unparse (exprData_getSingle (data)));
8313       break;
8314
8315     case XPR_TOK:
8316       ret = cstring_copy (lltok_unparse (exprData_getTok (data)));
8317       break;
8318
8319     case XPR_DOWHILE:
8320       ret = message ("do { %s } while (%s)",
8321                      exprNode_unparse (exprData_getPairB (data)),
8322                      exprNode_unparse (exprData_getPairA (data)));
8323       break;
8324       
8325     case XPR_BLOCK:
8326       ret = message ("{ %s }", exprNode_unparseFirst (exprData_getSingle (data)));
8327       break;
8328
8329     case XPR_STMT:
8330       ret = cstring_copy (exprNode_unparse (exprData_getUopNode (data)));
8331       break;
8332
8333     case XPR_STMTLIST:
8334       ret = message ("%s; %s", 
8335                      exprNode_unparse (exprData_getPairA (data)),
8336                      exprNode_unparse (exprData_getPairB (data)));
8337       break;
8338       
8339     case XPR_FTDEFAULT:
8340     case XPR_DEFAULT:
8341       ret = cstring_makeLiteral ("default:");
8342       break;
8343
8344     case XPR_SWITCH:
8345       ret = message ("switch (%s) %s", 
8346                      exprNode_unparse (exprData_getPairA (data)),
8347                      exprNode_unparse (exprData_getPairB (data)));
8348       break;
8349
8350     case XPR_FTCASE:
8351     case XPR_CASE:
8352       ret = message ("case %s:", 
8353                      exprNode_unparse (exprData_getSingle (data)));
8354       break;
8355       
8356     case XPR_INIT:
8357       ret = message ("%s = %s",
8358                      idDecl_getName (exprData_getInitId (data)),
8359                      exprNode_unparse (exprData_getInitNode (data)));
8360       break;
8361       
8362     case XPR_FACCESS:
8363       ret = message ("%s.%s",
8364                      exprNode_unparse (exprData_getFieldNode (data)),
8365                      exprData_getFieldName (data));
8366       break;
8367       
8368     case XPR_ARROW:
8369             ret = message ("%s->%s",
8370                      exprNode_unparse (exprData_getFieldNode (data)),
8371                      exprData_getFieldName (data));
8372       break;
8373
8374     case XPR_STRINGLITERAL:
8375       ret = cstring_copy (exprData_getLiteral (data));
8376       break;
8377
8378     case XPR_NUMLIT:
8379       ret = cstring_copy (exprData_getLiteral (data));
8380       break;
8381
8382     case XPR_NODE:
8383       ret = cstring_makeLiteral ("<node>");
8384       break;
8385     }
8386
8387   return ret;
8388 }
8389
8390 bool 
8391 exprNode_isCharLit (exprNode e)
8392 {
8393   if (exprNode_isDefined (e))
8394     {
8395       return (multiVal_isChar (exprNode_getValue (e)));
8396     }
8397   else
8398     {
8399       return FALSE;
8400     }
8401 }
8402
8403 bool
8404 exprNode_isNumLit (exprNode e)
8405 {
8406   if (exprNode_isDefined (e))
8407     {
8408       return (multiVal_isInt (exprNode_getValue (e)));
8409     }
8410   else
8411     {
8412       return FALSE;
8413     }
8414 }
8415
8416 static bool
8417 exprNode_isFalseConstant (exprNode e)
8418 {
8419   if (exprNode_isDefined (e))
8420     {
8421       cstring s = exprNode_rootVarName (e);
8422
8423       if (cstring_equal (s, context_getFalseName ()))
8424         {
8425           return TRUE;
8426         }
8427     }
8428
8429   return FALSE;
8430 }
8431
8432 bool
8433 exprNode_matchLiteral (ctype expected, exprNode e)
8434 {
8435   if (exprNode_isDefined (e))
8436     {
8437       multiVal m = exprNode_getValue (e);
8438       
8439       if (multiVal_isDefined (m))
8440         {
8441           if (multiVal_isInt (m))
8442             {
8443               long int val = multiVal_forceInt (m);
8444               
8445               if (ctype_isDirectBool (ctype_realishType (expected)))
8446                 {
8447                   if (val == 0) 
8448                     {
8449                       return FALSE; /* really?! return TRUE; allow use of 0 for FALSE */
8450                     }
8451                   else 
8452                     {
8453                       return FALSE;
8454                     }
8455                 }
8456               
8457               if (ctype_isRealInt (expected))
8458                 {
8459                   /*
8460                   ** unsigned <- [ constant >= 0 is okay ]
8461                   */
8462                   
8463                   if (ctype_isUnsigned (expected))
8464                     {
8465                       if (val < 0)
8466                         {
8467                           return FALSE;
8468                         }
8469                     }
8470                   
8471                   /*
8472                   ** No checks on sizes of integers...maybe add
8473                   ** these later.
8474                   */
8475
8476                   DPRINTF (("Here: %s => %s", exprNode_unparse (e), ctype_unparse (expected)));
8477                   DPRINTF (("Type: %s / %s", ctype_unparse (exprNode_getType (e)),
8478                             bool_unparse (ctype_isInt (exprNode_getType (e)))));
8479
8480                   if (context_getFlag (FLG_NUMLITERAL) 
8481                       && (ctype_isRegularInt (exprNode_getType (e)) || val == 0)) {
8482                     return TRUE;
8483                   } else {
8484                     if (val == 0) {
8485                       return TRUE;
8486                     } else {
8487                       return FALSE; /* evs 2000-05-17: previously, always returned TRUE */
8488                     }
8489                   }
8490                 }
8491               else if (ctype_isChar (expected))
8492                 {
8493                   return FALSE;
8494                 }
8495               else if (ctype_isArrayPtr (expected))
8496                 {
8497                   return (val == 0);
8498                 }
8499               else if (ctype_isAnyFloat (expected))
8500                 {
8501                   return (context_getFlag (FLG_NUMLITERAL));
8502                 }
8503               else
8504                 {
8505                   return FALSE;
8506                 }
8507             }
8508           else if (multiVal_isDouble (m))
8509             {
8510               if (ctype_isAnyFloat (expected))
8511                 {
8512                   return TRUE;
8513                 }
8514             }
8515           else if (multiVal_isChar (m))
8516             {
8517               char val = multiVal_forceChar (m);          
8518               
8519               if (ctype_isChar (expected))
8520                 {
8521                   if (ctype_isUnsigned (expected) && ((int)val) < 0)
8522                     {
8523                       return FALSE;
8524                     }
8525                   else
8526                     {
8527                       return TRUE;
8528                     }
8529                 }
8530             }
8531           else
8532             {
8533               return FALSE;
8534             }
8535         }
8536     }
8537   
8538   return FALSE;
8539 }
8540
8541 bool
8542 exprNode_matchType (ctype expected, exprNode e)
8543 {
8544   ctype actual;
8545   
8546   if (!exprNode_isDefined (e)) return TRUE;
8547
8548   actual = ctype_realishType (exprNode_getType (e));
8549
8550   if (ctype_match (ctype_realishType (expected), actual))
8551     {
8552       return TRUE;
8553     }
8554
8555   llassert (!exprNode_isError (e));
8556   return (exprNode_matchLiteral (expected, e));
8557 }
8558
8559 static bool
8560 exprNode_matchTypes (exprNode e1, exprNode e2)
8561 {
8562   ctype t1;
8563   ctype t2;
8564  
8565   if (!exprNode_isDefined (e1)) return TRUE;
8566   if (!exprNode_isDefined (e2)) return TRUE;
8567
8568   /*
8569   ** realish type --- keep bools, bools 
8570   */ 
8571
8572   t1 = ctype_realishType (exprNode_getType (e1));
8573   t2 = ctype_realishType (exprNode_getType (e2));
8574
8575   if (ctype_match (t1, t2)) 
8576     {
8577       return TRUE;
8578     }
8579
8580   return (exprNode_matchLiteral (t1, e2) || exprNode_matchLiteral (t2, e1));
8581 }
8582
8583 /*
8584 ** pass e as ct
8585 */
8586
8587 static bool
8588   exprNode_matchArgType (ctype ct, exprNode e)
8589 {
8590   ctype et;
8591
8592   if (!exprNode_isDefined (e))
8593     {
8594       return TRUE;
8595     }
8596
8597   et = ctype_realType (exprNode_getType (e));
8598
8599   if (ctype_matchArg (ct, et)) return TRUE;
8600   
8601   llassert (!exprNode_isError (e));
8602   return (exprNode_matchLiteral (ct, e));
8603 }
8604
8605 static /*@only@*/ exprNodeSList
8606   exprNode_flatten (/*@dependent@*/ exprNode e) /*@*/
8607 {
8608   if (exprNode_isDefined (e))
8609     {
8610       if (e->kind == XPR_STMTLIST)
8611         {
8612           return (exprNodeSList_append
8613                   (exprNode_flatten (exprData_getPairA (e->edata)),
8614                    exprNode_flatten (exprData_getPairB (e->edata))));
8615         }
8616       else if (e->kind == XPR_BLOCK)
8617         {
8618           return (exprNode_flatten (exprData_getSingle (e->edata)));
8619         }
8620       else
8621         {
8622           return (exprNodeSList_singleton (e));
8623         }
8624     }
8625
8626   return exprNodeSList_new ();
8627 }
8628
8629 static /*@exposed@*/ exprNode
8630 exprNode_lastStatement (/*@returned@*/ exprNode e)
8631 {
8632   if (exprNode_isDefined (e))
8633     {
8634       if (e->kind == XPR_STMTLIST)
8635         {
8636           exprNode b = exprData_getPairB (e->edata);
8637
8638           if (exprNode_isDefined (b))
8639             {
8640               return exprNode_lastStatement (b);
8641             }
8642           else
8643             {
8644               return exprNode_lastStatement (exprData_getPairA (e->edata));
8645             }
8646         }
8647       else if (e->kind == XPR_BLOCK)
8648         {
8649           return (exprNode_lastStatement (exprData_getSingle (e->edata)));
8650         }
8651       else
8652         {
8653           return (e);
8654         }
8655     }
8656
8657   return exprNode_undefined;
8658 }
8659
8660 static /*@exposed@*/ exprNode
8661 exprNode_firstStatement (/*@returned@*/ exprNode e)
8662 {
8663   if (exprNode_isDefined (e))
8664     {
8665       if (e->kind == XPR_STMTLIST)
8666         {
8667           exprNode b = exprData_getPairA (e->edata);
8668
8669           if (exprNode_isDefined (b))
8670             {
8671               return exprNode_firstStatement (b);
8672             }
8673           else
8674             {
8675               return exprNode_firstStatement (exprData_getPairB (e->edata));
8676             }
8677         }
8678       else if (e->kind == XPR_BLOCK)
8679         {
8680           return (exprNode_firstStatement (exprData_getSingle (e->edata)));
8681         }
8682       else
8683         {
8684           return (e);
8685         }
8686     }
8687
8688   return exprNode_undefined;
8689 }
8690   
8691 static void
8692 exprNode_mergeUSs (exprNode res, exprNode other)
8693 {
8694   if (exprNode_isDefined (res) && exprNode_isDefined (other))
8695     {
8696       res->msets = sRefSet_union (res->msets, other->msets);
8697       res->sets = sRefSet_union (res->sets, other->sets);
8698       res->uses = sRefSet_union (res->uses, other->uses);
8699     }
8700 }
8701
8702 static void
8703 exprNode_mergeCondUSs (exprNode res, exprNode other1, exprNode other2)
8704 {
8705   if (exprNode_isDefined (res))
8706     {
8707       if (exprNode_isDefined (other1))
8708         {
8709           res->sets = sRefSet_union (res->sets, other1->sets);
8710           res->msets = sRefSet_union (res->msets, other1->msets);
8711           res->uses = sRefSet_union (res->uses, other1->uses);
8712         }
8713       if (exprNode_isDefined (other2))
8714         {
8715           res->sets = sRefSet_union (res->sets, other2->sets);
8716           res->msets = sRefSet_union (res->msets, other2->msets);
8717           res->uses = sRefSet_union (res->uses, other2->uses);
8718         }
8719     }
8720 }
8721
8722 /*
8723 ** modifies e->uses
8724 **
8725 ** Reports errors is s is not defined.
8726 */
8727
8728 static void
8729 exprNode_addUse (exprNode e, sRef s)
8730 {
8731   if (exprNode_isDefined (e))
8732     {
8733       e->uses = sRefSet_insert (e->uses, s);
8734     }
8735 }
8736   
8737 void
8738 exprNode_checkUse (exprNode e, sRef s, fileloc loc)
8739 {
8740   if (sRef_isKnown (s) && !sRef_isConst (s))
8741     {
8742       /*
8743       ** need to check all outer types are useable
8744       */
8745
8746       DPRINTF (("Check use: %s / %s",
8747                 exprNode_unparse (e), sRef_unparse (s)));
8748
8749       exprNode_addUse (e, s);
8750      
8751       if (!context_inProtectVars ())
8752         {
8753           /*
8754           ** only report the deepest error
8755           */
8756           
8757           sRef errorRef = sRef_undefined;
8758           sRef lastRef  = sRef_undefined;
8759           bool deadRef = FALSE;
8760           bool unuseable = FALSE;
8761           bool errorMaybe = FALSE;
8762           
8763           while (sRef_isValid (s) && sRef_isKnown (s))
8764             {
8765               ynm readable = sRef_isReadable (s);
8766
8767               if (!(ynm_toBoolStrict (readable)))
8768                 {
8769                   if (ynm_isMaybe (readable))
8770                     {
8771                       lastRef = errorRef;
8772                       errorRef = s;
8773                       deadRef = sRef_isPossiblyDead (errorRef);
8774                       unuseable = sRef_isUnuseable (errorRef);
8775                       errorMaybe = TRUE;
8776                     }
8777                   else
8778                     {
8779                       lastRef = errorRef;
8780                       errorRef = s;
8781                       deadRef = sRef_isDead (errorRef);
8782                       unuseable = sRef_isUnuseable (errorRef);
8783                       errorMaybe = FALSE;
8784                     }
8785
8786                   if (!sRef_isPartial (s))
8787                     {
8788                       sRef_setDefined (s, fileloc_undefined);
8789                     }
8790                 }
8791
8792               s = sRef_getBaseSafe (s);
8793             } /* end while */
8794           
8795           if (sRef_isValid (errorRef)) 
8796             {
8797               if (sRef_isValid (lastRef) && sRef_isField (lastRef) 
8798                   && sRef_isPointer (errorRef))
8799                 {
8800                   errorRef = lastRef;
8801                 }
8802               
8803               if (deadRef)
8804                 {
8805                   if (sRef_isThroughArrayFetch (errorRef))
8806                     {
8807                       if (optgenerror 
8808                           (FLG_STRICTUSERELEASED,
8809                            message ("%q %q may be used after being released", 
8810                                     sRef_unparseKindNamePlain (errorRef),
8811                                     sRef_unparse (errorRef)),
8812                            loc))
8813                         {
8814                           sRef_showRefKilled (errorRef);
8815                           
8816                           if (sRef_isKept (errorRef))
8817                             {
8818                               sRef_clearAliasState (errorRef, loc);
8819                             }
8820                         }
8821                     }
8822                   else
8823                     {
8824                       DPRINTF (("HERE: %s", sRef_unparse (errorRef)));
8825
8826                       if (optgenerror
8827                           (FLG_USERELEASED,
8828                            message ("%q %q %qused after being released", 
8829                                     sRef_unparseKindNamePlain (errorRef),
8830                                     sRef_unparse (errorRef),
8831                                     cstring_makeLiteral (errorMaybe 
8832                                                          ? "may be " : "")),
8833                            loc))
8834                         {
8835                           sRef_showRefKilled (errorRef);
8836                           
8837                           if (sRef_isKept (errorRef))
8838                             {
8839                               sRef_clearAliasState (errorRef, loc);
8840                             }
8841                         }
8842                     }
8843                 }
8844               else if (unuseable)
8845                 {
8846                   if (optgenerror
8847                       (FLG_USEDEF,
8848                        message ("%q %q%qused in inconsistent state", 
8849                                 sRef_unparseKindName (errorRef),
8850                                 sRef_unparseOpt (errorRef),
8851                                 cstring_makeLiteral (errorMaybe ? "may be " : "")),
8852                        loc))
8853                     {
8854                       sRef_showStateInconsistent (errorRef);
8855                     }
8856                 }
8857               else
8858                 {
8859                   DPRINTF (("HERE: %s", sRef_unparse (errorRef)));
8860
8861                   voptgenerror 
8862                     (FLG_USEDEF,
8863                      message ("%q %q%qused before definition", 
8864                               sRef_unparseKindName (errorRef),
8865                               sRef_unparseOpt (errorRef),
8866                               cstring_makeLiteral (errorMaybe ? "may be " : "")),
8867                      loc);
8868                 }
8869               
8870               sRef_setDefined (errorRef, loc);
8871           
8872               if (sRef_isAddress (errorRef))
8873                 {
8874                   sRef_setDefined (sRef_getRootBase (errorRef), loc);
8875                 }
8876             } /* end is error */
8877         }
8878     }
8879
8880   setCodePoint ();
8881 }
8882
8883 static void
8884 checkSafeUse (exprNode e, sRef s)
8885 {
8886   if (exprNode_isDefined (e) && sRef_isKnown (s))
8887     {
8888       e->uses = sRefSet_insert (e->uses, s);
8889     }
8890 }
8891
8892 static void
8893 exprNode_checkSetAny (exprNode e, /*@dependent@*/ cstring name)
8894 {
8895   if (exprNode_isDefined (e))
8896     {
8897       e->sets = sRefSet_insert (e->sets, sRef_makeUnconstrained (name));
8898     }
8899 }
8900
8901 void
8902 exprNode_checkSet (exprNode e, sRef s)
8903 {
8904   sRef defines = sRef_undefined;
8905
8906   if (sRef_isValid (s) && !sRef_isNothing (s))
8907     {
8908       uentry ue = sRef_getBaseUentry (s);
8909
8910       if (uentry_isValid (ue))
8911         {
8912           uentry_setLset (ue);
8913         }
8914
8915       if (!ynm_toBoolStrict (sRef_isWriteable (s)))
8916         {
8917           voptgenerror (FLG_USEDEF,
8918                         message ("Attempt to set unuseable storage: %q", 
8919                                  sRef_unparse (s)),
8920                         exprNode_loc (e));
8921         }
8922      
8923       if (sRef_isMeaningful (s))
8924         {
8925           
8926           if (sRef_isDead (s))
8927             {
8928               sRef base = sRef_getBaseSafe (s);
8929
8930               if (sRef_isValid (base) 
8931                   && sRef_isDead (base))
8932                 {
8933                   sRef_setPartial (s, exprNode_loc (e));
8934                 }
8935               
8936               defines = s; /* okay - modifies for only param */
8937             }
8938           else if (sRef_isPartial (s))
8939             {
8940               sRef eref = exprNode_getSref (e);
8941
8942               if (!sRef_isPartial (eref))
8943                 {
8944                   /*
8945                   ** should do something different here???
8946                   */
8947                   
8948                   sRef_setDefinedComplete (eref, exprNode_loc (e));               
8949                 }
8950               else
8951                 {
8952                   sRef_setPartialDefinedComplete (eref, exprNode_loc (e));
8953                 }
8954
8955               if (sRef_isMeaningful (eref))
8956                 {
8957                   defines = eref;
8958                 }
8959               else
8960                 {                
8961                   defines = s;
8962                 }
8963             }
8964           else if (sRef_isAllocated (s))
8965             {
8966               sRef eref = exprNode_getSref (e);
8967
8968               
8969               if (!sRef_isAllocated (eref))
8970                 {
8971                   sRef_setDefinedComplete (eref, exprNode_loc (e));
8972                 }
8973               else
8974                 {
8975                   sRef base = sRef_getBaseSafe (eref);
8976                   
8977                   if (sRef_isValid (base))
8978                     {
8979                       sRef_setPdefined (base, exprNode_loc (e)); 
8980                     }
8981                 }
8982
8983               defines = s;
8984             }
8985           else 
8986             {
8987               sRef_setDefinedNCComplete (s, exprNode_loc (e));
8988               defines = s;
8989             }
8990
8991         }
8992       else /* not meaningful...but still need to insert it */
8993         {
8994           defines = s;
8995         }
8996     }
8997
8998   if (exprNode_isDefined (e) && sRef_isValid (defines))
8999     {
9000       e->sets = sRefSet_insert (e->sets, defines); 
9001     }
9002 }
9003
9004 void
9005 exprNode_checkMSet (exprNode e, sRef s)
9006 {
9007   if (sRef_isValid (s) && !sRef_isNothing (s))
9008     {
9009       uentry ue = sRef_getBaseUentry (s);
9010
9011       if (uentry_isValid (ue))
9012         {
9013           uentry_setLset (ue);
9014         }
9015
9016       if (!ynm_toBoolStrict (sRef_isWriteable (s)))
9017         {
9018           voptgenerror (FLG_USEDEF,
9019                         message ("Attempt to set unuseable storage: %q", sRef_unparse (s)),
9020                         exprNode_loc (e));
9021         }
9022       
9023       if (sRef_isMeaningful (s))
9024         {
9025           sRef_setDefinedComplete (s, exprNode_loc (e));
9026         }
9027       
9028       if (exprNode_isDefined (e))
9029         {
9030           e->msets = sRefSet_insert (e->msets, s);
9031         }
9032     }
9033 }
9034
9035 static void
9036 checkUnspecCall (/*@notnull@*/ /*@dependent@*/ exprNode fcn, uentryList params, exprNodeList args)
9037 {
9038   checkAnyCall (fcn, cstring_undefined, params, args, 
9039                 FALSE, sRefSet_undefined, FALSE, 0);
9040 }
9041
9042 static void
9043 checkOneArg (uentry ucurrent, /*@notnull@*/ exprNode current, 
9044              /*@dependent@*/ exprNode fcn, bool isSpec, int argno, int totargs)
9045 {
9046   setCodePoint ();
9047   
9048   if (uentry_isYield (ucurrent))
9049     {
9050       sRef_setDefined (exprNode_getSref (current), exprNode_loc (current));
9051       exprNode_checkSet (current, current->sref);
9052     }
9053   else 
9054     {
9055       if (uentry_isSefParam (ucurrent))
9056         {
9057           sRefSet sets = current->sets;
9058           sRef ref = exprNode_getSref (current);
9059
9060           if (sRef_isMacroParamRef (ref))
9061             {
9062               uentry ue = sRef_getUentry (ref);
9063
9064               if (!uentry_isSefParam (ue))
9065                 {
9066                   voptgenerror 
9067                     (FLG_SEFPARAMS,
9068                      message
9069                      ("Parameter %d to %s is declared sef, but "
9070                       "the argument is a macro parameter declared "
9071                       "without sef: %s",
9072                       argno, exprNode_unparse (fcn),
9073                       exprNode_unparse (current)),
9074                      exprNode_loc (current));
9075                 }
9076             }
9077
9078           if (!sRefSet_isEmpty (sets))
9079             {
9080               sRefSet reported = sRefSet_undefined;
9081               
9082               sRefSet_realElements (current->sets, el)
9083                 {
9084                   if (sRefSet_isSameNameMember (reported, el))
9085                     {
9086                       ; /* don't report again */
9087                     }
9088                   else
9089                     {
9090                       if (sRef_isUnconstrained (el))
9091                         {
9092                           voptgenerror 
9093                             (FLG_SEFUNSPEC,
9094                              message
9095                              ("Parameter %d to %s is declared sef, but "
9096                               "the argument calls unconstrained function %s "
9097                               "(no guarantee it will not modify something): %s",
9098                               argno, exprNode_unparse (fcn),
9099                               sRef_unconstrainedName (el),
9100                               exprNode_unparse (current)),
9101                              exprNode_loc (current));
9102                         }
9103                       else
9104                         {
9105                           voptgenerror 
9106                             (FLG_SEFPARAMS,
9107                              message
9108                              ("Parameter %d to %s is declared sef, but "
9109                               "the argument may modify %q: %s",
9110                               argno, exprNode_unparse (fcn),
9111                               sRef_unparse (el),
9112                               exprNode_unparse (current)),
9113                              exprNode_loc (current));
9114                         }
9115                     } 
9116                 } end_sRefSet_realElements;
9117             }
9118         }
9119       
9120       checkPassTransfer (current, ucurrent, isSpec, fcn, argno, totargs);
9121       exprNode_mergeUSs (fcn, current);
9122     }
9123 }
9124
9125 static void
9126   checkAnyCall (/*@dependent@*/ exprNode fcn, 
9127                 /*@dependent@*/ cstring fname,
9128                 uentryList pn, 
9129                 exprNodeList args, 
9130                 bool hasMods, sRefSet mods,
9131                 bool isSpec,
9132                 int specialArgs)
9133 {
9134   int paramno = 0;
9135   int nargs = exprNodeList_size (args);
9136
9137   setCodePoint ();
9138
9139   /*
9140   ** concat all args ud's to f, add each arg sref as a use unless
9141   ** it was specified as "out", in which case it is a def.
9142   */
9143   
9144   uentryList_reset (pn);
9145   
9146   /*
9147   ** aliasing checks:
9148   **
9149   **    if paramn is only or unique, no other arg may alias argn
9150   */
9151   
9152   exprNodeList_elements (args, current) 
9153     {
9154       paramno++;
9155       
9156       if (exprNode_isDefined (current)) 
9157         {
9158           if ((!uentryList_isUndefined (pn) && !uentryList_isFinished (pn))) 
9159             {
9160               uentry ucurrent = uentryList_current (pn);
9161               
9162               if (specialArgs == 0 
9163                   || (paramno < specialArgs))
9164                 {
9165                                   checkOneArg (ucurrent, current, fcn, isSpec, paramno, nargs);
9166
9167                   if (context_maybeSet (FLG_ALIASUNIQUE))
9168                     {
9169                       if (uentry_isOnly (ucurrent)
9170                           || uentry_isUnique (ucurrent))
9171                         {
9172                           checkUniqueParams (fcn, current, args,
9173                                              paramno, ucurrent);
9174                         }
9175                     }
9176                 } 
9177             }
9178           else /* uentry is undefined */
9179             {
9180               if (specialArgs == 0)
9181                 {
9182                   exprNode_checkUseParam (current);
9183                 }
9184
9185               exprNode_mergeUSs (fcn, current);
9186             }   
9187         }
9188       uentryList_advanceSafe (pn);
9189     } end_exprNodeList_elements;
9190   
9191   if (hasMods)
9192     {
9193       setCodePoint ();
9194
9195       sRefSet_allElements (mods, s)
9196         {
9197           sRef fb;
9198           sRef rb = sRef_getRootBase (s);
9199           
9200           if (sRef_isGlobal (rb))
9201             {
9202               context_usedGlobal (rb);
9203             }
9204           
9205           fb = sRef_fixBaseParam (s, args);
9206           
9207           if (!sRef_isMacroParamRef (fb))
9208             {
9209               if (sRef_isNothing (fb))
9210                 {
9211                   ;
9212                 }
9213               else
9214                 {
9215                   if (sRef_isValid (fb))
9216                     {
9217                       uentry ue = sRef_getBaseUentry (s);
9218                       
9219                       if (uentry_isValid (ue))
9220                         {
9221                           uentry_setLset (ue);
9222                         }
9223                     }
9224                   
9225                   fcn->sets = sRefSet_insert (fcn->sets, fb);
9226                 }
9227             }
9228           sRef_clearDerivedComplete (s); 
9229         } end_sRefSet_allElements;
9230       
9231       setCodePoint ();
9232     }
9233   else
9234     {
9235       if (context_hasMods ())
9236         {
9237           if (context_maybeSet (FLG_MODUNCON))
9238             {
9239               voptgenerror
9240                 (FLG_MODUNCON,
9241                  message ("Undetected modification possible "
9242                           "from call to unconstrained function %s: %s", 
9243                           fname,
9244                           exprNode_unparse (fcn)),
9245                  exprNode_loc (fcn));
9246             }
9247         }
9248       else
9249         {
9250           if (context_maybeSet (FLG_MODUNCONNOMODS)
9251               && !(context_inIterDef () || context_inIterEnd ()))
9252             {
9253               voptgenerror
9254                 (FLG_MODUNCONNOMODS,
9255                  message ("Undetected modification possible "
9256                           "from call to unconstrained function %s: %s", 
9257                           fname,
9258                           exprNode_unparse (fcn)),
9259                  exprNode_loc (fcn));
9260             }
9261         }
9262
9263       exprNode_checkSetAny (fcn, fname);
9264     }
9265 }
9266
9267 void exprNode_checkUseParam (exprNode current)
9268 {
9269   if (exprNode_isDefined (current))
9270     {
9271       exprNode_checkUse (current, current->sref, current->loc);
9272     }
9273 }
9274
9275 static ctype
9276   checkNumerics (ctype tr1, ctype tr2, ctype te1, ctype te2,
9277                  /*@notnull@*/ exprNode e1, /*@notnull@*/ exprNode e2,
9278                  lltok op)
9279 {
9280   ctype ret = tr1;
9281   
9282   if (!ctype_match (tr1, tr2))
9283     {
9284       if ((ctype_isRealInt (tr1) || ctype_isReal (tr1)) &&
9285           (ctype_isRealInt (tr2) || ctype_isReal (tr2)))
9286         {
9287           ;
9288         }
9289       else
9290         {
9291           (void) gentypeerror 
9292             (tr1, e1, tr2, e2,
9293              message ("Incompatible types for %s (%s, %s): %s %s %s",
9294                       lltok_unparse (op),
9295                       ctype_unparse (te1),
9296                       ctype_unparse (te2),
9297                       exprNode_unparse (e1), lltok_unparse (op), 
9298                       exprNode_unparse (e2)),
9299              e1->loc);
9300         }
9301       ret = ctype_unknown;
9302     }
9303   else
9304     {
9305       if (ctype_isForceRealNumeric (&tr1) && ctype_isForceRealNumeric (&tr2))
9306         {
9307           ret = ctype_resolveNumerics (tr1, tr2);
9308         }
9309       else if (!context_msgStrictOps ()) 
9310         {
9311                   if (ctype_isPointer (tr1))
9312             {
9313               if (ctype_isPointer (tr2) && !exprNode_isNullValue (e2))
9314                 {
9315                   ret = ctype_int;
9316                 }
9317               else if (ctype_isInt (tr2))
9318                 {
9319                   ret = te1;
9320                 }
9321               else
9322                 {
9323                   ret = ctype_unknown;
9324                 }
9325             }
9326           else if (ctype_isPointer (tr2))
9327             {
9328               if (ctype_isPointer (tr1))
9329                 {
9330                   ret = ctype_int;
9331                 }
9332               else if (ctype_isInt (tr1))
9333                 {
9334                   ret = te2;
9335                 }
9336               else
9337                 {
9338                   ret = ctype_unknown; 
9339                 }
9340             }
9341           else
9342             {
9343               ret = ctype_resolveNumerics (tr1, tr2);
9344             }
9345         }
9346       else
9347         {
9348           int opid = lltok_getTok (op);
9349           bool comparop = (opid == EQ_OP || opid == NE_OP 
9350                            || opid == TLT || opid == TGT
9351                            || opid == LE_OP || opid == GE_OP);
9352           
9353           if (!ctype_isNumeric (tr1) && !ctype_isNumeric (tr2))
9354             {
9355               if (comparop
9356                   && ((ctype_isEnum (tr1) && ctype_isEnum (tr2))
9357                       || (ctype_isBool (tr1) && ctype_isBool (tr2))
9358                       || (ctype_isChar (tr1) && ctype_isChar (tr2))))
9359                 {
9360                   ; /* no error */
9361                 }
9362               else
9363                 {
9364                   if (ctype_sameName (te1, te2))
9365                     {
9366                       voptgenerror
9367                         (FLG_STRICTOPS,
9368                          message ("Operands of %s are non-numeric (%t): %s %s %s",
9369                                   lltok_unparse (op), te1, 
9370                                   exprNode_unparse (e1), lltok_unparse (op), 
9371                                   exprNode_unparse (e2)),
9372                          e1->loc);
9373                     }
9374                   else
9375                     {
9376                       voptgenerror
9377                         (FLG_STRICTOPS,
9378                          message ("Operands of %s are non-numerics (%t, %t): %s %s %s",
9379                                   lltok_unparse (op), te1, te2, 
9380                                   exprNode_unparse (e1), lltok_unparse (op),
9381                                   exprNode_unparse (e2)),
9382                          e1->loc);
9383                     }
9384                 }
9385             }
9386           else if (!ctype_isNumeric (tr1))
9387             {
9388               voptgenerror
9389                 (FLG_STRICTOPS,
9390                  message ("Right operand of %s is non-numeric (%t): %s %s %s",
9391                           lltok_unparse (op), te1, 
9392                           exprNode_unparse (e1), lltok_unparse (op), 
9393                           exprNode_unparse (e2)),
9394                  e1->loc);
9395             }
9396           else 
9397             {
9398               if (!ctype_isNumeric (tr2))
9399                 {
9400                   voptgenerror
9401                     (FLG_STRICTOPS,
9402                      message ("Left operand of %s is non-numeric (%t): %s %s %s",
9403                               lltok_unparse (op), te2, 
9404                               exprNode_unparse (e1), lltok_unparse (op), 
9405                               exprNode_unparse (e2)),
9406                      e2->loc);
9407                 }
9408             }
9409           
9410           ret = ctype_unknown;
9411         }
9412     }
9413
9414   return ret;
9415 }
9416
9417 static void
9418 abstractOpError (ctype tr1, ctype tr2, lltok op, 
9419                  /*@notnull@*/ exprNode e1, /*@notnull@*/ exprNode e2, 
9420                  fileloc loc1, fileloc loc2)
9421 {
9422   if (ctype_isRealAbstract (tr1) && ctype_isRealAbstract (tr2))
9423     {
9424       if (ctype_match (tr1, tr2))
9425         {
9426           voptgenerror
9427             (FLG_ABSTRACT,
9428              message ("Operands of %s are abstract type (%t): %s %s %s",
9429                       lltok_unparse (op), tr1, 
9430                       exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
9431              loc1);
9432         }
9433       else
9434         {
9435           voptgenerror 
9436             (FLG_ABSTRACT,
9437              message ("Operands of %s are abstract types (%t, %t): %s %s %s",
9438                       lltok_unparse (op), tr1, tr2, 
9439                       exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
9440              loc1);
9441         }
9442     }
9443   else if (ctype_isRealAbstract (tr1))
9444     {
9445       voptgenerror
9446         (FLG_ABSTRACT,
9447          message ("Left operand of %s is abstract type (%t): %s %s %s",
9448                   lltok_unparse (op), tr1, 
9449                   exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
9450          loc1);
9451     }
9452   else 
9453     {
9454       if (ctype_isRealAbstract (tr2))
9455         {
9456           voptgenerror
9457             (FLG_ABSTRACT,
9458              message ("Right operand of %s is abstract type (%t): %s %s %s",
9459                       lltok_unparse (op), tr2, 
9460                       exprNode_unparse (e1), lltok_unparse (op), exprNode_unparse (e2)),
9461              loc2);
9462         }
9463     }
9464 }
9465
9466 /*
9467 ** e1 <= e2
9468 **
9469 ** requies e1 and e2 and not error exprNode's.
9470 **
9471 ** Checks:
9472 **
9473 **    If e1 is a component of an abstract type, and e2 is mutable and client-visible, 
9474 **    the rep of the abstract type is exposed.
9475 **
9476 ** The order is very important:
9477 **
9478 **    check rep expose (move into check transfer)
9479 **    check transfer
9480 **    setup aliases
9481 */
9482
9483 /*
9484 ** This isn't really a sensible procedure, but the indententation
9485 ** was getting too deep.
9486 */
9487
9488 static void
9489 checkOneRepExpose (sRef ysr, sRef base, 
9490                    /*@notnull@*/ exprNode e1, 
9491                    /*@notnull@*/ exprNode e2, ctype ct,
9492                    sRef s2b)
9493 {
9494   if (!(sRef_isOnly (ysr) || sRef_isKeep (ysr) 
9495         || sRef_isOwned (ysr) || sRef_isExposed (ysr)))
9496     {
9497       if (sRef_isAnyParam (base) && !sRef_isExposed (base))
9498         {
9499           if (sRef_isIReference (ysr))
9500             {
9501               if (sRef_sameName (base, sRef_getRootBase (e2->sref)))
9502                 {
9503                   voptgenerror 
9504                     (FLG_ASSIGNEXPOSE,
9505                      message
9506                      ("Assignment of mutable component of parameter %q "
9507                       "to component of abstract "
9508                       "type %s exposes rep: %s = %s",
9509                       sRef_unparse (base),
9510                       ctype_unparse (ct),
9511                       exprNode_unparse (e1), exprNode_unparse (e2)),
9512                      e1->loc);
9513                 }
9514               else
9515                 {
9516                   voptgenerror 
9517                     (FLG_ASSIGNEXPOSE,
9518                      message
9519                      ("Assignment of mutable component of parameter %q "
9520                       "(through alias %q) to component of abstract "
9521                       "type %s exposes rep: %s = %s",
9522                       sRef_unparse (base),
9523                       sRef_unparse (e2->sref),
9524                       ctype_unparse (ct),
9525                       exprNode_unparse (e1), exprNode_unparse (e2)),
9526                      e1->loc);
9527                 }
9528             }
9529           else
9530             {
9531               if (sRef_sameName (base, sRef_getRootBase (e2->sref)))
9532                 {
9533                   voptgenerror 
9534                     (FLG_ASSIGNEXPOSE,
9535                      message ("Assignment of mutable parameter %q "
9536                               "to component of abstract type %s "
9537                               "exposes rep: %s = %s",
9538                               sRef_unparse (base),
9539                               ctype_unparse (ct),
9540                               exprNode_unparse (e1), 
9541                               exprNode_unparse (e2)),
9542                      e1->loc);
9543                 }
9544               else
9545                 {
9546                   voptgenerror 
9547                     (FLG_ASSIGNEXPOSE,
9548                      message ("Assignment of mutable parameter %q "
9549                               "(through alias %q) to "
9550                               "component of abstract type %s exposes "
9551                               "rep: %s = %s",
9552                               sRef_unparse (base),
9553                               sRef_unparse (e2->sref),
9554                               ctype_unparse (ct),
9555                               exprNode_unparse (e1), 
9556                               exprNode_unparse (e2)),
9557                      e1->loc);
9558                 }
9559             }
9560         }
9561       
9562       if (sRef_isGlobal (s2b))
9563         {
9564           if (sRef_sameName (base, sRef_getRootBase (e2->sref)))
9565             {
9566               voptgenerror 
9567                 (FLG_REPEXPOSE,
9568                  message ("Assignment of global %q "
9569                           "to component of "
9570                           "abstract type %s exposes rep: %s = %s",
9571                           sRef_unparse (base),
9572                           ctype_unparse (ct),
9573                           exprNode_unparse (e1), exprNode_unparse (e2)),
9574                  e1->loc);
9575             }
9576           else
9577             {
9578               voptgenerror 
9579                 (FLG_REPEXPOSE,
9580                  message ("Assignment of global %q (through alias %q) "
9581                           "to component of "
9582                           "abstract type %s exposes rep: %s = %s",
9583                           sRef_unparse (base),
9584                           sRef_unparse (e2->sref),
9585                           ctype_unparse (ct),
9586                           exprNode_unparse (e1), exprNode_unparse (e2)),
9587                  e1->loc);
9588             }
9589         }
9590     }
9591 }
9592
9593 static void
9594 doAssign (/*@notnull@*/ exprNode e1, /*@notnull@*/ exprNode e2, bool isInit)
9595 {
9596   if (ctype_isRealFunction (exprNode_getType (e1))
9597       && !ctype_isRealPointer (exprNode_getType (e1)))
9598     {
9599       voptgenerror 
9600         (FLG_TYPE,
9601          message ("Invalid left-hand side of assignment (function type %s): %s",
9602                   ctype_unparse (exprNode_getType (e1)),
9603                   exprNode_unparse (e1)),
9604          e1->loc);
9605     }
9606
9607   if (context_getFlag (FLG_ASSIGNEXPOSE) && ctype_isMutable (e2->typ))
9608     {
9609       ctype t2 = exprNode_getType (e2);
9610       sRef sr = sRef_getRootBase (e1->sref);
9611       ctype ct = sRef_getType (sr);
9612
9613       if (ctype_isAbstract (t2) 
9614           && !(uentry_isMutableDatatype (usymtab_getTypeEntry (ctype_typeId (t2)))))
9615         {
9616           /* it is immutable, okay to reference */
9617           goto donerepexpose;
9618         }
9619
9620       if (ctype_isAbstract (ct) && sRef_isIReference (e1->sref))
9621         {
9622           sRef s2b = sRef_getRootBase (e2->sref);
9623           sRef s1 = e1->sref;
9624           sRef s1b = sRef_getRootBase (s1);
9625           sRefSet aliases;
9626
9627           aliases = usymtab_canAlias (e2->sref);
9628           
9629           if (!sRef_similar (s2b, s1b) 
9630               && !sRef_isExposed (s1)
9631               && !(sRef_isOnly (s2b) || sRef_isKeep (s2b) || sRef_isExposed (s2b)))
9632             {
9633               if (sRef_isAnyParam (s2b) && !sRef_isOnly (s2b) 
9634                   && !sRef_isOwned (s2b) && !sRef_isKeep (s2b)
9635                   && !sRef_isExposed (s2b))
9636                 {
9637                   if (sRef_isIReference (e2->sref))
9638                     {
9639                       voptgenerror 
9640                         (FLG_ASSIGNEXPOSE,
9641                          message 
9642                          ("Assignment of mutable component of parameter %q "
9643                           "to component of abstract type %s exposes rep: %s = %s",
9644                           sRef_unparse (s2b),
9645                           ctype_unparse (ct),
9646                           exprNode_unparse (e1), exprNode_unparse (e2)),
9647                          e1->loc);
9648                     }
9649                   else
9650                     {
9651                       voptgenerror 
9652                         (FLG_ASSIGNEXPOSE,
9653                          message ("Assignment of mutable parameter %q to "
9654                                   "component of abstract type %s exposes rep: %s = %s",
9655                                   sRef_unparse (s2b),
9656                                   ctype_unparse (ct),
9657                                   exprNode_unparse (e1), exprNode_unparse (e2)),
9658                          e1->loc);
9659                     }
9660                 }
9661
9662               if (sRef_isGlobal (s2b))
9663                 {
9664                   voptgenerror
9665                     (FLG_ASSIGNEXPOSE,
9666                      message ("Assignment of global %q to component of "
9667                               "abstract type %s exposes rep: %s = %s",
9668                               sRef_unparse (s2b),
9669                               ctype_unparse (ct),
9670                               exprNode_unparse (e1), exprNode_unparse (e2)),
9671                      e1->loc);
9672                 }
9673               
9674               sRefSet_realElements (aliases, ysr)
9675                 {
9676                   sRef base = sRef_getRootBase (ysr);
9677                   
9678                   if (sRef_similar (ysr, s2b) || sRef_similar (s1b, base)
9679                       || sRef_sameName (base, s1b))
9680                     {
9681                      ; /* error already reported or same sref */
9682                     }
9683                   else
9684                     {
9685                       checkOneRepExpose (ysr, base, e1, e2, ct, s2b);
9686                     }
9687                 } end_sRefSet_realElements;
9688             }
9689           sRefSet_free (aliases);
9690         }
9691     }
9692
9693  donerepexpose:
9694
9695   /*
9696   ** function variables don't really work...
9697   */
9698
9699   if (!ctype_isFunction (ctype_realType (e2->typ)))
9700     {
9701       if (isInit)
9702         {
9703           checkInitTransfer (e1, e2); 
9704         }
9705       else
9706         {
9707           checkAssignTransfer (e1, e2); 
9708         }
9709     }
9710   else
9711     {
9712       sRef fref = e2->sref;
9713
9714       sRef_setDefState (e1->sref, sRef_getDefState (fref), e1->loc);
9715       sRef_setNullState (e1->sref, sRef_getNullState (fref), e1->loc);
9716
9717             /* Need to typecheck the annotation on the parameters */
9718       
9719       if (ctype_isRealFunction (e1->typ)) {
9720         uentryList e1p = ctype_argsFunction (ctype_realType (e1->typ));
9721         uentryList e2p = ctype_argsFunction (ctype_realType (e2->typ));
9722
9723         if (!uentryList_isMissingParams (e1p)
9724             && !uentryList_isMissingParams (e2p)
9725             && uentryList_size (e1p) > 0) {
9726           if (uentryList_size (e1p) == uentryList_size (e2p)) {
9727             int n = 0;
9728             
9729             uentryList_elements (e1p, el1) {
9730               uentry el2;
9731
9732               el2 = uentryList_getN (e2p, n);
9733               n++;
9734               uentry_checkMatchParam (el1, el2, n, e2);
9735             } end_uentryList_elements;
9736           }
9737         }
9738       }
9739     }
9740
9741   if (isInit && sRef_isGlobal (e1->sref))
9742     {
9743        ;
9744     }
9745   else
9746     {
9747       updateAliases (e1, e2); 
9748     }
9749   updateEnvironment (e1, e2);
9750 }
9751
9752 static void 
9753 checkMacroParen (exprNode e)
9754 {
9755   if (exprNode_isError (e) || e->kind == XPR_CAST)
9756     {
9757      ;
9758     }
9759   else 
9760     {
9761       if (sRef_isUnsafe (e->sref) && !exprNode_isInParens (e))
9762         {
9763           voptgenerror 
9764             (FLG_MACROPARENS,
9765              message ("Macro parameter used without parentheses: %s", 
9766                       exprNode_unparse (e)),
9767              e->loc);
9768         }
9769     }
9770 }
9771
9772 static void
9773 reflectNullTest (/*@notnull@*/ exprNode e, bool isnull)
9774 {
9775   if (isnull)
9776     {
9777       e->guards = guardSet_addTrueGuard (e->guards, e->sref);
9778     }
9779   else
9780     {
9781       e->guards = guardSet_addFalseGuard (e->guards, e->sref);
9782     }
9783 }
9784
9785 /*
9786 ** e1 <= e2
9787 **
9788 ** if e2 is a parameter or global derived location which
9789 ** can be modified (that is, e2 is a mutable abstract type,
9790 ** or a derived pointer), then e1 can alias e2.
9791 **
9792 ** e1 can alias everything which e2 can alias.
9793 **
9794 ** Also, if e1 is guarded, remove from guard sets!
9795 */
9796
9797 static void updateAliases (/*@notnull@*/ exprNode e1, /*@notnull@*/ exprNode e2)
9798 {
9799   if (!context_inProtectVars ())
9800     {
9801       /*
9802       ** depends on types of e1 and e2
9803       */
9804       
9805       sRef s1 = e1->sref;
9806       sRef s2 = e2->sref;
9807       ctype t1 = exprNode_getType (e1);
9808       
9809       /* handle pointer sRefs, record fields, arrays, etc... */
9810       
9811       if (!ctype_isRealSU (t1))
9812         {
9813           sRef_copyRealDerivedComplete (s1, s2);
9814         }
9815
9816       if (ctype_isMutable (t1) && sRef_isKnown (s1))
9817         {
9818           usymtab_clearAlias (s1);
9819           usymtab_addMustAlias (s1, s2); 
9820         }
9821
9822       if (sRef_possiblyNull (s1) && usymtab_isGuarded (s1))
9823         {
9824           usymtab_unguard (s1);
9825         }
9826     }
9827 }
9828
9829 exprNode exprNode_updateLocation (/*@returned@*/ exprNode e, /*@temp@*/ fileloc loc)
9830 {
9831   if (exprNode_isDefined (e))
9832     {
9833       e->loc = fileloc_update (e->loc, loc);
9834     }
9835   else
9836     {
9837       e = exprNode_createLoc (ctype_unknown, fileloc_copy (loc));
9838     }
9839
9840   return (e);
9841 }
9842
9843 static void checkUniqueParams (exprNode fcn,
9844                                /*@notnull@*/ exprNode current, 
9845                                exprNodeList args, 
9846                                int paramno, uentry ucurrent)
9847 {
9848   int iparamno = 0;
9849   sRef thisref = exprNode_getSref (current);
9850   
9851   /*
9852   ** Check if any argument could match this argument.
9853   */
9854   
9855   exprNodeList_elements (args, icurrent) 
9856     {
9857       iparamno++;
9858       
9859       if (iparamno != paramno)
9860         {
9861           sRef sr = exprNode_getSref (icurrent);
9862           
9863           if (sRef_similarRelaxed (thisref, sr))
9864             {
9865               if (!sRef_isConst (thisref) && !sRef_isConst (sr))
9866                 {
9867                   voptgenerror 
9868                     (FLG_ALIASUNIQUE,
9869                      message
9870                      ("Parameter %d (%s) to function %s is declared %s but "
9871                       "is aliased by parameter %d (%s)",
9872                       paramno, 
9873                       exprNode_unparse (current),
9874                       exprNode_unparse (fcn),
9875                       alkind_unparse (uentry_getAliasKind (ucurrent)),
9876                       iparamno, exprNode_unparse (icurrent)),
9877                      current->loc);
9878                 }
9879             }
9880           else
9881             {
9882               sRefSet aliases = usymtab_canAlias (sr);
9883
9884               sRefSet_allElements (aliases, asr)
9885                 {
9886                   if (ctype_isUnknown (sRef_getType (thisref)))
9887                     {
9888                       sRef_setType (thisref, uentry_getType (ucurrent));
9889                     }
9890                   
9891                   if (sRef_similarRelaxed (thisref, asr)) 
9892                     {
9893                       if (sRef_isExternal (asr))  
9894                         {
9895                           if (sRef_isLocalState (thisref))
9896                             {
9897                               ; /* okay */
9898                             }
9899                           else
9900                             {
9901                               sRef base = sRef_getRootBase (asr);
9902                               
9903                               if (!sRef_similar (sRef_getBase (asr), thisref)) 
9904                                 {
9905                                   if (sRef_isUnique (base) || sRef_isOnly (base)
9906                                       || sRef_isKept (base)
9907                                       || (sRef_isAddress (asr) && sRef_isLocalVar (base))
9908                                       || (sRef_isAddress (thisref) 
9909                                           && sRef_isLocalVar (sRef_getRootBase (thisref))))
9910                                     {
9911                                       ; /* okay, no error */
9912                                     }
9913                                   else
9914                                     {
9915                                       voptgenerror 
9916                                         (FLG_MAYALIASUNIQUE,
9917                                          message
9918                                          ("Parameter %d (%s) to function %s is declared %s but "
9919                                           "may be aliased externally by parameter %d (%s)",
9920                                           paramno, 
9921                                           exprNode_unparse (current),
9922                                           exprNode_unparse (fcn),
9923                                           alkind_unparse (uentry_getAliasKind (ucurrent)),
9924                                           iparamno, exprNode_unparse (icurrent)),
9925                                          current->loc);
9926                                     }
9927                                 }
9928                             }
9929                         }
9930                       else
9931                         {
9932                           voptgenerror 
9933                             (FLG_ALIASUNIQUE,
9934                              message
9935                              ("Parameter %d (%s) to function %s is declared %s but "
9936                               "is aliased externally by parameter %d (%s) through "
9937                               "alias %q",
9938                               paramno, 
9939                               exprNode_unparse (current),
9940                               exprNode_unparse (fcn),
9941                               alkind_unparse (uentry_getAliasKind (ucurrent)),
9942                               iparamno, exprNode_unparse (icurrent),
9943                               sRef_unparse (asr)),
9944                              current->loc);
9945                         }
9946                     }
9947                 } end_sRefSet_allElements;
9948               sRefSet_free (aliases);
9949             }
9950         }
9951     } end_exprNodeList_elements;
9952 }
9953
9954 long exprNode_getLongValue (exprNode e) {
9955   long value;
9956
9957   if (exprNode_hasValue (e) 
9958       && multiVal_isInt (exprNode_getValue (e)))
9959     {
9960       value = multiVal_forceInt (exprNode_getValue (e));
9961     }
9962   else
9963     {
9964       value = 0;
9965     }
9966   
9967   return value;
9968 }
9969
9970 fileloc exprNode_getfileloc (exprNode p_e)
9971 {
9972   if (p_e)
9973     return fileloc_copy ( p_e->loc );
9974   else
9975     return fileloc_undefined;
9976 }
9977
9978 fileloc exprNode_getNextSequencePoint (exprNode e)
9979 {
9980   /*
9981   ** Returns the location of the sequence point following e.
9982   **
9983   ** Only works for statements (for now).
9984   */
9985
9986   if (exprNode_isDefined (e) && e->kind == XPR_STMT) {
9987     lltok t = exprData_getUopTok (e->edata);
9988     return lltok_getLoc (t);
9989   } else {
9990     #warning fix
9991     //    llcontbug (message ("Cannot get next sequence point: %s", exprNode_unparse (e)));
9992     return fileloc_undefined;
9993   }
9994  }
9995
9996
This page took 0.851294 seconds and 5 git commands to generate.