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