xref: /openbsd-src/gnu/gcc/gcc/ipa-reference.c (revision 404b540a9034ac75a6199ad1a32d1bbc7a0d4210)
1*404b540aSrobert /* Callgraph based analysis of static variables.
2*404b540aSrobert    Copyright (C) 2004, 2005 Free Software Foundation, Inc.
3*404b540aSrobert    Contributed by Kenneth Zadeck <zadeck@naturalbridge.com>
4*404b540aSrobert 
5*404b540aSrobert This file is part of GCC.
6*404b540aSrobert 
7*404b540aSrobert GCC is free software; you can redistribute it and/or modify it under
8*404b540aSrobert the terms of the GNU General Public License as published by the Free
9*404b540aSrobert Software Foundation; either version 2, or (at your option) any later
10*404b540aSrobert version.
11*404b540aSrobert 
12*404b540aSrobert GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13*404b540aSrobert WARRANTY; without even the implied warranty of MERCHANTABILITY or
14*404b540aSrobert FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15*404b540aSrobert for more details.
16*404b540aSrobert 
17*404b540aSrobert You should have received a copy of the GNU General Public License
18*404b540aSrobert along with GCC; see the file COPYING.  If not, write to the Free
19*404b540aSrobert Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
20*404b540aSrobert 02110-1301, USA.
21*404b540aSrobert */
22*404b540aSrobert 
23*404b540aSrobert /* This file gathers information about how variables whose scope is
24*404b540aSrobert    confined to the compilation unit are used.
25*404b540aSrobert 
26*404b540aSrobert    There are two categories of information produced by this pass:
27*404b540aSrobert 
28*404b540aSrobert    1) The addressable (TREE_ADDRESSABLE) bit and readonly
29*404b540aSrobert    (TREE_READONLY) bit associated with these variables is properly set
30*404b540aSrobert    based on scanning all of the code withing the compilation unit.
31*404b540aSrobert 
32*404b540aSrobert    2) The transitive call site specific clobber effects are computed
33*404b540aSrobert    for the variables whose scope is contained within this compilation
34*404b540aSrobert    unit.
35*404b540aSrobert 
36*404b540aSrobert    First each function and static variable initialization is analyzed
37*404b540aSrobert    to determine which local static variables are either read, written,
38*404b540aSrobert    or have their address taken.  Any local static that has its address
39*404b540aSrobert    taken is removed from consideration.  Once the local read and
40*404b540aSrobert    writes are determined, a transitive closure of this information is
41*404b540aSrobert    performed over the call graph to determine the worst case set of
42*404b540aSrobert    side effects of each call.  In later parts of the compiler, these
43*404b540aSrobert    local and global sets are examined to make the call clobbering less
44*404b540aSrobert    traumatic, promote some statics to registers, and improve aliasing
45*404b540aSrobert    information.
46*404b540aSrobert 
47*404b540aSrobert    Currently must be run after inlining decisions have been made since
48*404b540aSrobert    otherwise, the local sets will not contain information that is
49*404b540aSrobert    consistent with post inlined state.  The global sets are not prone
50*404b540aSrobert    to this problem since they are by definition transitive.
51*404b540aSrobert */
52*404b540aSrobert 
53*404b540aSrobert #include "config.h"
54*404b540aSrobert #include "system.h"
55*404b540aSrobert #include "coretypes.h"
56*404b540aSrobert #include "tm.h"
57*404b540aSrobert #include "tree.h"
58*404b540aSrobert #include "tree-flow.h"
59*404b540aSrobert #include "tree-inline.h"
60*404b540aSrobert #include "tree-pass.h"
61*404b540aSrobert #include "langhooks.h"
62*404b540aSrobert #include "pointer-set.h"
63*404b540aSrobert #include "ggc.h"
64*404b540aSrobert #include "ipa-utils.h"
65*404b540aSrobert #include "ipa-reference.h"
66*404b540aSrobert #include "c-common.h"
67*404b540aSrobert #include "tree-gimple.h"
68*404b540aSrobert #include "cgraph.h"
69*404b540aSrobert #include "output.h"
70*404b540aSrobert #include "flags.h"
71*404b540aSrobert #include "timevar.h"
72*404b540aSrobert #include "diagnostic.h"
73*404b540aSrobert #include "langhooks.h"
74*404b540aSrobert 
75*404b540aSrobert /* This splay tree contains all of the static variables that are
76*404b540aSrobert    being considered by the compilation level alias analysis.  For
77*404b540aSrobert    module_at_a_time compilation, this is the set of static but not
78*404b540aSrobert    public variables.  Any variables that either have their address
79*404b540aSrobert    taken or participate in otherwise unsavory operations are deleted
80*404b540aSrobert    from this list.  */
81*404b540aSrobert static GTY((param1_is(int), param2_is(tree)))
82*404b540aSrobert      splay_tree reference_vars_to_consider;
83*404b540aSrobert 
84*404b540aSrobert /* This bitmap is used to knock out the module static variables whose
85*404b540aSrobert    addresses have been taken and passed around.  */
86*404b540aSrobert static bitmap module_statics_escape;
87*404b540aSrobert 
88*404b540aSrobert /* This bitmap is used to knock out the module static variables that
89*404b540aSrobert    are not readonly.  */
90*404b540aSrobert static bitmap module_statics_written;
91*404b540aSrobert 
92*404b540aSrobert /* A bit is set for every module static we are considering.  This is
93*404b540aSrobert    ored into the local info when asm code is found that clobbers all
94*404b540aSrobert    memory. */
95*404b540aSrobert static bitmap all_module_statics;
96*404b540aSrobert 
97*404b540aSrobert static struct pointer_set_t *visited_nodes;
98*404b540aSrobert 
99*404b540aSrobert static bitmap_obstack ipa_obstack;
100*404b540aSrobert 
101*404b540aSrobert enum initialization_status_t
102*404b540aSrobert {
103*404b540aSrobert   UNINITIALIZED,
104*404b540aSrobert   RUNNING,
105*404b540aSrobert   FINISHED
106*404b540aSrobert };
107*404b540aSrobert 
108*404b540aSrobert tree memory_identifier_string;
109*404b540aSrobert 
110*404b540aSrobert /* Return the ipa_reference_vars structure starting from the cgraph NODE.  */
111*404b540aSrobert static inline ipa_reference_vars_info_t
get_reference_vars_info_from_cgraph(struct cgraph_node * node)112*404b540aSrobert get_reference_vars_info_from_cgraph (struct cgraph_node * node)
113*404b540aSrobert {
114*404b540aSrobert   return get_function_ann (node->decl)->reference_vars_info;
115*404b540aSrobert }
116*404b540aSrobert 
117*404b540aSrobert /* Get a bitmap that contains all of the locally referenced static
118*404b540aSrobert    variables for function FN.  */
119*404b540aSrobert static ipa_reference_local_vars_info_t
get_local_reference_vars_info(tree fn)120*404b540aSrobert get_local_reference_vars_info (tree fn)
121*404b540aSrobert {
122*404b540aSrobert   ipa_reference_vars_info_t info = get_function_ann (fn)->reference_vars_info;
123*404b540aSrobert 
124*404b540aSrobert   if (info)
125*404b540aSrobert     return info->local;
126*404b540aSrobert   else
127*404b540aSrobert     /* This phase was not run.  */
128*404b540aSrobert     return NULL;
129*404b540aSrobert }
130*404b540aSrobert 
131*404b540aSrobert /* Get a bitmap that contains all of the globally referenced static
132*404b540aSrobert    variables for function FN.  */
133*404b540aSrobert 
134*404b540aSrobert static ipa_reference_global_vars_info_t
get_global_reference_vars_info(tree fn)135*404b540aSrobert get_global_reference_vars_info (tree fn)
136*404b540aSrobert {
137*404b540aSrobert   ipa_reference_vars_info_t info = get_function_ann (fn)->reference_vars_info;
138*404b540aSrobert 
139*404b540aSrobert   if (info)
140*404b540aSrobert     return info->global;
141*404b540aSrobert   else
142*404b540aSrobert     /* This phase was not run.  */
143*404b540aSrobert     return NULL;
144*404b540aSrobert }
145*404b540aSrobert 
146*404b540aSrobert /* Return a bitmap indexed by VAR_DECL uid for the static variables
147*404b540aSrobert    that may be read locally by the execution of the function fn.
148*404b540aSrobert    Returns NULL if no data is available.  */
149*404b540aSrobert 
150*404b540aSrobert bitmap
ipa_reference_get_read_local(tree fn)151*404b540aSrobert ipa_reference_get_read_local (tree fn)
152*404b540aSrobert {
153*404b540aSrobert   ipa_reference_local_vars_info_t l = get_local_reference_vars_info (fn);
154*404b540aSrobert   if (l)
155*404b540aSrobert     return l->statics_read;
156*404b540aSrobert   else
157*404b540aSrobert     return NULL;
158*404b540aSrobert }
159*404b540aSrobert 
160*404b540aSrobert /* Return a bitmap indexed by VAR_DECL uid for the static variables
161*404b540aSrobert    that may be written locally by the execution of the function fn.
162*404b540aSrobert    Returns NULL if no data is available.  */
163*404b540aSrobert 
164*404b540aSrobert bitmap
ipa_reference_get_written_local(tree fn)165*404b540aSrobert ipa_reference_get_written_local (tree fn)
166*404b540aSrobert {
167*404b540aSrobert   ipa_reference_local_vars_info_t l = get_local_reference_vars_info (fn);
168*404b540aSrobert   if (l)
169*404b540aSrobert     return l->statics_written;
170*404b540aSrobert   else
171*404b540aSrobert     return NULL;
172*404b540aSrobert }
173*404b540aSrobert 
174*404b540aSrobert /* Return a bitmap indexed by VAR_DECL uid for the static variables
175*404b540aSrobert    that are read during the execution of the function FN.  Returns
176*404b540aSrobert    NULL if no data is available.  */
177*404b540aSrobert 
178*404b540aSrobert bitmap
ipa_reference_get_read_global(tree fn)179*404b540aSrobert ipa_reference_get_read_global (tree fn)
180*404b540aSrobert {
181*404b540aSrobert   ipa_reference_global_vars_info_t g = get_global_reference_vars_info (fn);
182*404b540aSrobert   if (g)
183*404b540aSrobert     return g->statics_read;
184*404b540aSrobert   else
185*404b540aSrobert     return NULL;
186*404b540aSrobert }
187*404b540aSrobert 
188*404b540aSrobert /* Return a bitmap indexed by VAR_DECL uid for the static variables
189*404b540aSrobert    that are written during the execution of the function FN.  Note
190*404b540aSrobert    that variables written may or may not be read during the function
191*404b540aSrobert    call.  Returns NULL if no data is available.  */
192*404b540aSrobert 
193*404b540aSrobert bitmap
ipa_reference_get_written_global(tree fn)194*404b540aSrobert ipa_reference_get_written_global (tree fn)
195*404b540aSrobert {
196*404b540aSrobert   ipa_reference_global_vars_info_t g = get_global_reference_vars_info (fn);
197*404b540aSrobert   if (g)
198*404b540aSrobert     return g->statics_written;
199*404b540aSrobert   else
200*404b540aSrobert     return NULL;
201*404b540aSrobert }
202*404b540aSrobert 
203*404b540aSrobert /* Return a bitmap indexed by_DECL_UID uid for the static variables
204*404b540aSrobert    that are not read during the execution of the function FN.  Returns
205*404b540aSrobert    NULL if no data is available.  */
206*404b540aSrobert 
207*404b540aSrobert bitmap
ipa_reference_get_not_read_global(tree fn)208*404b540aSrobert ipa_reference_get_not_read_global (tree fn)
209*404b540aSrobert {
210*404b540aSrobert   ipa_reference_global_vars_info_t g = get_global_reference_vars_info (fn);
211*404b540aSrobert   if (g)
212*404b540aSrobert     return g->statics_not_read;
213*404b540aSrobert   else
214*404b540aSrobert     return NULL;
215*404b540aSrobert }
216*404b540aSrobert 
217*404b540aSrobert /* Return a bitmap indexed by DECL_UID uid for the static variables
218*404b540aSrobert    that are not written during the execution of the function FN.  Note
219*404b540aSrobert    that variables written may or may not be read during the function
220*404b540aSrobert    call.  Returns NULL if no data is available.  */
221*404b540aSrobert 
222*404b540aSrobert bitmap
ipa_reference_get_not_written_global(tree fn)223*404b540aSrobert ipa_reference_get_not_written_global (tree fn)
224*404b540aSrobert {
225*404b540aSrobert   ipa_reference_global_vars_info_t g = get_global_reference_vars_info (fn);
226*404b540aSrobert   if (g)
227*404b540aSrobert     return g->statics_not_written;
228*404b540aSrobert   else
229*404b540aSrobert     return NULL;
230*404b540aSrobert }
231*404b540aSrobert 
232*404b540aSrobert 
233*404b540aSrobert 
234*404b540aSrobert /* Add VAR to all_module_statics and the two
235*404b540aSrobert    reference_vars_to_consider* sets.  */
236*404b540aSrobert 
237*404b540aSrobert static inline void
add_static_var(tree var)238*404b540aSrobert add_static_var (tree var)
239*404b540aSrobert {
240*404b540aSrobert   int uid = DECL_UID (var);
241*404b540aSrobert   if (!bitmap_bit_p (all_module_statics, uid))
242*404b540aSrobert     {
243*404b540aSrobert       splay_tree_insert (reference_vars_to_consider,
244*404b540aSrobert 			 uid, (splay_tree_value)var);
245*404b540aSrobert       bitmap_set_bit (all_module_statics, uid);
246*404b540aSrobert     }
247*404b540aSrobert }
248*404b540aSrobert 
249*404b540aSrobert /* Return true if the variable T is the right kind of static variable to
250*404b540aSrobert    perform compilation unit scope escape analysis.  */
251*404b540aSrobert 
252*404b540aSrobert static inline bool
has_proper_scope_for_analysis(tree t)253*404b540aSrobert has_proper_scope_for_analysis (tree t)
254*404b540aSrobert {
255*404b540aSrobert   /* If the variable has the "used" attribute, treat it as if it had a
256*404b540aSrobert      been touched by the devil.  */
257*404b540aSrobert   if (lookup_attribute ("used", DECL_ATTRIBUTES (t)))
258*404b540aSrobert     return false;
259*404b540aSrobert 
260*404b540aSrobert   /* Do not want to do anything with volatile except mark any
261*404b540aSrobert      function that uses one to be not const or pure.  */
262*404b540aSrobert   if (TREE_THIS_VOLATILE (t))
263*404b540aSrobert     return false;
264*404b540aSrobert 
265*404b540aSrobert   /* Do not care about a local automatic that is not static.  */
266*404b540aSrobert   if (!TREE_STATIC (t) && !DECL_EXTERNAL (t))
267*404b540aSrobert     return false;
268*404b540aSrobert 
269*404b540aSrobert   if (DECL_EXTERNAL (t) || TREE_PUBLIC (t))
270*404b540aSrobert     return false;
271*404b540aSrobert 
272*404b540aSrobert   /* This is a variable we care about.  Check if we have seen it
273*404b540aSrobert      before, and if not add it the set of variables we care about.  */
274*404b540aSrobert   if (!bitmap_bit_p (all_module_statics, DECL_UID (t)))
275*404b540aSrobert     add_static_var (t);
276*404b540aSrobert 
277*404b540aSrobert   return true;
278*404b540aSrobert }
279*404b540aSrobert 
280*404b540aSrobert /* If T is a VAR_DECL for a static that we are interested in, add the
281*404b540aSrobert    uid to the bitmap.  */
282*404b540aSrobert 
283*404b540aSrobert static void
check_operand(ipa_reference_local_vars_info_t local,tree t,bool checking_write)284*404b540aSrobert check_operand (ipa_reference_local_vars_info_t local,
285*404b540aSrobert 	       tree t, bool checking_write)
286*404b540aSrobert {
287*404b540aSrobert   if (!t) return;
288*404b540aSrobert 
289*404b540aSrobert   if ((TREE_CODE (t) == VAR_DECL || TREE_CODE (t) == FUNCTION_DECL)
290*404b540aSrobert       && (has_proper_scope_for_analysis (t)))
291*404b540aSrobert     {
292*404b540aSrobert       if (checking_write)
293*404b540aSrobert 	{
294*404b540aSrobert 	  if (local)
295*404b540aSrobert 	    bitmap_set_bit (local->statics_written, DECL_UID (t));
296*404b540aSrobert 	  /* Mark the write so we can tell which statics are
297*404b540aSrobert 	     readonly.  */
298*404b540aSrobert 	  bitmap_set_bit (module_statics_written, DECL_UID (t));
299*404b540aSrobert 	}
300*404b540aSrobert       else if (local)
301*404b540aSrobert 	bitmap_set_bit (local->statics_read, DECL_UID (t));
302*404b540aSrobert     }
303*404b540aSrobert }
304*404b540aSrobert 
305*404b540aSrobert /* Examine tree T for references to static variables. All internal
306*404b540aSrobert    references like array references or indirect references are added
307*404b540aSrobert    to the READ_BM. Direct references are added to either READ_BM or
308*404b540aSrobert    WRITE_BM depending on the value of CHECKING_WRITE.   */
309*404b540aSrobert 
310*404b540aSrobert static void
check_tree(ipa_reference_local_vars_info_t local,tree t,bool checking_write)311*404b540aSrobert check_tree (ipa_reference_local_vars_info_t local, tree t, bool checking_write)
312*404b540aSrobert {
313*404b540aSrobert   if ((TREE_CODE (t) == EXC_PTR_EXPR) || (TREE_CODE (t) == FILTER_EXPR))
314*404b540aSrobert     return;
315*404b540aSrobert 
316*404b540aSrobert   while (TREE_CODE (t) == REALPART_EXPR
317*404b540aSrobert 	 || TREE_CODE (t) == IMAGPART_EXPR
318*404b540aSrobert 	 || handled_component_p (t))
319*404b540aSrobert     {
320*404b540aSrobert       if (TREE_CODE (t) == ARRAY_REF)
321*404b540aSrobert 	check_operand (local, TREE_OPERAND (t, 1), false);
322*404b540aSrobert       t = TREE_OPERAND (t, 0);
323*404b540aSrobert     }
324*404b540aSrobert 
325*404b540aSrobert   /* The bottom of an indirect reference can only be read, not
326*404b540aSrobert      written.  So just recurse and whatever we find, check it against
327*404b540aSrobert      the read bitmaps.  */
328*404b540aSrobert 
329*404b540aSrobert   /*  if (INDIRECT_REF_P (t) || TREE_CODE (t) == MEM_REF) */
330*404b540aSrobert   /* FIXME when we have array_ref's of pointers.  */
331*404b540aSrobert   if (INDIRECT_REF_P (t))
332*404b540aSrobert     check_tree (local, TREE_OPERAND (t, 0), false);
333*404b540aSrobert 
334*404b540aSrobert   if (SSA_VAR_P (t))
335*404b540aSrobert     check_operand (local, t, checking_write);
336*404b540aSrobert }
337*404b540aSrobert 
338*404b540aSrobert /* Scan tree T to see if there are any addresses taken in within T.  */
339*404b540aSrobert 
340*404b540aSrobert static void
look_for_address_of(tree t)341*404b540aSrobert look_for_address_of (tree t)
342*404b540aSrobert {
343*404b540aSrobert   if (TREE_CODE (t) == ADDR_EXPR)
344*404b540aSrobert     {
345*404b540aSrobert       tree x = get_base_var (t);
346*404b540aSrobert       if (TREE_CODE (x) == VAR_DECL || TREE_CODE (x) == FUNCTION_DECL)
347*404b540aSrobert 	if (has_proper_scope_for_analysis (x))
348*404b540aSrobert 	  bitmap_set_bit (module_statics_escape, DECL_UID (x));
349*404b540aSrobert     }
350*404b540aSrobert }
351*404b540aSrobert 
352*404b540aSrobert /* Check to see if T is a read or address of operation on a static var
353*404b540aSrobert    we are interested in analyzing.  LOCAL is passed in to get access
354*404b540aSrobert    to its bit vectors.  Local is NULL if this is called from a static
355*404b540aSrobert    initializer.  */
356*404b540aSrobert 
357*404b540aSrobert static void
check_rhs_var(ipa_reference_local_vars_info_t local,tree t)358*404b540aSrobert check_rhs_var (ipa_reference_local_vars_info_t local, tree t)
359*404b540aSrobert {
360*404b540aSrobert   look_for_address_of (t);
361*404b540aSrobert 
362*404b540aSrobert   if (local == NULL)
363*404b540aSrobert     return;
364*404b540aSrobert 
365*404b540aSrobert   check_tree(local, t, false);
366*404b540aSrobert }
367*404b540aSrobert 
368*404b540aSrobert /* Check to see if T is an assignment to a static var we are
369*404b540aSrobert    interested in analyzing.  LOCAL is passed in to get access to its bit
370*404b540aSrobert    vectors.  */
371*404b540aSrobert 
372*404b540aSrobert static void
check_lhs_var(ipa_reference_local_vars_info_t local,tree t)373*404b540aSrobert check_lhs_var (ipa_reference_local_vars_info_t local, tree t)
374*404b540aSrobert {
375*404b540aSrobert   if (local == NULL)
376*404b540aSrobert     return;
377*404b540aSrobert 
378*404b540aSrobert   check_tree(local, t, true);
379*404b540aSrobert }
380*404b540aSrobert 
381*404b540aSrobert /* This is a scaled down version of get_asm_expr_operands from
382*404b540aSrobert    tree_ssa_operands.c.  The version there runs much later and assumes
383*404b540aSrobert    that aliasing information is already available. Here we are just
384*404b540aSrobert    trying to find if the set of inputs and outputs contain references
385*404b540aSrobert    or address of operations to local static variables.  FN is the
386*404b540aSrobert    function being analyzed and STMT is the actual asm statement.  */
387*404b540aSrobert 
388*404b540aSrobert static void
get_asm_expr_operands(ipa_reference_local_vars_info_t local,tree stmt)389*404b540aSrobert get_asm_expr_operands (ipa_reference_local_vars_info_t local, tree stmt)
390*404b540aSrobert {
391*404b540aSrobert   int noutputs = list_length (ASM_OUTPUTS (stmt));
392*404b540aSrobert   const char **oconstraints
393*404b540aSrobert     = (const char **) alloca ((noutputs) * sizeof (const char *));
394*404b540aSrobert   int i;
395*404b540aSrobert   tree link;
396*404b540aSrobert   const char *constraint;
397*404b540aSrobert   bool allows_mem, allows_reg, is_inout;
398*404b540aSrobert 
399*404b540aSrobert   for (i=0, link = ASM_OUTPUTS (stmt); link; ++i, link = TREE_CHAIN (link))
400*404b540aSrobert     {
401*404b540aSrobert       oconstraints[i] = constraint
402*404b540aSrobert 	= TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
403*404b540aSrobert       parse_output_constraint (&constraint, i, 0, 0,
404*404b540aSrobert 			       &allows_mem, &allows_reg, &is_inout);
405*404b540aSrobert 
406*404b540aSrobert       check_lhs_var (local, TREE_VALUE (link));
407*404b540aSrobert     }
408*404b540aSrobert 
409*404b540aSrobert   for (link = ASM_INPUTS (stmt); link; link = TREE_CHAIN (link))
410*404b540aSrobert     {
411*404b540aSrobert       constraint
412*404b540aSrobert 	= TREE_STRING_POINTER (TREE_VALUE (TREE_PURPOSE (link)));
413*404b540aSrobert       parse_input_constraint (&constraint, 0, 0, noutputs, 0,
414*404b540aSrobert 			      oconstraints, &allows_mem, &allows_reg);
415*404b540aSrobert 
416*404b540aSrobert       check_rhs_var (local, TREE_VALUE (link));
417*404b540aSrobert     }
418*404b540aSrobert 
419*404b540aSrobert   for (link = ASM_CLOBBERS (stmt); link; link = TREE_CHAIN (link))
420*404b540aSrobert     if (simple_cst_equal(TREE_VALUE (link), memory_identifier_string) == 1)
421*404b540aSrobert       {
422*404b540aSrobert 	/* Abandon all hope, ye who enter here. */
423*404b540aSrobert 	local->calls_read_all = true;
424*404b540aSrobert 	local->calls_write_all = true;
425*404b540aSrobert       }
426*404b540aSrobert }
427*404b540aSrobert 
428*404b540aSrobert /* Check the parameters of a function call from CALLER to CALL_EXPR to
429*404b540aSrobert    see if any of them are static vars.  Also check to see if this is
430*404b540aSrobert    either an indirect call, a call outside the compilation unit, or
431*404b540aSrobert    has special attributes that effect the clobbers.  The caller
432*404b540aSrobert    parameter is the tree node for the caller and the second operand is
433*404b540aSrobert    the tree node for the entire call expression.  */
434*404b540aSrobert 
435*404b540aSrobert static void
check_call(ipa_reference_local_vars_info_t local,tree call_expr)436*404b540aSrobert check_call (ipa_reference_local_vars_info_t local, tree call_expr)
437*404b540aSrobert {
438*404b540aSrobert   int flags = call_expr_flags (call_expr);
439*404b540aSrobert   tree operand_list = TREE_OPERAND (call_expr, 1);
440*404b540aSrobert   tree operand;
441*404b540aSrobert   tree callee_t = get_callee_fndecl (call_expr);
442*404b540aSrobert   enum availability avail = AVAIL_NOT_AVAILABLE;
443*404b540aSrobert 
444*404b540aSrobert   for (operand = operand_list;
445*404b540aSrobert        operand != NULL_TREE;
446*404b540aSrobert        operand = TREE_CHAIN (operand))
447*404b540aSrobert     {
448*404b540aSrobert       tree argument = TREE_VALUE (operand);
449*404b540aSrobert       check_rhs_var (local, argument);
450*404b540aSrobert     }
451*404b540aSrobert 
452*404b540aSrobert   if (callee_t)
453*404b540aSrobert     {
454*404b540aSrobert       struct cgraph_node* callee = cgraph_node(callee_t);
455*404b540aSrobert       avail = cgraph_function_body_availability (callee);
456*404b540aSrobert     }
457*404b540aSrobert 
458*404b540aSrobert   if (avail == AVAIL_NOT_AVAILABLE || avail == AVAIL_OVERWRITABLE)
459*404b540aSrobert     if (local)
460*404b540aSrobert       {
461*404b540aSrobert 	if (flags & ECF_PURE)
462*404b540aSrobert 	  local->calls_read_all = true;
463*404b540aSrobert 	else
464*404b540aSrobert 	  {
465*404b540aSrobert 	    local->calls_read_all = true;
466*404b540aSrobert 	    local->calls_write_all = true;
467*404b540aSrobert 	  }
468*404b540aSrobert       }
469*404b540aSrobert }
470*404b540aSrobert 
471*404b540aSrobert /* TP is the part of the tree currently under the microscope.
472*404b540aSrobert    WALK_SUBTREES is part of the walk_tree api but is unused here.
473*404b540aSrobert    DATA is cgraph_node of the function being walked.  */
474*404b540aSrobert 
475*404b540aSrobert /* FIXME: When this is converted to run over SSA form, this code
476*404b540aSrobert    should be converted to use the operand scanner.  */
477*404b540aSrobert 
478*404b540aSrobert static tree
scan_for_static_refs(tree * tp,int * walk_subtrees,void * data)479*404b540aSrobert scan_for_static_refs (tree *tp,
480*404b540aSrobert 		      int *walk_subtrees,
481*404b540aSrobert 		      void *data)
482*404b540aSrobert {
483*404b540aSrobert   struct cgraph_node *fn = data;
484*404b540aSrobert   tree t = *tp;
485*404b540aSrobert   ipa_reference_local_vars_info_t local = NULL;
486*404b540aSrobert   if (fn)
487*404b540aSrobert     local = get_reference_vars_info_from_cgraph (fn)->local;
488*404b540aSrobert 
489*404b540aSrobert   switch (TREE_CODE (t))
490*404b540aSrobert     {
491*404b540aSrobert     case VAR_DECL:
492*404b540aSrobert       if (DECL_INITIAL (t))
493*404b540aSrobert 	walk_tree (&DECL_INITIAL (t), scan_for_static_refs, fn, visited_nodes);
494*404b540aSrobert       *walk_subtrees = 0;
495*404b540aSrobert       break;
496*404b540aSrobert 
497*404b540aSrobert     case MODIFY_EXPR:
498*404b540aSrobert       {
499*404b540aSrobert 	/* First look on the lhs and see what variable is stored to */
500*404b540aSrobert 	tree lhs = TREE_OPERAND (t, 0);
501*404b540aSrobert 	tree rhs = TREE_OPERAND (t, 1);
502*404b540aSrobert 	check_lhs_var (local, lhs);
503*404b540aSrobert 
504*404b540aSrobert 	/* For the purposes of figuring out what the cast affects */
505*404b540aSrobert 
506*404b540aSrobert 	/* Next check the operands on the rhs to see if they are ok. */
507*404b540aSrobert 	switch (TREE_CODE_CLASS (TREE_CODE (rhs)))
508*404b540aSrobert 	  {
509*404b540aSrobert 	  case tcc_binary:
510*404b540aSrobert 	  case tcc_comparison:
511*404b540aSrobert  	    {
512*404b540aSrobert  	      tree op0 = TREE_OPERAND (rhs, 0);
513*404b540aSrobert  	      tree op1 = TREE_OPERAND (rhs, 1);
514*404b540aSrobert  	      check_rhs_var (local, op0);
515*404b540aSrobert  	      check_rhs_var (local, op1);
516*404b540aSrobert 	    }
517*404b540aSrobert 	    break;
518*404b540aSrobert 	  case tcc_unary:
519*404b540aSrobert  	    {
520*404b540aSrobert  	      tree op0 = TREE_OPERAND (rhs, 0);
521*404b540aSrobert  	      check_rhs_var (local, op0);
522*404b540aSrobert  	    }
523*404b540aSrobert 
524*404b540aSrobert 	    break;
525*404b540aSrobert 	  case tcc_reference:
526*404b540aSrobert 	    check_rhs_var (local, rhs);
527*404b540aSrobert 	    break;
528*404b540aSrobert 	  case tcc_declaration:
529*404b540aSrobert 	    check_rhs_var (local, rhs);
530*404b540aSrobert 	    break;
531*404b540aSrobert 	  case tcc_expression:
532*404b540aSrobert 	    switch (TREE_CODE (rhs))
533*404b540aSrobert 	      {
534*404b540aSrobert 	      case ADDR_EXPR:
535*404b540aSrobert 		check_rhs_var (local, rhs);
536*404b540aSrobert 		break;
537*404b540aSrobert 	      case CALL_EXPR:
538*404b540aSrobert 		check_call (local, rhs);
539*404b540aSrobert 		break;
540*404b540aSrobert 	      default:
541*404b540aSrobert 		break;
542*404b540aSrobert 	      }
543*404b540aSrobert 	    break;
544*404b540aSrobert 	  default:
545*404b540aSrobert 	    break;
546*404b540aSrobert 	  }
547*404b540aSrobert 	*walk_subtrees = 0;
548*404b540aSrobert       }
549*404b540aSrobert       break;
550*404b540aSrobert 
551*404b540aSrobert     case ADDR_EXPR:
552*404b540aSrobert       /* This case is here to find addresses on rhs of constructors in
553*404b540aSrobert 	 decl_initial of static variables. */
554*404b540aSrobert       check_rhs_var (local, t);
555*404b540aSrobert       *walk_subtrees = 0;
556*404b540aSrobert       break;
557*404b540aSrobert 
558*404b540aSrobert     case LABEL_EXPR:
559*404b540aSrobert       if (DECL_NONLOCAL (TREE_OPERAND (t, 0)))
560*404b540aSrobert 	{
561*404b540aSrobert 	  /* Target of long jump. */
562*404b540aSrobert 	  local->calls_read_all = true;
563*404b540aSrobert 	  local->calls_write_all = true;
564*404b540aSrobert 	}
565*404b540aSrobert       break;
566*404b540aSrobert 
567*404b540aSrobert     case CALL_EXPR:
568*404b540aSrobert       check_call (local, t);
569*404b540aSrobert       *walk_subtrees = 0;
570*404b540aSrobert       break;
571*404b540aSrobert 
572*404b540aSrobert     case ASM_EXPR:
573*404b540aSrobert       get_asm_expr_operands (local, t);
574*404b540aSrobert       *walk_subtrees = 0;
575*404b540aSrobert       break;
576*404b540aSrobert 
577*404b540aSrobert     default:
578*404b540aSrobert       break;
579*404b540aSrobert     }
580*404b540aSrobert   return NULL;
581*404b540aSrobert }
582*404b540aSrobert 
583*404b540aSrobert 
584*404b540aSrobert /* Lookup the tree node for the static variable that has UID.  */
585*404b540aSrobert static tree
get_static_decl(int index)586*404b540aSrobert get_static_decl (int index)
587*404b540aSrobert {
588*404b540aSrobert   splay_tree_node stn =
589*404b540aSrobert     splay_tree_lookup (reference_vars_to_consider, index);
590*404b540aSrobert   if (stn)
591*404b540aSrobert     return (tree)stn->value;
592*404b540aSrobert   return NULL;
593*404b540aSrobert }
594*404b540aSrobert 
595*404b540aSrobert /* Lookup the tree node for the static variable that has UID and
596*404b540aSrobert    convert the name to a string for debugging.  */
597*404b540aSrobert 
598*404b540aSrobert static const char *
get_static_name(int index)599*404b540aSrobert get_static_name (int index)
600*404b540aSrobert {
601*404b540aSrobert   splay_tree_node stn =
602*404b540aSrobert     splay_tree_lookup (reference_vars_to_consider, index);
603*404b540aSrobert   if (stn)
604*404b540aSrobert     return lang_hooks.decl_printable_name ((tree)(stn->value), 2);
605*404b540aSrobert   return NULL;
606*404b540aSrobert }
607*404b540aSrobert 
608*404b540aSrobert /* Or in all of the bits from every callee into X, the caller's, bit
609*404b540aSrobert    vector.  There are several cases to check to avoid the sparse
610*404b540aSrobert    bitmap oring.  */
611*404b540aSrobert 
612*404b540aSrobert static void
propagate_bits(struct cgraph_node * x)613*404b540aSrobert propagate_bits (struct cgraph_node *x)
614*404b540aSrobert {
615*404b540aSrobert   ipa_reference_vars_info_t x_info = get_reference_vars_info_from_cgraph (x);
616*404b540aSrobert   ipa_reference_global_vars_info_t x_global = x_info->global;
617*404b540aSrobert 
618*404b540aSrobert   struct cgraph_edge *e;
619*404b540aSrobert   for (e = x->callees; e; e = e->next_callee)
620*404b540aSrobert     {
621*404b540aSrobert       struct cgraph_node *y = e->callee;
622*404b540aSrobert 
623*404b540aSrobert       /* Only look at the master nodes and skip external nodes.  */
624*404b540aSrobert       y = cgraph_master_clone (y);
625*404b540aSrobert       if (y)
626*404b540aSrobert 	{
627*404b540aSrobert 	  if (get_reference_vars_info_from_cgraph (y))
628*404b540aSrobert 	    {
629*404b540aSrobert 	      ipa_reference_vars_info_t y_info = get_reference_vars_info_from_cgraph (y);
630*404b540aSrobert 	      ipa_reference_global_vars_info_t y_global = y_info->global;
631*404b540aSrobert 
632*404b540aSrobert 	      if (x_global->statics_read
633*404b540aSrobert 		  != all_module_statics)
634*404b540aSrobert 		{
635*404b540aSrobert 		  if (y_global->statics_read
636*404b540aSrobert 		      == all_module_statics)
637*404b540aSrobert 		    {
638*404b540aSrobert 		      BITMAP_FREE (x_global->statics_read);
639*404b540aSrobert 		      x_global->statics_read
640*404b540aSrobert 			= all_module_statics;
641*404b540aSrobert 		    }
642*404b540aSrobert 		  /* Skip bitmaps that are pointer equal to node's bitmap
643*404b540aSrobert 		     (no reason to spin within the cycle).  */
644*404b540aSrobert 		  else if (x_global->statics_read
645*404b540aSrobert 			   != y_global->statics_read)
646*404b540aSrobert 		    bitmap_ior_into (x_global->statics_read,
647*404b540aSrobert 				     y_global->statics_read);
648*404b540aSrobert 		}
649*404b540aSrobert 
650*404b540aSrobert 	      if (x_global->statics_written
651*404b540aSrobert 		  != all_module_statics)
652*404b540aSrobert 		{
653*404b540aSrobert 		  if (y_global->statics_written
654*404b540aSrobert 		      == all_module_statics)
655*404b540aSrobert 		    {
656*404b540aSrobert 		      BITMAP_FREE (x_global->statics_written);
657*404b540aSrobert 		      x_global->statics_written
658*404b540aSrobert 			= all_module_statics;
659*404b540aSrobert 		    }
660*404b540aSrobert 		  /* Skip bitmaps that are pointer equal to node's bitmap
661*404b540aSrobert 		     (no reason to spin within the cycle).  */
662*404b540aSrobert 		  else if (x_global->statics_written
663*404b540aSrobert 			   != y_global->statics_written)
664*404b540aSrobert 		    bitmap_ior_into (x_global->statics_written,
665*404b540aSrobert 				     y_global->statics_written);
666*404b540aSrobert 		}
667*404b540aSrobert 	    }
668*404b540aSrobert 	  else
669*404b540aSrobert 	    {
670*404b540aSrobert 	      gcc_unreachable ();
671*404b540aSrobert 	    }
672*404b540aSrobert 	}
673*404b540aSrobert     }
674*404b540aSrobert }
675*404b540aSrobert 
676*404b540aSrobert /* Look at all of the callees of X to see which ones represent inlined
677*404b540aSrobert    calls.  For each of these callees, merge their local info into
678*404b540aSrobert    TARGET and check their children recursively.
679*404b540aSrobert 
680*404b540aSrobert    This function goes away when Jan changes the inliner and IPA
681*404b540aSrobert    analysis so that this is not run between the time when inlining
682*404b540aSrobert    decisions are made and when the inlining actually occurs.  */
683*404b540aSrobert 
684*404b540aSrobert static void
merge_callee_local_info(struct cgraph_node * target,struct cgraph_node * x)685*404b540aSrobert merge_callee_local_info (struct cgraph_node *target,
686*404b540aSrobert 			 struct cgraph_node *x)
687*404b540aSrobert {
688*404b540aSrobert   struct cgraph_edge *e;
689*404b540aSrobert   ipa_reference_local_vars_info_t x_l =
690*404b540aSrobert     get_reference_vars_info_from_cgraph (target)->local;
691*404b540aSrobert 
692*404b540aSrobert   /* Make the world safe for tail recursion.  */
693*404b540aSrobert   struct ipa_dfs_info *node_info = x->aux;
694*404b540aSrobert 
695*404b540aSrobert   if (node_info->aux)
696*404b540aSrobert     return;
697*404b540aSrobert 
698*404b540aSrobert   node_info->aux = x;
699*404b540aSrobert 
700*404b540aSrobert   for (e = x->callees; e; e = e->next_callee)
701*404b540aSrobert     {
702*404b540aSrobert       struct cgraph_node *y = e->callee;
703*404b540aSrobert       if (y->global.inlined_to)
704*404b540aSrobert 	{
705*404b540aSrobert 	  ipa_reference_vars_info_t y_info;
706*404b540aSrobert 	  ipa_reference_local_vars_info_t y_l;
707*404b540aSrobert 	  struct cgraph_node* orig_y = y;
708*404b540aSrobert 
709*404b540aSrobert 	  y = cgraph_master_clone (y);
710*404b540aSrobert 	  if (y)
711*404b540aSrobert 	    {
712*404b540aSrobert 	      y_info = get_reference_vars_info_from_cgraph (y);
713*404b540aSrobert 	      y_l = y_info->local;
714*404b540aSrobert 	      if (x_l != y_l)
715*404b540aSrobert 		{
716*404b540aSrobert 		  bitmap_ior_into (x_l->statics_read,
717*404b540aSrobert 				   y_l->statics_read);
718*404b540aSrobert 		  bitmap_ior_into (x_l->statics_written,
719*404b540aSrobert 				   y_l->statics_written);
720*404b540aSrobert 		}
721*404b540aSrobert 	      x_l->calls_read_all |= y_l->calls_read_all;
722*404b540aSrobert 	      x_l->calls_write_all |= y_l->calls_write_all;
723*404b540aSrobert 	      merge_callee_local_info (target, y);
724*404b540aSrobert 	    }
725*404b540aSrobert 	  else
726*404b540aSrobert 	    {
727*404b540aSrobert 	      fprintf(stderr, "suspect inlining of ");
728*404b540aSrobert 	      dump_cgraph_node (stderr, orig_y);
729*404b540aSrobert 	      fprintf(stderr, "\ninto ");
730*404b540aSrobert 	      dump_cgraph_node (stderr, target);
731*404b540aSrobert 	      dump_cgraph (stderr);
732*404b540aSrobert 	      gcc_assert(false);
733*404b540aSrobert 	    }
734*404b540aSrobert 	}
735*404b540aSrobert     }
736*404b540aSrobert 
737*404b540aSrobert   node_info->aux = NULL;
738*404b540aSrobert }
739*404b540aSrobert 
740*404b540aSrobert /* The init routine for analyzing global static variable usage.  See
741*404b540aSrobert    comments at top for description.  */
742*404b540aSrobert static void
ipa_init(void)743*404b540aSrobert ipa_init (void)
744*404b540aSrobert {
745*404b540aSrobert   struct cgraph_node *node;
746*404b540aSrobert   memory_identifier_string = build_string(7, "memory");
747*404b540aSrobert 
748*404b540aSrobert   reference_vars_to_consider =
749*404b540aSrobert     splay_tree_new_ggc (splay_tree_compare_ints);
750*404b540aSrobert 
751*404b540aSrobert   bitmap_obstack_initialize (&ipa_obstack);
752*404b540aSrobert   module_statics_escape = BITMAP_ALLOC (&ipa_obstack);
753*404b540aSrobert   module_statics_written = BITMAP_ALLOC (&ipa_obstack);
754*404b540aSrobert   all_module_statics = BITMAP_ALLOC (&ipa_obstack);
755*404b540aSrobert 
756*404b540aSrobert   /* This will add NODE->DECL to the splay trees.  */
757*404b540aSrobert   for (node = cgraph_nodes; node; node = node->next)
758*404b540aSrobert     has_proper_scope_for_analysis (node->decl);
759*404b540aSrobert 
760*404b540aSrobert   /* There are some shared nodes, in particular the initializers on
761*404b540aSrobert      static declarations.  We do not need to scan them more than once
762*404b540aSrobert      since all we would be interested in are the addressof
763*404b540aSrobert      operations.  */
764*404b540aSrobert   visited_nodes = pointer_set_create ();
765*404b540aSrobert }
766*404b540aSrobert 
767*404b540aSrobert /* Check out the rhs of a static or global initialization VNODE to see
768*404b540aSrobert    if any of them contain addressof operations.  Note that some of
769*404b540aSrobert    these variables may  not even be referenced in the code in this
770*404b540aSrobert    compilation unit but their right hand sides may contain references
771*404b540aSrobert    to variables defined within this unit.  */
772*404b540aSrobert 
773*404b540aSrobert static void
analyze_variable(struct cgraph_varpool_node * vnode)774*404b540aSrobert analyze_variable (struct cgraph_varpool_node *vnode)
775*404b540aSrobert {
776*404b540aSrobert   tree global = vnode->decl;
777*404b540aSrobert   if (TREE_CODE (global) == VAR_DECL)
778*404b540aSrobert     {
779*404b540aSrobert       if (DECL_INITIAL (global))
780*404b540aSrobert 	walk_tree (&DECL_INITIAL (global), scan_for_static_refs,
781*404b540aSrobert 		   NULL, visited_nodes);
782*404b540aSrobert     }
783*404b540aSrobert   else gcc_unreachable ();
784*404b540aSrobert }
785*404b540aSrobert 
786*404b540aSrobert /* This is the main routine for finding the reference patterns for
787*404b540aSrobert    global variables within a function FN.  */
788*404b540aSrobert 
789*404b540aSrobert static void
analyze_function(struct cgraph_node * fn)790*404b540aSrobert analyze_function (struct cgraph_node *fn)
791*404b540aSrobert {
792*404b540aSrobert   ipa_reference_vars_info_t info
793*404b540aSrobert     = xcalloc (1, sizeof (struct ipa_reference_vars_info_d));
794*404b540aSrobert   ipa_reference_local_vars_info_t l
795*404b540aSrobert     = xcalloc (1, sizeof (struct ipa_reference_local_vars_info_d));
796*404b540aSrobert   tree decl = fn->decl;
797*404b540aSrobert 
798*404b540aSrobert   /* Add the info to the tree's annotation.  */
799*404b540aSrobert   get_function_ann (fn->decl)->reference_vars_info = info;
800*404b540aSrobert 
801*404b540aSrobert   info->local = l;
802*404b540aSrobert   l->statics_read = BITMAP_ALLOC (&ipa_obstack);
803*404b540aSrobert   l->statics_written = BITMAP_ALLOC (&ipa_obstack);
804*404b540aSrobert 
805*404b540aSrobert   if (dump_file)
806*404b540aSrobert     fprintf (dump_file, "\n local analysis of %s\n", cgraph_node_name (fn));
807*404b540aSrobert 
808*404b540aSrobert   {
809*404b540aSrobert     struct function *this_cfun = DECL_STRUCT_FUNCTION (decl);
810*404b540aSrobert     basic_block this_block;
811*404b540aSrobert 
812*404b540aSrobert     FOR_EACH_BB_FN (this_block, this_cfun)
813*404b540aSrobert       {
814*404b540aSrobert 	block_stmt_iterator bsi;
815*404b540aSrobert 	for (bsi = bsi_start (this_block); !bsi_end_p (bsi); bsi_next (&bsi))
816*404b540aSrobert 	  walk_tree (bsi_stmt_ptr (bsi), scan_for_static_refs,
817*404b540aSrobert 		     fn, visited_nodes);
818*404b540aSrobert       }
819*404b540aSrobert   }
820*404b540aSrobert 
821*404b540aSrobert   /* There may be const decls with interesting right hand sides.  */
822*404b540aSrobert   if (DECL_STRUCT_FUNCTION (decl))
823*404b540aSrobert     {
824*404b540aSrobert       tree step;
825*404b540aSrobert       for (step = DECL_STRUCT_FUNCTION (decl)->unexpanded_var_list;
826*404b540aSrobert 	   step;
827*404b540aSrobert 	   step = TREE_CHAIN (step))
828*404b540aSrobert 	{
829*404b540aSrobert 	  tree var = TREE_VALUE (step);
830*404b540aSrobert 	  if (TREE_CODE (var) == VAR_DECL
831*404b540aSrobert 	      && DECL_INITIAL (var)
832*404b540aSrobert 	      && !TREE_STATIC (var))
833*404b540aSrobert 	    walk_tree (&DECL_INITIAL (var), scan_for_static_refs,
834*404b540aSrobert 		       fn, visited_nodes);
835*404b540aSrobert 	}
836*404b540aSrobert     }
837*404b540aSrobert }
838*404b540aSrobert 
839*404b540aSrobert /* If FN is avail == AVAIL_OVERWRITABLE, replace the effects bit
840*404b540aSrobert    vectors with worst case bit vectors.  We had to analyze it above to
841*404b540aSrobert    find out if it took the address of any statics. However, now that
842*404b540aSrobert    we know that, we can get rid of all of the other side effects.  */
843*404b540aSrobert 
844*404b540aSrobert static void
clean_function(struct cgraph_node * fn)845*404b540aSrobert clean_function (struct cgraph_node *fn)
846*404b540aSrobert {
847*404b540aSrobert   ipa_reference_vars_info_t info = get_reference_vars_info_from_cgraph (fn);
848*404b540aSrobert   ipa_reference_local_vars_info_t l = info->local;
849*404b540aSrobert   ipa_reference_global_vars_info_t g = info->global;
850*404b540aSrobert 
851*404b540aSrobert   if (l)
852*404b540aSrobert     {
853*404b540aSrobert       if (l->statics_read
854*404b540aSrobert 	  && l->statics_read != all_module_statics)
855*404b540aSrobert 	BITMAP_FREE (l->statics_read);
856*404b540aSrobert       if (l->statics_written
857*404b540aSrobert 	  &&l->statics_written != all_module_statics)
858*404b540aSrobert 	BITMAP_FREE (l->statics_written);
859*404b540aSrobert       free (l);
860*404b540aSrobert     }
861*404b540aSrobert 
862*404b540aSrobert   if (g)
863*404b540aSrobert     {
864*404b540aSrobert       if (g->statics_read
865*404b540aSrobert 	  && g->statics_read != all_module_statics)
866*404b540aSrobert 	BITMAP_FREE (g->statics_read);
867*404b540aSrobert 
868*404b540aSrobert       if (g->statics_written
869*404b540aSrobert 	  && g->statics_written != all_module_statics)
870*404b540aSrobert 	BITMAP_FREE (g->statics_written);
871*404b540aSrobert 
872*404b540aSrobert       if (g->statics_not_read
873*404b540aSrobert 	  && g->statics_not_read != all_module_statics)
874*404b540aSrobert 	BITMAP_FREE (g->statics_not_read);
875*404b540aSrobert 
876*404b540aSrobert       if (g->statics_not_written
877*404b540aSrobert 	  && g->statics_not_written != all_module_statics)
878*404b540aSrobert 	BITMAP_FREE (g->statics_not_written);
879*404b540aSrobert       free (g);
880*404b540aSrobert     }
881*404b540aSrobert 
882*404b540aSrobert 
883*404b540aSrobert   free (get_function_ann (fn->decl)->reference_vars_info);
884*404b540aSrobert   get_function_ann (fn->decl)->reference_vars_info = NULL;
885*404b540aSrobert }
886*404b540aSrobert 
887*404b540aSrobert 
888*404b540aSrobert /* Produce the global information by preforming a transitive closure
889*404b540aSrobert    on the local information that was produced by ipa_analyze_function
890*404b540aSrobert    and ipa_analyze_variable.  */
891*404b540aSrobert 
892*404b540aSrobert static unsigned int
static_execute(void)893*404b540aSrobert static_execute (void)
894*404b540aSrobert {
895*404b540aSrobert   struct cgraph_node *node;
896*404b540aSrobert   struct cgraph_varpool_node *vnode;
897*404b540aSrobert   struct cgraph_node *w;
898*404b540aSrobert   struct cgraph_node **order =
899*404b540aSrobert     xcalloc (cgraph_n_nodes, sizeof (struct cgraph_node *));
900*404b540aSrobert   int order_pos = order_pos = ipa_utils_reduced_inorder (order, false, true);
901*404b540aSrobert   int i;
902*404b540aSrobert 
903*404b540aSrobert   ipa_init ();
904*404b540aSrobert 
905*404b540aSrobert   /* Process all of the variables first.  */
906*404b540aSrobert   for (vnode = cgraph_varpool_nodes_queue; vnode; vnode = vnode->next_needed)
907*404b540aSrobert     analyze_variable (vnode);
908*404b540aSrobert 
909*404b540aSrobert   /* Process all of the functions next.
910*404b540aSrobert 
911*404b540aSrobert      We do not want to process any of the clones so we check that this
912*404b540aSrobert      is a master clone.  However, we do need to process any
913*404b540aSrobert      AVAIL_OVERWRITABLE functions (these are never clones) because
914*404b540aSrobert      they may cause a static variable to escape.  The code that can
915*404b540aSrobert      overwrite such a function cannot access the statics because it
916*404b540aSrobert      would not be in the same compilation unit.  When the analysis is
917*404b540aSrobert      finished, the computed information of these AVAIL_OVERWRITABLE is
918*404b540aSrobert      replaced with worst case info.
919*404b540aSrobert   */
920*404b540aSrobert   for (node = cgraph_nodes; node; node = node->next)
921*404b540aSrobert     if (node->analyzed
922*404b540aSrobert 	&& (cgraph_is_master_clone (node)
923*404b540aSrobert 	    || (cgraph_function_body_availability (node)
924*404b540aSrobert 		== AVAIL_OVERWRITABLE)))
925*404b540aSrobert       analyze_function (node);
926*404b540aSrobert 
927*404b540aSrobert   pointer_set_destroy (visited_nodes);
928*404b540aSrobert   visited_nodes = NULL;
929*404b540aSrobert   if (dump_file)
930*404b540aSrobert     dump_cgraph (dump_file);
931*404b540aSrobert 
932*404b540aSrobert   /* Prune out the variables that were found to behave badly
933*404b540aSrobert      (i.e. have their address taken).  */
934*404b540aSrobert   {
935*404b540aSrobert     unsigned int index;
936*404b540aSrobert     bitmap_iterator bi;
937*404b540aSrobert     bitmap module_statics_readonly = BITMAP_ALLOC (&ipa_obstack);
938*404b540aSrobert     bitmap module_statics_const = BITMAP_ALLOC (&ipa_obstack);
939*404b540aSrobert     bitmap bm_temp = BITMAP_ALLOC (&ipa_obstack);
940*404b540aSrobert 
941*404b540aSrobert     EXECUTE_IF_SET_IN_BITMAP (module_statics_escape, 0, index, bi)
942*404b540aSrobert       {
943*404b540aSrobert 	splay_tree_remove (reference_vars_to_consider, index);
944*404b540aSrobert       }
945*404b540aSrobert 
946*404b540aSrobert     bitmap_and_compl_into (all_module_statics,
947*404b540aSrobert 			   module_statics_escape);
948*404b540aSrobert 
949*404b540aSrobert     bitmap_and_compl (module_statics_readonly, all_module_statics,
950*404b540aSrobert 		      module_statics_written);
951*404b540aSrobert 
952*404b540aSrobert     /* If the address is not taken, we can unset the addressable bit
953*404b540aSrobert        on this variable.  */
954*404b540aSrobert     EXECUTE_IF_SET_IN_BITMAP (all_module_statics, 0, index, bi)
955*404b540aSrobert       {
956*404b540aSrobert 	tree var = get_static_decl (index);
957*404b540aSrobert  	TREE_ADDRESSABLE (var) = 0;
958*404b540aSrobert 	if (dump_file)
959*404b540aSrobert 	  fprintf (dump_file, "Not TREE_ADDRESSABLE var %s\n",
960*404b540aSrobert 		   get_static_name (index));
961*404b540aSrobert       }
962*404b540aSrobert 
963*404b540aSrobert     /* If the variable is never written, we can set the TREE_READONLY
964*404b540aSrobert        flag.  Additionally if it has a DECL_INITIAL that is made up of
965*404b540aSrobert        constants we can treat the entire global as a constant.  */
966*404b540aSrobert 
967*404b540aSrobert     bitmap_and_compl (module_statics_readonly, all_module_statics,
968*404b540aSrobert 		      module_statics_written);
969*404b540aSrobert     EXECUTE_IF_SET_IN_BITMAP (module_statics_readonly, 0, index, bi)
970*404b540aSrobert       {
971*404b540aSrobert 	tree var = get_static_decl (index);
972*404b540aSrobert 
973*404b540aSrobert 	/* Readonly on a function decl is very different from the
974*404b540aSrobert 	   variable.  */
975*404b540aSrobert 	if (TREE_CODE (var) == FUNCTION_DECL)
976*404b540aSrobert 	  continue;
977*404b540aSrobert 
978*404b540aSrobert 	/* Ignore variables in named sections - changing TREE_READONLY
979*404b540aSrobert 	   changes the section flags, potentially causing conflicts with
980*404b540aSrobert 	   other variables in the same named section.  */
981*404b540aSrobert 	if (DECL_SECTION_NAME (var) == NULL_TREE)
982*404b540aSrobert 	  {
983*404b540aSrobert 	    TREE_READONLY (var) = 1;
984*404b540aSrobert 	    if (dump_file)
985*404b540aSrobert 	      fprintf (dump_file, "read-only var %s\n",
986*404b540aSrobert 		       get_static_name (index));
987*404b540aSrobert 	  }
988*404b540aSrobert 	if (DECL_INITIAL (var)
989*404b540aSrobert 	    && is_gimple_min_invariant (DECL_INITIAL (var)))
990*404b540aSrobert 	  {
991*404b540aSrobert  	    bitmap_set_bit (module_statics_const, index);
992*404b540aSrobert 	    if (dump_file)
993*404b540aSrobert 	      fprintf (dump_file, "read-only constant %s\n",
994*404b540aSrobert 		       get_static_name (index));
995*404b540aSrobert 	  }
996*404b540aSrobert       }
997*404b540aSrobert 
998*404b540aSrobert     BITMAP_FREE(module_statics_escape);
999*404b540aSrobert     BITMAP_FREE(module_statics_written);
1000*404b540aSrobert 
1001*404b540aSrobert     if (dump_file)
1002*404b540aSrobert       EXECUTE_IF_SET_IN_BITMAP (all_module_statics, 0, index, bi)
1003*404b540aSrobert 	{
1004*404b540aSrobert 	  fprintf (dump_file, "\nPromotable global:%s",
1005*404b540aSrobert 		   get_static_name (index));
1006*404b540aSrobert 	}
1007*404b540aSrobert 
1008*404b540aSrobert     for (i = 0; i < order_pos; i++ )
1009*404b540aSrobert       {
1010*404b540aSrobert 	ipa_reference_local_vars_info_t l;
1011*404b540aSrobert 	node = order[i];
1012*404b540aSrobert 	l = get_reference_vars_info_from_cgraph (node)->local;
1013*404b540aSrobert 
1014*404b540aSrobert 	/* Any variables that are not in all_module_statics are
1015*404b540aSrobert 	   removed from the local maps.  This will include all of the
1016*404b540aSrobert 	   variables that were found to escape in the function
1017*404b540aSrobert 	   scanning.  */
1018*404b540aSrobert 	bitmap_and_into (l->statics_read,
1019*404b540aSrobert 		         all_module_statics);
1020*404b540aSrobert 	bitmap_and_into (l->statics_written,
1021*404b540aSrobert 		         all_module_statics);
1022*404b540aSrobert       }
1023*404b540aSrobert 
1024*404b540aSrobert     BITMAP_FREE(module_statics_readonly);
1025*404b540aSrobert     BITMAP_FREE(module_statics_const);
1026*404b540aSrobert     BITMAP_FREE(bm_temp);
1027*404b540aSrobert   }
1028*404b540aSrobert 
1029*404b540aSrobert   if (dump_file)
1030*404b540aSrobert     {
1031*404b540aSrobert       for (i = 0; i < order_pos; i++ )
1032*404b540aSrobert 	{
1033*404b540aSrobert 	  unsigned int index;
1034*404b540aSrobert 	  ipa_reference_local_vars_info_t l;
1035*404b540aSrobert 	  bitmap_iterator bi;
1036*404b540aSrobert 
1037*404b540aSrobert 	  node = order[i];
1038*404b540aSrobert 	  l = get_reference_vars_info_from_cgraph (node)->local;
1039*404b540aSrobert 	  fprintf (dump_file,
1040*404b540aSrobert 		   "\nFunction name:%s/%i:",
1041*404b540aSrobert 		   cgraph_node_name (node), node->uid);
1042*404b540aSrobert 	  fprintf (dump_file, "\n  locals read: ");
1043*404b540aSrobert 	  EXECUTE_IF_SET_IN_BITMAP (l->statics_read,
1044*404b540aSrobert 				    0, index, bi)
1045*404b540aSrobert 	    {
1046*404b540aSrobert 	      fprintf (dump_file, "%s ",
1047*404b540aSrobert 		       get_static_name (index));
1048*404b540aSrobert 	    }
1049*404b540aSrobert 	  fprintf (dump_file, "\n  locals written: ");
1050*404b540aSrobert 	  EXECUTE_IF_SET_IN_BITMAP (l->statics_written,
1051*404b540aSrobert 				    0, index, bi)
1052*404b540aSrobert 	    {
1053*404b540aSrobert 	      fprintf(dump_file, "%s ",
1054*404b540aSrobert 		      get_static_name (index));
1055*404b540aSrobert 	    }
1056*404b540aSrobert 	}
1057*404b540aSrobert     }
1058*404b540aSrobert 
1059*404b540aSrobert   /* Propagate the local information thru the call graph to produce
1060*404b540aSrobert      the global information.  All the nodes within a cycle will have
1061*404b540aSrobert      the same info so we collapse cycles first.  Then we can do the
1062*404b540aSrobert      propagation in one pass from the leaves to the roots.  */
1063*404b540aSrobert   order_pos = ipa_utils_reduced_inorder (order, true, true);
1064*404b540aSrobert   if (dump_file)
1065*404b540aSrobert     ipa_utils_print_order(dump_file, "reduced", order, order_pos);
1066*404b540aSrobert 
1067*404b540aSrobert   for (i = 0; i < order_pos; i++ )
1068*404b540aSrobert     {
1069*404b540aSrobert       ipa_reference_vars_info_t node_info;
1070*404b540aSrobert       ipa_reference_global_vars_info_t node_g =
1071*404b540aSrobert 	xcalloc (1, sizeof (struct ipa_reference_global_vars_info_d));
1072*404b540aSrobert       ipa_reference_local_vars_info_t node_l;
1073*404b540aSrobert 
1074*404b540aSrobert       bool read_all;
1075*404b540aSrobert       bool write_all;
1076*404b540aSrobert       struct ipa_dfs_info * w_info;
1077*404b540aSrobert 
1078*404b540aSrobert       node = order[i];
1079*404b540aSrobert       node_info = get_reference_vars_info_from_cgraph (node);
1080*404b540aSrobert       if (!node_info)
1081*404b540aSrobert 	{
1082*404b540aSrobert 	  dump_cgraph_node (stderr, node);
1083*404b540aSrobert 	  dump_cgraph (stderr);
1084*404b540aSrobert 	  gcc_unreachable ();
1085*404b540aSrobert 	}
1086*404b540aSrobert 
1087*404b540aSrobert       node_info->global = node_g;
1088*404b540aSrobert       node_l = node_info->local;
1089*404b540aSrobert 
1090*404b540aSrobert       read_all = node_l->calls_read_all;
1091*404b540aSrobert       write_all = node_l->calls_write_all;
1092*404b540aSrobert 
1093*404b540aSrobert       /* If any node in a cycle is calls_read_all or calls_write_all
1094*404b540aSrobert 	 they all are. */
1095*404b540aSrobert       w_info = node->aux;
1096*404b540aSrobert       w = w_info->next_cycle;
1097*404b540aSrobert       while (w)
1098*404b540aSrobert 	{
1099*404b540aSrobert 	  ipa_reference_local_vars_info_t w_l =
1100*404b540aSrobert 	    get_reference_vars_info_from_cgraph (w)->local;
1101*404b540aSrobert 	  read_all |= w_l->calls_read_all;
1102*404b540aSrobert 	  write_all |= w_l->calls_write_all;
1103*404b540aSrobert 
1104*404b540aSrobert 	  w_info = w->aux;
1105*404b540aSrobert 	  w = w_info->next_cycle;
1106*404b540aSrobert 	}
1107*404b540aSrobert 
1108*404b540aSrobert       /* Initialized the bitmaps for the reduced nodes */
1109*404b540aSrobert       if (read_all)
1110*404b540aSrobert 	node_g->statics_read = all_module_statics;
1111*404b540aSrobert       else
1112*404b540aSrobert 	{
1113*404b540aSrobert 	  node_g->statics_read = BITMAP_ALLOC (&ipa_obstack);
1114*404b540aSrobert 	  bitmap_copy (node_g->statics_read,
1115*404b540aSrobert 		       node_l->statics_read);
1116*404b540aSrobert 	}
1117*404b540aSrobert 
1118*404b540aSrobert       if (write_all)
1119*404b540aSrobert 	node_g->statics_written = all_module_statics;
1120*404b540aSrobert       else
1121*404b540aSrobert 	{
1122*404b540aSrobert 	  node_g->statics_written = BITMAP_ALLOC (&ipa_obstack);
1123*404b540aSrobert 	  bitmap_copy (node_g->statics_written,
1124*404b540aSrobert 		       node_l->statics_written);
1125*404b540aSrobert 	}
1126*404b540aSrobert 
1127*404b540aSrobert       w_info = node->aux;
1128*404b540aSrobert       w = w_info->next_cycle;
1129*404b540aSrobert       while (w)
1130*404b540aSrobert 	{
1131*404b540aSrobert 	  ipa_reference_vars_info_t w_ri =
1132*404b540aSrobert 	    get_reference_vars_info_from_cgraph (w);
1133*404b540aSrobert 	  ipa_reference_local_vars_info_t w_l = w_ri->local;
1134*404b540aSrobert 
1135*404b540aSrobert 	  /* All nodes within a cycle share the same global info bitmaps.  */
1136*404b540aSrobert 	  w_ri->global = node_g;
1137*404b540aSrobert 
1138*404b540aSrobert 	  /* These global bitmaps are initialized from the local info
1139*404b540aSrobert 	     of all of the nodes in the region.  However there is no
1140*404b540aSrobert 	     need to do any work if the bitmaps were set to
1141*404b540aSrobert 	     all_module_statics.  */
1142*404b540aSrobert 	  if (!read_all)
1143*404b540aSrobert 	    bitmap_ior_into (node_g->statics_read,
1144*404b540aSrobert 			     w_l->statics_read);
1145*404b540aSrobert 	  if (!write_all)
1146*404b540aSrobert 	    bitmap_ior_into (node_g->statics_written,
1147*404b540aSrobert 			     w_l->statics_written);
1148*404b540aSrobert 	  w_info = w->aux;
1149*404b540aSrobert 	  w = w_info->next_cycle;
1150*404b540aSrobert 	}
1151*404b540aSrobert 
1152*404b540aSrobert       w = node;
1153*404b540aSrobert       while (w)
1154*404b540aSrobert 	{
1155*404b540aSrobert 	  propagate_bits (w);
1156*404b540aSrobert 	  w_info = w->aux;
1157*404b540aSrobert 	  w = w_info->next_cycle;
1158*404b540aSrobert 	}
1159*404b540aSrobert     }
1160*404b540aSrobert 
1161*404b540aSrobert   /* Need to fix up the local information sets.  The information that
1162*404b540aSrobert      has been gathered so far is preinlining.  However, the
1163*404b540aSrobert      compilation will progress post inlining so the local sets for the
1164*404b540aSrobert      inlined calls need to be merged into the callers.  Note that the
1165*404b540aSrobert      local sets are not shared between all of the nodes in a cycle so
1166*404b540aSrobert      those nodes in the cycle must be processed explicitly.  */
1167*404b540aSrobert   for (i = 0; i < order_pos; i++ )
1168*404b540aSrobert     {
1169*404b540aSrobert       struct ipa_dfs_info * w_info;
1170*404b540aSrobert       node = order[i];
1171*404b540aSrobert       merge_callee_local_info (node, node);
1172*404b540aSrobert 
1173*404b540aSrobert       w_info = node->aux;
1174*404b540aSrobert       w = w_info->next_cycle;
1175*404b540aSrobert       while (w)
1176*404b540aSrobert 	{
1177*404b540aSrobert 	  merge_callee_local_info (w, w);
1178*404b540aSrobert 	  w_info = w->aux;
1179*404b540aSrobert 	  w = w_info->next_cycle;
1180*404b540aSrobert 	}
1181*404b540aSrobert     }
1182*404b540aSrobert 
1183*404b540aSrobert   if (dump_file)
1184*404b540aSrobert     {
1185*404b540aSrobert       for (i = 0; i < order_pos; i++ )
1186*404b540aSrobert 	{
1187*404b540aSrobert 	  ipa_reference_vars_info_t node_info;
1188*404b540aSrobert 	  ipa_reference_global_vars_info_t node_g;
1189*404b540aSrobert 	  ipa_reference_local_vars_info_t node_l;
1190*404b540aSrobert 	  unsigned int index;
1191*404b540aSrobert 	  bitmap_iterator bi;
1192*404b540aSrobert 	  struct ipa_dfs_info * w_info;
1193*404b540aSrobert 
1194*404b540aSrobert 	  node = order[i];
1195*404b540aSrobert 	  node_info = get_reference_vars_info_from_cgraph (node);
1196*404b540aSrobert 	  node_g = node_info->global;
1197*404b540aSrobert 	  node_l = node_info->local;
1198*404b540aSrobert 	  fprintf (dump_file,
1199*404b540aSrobert 		   "\nFunction name:%s/%i:",
1200*404b540aSrobert 		   cgraph_node_name (node), node->uid);
1201*404b540aSrobert 	  fprintf (dump_file, "\n  locals read: ");
1202*404b540aSrobert 	  EXECUTE_IF_SET_IN_BITMAP (node_l->statics_read,
1203*404b540aSrobert 				    0, index, bi)
1204*404b540aSrobert 	    {
1205*404b540aSrobert 	      fprintf (dump_file, "%s ",
1206*404b540aSrobert 		       get_static_name (index));
1207*404b540aSrobert 	    }
1208*404b540aSrobert 	  fprintf (dump_file, "\n  locals written: ");
1209*404b540aSrobert 	  EXECUTE_IF_SET_IN_BITMAP (node_l->statics_written,
1210*404b540aSrobert 				    0, index, bi)
1211*404b540aSrobert 	    {
1212*404b540aSrobert 	      fprintf(dump_file, "%s ",
1213*404b540aSrobert 		      get_static_name (index));
1214*404b540aSrobert 	    }
1215*404b540aSrobert 
1216*404b540aSrobert 	  w_info = node->aux;
1217*404b540aSrobert 	  w = w_info->next_cycle;
1218*404b540aSrobert 	  while (w)
1219*404b540aSrobert 	    {
1220*404b540aSrobert 	      ipa_reference_vars_info_t w_ri =
1221*404b540aSrobert 		get_reference_vars_info_from_cgraph (w);
1222*404b540aSrobert 	      ipa_reference_local_vars_info_t w_l = w_ri->local;
1223*404b540aSrobert 	      fprintf (dump_file, "\n  next cycle: %s/%i ",
1224*404b540aSrobert 		       cgraph_node_name (w), w->uid);
1225*404b540aSrobert  	      fprintf (dump_file, "\n    locals read: ");
1226*404b540aSrobert 	      EXECUTE_IF_SET_IN_BITMAP (w_l->statics_read,
1227*404b540aSrobert 					0, index, bi)
1228*404b540aSrobert 		{
1229*404b540aSrobert 		  fprintf (dump_file, "%s ",
1230*404b540aSrobert 			   get_static_name (index));
1231*404b540aSrobert 		}
1232*404b540aSrobert 
1233*404b540aSrobert 	      fprintf (dump_file, "\n    locals written: ");
1234*404b540aSrobert 	      EXECUTE_IF_SET_IN_BITMAP (w_l->statics_written,
1235*404b540aSrobert 					0, index, bi)
1236*404b540aSrobert 		{
1237*404b540aSrobert 		  fprintf(dump_file, "%s ",
1238*404b540aSrobert 			  get_static_name (index));
1239*404b540aSrobert 		}
1240*404b540aSrobert 
1241*404b540aSrobert 
1242*404b540aSrobert 	      w_info = w->aux;
1243*404b540aSrobert 	      w = w_info->next_cycle;
1244*404b540aSrobert 	    }
1245*404b540aSrobert 	  fprintf (dump_file, "\n  globals read: ");
1246*404b540aSrobert 	  EXECUTE_IF_SET_IN_BITMAP (node_g->statics_read,
1247*404b540aSrobert 				    0, index, bi)
1248*404b540aSrobert 	    {
1249*404b540aSrobert 	      fprintf (dump_file, "%s ",
1250*404b540aSrobert 		       get_static_name (index));
1251*404b540aSrobert 	    }
1252*404b540aSrobert 	  fprintf (dump_file, "\n  globals written: ");
1253*404b540aSrobert 	  EXECUTE_IF_SET_IN_BITMAP (node_g->statics_written,
1254*404b540aSrobert 				    0, index, bi)
1255*404b540aSrobert 	    {
1256*404b540aSrobert 	      fprintf (dump_file, "%s ",
1257*404b540aSrobert 		       get_static_name (index));
1258*404b540aSrobert 	    }
1259*404b540aSrobert 	}
1260*404b540aSrobert     }
1261*404b540aSrobert 
1262*404b540aSrobert   /* Cleanup. */
1263*404b540aSrobert   for (i = 0; i < order_pos; i++ )
1264*404b540aSrobert     {
1265*404b540aSrobert       ipa_reference_vars_info_t node_info;
1266*404b540aSrobert       ipa_reference_global_vars_info_t node_g;
1267*404b540aSrobert       node = order[i];
1268*404b540aSrobert       node_info = get_reference_vars_info_from_cgraph (node);
1269*404b540aSrobert       node_g = node_info->global;
1270*404b540aSrobert 
1271*404b540aSrobert       /* Create the complimentary sets.  These are more useful for
1272*404b540aSrobert 	 certain apis.  */
1273*404b540aSrobert       node_g->statics_not_read = BITMAP_ALLOC (&ipa_obstack);
1274*404b540aSrobert       node_g->statics_not_written = BITMAP_ALLOC (&ipa_obstack);
1275*404b540aSrobert 
1276*404b540aSrobert       if (node_g->statics_read != all_module_statics)
1277*404b540aSrobert 	{
1278*404b540aSrobert 	  bitmap_and_compl (node_g->statics_not_read,
1279*404b540aSrobert 			    all_module_statics,
1280*404b540aSrobert 			    node_g->statics_read);
1281*404b540aSrobert 	}
1282*404b540aSrobert 
1283*404b540aSrobert       if (node_g->statics_written
1284*404b540aSrobert 	  != all_module_statics)
1285*404b540aSrobert 	bitmap_and_compl (node_g->statics_not_written,
1286*404b540aSrobert 			  all_module_statics,
1287*404b540aSrobert 			  node_g->statics_written);
1288*404b540aSrobert    }
1289*404b540aSrobert 
1290*404b540aSrobert   free (order);
1291*404b540aSrobert 
1292*404b540aSrobert   for (node = cgraph_nodes; node; node = node->next)
1293*404b540aSrobert     {
1294*404b540aSrobert       /* Get rid of the aux information.  */
1295*404b540aSrobert 
1296*404b540aSrobert       if (node->aux)
1297*404b540aSrobert 	{
1298*404b540aSrobert 	  free (node->aux);
1299*404b540aSrobert 	  node->aux = NULL;
1300*404b540aSrobert 	}
1301*404b540aSrobert 
1302*404b540aSrobert       if (node->analyzed
1303*404b540aSrobert 	  && (cgraph_function_body_availability (node) == AVAIL_OVERWRITABLE))
1304*404b540aSrobert 	clean_function (node);
1305*404b540aSrobert     }
1306*404b540aSrobert   return 0;
1307*404b540aSrobert }
1308*404b540aSrobert 
1309*404b540aSrobert 
1310*404b540aSrobert static bool
gate_reference(void)1311*404b540aSrobert gate_reference (void)
1312*404b540aSrobert {
1313*404b540aSrobert   return (flag_unit_at_a_time != 0  && flag_ipa_reference
1314*404b540aSrobert 	  /* Don't bother doing anything if the program has errors.  */
1315*404b540aSrobert 	  && !(errorcount || sorrycount));
1316*404b540aSrobert }
1317*404b540aSrobert 
1318*404b540aSrobert struct tree_opt_pass pass_ipa_reference =
1319*404b540aSrobert {
1320*404b540aSrobert   "static-var",				/* name */
1321*404b540aSrobert   gate_reference,			/* gate */
1322*404b540aSrobert   static_execute,			/* execute */
1323*404b540aSrobert   NULL,					/* sub */
1324*404b540aSrobert   NULL,					/* next */
1325*404b540aSrobert   0,					/* static_pass_number */
1326*404b540aSrobert   TV_IPA_REFERENCE,		        /* tv_id */
1327*404b540aSrobert   0,	                                /* properties_required */
1328*404b540aSrobert   0,					/* properties_provided */
1329*404b540aSrobert   0,					/* properties_destroyed */
1330*404b540aSrobert   0,					/* todo_flags_start */
1331*404b540aSrobert   0,                                    /* todo_flags_finish */
1332*404b540aSrobert   0					/* letter */
1333*404b540aSrobert };
1334*404b540aSrobert 
1335*404b540aSrobert #include "gt-ipa-reference.h"
1336*404b540aSrobert 
1337