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