xref: /openbsd/gnu/usr.bin/gcc/gcc/ra-rewrite.c (revision c87b03e5)
1*c87b03e5Sespie /* Graph coloring register allocator
2*c87b03e5Sespie    Copyright (C) 2001, 2002 Free Software Foundation, Inc.
3*c87b03e5Sespie    Contributed by Michael Matz <matz@suse.de>
4*c87b03e5Sespie    and Daniel Berlin <dan@cgsoftware.com>.
5*c87b03e5Sespie 
6*c87b03e5Sespie    This file is part of GCC.
7*c87b03e5Sespie 
8*c87b03e5Sespie    GCC is free software; you can redistribute it and/or modify it under the
9*c87b03e5Sespie    terms of the GNU General Public License as published by the Free Software
10*c87b03e5Sespie    Foundation; either version 2, or (at your option) any later version.
11*c87b03e5Sespie 
12*c87b03e5Sespie    GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13*c87b03e5Sespie    WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
14*c87b03e5Sespie    FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
15*c87b03e5Sespie    details.
16*c87b03e5Sespie 
17*c87b03e5Sespie    You should have received a copy of the GNU General Public License along
18*c87b03e5Sespie    with GCC; see the file COPYING.  If not, write to the Free Software
19*c87b03e5Sespie    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
20*c87b03e5Sespie 
21*c87b03e5Sespie #include "config.h"
22*c87b03e5Sespie #include "system.h"
23*c87b03e5Sespie #include "rtl.h"
24*c87b03e5Sespie #include "tm_p.h"
25*c87b03e5Sespie #include "function.h"
26*c87b03e5Sespie #include "regs.h"
27*c87b03e5Sespie #include "hard-reg-set.h"
28*c87b03e5Sespie #include "basic-block.h"
29*c87b03e5Sespie #include "df.h"
30*c87b03e5Sespie #include "expr.h"
31*c87b03e5Sespie #include "output.h"
32*c87b03e5Sespie #include "except.h"
33*c87b03e5Sespie #include "ra.h"
34*c87b03e5Sespie #include "insn-config.h"
35*c87b03e5Sespie #include "reload.h"
36*c87b03e5Sespie 
37*c87b03e5Sespie /* This file is part of the graph coloring register allocator, and
38*c87b03e5Sespie    contains the functions to change the insn stream.  I.e. it adds
39*c87b03e5Sespie    spill code, rewrites insns to use the new registers after
40*c87b03e5Sespie    coloring and deletes coalesced moves.  */
41*c87b03e5Sespie 
42*c87b03e5Sespie struct rewrite_info;
43*c87b03e5Sespie struct rtx_list;
44*c87b03e5Sespie 
45*c87b03e5Sespie static void spill_coalescing PARAMS ((sbitmap, sbitmap));
46*c87b03e5Sespie static unsigned HOST_WIDE_INT spill_prop_savings PARAMS ((struct web *,
47*c87b03e5Sespie 							  sbitmap));
48*c87b03e5Sespie static void spill_prop_insert PARAMS ((struct web *, sbitmap, sbitmap));
49*c87b03e5Sespie static int spill_propagation PARAMS ((sbitmap, sbitmap, sbitmap));
50*c87b03e5Sespie static void spill_coalprop PARAMS ((void));
51*c87b03e5Sespie static void allocate_spill_web PARAMS ((struct web *));
52*c87b03e5Sespie static void choose_spill_colors PARAMS ((void));
53*c87b03e5Sespie static void rewrite_program PARAMS ((bitmap));
54*c87b03e5Sespie static void remember_slot PARAMS ((struct rtx_list **, rtx));
55*c87b03e5Sespie static int slots_overlap_p PARAMS ((rtx, rtx));
56*c87b03e5Sespie static void delete_overlapping_slots PARAMS ((struct rtx_list **, rtx));
57*c87b03e5Sespie static int slot_member_p PARAMS ((struct rtx_list *, rtx));
58*c87b03e5Sespie static void insert_stores PARAMS ((bitmap));
59*c87b03e5Sespie static int spill_same_color_p PARAMS ((struct web *, struct web *));
60*c87b03e5Sespie static bool is_partly_live_1 PARAMS ((sbitmap, struct web *));
61*c87b03e5Sespie static void update_spill_colors PARAMS ((HARD_REG_SET *, struct web *, int));
62*c87b03e5Sespie static int spill_is_free PARAMS ((HARD_REG_SET *, struct web *));
63*c87b03e5Sespie static void emit_loads PARAMS ((struct rewrite_info *, int, rtx));
64*c87b03e5Sespie static void reloads_to_loads PARAMS ((struct rewrite_info *, struct ref **,
65*c87b03e5Sespie 				      unsigned int, struct web **));
66*c87b03e5Sespie static void rewrite_program2 PARAMS ((bitmap));
67*c87b03e5Sespie static void mark_refs_for_checking PARAMS ((struct web *, bitmap));
68*c87b03e5Sespie static void detect_web_parts_to_rebuild PARAMS ((void));
69*c87b03e5Sespie static void delete_useless_defs PARAMS ((void));
70*c87b03e5Sespie static void detect_non_changed_webs PARAMS ((void));
71*c87b03e5Sespie static void reset_changed_flag PARAMS ((void));
72*c87b03e5Sespie 
73*c87b03e5Sespie /* For tracking some statistics, we count the number (and cost)
74*c87b03e5Sespie    of deleted move insns.  */
75*c87b03e5Sespie static unsigned int deleted_move_insns;
76*c87b03e5Sespie static unsigned HOST_WIDE_INT deleted_move_cost;
77*c87b03e5Sespie 
78*c87b03e5Sespie /* This is the spill coalescing phase.  In SPILLED the IDs of all
79*c87b03e5Sespie    already spilled webs are noted.  In COALESCED the IDs of webs still
80*c87b03e5Sespie    to check for coalescing.  This tries to coalesce two webs, which were
81*c87b03e5Sespie    spilled, are connected by a move, and don't conflict.  Greatly
82*c87b03e5Sespie    reduces memory shuffling.  */
83*c87b03e5Sespie 
84*c87b03e5Sespie static void
spill_coalescing(coalesce,spilled)85*c87b03e5Sespie spill_coalescing (coalesce, spilled)
86*c87b03e5Sespie      sbitmap coalesce, spilled;
87*c87b03e5Sespie {
88*c87b03e5Sespie   struct move_list *ml;
89*c87b03e5Sespie   struct move *m;
90*c87b03e5Sespie   for (ml = wl_moves; ml; ml = ml->next)
91*c87b03e5Sespie     if ((m = ml->move) != NULL)
92*c87b03e5Sespie       {
93*c87b03e5Sespie 	struct web *s = alias (m->source_web);
94*c87b03e5Sespie 	struct web *t = alias (m->target_web);
95*c87b03e5Sespie 	if ((TEST_BIT (spilled, s->id) && TEST_BIT (coalesce, t->id))
96*c87b03e5Sespie 	    || (TEST_BIT (spilled, t->id) && TEST_BIT (coalesce, s->id)))
97*c87b03e5Sespie 	  {
98*c87b03e5Sespie 	    struct conflict_link *wl;
99*c87b03e5Sespie 	    if (TEST_BIT (sup_igraph, s->id * num_webs + t->id)
100*c87b03e5Sespie 		|| TEST_BIT (sup_igraph, t->id * num_webs + s->id)
101*c87b03e5Sespie 		|| s->pattern || t->pattern)
102*c87b03e5Sespie 	      continue;
103*c87b03e5Sespie 
104*c87b03e5Sespie 	    deleted_move_insns++;
105*c87b03e5Sespie 	    deleted_move_cost += BLOCK_FOR_INSN (m->insn)->frequency + 1;
106*c87b03e5Sespie 	    PUT_CODE (m->insn, NOTE);
107*c87b03e5Sespie 	    NOTE_LINE_NUMBER (m->insn) = NOTE_INSN_DELETED;
108*c87b03e5Sespie 	    df_insn_modify (df, BLOCK_FOR_INSN (m->insn), m->insn);
109*c87b03e5Sespie 
110*c87b03e5Sespie 	    m->target_web->target_of_spilled_move = 1;
111*c87b03e5Sespie 	    if (s == t)
112*c87b03e5Sespie 	      /* May be, already coalesced due to a former move.  */
113*c87b03e5Sespie 	      continue;
114*c87b03e5Sespie 	    /* Merge the nodes S and T in the I-graph.  Beware: the merging
115*c87b03e5Sespie 	       of conflicts relies on the fact, that in the conflict list
116*c87b03e5Sespie 	       of T all of it's conflicts are noted.  This is currently not
117*c87b03e5Sespie 	       the case if T would be the target of a coalesced web, because
118*c87b03e5Sespie 	       then (in combine () above) only those conflicts were noted in
119*c87b03e5Sespie 	       T from the web which was coalesced into T, which at the time
120*c87b03e5Sespie 	       of combine() were not already on the SELECT stack or were
121*c87b03e5Sespie 	       itself coalesced to something other.  */
122*c87b03e5Sespie 	    if (t->type != SPILLED || s->type != SPILLED)
123*c87b03e5Sespie 	      abort ();
124*c87b03e5Sespie 	    remove_list (t->dlink, &WEBS(SPILLED));
125*c87b03e5Sespie 	    put_web (t, COALESCED);
126*c87b03e5Sespie 	    t->alias = s;
127*c87b03e5Sespie 	    s->is_coalesced = 1;
128*c87b03e5Sespie 	    t->is_coalesced = 1;
129*c87b03e5Sespie 	    merge_moves (s, t);
130*c87b03e5Sespie 	    for (wl = t->conflict_list; wl; wl = wl->next)
131*c87b03e5Sespie 	      {
132*c87b03e5Sespie 		struct web *pweb = wl->t;
133*c87b03e5Sespie 		if (wl->sub == NULL)
134*c87b03e5Sespie 		  record_conflict (s, pweb);
135*c87b03e5Sespie 		else
136*c87b03e5Sespie 		  {
137*c87b03e5Sespie 		    struct sub_conflict *sl;
138*c87b03e5Sespie 		    for (sl = wl->sub; sl; sl = sl->next)
139*c87b03e5Sespie 		      {
140*c87b03e5Sespie 			struct web *sweb = NULL;
141*c87b03e5Sespie 			if (SUBWEB_P (sl->s))
142*c87b03e5Sespie 			  sweb = find_subweb (s, sl->s->orig_x);
143*c87b03e5Sespie 			if (!sweb)
144*c87b03e5Sespie 			  sweb = s;
145*c87b03e5Sespie 			record_conflict (sweb, sl->t);
146*c87b03e5Sespie 		      }
147*c87b03e5Sespie 		  }
148*c87b03e5Sespie 		/* No decrement_degree here, because we already have colored
149*c87b03e5Sespie 		   the graph, and don't want to insert pweb into any other
150*c87b03e5Sespie 		   list.  */
151*c87b03e5Sespie 		pweb->num_conflicts -= 1 + t->add_hardregs;
152*c87b03e5Sespie 	      }
153*c87b03e5Sespie 	  }
154*c87b03e5Sespie       }
155*c87b03e5Sespie }
156*c87b03e5Sespie 
157*c87b03e5Sespie /* Returns the probable saving of coalescing WEB with webs from
158*c87b03e5Sespie    SPILLED, in terms of removed move insn cost.  */
159*c87b03e5Sespie 
160*c87b03e5Sespie static unsigned HOST_WIDE_INT
spill_prop_savings(web,spilled)161*c87b03e5Sespie spill_prop_savings (web, spilled)
162*c87b03e5Sespie      struct web *web;
163*c87b03e5Sespie      sbitmap spilled;
164*c87b03e5Sespie {
165*c87b03e5Sespie   unsigned HOST_WIDE_INT savings = 0;
166*c87b03e5Sespie   struct move_list *ml;
167*c87b03e5Sespie   struct move *m;
168*c87b03e5Sespie   unsigned int cost;
169*c87b03e5Sespie   if (web->pattern)
170*c87b03e5Sespie     return 0;
171*c87b03e5Sespie   cost = 1 + MEMORY_MOVE_COST (GET_MODE (web->orig_x), web->regclass, 1);
172*c87b03e5Sespie   cost += 1 + MEMORY_MOVE_COST (GET_MODE (web->orig_x), web->regclass, 0);
173*c87b03e5Sespie   for (ml = wl_moves; ml; ml = ml->next)
174*c87b03e5Sespie     if ((m = ml->move) != NULL)
175*c87b03e5Sespie       {
176*c87b03e5Sespie 	struct web *s = alias (m->source_web);
177*c87b03e5Sespie 	struct web *t = alias (m->target_web);
178*c87b03e5Sespie 	if (s != web)
179*c87b03e5Sespie 	  {
180*c87b03e5Sespie 	    struct web *h = s;
181*c87b03e5Sespie 	    s = t;
182*c87b03e5Sespie 	    t = h;
183*c87b03e5Sespie 	  }
184*c87b03e5Sespie 	if (s != web || !TEST_BIT (spilled, t->id) || t->pattern
185*c87b03e5Sespie 	    || TEST_BIT (sup_igraph, s->id * num_webs + t->id)
186*c87b03e5Sespie 	    || TEST_BIT (sup_igraph, t->id * num_webs + s->id))
187*c87b03e5Sespie 	  continue;
188*c87b03e5Sespie 	savings += BLOCK_FOR_INSN (m->insn)->frequency * cost;
189*c87b03e5Sespie       }
190*c87b03e5Sespie   return savings;
191*c87b03e5Sespie }
192*c87b03e5Sespie 
193*c87b03e5Sespie /* This add all IDs of colored webs, which are connected to WEB by a move
194*c87b03e5Sespie    to LIST and PROCESSED.  */
195*c87b03e5Sespie 
196*c87b03e5Sespie static void
spill_prop_insert(web,list,processed)197*c87b03e5Sespie spill_prop_insert (web, list, processed)
198*c87b03e5Sespie      struct web *web;
199*c87b03e5Sespie      sbitmap list, processed;
200*c87b03e5Sespie {
201*c87b03e5Sespie   struct move_list *ml;
202*c87b03e5Sespie   struct move *m;
203*c87b03e5Sespie   for (ml = wl_moves; ml; ml = ml->next)
204*c87b03e5Sespie     if ((m = ml->move) != NULL)
205*c87b03e5Sespie       {
206*c87b03e5Sespie 	struct web *s = alias (m->source_web);
207*c87b03e5Sespie 	struct web *t = alias (m->target_web);
208*c87b03e5Sespie 	if (s != web)
209*c87b03e5Sespie 	  {
210*c87b03e5Sespie 	    struct web *h = s;
211*c87b03e5Sespie 	    s = t;
212*c87b03e5Sespie 	    t = h;
213*c87b03e5Sespie 	  }
214*c87b03e5Sespie 	if (s != web || t->type != COLORED || TEST_BIT (processed, t->id))
215*c87b03e5Sespie 	  continue;
216*c87b03e5Sespie 	SET_BIT (list, t->id);
217*c87b03e5Sespie 	SET_BIT (processed, t->id);
218*c87b03e5Sespie       }
219*c87b03e5Sespie }
220*c87b03e5Sespie 
221*c87b03e5Sespie /* The spill propagation pass.  If we have to spilled webs, the first
222*c87b03e5Sespie    connected through a move to a colored one, and the second also connected
223*c87b03e5Sespie    to that colored one, and this colored web is only used to connect both
224*c87b03e5Sespie    spilled webs, it might be worthwhile to spill that colored one.
225*c87b03e5Sespie    This is the case, if the cost of the removed copy insns (all three webs
226*c87b03e5Sespie    could be placed into the same stack slot) is higher than the spill cost
227*c87b03e5Sespie    of the web.
228*c87b03e5Sespie    TO_PROP are the webs we try to propagate from (i.e. spilled ones),
229*c87b03e5Sespie    SPILLED the set of all spilled webs so far and PROCESSED the set
230*c87b03e5Sespie    of all webs processed so far, so we don't do work twice.  */
231*c87b03e5Sespie 
232*c87b03e5Sespie static int
spill_propagation(to_prop,spilled,processed)233*c87b03e5Sespie spill_propagation (to_prop, spilled, processed)
234*c87b03e5Sespie      sbitmap to_prop, spilled, processed;
235*c87b03e5Sespie {
236*c87b03e5Sespie   int id;
237*c87b03e5Sespie   int again = 0;
238*c87b03e5Sespie   sbitmap list = sbitmap_alloc (num_webs);
239*c87b03e5Sespie   sbitmap_zero (list);
240*c87b03e5Sespie 
241*c87b03e5Sespie   /* First insert colored move neighbors into the candidate list.  */
242*c87b03e5Sespie   EXECUTE_IF_SET_IN_SBITMAP (to_prop, 0, id,
243*c87b03e5Sespie     {
244*c87b03e5Sespie       spill_prop_insert (ID2WEB (id), list, processed);
245*c87b03e5Sespie     });
246*c87b03e5Sespie   sbitmap_zero (to_prop);
247*c87b03e5Sespie 
248*c87b03e5Sespie   /* For all candidates, see, if the savings are higher than it's
249*c87b03e5Sespie      spill cost.  */
250*c87b03e5Sespie   while ((id = sbitmap_first_set_bit (list)) >= 0)
251*c87b03e5Sespie     {
252*c87b03e5Sespie       struct web *web = ID2WEB (id);
253*c87b03e5Sespie       RESET_BIT (list, id);
254*c87b03e5Sespie       if (spill_prop_savings (web, spilled) >= web->spill_cost)
255*c87b03e5Sespie 	{
256*c87b03e5Sespie 	  /* If so, we found a new spilled web.  Insert it's colored
257*c87b03e5Sespie 	     move neighbors again, and mark, that we need to repeat the
258*c87b03e5Sespie 	     whole mainloop of spillprog/coalescing again.  */
259*c87b03e5Sespie 	  remove_web_from_list (web);
260*c87b03e5Sespie 	  web->color = -1;
261*c87b03e5Sespie 	  put_web (web, SPILLED);
262*c87b03e5Sespie 	  SET_BIT (spilled, id);
263*c87b03e5Sespie 	  SET_BIT (to_prop, id);
264*c87b03e5Sespie 	  spill_prop_insert (web, list, processed);
265*c87b03e5Sespie 	  again = 1;
266*c87b03e5Sespie 	}
267*c87b03e5Sespie     }
268*c87b03e5Sespie   sbitmap_free (list);
269*c87b03e5Sespie   return again;
270*c87b03e5Sespie }
271*c87b03e5Sespie 
272*c87b03e5Sespie /* The main phase to improve spill costs.  This repeatedly runs
273*c87b03e5Sespie    spill coalescing and spill propagation, until nothing changes.  */
274*c87b03e5Sespie 
275*c87b03e5Sespie static void
spill_coalprop()276*c87b03e5Sespie spill_coalprop ()
277*c87b03e5Sespie {
278*c87b03e5Sespie   sbitmap spilled, processed, to_prop;
279*c87b03e5Sespie   struct dlist *d;
280*c87b03e5Sespie   int again;
281*c87b03e5Sespie   spilled = sbitmap_alloc (num_webs);
282*c87b03e5Sespie   processed = sbitmap_alloc (num_webs);
283*c87b03e5Sespie   to_prop = sbitmap_alloc (num_webs);
284*c87b03e5Sespie   sbitmap_zero (spilled);
285*c87b03e5Sespie   for (d = WEBS(SPILLED); d; d = d->next)
286*c87b03e5Sespie     SET_BIT (spilled, DLIST_WEB (d)->id);
287*c87b03e5Sespie   sbitmap_copy (to_prop, spilled);
288*c87b03e5Sespie   sbitmap_zero (processed);
289*c87b03e5Sespie   do
290*c87b03e5Sespie     {
291*c87b03e5Sespie       spill_coalescing (to_prop, spilled);
292*c87b03e5Sespie       /* XXX Currently (with optimistic coalescing) spill_propagation()
293*c87b03e5Sespie 	 doesn't give better code, sometimes it gives worse (but not by much)
294*c87b03e5Sespie 	 code.  I believe this is because of slightly wrong cost
295*c87b03e5Sespie 	 measurements.  Anyway right now it isn't worth the time it takes,
296*c87b03e5Sespie 	 so deactivate it for now.  */
297*c87b03e5Sespie       again = 0 && spill_propagation (to_prop, spilled, processed);
298*c87b03e5Sespie     }
299*c87b03e5Sespie   while (again);
300*c87b03e5Sespie   sbitmap_free (to_prop);
301*c87b03e5Sespie   sbitmap_free (processed);
302*c87b03e5Sespie   sbitmap_free (spilled);
303*c87b03e5Sespie }
304*c87b03e5Sespie 
305*c87b03e5Sespie /* Allocate a spill slot for a WEB.  Currently we spill to pseudo
306*c87b03e5Sespie    registers, to be able to track also webs for "stack slots", and also
307*c87b03e5Sespie    to possibly colorize them.  These pseudos are sometimes handled
308*c87b03e5Sespie    in a special way, where we know, that they also can represent
309*c87b03e5Sespie    MEM references.  */
310*c87b03e5Sespie 
311*c87b03e5Sespie static void
allocate_spill_web(web)312*c87b03e5Sespie allocate_spill_web (web)
313*c87b03e5Sespie      struct web *web;
314*c87b03e5Sespie {
315*c87b03e5Sespie   int regno = web->regno;
316*c87b03e5Sespie   rtx slot;
317*c87b03e5Sespie   if (web->stack_slot)
318*c87b03e5Sespie     return;
319*c87b03e5Sespie   slot = gen_reg_rtx (PSEUDO_REGNO_MODE (regno));
320*c87b03e5Sespie   web->stack_slot = slot;
321*c87b03e5Sespie }
322*c87b03e5Sespie 
323*c87b03e5Sespie /* This chooses a color for all SPILLED webs for interference region
324*c87b03e5Sespie    spilling.  The heuristic isn't good in any way.  */
325*c87b03e5Sespie 
326*c87b03e5Sespie static void
choose_spill_colors()327*c87b03e5Sespie choose_spill_colors ()
328*c87b03e5Sespie {
329*c87b03e5Sespie   struct dlist *d;
330*c87b03e5Sespie   unsigned HOST_WIDE_INT *costs = (unsigned HOST_WIDE_INT *)
331*c87b03e5Sespie     xmalloc (FIRST_PSEUDO_REGISTER * sizeof (costs[0]));
332*c87b03e5Sespie   for (d = WEBS(SPILLED); d; d = d->next)
333*c87b03e5Sespie     {
334*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
335*c87b03e5Sespie       struct conflict_link *wl;
336*c87b03e5Sespie       int bestc, c;
337*c87b03e5Sespie       HARD_REG_SET avail;
338*c87b03e5Sespie       memset (costs, 0, FIRST_PSEUDO_REGISTER * sizeof (costs[0]));
339*c87b03e5Sespie       for (wl = web->conflict_list; wl; wl = wl->next)
340*c87b03e5Sespie 	{
341*c87b03e5Sespie 	  struct web *pweb = wl->t;
342*c87b03e5Sespie 	  if (pweb->type == COLORED || pweb->type == PRECOLORED)
343*c87b03e5Sespie 	    costs[pweb->color] += pweb->spill_cost;
344*c87b03e5Sespie 	}
345*c87b03e5Sespie 
346*c87b03e5Sespie       COPY_HARD_REG_SET (avail, web->usable_regs);
347*c87b03e5Sespie       if (web->crosses_call)
348*c87b03e5Sespie 	{
349*c87b03e5Sespie 	  /* Add an arbitrary constant cost to colors not usable by
350*c87b03e5Sespie 	     call-crossing webs without saves/loads.  */
351*c87b03e5Sespie 	  for (c = 0; c < FIRST_PSEUDO_REGISTER; c++)
352*c87b03e5Sespie 	    if (TEST_HARD_REG_BIT (call_used_reg_set, c))
353*c87b03e5Sespie 	      costs[c] += 1000;
354*c87b03e5Sespie 	}
355*c87b03e5Sespie       bestc = -1;
356*c87b03e5Sespie       for (c = 0; c < FIRST_PSEUDO_REGISTER; c++)
357*c87b03e5Sespie 	if ((bestc < 0 || costs[bestc] > costs[c])
358*c87b03e5Sespie             && TEST_HARD_REG_BIT (avail, c)
359*c87b03e5Sespie 	    && HARD_REGNO_MODE_OK (c, PSEUDO_REGNO_MODE (web->regno)))
360*c87b03e5Sespie 	  {
361*c87b03e5Sespie 	    int i, size;
362*c87b03e5Sespie 	    size = HARD_REGNO_NREGS (c, PSEUDO_REGNO_MODE (web->regno));
363*c87b03e5Sespie 	    for (i = 1; i < size
364*c87b03e5Sespie 		 && TEST_HARD_REG_BIT (avail, c + i); i++);
365*c87b03e5Sespie 	    if (i == size)
366*c87b03e5Sespie 	      bestc = c;
367*c87b03e5Sespie 	  }
368*c87b03e5Sespie       web->color = bestc;
369*c87b03e5Sespie       ra_debug_msg (DUMP_PROCESS, "choosing color %d for spilled web %d\n",
370*c87b03e5Sespie 		 bestc, web->id);
371*c87b03e5Sespie     }
372*c87b03e5Sespie 
373*c87b03e5Sespie   free (costs);
374*c87b03e5Sespie }
375*c87b03e5Sespie 
376*c87b03e5Sespie /* For statistics sake we count the number and cost of all new loads,
377*c87b03e5Sespie    stores and emitted rematerializations.  */
378*c87b03e5Sespie static unsigned int emitted_spill_loads;
379*c87b03e5Sespie static unsigned int emitted_spill_stores;
380*c87b03e5Sespie static unsigned int emitted_remat;
381*c87b03e5Sespie static unsigned HOST_WIDE_INT spill_load_cost;
382*c87b03e5Sespie static unsigned HOST_WIDE_INT spill_store_cost;
383*c87b03e5Sespie static unsigned HOST_WIDE_INT spill_remat_cost;
384*c87b03e5Sespie 
385*c87b03e5Sespie /* In rewrite_program2() we detect if some def us useless, in the sense,
386*c87b03e5Sespie    that the pseudo set is not live anymore at that point.  The REF_IDs
387*c87b03e5Sespie    of such defs are noted here.  */
388*c87b03e5Sespie static bitmap useless_defs;
389*c87b03e5Sespie 
390*c87b03e5Sespie /* This is the simple and fast version of rewriting the program to
391*c87b03e5Sespie    include spill code.  It spills at every insn containing spilled
392*c87b03e5Sespie    defs or uses.  Loads are added only if flag_ra_spill_every_use is
393*c87b03e5Sespie    nonzero, otherwise only stores will be added.  This doesn't
394*c87b03e5Sespie    support rematerialization.
395*c87b03e5Sespie    NEW_DEATHS is filled with uids for insns, which probably contain
396*c87b03e5Sespie    deaths.  */
397*c87b03e5Sespie 
398*c87b03e5Sespie static void
rewrite_program(new_deaths)399*c87b03e5Sespie rewrite_program (new_deaths)
400*c87b03e5Sespie      bitmap new_deaths;
401*c87b03e5Sespie {
402*c87b03e5Sespie   unsigned int i;
403*c87b03e5Sespie   struct dlist *d;
404*c87b03e5Sespie   bitmap b = BITMAP_XMALLOC ();
405*c87b03e5Sespie 
406*c87b03e5Sespie   /* We walk over all webs, over all uses/defs.  For all webs, we need
407*c87b03e5Sespie      to look at spilled webs, and webs coalesced to spilled ones, in case
408*c87b03e5Sespie      their alias isn't broken up, or they got spill coalesced.  */
409*c87b03e5Sespie   for (i = 0; i < 2; i++)
410*c87b03e5Sespie     for (d = (i == 0) ? WEBS(SPILLED) : WEBS(COALESCED); d; d = d->next)
411*c87b03e5Sespie       {
412*c87b03e5Sespie 	struct web *web = DLIST_WEB (d);
413*c87b03e5Sespie 	struct web *aweb = alias (web);
414*c87b03e5Sespie 	unsigned int j;
415*c87b03e5Sespie 	rtx slot;
416*c87b03e5Sespie 
417*c87b03e5Sespie 	/* Is trivially true for spilled webs, but not for coalesced ones.  */
418*c87b03e5Sespie 	if (aweb->type != SPILLED)
419*c87b03e5Sespie 	  continue;
420*c87b03e5Sespie 
421*c87b03e5Sespie 	/* First add loads before every use, if we have to.  */
422*c87b03e5Sespie 	if (flag_ra_spill_every_use)
423*c87b03e5Sespie 	  {
424*c87b03e5Sespie 	    bitmap_clear (b);
425*c87b03e5Sespie 	    allocate_spill_web (aweb);
426*c87b03e5Sespie 	    slot = aweb->stack_slot;
427*c87b03e5Sespie 	    for (j = 0; j < web->num_uses; j++)
428*c87b03e5Sespie 	      {
429*c87b03e5Sespie 		rtx insns, target, source;
430*c87b03e5Sespie 		rtx insn = DF_REF_INSN (web->uses[j]);
431*c87b03e5Sespie 		rtx prev = PREV_INSN (insn);
432*c87b03e5Sespie 		basic_block bb = BLOCK_FOR_INSN (insn);
433*c87b03e5Sespie 		/* Happens when spill_coalescing() deletes move insns.  */
434*c87b03e5Sespie 		if (!INSN_P (insn))
435*c87b03e5Sespie 		  continue;
436*c87b03e5Sespie 
437*c87b03e5Sespie 		/* Check that we didn't already added a load for this web
438*c87b03e5Sespie 		   and insn.  Happens, when the an insn uses the same web
439*c87b03e5Sespie 		   multiple times.  */
440*c87b03e5Sespie 	        if (bitmap_bit_p (b, INSN_UID (insn)))
441*c87b03e5Sespie 		  continue;
442*c87b03e5Sespie 	        bitmap_set_bit (b, INSN_UID (insn));
443*c87b03e5Sespie 	        target = DF_REF_REG (web->uses[j]);
444*c87b03e5Sespie 	        source = slot;
445*c87b03e5Sespie 		start_sequence ();
446*c87b03e5Sespie 	        if (GET_CODE (target) == SUBREG)
447*c87b03e5Sespie 		  source = simplify_gen_subreg (GET_MODE (target), source,
448*c87b03e5Sespie 						GET_MODE (source),
449*c87b03e5Sespie 						SUBREG_BYTE (target));
450*c87b03e5Sespie 		ra_emit_move_insn (target, source);
451*c87b03e5Sespie 		insns = get_insns ();
452*c87b03e5Sespie 		end_sequence ();
453*c87b03e5Sespie 		emit_insn_before (insns, insn);
454*c87b03e5Sespie 
455*c87b03e5Sespie 	        if (bb->head == insn)
456*c87b03e5Sespie 		  bb->head = NEXT_INSN (prev);
457*c87b03e5Sespie 		for (insn = PREV_INSN (insn); insn != prev;
458*c87b03e5Sespie 		     insn = PREV_INSN (insn))
459*c87b03e5Sespie 		  {
460*c87b03e5Sespie 		    set_block_for_insn (insn, bb);
461*c87b03e5Sespie 		    df_insn_modify (df, bb, insn);
462*c87b03e5Sespie 		  }
463*c87b03e5Sespie 
464*c87b03e5Sespie 		emitted_spill_loads++;
465*c87b03e5Sespie 		spill_load_cost += bb->frequency + 1;
466*c87b03e5Sespie 	      }
467*c87b03e5Sespie 	  }
468*c87b03e5Sespie 
469*c87b03e5Sespie 	/* Now emit the stores after each def.
470*c87b03e5Sespie 	   If any uses were loaded from stackslots (compared to
471*c87b03e5Sespie 	   rematerialized or not reloaded due to IR spilling),
472*c87b03e5Sespie 	   aweb->stack_slot will be set.  If not, we don't need to emit
473*c87b03e5Sespie 	   any stack stores.  */
474*c87b03e5Sespie 	slot = aweb->stack_slot;
475*c87b03e5Sespie 	bitmap_clear (b);
476*c87b03e5Sespie 	if (slot)
477*c87b03e5Sespie 	  for (j = 0; j < web->num_defs; j++)
478*c87b03e5Sespie 	    {
479*c87b03e5Sespie 	      rtx insns, source, dest;
480*c87b03e5Sespie 	      rtx insn = DF_REF_INSN (web->defs[j]);
481*c87b03e5Sespie 	      rtx following = NEXT_INSN (insn);
482*c87b03e5Sespie 	      basic_block bb = BLOCK_FOR_INSN (insn);
483*c87b03e5Sespie 	      /* Happens when spill_coalescing() deletes move insns.  */
484*c87b03e5Sespie 	      if (!INSN_P (insn))
485*c87b03e5Sespie 		continue;
486*c87b03e5Sespie 	      if (bitmap_bit_p (b, INSN_UID (insn)))
487*c87b03e5Sespie 		continue;
488*c87b03e5Sespie 	      bitmap_set_bit (b, INSN_UID (insn));
489*c87b03e5Sespie 	      start_sequence ();
490*c87b03e5Sespie 	      source = DF_REF_REG (web->defs[j]);
491*c87b03e5Sespie 	      dest = slot;
492*c87b03e5Sespie 	      if (GET_CODE (source) == SUBREG)
493*c87b03e5Sespie 		dest = simplify_gen_subreg (GET_MODE (source), dest,
494*c87b03e5Sespie 					    GET_MODE (dest),
495*c87b03e5Sespie 					    SUBREG_BYTE (source));
496*c87b03e5Sespie 	      ra_emit_move_insn (dest, source);
497*c87b03e5Sespie 
498*c87b03e5Sespie 	      insns = get_insns ();
499*c87b03e5Sespie 	      end_sequence ();
500*c87b03e5Sespie 	      if (insns)
501*c87b03e5Sespie 		{
502*c87b03e5Sespie 		  emit_insn_after (insns, insn);
503*c87b03e5Sespie 		  if (bb->end == insn)
504*c87b03e5Sespie 		    bb->end = PREV_INSN (following);
505*c87b03e5Sespie 		  for (insn = insns; insn != following; insn = NEXT_INSN (insn))
506*c87b03e5Sespie 		    {
507*c87b03e5Sespie 		      set_block_for_insn (insn, bb);
508*c87b03e5Sespie 		      df_insn_modify (df, bb, insn);
509*c87b03e5Sespie 		    }
510*c87b03e5Sespie 		}
511*c87b03e5Sespie 	      else
512*c87b03e5Sespie 		df_insn_modify (df, bb, insn);
513*c87b03e5Sespie 	      emitted_spill_stores++;
514*c87b03e5Sespie 	      spill_store_cost += bb->frequency + 1;
515*c87b03e5Sespie 	      /* XXX we should set new_deaths for all inserted stores
516*c87b03e5Sespie 		 whose pseudo dies here.
517*c87b03e5Sespie 		 Note, that this isn't the case for _all_ stores.  */
518*c87b03e5Sespie 	      /* I.e. the next is wrong, and might cause some spilltemps
519*c87b03e5Sespie 		 to be categorized as spilltemp2's (i.e. live over a death),
520*c87b03e5Sespie 		 although they aren't.  This might make them spill again,
521*c87b03e5Sespie 		 which causes endlessness in the case, this insn is in fact
522*c87b03e5Sespie 		 _no_ death.  */
523*c87b03e5Sespie 	      bitmap_set_bit (new_deaths, INSN_UID (PREV_INSN (following)));
524*c87b03e5Sespie 	    }
525*c87b03e5Sespie       }
526*c87b03e5Sespie 
527*c87b03e5Sespie   BITMAP_XFREE (b);
528*c87b03e5Sespie }
529*c87b03e5Sespie 
530*c87b03e5Sespie /* A simple list of rtx's.  */
531*c87b03e5Sespie struct rtx_list
532*c87b03e5Sespie {
533*c87b03e5Sespie   struct rtx_list *next;
534*c87b03e5Sespie   rtx x;
535*c87b03e5Sespie };
536*c87b03e5Sespie 
537*c87b03e5Sespie /* Adds X to *LIST.  */
538*c87b03e5Sespie 
539*c87b03e5Sespie static void
remember_slot(list,x)540*c87b03e5Sespie remember_slot (list, x)
541*c87b03e5Sespie      struct rtx_list **list;
542*c87b03e5Sespie      rtx x;
543*c87b03e5Sespie {
544*c87b03e5Sespie   struct rtx_list *l;
545*c87b03e5Sespie   /* PRE: X is not already in LIST.  */
546*c87b03e5Sespie   l = (struct rtx_list *) ra_alloc (sizeof (*l));
547*c87b03e5Sespie   l->next = *list;
548*c87b03e5Sespie   l->x = x;
549*c87b03e5Sespie   *list = l;
550*c87b03e5Sespie }
551*c87b03e5Sespie 
552*c87b03e5Sespie /* Given two rtx' S1 and S2, either being REGs or MEMs (or SUBREGs
553*c87b03e5Sespie    thereof), return nonzero, if they overlap.  REGs and MEMs don't
554*c87b03e5Sespie    overlap, and if they are MEMs they must have an easy address
555*c87b03e5Sespie    (plus (basereg) (const_inst x)), otherwise they overlap.  */
556*c87b03e5Sespie 
557*c87b03e5Sespie static int
slots_overlap_p(s1,s2)558*c87b03e5Sespie slots_overlap_p (s1, s2)
559*c87b03e5Sespie      rtx s1, s2;
560*c87b03e5Sespie {
561*c87b03e5Sespie   rtx base1, base2;
562*c87b03e5Sespie   HOST_WIDE_INT ofs1 = 0, ofs2 = 0;
563*c87b03e5Sespie   int size1 = GET_MODE_SIZE (GET_MODE (s1));
564*c87b03e5Sespie   int size2 = GET_MODE_SIZE (GET_MODE (s2));
565*c87b03e5Sespie   if (GET_CODE (s1) == SUBREG)
566*c87b03e5Sespie     ofs1 = SUBREG_BYTE (s1), s1 = SUBREG_REG (s1);
567*c87b03e5Sespie   if (GET_CODE (s2) == SUBREG)
568*c87b03e5Sespie     ofs2 = SUBREG_BYTE (s2), s2 = SUBREG_REG (s2);
569*c87b03e5Sespie 
570*c87b03e5Sespie   if (s1 == s2)
571*c87b03e5Sespie     return 1;
572*c87b03e5Sespie 
573*c87b03e5Sespie   if (GET_CODE (s1) != GET_CODE (s2))
574*c87b03e5Sespie     return 0;
575*c87b03e5Sespie 
576*c87b03e5Sespie   if (GET_CODE (s1) == REG && GET_CODE (s2) == REG)
577*c87b03e5Sespie     {
578*c87b03e5Sespie       if (REGNO (s1) != REGNO (s2))
579*c87b03e5Sespie 	return 0;
580*c87b03e5Sespie       if (ofs1 >= ofs2 + size2 || ofs2 >= ofs1 + size1)
581*c87b03e5Sespie 	return 0;
582*c87b03e5Sespie       return 1;
583*c87b03e5Sespie     }
584*c87b03e5Sespie   if (GET_CODE (s1) != MEM || GET_CODE (s2) != MEM)
585*c87b03e5Sespie     abort ();
586*c87b03e5Sespie   s1 = XEXP (s1, 0);
587*c87b03e5Sespie   s2 = XEXP (s2, 0);
588*c87b03e5Sespie   if (GET_CODE (s1) != PLUS || GET_CODE (XEXP (s1, 0)) != REG
589*c87b03e5Sespie       || GET_CODE (XEXP (s1, 1)) != CONST_INT)
590*c87b03e5Sespie     return 1;
591*c87b03e5Sespie   if (GET_CODE (s2) != PLUS || GET_CODE (XEXP (s2, 0)) != REG
592*c87b03e5Sespie       || GET_CODE (XEXP (s2, 1)) != CONST_INT)
593*c87b03e5Sespie     return 1;
594*c87b03e5Sespie   base1 = XEXP (s1, 0);
595*c87b03e5Sespie   base2 = XEXP (s2, 0);
596*c87b03e5Sespie   if (!rtx_equal_p (base1, base2))
597*c87b03e5Sespie     return 1;
598*c87b03e5Sespie   ofs1 += INTVAL (XEXP (s1, 1));
599*c87b03e5Sespie   ofs2 += INTVAL (XEXP (s2, 1));
600*c87b03e5Sespie   if (ofs1 >= ofs2 + size2 || ofs2 >= ofs1 + size1)
601*c87b03e5Sespie     return 0;
602*c87b03e5Sespie   return 1;
603*c87b03e5Sespie }
604*c87b03e5Sespie 
605*c87b03e5Sespie /* This deletes from *LIST all rtx's which overlap with X in the sense
606*c87b03e5Sespie    of slots_overlap_p().  */
607*c87b03e5Sespie 
608*c87b03e5Sespie static void
delete_overlapping_slots(list,x)609*c87b03e5Sespie delete_overlapping_slots (list, x)
610*c87b03e5Sespie      struct rtx_list **list;
611*c87b03e5Sespie      rtx x;
612*c87b03e5Sespie {
613*c87b03e5Sespie   while (*list)
614*c87b03e5Sespie     {
615*c87b03e5Sespie       if (slots_overlap_p ((*list)->x, x))
616*c87b03e5Sespie 	*list = (*list)->next;
617*c87b03e5Sespie       else
618*c87b03e5Sespie 	list = &((*list)->next);
619*c87b03e5Sespie     }
620*c87b03e5Sespie }
621*c87b03e5Sespie 
622*c87b03e5Sespie /* Returns nonzero, of X is member of LIST.  */
623*c87b03e5Sespie 
624*c87b03e5Sespie static int
slot_member_p(list,x)625*c87b03e5Sespie slot_member_p (list, x)
626*c87b03e5Sespie      struct rtx_list *list;
627*c87b03e5Sespie      rtx x;
628*c87b03e5Sespie {
629*c87b03e5Sespie   for (;list; list = list->next)
630*c87b03e5Sespie     if (rtx_equal_p (list->x, x))
631*c87b03e5Sespie       return 1;
632*c87b03e5Sespie   return 0;
633*c87b03e5Sespie }
634*c87b03e5Sespie 
635*c87b03e5Sespie /* A more sophisticated (and slower) method of adding the stores, than
636*c87b03e5Sespie    rewrite_program().  This goes backward the insn stream, adding
637*c87b03e5Sespie    stores as it goes, but only if it hasn't just added a store to the
638*c87b03e5Sespie    same location.  NEW_DEATHS is a bitmap filled with uids of insns
639*c87b03e5Sespie    containing deaths.  */
640*c87b03e5Sespie 
641*c87b03e5Sespie static void
insert_stores(new_deaths)642*c87b03e5Sespie insert_stores (new_deaths)
643*c87b03e5Sespie      bitmap new_deaths;
644*c87b03e5Sespie {
645*c87b03e5Sespie   rtx insn;
646*c87b03e5Sespie   rtx last_slot = NULL_RTX;
647*c87b03e5Sespie   struct rtx_list *slots = NULL;
648*c87b03e5Sespie 
649*c87b03e5Sespie   /* We go simply backwards over basic block borders.  */
650*c87b03e5Sespie   for (insn = get_last_insn (); insn; insn = PREV_INSN (insn))
651*c87b03e5Sespie     {
652*c87b03e5Sespie       int uid = INSN_UID (insn);
653*c87b03e5Sespie 
654*c87b03e5Sespie       /* If we reach a basic block border, which has more than one
655*c87b03e5Sespie 	 outgoing edge, we simply forget all already emitted stores.  */
656*c87b03e5Sespie       if (GET_CODE (insn) == BARRIER
657*c87b03e5Sespie 	  || JUMP_P (insn) || can_throw_internal (insn))
658*c87b03e5Sespie 	{
659*c87b03e5Sespie 	  last_slot = NULL_RTX;
660*c87b03e5Sespie 	  slots = NULL;
661*c87b03e5Sespie 	}
662*c87b03e5Sespie       if (!INSN_P (insn))
663*c87b03e5Sespie 	continue;
664*c87b03e5Sespie 
665*c87b03e5Sespie       /* If this insn was not just added in this pass.  */
666*c87b03e5Sespie       if (uid < insn_df_max_uid)
667*c87b03e5Sespie 	{
668*c87b03e5Sespie 	  unsigned int n;
669*c87b03e5Sespie 	  rtx following = NEXT_INSN (insn);
670*c87b03e5Sespie 	  basic_block bb = BLOCK_FOR_INSN (insn);
671*c87b03e5Sespie 	  struct ra_insn_info info;
672*c87b03e5Sespie 
673*c87b03e5Sespie 	  info = insn_df[uid];
674*c87b03e5Sespie 	  for (n = 0; n < info.num_defs; n++)
675*c87b03e5Sespie 	    {
676*c87b03e5Sespie 	      struct web *web = def2web[DF_REF_ID (info.defs[n])];
677*c87b03e5Sespie 	      struct web *aweb = alias (find_web_for_subweb (web));
678*c87b03e5Sespie 	      rtx slot, source;
679*c87b03e5Sespie 	      if (aweb->type != SPILLED || !aweb->stack_slot)
680*c87b03e5Sespie 		continue;
681*c87b03e5Sespie 	      slot = aweb->stack_slot;
682*c87b03e5Sespie 	      source = DF_REF_REG (info.defs[n]);
683*c87b03e5Sespie 	      /* adjust_address() might generate code.  */
684*c87b03e5Sespie 	      start_sequence ();
685*c87b03e5Sespie 	      if (GET_CODE (source) == SUBREG)
686*c87b03e5Sespie 		slot = simplify_gen_subreg (GET_MODE (source), slot,
687*c87b03e5Sespie 					    GET_MODE (slot),
688*c87b03e5Sespie 					    SUBREG_BYTE (source));
689*c87b03e5Sespie 	      /* If we have no info about emitted stores, or it didn't
690*c87b03e5Sespie 		 contain the location we intend to use soon, then
691*c87b03e5Sespie 		 add the store.  */
692*c87b03e5Sespie 	      if ((!last_slot || !rtx_equal_p (slot, last_slot))
693*c87b03e5Sespie 		  && ! slot_member_p (slots, slot))
694*c87b03e5Sespie 		{
695*c87b03e5Sespie 		  rtx insns, ni;
696*c87b03e5Sespie 		  last_slot = slot;
697*c87b03e5Sespie 		  remember_slot (&slots, slot);
698*c87b03e5Sespie 		  ra_emit_move_insn (slot, source);
699*c87b03e5Sespie 		  insns = get_insns ();
700*c87b03e5Sespie 		  end_sequence ();
701*c87b03e5Sespie 		  if (insns)
702*c87b03e5Sespie 		    {
703*c87b03e5Sespie 		      emit_insn_after (insns, insn);
704*c87b03e5Sespie 		      if (bb->end == insn)
705*c87b03e5Sespie 			bb->end = PREV_INSN (following);
706*c87b03e5Sespie 		      for (ni = insns; ni != following; ni = NEXT_INSN (ni))
707*c87b03e5Sespie 			{
708*c87b03e5Sespie 			  set_block_for_insn (ni, bb);
709*c87b03e5Sespie 			  df_insn_modify (df, bb, ni);
710*c87b03e5Sespie 			}
711*c87b03e5Sespie 		    }
712*c87b03e5Sespie 		  else
713*c87b03e5Sespie 		    df_insn_modify (df, bb, insn);
714*c87b03e5Sespie 		  emitted_spill_stores++;
715*c87b03e5Sespie 		  spill_store_cost += bb->frequency + 1;
716*c87b03e5Sespie 		  bitmap_set_bit (new_deaths, INSN_UID (PREV_INSN (following)));
717*c87b03e5Sespie 		}
718*c87b03e5Sespie 	      else
719*c87b03e5Sespie 		{
720*c87b03e5Sespie 		  /* Otherwise ignore insns from adjust_address() above.  */
721*c87b03e5Sespie 		  end_sequence ();
722*c87b03e5Sespie 		}
723*c87b03e5Sespie 	    }
724*c87b03e5Sespie 	}
725*c87b03e5Sespie       /* If we look at a load generated by the allocator, forget
726*c87b03e5Sespie 	 the last emitted slot, and additionally clear all slots
727*c87b03e5Sespie 	 overlapping it's source (after all, we need it again).  */
728*c87b03e5Sespie       /* XXX If we emit the stack-ref directly into the using insn the
729*c87b03e5Sespie          following needs a change, because that is no new insn.  Preferably
730*c87b03e5Sespie 	 we would add some notes to the insn, what stackslots are needed
731*c87b03e5Sespie 	 for it.  */
732*c87b03e5Sespie       if (uid >= last_max_uid)
733*c87b03e5Sespie 	{
734*c87b03e5Sespie 	  rtx set = single_set (insn);
735*c87b03e5Sespie 	  last_slot = NULL_RTX;
736*c87b03e5Sespie 	  /* If this was no simple set, give up, and forget everything.  */
737*c87b03e5Sespie 	  if (!set)
738*c87b03e5Sespie 	    slots = NULL;
739*c87b03e5Sespie 	  else
740*c87b03e5Sespie 	    {
741*c87b03e5Sespie 	      if (1 || GET_CODE (SET_SRC (set)) == MEM)
742*c87b03e5Sespie 	        delete_overlapping_slots (&slots, SET_SRC (set));
743*c87b03e5Sespie 	    }
744*c87b03e5Sespie 	}
745*c87b03e5Sespie     }
746*c87b03e5Sespie }
747*c87b03e5Sespie 
748*c87b03e5Sespie /* Returns 1 if both colored webs have some hardregs in common, even if
749*c87b03e5Sespie    they are not the same width.  */
750*c87b03e5Sespie 
751*c87b03e5Sespie static int
spill_same_color_p(web1,web2)752*c87b03e5Sespie spill_same_color_p (web1, web2)
753*c87b03e5Sespie      struct web *web1, *web2;
754*c87b03e5Sespie {
755*c87b03e5Sespie   int c1, size1, c2, size2;
756*c87b03e5Sespie   if ((c1 = alias (web1)->color) < 0 || c1 == an_unusable_color)
757*c87b03e5Sespie     return 0;
758*c87b03e5Sespie   if ((c2 = alias (web2)->color) < 0 || c2 == an_unusable_color)
759*c87b03e5Sespie     return 0;
760*c87b03e5Sespie 
761*c87b03e5Sespie   size1 = web1->type == PRECOLORED
762*c87b03e5Sespie           ? 1 : HARD_REGNO_NREGS (c1, PSEUDO_REGNO_MODE (web1->regno));
763*c87b03e5Sespie   size2 = web2->type == PRECOLORED
764*c87b03e5Sespie           ? 1 : HARD_REGNO_NREGS (c2, PSEUDO_REGNO_MODE (web2->regno));
765*c87b03e5Sespie   if (c1 >= c2 + size2 || c2 >= c1 + size1)
766*c87b03e5Sespie     return 0;
767*c87b03e5Sespie   return 1;
768*c87b03e5Sespie }
769*c87b03e5Sespie 
770*c87b03e5Sespie /* Given the set of live web IDs LIVE, returns nonzero, if any of WEBs
771*c87b03e5Sespie    subwebs (or WEB itself) is live.  */
772*c87b03e5Sespie 
773*c87b03e5Sespie static bool
is_partly_live_1(live,web)774*c87b03e5Sespie is_partly_live_1 (live, web)
775*c87b03e5Sespie      sbitmap live;
776*c87b03e5Sespie      struct web *web;
777*c87b03e5Sespie {
778*c87b03e5Sespie   do
779*c87b03e5Sespie     if (TEST_BIT (live, web->id))
780*c87b03e5Sespie       return 1;
781*c87b03e5Sespie   while ((web = web->subreg_next));
782*c87b03e5Sespie   return 0;
783*c87b03e5Sespie }
784*c87b03e5Sespie 
785*c87b03e5Sespie /* Fast version in case WEB has no subwebs.  */
786*c87b03e5Sespie #define is_partly_live(live, web) ((!web->subreg_next)	\
787*c87b03e5Sespie 				   ? TEST_BIT (live, web->id)	\
788*c87b03e5Sespie 				   : is_partly_live_1 (live, web))
789*c87b03e5Sespie 
790*c87b03e5Sespie /* Change the set of currently IN_USE colors according to
791*c87b03e5Sespie    WEB's color.  Either add those colors to the hardreg set (if ADD
792*c87b03e5Sespie    is nonzero), or remove them.  */
793*c87b03e5Sespie 
794*c87b03e5Sespie static void
update_spill_colors(in_use,web,add)795*c87b03e5Sespie update_spill_colors (in_use, web, add)
796*c87b03e5Sespie      HARD_REG_SET *in_use;
797*c87b03e5Sespie      struct web *web;
798*c87b03e5Sespie      int add;
799*c87b03e5Sespie {
800*c87b03e5Sespie   int c, size;
801*c87b03e5Sespie   if ((c = alias (find_web_for_subweb (web))->color) < 0
802*c87b03e5Sespie       || c == an_unusable_color)
803*c87b03e5Sespie     return;
804*c87b03e5Sespie   size = HARD_REGNO_NREGS (c, GET_MODE (web->orig_x));
805*c87b03e5Sespie   if (SUBWEB_P (web))
806*c87b03e5Sespie     {
807*c87b03e5Sespie       c += subreg_regno_offset (c, GET_MODE (SUBREG_REG (web->orig_x)),
808*c87b03e5Sespie 				SUBREG_BYTE (web->orig_x),
809*c87b03e5Sespie 				GET_MODE (web->orig_x));
810*c87b03e5Sespie     }
811*c87b03e5Sespie   else if (web->type == PRECOLORED)
812*c87b03e5Sespie     size = 1;
813*c87b03e5Sespie   if (add)
814*c87b03e5Sespie     for (; size--;)
815*c87b03e5Sespie       SET_HARD_REG_BIT (*in_use, c + size);
816*c87b03e5Sespie   else
817*c87b03e5Sespie     for (; size--;)
818*c87b03e5Sespie       CLEAR_HARD_REG_BIT (*in_use, c + size);
819*c87b03e5Sespie }
820*c87b03e5Sespie 
821*c87b03e5Sespie /* Given a set of hardregs currently IN_USE and the color C of WEB,
822*c87b03e5Sespie    return -1 if WEB has no color, 1 of it has the unusable color,
823*c87b03e5Sespie    0 if one of it's used hardregs are in use, and 1 otherwise.
824*c87b03e5Sespie    Generally, if WEB can't be left colorized return 1.  */
825*c87b03e5Sespie 
826*c87b03e5Sespie static int
spill_is_free(in_use,web)827*c87b03e5Sespie spill_is_free (in_use, web)
828*c87b03e5Sespie      HARD_REG_SET *in_use;
829*c87b03e5Sespie      struct web *web;
830*c87b03e5Sespie {
831*c87b03e5Sespie   int c, size;
832*c87b03e5Sespie   if ((c = alias (web)->color) < 0)
833*c87b03e5Sespie     return -1;
834*c87b03e5Sespie   if (c == an_unusable_color)
835*c87b03e5Sespie     return 1;
836*c87b03e5Sespie   size = web->type == PRECOLORED
837*c87b03e5Sespie          ? 1 : HARD_REGNO_NREGS (c, PSEUDO_REGNO_MODE (web->regno));
838*c87b03e5Sespie   for (; size--;)
839*c87b03e5Sespie     if (TEST_HARD_REG_BIT (*in_use, c + size))
840*c87b03e5Sespie       return 0;
841*c87b03e5Sespie   return 1;
842*c87b03e5Sespie }
843*c87b03e5Sespie 
844*c87b03e5Sespie 
845*c87b03e5Sespie /* Structure for passing between rewrite_program2() and emit_loads().  */
846*c87b03e5Sespie struct rewrite_info
847*c87b03e5Sespie {
848*c87b03e5Sespie   /* The web IDs which currently would need a reload.  These are
849*c87b03e5Sespie      currently live spilled webs, whose color was still free.  */
850*c87b03e5Sespie   bitmap need_reload;
851*c87b03e5Sespie   /* We need a scratch bitmap, but don't want to allocate one a zillion
852*c87b03e5Sespie      times.  */
853*c87b03e5Sespie   bitmap scratch;
854*c87b03e5Sespie   /* Web IDs of currently live webs.  This are the precise IDs,
855*c87b03e5Sespie      not just those of the superwebs.  If only on part is live, only
856*c87b03e5Sespie      that ID is placed here.  */
857*c87b03e5Sespie   sbitmap live;
858*c87b03e5Sespie   /* An array of webs, which currently need a load added.
859*c87b03e5Sespie      They will be emitted when seeing the first death.  */
860*c87b03e5Sespie   struct web **needed_loads;
861*c87b03e5Sespie   /* The current number of entries in needed_loads.  */
862*c87b03e5Sespie   int nl_size;
863*c87b03e5Sespie   /* The number of bits set in need_reload.  */
864*c87b03e5Sespie   int num_reloads;
865*c87b03e5Sespie   /* The current set of hardregs not available.  */
866*c87b03e5Sespie   HARD_REG_SET colors_in_use;
867*c87b03e5Sespie   /* Nonzero, if we just added some spill temps to need_reload or
868*c87b03e5Sespie      needed_loads.  In this case we don't wait for the next death
869*c87b03e5Sespie      to emit their loads.  */
870*c87b03e5Sespie   int any_spilltemps_spilled;
871*c87b03e5Sespie   /* Nonzero, if we currently need to emit the loads.  E.g. when we
872*c87b03e5Sespie      saw an insn containing deaths.  */
873*c87b03e5Sespie   int need_load;
874*c87b03e5Sespie };
875*c87b03e5Sespie 
876*c87b03e5Sespie /* The needed_loads list of RI contains some webs for which
877*c87b03e5Sespie    we add the actual load insns here.  They are added just before
878*c87b03e5Sespie    their use last seen.  NL_FIRST_RELOAD is the index of the first
879*c87b03e5Sespie    load which is a converted reload, all other entries are normal
880*c87b03e5Sespie    loads.  LAST_BLOCK_INSN is the last insn of the current basic block.  */
881*c87b03e5Sespie 
882*c87b03e5Sespie static void
emit_loads(ri,nl_first_reload,last_block_insn)883*c87b03e5Sespie emit_loads (ri, nl_first_reload, last_block_insn)
884*c87b03e5Sespie      struct rewrite_info *ri;
885*c87b03e5Sespie      int nl_first_reload;
886*c87b03e5Sespie      rtx last_block_insn;
887*c87b03e5Sespie {
888*c87b03e5Sespie   int j;
889*c87b03e5Sespie   for (j = ri->nl_size; j;)
890*c87b03e5Sespie     {
891*c87b03e5Sespie       struct web *web = ri->needed_loads[--j];
892*c87b03e5Sespie       struct web *supweb;
893*c87b03e5Sespie       struct web *aweb;
894*c87b03e5Sespie       rtx ni, slot, reg;
895*c87b03e5Sespie       rtx before = NULL_RTX, after = NULL_RTX;
896*c87b03e5Sespie       basic_block bb;
897*c87b03e5Sespie       /* When spilltemps were spilled for the last insns, their
898*c87b03e5Sespie 	 loads already are emitted, which is noted by setting
899*c87b03e5Sespie 	 needed_loads[] for it to 0.  */
900*c87b03e5Sespie       if (!web)
901*c87b03e5Sespie 	continue;
902*c87b03e5Sespie       supweb = find_web_for_subweb (web);
903*c87b03e5Sespie       if (supweb->regno >= max_normal_pseudo)
904*c87b03e5Sespie 	abort ();
905*c87b03e5Sespie       /* Check for web being a spilltemp, if we only want to
906*c87b03e5Sespie 	 load spilltemps.  Also remember, that we emitted that
907*c87b03e5Sespie 	 load, which we don't need to do when we have a death,
908*c87b03e5Sespie 	 because then all of needed_loads[] is emptied.  */
909*c87b03e5Sespie       if (!ri->need_load)
910*c87b03e5Sespie 	{
911*c87b03e5Sespie 	  if (!supweb->spill_temp)
912*c87b03e5Sespie 	    continue;
913*c87b03e5Sespie 	  else
914*c87b03e5Sespie 	    ri->needed_loads[j] = 0;
915*c87b03e5Sespie 	}
916*c87b03e5Sespie       web->in_load = 0;
917*c87b03e5Sespie       /* The adding of reloads doesn't depend on liveness.  */
918*c87b03e5Sespie       if (j < nl_first_reload && !TEST_BIT (ri->live, web->id))
919*c87b03e5Sespie 	continue;
920*c87b03e5Sespie       aweb = alias (supweb);
921*c87b03e5Sespie       aweb->changed = 1;
922*c87b03e5Sespie       start_sequence ();
923*c87b03e5Sespie       if (supweb->pattern)
924*c87b03e5Sespie 	{
925*c87b03e5Sespie 	  /* XXX If we later allow non-constant sources for rematerialization
926*c87b03e5Sespie 	     we must also disallow coalescing _to_ rematerialized webs
927*c87b03e5Sespie 	     (at least then disallow spilling them, which we already ensure
928*c87b03e5Sespie 	     when flag_ra_break_aliases), or not take the pattern but a
929*c87b03e5Sespie 	     stackslot.  */
930*c87b03e5Sespie 	  if (aweb != supweb)
931*c87b03e5Sespie 	    abort ();
932*c87b03e5Sespie 	  slot = copy_rtx (supweb->pattern);
933*c87b03e5Sespie 	  reg = copy_rtx (supweb->orig_x);
934*c87b03e5Sespie 	  /* Sanity check.  orig_x should be a REG rtx, which should be
935*c87b03e5Sespie 	     shared over all RTL, so copy_rtx should have no effect.  */
936*c87b03e5Sespie 	  if (reg != supweb->orig_x)
937*c87b03e5Sespie 	    abort ();
938*c87b03e5Sespie 	}
939*c87b03e5Sespie       else
940*c87b03e5Sespie 	{
941*c87b03e5Sespie 	  allocate_spill_web (aweb);
942*c87b03e5Sespie 	  slot = aweb->stack_slot;
943*c87b03e5Sespie 
944*c87b03e5Sespie 	  /* If we don't copy the RTL there might be some SUBREG
945*c87b03e5Sespie 	     rtx shared in the next iteration although being in
946*c87b03e5Sespie 	     different webs, which leads to wrong code.  */
947*c87b03e5Sespie 	  reg = copy_rtx (web->orig_x);
948*c87b03e5Sespie 	  if (GET_CODE (reg) == SUBREG)
949*c87b03e5Sespie 	    /*slot = adjust_address (slot, GET_MODE (reg), SUBREG_BYTE
950*c87b03e5Sespie 	       (reg));*/
951*c87b03e5Sespie 	    slot = simplify_gen_subreg (GET_MODE (reg), slot, GET_MODE (slot),
952*c87b03e5Sespie 					SUBREG_BYTE (reg));
953*c87b03e5Sespie 	}
954*c87b03e5Sespie       ra_emit_move_insn (reg, slot);
955*c87b03e5Sespie       ni = get_insns ();
956*c87b03e5Sespie       end_sequence ();
957*c87b03e5Sespie       before = web->last_use_insn;
958*c87b03e5Sespie       web->last_use_insn = NULL_RTX;
959*c87b03e5Sespie       if (!before)
960*c87b03e5Sespie 	{
961*c87b03e5Sespie 	  if (JUMP_P (last_block_insn))
962*c87b03e5Sespie 	    before = last_block_insn;
963*c87b03e5Sespie 	  else
964*c87b03e5Sespie 	    after = last_block_insn;
965*c87b03e5Sespie 	}
966*c87b03e5Sespie       if (after)
967*c87b03e5Sespie 	{
968*c87b03e5Sespie 	  rtx foll = NEXT_INSN (after);
969*c87b03e5Sespie 	  bb = BLOCK_FOR_INSN (after);
970*c87b03e5Sespie 	  emit_insn_after (ni, after);
971*c87b03e5Sespie 	  if (bb->end == after)
972*c87b03e5Sespie 	    bb->end = PREV_INSN (foll);
973*c87b03e5Sespie 	  for (ni = NEXT_INSN (after); ni != foll; ni = NEXT_INSN (ni))
974*c87b03e5Sespie 	    {
975*c87b03e5Sespie 	      set_block_for_insn (ni, bb);
976*c87b03e5Sespie 	      df_insn_modify (df, bb, ni);
977*c87b03e5Sespie 	    }
978*c87b03e5Sespie 	}
979*c87b03e5Sespie       else
980*c87b03e5Sespie 	{
981*c87b03e5Sespie 	  rtx prev = PREV_INSN (before);
982*c87b03e5Sespie 	  bb = BLOCK_FOR_INSN (before);
983*c87b03e5Sespie 	  emit_insn_before (ni, before);
984*c87b03e5Sespie 	  if (bb->head == before)
985*c87b03e5Sespie 	    bb->head = NEXT_INSN (prev);
986*c87b03e5Sespie 	  for (; ni != before; ni = NEXT_INSN (ni))
987*c87b03e5Sespie 	    {
988*c87b03e5Sespie 	      set_block_for_insn (ni, bb);
989*c87b03e5Sespie 	      df_insn_modify (df, bb, ni);
990*c87b03e5Sespie 	    }
991*c87b03e5Sespie 	}
992*c87b03e5Sespie       if (supweb->pattern)
993*c87b03e5Sespie 	{
994*c87b03e5Sespie 	  emitted_remat++;
995*c87b03e5Sespie 	  spill_remat_cost += bb->frequency + 1;
996*c87b03e5Sespie 	}
997*c87b03e5Sespie       else
998*c87b03e5Sespie 	{
999*c87b03e5Sespie 	  emitted_spill_loads++;
1000*c87b03e5Sespie 	  spill_load_cost += bb->frequency + 1;
1001*c87b03e5Sespie 	}
1002*c87b03e5Sespie       RESET_BIT (ri->live, web->id);
1003*c87b03e5Sespie       /* In the special case documented above only emit the reloads and
1004*c87b03e5Sespie 	 one load.  */
1005*c87b03e5Sespie       if (ri->need_load == 2 && j < nl_first_reload)
1006*c87b03e5Sespie 	break;
1007*c87b03e5Sespie     }
1008*c87b03e5Sespie   if (ri->need_load)
1009*c87b03e5Sespie     ri->nl_size = j;
1010*c87b03e5Sespie }
1011*c87b03e5Sespie 
1012*c87b03e5Sespie /* Given a set of reloads in RI, an array of NUM_REFS references (either
1013*c87b03e5Sespie    uses or defs) in REFS, and REF2WEB to translate ref IDs to webs
1014*c87b03e5Sespie    (either use2web or def2web) convert some reloads to loads.
1015*c87b03e5Sespie    This looks at the webs referenced, and how they change the set of
1016*c87b03e5Sespie    available colors.  Now put all still live webs, which needed reloads,
1017*c87b03e5Sespie    and whose colors isn't free anymore, on the needed_loads list.  */
1018*c87b03e5Sespie 
1019*c87b03e5Sespie static void
reloads_to_loads(ri,refs,num_refs,ref2web)1020*c87b03e5Sespie reloads_to_loads (ri, refs, num_refs, ref2web)
1021*c87b03e5Sespie      struct rewrite_info *ri;
1022*c87b03e5Sespie      struct ref **refs;
1023*c87b03e5Sespie      unsigned int num_refs;
1024*c87b03e5Sespie      struct web **ref2web;
1025*c87b03e5Sespie {
1026*c87b03e5Sespie   unsigned int n;
1027*c87b03e5Sespie   int num_reloads = ri->num_reloads;
1028*c87b03e5Sespie   for (n = 0; n < num_refs && num_reloads; n++)
1029*c87b03e5Sespie     {
1030*c87b03e5Sespie       struct web *web = ref2web[DF_REF_ID (refs[n])];
1031*c87b03e5Sespie       struct web *supweb = find_web_for_subweb (web);
1032*c87b03e5Sespie       int is_death;
1033*c87b03e5Sespie       int j;
1034*c87b03e5Sespie       /* Only emit reloads when entering their interference
1035*c87b03e5Sespie 	 region.  A use of a spilled web never opens an
1036*c87b03e5Sespie 	 interference region, independent of it's color.  */
1037*c87b03e5Sespie       if (alias (supweb)->type == SPILLED)
1038*c87b03e5Sespie 	continue;
1039*c87b03e5Sespie       if (supweb->type == PRECOLORED
1040*c87b03e5Sespie 	  && TEST_HARD_REG_BIT (never_use_colors, supweb->color))
1041*c87b03e5Sespie 	continue;
1042*c87b03e5Sespie       /* Note, that if web (and supweb) are DEFs, we already cleared
1043*c87b03e5Sespie 	 the corresponding bits in live.  I.e. is_death becomes true, which
1044*c87b03e5Sespie 	 is what we want.  */
1045*c87b03e5Sespie       is_death = !TEST_BIT (ri->live, supweb->id);
1046*c87b03e5Sespie       is_death &= !TEST_BIT (ri->live, web->id);
1047*c87b03e5Sespie       if (is_death)
1048*c87b03e5Sespie 	{
1049*c87b03e5Sespie 	  int old_num_r = num_reloads;
1050*c87b03e5Sespie 	  bitmap_clear (ri->scratch);
1051*c87b03e5Sespie 	  EXECUTE_IF_SET_IN_BITMAP (ri->need_reload, 0, j,
1052*c87b03e5Sespie 	    {
1053*c87b03e5Sespie 	      struct web *web2 = ID2WEB (j);
1054*c87b03e5Sespie 	      struct web *aweb2 = alias (find_web_for_subweb (web2));
1055*c87b03e5Sespie 	      if (spill_is_free (&(ri->colors_in_use), aweb2) == 0)
1056*c87b03e5Sespie 		abort ();
1057*c87b03e5Sespie 	      if (spill_same_color_p (supweb, aweb2)
1058*c87b03e5Sespie 		  /* && interfere (web, web2) */)
1059*c87b03e5Sespie 		{
1060*c87b03e5Sespie 		  if (!web2->in_load)
1061*c87b03e5Sespie 		    {
1062*c87b03e5Sespie 		      ri->needed_loads[ri->nl_size++] = web2;
1063*c87b03e5Sespie 		      web2->in_load = 1;
1064*c87b03e5Sespie 		    }
1065*c87b03e5Sespie 		  bitmap_set_bit (ri->scratch, j);
1066*c87b03e5Sespie 		  num_reloads--;
1067*c87b03e5Sespie 		}
1068*c87b03e5Sespie 	    });
1069*c87b03e5Sespie 	  if (num_reloads != old_num_r)
1070*c87b03e5Sespie 	    bitmap_operation (ri->need_reload, ri->need_reload, ri->scratch,
1071*c87b03e5Sespie 			      BITMAP_AND_COMPL);
1072*c87b03e5Sespie 	}
1073*c87b03e5Sespie     }
1074*c87b03e5Sespie   ri->num_reloads = num_reloads;
1075*c87b03e5Sespie }
1076*c87b03e5Sespie 
1077*c87b03e5Sespie /* This adds loads for spilled webs to the program.  It uses a kind of
1078*c87b03e5Sespie    interference region spilling.  If flag_ra_ir_spilling is zero it
1079*c87b03e5Sespie    only uses improved chaitin spilling (adding loads only at insns
1080*c87b03e5Sespie    containing deaths).  */
1081*c87b03e5Sespie 
1082*c87b03e5Sespie static void
rewrite_program2(new_deaths)1083*c87b03e5Sespie rewrite_program2 (new_deaths)
1084*c87b03e5Sespie      bitmap new_deaths;
1085*c87b03e5Sespie {
1086*c87b03e5Sespie   basic_block bb;
1087*c87b03e5Sespie   int nl_first_reload;
1088*c87b03e5Sespie   struct rewrite_info ri;
1089*c87b03e5Sespie   rtx insn;
1090*c87b03e5Sespie   ri.needed_loads = (struct web **) xmalloc (num_webs * sizeof (struct web *));
1091*c87b03e5Sespie   ri.need_reload = BITMAP_XMALLOC ();
1092*c87b03e5Sespie   ri.scratch = BITMAP_XMALLOC ();
1093*c87b03e5Sespie   ri.live = sbitmap_alloc (num_webs);
1094*c87b03e5Sespie   ri.nl_size = 0;
1095*c87b03e5Sespie   ri.num_reloads = 0;
1096*c87b03e5Sespie   for (insn = get_last_insn (); insn; insn = PREV_INSN (insn))
1097*c87b03e5Sespie     {
1098*c87b03e5Sespie       basic_block last_bb = NULL;
1099*c87b03e5Sespie       rtx last_block_insn;
1100*c87b03e5Sespie       int i, j;
1101*c87b03e5Sespie       if (!INSN_P (insn))
1102*c87b03e5Sespie 	insn = prev_real_insn (insn);
1103*c87b03e5Sespie       while (insn && !(bb = BLOCK_FOR_INSN (insn)))
1104*c87b03e5Sespie 	insn = prev_real_insn (insn);
1105*c87b03e5Sespie       if (!insn)
1106*c87b03e5Sespie 	break;
1107*c87b03e5Sespie       i = bb->index + 2;
1108*c87b03e5Sespie       last_block_insn = insn;
1109*c87b03e5Sespie 
1110*c87b03e5Sespie       sbitmap_zero (ri.live);
1111*c87b03e5Sespie       CLEAR_HARD_REG_SET (ri.colors_in_use);
1112*c87b03e5Sespie       EXECUTE_IF_SET_IN_BITMAP (live_at_end[i - 2], 0, j,
1113*c87b03e5Sespie 	{
1114*c87b03e5Sespie 	  struct web *web = use2web[j];
1115*c87b03e5Sespie 	  struct web *aweb = alias (find_web_for_subweb (web));
1116*c87b03e5Sespie 	  /* A web is only live at end, if it isn't spilled.  If we wouldn't
1117*c87b03e5Sespie 	     check this, the last uses of spilled web per basic block
1118*c87b03e5Sespie 	     wouldn't be detected as deaths, although they are in the final
1119*c87b03e5Sespie 	     code.  This would lead to cumulating many loads without need,
1120*c87b03e5Sespie 	     only increasing register pressure.  */
1121*c87b03e5Sespie 	  /* XXX do add also spilled webs which got a color for IR spilling.
1122*c87b03e5Sespie 	     Remember to not add to colors_in_use in that case.  */
1123*c87b03e5Sespie 	  if (aweb->type != SPILLED /*|| aweb->color >= 0*/)
1124*c87b03e5Sespie 	    {
1125*c87b03e5Sespie 	      SET_BIT (ri.live, web->id);
1126*c87b03e5Sespie 	      if (aweb->type != SPILLED)
1127*c87b03e5Sespie 	        update_spill_colors (&(ri.colors_in_use), web, 1);
1128*c87b03e5Sespie 	    }
1129*c87b03e5Sespie 	});
1130*c87b03e5Sespie 
1131*c87b03e5Sespie       bitmap_clear (ri.need_reload);
1132*c87b03e5Sespie       ri.num_reloads = 0;
1133*c87b03e5Sespie       ri.any_spilltemps_spilled = 0;
1134*c87b03e5Sespie       if (flag_ra_ir_spilling)
1135*c87b03e5Sespie 	{
1136*c87b03e5Sespie 	  struct dlist *d;
1137*c87b03e5Sespie 	  int pass;
1138*c87b03e5Sespie 	  /* XXX If we don't add spilled nodes into live above, the following
1139*c87b03e5Sespie 	     becomes an empty loop.  */
1140*c87b03e5Sespie 	  for (pass = 0; pass < 2; pass++)
1141*c87b03e5Sespie 	    for (d = (pass) ? WEBS(SPILLED) : WEBS(COALESCED); d; d = d->next)
1142*c87b03e5Sespie 	      {
1143*c87b03e5Sespie 	        struct web *web = DLIST_WEB (d);
1144*c87b03e5Sespie 		struct web *aweb = alias (web);
1145*c87b03e5Sespie 		if (aweb->type != SPILLED)
1146*c87b03e5Sespie 		  continue;
1147*c87b03e5Sespie 	        if (is_partly_live (ri.live, web)
1148*c87b03e5Sespie 		    && spill_is_free (&(ri.colors_in_use), web) > 0)
1149*c87b03e5Sespie 		  {
1150*c87b03e5Sespie 		    ri.num_reloads++;
1151*c87b03e5Sespie 	            bitmap_set_bit (ri.need_reload, web->id);
1152*c87b03e5Sespie 		    /* Last using insn is somewhere in another block.  */
1153*c87b03e5Sespie 		    web->last_use_insn = NULL_RTX;
1154*c87b03e5Sespie 		  }
1155*c87b03e5Sespie 	      }
1156*c87b03e5Sespie 	}
1157*c87b03e5Sespie 
1158*c87b03e5Sespie       last_bb = bb;
1159*c87b03e5Sespie       for (; insn; insn = PREV_INSN (insn))
1160*c87b03e5Sespie 	{
1161*c87b03e5Sespie 	  struct ra_insn_info info;
1162*c87b03e5Sespie 	  unsigned int n;
1163*c87b03e5Sespie 
1164*c87b03e5Sespie 	  if (INSN_P (insn) && BLOCK_FOR_INSN (insn) != last_bb)
1165*c87b03e5Sespie 	    {
1166*c87b03e5Sespie 	      int index = BLOCK_FOR_INSN (insn)->index + 2;
1167*c87b03e5Sespie 	      EXECUTE_IF_SET_IN_BITMAP (live_at_end[index - 2], 0, j,
1168*c87b03e5Sespie 		{
1169*c87b03e5Sespie 		  struct web *web = use2web[j];
1170*c87b03e5Sespie 		  struct web *aweb = alias (find_web_for_subweb (web));
1171*c87b03e5Sespie 		  if (aweb->type != SPILLED)
1172*c87b03e5Sespie 		    {
1173*c87b03e5Sespie 		      SET_BIT (ri.live, web->id);
1174*c87b03e5Sespie 		      update_spill_colors (&(ri.colors_in_use), web, 1);
1175*c87b03e5Sespie 		    }
1176*c87b03e5Sespie 		});
1177*c87b03e5Sespie 	      bitmap_clear (ri.scratch);
1178*c87b03e5Sespie 	      EXECUTE_IF_SET_IN_BITMAP (ri.need_reload, 0, j,
1179*c87b03e5Sespie 		{
1180*c87b03e5Sespie 		  struct web *web2 = ID2WEB (j);
1181*c87b03e5Sespie 		  struct web *supweb2 = find_web_for_subweb (web2);
1182*c87b03e5Sespie 		  struct web *aweb2 = alias (supweb2);
1183*c87b03e5Sespie 		  if (spill_is_free (&(ri.colors_in_use), aweb2) <= 0)
1184*c87b03e5Sespie 		    {
1185*c87b03e5Sespie 		      if (!web2->in_load)
1186*c87b03e5Sespie 			{
1187*c87b03e5Sespie 			  ri.needed_loads[ri.nl_size++] = web2;
1188*c87b03e5Sespie 			  web2->in_load = 1;
1189*c87b03e5Sespie 			}
1190*c87b03e5Sespie 		      bitmap_set_bit (ri.scratch, j);
1191*c87b03e5Sespie 		      ri.num_reloads--;
1192*c87b03e5Sespie 		    }
1193*c87b03e5Sespie 		});
1194*c87b03e5Sespie 	      bitmap_operation (ri.need_reload, ri.need_reload, ri.scratch,
1195*c87b03e5Sespie 				BITMAP_AND_COMPL);
1196*c87b03e5Sespie 	      last_bb = BLOCK_FOR_INSN (insn);
1197*c87b03e5Sespie 	      last_block_insn = insn;
1198*c87b03e5Sespie 	      if (!INSN_P (last_block_insn))
1199*c87b03e5Sespie 	        last_block_insn = prev_real_insn (last_block_insn);
1200*c87b03e5Sespie 	    }
1201*c87b03e5Sespie 
1202*c87b03e5Sespie 	  ri.need_load = 0;
1203*c87b03e5Sespie 	  if (INSN_P (insn))
1204*c87b03e5Sespie 	    info = insn_df[INSN_UID (insn)];
1205*c87b03e5Sespie 
1206*c87b03e5Sespie 	  if (INSN_P (insn))
1207*c87b03e5Sespie 	    for (n = 0; n < info.num_defs; n++)
1208*c87b03e5Sespie 	      {
1209*c87b03e5Sespie 		struct ref *ref = info.defs[n];
1210*c87b03e5Sespie 		struct web *web = def2web[DF_REF_ID (ref)];
1211*c87b03e5Sespie 		struct web *supweb = find_web_for_subweb (web);
1212*c87b03e5Sespie 		int is_non_def = 0;
1213*c87b03e5Sespie 		unsigned int n2;
1214*c87b03e5Sespie 
1215*c87b03e5Sespie 		supweb = find_web_for_subweb (web);
1216*c87b03e5Sespie 		/* Webs which are defined here, but also used in the same insn
1217*c87b03e5Sespie 		   are rmw webs, or this use isn't a death because of looping
1218*c87b03e5Sespie 		   constructs.  In neither case makes this def available it's
1219*c87b03e5Sespie 		   resources.  Reloads for it are still needed, it's still
1220*c87b03e5Sespie 		   live and it's colors don't become free.  */
1221*c87b03e5Sespie 		for (n2 = 0; n2 < info.num_uses; n2++)
1222*c87b03e5Sespie 		  {
1223*c87b03e5Sespie 		    struct web *web2 = use2web[DF_REF_ID (info.uses[n2])];
1224*c87b03e5Sespie 		    if (supweb == find_web_for_subweb (web2))
1225*c87b03e5Sespie 		      {
1226*c87b03e5Sespie 			is_non_def = 1;
1227*c87b03e5Sespie 			break;
1228*c87b03e5Sespie 		      }
1229*c87b03e5Sespie 		  }
1230*c87b03e5Sespie 		if (is_non_def)
1231*c87b03e5Sespie 		  continue;
1232*c87b03e5Sespie 
1233*c87b03e5Sespie 		if (!is_partly_live (ri.live, supweb))
1234*c87b03e5Sespie 		  bitmap_set_bit (useless_defs, DF_REF_ID (ref));
1235*c87b03e5Sespie 
1236*c87b03e5Sespie 		RESET_BIT (ri.live, web->id);
1237*c87b03e5Sespie 		if (bitmap_bit_p (ri.need_reload, web->id))
1238*c87b03e5Sespie 		  {
1239*c87b03e5Sespie 		    ri.num_reloads--;
1240*c87b03e5Sespie 		    bitmap_clear_bit (ri.need_reload, web->id);
1241*c87b03e5Sespie 		  }
1242*c87b03e5Sespie 		if (web != supweb)
1243*c87b03e5Sespie 		  {
1244*c87b03e5Sespie 		    /* XXX subwebs aren't precisely tracked here.  We have
1245*c87b03e5Sespie 		       everything we need (inverse webs), but the code isn't
1246*c87b03e5Sespie 		       yet written.  We need to make all completely
1247*c87b03e5Sespie 		       overlapping web parts non-live here.  */
1248*c87b03e5Sespie 		    /* If by luck now the whole web isn't live anymore, no
1249*c87b03e5Sespie 		       reloads for it are needed.  */
1250*c87b03e5Sespie 		    if (!is_partly_live (ri.live, supweb)
1251*c87b03e5Sespie 			&& bitmap_bit_p (ri.need_reload, supweb->id))
1252*c87b03e5Sespie 		      {
1253*c87b03e5Sespie 			ri.num_reloads--;
1254*c87b03e5Sespie 			bitmap_clear_bit (ri.need_reload, supweb->id);
1255*c87b03e5Sespie 		      }
1256*c87b03e5Sespie 		  }
1257*c87b03e5Sespie 		else
1258*c87b03e5Sespie 		  {
1259*c87b03e5Sespie 		    struct web *sweb;
1260*c87b03e5Sespie 		    /* If the whole web is defined here, no parts of it are
1261*c87b03e5Sespie 		       live anymore and no reloads are needed for them.  */
1262*c87b03e5Sespie 		    for (sweb = supweb->subreg_next; sweb;
1263*c87b03e5Sespie 			 sweb = sweb->subreg_next)
1264*c87b03e5Sespie 		      {
1265*c87b03e5Sespie 		        RESET_BIT (ri.live, sweb->id);
1266*c87b03e5Sespie 			if (bitmap_bit_p (ri.need_reload, sweb->id))
1267*c87b03e5Sespie 			  {
1268*c87b03e5Sespie 		            ri.num_reloads--;
1269*c87b03e5Sespie 		            bitmap_clear_bit (ri.need_reload, sweb->id);
1270*c87b03e5Sespie 			  }
1271*c87b03e5Sespie 		      }
1272*c87b03e5Sespie 		  }
1273*c87b03e5Sespie 		if (alias (supweb)->type != SPILLED)
1274*c87b03e5Sespie 		  update_spill_colors (&(ri.colors_in_use), web, 0);
1275*c87b03e5Sespie 	      }
1276*c87b03e5Sespie 
1277*c87b03e5Sespie 	  nl_first_reload = ri.nl_size;
1278*c87b03e5Sespie 
1279*c87b03e5Sespie 	  /* CALL_INSNs are not really deaths, but still more registers
1280*c87b03e5Sespie 	     are free after a call, than before.
1281*c87b03e5Sespie 	     XXX Note, that sometimes reload barfs when we emit insns between
1282*c87b03e5Sespie 	     a call and the insn which copies the return register into a
1283*c87b03e5Sespie 	     pseudo.  */
1284*c87b03e5Sespie 	  if (GET_CODE (insn) == CALL_INSN)
1285*c87b03e5Sespie 	    ri.need_load = 1;
1286*c87b03e5Sespie 	  else if (INSN_P (insn))
1287*c87b03e5Sespie 	    for (n = 0; n < info.num_uses; n++)
1288*c87b03e5Sespie 	      {
1289*c87b03e5Sespie 		struct web *web = use2web[DF_REF_ID (info.uses[n])];
1290*c87b03e5Sespie 		struct web *supweb = find_web_for_subweb (web);
1291*c87b03e5Sespie 		int is_death;
1292*c87b03e5Sespie 		if (supweb->type == PRECOLORED
1293*c87b03e5Sespie 		    && TEST_HARD_REG_BIT (never_use_colors, supweb->color))
1294*c87b03e5Sespie 		  continue;
1295*c87b03e5Sespie 		is_death = !TEST_BIT (ri.live, supweb->id);
1296*c87b03e5Sespie 		is_death &= !TEST_BIT (ri.live, web->id);
1297*c87b03e5Sespie 		if (is_death)
1298*c87b03e5Sespie 		  {
1299*c87b03e5Sespie 		    ri.need_load = 1;
1300*c87b03e5Sespie 		    bitmap_set_bit (new_deaths, INSN_UID (insn));
1301*c87b03e5Sespie 		    break;
1302*c87b03e5Sespie 		  }
1303*c87b03e5Sespie 	      }
1304*c87b03e5Sespie 
1305*c87b03e5Sespie 	  if (INSN_P (insn) && ri.num_reloads)
1306*c87b03e5Sespie 	    {
1307*c87b03e5Sespie               int old_num_reloads = ri.num_reloads;
1308*c87b03e5Sespie 	      reloads_to_loads (&ri, info.uses, info.num_uses, use2web);
1309*c87b03e5Sespie 
1310*c87b03e5Sespie 	      /* If this insn sets a pseudo, which isn't used later
1311*c87b03e5Sespie 		 (i.e. wasn't live before) it is a dead store.  We need
1312*c87b03e5Sespie 		 to emit all reloads which have the same color as this def.
1313*c87b03e5Sespie 		 We don't need to check for non-liveness here to detect
1314*c87b03e5Sespie 		 the deadness (it anyway is too late, as we already cleared
1315*c87b03e5Sespie 		 the liveness in the first loop over the defs), because if it
1316*c87b03e5Sespie 		 _would_ be live here, no reload could have that color, as
1317*c87b03e5Sespie 		 they would already have been converted to a load.  */
1318*c87b03e5Sespie 	      if (ri.num_reloads)
1319*c87b03e5Sespie 		reloads_to_loads (&ri, info.defs, info.num_defs, def2web);
1320*c87b03e5Sespie 	      if (ri.num_reloads != old_num_reloads && !ri.need_load)
1321*c87b03e5Sespie 		ri.need_load = 1;
1322*c87b03e5Sespie 	    }
1323*c87b03e5Sespie 
1324*c87b03e5Sespie 	  if (ri.nl_size && (ri.need_load || ri.any_spilltemps_spilled))
1325*c87b03e5Sespie 	    emit_loads (&ri, nl_first_reload, last_block_insn);
1326*c87b03e5Sespie 
1327*c87b03e5Sespie 	  if (INSN_P (insn) && flag_ra_ir_spilling)
1328*c87b03e5Sespie 	    for (n = 0; n < info.num_uses; n++)
1329*c87b03e5Sespie 	      {
1330*c87b03e5Sespie 		struct web *web = use2web[DF_REF_ID (info.uses[n])];
1331*c87b03e5Sespie 		struct web *aweb = alias (find_web_for_subweb (web));
1332*c87b03e5Sespie 		if (aweb->type != SPILLED)
1333*c87b03e5Sespie 		  update_spill_colors (&(ri.colors_in_use), web, 1);
1334*c87b03e5Sespie 	      }
1335*c87b03e5Sespie 
1336*c87b03e5Sespie 	  ri.any_spilltemps_spilled = 0;
1337*c87b03e5Sespie 	  if (INSN_P (insn))
1338*c87b03e5Sespie 	    for (n = 0; n < info.num_uses; n++)
1339*c87b03e5Sespie 	      {
1340*c87b03e5Sespie 		struct web *web = use2web[DF_REF_ID (info.uses[n])];
1341*c87b03e5Sespie 		struct web *supweb = find_web_for_subweb (web);
1342*c87b03e5Sespie 		struct web *aweb = alias (supweb);
1343*c87b03e5Sespie 		SET_BIT (ri.live, web->id);
1344*c87b03e5Sespie 		if (aweb->type != SPILLED)
1345*c87b03e5Sespie 		  continue;
1346*c87b03e5Sespie 		if (supweb->spill_temp)
1347*c87b03e5Sespie 		  ri.any_spilltemps_spilled = 1;
1348*c87b03e5Sespie 		web->last_use_insn = insn;
1349*c87b03e5Sespie 		if (!web->in_load)
1350*c87b03e5Sespie 		  {
1351*c87b03e5Sespie 		    if (spill_is_free (&(ri.colors_in_use), aweb) <= 0
1352*c87b03e5Sespie 			|| !flag_ra_ir_spilling)
1353*c87b03e5Sespie 		      {
1354*c87b03e5Sespie 			ri.needed_loads[ri.nl_size++] = web;
1355*c87b03e5Sespie 			web->in_load = 1;
1356*c87b03e5Sespie 			web->one_load = 1;
1357*c87b03e5Sespie 		      }
1358*c87b03e5Sespie 		    else if (!bitmap_bit_p (ri.need_reload, web->id))
1359*c87b03e5Sespie 		      {
1360*c87b03e5Sespie 		        bitmap_set_bit (ri.need_reload, web->id);
1361*c87b03e5Sespie 			ri.num_reloads++;
1362*c87b03e5Sespie 			web->one_load = 1;
1363*c87b03e5Sespie 		      }
1364*c87b03e5Sespie 		    else
1365*c87b03e5Sespie 		      web->one_load = 0;
1366*c87b03e5Sespie 		  }
1367*c87b03e5Sespie 		else
1368*c87b03e5Sespie 		  web->one_load = 0;
1369*c87b03e5Sespie 	      }
1370*c87b03e5Sespie 
1371*c87b03e5Sespie 	  if (GET_CODE (insn) == CODE_LABEL)
1372*c87b03e5Sespie 	    break;
1373*c87b03e5Sespie 	}
1374*c87b03e5Sespie 
1375*c87b03e5Sespie       nl_first_reload = ri.nl_size;
1376*c87b03e5Sespie       if (ri.num_reloads)
1377*c87b03e5Sespie 	{
1378*c87b03e5Sespie 	  int in_ir = 0;
1379*c87b03e5Sespie 	  edge e;
1380*c87b03e5Sespie 	  int num = 0;
1381*c87b03e5Sespie 	  HARD_REG_SET cum_colors, colors;
1382*c87b03e5Sespie 	  CLEAR_HARD_REG_SET (cum_colors);
1383*c87b03e5Sespie 	  for (e = bb->pred; e && num < 5; e = e->pred_next, num++)
1384*c87b03e5Sespie 	    {
1385*c87b03e5Sespie 	      int j;
1386*c87b03e5Sespie 	      CLEAR_HARD_REG_SET (colors);
1387*c87b03e5Sespie 	      EXECUTE_IF_SET_IN_BITMAP (live_at_end[e->src->index], 0, j,
1388*c87b03e5Sespie 		{
1389*c87b03e5Sespie 		  struct web *web = use2web[j];
1390*c87b03e5Sespie 		  struct web *aweb = alias (find_web_for_subweb (web));
1391*c87b03e5Sespie 		  if (aweb->type != SPILLED)
1392*c87b03e5Sespie 		    update_spill_colors (&colors, web, 1);
1393*c87b03e5Sespie 		});
1394*c87b03e5Sespie 	      IOR_HARD_REG_SET (cum_colors, colors);
1395*c87b03e5Sespie 	    }
1396*c87b03e5Sespie 	  if (num == 5)
1397*c87b03e5Sespie 	    in_ir = 1;
1398*c87b03e5Sespie 
1399*c87b03e5Sespie 	  bitmap_clear (ri.scratch);
1400*c87b03e5Sespie 	  EXECUTE_IF_SET_IN_BITMAP (ri.need_reload, 0, j,
1401*c87b03e5Sespie 	    {
1402*c87b03e5Sespie 	      struct web *web2 = ID2WEB (j);
1403*c87b03e5Sespie 	      struct web *supweb2 = find_web_for_subweb (web2);
1404*c87b03e5Sespie 	      struct web *aweb2 = alias (supweb2);
1405*c87b03e5Sespie 	      /* block entry is IR boundary for aweb2?
1406*c87b03e5Sespie 		 Currently more some tries for good conditions.  */
1407*c87b03e5Sespie 	      if (((ra_pass > 0 || supweb2->target_of_spilled_move)
1408*c87b03e5Sespie 		  && (1 || in_ir || spill_is_free (&cum_colors, aweb2) <= 0))
1409*c87b03e5Sespie 		  || (ra_pass == 1
1410*c87b03e5Sespie 		      && (in_ir
1411*c87b03e5Sespie 			  || spill_is_free (&cum_colors, aweb2) <= 0)))
1412*c87b03e5Sespie 		{
1413*c87b03e5Sespie 		  if (!web2->in_load)
1414*c87b03e5Sespie 		    {
1415*c87b03e5Sespie 		      ri.needed_loads[ri.nl_size++] = web2;
1416*c87b03e5Sespie 		      web2->in_load = 1;
1417*c87b03e5Sespie 		    }
1418*c87b03e5Sespie 		  bitmap_set_bit (ri.scratch, j);
1419*c87b03e5Sespie 		  ri.num_reloads--;
1420*c87b03e5Sespie 		}
1421*c87b03e5Sespie 	    });
1422*c87b03e5Sespie 	  bitmap_operation (ri.need_reload, ri.need_reload, ri.scratch,
1423*c87b03e5Sespie 			    BITMAP_AND_COMPL);
1424*c87b03e5Sespie 	}
1425*c87b03e5Sespie 
1426*c87b03e5Sespie       ri.need_load = 1;
1427*c87b03e5Sespie       emit_loads (&ri, nl_first_reload, last_block_insn);
1428*c87b03e5Sespie       if (ri.nl_size != 0 /*|| ri.num_reloads != 0*/)
1429*c87b03e5Sespie 	abort ();
1430*c87b03e5Sespie       if (!insn)
1431*c87b03e5Sespie 	break;
1432*c87b03e5Sespie     }
1433*c87b03e5Sespie   free (ri.needed_loads);
1434*c87b03e5Sespie   sbitmap_free (ri.live);
1435*c87b03e5Sespie   BITMAP_XFREE (ri.scratch);
1436*c87b03e5Sespie   BITMAP_XFREE (ri.need_reload);
1437*c87b03e5Sespie }
1438*c87b03e5Sespie 
1439*c87b03e5Sespie /* WEBS is a web conflicting with a spilled one.  Prepare it
1440*c87b03e5Sespie    to be able to rescan it in the next pass.  Mark all it's uses
1441*c87b03e5Sespie    for checking, and clear the some members of their web parts
1442*c87b03e5Sespie    (of defs and uses).  Notably don't clear the uplink.  We don't
1443*c87b03e5Sespie    change the layout of this web, just it's conflicts.
1444*c87b03e5Sespie    Also remember all IDs of its uses in USES_AS_BITMAP.  */
1445*c87b03e5Sespie 
1446*c87b03e5Sespie static void
mark_refs_for_checking(web,uses_as_bitmap)1447*c87b03e5Sespie mark_refs_for_checking (web, uses_as_bitmap)
1448*c87b03e5Sespie      struct web *web;
1449*c87b03e5Sespie      bitmap uses_as_bitmap;
1450*c87b03e5Sespie {
1451*c87b03e5Sespie   unsigned int i;
1452*c87b03e5Sespie   for (i = 0; i < web->num_uses; i++)
1453*c87b03e5Sespie     {
1454*c87b03e5Sespie       unsigned int id = DF_REF_ID (web->uses[i]);
1455*c87b03e5Sespie       SET_BIT (last_check_uses, id);
1456*c87b03e5Sespie       bitmap_set_bit (uses_as_bitmap, id);
1457*c87b03e5Sespie       web_parts[df->def_id + id].spanned_deaths = 0;
1458*c87b03e5Sespie       web_parts[df->def_id + id].crosses_call = 0;
1459*c87b03e5Sespie     }
1460*c87b03e5Sespie   for (i = 0; i < web->num_defs; i++)
1461*c87b03e5Sespie     {
1462*c87b03e5Sespie       unsigned int id = DF_REF_ID (web->defs[i]);
1463*c87b03e5Sespie       web_parts[id].spanned_deaths = 0;
1464*c87b03e5Sespie       web_parts[id].crosses_call = 0;
1465*c87b03e5Sespie     }
1466*c87b03e5Sespie }
1467*c87b03e5Sespie 
1468*c87b03e5Sespie /* The last step of the spill phase is to set up the structures for
1469*c87b03e5Sespie    incrementally rebuilding the interference graph.  We break up
1470*c87b03e5Sespie    the web part structure of all spilled webs, mark their uses for
1471*c87b03e5Sespie    rechecking, look at their neighbors, and clean up some global
1472*c87b03e5Sespie    information, we will rebuild.  */
1473*c87b03e5Sespie 
1474*c87b03e5Sespie static void
detect_web_parts_to_rebuild()1475*c87b03e5Sespie detect_web_parts_to_rebuild ()
1476*c87b03e5Sespie {
1477*c87b03e5Sespie   bitmap uses_as_bitmap;
1478*c87b03e5Sespie   unsigned int i, pass;
1479*c87b03e5Sespie   struct dlist *d;
1480*c87b03e5Sespie   sbitmap already_webs = sbitmap_alloc (num_webs);
1481*c87b03e5Sespie 
1482*c87b03e5Sespie   uses_as_bitmap = BITMAP_XMALLOC ();
1483*c87b03e5Sespie   if (last_check_uses)
1484*c87b03e5Sespie     sbitmap_free (last_check_uses);
1485*c87b03e5Sespie   last_check_uses = sbitmap_alloc (df->use_id);
1486*c87b03e5Sespie   sbitmap_zero (last_check_uses);
1487*c87b03e5Sespie   sbitmap_zero (already_webs);
1488*c87b03e5Sespie   /* We need to recheck all uses of all webs involved in spilling (and the
1489*c87b03e5Sespie      uses added by spill insns, but those are not analyzed yet).
1490*c87b03e5Sespie      Those are the spilled webs themself, webs coalesced to spilled ones,
1491*c87b03e5Sespie      and webs conflicting with any of them.  */
1492*c87b03e5Sespie   for (pass = 0; pass < 2; pass++)
1493*c87b03e5Sespie     for (d = (pass == 0) ? WEBS(SPILLED) : WEBS(COALESCED); d; d = d->next)
1494*c87b03e5Sespie       {
1495*c87b03e5Sespie         struct web *web = DLIST_WEB (d);
1496*c87b03e5Sespie 	struct conflict_link *wl;
1497*c87b03e5Sespie 	unsigned int j;
1498*c87b03e5Sespie 	/* This check is only needed for coalesced nodes, but hey.  */
1499*c87b03e5Sespie 	if (alias (web)->type != SPILLED)
1500*c87b03e5Sespie 	  continue;
1501*c87b03e5Sespie 
1502*c87b03e5Sespie 	/* For the spilled web itself we also need to clear it's
1503*c87b03e5Sespie 	   uplink, to be able to rebuild smaller webs.  After all
1504*c87b03e5Sespie 	   spilling has split the web.  */
1505*c87b03e5Sespie         for (i = 0; i < web->num_uses; i++)
1506*c87b03e5Sespie 	  {
1507*c87b03e5Sespie 	    unsigned int id = DF_REF_ID (web->uses[i]);
1508*c87b03e5Sespie 	    SET_BIT (last_check_uses, id);
1509*c87b03e5Sespie 	    bitmap_set_bit (uses_as_bitmap, id);
1510*c87b03e5Sespie 	    web_parts[df->def_id + id].uplink = NULL;
1511*c87b03e5Sespie 	    web_parts[df->def_id + id].spanned_deaths = 0;
1512*c87b03e5Sespie 	    web_parts[df->def_id + id].crosses_call = 0;
1513*c87b03e5Sespie 	  }
1514*c87b03e5Sespie 	for (i = 0; i < web->num_defs; i++)
1515*c87b03e5Sespie 	  {
1516*c87b03e5Sespie 	    unsigned int id = DF_REF_ID (web->defs[i]);
1517*c87b03e5Sespie 	    web_parts[id].uplink = NULL;
1518*c87b03e5Sespie 	    web_parts[id].spanned_deaths = 0;
1519*c87b03e5Sespie 	    web_parts[id].crosses_call = 0;
1520*c87b03e5Sespie 	  }
1521*c87b03e5Sespie 
1522*c87b03e5Sespie 	/* Now look at all neighbors of this spilled web.  */
1523*c87b03e5Sespie 	if (web->have_orig_conflicts)
1524*c87b03e5Sespie 	  wl = web->orig_conflict_list;
1525*c87b03e5Sespie 	else
1526*c87b03e5Sespie 	  wl = web->conflict_list;
1527*c87b03e5Sespie 	for (; wl; wl = wl->next)
1528*c87b03e5Sespie 	  {
1529*c87b03e5Sespie 	    if (TEST_BIT (already_webs, wl->t->id))
1530*c87b03e5Sespie 	      continue;
1531*c87b03e5Sespie 	    SET_BIT (already_webs, wl->t->id);
1532*c87b03e5Sespie 	    mark_refs_for_checking (wl->t, uses_as_bitmap);
1533*c87b03e5Sespie 	  }
1534*c87b03e5Sespie 	EXECUTE_IF_SET_IN_BITMAP (web->useless_conflicts, 0, j,
1535*c87b03e5Sespie 	  {
1536*c87b03e5Sespie 	    struct web *web2 = ID2WEB (j);
1537*c87b03e5Sespie 	    if (TEST_BIT (already_webs, web2->id))
1538*c87b03e5Sespie 	      continue;
1539*c87b03e5Sespie 	    SET_BIT (already_webs, web2->id);
1540*c87b03e5Sespie 	    mark_refs_for_checking (web2, uses_as_bitmap);
1541*c87b03e5Sespie 	  });
1542*c87b03e5Sespie       }
1543*c87b03e5Sespie 
1544*c87b03e5Sespie   /* We also recheck unconditionally all uses of any hardregs.  This means
1545*c87b03e5Sespie      we _can_ delete all these uses from the live_at_end[] bitmaps.
1546*c87b03e5Sespie      And because we sometimes delete insn refering to hardregs (when
1547*c87b03e5Sespie      they became useless because they setup a rematerializable pseudo, which
1548*c87b03e5Sespie      then was rematerialized), some of those uses will go away with the next
1549*c87b03e5Sespie      df_analyse().  This means we even _must_ delete those uses from
1550*c87b03e5Sespie      the live_at_end[] bitmaps.  For simplicity we simply delete
1551*c87b03e5Sespie      all of them.  */
1552*c87b03e5Sespie   for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
1553*c87b03e5Sespie     if (!fixed_regs[i])
1554*c87b03e5Sespie       {
1555*c87b03e5Sespie 	struct df_link *link;
1556*c87b03e5Sespie 	for (link = df->regs[i].uses; link; link = link->next)
1557*c87b03e5Sespie 	  if (link->ref)
1558*c87b03e5Sespie 	    bitmap_set_bit (uses_as_bitmap, DF_REF_ID (link->ref));
1559*c87b03e5Sespie       }
1560*c87b03e5Sespie 
1561*c87b03e5Sespie   /* The information in live_at_end[] will be rebuild for all uses
1562*c87b03e5Sespie      we recheck, so clear it here (the uses of spilled webs, might
1563*c87b03e5Sespie      indeed not become member of it again).  */
1564*c87b03e5Sespie   live_at_end -= 2;
1565*c87b03e5Sespie   for (i = 0; i < (unsigned int) last_basic_block + 2; i++)
1566*c87b03e5Sespie     bitmap_operation (live_at_end[i], live_at_end[i], uses_as_bitmap,
1567*c87b03e5Sespie 		      BITMAP_AND_COMPL);
1568*c87b03e5Sespie   live_at_end += 2;
1569*c87b03e5Sespie 
1570*c87b03e5Sespie   if (rtl_dump_file && (debug_new_regalloc & DUMP_REBUILD) != 0)
1571*c87b03e5Sespie     {
1572*c87b03e5Sespie       ra_debug_msg (DUMP_REBUILD, "need to check these uses:\n");
1573*c87b03e5Sespie       dump_sbitmap_file (rtl_dump_file, last_check_uses);
1574*c87b03e5Sespie     }
1575*c87b03e5Sespie   sbitmap_free (already_webs);
1576*c87b03e5Sespie   BITMAP_XFREE (uses_as_bitmap);
1577*c87b03e5Sespie }
1578*c87b03e5Sespie 
1579*c87b03e5Sespie /* Statistics about deleted insns, which are useless now.  */
1580*c87b03e5Sespie static unsigned int deleted_def_insns;
1581*c87b03e5Sespie static unsigned HOST_WIDE_INT deleted_def_cost;
1582*c87b03e5Sespie 
1583*c87b03e5Sespie /* In rewrite_program2() we noticed, when a certain insn set a pseudo
1584*c87b03e5Sespie    which wasn't live.  Try to delete all those insns.  */
1585*c87b03e5Sespie 
1586*c87b03e5Sespie static void
delete_useless_defs()1587*c87b03e5Sespie delete_useless_defs ()
1588*c87b03e5Sespie {
1589*c87b03e5Sespie   unsigned int i;
1590*c87b03e5Sespie   /* If the insn only sets the def without any sideeffect (besides
1591*c87b03e5Sespie      clobbers or uses), we can delete it.  single_set() also tests
1592*c87b03e5Sespie      for INSN_P(insn).  */
1593*c87b03e5Sespie   EXECUTE_IF_SET_IN_BITMAP (useless_defs, 0, i,
1594*c87b03e5Sespie     {
1595*c87b03e5Sespie       rtx insn = DF_REF_INSN (df->defs[i]);
1596*c87b03e5Sespie       rtx set = single_set (insn);
1597*c87b03e5Sespie       struct web *web = find_web_for_subweb (def2web[i]);
1598*c87b03e5Sespie       if (set && web->type == SPILLED && web->stack_slot == NULL)
1599*c87b03e5Sespie         {
1600*c87b03e5Sespie 	  deleted_def_insns++;
1601*c87b03e5Sespie 	  deleted_def_cost += BLOCK_FOR_INSN (insn)->frequency + 1;
1602*c87b03e5Sespie 	  PUT_CODE (insn, NOTE);
1603*c87b03e5Sespie 	  NOTE_LINE_NUMBER (insn) = NOTE_INSN_DELETED;
1604*c87b03e5Sespie 	  df_insn_modify (df, BLOCK_FOR_INSN (insn), insn);
1605*c87b03e5Sespie 	}
1606*c87b03e5Sespie     });
1607*c87b03e5Sespie }
1608*c87b03e5Sespie 
1609*c87b03e5Sespie /* Look for spilled webs, on whose behalf no insns were emitted.
1610*c87b03e5Sespie    We inversify (sp?) the changed flag of the webs, so after this function
1611*c87b03e5Sespie    a nonzero changed flag means, that this web was not spillable (at least
1612*c87b03e5Sespie    in this pass).  */
1613*c87b03e5Sespie 
1614*c87b03e5Sespie static void
detect_non_changed_webs()1615*c87b03e5Sespie detect_non_changed_webs ()
1616*c87b03e5Sespie {
1617*c87b03e5Sespie   struct dlist *d, *d_next;
1618*c87b03e5Sespie   for (d = WEBS(SPILLED); d; d = d_next)
1619*c87b03e5Sespie     {
1620*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
1621*c87b03e5Sespie       d_next = d->next;
1622*c87b03e5Sespie       if (!web->changed)
1623*c87b03e5Sespie 	{
1624*c87b03e5Sespie 	  ra_debug_msg (DUMP_PROCESS, "no insns emitted for spilled web %d\n",
1625*c87b03e5Sespie 		     web->id);
1626*c87b03e5Sespie 	  remove_web_from_list (web);
1627*c87b03e5Sespie 	  put_web (web, COLORED);
1628*c87b03e5Sespie 	  web->changed = 1;
1629*c87b03e5Sespie 	}
1630*c87b03e5Sespie       else
1631*c87b03e5Sespie 	web->changed = 0;
1632*c87b03e5Sespie       /* From now on web->changed is used as the opposite flag.
1633*c87b03e5Sespie 	 I.e. colored webs, which have changed set were formerly
1634*c87b03e5Sespie 	 spilled webs for which no insns were emitted.  */
1635*c87b03e5Sespie     }
1636*c87b03e5Sespie }
1637*c87b03e5Sespie 
1638*c87b03e5Sespie /* Before spilling we clear the changed flags for all spilled webs.  */
1639*c87b03e5Sespie 
1640*c87b03e5Sespie static void
reset_changed_flag()1641*c87b03e5Sespie reset_changed_flag ()
1642*c87b03e5Sespie {
1643*c87b03e5Sespie   struct dlist *d;
1644*c87b03e5Sespie   for (d = WEBS(SPILLED); d; d = d->next)
1645*c87b03e5Sespie     DLIST_WEB(d)->changed = 0;
1646*c87b03e5Sespie }
1647*c87b03e5Sespie 
1648*c87b03e5Sespie /* The toplevel function for this file.  Given a colorized graph,
1649*c87b03e5Sespie    and lists of spilled, coalesced and colored webs, we add some
1650*c87b03e5Sespie    spill code.  This also sets up the structures for incrementally
1651*c87b03e5Sespie    building the interference graph in the next pass.  */
1652*c87b03e5Sespie 
1653*c87b03e5Sespie void
actual_spill()1654*c87b03e5Sespie actual_spill ()
1655*c87b03e5Sespie {
1656*c87b03e5Sespie   int i;
1657*c87b03e5Sespie   bitmap new_deaths = BITMAP_XMALLOC ();
1658*c87b03e5Sespie   reset_changed_flag ();
1659*c87b03e5Sespie   spill_coalprop ();
1660*c87b03e5Sespie   choose_spill_colors ();
1661*c87b03e5Sespie   useless_defs = BITMAP_XMALLOC ();
1662*c87b03e5Sespie   if (flag_ra_improved_spilling)
1663*c87b03e5Sespie     rewrite_program2 (new_deaths);
1664*c87b03e5Sespie   else
1665*c87b03e5Sespie     rewrite_program (new_deaths);
1666*c87b03e5Sespie   insert_stores (new_deaths);
1667*c87b03e5Sespie   delete_useless_defs ();
1668*c87b03e5Sespie   BITMAP_XFREE (useless_defs);
1669*c87b03e5Sespie   sbitmap_free (insns_with_deaths);
1670*c87b03e5Sespie   insns_with_deaths = sbitmap_alloc (get_max_uid ());
1671*c87b03e5Sespie   death_insns_max_uid = get_max_uid ();
1672*c87b03e5Sespie   sbitmap_zero (insns_with_deaths);
1673*c87b03e5Sespie   EXECUTE_IF_SET_IN_BITMAP (new_deaths, 0, i,
1674*c87b03e5Sespie     { SET_BIT (insns_with_deaths, i);});
1675*c87b03e5Sespie   detect_non_changed_webs ();
1676*c87b03e5Sespie   detect_web_parts_to_rebuild ();
1677*c87b03e5Sespie   BITMAP_XFREE (new_deaths);
1678*c87b03e5Sespie }
1679*c87b03e5Sespie 
1680*c87b03e5Sespie /* A bitmap of pseudo reg numbers which are coalesced directly
1681*c87b03e5Sespie    to a hardreg.  Set in emit_colors(), used and freed in
1682*c87b03e5Sespie    remove_suspicious_death_notes().  */
1683*c87b03e5Sespie static bitmap regnos_coalesced_to_hardregs;
1684*c87b03e5Sespie 
1685*c87b03e5Sespie /* Create new pseudos for each web we colored, change insns to
1686*c87b03e5Sespie    use those pseudos and set up ra_reg_renumber.  */
1687*c87b03e5Sespie 
1688*c87b03e5Sespie void
emit_colors(df)1689*c87b03e5Sespie emit_colors (df)
1690*c87b03e5Sespie      struct df *df;
1691*c87b03e5Sespie {
1692*c87b03e5Sespie   unsigned int i;
1693*c87b03e5Sespie   int si;
1694*c87b03e5Sespie   struct web *web;
1695*c87b03e5Sespie   int old_max_regno = max_reg_num ();
1696*c87b03e5Sespie   regset old_regs;
1697*c87b03e5Sespie   basic_block bb;
1698*c87b03e5Sespie 
1699*c87b03e5Sespie   /* This bitmap is freed in remove_suspicious_death_notes(),
1700*c87b03e5Sespie      which is also the user of it.  */
1701*c87b03e5Sespie   regnos_coalesced_to_hardregs = BITMAP_XMALLOC ();
1702*c87b03e5Sespie   /* First create the (REG xx) rtx's for all webs, as we need to know
1703*c87b03e5Sespie      the number, to make sure, flow has enough memory for them in the
1704*c87b03e5Sespie      various tables.  */
1705*c87b03e5Sespie   for (i = 0; i < num_webs - num_subwebs; i++)
1706*c87b03e5Sespie     {
1707*c87b03e5Sespie       web = ID2WEB (i);
1708*c87b03e5Sespie       if (web->type != COLORED && web->type != COALESCED)
1709*c87b03e5Sespie 	continue;
1710*c87b03e5Sespie       if (web->type == COALESCED && alias (web)->type == COLORED)
1711*c87b03e5Sespie 	continue;
1712*c87b03e5Sespie       if (web->reg_rtx || web->regno < FIRST_PSEUDO_REGISTER)
1713*c87b03e5Sespie 	abort ();
1714*c87b03e5Sespie 
1715*c87b03e5Sespie       if (web->regno >= max_normal_pseudo)
1716*c87b03e5Sespie 	{
1717*c87b03e5Sespie 	  rtx place;
1718*c87b03e5Sespie 	  if (web->color == an_unusable_color)
1719*c87b03e5Sespie 	    {
1720*c87b03e5Sespie 	      unsigned int inherent_size = PSEUDO_REGNO_BYTES (web->regno);
1721*c87b03e5Sespie 	      unsigned int total_size = MAX (inherent_size, 0);
1722*c87b03e5Sespie 	      place = assign_stack_local (PSEUDO_REGNO_MODE (web->regno),
1723*c87b03e5Sespie 					  total_size,
1724*c87b03e5Sespie 					  inherent_size == total_size ? 0 : -1);
1725*c87b03e5Sespie 	      RTX_UNCHANGING_P (place) =
1726*c87b03e5Sespie 		  RTX_UNCHANGING_P (regno_reg_rtx[web->regno]);
1727*c87b03e5Sespie 	      set_mem_alias_set (place, new_alias_set ());
1728*c87b03e5Sespie 	    }
1729*c87b03e5Sespie 	  else
1730*c87b03e5Sespie 	    {
1731*c87b03e5Sespie 	      place = gen_reg_rtx (PSEUDO_REGNO_MODE (web->regno));
1732*c87b03e5Sespie 	    }
1733*c87b03e5Sespie 	  web->reg_rtx = place;
1734*c87b03e5Sespie 	}
1735*c87b03e5Sespie       else
1736*c87b03e5Sespie 	{
1737*c87b03e5Sespie 	  /* Special case for i386 'fix_truncdi_nomemory' insn.
1738*c87b03e5Sespie 	     We must choose mode from insns not from PSEUDO_REGNO_MODE.
1739*c87b03e5Sespie 	     Actual only for clobbered register.  */
1740*c87b03e5Sespie 	  if (web->num_uses == 0 && web->num_defs == 1)
1741*c87b03e5Sespie 	    web->reg_rtx = gen_reg_rtx (GET_MODE (DF_REF_REAL_REG (web->defs[0])));
1742*c87b03e5Sespie 	  else
1743*c87b03e5Sespie 	    web->reg_rtx = gen_reg_rtx (PSEUDO_REGNO_MODE (web->regno));
1744*c87b03e5Sespie 	  /* Remember the different parts directly coalesced to a hardreg.  */
1745*c87b03e5Sespie 	  if (web->type == COALESCED)
1746*c87b03e5Sespie 	    bitmap_set_bit (regnos_coalesced_to_hardregs, REGNO (web->reg_rtx));
1747*c87b03e5Sespie 	}
1748*c87b03e5Sespie     }
1749*c87b03e5Sespie   ra_max_regno = max_regno = max_reg_num ();
1750*c87b03e5Sespie   allocate_reg_info (max_regno, FALSE, FALSE);
1751*c87b03e5Sespie   ra_reg_renumber = (short *) xmalloc (max_regno * sizeof (short));
1752*c87b03e5Sespie   for (si = 0; si < max_regno; si++)
1753*c87b03e5Sespie     ra_reg_renumber[si] = -1;
1754*c87b03e5Sespie 
1755*c87b03e5Sespie   /* Then go through all references, and replace them by a new
1756*c87b03e5Sespie      pseudoreg for each web.  All uses.  */
1757*c87b03e5Sespie   /* XXX
1758*c87b03e5Sespie      Beware: The order of replacements (first uses, then defs) matters only
1759*c87b03e5Sespie      for read-mod-write insns, where the RTL expression for the REG is
1760*c87b03e5Sespie      shared between def and use.  For normal rmw insns we connected all such
1761*c87b03e5Sespie      webs, i.e. both the use and the def (which are the same memory)
1762*c87b03e5Sespie      there get the same new pseudo-reg, so order would not matter.
1763*c87b03e5Sespie      _However_ we did not connect webs, were the read cycle was an
1764*c87b03e5Sespie      uninitialized read.  If we now would first replace the def reference
1765*c87b03e5Sespie      and then the use ref, we would initialize it with a REG rtx, which
1766*c87b03e5Sespie      gets never initialized, and yet more wrong, which would overwrite
1767*c87b03e5Sespie      the definition of the other REG rtx.  So we must replace the defs last.
1768*c87b03e5Sespie    */
1769*c87b03e5Sespie   for (i = 0; i < df->use_id; i++)
1770*c87b03e5Sespie     if (df->uses[i])
1771*c87b03e5Sespie       {
1772*c87b03e5Sespie 	regset rs = DF_REF_BB (df->uses[i])->global_live_at_start;
1773*c87b03e5Sespie 	rtx regrtx;
1774*c87b03e5Sespie 	web = use2web[i];
1775*c87b03e5Sespie 	web = find_web_for_subweb (web);
1776*c87b03e5Sespie 	if (web->type != COLORED && web->type != COALESCED)
1777*c87b03e5Sespie 	  continue;
1778*c87b03e5Sespie 	regrtx = alias (web)->reg_rtx;
1779*c87b03e5Sespie 	if (!regrtx)
1780*c87b03e5Sespie 	  regrtx = web->reg_rtx;
1781*c87b03e5Sespie 	*DF_REF_REAL_LOC (df->uses[i]) = regrtx;
1782*c87b03e5Sespie 	if (REGNO_REG_SET_P (rs, web->regno) && REG_P (regrtx))
1783*c87b03e5Sespie 	  {
1784*c87b03e5Sespie 	    /*CLEAR_REGNO_REG_SET (rs, web->regno);*/
1785*c87b03e5Sespie 	    SET_REGNO_REG_SET (rs, REGNO (regrtx));
1786*c87b03e5Sespie 	  }
1787*c87b03e5Sespie       }
1788*c87b03e5Sespie 
1789*c87b03e5Sespie   /* And all defs.  */
1790*c87b03e5Sespie   for (i = 0; i < df->def_id; i++)
1791*c87b03e5Sespie     {
1792*c87b03e5Sespie       regset rs;
1793*c87b03e5Sespie       rtx regrtx;
1794*c87b03e5Sespie       if (!df->defs[i])
1795*c87b03e5Sespie 	continue;
1796*c87b03e5Sespie       rs = DF_REF_BB (df->defs[i])->global_live_at_start;
1797*c87b03e5Sespie       web = def2web[i];
1798*c87b03e5Sespie       web = find_web_for_subweb (web);
1799*c87b03e5Sespie       if (web->type != COLORED && web->type != COALESCED)
1800*c87b03e5Sespie 	continue;
1801*c87b03e5Sespie       regrtx = alias (web)->reg_rtx;
1802*c87b03e5Sespie       if (!regrtx)
1803*c87b03e5Sespie 	regrtx = web->reg_rtx;
1804*c87b03e5Sespie       *DF_REF_REAL_LOC (df->defs[i]) = regrtx;
1805*c87b03e5Sespie       if (REGNO_REG_SET_P (rs, web->regno) && REG_P (regrtx))
1806*c87b03e5Sespie 	{
1807*c87b03e5Sespie 	  /* Don't simply clear the current regno, as it might be
1808*c87b03e5Sespie 	     replaced by two webs.  */
1809*c87b03e5Sespie           /*CLEAR_REGNO_REG_SET (rs, web->regno);*/
1810*c87b03e5Sespie           SET_REGNO_REG_SET (rs, REGNO (regrtx));
1811*c87b03e5Sespie 	}
1812*c87b03e5Sespie     }
1813*c87b03e5Sespie 
1814*c87b03e5Sespie   /* And now set up the ra_reg_renumber array for reload with all the new
1815*c87b03e5Sespie      pseudo-regs.  */
1816*c87b03e5Sespie   for (i = 0; i < num_webs - num_subwebs; i++)
1817*c87b03e5Sespie     {
1818*c87b03e5Sespie       web = ID2WEB (i);
1819*c87b03e5Sespie       if (web->reg_rtx && REG_P (web->reg_rtx))
1820*c87b03e5Sespie 	{
1821*c87b03e5Sespie 	  int r = REGNO (web->reg_rtx);
1822*c87b03e5Sespie           ra_reg_renumber[r] = web->color;
1823*c87b03e5Sespie           ra_debug_msg (DUMP_COLORIZE, "Renumber pseudo %d (== web %d) to %d\n",
1824*c87b03e5Sespie 		     r, web->id, ra_reg_renumber[r]);
1825*c87b03e5Sespie 	}
1826*c87b03e5Sespie     }
1827*c87b03e5Sespie 
1828*c87b03e5Sespie   old_regs = BITMAP_XMALLOC ();
1829*c87b03e5Sespie   for (si = FIRST_PSEUDO_REGISTER; si < old_max_regno; si++)
1830*c87b03e5Sespie     SET_REGNO_REG_SET (old_regs, si);
1831*c87b03e5Sespie   FOR_EACH_BB (bb)
1832*c87b03e5Sespie     {
1833*c87b03e5Sespie       AND_COMPL_REG_SET (bb->global_live_at_start, old_regs);
1834*c87b03e5Sespie       AND_COMPL_REG_SET (bb->global_live_at_end, old_regs);
1835*c87b03e5Sespie     }
1836*c87b03e5Sespie   BITMAP_XFREE (old_regs);
1837*c87b03e5Sespie }
1838*c87b03e5Sespie 
1839*c87b03e5Sespie /* Delete some coalesced moves from the insn stream.  */
1840*c87b03e5Sespie 
1841*c87b03e5Sespie void
delete_moves()1842*c87b03e5Sespie delete_moves ()
1843*c87b03e5Sespie {
1844*c87b03e5Sespie   struct move_list *ml;
1845*c87b03e5Sespie   struct web *s, *t;
1846*c87b03e5Sespie   /* XXX Beware: We normally would test here each copy insn, if
1847*c87b03e5Sespie      source and target got the same color (either by coalescing or by pure
1848*c87b03e5Sespie      luck), and then delete it.
1849*c87b03e5Sespie      This will currently not work.  One problem is, that we don't color
1850*c87b03e5Sespie      the regs ourself, but instead defer to reload.  So the colorization
1851*c87b03e5Sespie      is only a kind of suggestion, which reload doesn't have to follow.
1852*c87b03e5Sespie      For webs which are coalesced to a normal colored web, we only have one
1853*c87b03e5Sespie      new pseudo, so in this case we indeed can delete copy insns involving
1854*c87b03e5Sespie      those (because even if reload colors them different from our suggestion,
1855*c87b03e5Sespie      it still has to color them the same, as only one pseudo exists).  But for
1856*c87b03e5Sespie      webs coalesced to precolored ones, we have not a single pseudo, but
1857*c87b03e5Sespie      instead one for each coalesced web.  This means, that we can't delete
1858*c87b03e5Sespie      copy insns, where source and target are webs coalesced to precolored
1859*c87b03e5Sespie      ones, because then the connection between both webs is destroyed.  Note
1860*c87b03e5Sespie      that this not only means copy insns, where one side is the precolored one
1861*c87b03e5Sespie      itself, but also those between webs which are coalesced to one color.
1862*c87b03e5Sespie      Also because reload we can't delete copy insns which involve any
1863*c87b03e5Sespie      precolored web at all.  These often have also special meaning (e.g.
1864*c87b03e5Sespie      copying a return value of a call to a pseudo, or copying pseudo to the
1865*c87b03e5Sespie      return register), and the deletion would confuse reload in thinking the
1866*c87b03e5Sespie      pseudo isn't needed.  One of those days reload will get away and we can
1867*c87b03e5Sespie      do everything we want.
1868*c87b03e5Sespie      In effect because of the later reload, we can't base our deletion on the
1869*c87b03e5Sespie      colors itself, but instead need to base them on the newly created
1870*c87b03e5Sespie      pseudos.  */
1871*c87b03e5Sespie   for (ml = wl_moves; ml; ml = ml->next)
1872*c87b03e5Sespie     /* The real condition we would ideally use is: s->color == t->color.
1873*c87b03e5Sespie        Additionally: s->type != PRECOLORED && t->type != PRECOLORED, in case
1874*c87b03e5Sespie        we want to prevent deletion of "special" copies.  */
1875*c87b03e5Sespie     if (ml->move
1876*c87b03e5Sespie 	&& (s = alias (ml->move->source_web))->reg_rtx
1877*c87b03e5Sespie 	    == (t = alias (ml->move->target_web))->reg_rtx
1878*c87b03e5Sespie 	&& s->type != PRECOLORED && t->type != PRECOLORED)
1879*c87b03e5Sespie       {
1880*c87b03e5Sespie 	basic_block bb = BLOCK_FOR_INSN (ml->move->insn);
1881*c87b03e5Sespie 	df_insn_delete (df, bb, ml->move->insn);
1882*c87b03e5Sespie 	deleted_move_insns++;
1883*c87b03e5Sespie 	deleted_move_cost += bb->frequency + 1;
1884*c87b03e5Sespie       }
1885*c87b03e5Sespie }
1886*c87b03e5Sespie 
1887*c87b03e5Sespie /* Due to resons documented elsewhere we create different pseudos
1888*c87b03e5Sespie    for all webs coalesced to hardregs.  For these parts life_analysis()
1889*c87b03e5Sespie    might have added REG_DEAD notes without considering, that only this part
1890*c87b03e5Sespie    but not the whole coalesced web dies.  The RTL is correct, there is no
1891*c87b03e5Sespie    coalescing yet.  But if later reload's alter_reg() substitutes the
1892*c87b03e5Sespie    hardreg into the REG rtx it looks like that particular hardreg dies here,
1893*c87b03e5Sespie    although (due to coalescing) it still is live.  This might make different
1894*c87b03e5Sespie    places of reload think, it can use that hardreg for reload regs,
1895*c87b03e5Sespie    accidentally overwriting it.  So we need to remove those REG_DEAD notes.
1896*c87b03e5Sespie    (Or better teach life_analysis() and reload about our coalescing, but
1897*c87b03e5Sespie    that comes later) Bah.  */
1898*c87b03e5Sespie 
1899*c87b03e5Sespie void
remove_suspicious_death_notes()1900*c87b03e5Sespie remove_suspicious_death_notes ()
1901*c87b03e5Sespie {
1902*c87b03e5Sespie   rtx insn;
1903*c87b03e5Sespie   for (insn = get_insns(); insn; insn = NEXT_INSN (insn))
1904*c87b03e5Sespie     if (INSN_P (insn))
1905*c87b03e5Sespie       {
1906*c87b03e5Sespie 	rtx *pnote = &REG_NOTES (insn);
1907*c87b03e5Sespie 	while (*pnote)
1908*c87b03e5Sespie 	  {
1909*c87b03e5Sespie 	    rtx note = *pnote;
1910*c87b03e5Sespie 	    if ((REG_NOTE_KIND (note) == REG_DEAD
1911*c87b03e5Sespie 		 || REG_NOTE_KIND (note) == REG_UNUSED)
1912*c87b03e5Sespie 		&& (GET_CODE (XEXP (note, 0)) == REG
1913*c87b03e5Sespie 		    && bitmap_bit_p (regnos_coalesced_to_hardregs,
1914*c87b03e5Sespie 				     REGNO (XEXP (note, 0)))))
1915*c87b03e5Sespie 	      *pnote = XEXP (note, 1);
1916*c87b03e5Sespie 	    else
1917*c87b03e5Sespie 	      pnote = &XEXP (*pnote, 1);
1918*c87b03e5Sespie 	  }
1919*c87b03e5Sespie       }
1920*c87b03e5Sespie   BITMAP_XFREE (regnos_coalesced_to_hardregs);
1921*c87b03e5Sespie   regnos_coalesced_to_hardregs = NULL;
1922*c87b03e5Sespie }
1923*c87b03e5Sespie 
1924*c87b03e5Sespie /* Allocate space for max_reg_num() pseudo registers, and
1925*c87b03e5Sespie    fill reg_renumber[] from ra_reg_renumber[].  If FREE_IT
1926*c87b03e5Sespie    is nonzero, also free ra_reg_renumber and reset ra_max_regno.  */
1927*c87b03e5Sespie 
1928*c87b03e5Sespie void
setup_renumber(free_it)1929*c87b03e5Sespie setup_renumber (free_it)
1930*c87b03e5Sespie      int free_it;
1931*c87b03e5Sespie {
1932*c87b03e5Sespie   int i;
1933*c87b03e5Sespie   max_regno = max_reg_num ();
1934*c87b03e5Sespie   allocate_reg_info (max_regno, FALSE, TRUE);
1935*c87b03e5Sespie   for (i = 0; i < max_regno; i++)
1936*c87b03e5Sespie     {
1937*c87b03e5Sespie       reg_renumber[i] = (i < ra_max_regno) ? ra_reg_renumber[i] : -1;
1938*c87b03e5Sespie     }
1939*c87b03e5Sespie   if (free_it)
1940*c87b03e5Sespie     {
1941*c87b03e5Sespie       free (ra_reg_renumber);
1942*c87b03e5Sespie       ra_reg_renumber = NULL;
1943*c87b03e5Sespie       ra_max_regno = 0;
1944*c87b03e5Sespie     }
1945*c87b03e5Sespie }
1946*c87b03e5Sespie 
1947*c87b03e5Sespie /* Dump the costs and savings due to spilling, i.e. of added spill insns
1948*c87b03e5Sespie    and removed moves or useless defs.  */
1949*c87b03e5Sespie 
1950*c87b03e5Sespie void
dump_cost(level)1951*c87b03e5Sespie dump_cost (level)
1952*c87b03e5Sespie      unsigned int level;
1953*c87b03e5Sespie {
1954*c87b03e5Sespie   ra_debug_msg (level, "Instructions for spilling\n added:\n");
1955*c87b03e5Sespie   ra_debug_msg (level, "  loads =%d cost=", emitted_spill_loads);
1956*c87b03e5Sespie   ra_debug_msg (level, HOST_WIDE_INT_PRINT_UNSIGNED, spill_load_cost);
1957*c87b03e5Sespie   ra_debug_msg (level, "\n  stores=%d cost=", emitted_spill_stores);
1958*c87b03e5Sespie   ra_debug_msg (level, HOST_WIDE_INT_PRINT_UNSIGNED, spill_store_cost);
1959*c87b03e5Sespie   ra_debug_msg (level, "\n  remat =%d cost=", emitted_remat);
1960*c87b03e5Sespie   ra_debug_msg (level, HOST_WIDE_INT_PRINT_UNSIGNED, spill_remat_cost);
1961*c87b03e5Sespie   ra_debug_msg (level, "\n removed:\n  moves =%d cost=", deleted_move_insns);
1962*c87b03e5Sespie   ra_debug_msg (level, HOST_WIDE_INT_PRINT_UNSIGNED, deleted_move_cost);
1963*c87b03e5Sespie   ra_debug_msg (level, "\n  others=%d cost=", deleted_def_insns);
1964*c87b03e5Sespie   ra_debug_msg (level, HOST_WIDE_INT_PRINT_UNSIGNED, deleted_def_cost);
1965*c87b03e5Sespie   ra_debug_msg (level, "\n");
1966*c87b03e5Sespie }
1967*c87b03e5Sespie 
1968*c87b03e5Sespie /* Initialization of the rewrite phase.  */
1969*c87b03e5Sespie 
1970*c87b03e5Sespie void
ra_rewrite_init()1971*c87b03e5Sespie ra_rewrite_init ()
1972*c87b03e5Sespie {
1973*c87b03e5Sespie   emitted_spill_loads = 0;
1974*c87b03e5Sespie   emitted_spill_stores = 0;
1975*c87b03e5Sespie   emitted_remat = 0;
1976*c87b03e5Sespie   spill_load_cost = 0;
1977*c87b03e5Sespie   spill_store_cost = 0;
1978*c87b03e5Sespie   spill_remat_cost = 0;
1979*c87b03e5Sespie   deleted_move_insns = 0;
1980*c87b03e5Sespie   deleted_move_cost = 0;
1981*c87b03e5Sespie   deleted_def_insns = 0;
1982*c87b03e5Sespie   deleted_def_cost = 0;
1983*c87b03e5Sespie }
1984*c87b03e5Sespie 
1985*c87b03e5Sespie /*
1986*c87b03e5Sespie vim:cinoptions={.5s,g0,p5,t0,(0,^-0.5s,n-0.5s:tw=78:cindent:sw=4:
1987*c87b03e5Sespie */
1988