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