xref: /openbsd/gnu/usr.bin/gcc/gcc/ra-build.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 "insn-config.h"
26*c87b03e5Sespie #include "recog.h"
27*c87b03e5Sespie #include "reload.h"
28*c87b03e5Sespie #include "function.h"
29*c87b03e5Sespie #include "regs.h"
30*c87b03e5Sespie #include "hard-reg-set.h"
31*c87b03e5Sespie #include "basic-block.h"
32*c87b03e5Sespie #include "df.h"
33*c87b03e5Sespie #include "output.h"
34*c87b03e5Sespie #include "ggc.h"
35*c87b03e5Sespie #include "ra.h"
36*c87b03e5Sespie 
37*c87b03e5Sespie /* This file is part of the graph coloring register alloctor.
38*c87b03e5Sespie    It deals with building the interference graph.  When rebuilding
39*c87b03e5Sespie    the graph for a function after spilling, we rebuild only those
40*c87b03e5Sespie    parts needed, i.e. it works incrementally.
41*c87b03e5Sespie 
42*c87b03e5Sespie    The first part (the functions called from build_web_parts_and_conflicts()
43*c87b03e5Sespie    ) constructs a web_part for each pseudo register reference in the insn
44*c87b03e5Sespie    stream, then goes backward from each use, until it reaches defs for that
45*c87b03e5Sespie    pseudo.  While going back it remember seen defs for other registers as
46*c87b03e5Sespie    conflicts.  By connecting the uses and defs, which reach each other, webs
47*c87b03e5Sespie    (or live ranges) are built conceptually.
48*c87b03e5Sespie 
49*c87b03e5Sespie    The second part (make_webs() and childs) deals with converting that
50*c87b03e5Sespie    structure to the nodes and edges, on which our interference graph is
51*c87b03e5Sespie    built.  For each root web part constructed above, an instance of struct
52*c87b03e5Sespie    web is created.  For all subregs of pseudos, which matter for allocation,
53*c87b03e5Sespie    a subweb of the corresponding super web is built.  Finally all the
54*c87b03e5Sespie    conflicts noted in the first part (as bitmaps) are transformed into real
55*c87b03e5Sespie    edges.
56*c87b03e5Sespie 
57*c87b03e5Sespie    As part of that process the webs are also classified (their spill cost
58*c87b03e5Sespie    is calculated, and if they are spillable at all, and if not, for what
59*c87b03e5Sespie    reason; or if they are rematerializable), and move insns are collected,
60*c87b03e5Sespie    which are potentially coalescable.
61*c87b03e5Sespie 
62*c87b03e5Sespie    The top-level entry of this file (build_i_graph) puts it all together,
63*c87b03e5Sespie    and leaves us with a complete interference graph, which just has to
64*c87b03e5Sespie    be colored.  */
65*c87b03e5Sespie 
66*c87b03e5Sespie 
67*c87b03e5Sespie struct curr_use;
68*c87b03e5Sespie 
69*c87b03e5Sespie static unsigned HOST_WIDE_INT rtx_to_undefined PARAMS ((rtx));
70*c87b03e5Sespie static bitmap find_sub_conflicts PARAMS ((struct web_part *, unsigned int));
71*c87b03e5Sespie static bitmap get_sub_conflicts PARAMS ((struct web_part *, unsigned int));
72*c87b03e5Sespie static unsigned int undef_to_size_word PARAMS ((rtx, unsigned HOST_WIDE_INT *));
73*c87b03e5Sespie static bitmap undef_to_bitmap PARAMS ((struct web_part *,
74*c87b03e5Sespie 				       unsigned HOST_WIDE_INT *));
75*c87b03e5Sespie static struct web_part * find_web_part_1 PARAMS ((struct web_part *));
76*c87b03e5Sespie static struct web_part * union_web_part_roots
77*c87b03e5Sespie 				PARAMS ((struct web_part *, struct web_part *));
78*c87b03e5Sespie static int defuse_overlap_p_1 PARAMS ((rtx, struct curr_use *));
79*c87b03e5Sespie static int live_out_1 PARAMS ((struct df *, struct curr_use *, rtx));
80*c87b03e5Sespie static int live_out PARAMS ((struct df *, struct curr_use *, rtx));
81*c87b03e5Sespie static rtx live_in_edge PARAMS (( struct df *, struct curr_use *, edge));
82*c87b03e5Sespie static void live_in PARAMS ((struct df *, struct curr_use *, rtx));
83*c87b03e5Sespie static int copy_insn_p PARAMS ((rtx, rtx *, rtx *));
84*c87b03e5Sespie static void remember_move PARAMS ((rtx));
85*c87b03e5Sespie static void handle_asm_insn PARAMS ((struct df *, rtx));
86*c87b03e5Sespie static void prune_hardregs_for_mode PARAMS ((HARD_REG_SET *,
87*c87b03e5Sespie 					     enum machine_mode));
88*c87b03e5Sespie static void init_one_web_common PARAMS ((struct web *, rtx));
89*c87b03e5Sespie static void init_one_web PARAMS ((struct web *, rtx));
90*c87b03e5Sespie static void reinit_one_web PARAMS ((struct web *, rtx));
91*c87b03e5Sespie static struct web * add_subweb PARAMS ((struct web *, rtx));
92*c87b03e5Sespie static struct web * add_subweb_2 PARAMS ((struct web *, unsigned int));
93*c87b03e5Sespie static void init_web_parts PARAMS ((struct df *));
94*c87b03e5Sespie static void copy_conflict_list PARAMS ((struct web *));
95*c87b03e5Sespie static void add_conflict_edge PARAMS ((struct web *, struct web *));
96*c87b03e5Sespie static void build_inverse_webs PARAMS ((struct web *));
97*c87b03e5Sespie static void copy_web PARAMS ((struct web *, struct web_link **));
98*c87b03e5Sespie static void compare_and_free_webs PARAMS ((struct web_link **));
99*c87b03e5Sespie static void init_webs_defs_uses PARAMS ((void));
100*c87b03e5Sespie static unsigned int parts_to_webs_1 PARAMS ((struct df *, struct web_link **,
101*c87b03e5Sespie 					     struct df_link *));
102*c87b03e5Sespie static void parts_to_webs PARAMS ((struct df *));
103*c87b03e5Sespie static void reset_conflicts PARAMS ((void));
104*c87b03e5Sespie #if 0
105*c87b03e5Sespie static void check_conflict_numbers PARAMS ((void));
106*c87b03e5Sespie #endif
107*c87b03e5Sespie static void conflicts_between_webs PARAMS ((struct df *));
108*c87b03e5Sespie static void remember_web_was_spilled PARAMS ((struct web *));
109*c87b03e5Sespie static void detect_spill_temps PARAMS ((void));
110*c87b03e5Sespie static int contains_pseudo PARAMS ((rtx));
111*c87b03e5Sespie static int want_to_remat PARAMS ((rtx x));
112*c87b03e5Sespie static void detect_remat_webs PARAMS ((void));
113*c87b03e5Sespie static void determine_web_costs PARAMS ((void));
114*c87b03e5Sespie static void detect_webs_set_in_cond_jump PARAMS ((void));
115*c87b03e5Sespie static void make_webs PARAMS ((struct df *));
116*c87b03e5Sespie static void moves_to_webs PARAMS ((struct df *));
117*c87b03e5Sespie static void connect_rmw_web_parts PARAMS ((struct df *));
118*c87b03e5Sespie static void update_regnos_mentioned PARAMS ((void));
119*c87b03e5Sespie static void livethrough_conflicts_bb PARAMS ((basic_block));
120*c87b03e5Sespie static void init_bb_info PARAMS ((void));
121*c87b03e5Sespie static void free_bb_info PARAMS ((void));
122*c87b03e5Sespie static void build_web_parts_and_conflicts PARAMS ((struct df *));
123*c87b03e5Sespie 
124*c87b03e5Sespie 
125*c87b03e5Sespie /* A sbitmap of DF_REF_IDs of uses, which are live over an abnormal
126*c87b03e5Sespie    edge.  */
127*c87b03e5Sespie static sbitmap live_over_abnormal;
128*c87b03e5Sespie 
129*c87b03e5Sespie /* To cache if we already saw a certain edge while analyzing one
130*c87b03e5Sespie    use, we use a tick count incremented per use.  */
131*c87b03e5Sespie static unsigned int visited_pass;
132*c87b03e5Sespie 
133*c87b03e5Sespie /* A sbitmap of UIDs of move insns, which we already analyzed.  */
134*c87b03e5Sespie static sbitmap move_handled;
135*c87b03e5Sespie 
136*c87b03e5Sespie /* One such structed is allocated per insn, and traces for the currently
137*c87b03e5Sespie    analyzed use, which web part belongs to it, and how many bytes of
138*c87b03e5Sespie    it were still undefined when that insn was reached.  */
139*c87b03e5Sespie struct visit_trace
140*c87b03e5Sespie {
141*c87b03e5Sespie   struct web_part *wp;
142*c87b03e5Sespie   unsigned HOST_WIDE_INT undefined;
143*c87b03e5Sespie };
144*c87b03e5Sespie /* Indexed by UID.  */
145*c87b03e5Sespie static struct visit_trace *visit_trace;
146*c87b03e5Sespie 
147*c87b03e5Sespie /* Per basic block we have one such structure, used to speed up
148*c87b03e5Sespie    the backtracing of uses.  */
149*c87b03e5Sespie struct ra_bb_info
150*c87b03e5Sespie {
151*c87b03e5Sespie   /* The value of visited_pass, as the first insn of this BB was reached
152*c87b03e5Sespie      the last time.  If this equals the current visited_pass, then
153*c87b03e5Sespie      undefined is valid.  Otherwise not.  */
154*c87b03e5Sespie   unsigned int pass;
155*c87b03e5Sespie   /* The still undefined bytes at that time.  The use to which this is
156*c87b03e5Sespie      relative is the current use.  */
157*c87b03e5Sespie   unsigned HOST_WIDE_INT undefined;
158*c87b03e5Sespie   /* Bit regno is set, if that regno is mentioned in this BB as a def, or
159*c87b03e5Sespie      the source of a copy insn.  In these cases we can not skip the whole
160*c87b03e5Sespie      block if we reach it from the end.  */
161*c87b03e5Sespie   bitmap regnos_mentioned;
162*c87b03e5Sespie   /* If a use reaches the end of a BB, and that BB doesn't mention its
163*c87b03e5Sespie      regno, we skip the block, and remember the ID of that use
164*c87b03e5Sespie      as living throughout the whole block.  */
165*c87b03e5Sespie   bitmap live_throughout;
166*c87b03e5Sespie   /* The content of the aux field before placing a pointer to this
167*c87b03e5Sespie      structure there.  */
168*c87b03e5Sespie   void *old_aux;
169*c87b03e5Sespie };
170*c87b03e5Sespie 
171*c87b03e5Sespie /* We need a fast way to describe a certain part of a register.
172*c87b03e5Sespie    Therefore we put together the size and offset (in bytes) in one
173*c87b03e5Sespie    integer.  */
174*c87b03e5Sespie #define BL_TO_WORD(b, l) ((((b) & 0xFFFF) << 16) | ((l) & 0xFFFF))
175*c87b03e5Sespie #define BYTE_BEGIN(i) (((unsigned int)(i) >> 16) & 0xFFFF)
176*c87b03e5Sespie #define BYTE_LENGTH(i) ((unsigned int)(i) & 0xFFFF)
177*c87b03e5Sespie 
178*c87b03e5Sespie /* For a REG or SUBREG expression X return the size/offset pair
179*c87b03e5Sespie    as an integer.  */
180*c87b03e5Sespie 
181*c87b03e5Sespie unsigned int
rtx_to_bits(x)182*c87b03e5Sespie rtx_to_bits (x)
183*c87b03e5Sespie      rtx x;
184*c87b03e5Sespie {
185*c87b03e5Sespie   unsigned int len, beg;
186*c87b03e5Sespie   len = GET_MODE_SIZE (GET_MODE (x));
187*c87b03e5Sespie   beg = (GET_CODE (x) == SUBREG) ? SUBREG_BYTE (x) : 0;
188*c87b03e5Sespie   return BL_TO_WORD (beg, len);
189*c87b03e5Sespie }
190*c87b03e5Sespie 
191*c87b03e5Sespie /* X is a REG or SUBREG rtx.  Return the bytes it touches as a bitmask.  */
192*c87b03e5Sespie 
193*c87b03e5Sespie static unsigned HOST_WIDE_INT
rtx_to_undefined(x)194*c87b03e5Sespie rtx_to_undefined (x)
195*c87b03e5Sespie      rtx x;
196*c87b03e5Sespie {
197*c87b03e5Sespie   unsigned int len, beg;
198*c87b03e5Sespie   unsigned HOST_WIDE_INT ret;
199*c87b03e5Sespie   len = GET_MODE_SIZE (GET_MODE (x));
200*c87b03e5Sespie   beg = (GET_CODE (x) == SUBREG) ? SUBREG_BYTE (x) : 0;
201*c87b03e5Sespie   ret = ~ ((unsigned HOST_WIDE_INT) 0);
202*c87b03e5Sespie   ret = (~(ret << len)) << beg;
203*c87b03e5Sespie   return ret;
204*c87b03e5Sespie }
205*c87b03e5Sespie 
206*c87b03e5Sespie /* We remember if we've analyzed an insn for being a move insn, and if yes
207*c87b03e5Sespie    between which operands.  */
208*c87b03e5Sespie struct copy_p_cache
209*c87b03e5Sespie {
210*c87b03e5Sespie   int seen;
211*c87b03e5Sespie   rtx source;
212*c87b03e5Sespie   rtx target;
213*c87b03e5Sespie };
214*c87b03e5Sespie 
215*c87b03e5Sespie /* On demand cache, for if insns are copy insns, and if yes, what
216*c87b03e5Sespie    source/target they have.  */
217*c87b03e5Sespie static struct copy_p_cache * copy_cache;
218*c87b03e5Sespie 
219*c87b03e5Sespie int *number_seen;
220*c87b03e5Sespie 
221*c87b03e5Sespie /* For INSN, return nonzero, if it's a move insn, we consider to coalesce
222*c87b03e5Sespie    later, and place the operands in *SOURCE and *TARGET, if they are
223*c87b03e5Sespie    not NULL.  */
224*c87b03e5Sespie 
225*c87b03e5Sespie static int
copy_insn_p(insn,source,target)226*c87b03e5Sespie copy_insn_p (insn, source, target)
227*c87b03e5Sespie      rtx insn;
228*c87b03e5Sespie      rtx *source;
229*c87b03e5Sespie      rtx *target;
230*c87b03e5Sespie {
231*c87b03e5Sespie   rtx d, s;
232*c87b03e5Sespie   unsigned int d_regno, s_regno;
233*c87b03e5Sespie   int uid = INSN_UID (insn);
234*c87b03e5Sespie 
235*c87b03e5Sespie   if (!INSN_P (insn))
236*c87b03e5Sespie     abort ();
237*c87b03e5Sespie 
238*c87b03e5Sespie   /* First look, if we already saw this insn.  */
239*c87b03e5Sespie   if (copy_cache[uid].seen)
240*c87b03e5Sespie     {
241*c87b03e5Sespie       /* And if we saw it, if it's actually a copy insn.  */
242*c87b03e5Sespie       if (copy_cache[uid].seen == 1)
243*c87b03e5Sespie 	{
244*c87b03e5Sespie 	  if (source)
245*c87b03e5Sespie 	    *source = copy_cache[uid].source;
246*c87b03e5Sespie 	  if (target)
247*c87b03e5Sespie 	    *target = copy_cache[uid].target;
248*c87b03e5Sespie 	  return 1;
249*c87b03e5Sespie 	}
250*c87b03e5Sespie       return 0;
251*c87b03e5Sespie     }
252*c87b03e5Sespie 
253*c87b03e5Sespie   /* Mark it as seen, but not being a copy insn.  */
254*c87b03e5Sespie   copy_cache[uid].seen = 2;
255*c87b03e5Sespie   insn = single_set (insn);
256*c87b03e5Sespie   if (!insn)
257*c87b03e5Sespie     return 0;
258*c87b03e5Sespie   d = SET_DEST (insn);
259*c87b03e5Sespie   s = SET_SRC (insn);
260*c87b03e5Sespie 
261*c87b03e5Sespie   /* We recognize moves between subreg's as copy insns.  This is used to avoid
262*c87b03e5Sespie      conflicts of those subwebs.  But they are currently _not_ used for
263*c87b03e5Sespie      coalescing (the check for this is in remember_move() below).  */
264*c87b03e5Sespie   while (GET_CODE (d) == STRICT_LOW_PART)
265*c87b03e5Sespie     d = XEXP (d, 0);
266*c87b03e5Sespie   if (GET_CODE (d) != REG
267*c87b03e5Sespie       && (GET_CODE (d) != SUBREG || GET_CODE (SUBREG_REG (d)) != REG))
268*c87b03e5Sespie     return 0;
269*c87b03e5Sespie   while (GET_CODE (s) == STRICT_LOW_PART)
270*c87b03e5Sespie     s = XEXP (s, 0);
271*c87b03e5Sespie   if (GET_CODE (s) != REG
272*c87b03e5Sespie       && (GET_CODE (s) != SUBREG || GET_CODE (SUBREG_REG (s)) != REG))
273*c87b03e5Sespie     return 0;
274*c87b03e5Sespie 
275*c87b03e5Sespie   s_regno = (unsigned) REGNO (GET_CODE (s) == SUBREG ? SUBREG_REG (s) : s);
276*c87b03e5Sespie   d_regno = (unsigned) REGNO (GET_CODE (d) == SUBREG ? SUBREG_REG (d) : d);
277*c87b03e5Sespie 
278*c87b03e5Sespie   /* Copies between hardregs are useless for us, as not coalesable anyway.  */
279*c87b03e5Sespie   if ((s_regno < FIRST_PSEUDO_REGISTER
280*c87b03e5Sespie        && d_regno < FIRST_PSEUDO_REGISTER)
281*c87b03e5Sespie       || s_regno >= max_normal_pseudo
282*c87b03e5Sespie       || d_regno >= max_normal_pseudo)
283*c87b03e5Sespie     return 0;
284*c87b03e5Sespie 
285*c87b03e5Sespie   if (source)
286*c87b03e5Sespie     *source = s;
287*c87b03e5Sespie   if (target)
288*c87b03e5Sespie     *target = d;
289*c87b03e5Sespie 
290*c87b03e5Sespie   /* Still mark it as seen, but as a copy insn this time.  */
291*c87b03e5Sespie   copy_cache[uid].seen = 1;
292*c87b03e5Sespie   copy_cache[uid].source = s;
293*c87b03e5Sespie   copy_cache[uid].target = d;
294*c87b03e5Sespie   return 1;
295*c87b03e5Sespie }
296*c87b03e5Sespie 
297*c87b03e5Sespie /* We build webs, as we process the conflicts.  For each use we go upward
298*c87b03e5Sespie    the insn stream, noting any defs as potentially conflicting with the
299*c87b03e5Sespie    current use.  We stop at defs of the current regno.  The conflicts are only
300*c87b03e5Sespie    potentially, because we may never reach a def, so this is an undefined use,
301*c87b03e5Sespie    which conflicts with nothing.  */
302*c87b03e5Sespie 
303*c87b03e5Sespie 
304*c87b03e5Sespie /* Given a web part WP, and the location of a reg part SIZE_WORD
305*c87b03e5Sespie    return the conflict bitmap for that reg part, or NULL if it doesn't
306*c87b03e5Sespie    exist yet in WP.  */
307*c87b03e5Sespie 
308*c87b03e5Sespie static bitmap
find_sub_conflicts(wp,size_word)309*c87b03e5Sespie find_sub_conflicts (wp, size_word)
310*c87b03e5Sespie      struct web_part *wp;
311*c87b03e5Sespie      unsigned int size_word;
312*c87b03e5Sespie {
313*c87b03e5Sespie   struct tagged_conflict *cl;
314*c87b03e5Sespie   cl = wp->sub_conflicts;
315*c87b03e5Sespie   for (; cl; cl = cl->next)
316*c87b03e5Sespie     if (cl->size_word == size_word)
317*c87b03e5Sespie       return cl->conflicts;
318*c87b03e5Sespie   return NULL;
319*c87b03e5Sespie }
320*c87b03e5Sespie 
321*c87b03e5Sespie /* Similar to find_sub_conflicts(), but creates that bitmap, if it
322*c87b03e5Sespie    doesn't exist.  I.e. this never returns NULL.  */
323*c87b03e5Sespie 
324*c87b03e5Sespie static bitmap
get_sub_conflicts(wp,size_word)325*c87b03e5Sespie get_sub_conflicts (wp, size_word)
326*c87b03e5Sespie      struct web_part *wp;
327*c87b03e5Sespie      unsigned int size_word;
328*c87b03e5Sespie {
329*c87b03e5Sespie   bitmap b = find_sub_conflicts (wp, size_word);
330*c87b03e5Sespie   if (!b)
331*c87b03e5Sespie     {
332*c87b03e5Sespie       struct tagged_conflict *cl =
333*c87b03e5Sespie 	(struct tagged_conflict *) ra_alloc (sizeof *cl);
334*c87b03e5Sespie       cl->conflicts = BITMAP_XMALLOC ();
335*c87b03e5Sespie       cl->size_word = size_word;
336*c87b03e5Sespie       cl->next = wp->sub_conflicts;
337*c87b03e5Sespie       wp->sub_conflicts = cl;
338*c87b03e5Sespie       b = cl->conflicts;
339*c87b03e5Sespie     }
340*c87b03e5Sespie   return b;
341*c87b03e5Sespie }
342*c87b03e5Sespie 
343*c87b03e5Sespie /* Helper table for undef_to_size_word() below for small values
344*c87b03e5Sespie    of UNDEFINED.  Offsets and lengths are byte based.  */
345*c87b03e5Sespie static struct undef_table_s {
346*c87b03e5Sespie   unsigned int new_undef;
347*c87b03e5Sespie   /* size | (byte << 16)  */
348*c87b03e5Sespie   unsigned int size_word;
349*c87b03e5Sespie } const undef_table [] = {
350*c87b03e5Sespie   { 0, BL_TO_WORD (0, 0)}, /* 0 */
351*c87b03e5Sespie   { 0, BL_TO_WORD (0, 1)},
352*c87b03e5Sespie   { 0, BL_TO_WORD (1, 1)},
353*c87b03e5Sespie   { 0, BL_TO_WORD (0, 2)},
354*c87b03e5Sespie   { 0, BL_TO_WORD (2, 1)}, /* 4 */
355*c87b03e5Sespie   { 1, BL_TO_WORD (2, 1)},
356*c87b03e5Sespie   { 2, BL_TO_WORD (2, 1)},
357*c87b03e5Sespie   { 3, BL_TO_WORD (2, 1)},
358*c87b03e5Sespie   { 0, BL_TO_WORD (3, 1)}, /* 8 */
359*c87b03e5Sespie   { 1, BL_TO_WORD (3, 1)},
360*c87b03e5Sespie   { 2, BL_TO_WORD (3, 1)},
361*c87b03e5Sespie   { 3, BL_TO_WORD (3, 1)},
362*c87b03e5Sespie   { 0, BL_TO_WORD (2, 2)}, /* 12 */
363*c87b03e5Sespie   { 1, BL_TO_WORD (2, 2)},
364*c87b03e5Sespie   { 2, BL_TO_WORD (2, 2)},
365*c87b03e5Sespie   { 0, BL_TO_WORD (0, 4)}};
366*c87b03e5Sespie 
367*c87b03e5Sespie /* Interpret *UNDEFINED as bitmask where each bit corresponds to a byte.
368*c87b03e5Sespie    A set bit means an undefined byte.  Factor all undefined bytes into
369*c87b03e5Sespie    groups, and return a size/ofs pair of consecutive undefined bytes,
370*c87b03e5Sespie    but according to certain borders.  Clear out those bits corrsponding
371*c87b03e5Sespie    to bytes overlaid by that size/ofs pair.  REG is only used for
372*c87b03e5Sespie    the mode, to detect if it's a floating mode or not.
373*c87b03e5Sespie 
374*c87b03e5Sespie    For example:	*UNDEFINED	size+ofs	new *UNDEFINED
375*c87b03e5Sespie 		 1111		4+0		  0
376*c87b03e5Sespie 		 1100		2+2		  0
377*c87b03e5Sespie 		 1101		2+2		  1
378*c87b03e5Sespie 		 0001		1+0		  0
379*c87b03e5Sespie 		10101		1+4		101
380*c87b03e5Sespie 
381*c87b03e5Sespie    */
382*c87b03e5Sespie 
383*c87b03e5Sespie static unsigned int
undef_to_size_word(reg,undefined)384*c87b03e5Sespie undef_to_size_word (reg, undefined)
385*c87b03e5Sespie      rtx reg;
386*c87b03e5Sespie      unsigned HOST_WIDE_INT *undefined;
387*c87b03e5Sespie {
388*c87b03e5Sespie   /* When only the lower four bits are possibly set, we use
389*c87b03e5Sespie      a fast lookup table.  */
390*c87b03e5Sespie   if (*undefined <= 15)
391*c87b03e5Sespie     {
392*c87b03e5Sespie       struct undef_table_s u;
393*c87b03e5Sespie       u = undef_table[*undefined];
394*c87b03e5Sespie       *undefined = u.new_undef;
395*c87b03e5Sespie       return u.size_word;
396*c87b03e5Sespie     }
397*c87b03e5Sespie 
398*c87b03e5Sespie   /* Otherwise we handle certain cases directly.  */
399*c87b03e5Sespie   switch (*undefined)
400*c87b03e5Sespie     {
401*c87b03e5Sespie       case 0x00f0 : *undefined = 0; return BL_TO_WORD (4, 4);
402*c87b03e5Sespie       case 0x00ff : *undefined = 0; return BL_TO_WORD (0, 8);
403*c87b03e5Sespie       case 0x0f00 : *undefined = 0; return BL_TO_WORD (8, 4);
404*c87b03e5Sespie       case 0x0ff0 : *undefined = 0xf0; return BL_TO_WORD (8, 4);
405*c87b03e5Sespie       case 0x0fff :
406*c87b03e5Sespie 	if (INTEGRAL_MODE_P (GET_MODE (reg)))
407*c87b03e5Sespie 	  { *undefined = 0xff; return BL_TO_WORD (8, 4); }
408*c87b03e5Sespie 	else
409*c87b03e5Sespie 	  { *undefined = 0; return BL_TO_WORD (0, 12); /* XFmode */ }
410*c87b03e5Sespie       case 0xf000 : *undefined = 0; return BL_TO_WORD (12, 4);
411*c87b03e5Sespie       case 0xff00 : *undefined = 0; return BL_TO_WORD (8, 8);
412*c87b03e5Sespie       case 0xfff0 : *undefined = 0xf0; return BL_TO_WORD (8, 8);
413*c87b03e5Sespie       case 0xffff : *undefined = 0; return BL_TO_WORD (0, 16);
414*c87b03e5Sespie 
415*c87b03e5Sespie       /* And if nothing matched fall back to the general solution.
416*c87b03e5Sespie 	 For now unknown undefined bytes are converted to sequences
417*c87b03e5Sespie 	 of maximal length 4 bytes.  We could make this larger if
418*c87b03e5Sespie 	 necessary.  */
419*c87b03e5Sespie       default :
420*c87b03e5Sespie 	{
421*c87b03e5Sespie 	  unsigned HOST_WIDE_INT u = *undefined;
422*c87b03e5Sespie 	  int word;
423*c87b03e5Sespie 	  struct undef_table_s tab;
424*c87b03e5Sespie 	  for (word = 0; (u & 15) == 0; word += 4)
425*c87b03e5Sespie 	    u >>= 4;
426*c87b03e5Sespie 	  u = u & 15;
427*c87b03e5Sespie 	  tab = undef_table[u];
428*c87b03e5Sespie 	  u = tab.new_undef;
429*c87b03e5Sespie 	  u = (*undefined & ~((unsigned HOST_WIDE_INT)15 << word))
430*c87b03e5Sespie 	      | (u << word);
431*c87b03e5Sespie 	  *undefined = u;
432*c87b03e5Sespie 	  /* Size remains the same, only the begin is moved up move bytes.  */
433*c87b03e5Sespie 	  return tab.size_word + BL_TO_WORD (word, 0);
434*c87b03e5Sespie 	}
435*c87b03e5Sespie 	break;
436*c87b03e5Sespie     }
437*c87b03e5Sespie }
438*c87b03e5Sespie 
439*c87b03e5Sespie /* Put the above three functions together.  For a set of undefined bytes
440*c87b03e5Sespie    as bitmap *UNDEFINED, look for (create if necessary) and return the
441*c87b03e5Sespie    corresponding conflict bitmap.  Change *UNDEFINED to remove the bytes
442*c87b03e5Sespie    covered by the part for that bitmap.  */
443*c87b03e5Sespie 
444*c87b03e5Sespie static bitmap
undef_to_bitmap(wp,undefined)445*c87b03e5Sespie undef_to_bitmap (wp, undefined)
446*c87b03e5Sespie      struct web_part *wp;
447*c87b03e5Sespie      unsigned HOST_WIDE_INT *undefined;
448*c87b03e5Sespie {
449*c87b03e5Sespie   unsigned int size_word = undef_to_size_word (DF_REF_REAL_REG (wp->ref),
450*c87b03e5Sespie 					       undefined);
451*c87b03e5Sespie   return get_sub_conflicts (wp, size_word);
452*c87b03e5Sespie }
453*c87b03e5Sespie 
454*c87b03e5Sespie /* Returns the root of the web part P is a member of.  Additionally
455*c87b03e5Sespie    it compresses the path.  P may not be NULL.  */
456*c87b03e5Sespie 
457*c87b03e5Sespie static struct web_part *
find_web_part_1(p)458*c87b03e5Sespie find_web_part_1 (p)
459*c87b03e5Sespie      struct web_part *p;
460*c87b03e5Sespie {
461*c87b03e5Sespie   struct web_part *r = p;
462*c87b03e5Sespie   struct web_part *p_next;
463*c87b03e5Sespie   while (r->uplink)
464*c87b03e5Sespie     r = r->uplink;
465*c87b03e5Sespie   for (; p != r; p = p_next)
466*c87b03e5Sespie     {
467*c87b03e5Sespie       p_next = p->uplink;
468*c87b03e5Sespie       p->uplink = r;
469*c87b03e5Sespie     }
470*c87b03e5Sespie   return r;
471*c87b03e5Sespie }
472*c87b03e5Sespie 
473*c87b03e5Sespie /* Fast macro for the common case (WP either being the root itself, or
474*c87b03e5Sespie    the end of an already compressed path.  */
475*c87b03e5Sespie 
476*c87b03e5Sespie #define find_web_part(wp) ((! (wp)->uplink) ? (wp) \
477*c87b03e5Sespie   : (! (wp)->uplink->uplink) ? (wp)->uplink : find_web_part_1 (wp))
478*c87b03e5Sespie 
479*c87b03e5Sespie /* Unions together the parts R1 resp. R2 is a root of.
480*c87b03e5Sespie    All dynamic information associated with the parts (number of spanned insns
481*c87b03e5Sespie    and so on) is also merged.
482*c87b03e5Sespie    The root of the resulting (possibly larger) web part is returned.  */
483*c87b03e5Sespie 
484*c87b03e5Sespie static struct web_part *
union_web_part_roots(r1,r2)485*c87b03e5Sespie union_web_part_roots (r1, r2)
486*c87b03e5Sespie      struct web_part *r1, *r2;
487*c87b03e5Sespie {
488*c87b03e5Sespie   if (r1 != r2)
489*c87b03e5Sespie     {
490*c87b03e5Sespie       /* The new root is the smaller (pointerwise) of both.  This is crucial
491*c87b03e5Sespie          to make the construction of webs from web parts work (so, when
492*c87b03e5Sespie 	 scanning all parts, we see the roots before all it's childs).
493*c87b03e5Sespie          Additionally this ensures, that if the web has a def at all, than
494*c87b03e5Sespie          the root is a def (because all def parts are before use parts in the
495*c87b03e5Sespie 	 web_parts[] array), or put another way, as soon, as the root of a
496*c87b03e5Sespie          web part is not a def, this is an uninitialized web part.  The
497*c87b03e5Sespie          way we construct the I-graph ensures, that if a web is initialized,
498*c87b03e5Sespie          then the first part we find (besides trivial 1 item parts) has a
499*c87b03e5Sespie          def.  */
500*c87b03e5Sespie       if (r1 > r2)
501*c87b03e5Sespie 	{
502*c87b03e5Sespie 	  struct web_part *h = r1;
503*c87b03e5Sespie 	  r1 = r2;
504*c87b03e5Sespie 	  r2 = h;
505*c87b03e5Sespie 	}
506*c87b03e5Sespie       r2->uplink = r1;
507*c87b03e5Sespie       num_webs--;
508*c87b03e5Sespie 
509*c87b03e5Sespie       /* Now we merge the dynamic information of R1 and R2.  */
510*c87b03e5Sespie       r1->spanned_deaths += r2->spanned_deaths;
511*c87b03e5Sespie 
512*c87b03e5Sespie       if (!r1->sub_conflicts)
513*c87b03e5Sespie 	r1->sub_conflicts = r2->sub_conflicts;
514*c87b03e5Sespie       else if (r2->sub_conflicts)
515*c87b03e5Sespie 	/* We need to merge the conflict bitmaps from R2 into R1.  */
516*c87b03e5Sespie 	{
517*c87b03e5Sespie 	  struct tagged_conflict *cl1, *cl2;
518*c87b03e5Sespie 	  /* First those from R2, which are also contained in R1.
519*c87b03e5Sespie 	     We union the bitmaps, and free those from R2, resetting them
520*c87b03e5Sespie 	     to 0.  */
521*c87b03e5Sespie 	  for (cl1 = r1->sub_conflicts; cl1; cl1 = cl1->next)
522*c87b03e5Sespie 	    for (cl2 = r2->sub_conflicts; cl2; cl2 = cl2->next)
523*c87b03e5Sespie 	      if (cl1->size_word == cl2->size_word)
524*c87b03e5Sespie 		{
525*c87b03e5Sespie 		  bitmap_operation (cl1->conflicts, cl1->conflicts,
526*c87b03e5Sespie 				    cl2->conflicts, BITMAP_IOR);
527*c87b03e5Sespie 		  BITMAP_XFREE (cl2->conflicts);
528*c87b03e5Sespie 		  cl2->conflicts = NULL;
529*c87b03e5Sespie 		}
530*c87b03e5Sespie 	  /* Now the conflict lists from R2 which weren't in R1.
531*c87b03e5Sespie 	     We simply copy the entries from R2 into R1' list.  */
532*c87b03e5Sespie 	  for (cl2 = r2->sub_conflicts; cl2;)
533*c87b03e5Sespie 	    {
534*c87b03e5Sespie 	      struct tagged_conflict *cl_next = cl2->next;
535*c87b03e5Sespie 	      if (cl2->conflicts)
536*c87b03e5Sespie 		{
537*c87b03e5Sespie 		  cl2->next = r1->sub_conflicts;
538*c87b03e5Sespie 		  r1->sub_conflicts = cl2;
539*c87b03e5Sespie 		}
540*c87b03e5Sespie 	      cl2 = cl_next;
541*c87b03e5Sespie 	    }
542*c87b03e5Sespie 	}
543*c87b03e5Sespie       r2->sub_conflicts = NULL;
544*c87b03e5Sespie       r1->crosses_call |= r2->crosses_call;
545*c87b03e5Sespie     }
546*c87b03e5Sespie   return r1;
547*c87b03e5Sespie }
548*c87b03e5Sespie 
549*c87b03e5Sespie /* Convenience macro, that is cabable of unioning also non-roots.  */
550*c87b03e5Sespie #define union_web_parts(p1, p2) \
551*c87b03e5Sespie   ((p1 == p2) ? find_web_part (p1) \
552*c87b03e5Sespie       : union_web_part_roots (find_web_part (p1), find_web_part (p2)))
553*c87b03e5Sespie 
554*c87b03e5Sespie /* Remember that we've handled a given move, so we don't reprocess it.  */
555*c87b03e5Sespie 
556*c87b03e5Sespie static void
remember_move(insn)557*c87b03e5Sespie remember_move (insn)
558*c87b03e5Sespie      rtx insn;
559*c87b03e5Sespie {
560*c87b03e5Sespie   if (!TEST_BIT (move_handled, INSN_UID (insn)))
561*c87b03e5Sespie     {
562*c87b03e5Sespie       rtx s, d;
563*c87b03e5Sespie       SET_BIT (move_handled, INSN_UID (insn));
564*c87b03e5Sespie       if (copy_insn_p (insn, &s, &d))
565*c87b03e5Sespie 	{
566*c87b03e5Sespie 	  /* Some sanity test for the copy insn.  */
567*c87b03e5Sespie 	  struct df_link *slink = DF_INSN_USES (df, insn);
568*c87b03e5Sespie 	  struct df_link *link = DF_INSN_DEFS (df, insn);
569*c87b03e5Sespie 	  if (!link || !link->ref || !slink || !slink->ref)
570*c87b03e5Sespie 	    abort ();
571*c87b03e5Sespie 	  /* The following (link->next != 0) happens when a hardreg
572*c87b03e5Sespie 	     is used in wider mode (REG:DI %eax).  Then df.* creates
573*c87b03e5Sespie 	     a def/use for each hardreg contained therein.  We only
574*c87b03e5Sespie 	     allow hardregs here.  */
575*c87b03e5Sespie 	  if (link->next
576*c87b03e5Sespie 	      && DF_REF_REGNO (link->next->ref) >= FIRST_PSEUDO_REGISTER)
577*c87b03e5Sespie 	    abort ();
578*c87b03e5Sespie 	}
579*c87b03e5Sespie       else
580*c87b03e5Sespie 	abort ();
581*c87b03e5Sespie       /* XXX for now we don't remember move insns involving any subregs.
582*c87b03e5Sespie 	 Those would be difficult to coalesce (we would need to implement
583*c87b03e5Sespie 	 handling of all the subwebs in the allocator, including that such
584*c87b03e5Sespie 	 subwebs could be source and target of coalesing).  */
585*c87b03e5Sespie       if (GET_CODE (s) == REG && GET_CODE (d) == REG)
586*c87b03e5Sespie 	{
587*c87b03e5Sespie 	  struct move *m = (struct move *) ra_calloc (sizeof (struct move));
588*c87b03e5Sespie 	  struct move_list *ml;
589*c87b03e5Sespie 	  m->insn = insn;
590*c87b03e5Sespie 	  ml = (struct move_list *) ra_alloc (sizeof (struct move_list));
591*c87b03e5Sespie 	  ml->move = m;
592*c87b03e5Sespie 	  ml->next = wl_moves;
593*c87b03e5Sespie 	  wl_moves = ml;
594*c87b03e5Sespie 	}
595*c87b03e5Sespie     }
596*c87b03e5Sespie }
597*c87b03e5Sespie 
598*c87b03e5Sespie /* This describes the USE currently looked at in the main-loop in
599*c87b03e5Sespie    build_web_parts_and_conflicts().  */
600*c87b03e5Sespie struct curr_use {
601*c87b03e5Sespie   struct web_part *wp;
602*c87b03e5Sespie   /* This has a 1-bit for each byte in the USE, which is still undefined.  */
603*c87b03e5Sespie   unsigned HOST_WIDE_INT undefined;
604*c87b03e5Sespie   /* For easy access.  */
605*c87b03e5Sespie   unsigned int regno;
606*c87b03e5Sespie   rtx x;
607*c87b03e5Sespie   /* If some bits of this USE are live over an abnormal edge.  */
608*c87b03e5Sespie   unsigned int live_over_abnormal;
609*c87b03e5Sespie };
610*c87b03e5Sespie 
611*c87b03e5Sespie /* Returns nonzero iff rtx DEF and USE have bits in common (but see below).
612*c87b03e5Sespie    It is only called with DEF and USE being (reg:M a) or (subreg:M1 (reg:M2 a)
613*c87b03e5Sespie    x) rtx's.  Furthermore if it's a subreg rtx M1 is at least one word wide,
614*c87b03e5Sespie    and a is a multi-word pseudo.  If DEF or USE are hardregs, they are in
615*c87b03e5Sespie    word_mode, so we don't need to check for further hardregs which would result
616*c87b03e5Sespie    from wider references.  We are never called with paradoxical subregs.
617*c87b03e5Sespie 
618*c87b03e5Sespie    This returns:
619*c87b03e5Sespie    0 for no common bits,
620*c87b03e5Sespie    1 if DEF and USE exactly cover the same bytes,
621*c87b03e5Sespie    2 if the DEF only covers a part of the bits of USE
622*c87b03e5Sespie    3 if the DEF covers more than the bits of the USE, and
623*c87b03e5Sespie    4 if both are SUBREG's of different size, but have bytes in common.
624*c87b03e5Sespie    -1 is a special case, for when DEF and USE refer to the same regno, but
625*c87b03e5Sespie       have for other reasons no bits in common (can only happen with
626*c87b03e5Sespie       subregs refering to different words, or to words which already were
627*c87b03e5Sespie       defined for this USE).
628*c87b03e5Sespie    Furthermore it modifies use->undefined to clear the bits which get defined
629*c87b03e5Sespie    by DEF (only for cases with partial overlap).
630*c87b03e5Sespie    I.e. if bit 1 is set for the result != -1, the USE was completely covered,
631*c87b03e5Sespie    otherwise a test is needed to track the already defined bytes.  */
632*c87b03e5Sespie 
633*c87b03e5Sespie static int
defuse_overlap_p_1(def,use)634*c87b03e5Sespie defuse_overlap_p_1 (def, use)
635*c87b03e5Sespie      rtx def;
636*c87b03e5Sespie      struct curr_use *use;
637*c87b03e5Sespie {
638*c87b03e5Sespie   int mode = 0;
639*c87b03e5Sespie   if (def == use->x)
640*c87b03e5Sespie     return 1;
641*c87b03e5Sespie   if (!def)
642*c87b03e5Sespie     return 0;
643*c87b03e5Sespie   if (GET_CODE (def) == SUBREG)
644*c87b03e5Sespie     {
645*c87b03e5Sespie       if (REGNO (SUBREG_REG (def)) != use->regno)
646*c87b03e5Sespie 	return 0;
647*c87b03e5Sespie       mode |= 1;
648*c87b03e5Sespie     }
649*c87b03e5Sespie   else if (REGNO (def) != use->regno)
650*c87b03e5Sespie     return 0;
651*c87b03e5Sespie   if (GET_CODE (use->x) == SUBREG)
652*c87b03e5Sespie     mode |= 2;
653*c87b03e5Sespie   switch (mode)
654*c87b03e5Sespie     {
655*c87b03e5Sespie       case 0: /* REG, REG */
656*c87b03e5Sespie 	return 1;
657*c87b03e5Sespie       case 1: /* SUBREG, REG */
658*c87b03e5Sespie 	{
659*c87b03e5Sespie 	  unsigned HOST_WIDE_INT old_u = use->undefined;
660*c87b03e5Sespie 	  use->undefined &= ~ rtx_to_undefined (def);
661*c87b03e5Sespie 	  return (old_u != use->undefined) ? 2 : -1;
662*c87b03e5Sespie 	}
663*c87b03e5Sespie       case 2: /* REG, SUBREG */
664*c87b03e5Sespie 	return 3;
665*c87b03e5Sespie       case 3: /* SUBREG, SUBREG */
666*c87b03e5Sespie 	if (GET_MODE_SIZE (GET_MODE (def)) == GET_MODE_SIZE (GET_MODE (use->x)))
667*c87b03e5Sespie 	  /* If the size of both things is the same, the subreg's overlap
668*c87b03e5Sespie 	     if they refer to the same word.  */
669*c87b03e5Sespie 	  if (SUBREG_BYTE (def) == SUBREG_BYTE (use->x))
670*c87b03e5Sespie 	    return 1;
671*c87b03e5Sespie 	/* Now the more difficult part: the same regno is refered, but the
672*c87b03e5Sespie 	   sizes of the references or the words differ.  E.g.
673*c87b03e5Sespie            (subreg:SI (reg:CDI a) 0) and (subreg:DI (reg:CDI a) 2) do not
674*c87b03e5Sespie 	   overlap, wereas the latter overlaps with (subreg:SI (reg:CDI a) 3).
675*c87b03e5Sespie 	   */
676*c87b03e5Sespie 	{
677*c87b03e5Sespie 	  unsigned HOST_WIDE_INT old_u;
678*c87b03e5Sespie 	  int b1, e1, b2, e2;
679*c87b03e5Sespie 	  unsigned int bl1, bl2;
680*c87b03e5Sespie 	  bl1 = rtx_to_bits (def);
681*c87b03e5Sespie 	  bl2 = rtx_to_bits (use->x);
682*c87b03e5Sespie 	  b1 = BYTE_BEGIN (bl1);
683*c87b03e5Sespie 	  b2 = BYTE_BEGIN (bl2);
684*c87b03e5Sespie 	  e1 = b1 + BYTE_LENGTH (bl1) - 1;
685*c87b03e5Sespie 	  e2 = b2 + BYTE_LENGTH (bl2) - 1;
686*c87b03e5Sespie 	  if (b1 > e2 || b2 > e1)
687*c87b03e5Sespie 	    return -1;
688*c87b03e5Sespie 	  old_u = use->undefined;
689*c87b03e5Sespie 	  use->undefined &= ~ rtx_to_undefined (def);
690*c87b03e5Sespie 	  return (old_u != use->undefined) ? 4 : -1;
691*c87b03e5Sespie 	}
692*c87b03e5Sespie       default:
693*c87b03e5Sespie         abort ();
694*c87b03e5Sespie     }
695*c87b03e5Sespie }
696*c87b03e5Sespie 
697*c87b03e5Sespie /* Macro for the common case of either def and use having the same rtx,
698*c87b03e5Sespie    or based on different regnos.  */
699*c87b03e5Sespie #define defuse_overlap_p(def, use) \
700*c87b03e5Sespie   ((def) == (use)->x ? 1 : \
701*c87b03e5Sespie      (REGNO (GET_CODE (def) == SUBREG \
702*c87b03e5Sespie 	     ? SUBREG_REG (def) : def) != use->regno \
703*c87b03e5Sespie       ? 0 : defuse_overlap_p_1 (def, use)))
704*c87b03e5Sespie 
705*c87b03e5Sespie 
706*c87b03e5Sespie /* The use USE flows into INSN (backwards).  Determine INSNs effect on it,
707*c87b03e5Sespie    and return nonzero, if (parts of) that USE are also live before it.
708*c87b03e5Sespie    This also notes conflicts between the USE and all DEFS in that insn,
709*c87b03e5Sespie    and modifies the undefined bits of USE in case parts of it were set in
710*c87b03e5Sespie    this insn.  */
711*c87b03e5Sespie 
712*c87b03e5Sespie static int
live_out_1(df,use,insn)713*c87b03e5Sespie live_out_1 (df, use, insn)
714*c87b03e5Sespie      struct df *df ATTRIBUTE_UNUSED;
715*c87b03e5Sespie      struct curr_use *use;
716*c87b03e5Sespie      rtx insn;
717*c87b03e5Sespie {
718*c87b03e5Sespie   int defined = 0;
719*c87b03e5Sespie   int uid = INSN_UID (insn);
720*c87b03e5Sespie   struct web_part *wp = use->wp;
721*c87b03e5Sespie 
722*c87b03e5Sespie   /* Mark, that this insn needs this webpart live.  */
723*c87b03e5Sespie   visit_trace[uid].wp = wp;
724*c87b03e5Sespie   visit_trace[uid].undefined = use->undefined;
725*c87b03e5Sespie 
726*c87b03e5Sespie   if (INSN_P (insn))
727*c87b03e5Sespie     {
728*c87b03e5Sespie       unsigned int source_regno = ~0;
729*c87b03e5Sespie       unsigned int regno = use->regno;
730*c87b03e5Sespie       unsigned HOST_WIDE_INT orig_undef = use->undefined;
731*c87b03e5Sespie       unsigned HOST_WIDE_INT final_undef = use->undefined;
732*c87b03e5Sespie       rtx s = NULL;
733*c87b03e5Sespie       unsigned int n, num_defs = insn_df[uid].num_defs;
734*c87b03e5Sespie       struct ref **defs = insn_df[uid].defs;
735*c87b03e5Sespie 
736*c87b03e5Sespie       /* We want to access the root webpart.  */
737*c87b03e5Sespie       wp = find_web_part (wp);
738*c87b03e5Sespie       if (GET_CODE (insn) == CALL_INSN)
739*c87b03e5Sespie 	wp->crosses_call = 1;
740*c87b03e5Sespie       else if (copy_insn_p (insn, &s, NULL))
741*c87b03e5Sespie 	source_regno = REGNO (GET_CODE (s) == SUBREG ? SUBREG_REG (s) : s);
742*c87b03e5Sespie 
743*c87b03e5Sespie       /* Look at all DEFS in this insn.  */
744*c87b03e5Sespie       for (n = 0; n < num_defs; n++)
745*c87b03e5Sespie 	{
746*c87b03e5Sespie 	  struct ref *ref = defs[n];
747*c87b03e5Sespie 	  int lap;
748*c87b03e5Sespie 
749*c87b03e5Sespie 	  /* Reset the undefined bits for each iteration, in case this
750*c87b03e5Sespie 	     insn has more than one set, and one of them sets this regno.
751*c87b03e5Sespie 	     But still the original undefined part conflicts with the other
752*c87b03e5Sespie 	     sets.  */
753*c87b03e5Sespie 	  use->undefined = orig_undef;
754*c87b03e5Sespie 	  if ((lap = defuse_overlap_p (DF_REF_REG (ref), use)) != 0)
755*c87b03e5Sespie 	    {
756*c87b03e5Sespie 	      if (lap == -1)
757*c87b03e5Sespie 		  /* Same regnos but non-overlapping or already defined bits,
758*c87b03e5Sespie 		     so ignore this DEF, or better said make the yet undefined
759*c87b03e5Sespie 		     part and this DEF conflicting.  */
760*c87b03e5Sespie 		{
761*c87b03e5Sespie 		  unsigned HOST_WIDE_INT undef;
762*c87b03e5Sespie 		  undef = use->undefined;
763*c87b03e5Sespie 		  while (undef)
764*c87b03e5Sespie 		    bitmap_set_bit (undef_to_bitmap (wp, &undef),
765*c87b03e5Sespie 				    DF_REF_ID (ref));
766*c87b03e5Sespie 		  continue;
767*c87b03e5Sespie 		}
768*c87b03e5Sespie 	      if ((lap & 1) != 0)
769*c87b03e5Sespie 		  /* The current DEF completely covers the USE, so we can
770*c87b03e5Sespie 		     stop traversing the code looking for further DEFs.  */
771*c87b03e5Sespie 		defined = 1;
772*c87b03e5Sespie 	      else
773*c87b03e5Sespie 		  /* We have a partial overlap.  */
774*c87b03e5Sespie 		{
775*c87b03e5Sespie 		  final_undef &= use->undefined;
776*c87b03e5Sespie 		  if (final_undef == 0)
777*c87b03e5Sespie 		    /* Now the USE is completely defined, which means, that
778*c87b03e5Sespie 		       we can stop looking for former DEFs.  */
779*c87b03e5Sespie 		    defined = 1;
780*c87b03e5Sespie 		  /* If this is a partial overlap, which left some bits
781*c87b03e5Sespie 		     in USE undefined, we normally would need to create
782*c87b03e5Sespie 		     conflicts between that undefined part and the part of
783*c87b03e5Sespie 		     this DEF which overlapped with some of the formerly
784*c87b03e5Sespie 		     undefined bits.  We don't need to do this, because both
785*c87b03e5Sespie 		     parts of this DEF (that which overlaps, and that which
786*c87b03e5Sespie 		     doesn't) are written together in this one DEF, and can
787*c87b03e5Sespie 		     not be colored in a way which would conflict with
788*c87b03e5Sespie 		     the USE.  This is only true for partial overlap,
789*c87b03e5Sespie 		     because only then the DEF and USE have bits in common,
790*c87b03e5Sespie 		     which makes the DEF move, if the USE moves, making them
791*c87b03e5Sespie 		     aligned.
792*c87b03e5Sespie 		     If they have no bits in common (lap == -1), they are
793*c87b03e5Sespie 		     really independent.  Therefore we there made a
794*c87b03e5Sespie 		     conflict above.  */
795*c87b03e5Sespie 		}
796*c87b03e5Sespie 	      /* This is at least a partial overlap, so we need to union
797*c87b03e5Sespie 		 the web parts.  */
798*c87b03e5Sespie 	      wp = union_web_parts (wp, &web_parts[DF_REF_ID (ref)]);
799*c87b03e5Sespie 	    }
800*c87b03e5Sespie 	  else
801*c87b03e5Sespie 	    {
802*c87b03e5Sespie 	      /* The DEF and the USE don't overlap at all, different
803*c87b03e5Sespie 		 regnos.  I.e. make conflicts between the undefined bits,
804*c87b03e5Sespie 	         and that DEF.  */
805*c87b03e5Sespie 	      unsigned HOST_WIDE_INT undef = use->undefined;
806*c87b03e5Sespie 
807*c87b03e5Sespie 	      if (regno == source_regno)
808*c87b03e5Sespie 		/* This triggers only, when this was a copy insn and the
809*c87b03e5Sespie 		   source is at least a part of the USE currently looked at.
810*c87b03e5Sespie 		   In this case only the bits of the USE conflict with the
811*c87b03e5Sespie 		   DEF, which are not covered by the source of this copy
812*c87b03e5Sespie 		   insn, and which are still undefined.  I.e. in the best
813*c87b03e5Sespie 		   case (the whole reg being the source), _no_ conflicts
814*c87b03e5Sespie 		   between that USE and this DEF (the target of the move)
815*c87b03e5Sespie 		   are created by this insn (though they might be by
816*c87b03e5Sespie 		   others).  This is a super case of the normal copy insn
817*c87b03e5Sespie 		   only between full regs.  */
818*c87b03e5Sespie 		{
819*c87b03e5Sespie 		  undef &= ~ rtx_to_undefined (s);
820*c87b03e5Sespie 		}
821*c87b03e5Sespie 	      if (undef)
822*c87b03e5Sespie 		{
823*c87b03e5Sespie 		  /*struct web_part *cwp;
824*c87b03e5Sespie 		    cwp = find_web_part (&web_parts[DF_REF_ID
825*c87b03e5Sespie 		    (ref)]);*/
826*c87b03e5Sespie 
827*c87b03e5Sespie 		  /* TODO: somehow instead of noting the ID of the LINK
828*c87b03e5Sespie 		     use an ID nearer to the root webpart of that LINK.
829*c87b03e5Sespie 		     We can't use the root itself, because we later use the
830*c87b03e5Sespie 		     ID to look at the form (reg or subreg, and if yes,
831*c87b03e5Sespie 		     which subreg) of this conflict.  This means, that we
832*c87b03e5Sespie 		     need to remember in the root an ID for each form, and
833*c87b03e5Sespie 		     maintaining this, when merging web parts.  This makes
834*c87b03e5Sespie 		     the bitmaps smaller.  */
835*c87b03e5Sespie 		  do
836*c87b03e5Sespie 		    bitmap_set_bit (undef_to_bitmap (wp, &undef),
837*c87b03e5Sespie 				    DF_REF_ID (ref));
838*c87b03e5Sespie 		  while (undef);
839*c87b03e5Sespie 		}
840*c87b03e5Sespie 	    }
841*c87b03e5Sespie 	}
842*c87b03e5Sespie       if (defined)
843*c87b03e5Sespie 	use->undefined = 0;
844*c87b03e5Sespie       else
845*c87b03e5Sespie 	{
846*c87b03e5Sespie 	  /* If this insn doesn't completely define the USE, increment also
847*c87b03e5Sespie 	     it's spanned deaths count (if this insn contains a death).  */
848*c87b03e5Sespie 	  if (uid >= death_insns_max_uid)
849*c87b03e5Sespie 	    abort ();
850*c87b03e5Sespie 	  if (TEST_BIT (insns_with_deaths, uid))
851*c87b03e5Sespie 	    wp->spanned_deaths++;
852*c87b03e5Sespie 	  use->undefined = final_undef;
853*c87b03e5Sespie 	}
854*c87b03e5Sespie     }
855*c87b03e5Sespie 
856*c87b03e5Sespie   return !defined;
857*c87b03e5Sespie }
858*c87b03e5Sespie 
859*c87b03e5Sespie /* Same as live_out_1() (actually calls it), but caches some information.
860*c87b03e5Sespie    E.g. if we reached this INSN with the current regno already, and the
861*c87b03e5Sespie    current undefined bits are a subset of those as we came here, we
862*c87b03e5Sespie    simply connect the web parts of the USE, and the one cached for this
863*c87b03e5Sespie    INSN, and additionally return zero, indicating we don't need to traverse
864*c87b03e5Sespie    this path any longer (all effect were already seen, as we first reached
865*c87b03e5Sespie    this insn).  */
866*c87b03e5Sespie 
867*c87b03e5Sespie static inline int
live_out(df,use,insn)868*c87b03e5Sespie live_out (df, use, insn)
869*c87b03e5Sespie      struct df *df;
870*c87b03e5Sespie      struct curr_use *use;
871*c87b03e5Sespie      rtx insn;
872*c87b03e5Sespie {
873*c87b03e5Sespie   unsigned int uid = INSN_UID (insn);
874*c87b03e5Sespie   if (visit_trace[uid].wp
875*c87b03e5Sespie       && DF_REF_REGNO (visit_trace[uid].wp->ref) == use->regno
876*c87b03e5Sespie       && (use->undefined & ~visit_trace[uid].undefined) == 0)
877*c87b03e5Sespie     {
878*c87b03e5Sespie       union_web_parts (visit_trace[uid].wp, use->wp);
879*c87b03e5Sespie       /* Don't search any further, as we already were here with this regno.  */
880*c87b03e5Sespie       return 0;
881*c87b03e5Sespie     }
882*c87b03e5Sespie   else
883*c87b03e5Sespie     return live_out_1 (df, use, insn);
884*c87b03e5Sespie }
885*c87b03e5Sespie 
886*c87b03e5Sespie /* The current USE reached a basic block head.  The edge E is one
887*c87b03e5Sespie    of the predecessors edges.  This evaluates the effect of the predecessor
888*c87b03e5Sespie    block onto the USE, and returns the next insn, which should be looked at.
889*c87b03e5Sespie    This either is the last insn of that pred. block, or the first one.
890*c87b03e5Sespie    The latter happens, when the pred. block has no possible effect on the
891*c87b03e5Sespie    USE, except for conflicts.  In that case, it's remembered, that the USE
892*c87b03e5Sespie    is live over that whole block, and it's skipped.  Otherwise we simply
893*c87b03e5Sespie    continue with the last insn of the block.
894*c87b03e5Sespie 
895*c87b03e5Sespie    This also determines the effects of abnormal edges, and remembers
896*c87b03e5Sespie    which uses are live at the end of that basic block.  */
897*c87b03e5Sespie 
898*c87b03e5Sespie static rtx
live_in_edge(df,use,e)899*c87b03e5Sespie live_in_edge (df, use, e)
900*c87b03e5Sespie      struct df *df;
901*c87b03e5Sespie      struct curr_use *use;
902*c87b03e5Sespie      edge e;
903*c87b03e5Sespie {
904*c87b03e5Sespie   struct ra_bb_info *info_pred;
905*c87b03e5Sespie   rtx next_insn;
906*c87b03e5Sespie   /* Call used hard regs die over an exception edge, ergo
907*c87b03e5Sespie      they don't reach the predecessor block, so ignore such
908*c87b03e5Sespie      uses.  And also don't set the live_over_abnormal flag
909*c87b03e5Sespie      for them.  */
910*c87b03e5Sespie   if ((e->flags & EDGE_EH) && use->regno < FIRST_PSEUDO_REGISTER
911*c87b03e5Sespie       && call_used_regs[use->regno])
912*c87b03e5Sespie     return NULL_RTX;
913*c87b03e5Sespie   if (e->flags & EDGE_ABNORMAL)
914*c87b03e5Sespie     use->live_over_abnormal = 1;
915*c87b03e5Sespie   bitmap_set_bit (live_at_end[e->src->index], DF_REF_ID (use->wp->ref));
916*c87b03e5Sespie   info_pred = (struct ra_bb_info *) e->src->aux;
917*c87b03e5Sespie   next_insn = e->src->end;
918*c87b03e5Sespie 
919*c87b03e5Sespie   /* If the last insn of the pred. block doesn't completely define the
920*c87b03e5Sespie      current use, we need to check the block.  */
921*c87b03e5Sespie   if (live_out (df, use, next_insn))
922*c87b03e5Sespie     {
923*c87b03e5Sespie       /* If the current regno isn't mentioned anywhere in the whole block,
924*c87b03e5Sespie 	 and the complete use is still undefined...  */
925*c87b03e5Sespie       if (!bitmap_bit_p (info_pred->regnos_mentioned, use->regno)
926*c87b03e5Sespie 	  && (rtx_to_undefined (use->x) & ~use->undefined) == 0)
927*c87b03e5Sespie 	{
928*c87b03e5Sespie 	  /* ...we can hop over the whole block and defer conflict
929*c87b03e5Sespie 	     creation to later.  */
930*c87b03e5Sespie 	  bitmap_set_bit (info_pred->live_throughout,
931*c87b03e5Sespie 			  DF_REF_ID (use->wp->ref));
932*c87b03e5Sespie 	  next_insn = e->src->head;
933*c87b03e5Sespie 	}
934*c87b03e5Sespie       return next_insn;
935*c87b03e5Sespie     }
936*c87b03e5Sespie   else
937*c87b03e5Sespie     return NULL_RTX;
938*c87b03e5Sespie }
939*c87b03e5Sespie 
940*c87b03e5Sespie /* USE flows into the end of the insns preceding INSN.  Determine
941*c87b03e5Sespie    their effects (in live_out()) and possibly loop over the preceding INSN,
942*c87b03e5Sespie    or call itself recursively on a basic block border.  When a topleve
943*c87b03e5Sespie    call of this function returns the USE is completely analyzed.  I.e.
944*c87b03e5Sespie    its def-use chain (at least) is built, possibly connected with other
945*c87b03e5Sespie    def-use chains, and all defs during that chain are noted.  */
946*c87b03e5Sespie 
947*c87b03e5Sespie static void
live_in(df,use,insn)948*c87b03e5Sespie live_in (df, use, insn)
949*c87b03e5Sespie      struct df *df;
950*c87b03e5Sespie      struct curr_use *use;
951*c87b03e5Sespie      rtx insn;
952*c87b03e5Sespie {
953*c87b03e5Sespie   unsigned int loc_vpass = visited_pass;
954*c87b03e5Sespie 
955*c87b03e5Sespie   /* Note, that, even _if_ we are called with use->wp a root-part, this might
956*c87b03e5Sespie      become non-root in the for() loop below (due to live_out() unioning
957*c87b03e5Sespie      it).  So beware, not to change use->wp in a way, for which only root-webs
958*c87b03e5Sespie      are allowed.  */
959*c87b03e5Sespie   while (1)
960*c87b03e5Sespie     {
961*c87b03e5Sespie       int uid = INSN_UID (insn);
962*c87b03e5Sespie       basic_block bb = BLOCK_FOR_INSN (insn);
963*c87b03e5Sespie       number_seen[uid]++;
964*c87b03e5Sespie 
965*c87b03e5Sespie       /* We want to be as fast as possible, so explicitely write
966*c87b03e5Sespie 	 this loop.  */
967*c87b03e5Sespie       for (insn = PREV_INSN (insn); insn && !INSN_P (insn);
968*c87b03e5Sespie 	   insn = PREV_INSN (insn))
969*c87b03e5Sespie 	;
970*c87b03e5Sespie       if (!insn)
971*c87b03e5Sespie 	return;
972*c87b03e5Sespie       if (bb != BLOCK_FOR_INSN (insn))
973*c87b03e5Sespie 	{
974*c87b03e5Sespie 	  edge e;
975*c87b03e5Sespie 	  unsigned HOST_WIDE_INT undef = use->undefined;
976*c87b03e5Sespie 	  struct ra_bb_info *info = (struct ra_bb_info *) bb->aux;
977*c87b03e5Sespie 	  if ((e = bb->pred) == NULL)
978*c87b03e5Sespie 	    return;
979*c87b03e5Sespie 	  /* We now check, if we already traversed the predecessors of this
980*c87b03e5Sespie 	     block for the current pass and the current set of undefined
981*c87b03e5Sespie 	     bits.  If yes, we don't need to check the predecessors again.
982*c87b03e5Sespie 	     So, conceptually this information is tagged to the first
983*c87b03e5Sespie 	     insn of a basic block.  */
984*c87b03e5Sespie 	  if (info->pass == loc_vpass && (undef & ~info->undefined) == 0)
985*c87b03e5Sespie 	    return;
986*c87b03e5Sespie 	  info->pass = loc_vpass;
987*c87b03e5Sespie 	  info->undefined = undef;
988*c87b03e5Sespie 	  /* All but the last predecessor are handled recursively.  */
989*c87b03e5Sespie 	  for (; e->pred_next; e = e->pred_next)
990*c87b03e5Sespie 	    {
991*c87b03e5Sespie 	      insn = live_in_edge (df, use, e);
992*c87b03e5Sespie 	      if (insn)
993*c87b03e5Sespie 		live_in (df, use, insn);
994*c87b03e5Sespie 	      use->undefined = undef;
995*c87b03e5Sespie 	    }
996*c87b03e5Sespie 	  insn = live_in_edge (df, use, e);
997*c87b03e5Sespie 	  if (!insn)
998*c87b03e5Sespie 	    return;
999*c87b03e5Sespie 	}
1000*c87b03e5Sespie       else if (!live_out (df, use, insn))
1001*c87b03e5Sespie 	return;
1002*c87b03e5Sespie     }
1003*c87b03e5Sespie }
1004*c87b03e5Sespie 
1005*c87b03e5Sespie /* Determine all regnos which are mentioned in a basic block, in an
1006*c87b03e5Sespie    interesting way.  Interesting here means either in a def, or as the
1007*c87b03e5Sespie    source of a move insn.  We only look at insns added since the last
1008*c87b03e5Sespie    pass.  */
1009*c87b03e5Sespie 
1010*c87b03e5Sespie static void
update_regnos_mentioned()1011*c87b03e5Sespie update_regnos_mentioned ()
1012*c87b03e5Sespie {
1013*c87b03e5Sespie   int last_uid = last_max_uid;
1014*c87b03e5Sespie   rtx insn;
1015*c87b03e5Sespie   basic_block bb;
1016*c87b03e5Sespie   for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
1017*c87b03e5Sespie     if (INSN_P (insn))
1018*c87b03e5Sespie       {
1019*c87b03e5Sespie 	/* Don't look at old insns.  */
1020*c87b03e5Sespie 	if (INSN_UID (insn) < last_uid)
1021*c87b03e5Sespie 	  {
1022*c87b03e5Sespie 	    /* XXX We should also remember moves over iterations (we already
1023*c87b03e5Sespie 	       save the cache, but not the movelist).  */
1024*c87b03e5Sespie 	    if (copy_insn_p (insn, NULL, NULL))
1025*c87b03e5Sespie 	      remember_move (insn);
1026*c87b03e5Sespie 	  }
1027*c87b03e5Sespie 	else if ((bb = BLOCK_FOR_INSN (insn)) != NULL)
1028*c87b03e5Sespie 	  {
1029*c87b03e5Sespie 	    rtx source;
1030*c87b03e5Sespie 	    struct ra_bb_info *info = (struct ra_bb_info *) bb->aux;
1031*c87b03e5Sespie 	    bitmap mentioned = info->regnos_mentioned;
1032*c87b03e5Sespie 	    struct df_link *link;
1033*c87b03e5Sespie 	    if (copy_insn_p (insn, &source, NULL))
1034*c87b03e5Sespie 	      {
1035*c87b03e5Sespie 		remember_move (insn);
1036*c87b03e5Sespie 		bitmap_set_bit (mentioned,
1037*c87b03e5Sespie 				REGNO (GET_CODE (source) == SUBREG
1038*c87b03e5Sespie 				       ? SUBREG_REG (source) : source));
1039*c87b03e5Sespie 	      }
1040*c87b03e5Sespie 	    for (link = DF_INSN_DEFS (df, insn); link; link = link->next)
1041*c87b03e5Sespie 	      if (link->ref)
1042*c87b03e5Sespie 		bitmap_set_bit (mentioned, DF_REF_REGNO (link->ref));
1043*c87b03e5Sespie 	  }
1044*c87b03e5Sespie       }
1045*c87b03e5Sespie }
1046*c87b03e5Sespie 
1047*c87b03e5Sespie /* Handle the uses which reach a block end, but were defered due
1048*c87b03e5Sespie    to it's regno not being mentioned in that block.  This adds the
1049*c87b03e5Sespie    remaining conflicts and updates also the crosses_call and
1050*c87b03e5Sespie    spanned_deaths members.  */
1051*c87b03e5Sespie 
1052*c87b03e5Sespie static void
livethrough_conflicts_bb(bb)1053*c87b03e5Sespie livethrough_conflicts_bb (bb)
1054*c87b03e5Sespie      basic_block bb;
1055*c87b03e5Sespie {
1056*c87b03e5Sespie   struct ra_bb_info *info = (struct ra_bb_info *) bb->aux;
1057*c87b03e5Sespie   rtx insn;
1058*c87b03e5Sespie   bitmap all_defs;
1059*c87b03e5Sespie   int first, use_id;
1060*c87b03e5Sespie   unsigned int deaths = 0;
1061*c87b03e5Sespie   unsigned int contains_call = 0;
1062*c87b03e5Sespie 
1063*c87b03e5Sespie   /* If there are no defered uses, just return.  */
1064*c87b03e5Sespie   if ((first = bitmap_first_set_bit (info->live_throughout)) < 0)
1065*c87b03e5Sespie     return;
1066*c87b03e5Sespie 
1067*c87b03e5Sespie   /* First collect the IDs of all defs, count the number of death
1068*c87b03e5Sespie      containing insns, and if there's some call_insn here.  */
1069*c87b03e5Sespie   all_defs = BITMAP_XMALLOC ();
1070*c87b03e5Sespie   for (insn = bb->head; insn; insn = NEXT_INSN (insn))
1071*c87b03e5Sespie     {
1072*c87b03e5Sespie       if (INSN_P (insn))
1073*c87b03e5Sespie 	{
1074*c87b03e5Sespie 	  unsigned int n;
1075*c87b03e5Sespie 	  struct ra_insn_info info;
1076*c87b03e5Sespie 
1077*c87b03e5Sespie 	  info = insn_df[INSN_UID (insn)];
1078*c87b03e5Sespie 	  for (n = 0; n < info.num_defs; n++)
1079*c87b03e5Sespie 	    bitmap_set_bit (all_defs, DF_REF_ID (info.defs[n]));
1080*c87b03e5Sespie 	  if (TEST_BIT (insns_with_deaths, INSN_UID (insn)))
1081*c87b03e5Sespie 	    deaths++;
1082*c87b03e5Sespie 	  if (GET_CODE (insn) == CALL_INSN)
1083*c87b03e5Sespie 	    contains_call = 1;
1084*c87b03e5Sespie 	}
1085*c87b03e5Sespie       if (insn == bb->end)
1086*c87b03e5Sespie 	break;
1087*c87b03e5Sespie     }
1088*c87b03e5Sespie 
1089*c87b03e5Sespie   /* And now, if we have found anything, make all live_through
1090*c87b03e5Sespie      uses conflict with all defs, and update their other members.  */
1091*c87b03e5Sespie   if (deaths > 0 || bitmap_first_set_bit (all_defs) >= 0)
1092*c87b03e5Sespie     EXECUTE_IF_SET_IN_BITMAP (info->live_throughout, first, use_id,
1093*c87b03e5Sespie       {
1094*c87b03e5Sespie         struct web_part *wp = &web_parts[df->def_id + use_id];
1095*c87b03e5Sespie         unsigned int bl = rtx_to_bits (DF_REF_REG (wp->ref));
1096*c87b03e5Sespie         bitmap conflicts;
1097*c87b03e5Sespie         wp = find_web_part (wp);
1098*c87b03e5Sespie         wp->spanned_deaths += deaths;
1099*c87b03e5Sespie 	wp->crosses_call |= contains_call;
1100*c87b03e5Sespie         conflicts = get_sub_conflicts (wp, bl);
1101*c87b03e5Sespie         bitmap_operation (conflicts, conflicts, all_defs, BITMAP_IOR);
1102*c87b03e5Sespie       });
1103*c87b03e5Sespie 
1104*c87b03e5Sespie   BITMAP_XFREE (all_defs);
1105*c87b03e5Sespie }
1106*c87b03e5Sespie 
1107*c87b03e5Sespie /* Allocate the per basic block info for traversing the insn stream for
1108*c87b03e5Sespie    building live ranges.  */
1109*c87b03e5Sespie 
1110*c87b03e5Sespie static void
init_bb_info()1111*c87b03e5Sespie init_bb_info ()
1112*c87b03e5Sespie {
1113*c87b03e5Sespie   basic_block bb;
1114*c87b03e5Sespie   FOR_ALL_BB (bb)
1115*c87b03e5Sespie     {
1116*c87b03e5Sespie       struct ra_bb_info *info =
1117*c87b03e5Sespie 	(struct ra_bb_info *) xcalloc (1, sizeof *info);
1118*c87b03e5Sespie       info->regnos_mentioned = BITMAP_XMALLOC ();
1119*c87b03e5Sespie       info->live_throughout = BITMAP_XMALLOC ();
1120*c87b03e5Sespie       info->old_aux = bb->aux;
1121*c87b03e5Sespie       bb->aux = (void *) info;
1122*c87b03e5Sespie     }
1123*c87b03e5Sespie }
1124*c87b03e5Sespie 
1125*c87b03e5Sespie /* Free that per basic block info.  */
1126*c87b03e5Sespie 
1127*c87b03e5Sespie static void
free_bb_info()1128*c87b03e5Sespie free_bb_info ()
1129*c87b03e5Sespie {
1130*c87b03e5Sespie   basic_block bb;
1131*c87b03e5Sespie   FOR_ALL_BB (bb)
1132*c87b03e5Sespie     {
1133*c87b03e5Sespie       struct ra_bb_info *info = (struct ra_bb_info *) bb->aux;
1134*c87b03e5Sespie       BITMAP_XFREE (info->regnos_mentioned);
1135*c87b03e5Sespie       BITMAP_XFREE (info->live_throughout);
1136*c87b03e5Sespie       bb->aux = info->old_aux;
1137*c87b03e5Sespie       free (info);
1138*c87b03e5Sespie     }
1139*c87b03e5Sespie }
1140*c87b03e5Sespie 
1141*c87b03e5Sespie /* Toplevel function for the first part of this file.
1142*c87b03e5Sespie    Connect web parts, thereby implicitely building webs, and remember
1143*c87b03e5Sespie    their conflicts.  */
1144*c87b03e5Sespie 
1145*c87b03e5Sespie static void
build_web_parts_and_conflicts(df)1146*c87b03e5Sespie build_web_parts_and_conflicts (df)
1147*c87b03e5Sespie      struct df *df;
1148*c87b03e5Sespie {
1149*c87b03e5Sespie   struct df_link *link;
1150*c87b03e5Sespie   struct curr_use use;
1151*c87b03e5Sespie   basic_block bb;
1152*c87b03e5Sespie 
1153*c87b03e5Sespie   number_seen = (int *) xcalloc (get_max_uid (), sizeof (int));
1154*c87b03e5Sespie   visit_trace = (struct visit_trace *) xcalloc (get_max_uid (),
1155*c87b03e5Sespie 						sizeof (visit_trace[0]));
1156*c87b03e5Sespie   update_regnos_mentioned ();
1157*c87b03e5Sespie 
1158*c87b03e5Sespie   /* Here's the main loop.
1159*c87b03e5Sespie      It goes through all insn's, connects web parts along the way, notes
1160*c87b03e5Sespie      conflicts between webparts, and remembers move instructions.  */
1161*c87b03e5Sespie   visited_pass = 0;
1162*c87b03e5Sespie   for (use.regno = 0; use.regno < (unsigned int)max_regno; use.regno++)
1163*c87b03e5Sespie     if (use.regno >= FIRST_PSEUDO_REGISTER || !fixed_regs[use.regno])
1164*c87b03e5Sespie       for (link = df->regs[use.regno].uses; link; link = link->next)
1165*c87b03e5Sespie         if (link->ref)
1166*c87b03e5Sespie 	  {
1167*c87b03e5Sespie 	    struct ref *ref = link->ref;
1168*c87b03e5Sespie 	    rtx insn = DF_REF_INSN (ref);
1169*c87b03e5Sespie 	    /* Only recheck marked or new uses, or uses from hardregs.  */
1170*c87b03e5Sespie 	    if (use.regno >= FIRST_PSEUDO_REGISTER
1171*c87b03e5Sespie 		&& DF_REF_ID (ref) < last_use_id
1172*c87b03e5Sespie 		&& !TEST_BIT (last_check_uses, DF_REF_ID (ref)))
1173*c87b03e5Sespie 	      continue;
1174*c87b03e5Sespie 	    use.wp = &web_parts[df->def_id + DF_REF_ID (ref)];
1175*c87b03e5Sespie 	    use.x = DF_REF_REG (ref);
1176*c87b03e5Sespie 	    use.live_over_abnormal = 0;
1177*c87b03e5Sespie 	    use.undefined = rtx_to_undefined (use.x);
1178*c87b03e5Sespie 	    visited_pass++;
1179*c87b03e5Sespie 	    live_in (df, &use, insn);
1180*c87b03e5Sespie 	    if (use.live_over_abnormal)
1181*c87b03e5Sespie 	      SET_BIT (live_over_abnormal, DF_REF_ID (ref));
1182*c87b03e5Sespie 	  }
1183*c87b03e5Sespie 
1184*c87b03e5Sespie   dump_number_seen ();
1185*c87b03e5Sespie   FOR_ALL_BB (bb)
1186*c87b03e5Sespie     {
1187*c87b03e5Sespie       struct ra_bb_info *info = (struct ra_bb_info *) bb->aux;
1188*c87b03e5Sespie       livethrough_conflicts_bb (bb);
1189*c87b03e5Sespie       bitmap_zero (info->live_throughout);
1190*c87b03e5Sespie       info->pass = 0;
1191*c87b03e5Sespie     }
1192*c87b03e5Sespie   free (visit_trace);
1193*c87b03e5Sespie   free (number_seen);
1194*c87b03e5Sespie }
1195*c87b03e5Sespie 
1196*c87b03e5Sespie /* Here we look per insn, for DF references being in uses _and_ defs.
1197*c87b03e5Sespie    This means, in the RTL a (REG xx) expression was seen as a
1198*c87b03e5Sespie    read/modify/write, as happens for (set (subreg:SI (reg:DI xx)) (...))
1199*c87b03e5Sespie    e.g.  Our code has created two webs for this, as it should.  Unfortunately,
1200*c87b03e5Sespie    as the REG reference is only one time in the RTL we can't color
1201*c87b03e5Sespie    both webs different (arguably this also would be wrong for a real
1202*c87b03e5Sespie    read-mod-write instruction), so we must reconnect such webs.  */
1203*c87b03e5Sespie 
1204*c87b03e5Sespie static void
connect_rmw_web_parts(df)1205*c87b03e5Sespie connect_rmw_web_parts (df)
1206*c87b03e5Sespie      struct df *df;
1207*c87b03e5Sespie {
1208*c87b03e5Sespie   unsigned int i;
1209*c87b03e5Sespie 
1210*c87b03e5Sespie   for (i = 0; i < df->use_id; i++)
1211*c87b03e5Sespie     {
1212*c87b03e5Sespie       struct web_part *wp1 = &web_parts[df->def_id + i];
1213*c87b03e5Sespie       rtx reg;
1214*c87b03e5Sespie       struct df_link *link;
1215*c87b03e5Sespie       if (!wp1->ref)
1216*c87b03e5Sespie 	continue;
1217*c87b03e5Sespie       /* If it's an uninitialized web, we don't want to connect it to others,
1218*c87b03e5Sespie 	 as the read cycle in read-mod-write had probably no effect.  */
1219*c87b03e5Sespie       if (find_web_part (wp1) >= &web_parts[df->def_id])
1220*c87b03e5Sespie 	continue;
1221*c87b03e5Sespie       reg = DF_REF_REAL_REG (wp1->ref);
1222*c87b03e5Sespie       link = DF_INSN_DEFS (df, DF_REF_INSN (wp1->ref));
1223*c87b03e5Sespie       for (; link; link = link->next)
1224*c87b03e5Sespie         if (reg == DF_REF_REAL_REG (link->ref))
1225*c87b03e5Sespie 	  {
1226*c87b03e5Sespie 	    struct web_part *wp2 = &web_parts[DF_REF_ID (link->ref)];
1227*c87b03e5Sespie 	    union_web_parts (wp1, wp2);
1228*c87b03e5Sespie 	  }
1229*c87b03e5Sespie     }
1230*c87b03e5Sespie }
1231*c87b03e5Sespie 
1232*c87b03e5Sespie /* Deletes all hardregs from *S which are not allowed for MODE.  */
1233*c87b03e5Sespie 
1234*c87b03e5Sespie static void
prune_hardregs_for_mode(s,mode)1235*c87b03e5Sespie prune_hardregs_for_mode (s, mode)
1236*c87b03e5Sespie      HARD_REG_SET *s;
1237*c87b03e5Sespie      enum machine_mode mode;
1238*c87b03e5Sespie {
1239*c87b03e5Sespie   AND_HARD_REG_SET (*s, hardregs_for_mode[(int) mode]);
1240*c87b03e5Sespie }
1241*c87b03e5Sespie 
1242*c87b03e5Sespie /* Initialize the members of a web, which are deducible from REG.  */
1243*c87b03e5Sespie 
1244*c87b03e5Sespie static void
init_one_web_common(web,reg)1245*c87b03e5Sespie init_one_web_common (web, reg)
1246*c87b03e5Sespie      struct web *web;
1247*c87b03e5Sespie      rtx reg;
1248*c87b03e5Sespie {
1249*c87b03e5Sespie   if (GET_CODE (reg) != REG)
1250*c87b03e5Sespie     abort ();
1251*c87b03e5Sespie   /* web->id isn't initialized here.  */
1252*c87b03e5Sespie   web->regno = REGNO (reg);
1253*c87b03e5Sespie   web->orig_x = reg;
1254*c87b03e5Sespie   if (!web->dlink)
1255*c87b03e5Sespie     {
1256*c87b03e5Sespie       web->dlink = (struct dlist *) ra_calloc (sizeof (struct dlist));
1257*c87b03e5Sespie       DLIST_WEB (web->dlink) = web;
1258*c87b03e5Sespie     }
1259*c87b03e5Sespie   /* XXX
1260*c87b03e5Sespie      the former (superunion) doesn't constrain the graph enough. E.g.
1261*c87b03e5Sespie      on x86 QImode _requires_ QI_REGS, but as alternate class usually
1262*c87b03e5Sespie      GENERAL_REGS is given.  So the graph is not constrained enough,
1263*c87b03e5Sespie      thinking it has more freedom then it really has, which leads
1264*c87b03e5Sespie      to repeated spill tryings.  OTOH the latter (only using preferred
1265*c87b03e5Sespie      class) is too constrained, as normally (e.g. with all SImode
1266*c87b03e5Sespie      pseudos), they can be allocated also in the alternate class.
1267*c87b03e5Sespie      What we really want, are the _exact_ hard regs allowed, not
1268*c87b03e5Sespie      just a class.  Later.  */
1269*c87b03e5Sespie   /*web->regclass = reg_class_superunion
1270*c87b03e5Sespie 		    [reg_preferred_class (web->regno)]
1271*c87b03e5Sespie 		    [reg_alternate_class (web->regno)];*/
1272*c87b03e5Sespie   /*web->regclass = reg_preferred_class (web->regno);*/
1273*c87b03e5Sespie   web->regclass = reg_class_subunion
1274*c87b03e5Sespie     [reg_preferred_class (web->regno)] [reg_alternate_class (web->regno)];
1275*c87b03e5Sespie   web->regclass = reg_preferred_class (web->regno);
1276*c87b03e5Sespie   if (web->regno < FIRST_PSEUDO_REGISTER)
1277*c87b03e5Sespie     {
1278*c87b03e5Sespie       web->color = web->regno;
1279*c87b03e5Sespie       put_web (web, PRECOLORED);
1280*c87b03e5Sespie       web->num_conflicts = UINT_MAX;
1281*c87b03e5Sespie       web->add_hardregs = 0;
1282*c87b03e5Sespie       CLEAR_HARD_REG_SET (web->usable_regs);
1283*c87b03e5Sespie       SET_HARD_REG_BIT (web->usable_regs, web->regno);
1284*c87b03e5Sespie       web->num_freedom = 1;
1285*c87b03e5Sespie     }
1286*c87b03e5Sespie   else
1287*c87b03e5Sespie     {
1288*c87b03e5Sespie       HARD_REG_SET alternate;
1289*c87b03e5Sespie       web->color = -1;
1290*c87b03e5Sespie       put_web (web, INITIAL);
1291*c87b03e5Sespie       /* add_hardregs is wrong in multi-length classes, e.g.
1292*c87b03e5Sespie 	 using a DFmode pseudo on x86 can result in class FLOAT_INT_REGS,
1293*c87b03e5Sespie 	 where, if it finally is allocated to GENERAL_REGS it needs two,
1294*c87b03e5Sespie 	 if allocated to FLOAT_REGS only one hardreg.  XXX */
1295*c87b03e5Sespie       web->add_hardregs =
1296*c87b03e5Sespie 	CLASS_MAX_NREGS (web->regclass, PSEUDO_REGNO_MODE (web->regno)) - 1;
1297*c87b03e5Sespie       web->num_conflicts = 0 * web->add_hardregs;
1298*c87b03e5Sespie       COPY_HARD_REG_SET (web->usable_regs,
1299*c87b03e5Sespie 			reg_class_contents[reg_preferred_class (web->regno)]);
1300*c87b03e5Sespie       COPY_HARD_REG_SET (alternate,
1301*c87b03e5Sespie 			reg_class_contents[reg_alternate_class (web->regno)]);
1302*c87b03e5Sespie       IOR_HARD_REG_SET (web->usable_regs, alternate);
1303*c87b03e5Sespie       /*IOR_HARD_REG_SET (web->usable_regs,
1304*c87b03e5Sespie 			reg_class_contents[reg_alternate_class
1305*c87b03e5Sespie 			(web->regno)]);*/
1306*c87b03e5Sespie       AND_COMPL_HARD_REG_SET (web->usable_regs, never_use_colors);
1307*c87b03e5Sespie       prune_hardregs_for_mode (&web->usable_regs,
1308*c87b03e5Sespie 			       PSEUDO_REGNO_MODE (web->regno));
1309*c87b03e5Sespie #ifdef CLASS_CANNOT_CHANGE_MODE
1310*c87b03e5Sespie       if (web->mode_changed)
1311*c87b03e5Sespie         AND_COMPL_HARD_REG_SET (web->usable_regs, reg_class_contents[
1312*c87b03e5Sespie 			          (int) CLASS_CANNOT_CHANGE_MODE]);
1313*c87b03e5Sespie #endif
1314*c87b03e5Sespie       web->num_freedom = hard_regs_count (web->usable_regs);
1315*c87b03e5Sespie       web->num_freedom -= web->add_hardregs;
1316*c87b03e5Sespie       if (!web->num_freedom)
1317*c87b03e5Sespie 	abort();
1318*c87b03e5Sespie     }
1319*c87b03e5Sespie   COPY_HARD_REG_SET (web->orig_usable_regs, web->usable_regs);
1320*c87b03e5Sespie }
1321*c87b03e5Sespie 
1322*c87b03e5Sespie /* Initializes WEBs members from REG or zero them.  */
1323*c87b03e5Sespie 
1324*c87b03e5Sespie static void
init_one_web(web,reg)1325*c87b03e5Sespie init_one_web (web, reg)
1326*c87b03e5Sespie      struct web *web;
1327*c87b03e5Sespie      rtx reg;
1328*c87b03e5Sespie {
1329*c87b03e5Sespie   memset (web, 0, sizeof (struct web));
1330*c87b03e5Sespie   init_one_web_common (web, reg);
1331*c87b03e5Sespie   web->useless_conflicts = BITMAP_XMALLOC ();
1332*c87b03e5Sespie }
1333*c87b03e5Sespie 
1334*c87b03e5Sespie /* WEB is an old web, meaning it came from the last pass, and got a
1335*c87b03e5Sespie    color.  We want to remember some of it's info, so zero only some
1336*c87b03e5Sespie    members.  */
1337*c87b03e5Sespie 
1338*c87b03e5Sespie static void
reinit_one_web(web,reg)1339*c87b03e5Sespie reinit_one_web (web, reg)
1340*c87b03e5Sespie      struct web *web;
1341*c87b03e5Sespie      rtx reg;
1342*c87b03e5Sespie {
1343*c87b03e5Sespie   web->old_color = web->color + 1;
1344*c87b03e5Sespie   init_one_web_common (web, reg);
1345*c87b03e5Sespie   web->span_deaths = 0;
1346*c87b03e5Sespie   web->spill_temp = 0;
1347*c87b03e5Sespie   web->orig_spill_temp = 0;
1348*c87b03e5Sespie   web->use_my_regs = 0;
1349*c87b03e5Sespie   web->spill_cost = 0;
1350*c87b03e5Sespie   web->was_spilled = 0;
1351*c87b03e5Sespie   web->is_coalesced = 0;
1352*c87b03e5Sespie   web->artificial = 0;
1353*c87b03e5Sespie   web->live_over_abnormal = 0;
1354*c87b03e5Sespie   web->mode_changed = 0;
1355*c87b03e5Sespie   web->move_related = 0;
1356*c87b03e5Sespie   web->in_load = 0;
1357*c87b03e5Sespie   web->target_of_spilled_move = 0;
1358*c87b03e5Sespie   web->num_aliased = 0;
1359*c87b03e5Sespie   if (web->type == PRECOLORED)
1360*c87b03e5Sespie     {
1361*c87b03e5Sespie       web->num_defs = 0;
1362*c87b03e5Sespie       web->num_uses = 0;
1363*c87b03e5Sespie       web->orig_spill_cost = 0;
1364*c87b03e5Sespie     }
1365*c87b03e5Sespie   CLEAR_HARD_REG_SET (web->bias_colors);
1366*c87b03e5Sespie   CLEAR_HARD_REG_SET (web->prefer_colors);
1367*c87b03e5Sespie   web->reg_rtx = NULL;
1368*c87b03e5Sespie   web->stack_slot = NULL;
1369*c87b03e5Sespie   web->pattern = NULL;
1370*c87b03e5Sespie   web->alias = NULL;
1371*c87b03e5Sespie   if (web->moves)
1372*c87b03e5Sespie     abort ();
1373*c87b03e5Sespie   if (!web->useless_conflicts)
1374*c87b03e5Sespie     abort ();
1375*c87b03e5Sespie }
1376*c87b03e5Sespie 
1377*c87b03e5Sespie /* Insert and returns a subweb corresponding to REG into WEB (which
1378*c87b03e5Sespie    becomes its super web).  It must not exist already.  */
1379*c87b03e5Sespie 
1380*c87b03e5Sespie static struct web *
add_subweb(web,reg)1381*c87b03e5Sespie add_subweb (web, reg)
1382*c87b03e5Sespie      struct web *web;
1383*c87b03e5Sespie      rtx reg;
1384*c87b03e5Sespie {
1385*c87b03e5Sespie   struct web *w;
1386*c87b03e5Sespie   if (GET_CODE (reg) != SUBREG)
1387*c87b03e5Sespie     abort ();
1388*c87b03e5Sespie   w = (struct web *) xmalloc (sizeof (struct web));
1389*c87b03e5Sespie   /* Copy most content from parent-web.  */
1390*c87b03e5Sespie   *w = *web;
1391*c87b03e5Sespie   /* And initialize the private stuff.  */
1392*c87b03e5Sespie   w->orig_x = reg;
1393*c87b03e5Sespie   w->add_hardregs = CLASS_MAX_NREGS (web->regclass, GET_MODE (reg)) - 1;
1394*c87b03e5Sespie   w->num_conflicts = 0 * w->add_hardregs;
1395*c87b03e5Sespie   w->num_defs = 0;
1396*c87b03e5Sespie   w->num_uses = 0;
1397*c87b03e5Sespie   w->dlink = NULL;
1398*c87b03e5Sespie   w->parent_web = web;
1399*c87b03e5Sespie   w->subreg_next = web->subreg_next;
1400*c87b03e5Sespie   web->subreg_next = w;
1401*c87b03e5Sespie   return w;
1402*c87b03e5Sespie }
1403*c87b03e5Sespie 
1404*c87b03e5Sespie /* Similar to add_subweb(), but instead of relying on a given SUBREG,
1405*c87b03e5Sespie    we have just a size and an offset of the subpart of the REG rtx.
1406*c87b03e5Sespie    In difference to add_subweb() this marks the new subweb as artificial.  */
1407*c87b03e5Sespie 
1408*c87b03e5Sespie static struct web *
add_subweb_2(web,size_word)1409*c87b03e5Sespie add_subweb_2 (web, size_word)
1410*c87b03e5Sespie      struct web *web;
1411*c87b03e5Sespie      unsigned int size_word;
1412*c87b03e5Sespie {
1413*c87b03e5Sespie   /* To get a correct mode for the to be produced subreg, we don't want to
1414*c87b03e5Sespie      simply do a mode_for_size() for the mode_class of the whole web.
1415*c87b03e5Sespie      Suppose we deal with a CDImode web, but search for a 8 byte part.
1416*c87b03e5Sespie      Now mode_for_size() would only search in the class MODE_COMPLEX_INT
1417*c87b03e5Sespie      and would find CSImode which probably is not what we want.  Instead
1418*c87b03e5Sespie      we want DImode, which is in a completely other class.  For this to work
1419*c87b03e5Sespie      we instead first search the already existing subwebs, and take
1420*c87b03e5Sespie      _their_ modeclasses as base for a search for ourself.  */
1421*c87b03e5Sespie   rtx ref_rtx = (web->subreg_next ? web->subreg_next : web)->orig_x;
1422*c87b03e5Sespie   unsigned int size = BYTE_LENGTH (size_word) * BITS_PER_UNIT;
1423*c87b03e5Sespie   enum machine_mode mode;
1424*c87b03e5Sespie   mode = mode_for_size (size, GET_MODE_CLASS (GET_MODE (ref_rtx)), 0);
1425*c87b03e5Sespie   if (mode == BLKmode)
1426*c87b03e5Sespie     mode = mode_for_size (size, MODE_INT, 0);
1427*c87b03e5Sespie   if (mode == BLKmode)
1428*c87b03e5Sespie     abort ();
1429*c87b03e5Sespie   web = add_subweb (web, gen_rtx_SUBREG (mode, web->orig_x,
1430*c87b03e5Sespie 					 BYTE_BEGIN (size_word)));
1431*c87b03e5Sespie   web->artificial = 1;
1432*c87b03e5Sespie   return web;
1433*c87b03e5Sespie }
1434*c87b03e5Sespie 
1435*c87b03e5Sespie /* Initialize all the web parts we are going to need.  */
1436*c87b03e5Sespie 
1437*c87b03e5Sespie static void
init_web_parts(df)1438*c87b03e5Sespie init_web_parts (df)
1439*c87b03e5Sespie      struct df *df;
1440*c87b03e5Sespie {
1441*c87b03e5Sespie   int regno;
1442*c87b03e5Sespie   unsigned int no;
1443*c87b03e5Sespie   num_webs = 0;
1444*c87b03e5Sespie   for (no = 0; no < df->def_id; no++)
1445*c87b03e5Sespie     {
1446*c87b03e5Sespie       if (df->defs[no])
1447*c87b03e5Sespie 	{
1448*c87b03e5Sespie 	  if (no < last_def_id && web_parts[no].ref != df->defs[no])
1449*c87b03e5Sespie 	    abort ();
1450*c87b03e5Sespie 	  web_parts[no].ref = df->defs[no];
1451*c87b03e5Sespie 	  /* Uplink might be set from the last iteration.  */
1452*c87b03e5Sespie 	  if (!web_parts[no].uplink)
1453*c87b03e5Sespie 	    num_webs++;
1454*c87b03e5Sespie 	}
1455*c87b03e5Sespie       else
1456*c87b03e5Sespie 	/* The last iteration might have left .ref set, while df_analyse()
1457*c87b03e5Sespie 	   removed that ref (due to a removed copy insn) from the df->defs[]
1458*c87b03e5Sespie 	   array.  As we don't check for that in realloc_web_parts()
1459*c87b03e5Sespie 	   we do that here.  */
1460*c87b03e5Sespie 	web_parts[no].ref = NULL;
1461*c87b03e5Sespie     }
1462*c87b03e5Sespie   for (no = 0; no < df->use_id; no++)
1463*c87b03e5Sespie     {
1464*c87b03e5Sespie       if (df->uses[no])
1465*c87b03e5Sespie 	{
1466*c87b03e5Sespie 	  if (no < last_use_id
1467*c87b03e5Sespie 	      && web_parts[no + df->def_id].ref != df->uses[no])
1468*c87b03e5Sespie 	    abort ();
1469*c87b03e5Sespie 	  web_parts[no + df->def_id].ref = df->uses[no];
1470*c87b03e5Sespie 	  if (!web_parts[no + df->def_id].uplink)
1471*c87b03e5Sespie 	    num_webs++;
1472*c87b03e5Sespie 	}
1473*c87b03e5Sespie       else
1474*c87b03e5Sespie 	web_parts[no + df->def_id].ref = NULL;
1475*c87b03e5Sespie     }
1476*c87b03e5Sespie 
1477*c87b03e5Sespie   /* We want to have only one web for each precolored register.  */
1478*c87b03e5Sespie   for (regno = 0; regno < FIRST_PSEUDO_REGISTER; regno++)
1479*c87b03e5Sespie     {
1480*c87b03e5Sespie       struct web_part *r1 = NULL;
1481*c87b03e5Sespie       struct df_link *link;
1482*c87b03e5Sespie       /* Here once was a test, if there is any DEF at all, and only then to
1483*c87b03e5Sespie 	 merge all the parts.  This was incorrect, we really also want to have
1484*c87b03e5Sespie 	 only one web-part for hardregs, even if there is no explicit DEF.  */
1485*c87b03e5Sespie       /* Link together all defs...  */
1486*c87b03e5Sespie       for (link = df->regs[regno].defs; link; link = link->next)
1487*c87b03e5Sespie         if (link->ref)
1488*c87b03e5Sespie 	  {
1489*c87b03e5Sespie 	    struct web_part *r2 = &web_parts[DF_REF_ID (link->ref)];
1490*c87b03e5Sespie 	    if (!r1)
1491*c87b03e5Sespie 	      r1 = r2;
1492*c87b03e5Sespie 	    else
1493*c87b03e5Sespie 	      r1 = union_web_parts (r1, r2);
1494*c87b03e5Sespie 	  }
1495*c87b03e5Sespie       /* ... and all uses.  */
1496*c87b03e5Sespie       for (link = df->regs[regno].uses; link; link = link->next)
1497*c87b03e5Sespie 	if (link->ref)
1498*c87b03e5Sespie 	  {
1499*c87b03e5Sespie 	    struct web_part *r2 = &web_parts[df->def_id
1500*c87b03e5Sespie 		                             + DF_REF_ID (link->ref)];
1501*c87b03e5Sespie 	    if (!r1)
1502*c87b03e5Sespie 	      r1 = r2;
1503*c87b03e5Sespie 	    else
1504*c87b03e5Sespie 	      r1 = union_web_parts (r1, r2);
1505*c87b03e5Sespie 	  }
1506*c87b03e5Sespie     }
1507*c87b03e5Sespie }
1508*c87b03e5Sespie 
1509*c87b03e5Sespie /* In case we want to remember the conflict list of a WEB, before adding
1510*c87b03e5Sespie    new conflicts, we copy it here to orig_conflict_list.  */
1511*c87b03e5Sespie 
1512*c87b03e5Sespie static void
copy_conflict_list(web)1513*c87b03e5Sespie copy_conflict_list (web)
1514*c87b03e5Sespie      struct web *web;
1515*c87b03e5Sespie {
1516*c87b03e5Sespie   struct conflict_link *cl;
1517*c87b03e5Sespie   if (web->orig_conflict_list || web->have_orig_conflicts)
1518*c87b03e5Sespie     abort ();
1519*c87b03e5Sespie   web->have_orig_conflicts = 1;
1520*c87b03e5Sespie   for (cl = web->conflict_list; cl; cl = cl->next)
1521*c87b03e5Sespie     {
1522*c87b03e5Sespie       struct conflict_link *ncl;
1523*c87b03e5Sespie       ncl = (struct conflict_link *) ra_alloc (sizeof *ncl);
1524*c87b03e5Sespie       ncl->t = cl->t;
1525*c87b03e5Sespie       ncl->sub = NULL;
1526*c87b03e5Sespie       ncl->next = web->orig_conflict_list;
1527*c87b03e5Sespie       web->orig_conflict_list = ncl;
1528*c87b03e5Sespie       if (cl->sub)
1529*c87b03e5Sespie 	{
1530*c87b03e5Sespie 	  struct sub_conflict *sl, *nsl;
1531*c87b03e5Sespie 	  for (sl = cl->sub; sl; sl = sl->next)
1532*c87b03e5Sespie 	    {
1533*c87b03e5Sespie 	      nsl = (struct sub_conflict *) ra_alloc (sizeof *nsl);
1534*c87b03e5Sespie 	      nsl->s = sl->s;
1535*c87b03e5Sespie 	      nsl->t = sl->t;
1536*c87b03e5Sespie 	      nsl->next = ncl->sub;
1537*c87b03e5Sespie 	      ncl->sub = nsl;
1538*c87b03e5Sespie 	    }
1539*c87b03e5Sespie 	}
1540*c87b03e5Sespie     }
1541*c87b03e5Sespie }
1542*c87b03e5Sespie 
1543*c87b03e5Sespie /* Possibly add an edge from web FROM to TO marking a conflict between
1544*c87b03e5Sespie    those two.  This is one half of marking a complete conflict, which notes
1545*c87b03e5Sespie    in FROM, that TO is a conflict.  Adding TO to FROM's conflicts might
1546*c87b03e5Sespie    make other conflicts superflous, because the current TO overlaps some web
1547*c87b03e5Sespie    already being in conflict with FROM.  In this case the smaller webs are
1548*c87b03e5Sespie    deleted from the conflict list.  Likewise if TO is overlapped by a web
1549*c87b03e5Sespie    already in the list, it isn't added at all.  Note, that this can only
1550*c87b03e5Sespie    happen, if SUBREG webs are involved.  */
1551*c87b03e5Sespie 
1552*c87b03e5Sespie static void
add_conflict_edge(from,to)1553*c87b03e5Sespie add_conflict_edge (from, to)
1554*c87b03e5Sespie      struct web *from, *to;
1555*c87b03e5Sespie {
1556*c87b03e5Sespie   if (from->type != PRECOLORED)
1557*c87b03e5Sespie     {
1558*c87b03e5Sespie       struct web *pfrom = find_web_for_subweb (from);
1559*c87b03e5Sespie       struct web *pto = find_web_for_subweb (to);
1560*c87b03e5Sespie       struct sub_conflict *sl;
1561*c87b03e5Sespie       struct conflict_link *cl = pfrom->conflict_list;
1562*c87b03e5Sespie       int may_delete = 1;
1563*c87b03e5Sespie 
1564*c87b03e5Sespie       /* This can happen when subwebs of one web conflict with each
1565*c87b03e5Sespie 	 other.  In live_out_1() we created such conflicts between yet
1566*c87b03e5Sespie 	 undefined webparts and defs of parts which didn't overlap with the
1567*c87b03e5Sespie 	 undefined bits.  Then later they nevertheless could have merged into
1568*c87b03e5Sespie 	 one web, and then we land here.  */
1569*c87b03e5Sespie       if (pfrom == pto)
1570*c87b03e5Sespie 	return;
1571*c87b03e5Sespie       if (remember_conflicts && !pfrom->have_orig_conflicts)
1572*c87b03e5Sespie 	copy_conflict_list (pfrom);
1573*c87b03e5Sespie       if (!TEST_BIT (sup_igraph, (pfrom->id * num_webs + pto->id)))
1574*c87b03e5Sespie 	{
1575*c87b03e5Sespie 	  cl = (struct conflict_link *) ra_alloc (sizeof (*cl));
1576*c87b03e5Sespie 	  cl->t = pto;
1577*c87b03e5Sespie 	  cl->sub = NULL;
1578*c87b03e5Sespie 	  cl->next = pfrom->conflict_list;
1579*c87b03e5Sespie 	  pfrom->conflict_list = cl;
1580*c87b03e5Sespie 	  if (pto->type != SELECT && pto->type != COALESCED)
1581*c87b03e5Sespie 	    pfrom->num_conflicts += 1 + pto->add_hardregs;
1582*c87b03e5Sespie           SET_BIT (sup_igraph, (pfrom->id * num_webs + pto->id));
1583*c87b03e5Sespie 	  may_delete = 0;
1584*c87b03e5Sespie 	}
1585*c87b03e5Sespie       else
1586*c87b03e5Sespie         /* We don't need to test for cl==NULL, because at this point
1587*c87b03e5Sespie 	   a cl with cl->t==pto is guaranteed to exist.  */
1588*c87b03e5Sespie         while (cl->t != pto)
1589*c87b03e5Sespie 	  cl = cl->next;
1590*c87b03e5Sespie       if (pfrom != from || pto != to)
1591*c87b03e5Sespie 	{
1592*c87b03e5Sespie 	  /* This is a subconflict which should be added.
1593*c87b03e5Sespie 	     If we inserted cl in this invocation, we really need to add this
1594*c87b03e5Sespie 	     subconflict.  If we did _not_ add it here, we only add the
1595*c87b03e5Sespie 	     subconflict, if cl already had subconflicts, because otherwise
1596*c87b03e5Sespie 	     this indicated, that the whole webs already conflict, which
1597*c87b03e5Sespie 	     means we are not interested in this subconflict.  */
1598*c87b03e5Sespie 	  if (!may_delete || cl->sub != NULL)
1599*c87b03e5Sespie 	    {
1600*c87b03e5Sespie 	      sl = (struct sub_conflict *) ra_alloc (sizeof (*sl));
1601*c87b03e5Sespie 	      sl->s = from;
1602*c87b03e5Sespie 	      sl->t = to;
1603*c87b03e5Sespie 	      sl->next = cl->sub;
1604*c87b03e5Sespie 	      cl->sub = sl;
1605*c87b03e5Sespie 	    }
1606*c87b03e5Sespie 	}
1607*c87b03e5Sespie       else
1608*c87b03e5Sespie 	/* pfrom == from && pto == to means, that we are not interested
1609*c87b03e5Sespie 	   anymore in the subconflict list for this pair, because anyway
1610*c87b03e5Sespie 	   the whole webs conflict.  */
1611*c87b03e5Sespie 	cl->sub = NULL;
1612*c87b03e5Sespie     }
1613*c87b03e5Sespie }
1614*c87b03e5Sespie 
1615*c87b03e5Sespie /* Record a conflict between two webs, if we haven't recorded it
1616*c87b03e5Sespie    already.  */
1617*c87b03e5Sespie 
1618*c87b03e5Sespie void
record_conflict(web1,web2)1619*c87b03e5Sespie record_conflict (web1, web2)
1620*c87b03e5Sespie      struct web *web1, *web2;
1621*c87b03e5Sespie {
1622*c87b03e5Sespie   unsigned int id1 = web1->id, id2 = web2->id;
1623*c87b03e5Sespie   unsigned int index = igraph_index (id1, id2);
1624*c87b03e5Sespie   /* Trivial non-conflict or already recorded conflict.  */
1625*c87b03e5Sespie   if (web1 == web2 || TEST_BIT (igraph, index))
1626*c87b03e5Sespie     return;
1627*c87b03e5Sespie   if (id1 == id2)
1628*c87b03e5Sespie     abort ();
1629*c87b03e5Sespie   /* As fixed_regs are no targets for allocation, conflicts with them
1630*c87b03e5Sespie      are pointless.  */
1631*c87b03e5Sespie   if ((web1->regno < FIRST_PSEUDO_REGISTER && fixed_regs[web1->regno])
1632*c87b03e5Sespie       || (web2->regno < FIRST_PSEUDO_REGISTER && fixed_regs[web2->regno]))
1633*c87b03e5Sespie     return;
1634*c87b03e5Sespie   /* Conflicts with hardregs, which are not even a candidate
1635*c87b03e5Sespie      for this pseudo are also pointless.  */
1636*c87b03e5Sespie   if ((web1->type == PRECOLORED
1637*c87b03e5Sespie        && ! TEST_HARD_REG_BIT (web2->usable_regs, web1->regno))
1638*c87b03e5Sespie       || (web2->type == PRECOLORED
1639*c87b03e5Sespie 	  && ! TEST_HARD_REG_BIT (web1->usable_regs, web2->regno)))
1640*c87b03e5Sespie     return;
1641*c87b03e5Sespie   /* Similar if the set of possible hardregs don't intersect.  This iteration
1642*c87b03e5Sespie      those conflicts are useless (and would make num_conflicts wrong, because
1643*c87b03e5Sespie      num_freedom is calculated from the set of possible hardregs).
1644*c87b03e5Sespie      But in presence of spilling and incremental building of the graph we
1645*c87b03e5Sespie      need to note all uses of webs conflicting with the spilled ones.
1646*c87b03e5Sespie      Because the set of possible hardregs can change in the next round for
1647*c87b03e5Sespie      spilled webs, we possibly have then conflicts with webs which would
1648*c87b03e5Sespie      be excluded now (because then hardregs intersect).  But we actually
1649*c87b03e5Sespie      need to check those uses, and to get hold of them, we need to remember
1650*c87b03e5Sespie      also webs conflicting with this one, although not conflicting in this
1651*c87b03e5Sespie      round because of non-intersecting hardregs.  */
1652*c87b03e5Sespie   if (web1->type != PRECOLORED && web2->type != PRECOLORED
1653*c87b03e5Sespie       && ! hard_regs_intersect_p (&web1->usable_regs, &web2->usable_regs))
1654*c87b03e5Sespie     {
1655*c87b03e5Sespie       struct web *p1 = find_web_for_subweb (web1);
1656*c87b03e5Sespie       struct web *p2 = find_web_for_subweb (web2);
1657*c87b03e5Sespie       /* We expect these to be rare enough to justify bitmaps.  And because
1658*c87b03e5Sespie          we have only a special use for it, we note only the superwebs.  */
1659*c87b03e5Sespie       bitmap_set_bit (p1->useless_conflicts, p2->id);
1660*c87b03e5Sespie       bitmap_set_bit (p2->useless_conflicts, p1->id);
1661*c87b03e5Sespie       return;
1662*c87b03e5Sespie     }
1663*c87b03e5Sespie   SET_BIT (igraph, index);
1664*c87b03e5Sespie   add_conflict_edge (web1, web2);
1665*c87b03e5Sespie   add_conflict_edge (web2, web1);
1666*c87b03e5Sespie }
1667*c87b03e5Sespie 
1668*c87b03e5Sespie /* For each web W this produces the missing subwebs Wx, such that it's
1669*c87b03e5Sespie    possible to exactly specify (W-Wy) for all already existing subwebs Wy.  */
1670*c87b03e5Sespie 
1671*c87b03e5Sespie static void
build_inverse_webs(web)1672*c87b03e5Sespie build_inverse_webs (web)
1673*c87b03e5Sespie      struct web *web;
1674*c87b03e5Sespie {
1675*c87b03e5Sespie   struct web *sweb = web->subreg_next;
1676*c87b03e5Sespie   unsigned HOST_WIDE_INT undef;
1677*c87b03e5Sespie 
1678*c87b03e5Sespie   undef = rtx_to_undefined (web->orig_x);
1679*c87b03e5Sespie   for (; sweb; sweb = sweb->subreg_next)
1680*c87b03e5Sespie     /* Only create inverses of non-artificial webs.  */
1681*c87b03e5Sespie     if (!sweb->artificial)
1682*c87b03e5Sespie       {
1683*c87b03e5Sespie 	unsigned HOST_WIDE_INT bits;
1684*c87b03e5Sespie 	bits = undef & ~ rtx_to_undefined (sweb->orig_x);
1685*c87b03e5Sespie 	while (bits)
1686*c87b03e5Sespie 	  {
1687*c87b03e5Sespie 	    unsigned int size_word = undef_to_size_word (web->orig_x, &bits);
1688*c87b03e5Sespie 	    if (!find_subweb_2 (web, size_word))
1689*c87b03e5Sespie 	      add_subweb_2 (web, size_word);
1690*c87b03e5Sespie 	  }
1691*c87b03e5Sespie       }
1692*c87b03e5Sespie }
1693*c87b03e5Sespie 
1694*c87b03e5Sespie /* Copies the content of WEB to a new one, and link it into WL.
1695*c87b03e5Sespie    Used for consistency checking.  */
1696*c87b03e5Sespie 
1697*c87b03e5Sespie static void
copy_web(web,wl)1698*c87b03e5Sespie copy_web (web, wl)
1699*c87b03e5Sespie      struct web *web;
1700*c87b03e5Sespie      struct web_link **wl;
1701*c87b03e5Sespie {
1702*c87b03e5Sespie   struct web *cweb = (struct web *) xmalloc (sizeof *cweb);
1703*c87b03e5Sespie   struct web_link *link = (struct web_link *) ra_alloc (sizeof *link);
1704*c87b03e5Sespie   link->next = *wl;
1705*c87b03e5Sespie   *wl = link;
1706*c87b03e5Sespie   link->web = cweb;
1707*c87b03e5Sespie   *cweb = *web;
1708*c87b03e5Sespie }
1709*c87b03e5Sespie 
1710*c87b03e5Sespie /* Given a list of webs LINK, compare the content of the webs therein
1711*c87b03e5Sespie    with the global webs of the same ID.  For consistency checking.  */
1712*c87b03e5Sespie 
1713*c87b03e5Sespie static void
compare_and_free_webs(link)1714*c87b03e5Sespie compare_and_free_webs (link)
1715*c87b03e5Sespie      struct web_link **link;
1716*c87b03e5Sespie {
1717*c87b03e5Sespie   struct web_link *wl;
1718*c87b03e5Sespie   for (wl = *link; wl; wl = wl->next)
1719*c87b03e5Sespie     {
1720*c87b03e5Sespie       struct web *web1 = wl->web;
1721*c87b03e5Sespie       struct web *web2 = ID2WEB (web1->id);
1722*c87b03e5Sespie       if (web1->regno != web2->regno
1723*c87b03e5Sespie 	  || web1->crosses_call != web2->crosses_call
1724*c87b03e5Sespie 	  || web1->live_over_abnormal != web2->live_over_abnormal
1725*c87b03e5Sespie 	  || web1->mode_changed != web2->mode_changed
1726*c87b03e5Sespie 	  || !rtx_equal_p (web1->orig_x, web2->orig_x)
1727*c87b03e5Sespie 	  || web1->type != web2->type
1728*c87b03e5Sespie 	  /* Only compare num_defs/num_uses with non-hardreg webs.
1729*c87b03e5Sespie 	     E.g. the number of uses of the framepointer changes due to
1730*c87b03e5Sespie 	     inserting spill code.  */
1731*c87b03e5Sespie 	  || (web1->type != PRECOLORED &&
1732*c87b03e5Sespie 	      (web1->num_uses != web2->num_uses
1733*c87b03e5Sespie 	       || web1->num_defs != web2->num_defs)))
1734*c87b03e5Sespie 	abort ();
1735*c87b03e5Sespie       if (web1->type != PRECOLORED)
1736*c87b03e5Sespie 	{
1737*c87b03e5Sespie 	  unsigned int i;
1738*c87b03e5Sespie 	  for (i = 0; i < web1->num_defs; i++)
1739*c87b03e5Sespie 	    if (web1->defs[i] != web2->defs[i])
1740*c87b03e5Sespie 	      abort ();
1741*c87b03e5Sespie 	  for (i = 0; i < web1->num_uses; i++)
1742*c87b03e5Sespie 	    if (web1->uses[i] != web2->uses[i])
1743*c87b03e5Sespie 	      abort ();
1744*c87b03e5Sespie 	}
1745*c87b03e5Sespie       if (web1->type == PRECOLORED)
1746*c87b03e5Sespie 	{
1747*c87b03e5Sespie 	  if (web1->defs)
1748*c87b03e5Sespie 	    free (web1->defs);
1749*c87b03e5Sespie 	  if (web1->uses)
1750*c87b03e5Sespie 	    free (web1->uses);
1751*c87b03e5Sespie 	}
1752*c87b03e5Sespie       free (web1);
1753*c87b03e5Sespie     }
1754*c87b03e5Sespie   *link = NULL;
1755*c87b03e5Sespie }
1756*c87b03e5Sespie 
1757*c87b03e5Sespie /* Setup and fill uses[] and defs[] arrays of the webs.  */
1758*c87b03e5Sespie 
1759*c87b03e5Sespie static void
init_webs_defs_uses()1760*c87b03e5Sespie init_webs_defs_uses ()
1761*c87b03e5Sespie {
1762*c87b03e5Sespie   struct dlist *d;
1763*c87b03e5Sespie   for (d = WEBS(INITIAL); d; d = d->next)
1764*c87b03e5Sespie     {
1765*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
1766*c87b03e5Sespie       unsigned int def_i, use_i;
1767*c87b03e5Sespie       struct df_link *link;
1768*c87b03e5Sespie       if (web->old_web)
1769*c87b03e5Sespie 	continue;
1770*c87b03e5Sespie       if (web->type == PRECOLORED)
1771*c87b03e5Sespie 	{
1772*c87b03e5Sespie 	  web->num_defs = web->num_uses = 0;
1773*c87b03e5Sespie 	  continue;
1774*c87b03e5Sespie 	}
1775*c87b03e5Sespie       if (web->num_defs)
1776*c87b03e5Sespie         web->defs = (struct ref **) xmalloc (web->num_defs *
1777*c87b03e5Sespie 					     sizeof (web->defs[0]));
1778*c87b03e5Sespie       if (web->num_uses)
1779*c87b03e5Sespie         web->uses = (struct ref **) xmalloc (web->num_uses *
1780*c87b03e5Sespie 					     sizeof (web->uses[0]));
1781*c87b03e5Sespie       def_i = use_i = 0;
1782*c87b03e5Sespie       for (link = web->temp_refs; link; link = link->next)
1783*c87b03e5Sespie 	{
1784*c87b03e5Sespie 	  if (DF_REF_REG_DEF_P (link->ref))
1785*c87b03e5Sespie 	    web->defs[def_i++] = link->ref;
1786*c87b03e5Sespie 	  else
1787*c87b03e5Sespie 	    web->uses[use_i++] = link->ref;
1788*c87b03e5Sespie 	}
1789*c87b03e5Sespie       web->temp_refs = NULL;
1790*c87b03e5Sespie       if (def_i != web->num_defs || use_i != web->num_uses)
1791*c87b03e5Sespie 	abort ();
1792*c87b03e5Sespie     }
1793*c87b03e5Sespie }
1794*c87b03e5Sespie 
1795*c87b03e5Sespie /* Called by parts_to_webs().  This creates (or recreates) the webs (and
1796*c87b03e5Sespie    subwebs) from web parts, gives them IDs (only to super webs), and sets
1797*c87b03e5Sespie    up use2web and def2web arrays.  */
1798*c87b03e5Sespie 
1799*c87b03e5Sespie static unsigned int
parts_to_webs_1(df,copy_webs,all_refs)1800*c87b03e5Sespie parts_to_webs_1 (df, copy_webs, all_refs)
1801*c87b03e5Sespie      struct df *df;
1802*c87b03e5Sespie      struct web_link **copy_webs;
1803*c87b03e5Sespie      struct df_link *all_refs;
1804*c87b03e5Sespie {
1805*c87b03e5Sespie   unsigned int i;
1806*c87b03e5Sespie   unsigned int webnum;
1807*c87b03e5Sespie   unsigned int def_id = df->def_id;
1808*c87b03e5Sespie   unsigned int use_id = df->use_id;
1809*c87b03e5Sespie   struct web_part *wp_first_use = &web_parts[def_id];
1810*c87b03e5Sespie 
1811*c87b03e5Sespie   /* For each root web part: create and initialize a new web,
1812*c87b03e5Sespie      setup def2web[] and use2web[] for all defs and uses, and
1813*c87b03e5Sespie      id2web for all new webs.  */
1814*c87b03e5Sespie 
1815*c87b03e5Sespie   webnum = 0;
1816*c87b03e5Sespie   for (i = 0; i < def_id + use_id; i++)
1817*c87b03e5Sespie     {
1818*c87b03e5Sespie       struct web *subweb, *web = 0; /* Initialize web to silence warnings.  */
1819*c87b03e5Sespie       struct web_part *wp = &web_parts[i];
1820*c87b03e5Sespie       struct ref *ref = wp->ref;
1821*c87b03e5Sespie       unsigned int ref_id;
1822*c87b03e5Sespie       rtx reg;
1823*c87b03e5Sespie       if (!ref)
1824*c87b03e5Sespie 	continue;
1825*c87b03e5Sespie       ref_id = i;
1826*c87b03e5Sespie       if (i >= def_id)
1827*c87b03e5Sespie 	ref_id -= def_id;
1828*c87b03e5Sespie       all_refs[i].ref = ref;
1829*c87b03e5Sespie       reg = DF_REF_REG (ref);
1830*c87b03e5Sespie       if (! wp->uplink)
1831*c87b03e5Sespie 	{
1832*c87b03e5Sespie 	  /* If we have a web part root, create a new web.  */
1833*c87b03e5Sespie 	  unsigned int newid = ~(unsigned)0;
1834*c87b03e5Sespie 	  unsigned int old_web = 0;
1835*c87b03e5Sespie 
1836*c87b03e5Sespie 	  /* In the first pass, there are no old webs, so unconditionally
1837*c87b03e5Sespie 	     allocate a new one.  */
1838*c87b03e5Sespie 	  if (ra_pass == 1)
1839*c87b03e5Sespie 	    {
1840*c87b03e5Sespie 	      web = (struct web *) xmalloc (sizeof (struct web));
1841*c87b03e5Sespie 	      newid = last_num_webs++;
1842*c87b03e5Sespie 	      init_one_web (web, GET_CODE (reg) == SUBREG
1843*c87b03e5Sespie 			         ? SUBREG_REG (reg) : reg);
1844*c87b03e5Sespie 	    }
1845*c87b03e5Sespie 	  /* Otherwise, we look for an old web.  */
1846*c87b03e5Sespie 	  else
1847*c87b03e5Sespie 	    {
1848*c87b03e5Sespie 	      /* Remember, that use2web == def2web + def_id.
1849*c87b03e5Sespie 		 Ergo is def2web[i] == use2web[i - def_id] for i >= def_id.
1850*c87b03e5Sespie 		 So we only need to look into def2web[] array.
1851*c87b03e5Sespie 		 Try to look at the web, which formerly belonged to this
1852*c87b03e5Sespie 		 def (or use).  */
1853*c87b03e5Sespie 	      web = def2web[i];
1854*c87b03e5Sespie 	      /* Or which belonged to this hardreg.  */
1855*c87b03e5Sespie 	      if (!web && DF_REF_REGNO (ref) < FIRST_PSEUDO_REGISTER)
1856*c87b03e5Sespie 		web = hardreg2web[DF_REF_REGNO (ref)];
1857*c87b03e5Sespie 	      if (web)
1858*c87b03e5Sespie 		{
1859*c87b03e5Sespie 		  /* If we found one, reuse it.  */
1860*c87b03e5Sespie 		  web = find_web_for_subweb (web);
1861*c87b03e5Sespie 		  remove_list (web->dlink, &WEBS(INITIAL));
1862*c87b03e5Sespie 		  old_web = 1;
1863*c87b03e5Sespie 		  copy_web (web, copy_webs);
1864*c87b03e5Sespie 		}
1865*c87b03e5Sespie 	      else
1866*c87b03e5Sespie 		{
1867*c87b03e5Sespie 		  /* Otherwise use a new one.  First from the free list.  */
1868*c87b03e5Sespie 		  if (WEBS(FREE))
1869*c87b03e5Sespie 		    web = DLIST_WEB (pop_list (&WEBS(FREE)));
1870*c87b03e5Sespie 		  else
1871*c87b03e5Sespie 		    {
1872*c87b03e5Sespie 		      /* Else allocate a new one.  */
1873*c87b03e5Sespie 		      web = (struct web *) xmalloc (sizeof (struct web));
1874*c87b03e5Sespie 		      newid = last_num_webs++;
1875*c87b03e5Sespie 		    }
1876*c87b03e5Sespie 		}
1877*c87b03e5Sespie 	      /* The id is zeroed in init_one_web().  */
1878*c87b03e5Sespie 	      if (newid == ~(unsigned)0)
1879*c87b03e5Sespie 		newid = web->id;
1880*c87b03e5Sespie 	      if (old_web)
1881*c87b03e5Sespie 		reinit_one_web (web, GET_CODE (reg) == SUBREG
1882*c87b03e5Sespie 				     ? SUBREG_REG (reg) : reg);
1883*c87b03e5Sespie 	      else
1884*c87b03e5Sespie 		init_one_web (web, GET_CODE (reg) == SUBREG
1885*c87b03e5Sespie 				   ? SUBREG_REG (reg) : reg);
1886*c87b03e5Sespie 	      web->old_web = (old_web && web->type != PRECOLORED) ? 1 : 0;
1887*c87b03e5Sespie 	    }
1888*c87b03e5Sespie 	  web->span_deaths = wp->spanned_deaths;
1889*c87b03e5Sespie 	  web->crosses_call = wp->crosses_call;
1890*c87b03e5Sespie 	  web->id = newid;
1891*c87b03e5Sespie 	  web->temp_refs = NULL;
1892*c87b03e5Sespie 	  webnum++;
1893*c87b03e5Sespie 	  if (web->regno < FIRST_PSEUDO_REGISTER && !hardreg2web[web->regno])
1894*c87b03e5Sespie 	    hardreg2web[web->regno] = web;
1895*c87b03e5Sespie 	  else if (web->regno < FIRST_PSEUDO_REGISTER
1896*c87b03e5Sespie 		   && hardreg2web[web->regno] != web)
1897*c87b03e5Sespie 	    abort ();
1898*c87b03e5Sespie 	}
1899*c87b03e5Sespie 
1900*c87b03e5Sespie       /* If this reference already had a web assigned, we are done.
1901*c87b03e5Sespie          This test better is equivalent to the web being an old web.
1902*c87b03e5Sespie          Otherwise something is screwed.  (This is tested)  */
1903*c87b03e5Sespie       if (def2web[i] != NULL)
1904*c87b03e5Sespie 	{
1905*c87b03e5Sespie 	  web = def2web[i];
1906*c87b03e5Sespie 	  web = find_web_for_subweb (web);
1907*c87b03e5Sespie 	  /* But if this ref includes a mode change, or was a use live
1908*c87b03e5Sespie 	     over an abnormal call, set appropriate flags in the web.  */
1909*c87b03e5Sespie 	  if ((DF_REF_FLAGS (ref) & DF_REF_MODE_CHANGE) != 0
1910*c87b03e5Sespie 	      && web->regno >= FIRST_PSEUDO_REGISTER)
1911*c87b03e5Sespie 	    web->mode_changed = 1;
1912*c87b03e5Sespie 	  if (i >= def_id
1913*c87b03e5Sespie 	      && TEST_BIT (live_over_abnormal, ref_id))
1914*c87b03e5Sespie 	    web->live_over_abnormal = 1;
1915*c87b03e5Sespie 	  /* And check, that it's not a newly allocated web.  This would be
1916*c87b03e5Sespie 	     an inconsistency.  */
1917*c87b03e5Sespie 	  if (!web->old_web || web->type == PRECOLORED)
1918*c87b03e5Sespie 	    abort ();
1919*c87b03e5Sespie 	  continue;
1920*c87b03e5Sespie 	}
1921*c87b03e5Sespie       /* In case this was no web part root, we need to initialize WEB
1922*c87b03e5Sespie 	 from the ref2web array belonging to the root.  */
1923*c87b03e5Sespie       if (wp->uplink)
1924*c87b03e5Sespie 	{
1925*c87b03e5Sespie 	  struct web_part *rwp = find_web_part (wp);
1926*c87b03e5Sespie 	  unsigned int j = DF_REF_ID (rwp->ref);
1927*c87b03e5Sespie 	  if (rwp < wp_first_use)
1928*c87b03e5Sespie 	    web = def2web[j];
1929*c87b03e5Sespie 	  else
1930*c87b03e5Sespie 	    web = use2web[j];
1931*c87b03e5Sespie 	  web = find_web_for_subweb (web);
1932*c87b03e5Sespie 	}
1933*c87b03e5Sespie 
1934*c87b03e5Sespie       /* Remember all references for a web in a single linked list.  */
1935*c87b03e5Sespie       all_refs[i].next = web->temp_refs;
1936*c87b03e5Sespie       web->temp_refs = &all_refs[i];
1937*c87b03e5Sespie 
1938*c87b03e5Sespie       /* And the test, that if def2web[i] was NULL above, that we are _not_
1939*c87b03e5Sespie 	 an old web.  */
1940*c87b03e5Sespie       if (web->old_web && web->type != PRECOLORED)
1941*c87b03e5Sespie 	abort ();
1942*c87b03e5Sespie 
1943*c87b03e5Sespie       /* Possible create a subweb, if this ref was a subreg.  */
1944*c87b03e5Sespie       if (GET_CODE (reg) == SUBREG)
1945*c87b03e5Sespie 	{
1946*c87b03e5Sespie 	  subweb = find_subweb (web, reg);
1947*c87b03e5Sespie 	  if (!subweb)
1948*c87b03e5Sespie 	    {
1949*c87b03e5Sespie 	      subweb = add_subweb (web, reg);
1950*c87b03e5Sespie 	      if (web->old_web)
1951*c87b03e5Sespie 		abort ();
1952*c87b03e5Sespie 	    }
1953*c87b03e5Sespie 	}
1954*c87b03e5Sespie       else
1955*c87b03e5Sespie 	subweb = web;
1956*c87b03e5Sespie 
1957*c87b03e5Sespie       /* And look, if the ref involves an invalid mode change.  */
1958*c87b03e5Sespie       if ((DF_REF_FLAGS (ref) & DF_REF_MODE_CHANGE) != 0
1959*c87b03e5Sespie 	  && web->regno >= FIRST_PSEUDO_REGISTER)
1960*c87b03e5Sespie 	web->mode_changed = 1;
1961*c87b03e5Sespie 
1962*c87b03e5Sespie       /* Setup def2web, or use2web, and increment num_defs or num_uses.  */
1963*c87b03e5Sespie       if (i < def_id)
1964*c87b03e5Sespie 	{
1965*c87b03e5Sespie 	  /* Some sanity checks.  */
1966*c87b03e5Sespie 	  if (ra_pass > 1)
1967*c87b03e5Sespie 	    {
1968*c87b03e5Sespie 	      struct web *compare = def2web[i];
1969*c87b03e5Sespie 	      if (i < last_def_id)
1970*c87b03e5Sespie 		{
1971*c87b03e5Sespie 		  if (web->old_web && compare != subweb)
1972*c87b03e5Sespie 		    abort ();
1973*c87b03e5Sespie 		}
1974*c87b03e5Sespie 	      if (!web->old_web && compare)
1975*c87b03e5Sespie 		abort ();
1976*c87b03e5Sespie 	      if (compare && compare != subweb)
1977*c87b03e5Sespie 		abort ();
1978*c87b03e5Sespie 	    }
1979*c87b03e5Sespie 	  def2web[i] = subweb;
1980*c87b03e5Sespie 	  web->num_defs++;
1981*c87b03e5Sespie 	}
1982*c87b03e5Sespie       else
1983*c87b03e5Sespie 	{
1984*c87b03e5Sespie 	  if (ra_pass > 1)
1985*c87b03e5Sespie 	    {
1986*c87b03e5Sespie 	      struct web *compare = use2web[ref_id];
1987*c87b03e5Sespie 	      if (ref_id < last_use_id)
1988*c87b03e5Sespie 		{
1989*c87b03e5Sespie 		  if (web->old_web && compare != subweb)
1990*c87b03e5Sespie 		    abort ();
1991*c87b03e5Sespie 		}
1992*c87b03e5Sespie 	      if (!web->old_web && compare)
1993*c87b03e5Sespie 		abort ();
1994*c87b03e5Sespie 	      if (compare && compare != subweb)
1995*c87b03e5Sespie 		abort ();
1996*c87b03e5Sespie 	    }
1997*c87b03e5Sespie 	  use2web[ref_id] = subweb;
1998*c87b03e5Sespie 	  web->num_uses++;
1999*c87b03e5Sespie 	  if (TEST_BIT (live_over_abnormal, ref_id))
2000*c87b03e5Sespie 	    web->live_over_abnormal = 1;
2001*c87b03e5Sespie 	}
2002*c87b03e5Sespie     }
2003*c87b03e5Sespie 
2004*c87b03e5Sespie   /* We better now have exactly as many webs as we had web part roots.  */
2005*c87b03e5Sespie   if (webnum != num_webs)
2006*c87b03e5Sespie     abort ();
2007*c87b03e5Sespie 
2008*c87b03e5Sespie   return webnum;
2009*c87b03e5Sespie }
2010*c87b03e5Sespie 
2011*c87b03e5Sespie /* This builds full webs out of web parts, without relating them to each
2012*c87b03e5Sespie    other (i.e. without creating the conflict edges).  */
2013*c87b03e5Sespie 
2014*c87b03e5Sespie static void
parts_to_webs(df)2015*c87b03e5Sespie parts_to_webs (df)
2016*c87b03e5Sespie      struct df *df;
2017*c87b03e5Sespie {
2018*c87b03e5Sespie   unsigned int i;
2019*c87b03e5Sespie   unsigned int webnum;
2020*c87b03e5Sespie   struct web_link *copy_webs = NULL;
2021*c87b03e5Sespie   struct dlist *d;
2022*c87b03e5Sespie   struct df_link *all_refs;
2023*c87b03e5Sespie   num_subwebs = 0;
2024*c87b03e5Sespie 
2025*c87b03e5Sespie   /* First build webs and ordinary subwebs.  */
2026*c87b03e5Sespie   all_refs = (struct df_link *) xcalloc (df->def_id + df->use_id,
2027*c87b03e5Sespie 					 sizeof (all_refs[0]));
2028*c87b03e5Sespie   webnum = parts_to_webs_1 (df, &copy_webs, all_refs);
2029*c87b03e5Sespie 
2030*c87b03e5Sespie   /* Setup the webs for hardregs which are still missing (weren't
2031*c87b03e5Sespie      mentioned in the code).  */
2032*c87b03e5Sespie   for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
2033*c87b03e5Sespie     if (!hardreg2web[i])
2034*c87b03e5Sespie       {
2035*c87b03e5Sespie 	struct web *web = (struct web *) xmalloc (sizeof (struct web));
2036*c87b03e5Sespie 	init_one_web (web, gen_rtx_REG (reg_raw_mode[i], i));
2037*c87b03e5Sespie 	web->id = last_num_webs++;
2038*c87b03e5Sespie 	hardreg2web[web->regno] = web;
2039*c87b03e5Sespie       }
2040*c87b03e5Sespie   num_webs = last_num_webs;
2041*c87b03e5Sespie 
2042*c87b03e5Sespie   /* Now create all artificial subwebs, i.e. those, which do
2043*c87b03e5Sespie      not correspond to a real subreg in the current function's RTL, but
2044*c87b03e5Sespie      which nevertheless is a target of a conflict.
2045*c87b03e5Sespie      XXX we need to merge this loop with the one above, which means, we need
2046*c87b03e5Sespie      a way to later override the artificiality.  Beware: currently
2047*c87b03e5Sespie      add_subweb_2() relies on the existence of normal subwebs for deducing
2048*c87b03e5Sespie      a sane mode to use for the artificial subwebs.  */
2049*c87b03e5Sespie   for (i = 0; i < df->def_id + df->use_id; i++)
2050*c87b03e5Sespie     {
2051*c87b03e5Sespie       struct web_part *wp = &web_parts[i];
2052*c87b03e5Sespie       struct tagged_conflict *cl;
2053*c87b03e5Sespie       struct web *web;
2054*c87b03e5Sespie       if (wp->uplink || !wp->ref)
2055*c87b03e5Sespie 	{
2056*c87b03e5Sespie 	  if (wp->sub_conflicts)
2057*c87b03e5Sespie 	    abort ();
2058*c87b03e5Sespie 	  continue;
2059*c87b03e5Sespie 	}
2060*c87b03e5Sespie       web = def2web[i];
2061*c87b03e5Sespie       web = find_web_for_subweb (web);
2062*c87b03e5Sespie       for (cl = wp->sub_conflicts; cl; cl = cl->next)
2063*c87b03e5Sespie         if (!find_subweb_2 (web, cl->size_word))
2064*c87b03e5Sespie 	  add_subweb_2 (web, cl->size_word);
2065*c87b03e5Sespie     }
2066*c87b03e5Sespie 
2067*c87b03e5Sespie   /* And now create artificial subwebs needed for representing the inverse
2068*c87b03e5Sespie      of some subwebs.  This also gives IDs to all subwebs.  */
2069*c87b03e5Sespie   webnum = last_num_webs;
2070*c87b03e5Sespie   for (d = WEBS(INITIAL); d; d = d->next)
2071*c87b03e5Sespie     {
2072*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
2073*c87b03e5Sespie       if (web->subreg_next)
2074*c87b03e5Sespie 	{
2075*c87b03e5Sespie 	  struct web *sweb;
2076*c87b03e5Sespie           build_inverse_webs (web);
2077*c87b03e5Sespie 	  for (sweb = web->subreg_next; sweb; sweb = sweb->subreg_next)
2078*c87b03e5Sespie 	    sweb->id = webnum++;
2079*c87b03e5Sespie 	}
2080*c87b03e5Sespie     }
2081*c87b03e5Sespie 
2082*c87b03e5Sespie   /* Now that everyone has an ID, we can setup the id2web array.  */
2083*c87b03e5Sespie   id2web = (struct web **) xcalloc (webnum, sizeof (id2web[0]));
2084*c87b03e5Sespie   for (d = WEBS(INITIAL); d; d = d->next)
2085*c87b03e5Sespie     {
2086*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
2087*c87b03e5Sespie       ID2WEB (web->id) = web;
2088*c87b03e5Sespie       for (web = web->subreg_next; web; web = web->subreg_next)
2089*c87b03e5Sespie         ID2WEB (web->id) = web;
2090*c87b03e5Sespie     }
2091*c87b03e5Sespie   num_subwebs = webnum - last_num_webs;
2092*c87b03e5Sespie   num_allwebs = num_webs + num_subwebs;
2093*c87b03e5Sespie   num_webs += num_subwebs;
2094*c87b03e5Sespie 
2095*c87b03e5Sespie   /* Allocate and clear the conflict graph bitmaps.  */
2096*c87b03e5Sespie   igraph = sbitmap_alloc (num_webs * num_webs / 2);
2097*c87b03e5Sespie   sup_igraph = sbitmap_alloc (num_webs * num_webs);
2098*c87b03e5Sespie   sbitmap_zero (igraph);
2099*c87b03e5Sespie   sbitmap_zero (sup_igraph);
2100*c87b03e5Sespie 
2101*c87b03e5Sespie   /* Distibute the references to their webs.  */
2102*c87b03e5Sespie   init_webs_defs_uses ();
2103*c87b03e5Sespie   /* And do some sanity checks if old webs, and those recreated from the
2104*c87b03e5Sespie      really are the same.  */
2105*c87b03e5Sespie   compare_and_free_webs (&copy_webs);
2106*c87b03e5Sespie   free (all_refs);
2107*c87b03e5Sespie }
2108*c87b03e5Sespie 
2109*c87b03e5Sespie /* This deletes all conflicts to and from webs which need to be renewed
2110*c87b03e5Sespie    in this pass of the allocator, i.e. those which were spilled in the
2111*c87b03e5Sespie    last pass.  Furthermore it also rebuilds the bitmaps for the remaining
2112*c87b03e5Sespie    conflicts.  */
2113*c87b03e5Sespie 
2114*c87b03e5Sespie static void
reset_conflicts()2115*c87b03e5Sespie reset_conflicts ()
2116*c87b03e5Sespie {
2117*c87b03e5Sespie   unsigned int i;
2118*c87b03e5Sespie   bitmap newwebs = BITMAP_XMALLOC ();
2119*c87b03e5Sespie   for (i = 0; i < num_webs - num_subwebs; i++)
2120*c87b03e5Sespie     {
2121*c87b03e5Sespie       struct web *web = ID2WEB (i);
2122*c87b03e5Sespie       /* Hardreg webs and non-old webs are new webs (which
2123*c87b03e5Sespie 	 need rebuilding).  */
2124*c87b03e5Sespie       if (web->type == PRECOLORED || !web->old_web)
2125*c87b03e5Sespie 	bitmap_set_bit (newwebs, web->id);
2126*c87b03e5Sespie     }
2127*c87b03e5Sespie 
2128*c87b03e5Sespie   for (i = 0; i < num_webs - num_subwebs; i++)
2129*c87b03e5Sespie     {
2130*c87b03e5Sespie       struct web *web = ID2WEB (i);
2131*c87b03e5Sespie       struct conflict_link *cl;
2132*c87b03e5Sespie       struct conflict_link **pcl;
2133*c87b03e5Sespie       pcl = &(web->conflict_list);
2134*c87b03e5Sespie 
2135*c87b03e5Sespie       /* First restore the conflict list to be like it was before
2136*c87b03e5Sespie 	 coalescing.  */
2137*c87b03e5Sespie       if (web->have_orig_conflicts)
2138*c87b03e5Sespie 	{
2139*c87b03e5Sespie 	  web->conflict_list = web->orig_conflict_list;
2140*c87b03e5Sespie 	  web->orig_conflict_list = NULL;
2141*c87b03e5Sespie 	}
2142*c87b03e5Sespie       if (web->orig_conflict_list)
2143*c87b03e5Sespie 	abort ();
2144*c87b03e5Sespie 
2145*c87b03e5Sespie       /* New non-precolored webs, have no conflict list.  */
2146*c87b03e5Sespie       if (web->type != PRECOLORED && !web->old_web)
2147*c87b03e5Sespie 	{
2148*c87b03e5Sespie 	  *pcl = NULL;
2149*c87b03e5Sespie 	  /* Useless conflicts will be rebuilt completely.  But check
2150*c87b03e5Sespie 	     for cleanlyness, as the web might have come from the
2151*c87b03e5Sespie 	     free list.  */
2152*c87b03e5Sespie 	  if (bitmap_first_set_bit (web->useless_conflicts) >= 0)
2153*c87b03e5Sespie 	    abort ();
2154*c87b03e5Sespie 	}
2155*c87b03e5Sespie       else
2156*c87b03e5Sespie 	{
2157*c87b03e5Sespie 	  /* Useless conflicts with new webs will be rebuilt if they
2158*c87b03e5Sespie 	     are still there.  */
2159*c87b03e5Sespie 	  bitmap_operation (web->useless_conflicts, web->useless_conflicts,
2160*c87b03e5Sespie 			    newwebs, BITMAP_AND_COMPL);
2161*c87b03e5Sespie 	  /* Go through all conflicts, and retain those to old webs.  */
2162*c87b03e5Sespie 	  for (cl = web->conflict_list; cl; cl = cl->next)
2163*c87b03e5Sespie 	    {
2164*c87b03e5Sespie 	      if (cl->t->old_web || cl->t->type == PRECOLORED)
2165*c87b03e5Sespie 		{
2166*c87b03e5Sespie 		  *pcl = cl;
2167*c87b03e5Sespie 		  pcl = &(cl->next);
2168*c87b03e5Sespie 
2169*c87b03e5Sespie 		  /* Also restore the entries in the igraph bitmaps.  */
2170*c87b03e5Sespie 		  web->num_conflicts += 1 + cl->t->add_hardregs;
2171*c87b03e5Sespie 		  SET_BIT (sup_igraph, (web->id * num_webs + cl->t->id));
2172*c87b03e5Sespie 		  /* No subconflicts mean full webs conflict.  */
2173*c87b03e5Sespie 		  if (!cl->sub)
2174*c87b03e5Sespie 		    SET_BIT (igraph, igraph_index (web->id, cl->t->id));
2175*c87b03e5Sespie 		  else
2176*c87b03e5Sespie 		    /* Else only the parts in cl->sub must be in the
2177*c87b03e5Sespie 		       bitmap.  */
2178*c87b03e5Sespie 		    {
2179*c87b03e5Sespie 		      struct sub_conflict *sl;
2180*c87b03e5Sespie 		      for (sl = cl->sub; sl; sl = sl->next)
2181*c87b03e5Sespie 			SET_BIT (igraph, igraph_index (sl->s->id, sl->t->id));
2182*c87b03e5Sespie 		    }
2183*c87b03e5Sespie 		}
2184*c87b03e5Sespie 	    }
2185*c87b03e5Sespie 	  *pcl = NULL;
2186*c87b03e5Sespie 	}
2187*c87b03e5Sespie       web->have_orig_conflicts = 0;
2188*c87b03e5Sespie     }
2189*c87b03e5Sespie   BITMAP_XFREE (newwebs);
2190*c87b03e5Sespie }
2191*c87b03e5Sespie 
2192*c87b03e5Sespie /* For each web check it's num_conflicts member against that
2193*c87b03e5Sespie    number, as calculated from scratch from all neighbors.  */
2194*c87b03e5Sespie 
2195*c87b03e5Sespie #if 0
2196*c87b03e5Sespie static void
2197*c87b03e5Sespie check_conflict_numbers ()
2198*c87b03e5Sespie {
2199*c87b03e5Sespie   unsigned int i;
2200*c87b03e5Sespie   for (i = 0; i < num_webs; i++)
2201*c87b03e5Sespie     {
2202*c87b03e5Sespie       struct web *web = ID2WEB (i);
2203*c87b03e5Sespie       int new_conf = 0 * web->add_hardregs;
2204*c87b03e5Sespie       struct conflict_link *cl;
2205*c87b03e5Sespie       for (cl = web->conflict_list; cl; cl = cl->next)
2206*c87b03e5Sespie 	if (cl->t->type != SELECT && cl->t->type != COALESCED)
2207*c87b03e5Sespie 	  new_conf += 1 + cl->t->add_hardregs;
2208*c87b03e5Sespie       if (web->type != PRECOLORED && new_conf != web->num_conflicts)
2209*c87b03e5Sespie 	abort ();
2210*c87b03e5Sespie     }
2211*c87b03e5Sespie }
2212*c87b03e5Sespie #endif
2213*c87b03e5Sespie 
2214*c87b03e5Sespie /* Convert the conflicts between web parts to conflicts between full webs.
2215*c87b03e5Sespie 
2216*c87b03e5Sespie    This can't be done in parts_to_webs(), because for recording conflicts
2217*c87b03e5Sespie    between webs we need to know their final usable_regs set, which is used
2218*c87b03e5Sespie    to discard non-conflicts (between webs having no hard reg in common).
2219*c87b03e5Sespie    But this is set for spill temporaries only after the webs itself are
2220*c87b03e5Sespie    built.  Until then the usable_regs set is based on the pseudo regno used
2221*c87b03e5Sespie    in this web, which may contain far less registers than later determined.
2222*c87b03e5Sespie    This would result in us loosing conflicts (due to record_conflict()
2223*c87b03e5Sespie    thinking that a web can only be allocated to the current usable_regs,
2224*c87b03e5Sespie    whereas later this is extended) leading to colorings, where some regs which
2225*c87b03e5Sespie    in reality conflict get the same color.  */
2226*c87b03e5Sespie 
2227*c87b03e5Sespie static void
conflicts_between_webs(df)2228*c87b03e5Sespie conflicts_between_webs (df)
2229*c87b03e5Sespie      struct df *df;
2230*c87b03e5Sespie {
2231*c87b03e5Sespie   unsigned int i;
2232*c87b03e5Sespie #ifdef STACK_REGS
2233*c87b03e5Sespie   struct dlist *d;
2234*c87b03e5Sespie #endif
2235*c87b03e5Sespie   bitmap ignore_defs = BITMAP_XMALLOC ();
2236*c87b03e5Sespie   unsigned int have_ignored;
2237*c87b03e5Sespie   unsigned int *pass_cache = (unsigned int *) xcalloc (num_webs, sizeof (int));
2238*c87b03e5Sespie   unsigned int pass = 0;
2239*c87b03e5Sespie 
2240*c87b03e5Sespie   if (ra_pass > 1)
2241*c87b03e5Sespie     reset_conflicts ();
2242*c87b03e5Sespie 
2243*c87b03e5Sespie   /* It is possible, that in the conflict bitmaps still some defs I are noted,
2244*c87b03e5Sespie      which have web_parts[I].ref being NULL.  This can happen, when from the
2245*c87b03e5Sespie      last iteration the conflict bitmap for this part wasn't deleted, but a
2246*c87b03e5Sespie      conflicting move insn was removed.  It's DEF is still in the conflict
2247*c87b03e5Sespie      bitmap, but it doesn't exist anymore in df->defs.  To not have to check
2248*c87b03e5Sespie      it in the tight loop below, we instead remember the ID's of them in a
2249*c87b03e5Sespie      bitmap, and loop only over IDs which are not in it.  */
2250*c87b03e5Sespie   for (i = 0; i < df->def_id; i++)
2251*c87b03e5Sespie     if (web_parts[i].ref == NULL)
2252*c87b03e5Sespie       bitmap_set_bit (ignore_defs, i);
2253*c87b03e5Sespie   have_ignored = (bitmap_first_set_bit (ignore_defs) >= 0);
2254*c87b03e5Sespie 
2255*c87b03e5Sespie   /* Now record all conflicts between webs.  Note that we only check
2256*c87b03e5Sespie      the conflict bitmaps of all defs.  Conflict bitmaps are only in
2257*c87b03e5Sespie      webpart roots.  If they are in uses, those uses are roots, which
2258*c87b03e5Sespie      means, that this is an uninitialized web, whose conflicts
2259*c87b03e5Sespie      don't matter.  Nevertheless for hardregs we also need to check uses.
2260*c87b03e5Sespie      E.g. hardregs used for argument passing have no DEF in the RTL,
2261*c87b03e5Sespie      but if they have uses, they indeed conflict with all DEFs they
2262*c87b03e5Sespie      overlap.  */
2263*c87b03e5Sespie   for (i = 0; i < df->def_id + df->use_id; i++)
2264*c87b03e5Sespie     {
2265*c87b03e5Sespie       struct tagged_conflict *cl = web_parts[i].sub_conflicts;
2266*c87b03e5Sespie       struct web *supweb1;
2267*c87b03e5Sespie       if (!cl
2268*c87b03e5Sespie 	  || (i >= df->def_id
2269*c87b03e5Sespie 	      && DF_REF_REGNO (web_parts[i].ref) >= FIRST_PSEUDO_REGISTER))
2270*c87b03e5Sespie 	continue;
2271*c87b03e5Sespie       supweb1 = def2web[i];
2272*c87b03e5Sespie       supweb1 = find_web_for_subweb (supweb1);
2273*c87b03e5Sespie       for (; cl; cl = cl->next)
2274*c87b03e5Sespie         if (cl->conflicts)
2275*c87b03e5Sespie 	  {
2276*c87b03e5Sespie 	    int j;
2277*c87b03e5Sespie 	    struct web *web1 = find_subweb_2 (supweb1, cl->size_word);
2278*c87b03e5Sespie 	    if (have_ignored)
2279*c87b03e5Sespie 	      bitmap_operation (cl->conflicts, cl->conflicts, ignore_defs,
2280*c87b03e5Sespie 			        BITMAP_AND_COMPL);
2281*c87b03e5Sespie 	    /* We reduce the number of calls to record_conflict() with this
2282*c87b03e5Sespie 	       pass thing.  record_conflict() itself also has some early-out
2283*c87b03e5Sespie 	       optimizations, but here we can use the special properties of
2284*c87b03e5Sespie 	       the loop (constant web1) to reduce that even more.
2285*c87b03e5Sespie 	       We once used an sbitmap of already handled web indices,
2286*c87b03e5Sespie 	       but sbitmaps are slow to clear and bitmaps are slow to
2287*c87b03e5Sespie 	       set/test.  The current approach needs more memory, but
2288*c87b03e5Sespie 	       locality is large.  */
2289*c87b03e5Sespie 	    pass++;
2290*c87b03e5Sespie 
2291*c87b03e5Sespie 	    /* Note, that there are only defs in the conflicts bitset.  */
2292*c87b03e5Sespie 	    EXECUTE_IF_SET_IN_BITMAP (
2293*c87b03e5Sespie 	      cl->conflicts, 0, j,
2294*c87b03e5Sespie 	      {
2295*c87b03e5Sespie 		struct web *web2 = def2web[j];
2296*c87b03e5Sespie 		unsigned int id2 = web2->id;
2297*c87b03e5Sespie 		if (pass_cache[id2] != pass)
2298*c87b03e5Sespie 		  {
2299*c87b03e5Sespie 		    pass_cache[id2] = pass;
2300*c87b03e5Sespie 		    record_conflict (web1, web2);
2301*c87b03e5Sespie 		  }
2302*c87b03e5Sespie 	      });
2303*c87b03e5Sespie 	  }
2304*c87b03e5Sespie     }
2305*c87b03e5Sespie 
2306*c87b03e5Sespie   free (pass_cache);
2307*c87b03e5Sespie   BITMAP_XFREE (ignore_defs);
2308*c87b03e5Sespie 
2309*c87b03e5Sespie #ifdef STACK_REGS
2310*c87b03e5Sespie   /* Pseudos can't go in stack regs if they are live at the beginning of
2311*c87b03e5Sespie      a block that is reached by an abnormal edge.  */
2312*c87b03e5Sespie   for (d = WEBS(INITIAL); d; d = d->next)
2313*c87b03e5Sespie     {
2314*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
2315*c87b03e5Sespie       int j;
2316*c87b03e5Sespie       if (web->live_over_abnormal)
2317*c87b03e5Sespie 	for (j = FIRST_STACK_REG; j <= LAST_STACK_REG; j++)
2318*c87b03e5Sespie 	  record_conflict (web, hardreg2web[j]);
2319*c87b03e5Sespie     }
2320*c87b03e5Sespie #endif
2321*c87b03e5Sespie }
2322*c87b03e5Sespie 
2323*c87b03e5Sespie /* Remember that a web was spilled, and change some characteristics
2324*c87b03e5Sespie    accordingly.  */
2325*c87b03e5Sespie 
2326*c87b03e5Sespie static void
remember_web_was_spilled(web)2327*c87b03e5Sespie remember_web_was_spilled (web)
2328*c87b03e5Sespie      struct web *web;
2329*c87b03e5Sespie {
2330*c87b03e5Sespie   int i;
2331*c87b03e5Sespie   unsigned int found_size = 0;
2332*c87b03e5Sespie   int adjust;
2333*c87b03e5Sespie   web->spill_temp = 1;
2334*c87b03e5Sespie 
2335*c87b03e5Sespie   /* From now on don't use reg_pref/alt_class (regno) anymore for
2336*c87b03e5Sespie      this web, but instead  usable_regs.  We can't use spill_temp for
2337*c87b03e5Sespie      this, as it might get reset later, when we are coalesced to a
2338*c87b03e5Sespie      non-spill-temp.  In that case we still want to use usable_regs.  */
2339*c87b03e5Sespie   web->use_my_regs = 1;
2340*c87b03e5Sespie 
2341*c87b03e5Sespie   /* We don't constrain spill temporaries in any way for now.
2342*c87b03e5Sespie      It's wrong sometimes to have the same constraints or
2343*c87b03e5Sespie      preferences as the original pseudo, esp. if they were very narrow.
2344*c87b03e5Sespie      (E.g. there once was a reg wanting class AREG (only one register)
2345*c87b03e5Sespie      without alternative class.  As long, as also the spill-temps for
2346*c87b03e5Sespie      this pseudo had the same constraints it was spilled over and over.
2347*c87b03e5Sespie      Ideally we want some constraints also on spill-temps: Because they are
2348*c87b03e5Sespie      not only loaded/stored, but also worked with, any constraints from insn
2349*c87b03e5Sespie      alternatives needs applying.  Currently this is dealt with by reload, as
2350*c87b03e5Sespie      many other things, but at some time we want to integrate that
2351*c87b03e5Sespie      functionality into the allocator.  */
2352*c87b03e5Sespie   if (web->regno >= max_normal_pseudo)
2353*c87b03e5Sespie     {
2354*c87b03e5Sespie       COPY_HARD_REG_SET (web->usable_regs,
2355*c87b03e5Sespie 			reg_class_contents[reg_preferred_class (web->regno)]);
2356*c87b03e5Sespie       IOR_HARD_REG_SET (web->usable_regs,
2357*c87b03e5Sespie 			reg_class_contents[reg_alternate_class (web->regno)]);
2358*c87b03e5Sespie     }
2359*c87b03e5Sespie   else
2360*c87b03e5Sespie     COPY_HARD_REG_SET (web->usable_regs,
2361*c87b03e5Sespie 		       reg_class_contents[(int) GENERAL_REGS]);
2362*c87b03e5Sespie   AND_COMPL_HARD_REG_SET (web->usable_regs, never_use_colors);
2363*c87b03e5Sespie   prune_hardregs_for_mode (&web->usable_regs, PSEUDO_REGNO_MODE (web->regno));
2364*c87b03e5Sespie #ifdef CLASS_CANNOT_CHANGE_MODE
2365*c87b03e5Sespie   if (web->mode_changed)
2366*c87b03e5Sespie     AND_COMPL_HARD_REG_SET (web->usable_regs, reg_class_contents[
2367*c87b03e5Sespie 			      (int) CLASS_CANNOT_CHANGE_MODE]);
2368*c87b03e5Sespie #endif
2369*c87b03e5Sespie   web->num_freedom = hard_regs_count (web->usable_regs);
2370*c87b03e5Sespie   if (!web->num_freedom)
2371*c87b03e5Sespie     abort();
2372*c87b03e5Sespie   COPY_HARD_REG_SET (web->orig_usable_regs, web->usable_regs);
2373*c87b03e5Sespie   /* Now look for a class, which is subset of our constraints, to
2374*c87b03e5Sespie      setup add_hardregs, and regclass for debug output.  */
2375*c87b03e5Sespie   web->regclass = NO_REGS;
2376*c87b03e5Sespie   for (i = (int) ALL_REGS - 1; i > 0; i--)
2377*c87b03e5Sespie     {
2378*c87b03e5Sespie       unsigned int size;
2379*c87b03e5Sespie       HARD_REG_SET test;
2380*c87b03e5Sespie       COPY_HARD_REG_SET (test, reg_class_contents[i]);
2381*c87b03e5Sespie       AND_COMPL_HARD_REG_SET (test, never_use_colors);
2382*c87b03e5Sespie       GO_IF_HARD_REG_SUBSET (test, web->usable_regs, found);
2383*c87b03e5Sespie       continue;
2384*c87b03e5Sespie     found:
2385*c87b03e5Sespie       /* Measure the actual number of bits which really are overlapping
2386*c87b03e5Sespie 	 the target regset, not just the reg_class_size.  */
2387*c87b03e5Sespie       size = hard_regs_count (test);
2388*c87b03e5Sespie       if (found_size < size)
2389*c87b03e5Sespie 	{
2390*c87b03e5Sespie           web->regclass = (enum reg_class) i;
2391*c87b03e5Sespie 	  found_size = size;
2392*c87b03e5Sespie 	}
2393*c87b03e5Sespie     }
2394*c87b03e5Sespie 
2395*c87b03e5Sespie   adjust = 0 * web->add_hardregs;
2396*c87b03e5Sespie   web->add_hardregs =
2397*c87b03e5Sespie     CLASS_MAX_NREGS (web->regclass, PSEUDO_REGNO_MODE (web->regno)) - 1;
2398*c87b03e5Sespie   web->num_freedom -= web->add_hardregs;
2399*c87b03e5Sespie   if (!web->num_freedom)
2400*c87b03e5Sespie     abort();
2401*c87b03e5Sespie   adjust -= 0 * web->add_hardregs;
2402*c87b03e5Sespie   web->num_conflicts -= adjust;
2403*c87b03e5Sespie }
2404*c87b03e5Sespie 
2405*c87b03e5Sespie /* Look at each web, if it is used as spill web.  Or better said,
2406*c87b03e5Sespie    if it will be spillable in this pass.  */
2407*c87b03e5Sespie 
2408*c87b03e5Sespie static void
detect_spill_temps()2409*c87b03e5Sespie detect_spill_temps ()
2410*c87b03e5Sespie {
2411*c87b03e5Sespie   struct dlist *d;
2412*c87b03e5Sespie   bitmap already = BITMAP_XMALLOC ();
2413*c87b03e5Sespie 
2414*c87b03e5Sespie   /* Detect webs used for spill temporaries.  */
2415*c87b03e5Sespie   for (d = WEBS(INITIAL); d; d = d->next)
2416*c87b03e5Sespie     {
2417*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
2418*c87b03e5Sespie 
2419*c87b03e5Sespie       /* Below only the detection of spill temporaries.  We never spill
2420*c87b03e5Sespie          precolored webs, so those can't be spill temporaries.  The code above
2421*c87b03e5Sespie          (remember_web_was_spilled) can't currently cope with hardregs
2422*c87b03e5Sespie          anyway.  */
2423*c87b03e5Sespie       if (web->regno < FIRST_PSEUDO_REGISTER)
2424*c87b03e5Sespie 	continue;
2425*c87b03e5Sespie       /* Uninitialized webs can't be spill-temporaries.  */
2426*c87b03e5Sespie       if (web->num_defs == 0)
2427*c87b03e5Sespie 	continue;
2428*c87b03e5Sespie 
2429*c87b03e5Sespie       /* A web with only defs and no uses can't be spilled.  Nevertheless
2430*c87b03e5Sespie 	 it must get a color, as it takes away an register from all webs
2431*c87b03e5Sespie 	 live at these defs.  So we make it a short web.  */
2432*c87b03e5Sespie       if (web->num_uses == 0)
2433*c87b03e5Sespie 	web->spill_temp = 3;
2434*c87b03e5Sespie       /* A web which was spilled last time, but for which no insns were
2435*c87b03e5Sespie          emitted (can happen with IR spilling ignoring sometimes
2436*c87b03e5Sespie 	 all deaths).  */
2437*c87b03e5Sespie       else if (web->changed)
2438*c87b03e5Sespie 	web->spill_temp = 1;
2439*c87b03e5Sespie       /* A spill temporary has one def, one or more uses, all uses
2440*c87b03e5Sespie 	 are in one insn, and either the def or use insn was inserted
2441*c87b03e5Sespie 	 by the allocator.  */
2442*c87b03e5Sespie       /* XXX not correct currently.  There might also be spill temps
2443*c87b03e5Sespie 	 involving more than one def.  Usually that's an additional
2444*c87b03e5Sespie 	 clobber in the using instruction.  We might also constrain
2445*c87b03e5Sespie 	 ourself to that, instead of like currently marking all
2446*c87b03e5Sespie 	 webs involving any spill insns at all.  */
2447*c87b03e5Sespie       else
2448*c87b03e5Sespie 	{
2449*c87b03e5Sespie 	  unsigned int i;
2450*c87b03e5Sespie 	  int spill_involved = 0;
2451*c87b03e5Sespie 	  for (i = 0; i < web->num_uses && !spill_involved; i++)
2452*c87b03e5Sespie 	    if (DF_REF_INSN_UID (web->uses[i]) >= orig_max_uid)
2453*c87b03e5Sespie 	      spill_involved = 1;
2454*c87b03e5Sespie 	  for (i = 0; i < web->num_defs && !spill_involved; i++)
2455*c87b03e5Sespie 	    if (DF_REF_INSN_UID (web->defs[i]) >= orig_max_uid)
2456*c87b03e5Sespie 	      spill_involved = 1;
2457*c87b03e5Sespie 
2458*c87b03e5Sespie 	  if (spill_involved/* && ra_pass > 2*/)
2459*c87b03e5Sespie 	    {
2460*c87b03e5Sespie 	      int num_deaths = web->span_deaths;
2461*c87b03e5Sespie 	      /* Mark webs involving at least one spill insn as
2462*c87b03e5Sespie 		 spill temps.  */
2463*c87b03e5Sespie 	      remember_web_was_spilled (web);
2464*c87b03e5Sespie 	      /* Search for insns which define and use the web in question
2465*c87b03e5Sespie 		 at the same time, i.e. look for rmw insns.  If these insns
2466*c87b03e5Sespie 		 are also deaths of other webs they might have been counted
2467*c87b03e5Sespie 		 as such into web->span_deaths.  But because of the rmw nature
2468*c87b03e5Sespie 		 of this insn it is no point where a load/reload could be
2469*c87b03e5Sespie 		 placed successfully (it would still conflict with the
2470*c87b03e5Sespie 		 dead web), so reduce the number of spanned deaths by those
2471*c87b03e5Sespie 		 insns.  Note that sometimes such deaths are _not_ counted,
2472*c87b03e5Sespie 	         so negative values can result.  */
2473*c87b03e5Sespie 	      bitmap_zero (already);
2474*c87b03e5Sespie 	      for (i = 0; i < web->num_defs; i++)
2475*c87b03e5Sespie 		{
2476*c87b03e5Sespie 		  rtx insn = web->defs[i]->insn;
2477*c87b03e5Sespie 		  if (TEST_BIT (insns_with_deaths, INSN_UID (insn))
2478*c87b03e5Sespie 		      && !bitmap_bit_p (already, INSN_UID (insn)))
2479*c87b03e5Sespie 		    {
2480*c87b03e5Sespie 		      unsigned int j;
2481*c87b03e5Sespie 		      bitmap_set_bit (already, INSN_UID (insn));
2482*c87b03e5Sespie 		      /* Only decrement it once for each insn.  */
2483*c87b03e5Sespie 		      for (j = 0; j < web->num_uses; j++)
2484*c87b03e5Sespie 			if (web->uses[j]->insn == insn)
2485*c87b03e5Sespie 			  {
2486*c87b03e5Sespie 			    num_deaths--;
2487*c87b03e5Sespie 			    break;
2488*c87b03e5Sespie 			  }
2489*c87b03e5Sespie 		    }
2490*c87b03e5Sespie 		}
2491*c87b03e5Sespie 	      /* But mark them specially if they could possibly be spilled,
2492*c87b03e5Sespie 		 either because they cross some deaths (without the above
2493*c87b03e5Sespie 		 mentioned ones) or calls.  */
2494*c87b03e5Sespie 	      if (web->crosses_call || num_deaths > 0)
2495*c87b03e5Sespie 		web->spill_temp = 1 * 2;
2496*c87b03e5Sespie 	    }
2497*c87b03e5Sespie 	  /* A web spanning no deaths can't be spilled either.  No loads
2498*c87b03e5Sespie 	     would be created for it, ergo no defs.  So the insns wouldn't
2499*c87b03e5Sespie 	     change making the graph not easier to color.  Make this also
2500*c87b03e5Sespie 	     a short web.  Don't do this if it crosses calls, as these are
2501*c87b03e5Sespie 	     also points of reloads.  */
2502*c87b03e5Sespie 	  else if (web->span_deaths == 0 && !web->crosses_call)
2503*c87b03e5Sespie 	    web->spill_temp = 3;
2504*c87b03e5Sespie 	}
2505*c87b03e5Sespie       web->orig_spill_temp = web->spill_temp;
2506*c87b03e5Sespie     }
2507*c87b03e5Sespie   BITMAP_XFREE (already);
2508*c87b03e5Sespie }
2509*c87b03e5Sespie 
2510*c87b03e5Sespie /* Returns nonzero if the rtx MEM refers somehow to a stack location.  */
2511*c87b03e5Sespie 
2512*c87b03e5Sespie int
memref_is_stack_slot(mem)2513*c87b03e5Sespie memref_is_stack_slot (mem)
2514*c87b03e5Sespie      rtx mem;
2515*c87b03e5Sespie {
2516*c87b03e5Sespie   rtx ad = XEXP (mem, 0);
2517*c87b03e5Sespie   rtx x;
2518*c87b03e5Sespie   if (GET_CODE (ad) != PLUS || GET_CODE (XEXP (ad, 1)) != CONST_INT)
2519*c87b03e5Sespie     return 0;
2520*c87b03e5Sespie   x = XEXP (ad, 0);
2521*c87b03e5Sespie   if (x == frame_pointer_rtx || x == hard_frame_pointer_rtx
2522*c87b03e5Sespie       || (x == arg_pointer_rtx && fixed_regs[ARG_POINTER_REGNUM])
2523*c87b03e5Sespie       || x == stack_pointer_rtx)
2524*c87b03e5Sespie     return 1;
2525*c87b03e5Sespie   return 0;
2526*c87b03e5Sespie }
2527*c87b03e5Sespie 
2528*c87b03e5Sespie /* Returns nonzero, if rtx X somewhere contains any pseudo register.  */
2529*c87b03e5Sespie 
2530*c87b03e5Sespie static int
contains_pseudo(x)2531*c87b03e5Sespie contains_pseudo (x)
2532*c87b03e5Sespie      rtx x;
2533*c87b03e5Sespie {
2534*c87b03e5Sespie   const char *fmt;
2535*c87b03e5Sespie   int i;
2536*c87b03e5Sespie   if (GET_CODE (x) == SUBREG)
2537*c87b03e5Sespie     x = SUBREG_REG (x);
2538*c87b03e5Sespie   if (GET_CODE (x) == REG)
2539*c87b03e5Sespie     {
2540*c87b03e5Sespie       if (REGNO (x) >= FIRST_PSEUDO_REGISTER)
2541*c87b03e5Sespie         return 1;
2542*c87b03e5Sespie       else
2543*c87b03e5Sespie 	return 0;
2544*c87b03e5Sespie     }
2545*c87b03e5Sespie 
2546*c87b03e5Sespie   fmt = GET_RTX_FORMAT (GET_CODE (x));
2547*c87b03e5Sespie   for (i = GET_RTX_LENGTH (GET_CODE (x)) - 1; i >= 0; i--)
2548*c87b03e5Sespie     if (fmt[i] == 'e')
2549*c87b03e5Sespie       {
2550*c87b03e5Sespie 	if (contains_pseudo (XEXP (x, i)))
2551*c87b03e5Sespie 	  return 1;
2552*c87b03e5Sespie       }
2553*c87b03e5Sespie     else if (fmt[i] == 'E')
2554*c87b03e5Sespie       {
2555*c87b03e5Sespie 	int j;
2556*c87b03e5Sespie 	for (j = 0; j < XVECLEN (x, i); j++)
2557*c87b03e5Sespie 	  if (contains_pseudo (XVECEXP (x, i, j)))
2558*c87b03e5Sespie 	    return 1;
2559*c87b03e5Sespie       }
2560*c87b03e5Sespie   return 0;
2561*c87b03e5Sespie }
2562*c87b03e5Sespie 
2563*c87b03e5Sespie /* Returns nonzero, if we are able to rematerialize something with
2564*c87b03e5Sespie    value X.  If it's not a general operand, we test if we can produce
2565*c87b03e5Sespie    a valid insn which set a pseudo to that value, and that insn doesn't
2566*c87b03e5Sespie    clobber anything.  */
2567*c87b03e5Sespie 
2568*c87b03e5Sespie static GTY(()) rtx remat_test_insn;
2569*c87b03e5Sespie static int
want_to_remat(x)2570*c87b03e5Sespie want_to_remat (x)
2571*c87b03e5Sespie      rtx x;
2572*c87b03e5Sespie {
2573*c87b03e5Sespie   int num_clobbers = 0;
2574*c87b03e5Sespie   int icode;
2575*c87b03e5Sespie 
2576*c87b03e5Sespie   /* If this is a valid operand, we are OK.  If it's VOIDmode, we aren't.  */
2577*c87b03e5Sespie   if (general_operand (x, GET_MODE (x)))
2578*c87b03e5Sespie     return 1;
2579*c87b03e5Sespie 
2580*c87b03e5Sespie   /* Otherwise, check if we can make a valid insn from it.  First initialize
2581*c87b03e5Sespie      our test insn if we haven't already.  */
2582*c87b03e5Sespie   if (remat_test_insn == 0)
2583*c87b03e5Sespie     {
2584*c87b03e5Sespie       remat_test_insn
2585*c87b03e5Sespie 	= make_insn_raw (gen_rtx_SET (VOIDmode,
2586*c87b03e5Sespie 				      gen_rtx_REG (word_mode,
2587*c87b03e5Sespie 						   FIRST_PSEUDO_REGISTER * 2),
2588*c87b03e5Sespie 				      const0_rtx));
2589*c87b03e5Sespie       NEXT_INSN (remat_test_insn) = PREV_INSN (remat_test_insn) = 0;
2590*c87b03e5Sespie     }
2591*c87b03e5Sespie 
2592*c87b03e5Sespie   /* Now make an insn like the one we would make when rematerializing
2593*c87b03e5Sespie      the value X and see if valid.  */
2594*c87b03e5Sespie   PUT_MODE (SET_DEST (PATTERN (remat_test_insn)), GET_MODE (x));
2595*c87b03e5Sespie   SET_SRC (PATTERN (remat_test_insn)) = x;
2596*c87b03e5Sespie   /* XXX For now we don't allow any clobbers to be added, not just no
2597*c87b03e5Sespie      hardreg clobbers.  */
2598*c87b03e5Sespie   return ((icode = recog (PATTERN (remat_test_insn), remat_test_insn,
2599*c87b03e5Sespie 			  &num_clobbers)) >= 0
2600*c87b03e5Sespie 	  && (num_clobbers == 0
2601*c87b03e5Sespie 	      /*|| ! added_clobbers_hard_reg_p (icode)*/));
2602*c87b03e5Sespie }
2603*c87b03e5Sespie 
2604*c87b03e5Sespie /* Look at all webs, if they perhaps are rematerializable.
2605*c87b03e5Sespie    They are, if all their defs are simple sets to the same value,
2606*c87b03e5Sespie    and that value is simple enough, and want_to_remat() holds for it.  */
2607*c87b03e5Sespie 
2608*c87b03e5Sespie static void
detect_remat_webs()2609*c87b03e5Sespie detect_remat_webs ()
2610*c87b03e5Sespie {
2611*c87b03e5Sespie   struct dlist *d;
2612*c87b03e5Sespie   for (d = WEBS(INITIAL); d; d = d->next)
2613*c87b03e5Sespie     {
2614*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
2615*c87b03e5Sespie       unsigned int i;
2616*c87b03e5Sespie       rtx pat = NULL_RTX;
2617*c87b03e5Sespie       /* Hardregs and useless webs aren't spilled -> no remat necessary.
2618*c87b03e5Sespie 	 Defless webs obviously also can't be rematerialized.  */
2619*c87b03e5Sespie       if (web->regno < FIRST_PSEUDO_REGISTER || !web->num_defs
2620*c87b03e5Sespie 	  || !web->num_uses)
2621*c87b03e5Sespie 	continue;
2622*c87b03e5Sespie       for (i = 0; i < web->num_defs; i++)
2623*c87b03e5Sespie 	{
2624*c87b03e5Sespie 	  rtx insn;
2625*c87b03e5Sespie 	  rtx set = single_set (insn = DF_REF_INSN (web->defs[i]));
2626*c87b03e5Sespie 	  rtx src;
2627*c87b03e5Sespie 	  if (!set)
2628*c87b03e5Sespie 	    break;
2629*c87b03e5Sespie 	  src = SET_SRC (set);
2630*c87b03e5Sespie 	  /* When only subregs of the web are set it isn't easily
2631*c87b03e5Sespie 	     rematerializable.  */
2632*c87b03e5Sespie 	  if (!rtx_equal_p (SET_DEST (set), web->orig_x))
2633*c87b03e5Sespie 	    break;
2634*c87b03e5Sespie 	  /* If we already have a pattern it must be equal to the current.  */
2635*c87b03e5Sespie 	  if (pat && !rtx_equal_p (pat, src))
2636*c87b03e5Sespie 	    break;
2637*c87b03e5Sespie 	  /* Don't do the expensive checks multiple times.  */
2638*c87b03e5Sespie 	  if (pat)
2639*c87b03e5Sespie 	    continue;
2640*c87b03e5Sespie 	  /* For now we allow only constant sources.  */
2641*c87b03e5Sespie 	  if ((CONSTANT_P (src)
2642*c87b03e5Sespie 	       /* If the whole thing is stable already, it is a source for
2643*c87b03e5Sespie 		  remat, no matter how complicated (probably all needed
2644*c87b03e5Sespie 		  resources for it are live everywhere, and don't take
2645*c87b03e5Sespie 		  additional register resources).  */
2646*c87b03e5Sespie 	       /* XXX Currently we can't use patterns which contain
2647*c87b03e5Sespie 		  pseudos, _even_ if they are stable.  The code simply isn't
2648*c87b03e5Sespie 		  prepared for that.  All those operands can't be spilled (or
2649*c87b03e5Sespie 		  the dependent remat webs are not remat anymore), so they
2650*c87b03e5Sespie 		  would be oldwebs in the next iteration.  But currently
2651*c87b03e5Sespie 		  oldwebs can't have their references changed.  The
2652*c87b03e5Sespie 		  incremental machinery barfs on that.  */
2653*c87b03e5Sespie 	       || (!rtx_unstable_p (src) && !contains_pseudo (src))
2654*c87b03e5Sespie 	       /* Additionally also memrefs to stack-slots are usefull, when
2655*c87b03e5Sespie 		  we created them ourself.  They might not have set their
2656*c87b03e5Sespie 		  unchanging flag set, but nevertheless they are stable across
2657*c87b03e5Sespie 		  the livetime in question.  */
2658*c87b03e5Sespie 	       || (GET_CODE (src) == MEM
2659*c87b03e5Sespie 		   && INSN_UID (insn) >= orig_max_uid
2660*c87b03e5Sespie 		   && memref_is_stack_slot (src)))
2661*c87b03e5Sespie 	      /* And we must be able to construct an insn without
2662*c87b03e5Sespie 		 side-effects to actually load that value into a reg.  */
2663*c87b03e5Sespie 	      && want_to_remat (src))
2664*c87b03e5Sespie 	    pat = src;
2665*c87b03e5Sespie 	  else
2666*c87b03e5Sespie 	    break;
2667*c87b03e5Sespie 	}
2668*c87b03e5Sespie       if (pat && i == web->num_defs)
2669*c87b03e5Sespie 	web->pattern = pat;
2670*c87b03e5Sespie     }
2671*c87b03e5Sespie }
2672*c87b03e5Sespie 
2673*c87b03e5Sespie /* Determine the spill costs of all webs.  */
2674*c87b03e5Sespie 
2675*c87b03e5Sespie static void
determine_web_costs()2676*c87b03e5Sespie determine_web_costs ()
2677*c87b03e5Sespie {
2678*c87b03e5Sespie   struct dlist *d;
2679*c87b03e5Sespie   for (d = WEBS(INITIAL); d; d = d->next)
2680*c87b03e5Sespie     {
2681*c87b03e5Sespie       unsigned int i, num_loads;
2682*c87b03e5Sespie       int load_cost, store_cost;
2683*c87b03e5Sespie       unsigned HOST_WIDE_INT w;
2684*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
2685*c87b03e5Sespie       if (web->type == PRECOLORED)
2686*c87b03e5Sespie 	continue;
2687*c87b03e5Sespie       /* Get costs for one load/store.  Note that we offset them by 1,
2688*c87b03e5Sespie 	 because some patterns have a zero rtx_cost(), but we of course
2689*c87b03e5Sespie 	 still need the actual load/store insns.  With zero all those
2690*c87b03e5Sespie 	 webs would be the same, no matter how often and where
2691*c87b03e5Sespie 	 they are used.  */
2692*c87b03e5Sespie       if (web->pattern)
2693*c87b03e5Sespie 	{
2694*c87b03e5Sespie 	  /* This web is rematerializable.  Beware, we set store_cost to
2695*c87b03e5Sespie 	     zero optimistically assuming, that we indeed don't emit any
2696*c87b03e5Sespie 	     stores in the spill-code addition.  This might be wrong if
2697*c87b03e5Sespie 	     at the point of the load not all needed resources are
2698*c87b03e5Sespie 	     available, in which case we emit a stack-based load, for
2699*c87b03e5Sespie 	     which we in turn need the according stores.  */
2700*c87b03e5Sespie 	  load_cost = 1 + rtx_cost (web->pattern, 0);
2701*c87b03e5Sespie 	  store_cost = 0;
2702*c87b03e5Sespie 	}
2703*c87b03e5Sespie       else
2704*c87b03e5Sespie 	{
2705*c87b03e5Sespie 	  load_cost = 1 + MEMORY_MOVE_COST (GET_MODE (web->orig_x),
2706*c87b03e5Sespie 					    web->regclass, 1);
2707*c87b03e5Sespie 	  store_cost = 1 + MEMORY_MOVE_COST (GET_MODE (web->orig_x),
2708*c87b03e5Sespie 					     web->regclass, 0);
2709*c87b03e5Sespie 	}
2710*c87b03e5Sespie       /* We create only loads at deaths, whose number is in span_deaths.  */
2711*c87b03e5Sespie       num_loads = MIN (web->span_deaths, web->num_uses);
2712*c87b03e5Sespie       for (w = 0, i = 0; i < web->num_uses; i++)
2713*c87b03e5Sespie 	w += DF_REF_BB (web->uses[i])->frequency + 1;
2714*c87b03e5Sespie       if (num_loads < web->num_uses)
2715*c87b03e5Sespie 	w = (w * num_loads + web->num_uses - 1) / web->num_uses;
2716*c87b03e5Sespie       web->spill_cost = w * load_cost;
2717*c87b03e5Sespie       if (store_cost)
2718*c87b03e5Sespie 	{
2719*c87b03e5Sespie 	  for (w = 0, i = 0; i < web->num_defs; i++)
2720*c87b03e5Sespie 	    w += DF_REF_BB (web->defs[i])->frequency + 1;
2721*c87b03e5Sespie 	  web->spill_cost += w * store_cost;
2722*c87b03e5Sespie 	}
2723*c87b03e5Sespie       web->orig_spill_cost = web->spill_cost;
2724*c87b03e5Sespie     }
2725*c87b03e5Sespie }
2726*c87b03e5Sespie 
2727*c87b03e5Sespie /* Detect webs which are set in a conditional jump insn (possibly a
2728*c87b03e5Sespie    decrement-and-branch type of insn), and mark them not to be
2729*c87b03e5Sespie    spillable.  The stores for them would need to be placed on edges,
2730*c87b03e5Sespie    which destroys the CFG.  (Somewhen we want to deal with that XXX)  */
2731*c87b03e5Sespie 
2732*c87b03e5Sespie static void
detect_webs_set_in_cond_jump()2733*c87b03e5Sespie detect_webs_set_in_cond_jump ()
2734*c87b03e5Sespie {
2735*c87b03e5Sespie   basic_block bb;
2736*c87b03e5Sespie   FOR_EACH_BB (bb)
2737*c87b03e5Sespie     if (GET_CODE (bb->end) == JUMP_INSN)
2738*c87b03e5Sespie       {
2739*c87b03e5Sespie 	struct df_link *link;
2740*c87b03e5Sespie 	for (link = DF_INSN_DEFS (df, bb->end); link; link = link->next)
2741*c87b03e5Sespie 	  if (link->ref && DF_REF_REGNO (link->ref) >= FIRST_PSEUDO_REGISTER)
2742*c87b03e5Sespie 	    {
2743*c87b03e5Sespie 	      struct web *web = def2web[DF_REF_ID (link->ref)];
2744*c87b03e5Sespie 	      web->orig_spill_temp = web->spill_temp = 3;
2745*c87b03e5Sespie 	    }
2746*c87b03e5Sespie       }
2747*c87b03e5Sespie }
2748*c87b03e5Sespie 
2749*c87b03e5Sespie /* Second top-level function of this file.
2750*c87b03e5Sespie    Converts the connected web parts to full webs.  This means, it allocates
2751*c87b03e5Sespie    all webs, and initializes all fields, including detecting spill
2752*c87b03e5Sespie    temporaries.  It does not distribute moves to their corresponding webs,
2753*c87b03e5Sespie    though.  */
2754*c87b03e5Sespie 
2755*c87b03e5Sespie static void
make_webs(df)2756*c87b03e5Sespie make_webs (df)
2757*c87b03e5Sespie      struct df *df;
2758*c87b03e5Sespie {
2759*c87b03e5Sespie   /* First build all the webs itself.  They are not related with
2760*c87b03e5Sespie      others yet.  */
2761*c87b03e5Sespie   parts_to_webs (df);
2762*c87b03e5Sespie   /* Now detect spill temporaries to initialize their usable_regs set.  */
2763*c87b03e5Sespie   detect_spill_temps ();
2764*c87b03e5Sespie   detect_webs_set_in_cond_jump ();
2765*c87b03e5Sespie   /* And finally relate them to each other, meaning to record all possible
2766*c87b03e5Sespie      conflicts between webs (see the comment there).  */
2767*c87b03e5Sespie   conflicts_between_webs (df);
2768*c87b03e5Sespie   detect_remat_webs ();
2769*c87b03e5Sespie   determine_web_costs ();
2770*c87b03e5Sespie }
2771*c87b03e5Sespie 
2772*c87b03e5Sespie /* Distribute moves to the corresponding webs.  */
2773*c87b03e5Sespie 
2774*c87b03e5Sespie static void
moves_to_webs(df)2775*c87b03e5Sespie moves_to_webs (df)
2776*c87b03e5Sespie      struct df *df;
2777*c87b03e5Sespie {
2778*c87b03e5Sespie   struct df_link *link;
2779*c87b03e5Sespie   struct move_list *ml;
2780*c87b03e5Sespie 
2781*c87b03e5Sespie   /* Distribute all moves to their corresponding webs, making sure,
2782*c87b03e5Sespie      each move is in a web maximally one time (happens on some strange
2783*c87b03e5Sespie      insns).  */
2784*c87b03e5Sespie   for (ml = wl_moves; ml; ml = ml->next)
2785*c87b03e5Sespie     {
2786*c87b03e5Sespie       struct move *m = ml->move;
2787*c87b03e5Sespie       struct web *web;
2788*c87b03e5Sespie       struct move_list *newml;
2789*c87b03e5Sespie       if (!m)
2790*c87b03e5Sespie 	continue;
2791*c87b03e5Sespie       m->type = WORKLIST;
2792*c87b03e5Sespie       m->dlink = NULL;
2793*c87b03e5Sespie       /* Multiple defs/uses can happen in moves involving hard-regs in
2794*c87b03e5Sespie 	 a wider mode.  For those df.* creates use/def references for each
2795*c87b03e5Sespie 	 real hard-reg involved.  For coalescing we are interested in
2796*c87b03e5Sespie 	 the smallest numbered hard-reg.  */
2797*c87b03e5Sespie       for (link = DF_INSN_DEFS (df, m->insn); link; link = link->next)
2798*c87b03e5Sespie         if (link->ref)
2799*c87b03e5Sespie 	  {
2800*c87b03e5Sespie 	    web = def2web[DF_REF_ID (link->ref)];
2801*c87b03e5Sespie 	    web = find_web_for_subweb (web);
2802*c87b03e5Sespie 	    if (!m->target_web || web->regno < m->target_web->regno)
2803*c87b03e5Sespie 	      m->target_web = web;
2804*c87b03e5Sespie 	  }
2805*c87b03e5Sespie       for (link = DF_INSN_USES (df, m->insn); link; link = link->next)
2806*c87b03e5Sespie         if (link->ref)
2807*c87b03e5Sespie 	  {
2808*c87b03e5Sespie 	    web = use2web[DF_REF_ID (link->ref)];
2809*c87b03e5Sespie 	    web = find_web_for_subweb (web);
2810*c87b03e5Sespie 	    if (!m->source_web || web->regno < m->source_web->regno)
2811*c87b03e5Sespie 	      m->source_web = web;
2812*c87b03e5Sespie 	  }
2813*c87b03e5Sespie       if (m->source_web && m->target_web
2814*c87b03e5Sespie 	  /* If the usable_regs don't intersect we can't coalesce the two
2815*c87b03e5Sespie 	     webs anyway, as this is no simple copy insn (it might even
2816*c87b03e5Sespie 	     need an intermediate stack temp to execute this "copy" insn).  */
2817*c87b03e5Sespie 	  && hard_regs_intersect_p (&m->source_web->usable_regs,
2818*c87b03e5Sespie 				    &m->target_web->usable_regs))
2819*c87b03e5Sespie 	{
2820*c87b03e5Sespie 	  if (!flag_ra_optimistic_coalescing)
2821*c87b03e5Sespie 	    {
2822*c87b03e5Sespie 	      struct move_list *test = m->source_web->moves;
2823*c87b03e5Sespie 	      for (; test && test->move != m; test = test->next);
2824*c87b03e5Sespie 	      if (! test)
2825*c87b03e5Sespie 		{
2826*c87b03e5Sespie 		  newml = (struct move_list*)
2827*c87b03e5Sespie 		    ra_alloc (sizeof (struct move_list));
2828*c87b03e5Sespie 		  newml->move = m;
2829*c87b03e5Sespie 		  newml->next = m->source_web->moves;
2830*c87b03e5Sespie 		  m->source_web->moves = newml;
2831*c87b03e5Sespie 		}
2832*c87b03e5Sespie 	      test = m->target_web->moves;
2833*c87b03e5Sespie 	      for (; test && test->move != m; test = test->next);
2834*c87b03e5Sespie 	      if (! test)
2835*c87b03e5Sespie 		{
2836*c87b03e5Sespie 		  newml = (struct move_list*)
2837*c87b03e5Sespie 		    ra_alloc (sizeof (struct move_list));
2838*c87b03e5Sespie 		  newml->move = m;
2839*c87b03e5Sespie 		  newml->next = m->target_web->moves;
2840*c87b03e5Sespie 		  m->target_web->moves = newml;
2841*c87b03e5Sespie 		}
2842*c87b03e5Sespie 	    }
2843*c87b03e5Sespie 	}
2844*c87b03e5Sespie       else
2845*c87b03e5Sespie 	/* Delete this move.  */
2846*c87b03e5Sespie 	ml->move = NULL;
2847*c87b03e5Sespie     }
2848*c87b03e5Sespie }
2849*c87b03e5Sespie 
2850*c87b03e5Sespie /* Handle tricky asm insns.
2851*c87b03e5Sespie    Supposed to create conflicts to hardregs which aren't allowed in
2852*c87b03e5Sespie    the constraints.  Doesn't actually do that, as it might confuse
2853*c87b03e5Sespie    and constrain the allocator too much.  */
2854*c87b03e5Sespie 
2855*c87b03e5Sespie static void
handle_asm_insn(df,insn)2856*c87b03e5Sespie handle_asm_insn (df, insn)
2857*c87b03e5Sespie      struct df *df;
2858*c87b03e5Sespie      rtx insn;
2859*c87b03e5Sespie {
2860*c87b03e5Sespie   const char *constraints[MAX_RECOG_OPERANDS];
2861*c87b03e5Sespie   enum machine_mode operand_mode[MAX_RECOG_OPERANDS];
2862*c87b03e5Sespie   int i, noperands, in_output;
2863*c87b03e5Sespie   HARD_REG_SET clobbered, allowed, conflict;
2864*c87b03e5Sespie   rtx pat;
2865*c87b03e5Sespie   if (! INSN_P (insn)
2866*c87b03e5Sespie       || (noperands = asm_noperands (PATTERN (insn))) < 0)
2867*c87b03e5Sespie     return;
2868*c87b03e5Sespie   pat = PATTERN (insn);
2869*c87b03e5Sespie   CLEAR_HARD_REG_SET (clobbered);
2870*c87b03e5Sespie 
2871*c87b03e5Sespie   if (GET_CODE (pat) == PARALLEL)
2872*c87b03e5Sespie     for (i = 0; i < XVECLEN (pat, 0); i++)
2873*c87b03e5Sespie       {
2874*c87b03e5Sespie 	rtx t = XVECEXP (pat, 0, i);
2875*c87b03e5Sespie 	if (GET_CODE (t) == CLOBBER && GET_CODE (XEXP (t, 0)) == REG
2876*c87b03e5Sespie 	    && REGNO (XEXP (t, 0)) < FIRST_PSEUDO_REGISTER)
2877*c87b03e5Sespie 	  SET_HARD_REG_BIT (clobbered, REGNO (XEXP (t, 0)));
2878*c87b03e5Sespie       }
2879*c87b03e5Sespie 
2880*c87b03e5Sespie   decode_asm_operands (pat, recog_data.operand, recog_data.operand_loc,
2881*c87b03e5Sespie 		       constraints, operand_mode);
2882*c87b03e5Sespie   in_output = 1;
2883*c87b03e5Sespie   for (i = 0; i < noperands; i++)
2884*c87b03e5Sespie     {
2885*c87b03e5Sespie       const char *p = constraints[i];
2886*c87b03e5Sespie       int cls = (int) NO_REGS;
2887*c87b03e5Sespie       struct df_link *link;
2888*c87b03e5Sespie       rtx reg;
2889*c87b03e5Sespie       struct web *web;
2890*c87b03e5Sespie       int nothing_allowed = 1;
2891*c87b03e5Sespie       reg = recog_data.operand[i];
2892*c87b03e5Sespie 
2893*c87b03e5Sespie       /* Look, if the constraints apply to a pseudo reg, and not to
2894*c87b03e5Sespie 	 e.g. a mem.  */
2895*c87b03e5Sespie       while (GET_CODE (reg) == SUBREG
2896*c87b03e5Sespie 	     || GET_CODE (reg) == ZERO_EXTRACT
2897*c87b03e5Sespie 	     || GET_CODE (reg) == SIGN_EXTRACT
2898*c87b03e5Sespie 	     || GET_CODE (reg) == STRICT_LOW_PART)
2899*c87b03e5Sespie 	reg = XEXP (reg, 0);
2900*c87b03e5Sespie       if (GET_CODE (reg) != REG || REGNO (reg) < FIRST_PSEUDO_REGISTER)
2901*c87b03e5Sespie 	continue;
2902*c87b03e5Sespie 
2903*c87b03e5Sespie       /* Search the web corresponding to this operand.  We depend on
2904*c87b03e5Sespie 	 that decode_asm_operands() places the output operands
2905*c87b03e5Sespie 	 before the input operands.  */
2906*c87b03e5Sespie       while (1)
2907*c87b03e5Sespie 	{
2908*c87b03e5Sespie 	  if (in_output)
2909*c87b03e5Sespie 	    link = df->insns[INSN_UID (insn)].defs;
2910*c87b03e5Sespie 	  else
2911*c87b03e5Sespie 	    link = df->insns[INSN_UID (insn)].uses;
2912*c87b03e5Sespie 	  while (link && link->ref && DF_REF_REAL_REG (link->ref) != reg)
2913*c87b03e5Sespie 	    link = link->next;
2914*c87b03e5Sespie 	  if (!link || !link->ref)
2915*c87b03e5Sespie 	    {
2916*c87b03e5Sespie 	      if (in_output)
2917*c87b03e5Sespie 	        in_output = 0;
2918*c87b03e5Sespie 	      else
2919*c87b03e5Sespie 	        abort ();
2920*c87b03e5Sespie 	    }
2921*c87b03e5Sespie 	  else
2922*c87b03e5Sespie 	    break;
2923*c87b03e5Sespie 	}
2924*c87b03e5Sespie       if (in_output)
2925*c87b03e5Sespie 	web = def2web[DF_REF_ID (link->ref)];
2926*c87b03e5Sespie       else
2927*c87b03e5Sespie 	web = use2web[DF_REF_ID (link->ref)];
2928*c87b03e5Sespie       reg = DF_REF_REG (link->ref);
2929*c87b03e5Sespie 
2930*c87b03e5Sespie       /* Find the constraints, noting the allowed hardregs in allowed.  */
2931*c87b03e5Sespie       CLEAR_HARD_REG_SET (allowed);
2932*c87b03e5Sespie       while (1)
2933*c87b03e5Sespie 	{
2934*c87b03e5Sespie 	  char c = *p++;
2935*c87b03e5Sespie 
2936*c87b03e5Sespie 	  if (c == '\0' || c == ',' || c == '#')
2937*c87b03e5Sespie 	    {
2938*c87b03e5Sespie 	      /* End of one alternative - mark the regs in the current
2939*c87b03e5Sespie 	       class, and reset the class.
2940*c87b03e5Sespie 	       */
2941*c87b03e5Sespie 	      IOR_HARD_REG_SET (allowed, reg_class_contents[cls]);
2942*c87b03e5Sespie 	      if (cls != NO_REGS)
2943*c87b03e5Sespie 		nothing_allowed = 0;
2944*c87b03e5Sespie 	      cls = NO_REGS;
2945*c87b03e5Sespie 	      if (c == '#')
2946*c87b03e5Sespie 		do {
2947*c87b03e5Sespie 		    c = *p++;
2948*c87b03e5Sespie 		} while (c != '\0' && c != ',');
2949*c87b03e5Sespie 	      if (c == '\0')
2950*c87b03e5Sespie 	        break;
2951*c87b03e5Sespie 	      continue;
2952*c87b03e5Sespie 	    }
2953*c87b03e5Sespie 
2954*c87b03e5Sespie 	  switch (c)
2955*c87b03e5Sespie 	    {
2956*c87b03e5Sespie 	      case '=': case '+': case '*': case '%': case '?': case '!':
2957*c87b03e5Sespie 	      case '0': case '1': case '2': case '3': case '4': case 'm':
2958*c87b03e5Sespie 	      case '<': case '>': case 'V': case 'o': case '&': case 'E':
2959*c87b03e5Sespie 	      case 'F': case 's': case 'i': case 'n': case 'X': case 'I':
2960*c87b03e5Sespie 	      case 'J': case 'K': case 'L': case 'M': case 'N': case 'O':
2961*c87b03e5Sespie 	      case 'P':
2962*c87b03e5Sespie 		break;
2963*c87b03e5Sespie 
2964*c87b03e5Sespie 	      case 'p':
2965*c87b03e5Sespie 		cls = (int) reg_class_subunion[cls][(int) BASE_REG_CLASS];
2966*c87b03e5Sespie 		nothing_allowed = 0;
2967*c87b03e5Sespie 	        break;
2968*c87b03e5Sespie 
2969*c87b03e5Sespie 	      case 'g':
2970*c87b03e5Sespie 	      case 'r':
2971*c87b03e5Sespie 		cls = (int) reg_class_subunion[cls][(int) GENERAL_REGS];
2972*c87b03e5Sespie 		nothing_allowed = 0;
2973*c87b03e5Sespie 		break;
2974*c87b03e5Sespie 
2975*c87b03e5Sespie 	      default:
2976*c87b03e5Sespie 		cls =
2977*c87b03e5Sespie 		  (int) reg_class_subunion[cls][(int)
2978*c87b03e5Sespie 						REG_CLASS_FROM_LETTER (c)];
2979*c87b03e5Sespie 	    }
2980*c87b03e5Sespie 	}
2981*c87b03e5Sespie 
2982*c87b03e5Sespie       /* Now make conflicts between this web, and all hardregs, which
2983*c87b03e5Sespie 	 are not allowed by the constraints.  */
2984*c87b03e5Sespie       if (nothing_allowed)
2985*c87b03e5Sespie 	{
2986*c87b03e5Sespie 	  /* If we had no real constraints nothing was explicitely
2987*c87b03e5Sespie 	     allowed, so we allow the whole class (i.e. we make no
2988*c87b03e5Sespie 	     additional conflicts).  */
2989*c87b03e5Sespie 	  CLEAR_HARD_REG_SET (conflict);
2990*c87b03e5Sespie 	}
2991*c87b03e5Sespie       else
2992*c87b03e5Sespie 	{
2993*c87b03e5Sespie 	  COPY_HARD_REG_SET (conflict, usable_regs
2994*c87b03e5Sespie 			     [reg_preferred_class (web->regno)]);
2995*c87b03e5Sespie 	  IOR_HARD_REG_SET (conflict, usable_regs
2996*c87b03e5Sespie 			    [reg_alternate_class (web->regno)]);
2997*c87b03e5Sespie 	  AND_COMPL_HARD_REG_SET (conflict, allowed);
2998*c87b03e5Sespie 	  /* We can't yet establish these conflicts.  Reload must go first
2999*c87b03e5Sespie 	     (or better said, we must implement some functionality of reload).
3000*c87b03e5Sespie 	     E.g. if some operands must match, and they need the same color
3001*c87b03e5Sespie 	     we don't see yet, that they do not conflict (because they match).
3002*c87b03e5Sespie 	     For us it looks like two normal references with different DEFs,
3003*c87b03e5Sespie 	     so they conflict, and as they both need the same color, the
3004*c87b03e5Sespie 	     graph becomes uncolorable.  */
3005*c87b03e5Sespie #if 0
3006*c87b03e5Sespie 	  for (c = 0; c < FIRST_PSEUDO_REGISTER; c++)
3007*c87b03e5Sespie 	    if (TEST_HARD_REG_BIT (conflict, c))
3008*c87b03e5Sespie 	      record_conflict (web, hardreg2web[c]);
3009*c87b03e5Sespie #endif
3010*c87b03e5Sespie 	}
3011*c87b03e5Sespie       if (rtl_dump_file)
3012*c87b03e5Sespie 	{
3013*c87b03e5Sespie 	  int c;
3014*c87b03e5Sespie 	  ra_debug_msg (DUMP_ASM, " ASM constrain Web %d conflicts with:", web->id);
3015*c87b03e5Sespie 	  for (c = 0; c < FIRST_PSEUDO_REGISTER; c++)
3016*c87b03e5Sespie 	    if (TEST_HARD_REG_BIT (conflict, c))
3017*c87b03e5Sespie 	      ra_debug_msg (DUMP_ASM, " %d", c);
3018*c87b03e5Sespie 	  ra_debug_msg (DUMP_ASM, "\n");
3019*c87b03e5Sespie 	}
3020*c87b03e5Sespie     }
3021*c87b03e5Sespie }
3022*c87b03e5Sespie 
3023*c87b03e5Sespie /* The real toplevel function in this file.
3024*c87b03e5Sespie    Build (or rebuilds) the complete interference graph with webs
3025*c87b03e5Sespie    and conflicts.  */
3026*c87b03e5Sespie 
3027*c87b03e5Sespie void
build_i_graph(df)3028*c87b03e5Sespie build_i_graph (df)
3029*c87b03e5Sespie      struct df *df;
3030*c87b03e5Sespie {
3031*c87b03e5Sespie   rtx insn;
3032*c87b03e5Sespie 
3033*c87b03e5Sespie   init_web_parts (df);
3034*c87b03e5Sespie 
3035*c87b03e5Sespie   sbitmap_zero (move_handled);
3036*c87b03e5Sespie   wl_moves = NULL;
3037*c87b03e5Sespie 
3038*c87b03e5Sespie   build_web_parts_and_conflicts (df);
3039*c87b03e5Sespie 
3040*c87b03e5Sespie   /* For read-modify-write instructions we may have created two webs.
3041*c87b03e5Sespie      Reconnect them here.  (s.a.)  */
3042*c87b03e5Sespie   connect_rmw_web_parts (df);
3043*c87b03e5Sespie 
3044*c87b03e5Sespie   /* The webs are conceptually complete now, but still scattered around as
3045*c87b03e5Sespie      connected web parts.  Collect all information and build the webs
3046*c87b03e5Sespie      including all conflicts between webs (instead web parts).  */
3047*c87b03e5Sespie   make_webs (df);
3048*c87b03e5Sespie   moves_to_webs (df);
3049*c87b03e5Sespie 
3050*c87b03e5Sespie   /* Look for additional constraints given by asms.  */
3051*c87b03e5Sespie   for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
3052*c87b03e5Sespie     handle_asm_insn (df, insn);
3053*c87b03e5Sespie }
3054*c87b03e5Sespie 
3055*c87b03e5Sespie /* Allocates or reallocates most memory for the interference graph and
3056*c87b03e5Sespie    assiciated structures.  If it reallocates memory (meaning, this is not
3057*c87b03e5Sespie    the first pass), this also changes some structures to reflect the
3058*c87b03e5Sespie    additional entries in various array, and the higher number of
3059*c87b03e5Sespie    defs and uses.  */
3060*c87b03e5Sespie 
3061*c87b03e5Sespie void
ra_build_realloc(df)3062*c87b03e5Sespie ra_build_realloc (df)
3063*c87b03e5Sespie      struct df *df;
3064*c87b03e5Sespie {
3065*c87b03e5Sespie   struct web_part *last_web_parts = web_parts;
3066*c87b03e5Sespie   struct web **last_def2web = def2web;
3067*c87b03e5Sespie   struct web **last_use2web = use2web;
3068*c87b03e5Sespie   sbitmap last_live_over_abnormal = live_over_abnormal;
3069*c87b03e5Sespie   unsigned int i;
3070*c87b03e5Sespie   struct dlist *d;
3071*c87b03e5Sespie   move_handled = sbitmap_alloc (get_max_uid () );
3072*c87b03e5Sespie   web_parts = (struct web_part *) xcalloc (df->def_id + df->use_id,
3073*c87b03e5Sespie 					   sizeof web_parts[0]);
3074*c87b03e5Sespie   def2web = (struct web **) xcalloc (df->def_id + df->use_id,
3075*c87b03e5Sespie 				     sizeof def2web[0]);
3076*c87b03e5Sespie   use2web = &def2web[df->def_id];
3077*c87b03e5Sespie   live_over_abnormal = sbitmap_alloc (df->use_id);
3078*c87b03e5Sespie   sbitmap_zero (live_over_abnormal);
3079*c87b03e5Sespie 
3080*c87b03e5Sespie   /* First go through all old defs and uses.  */
3081*c87b03e5Sespie   for (i = 0; i < last_def_id + last_use_id; i++)
3082*c87b03e5Sespie     {
3083*c87b03e5Sespie       /* And relocate them to the new array.  This is made ugly by the
3084*c87b03e5Sespie          fact, that defs and uses are placed consecutive into one array.  */
3085*c87b03e5Sespie       struct web_part *dest = &web_parts[i < last_def_id
3086*c87b03e5Sespie 					 ? i : (df->def_id + i - last_def_id)];
3087*c87b03e5Sespie       struct web_part *up;
3088*c87b03e5Sespie       *dest = last_web_parts[i];
3089*c87b03e5Sespie       up = dest->uplink;
3090*c87b03e5Sespie       dest->uplink = NULL;
3091*c87b03e5Sespie 
3092*c87b03e5Sespie       /* Also relocate the uplink to point into the new array.  */
3093*c87b03e5Sespie       if (up && up->ref)
3094*c87b03e5Sespie 	{
3095*c87b03e5Sespie 	  unsigned int id = DF_REF_ID (up->ref);
3096*c87b03e5Sespie 	  if (up < &last_web_parts[last_def_id])
3097*c87b03e5Sespie 	    {
3098*c87b03e5Sespie 	      if (df->defs[id])
3099*c87b03e5Sespie 	        dest->uplink = &web_parts[DF_REF_ID (up->ref)];
3100*c87b03e5Sespie 	    }
3101*c87b03e5Sespie 	  else if (df->uses[id])
3102*c87b03e5Sespie 	    dest->uplink = &web_parts[df->def_id + DF_REF_ID (up->ref)];
3103*c87b03e5Sespie 	}
3104*c87b03e5Sespie     }
3105*c87b03e5Sespie 
3106*c87b03e5Sespie   /* Also set up the def2web and use2web arrays, from the last pass.i
3107*c87b03e5Sespie      Remember also the state of live_over_abnormal.  */
3108*c87b03e5Sespie   for (i = 0; i < last_def_id; i++)
3109*c87b03e5Sespie     {
3110*c87b03e5Sespie       struct web *web = last_def2web[i];
3111*c87b03e5Sespie       if (web)
3112*c87b03e5Sespie 	{
3113*c87b03e5Sespie 	  web = find_web_for_subweb (web);
3114*c87b03e5Sespie 	  if (web->type != FREE && web->type != PRECOLORED)
3115*c87b03e5Sespie 	    def2web[i] = last_def2web[i];
3116*c87b03e5Sespie 	}
3117*c87b03e5Sespie     }
3118*c87b03e5Sespie   for (i = 0; i < last_use_id; i++)
3119*c87b03e5Sespie     {
3120*c87b03e5Sespie       struct web *web = last_use2web[i];
3121*c87b03e5Sespie       if (web)
3122*c87b03e5Sespie 	{
3123*c87b03e5Sespie 	  web = find_web_for_subweb (web);
3124*c87b03e5Sespie 	  if (web->type != FREE && web->type != PRECOLORED)
3125*c87b03e5Sespie 	    use2web[i] = last_use2web[i];
3126*c87b03e5Sespie 	}
3127*c87b03e5Sespie       if (TEST_BIT (last_live_over_abnormal, i))
3128*c87b03e5Sespie 	SET_BIT (live_over_abnormal, i);
3129*c87b03e5Sespie     }
3130*c87b03e5Sespie 
3131*c87b03e5Sespie   /* We don't have any subwebs for now.  Somewhen we might want to
3132*c87b03e5Sespie      remember them too, instead of recreating all of them every time.
3133*c87b03e5Sespie      The problem is, that which subwebs we need, depends also on what
3134*c87b03e5Sespie      other webs and subwebs exist, and which conflicts are there.
3135*c87b03e5Sespie      OTOH it should be no problem, if we had some more subwebs than strictly
3136*c87b03e5Sespie      needed.  Later.  */
3137*c87b03e5Sespie   for (d = WEBS(FREE); d; d = d->next)
3138*c87b03e5Sespie     {
3139*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
3140*c87b03e5Sespie       struct web *wnext;
3141*c87b03e5Sespie       for (web = web->subreg_next; web; web = wnext)
3142*c87b03e5Sespie 	{
3143*c87b03e5Sespie 	  wnext = web->subreg_next;
3144*c87b03e5Sespie 	  free (web);
3145*c87b03e5Sespie 	}
3146*c87b03e5Sespie       DLIST_WEB (d)->subreg_next = NULL;
3147*c87b03e5Sespie     }
3148*c87b03e5Sespie 
3149*c87b03e5Sespie   /* The uses we anyway are going to check, are not yet live over an abnormal
3150*c87b03e5Sespie      edge.  In fact, they might actually not anymore, due to added
3151*c87b03e5Sespie      loads.  */
3152*c87b03e5Sespie   if (last_check_uses)
3153*c87b03e5Sespie     sbitmap_difference (live_over_abnormal, live_over_abnormal,
3154*c87b03e5Sespie 		        last_check_uses);
3155*c87b03e5Sespie 
3156*c87b03e5Sespie   if (last_def_id || last_use_id)
3157*c87b03e5Sespie     {
3158*c87b03e5Sespie       sbitmap_free (last_live_over_abnormal);
3159*c87b03e5Sespie       free (last_web_parts);
3160*c87b03e5Sespie       free (last_def2web);
3161*c87b03e5Sespie     }
3162*c87b03e5Sespie   if (!last_max_uid)
3163*c87b03e5Sespie     {
3164*c87b03e5Sespie       /* Setup copy cache, for copy_insn_p ().  */
3165*c87b03e5Sespie       copy_cache = (struct copy_p_cache *)
3166*c87b03e5Sespie 	xcalloc (get_max_uid (), sizeof (copy_cache[0]));
3167*c87b03e5Sespie       init_bb_info ();
3168*c87b03e5Sespie     }
3169*c87b03e5Sespie   else
3170*c87b03e5Sespie     {
3171*c87b03e5Sespie       copy_cache = (struct copy_p_cache *)
3172*c87b03e5Sespie 	xrealloc (copy_cache, get_max_uid () * sizeof (copy_cache[0]));
3173*c87b03e5Sespie       memset (&copy_cache[last_max_uid], 0,
3174*c87b03e5Sespie 	      (get_max_uid () - last_max_uid) * sizeof (copy_cache[0]));
3175*c87b03e5Sespie     }
3176*c87b03e5Sespie }
3177*c87b03e5Sespie 
3178*c87b03e5Sespie /* Free up/clear some memory, only needed for one pass.  */
3179*c87b03e5Sespie 
3180*c87b03e5Sespie void
ra_build_free()3181*c87b03e5Sespie ra_build_free ()
3182*c87b03e5Sespie {
3183*c87b03e5Sespie   struct dlist *d;
3184*c87b03e5Sespie   unsigned int i;
3185*c87b03e5Sespie 
3186*c87b03e5Sespie   /* Clear the moves associated with a web (we also need to look into
3187*c87b03e5Sespie      subwebs here).  */
3188*c87b03e5Sespie   for (i = 0; i < num_webs; i++)
3189*c87b03e5Sespie     {
3190*c87b03e5Sespie       struct web *web = ID2WEB (i);
3191*c87b03e5Sespie       if (!web)
3192*c87b03e5Sespie 	abort ();
3193*c87b03e5Sespie       if (i >= num_webs - num_subwebs
3194*c87b03e5Sespie 	  && (web->conflict_list || web->orig_conflict_list))
3195*c87b03e5Sespie 	abort ();
3196*c87b03e5Sespie       web->moves = NULL;
3197*c87b03e5Sespie     }
3198*c87b03e5Sespie   /* All webs in the free list have no defs or uses anymore.  */
3199*c87b03e5Sespie   for (d = WEBS(FREE); d; d = d->next)
3200*c87b03e5Sespie     {
3201*c87b03e5Sespie       struct web *web = DLIST_WEB (d);
3202*c87b03e5Sespie       if (web->defs)
3203*c87b03e5Sespie 	free (web->defs);
3204*c87b03e5Sespie       web->defs = NULL;
3205*c87b03e5Sespie       if (web->uses)
3206*c87b03e5Sespie 	free (web->uses);
3207*c87b03e5Sespie       web->uses = NULL;
3208*c87b03e5Sespie       /* We can't free the subwebs here, as they are referenced from
3209*c87b03e5Sespie 	 def2web[], and possibly needed in the next ra_build_realloc().
3210*c87b03e5Sespie 	 We free them there (or in free_all_mem()).  */
3211*c87b03e5Sespie     }
3212*c87b03e5Sespie 
3213*c87b03e5Sespie   /* Free all conflict bitmaps from web parts.  Note that we clear
3214*c87b03e5Sespie      _all_ these conflicts, and don't rebuild them next time for uses
3215*c87b03e5Sespie      which aren't rechecked.  This mean, that those conflict bitmaps
3216*c87b03e5Sespie      only contain the incremental information.  The cumulative one
3217*c87b03e5Sespie      is still contained in the edges of the I-graph, i.e. in
3218*c87b03e5Sespie      conflict_list (or orig_conflict_list) of the webs.  */
3219*c87b03e5Sespie   for (i = 0; i < df->def_id + df->use_id; i++)
3220*c87b03e5Sespie     {
3221*c87b03e5Sespie       struct tagged_conflict *cl;
3222*c87b03e5Sespie       for (cl = web_parts[i].sub_conflicts; cl; cl = cl->next)
3223*c87b03e5Sespie 	{
3224*c87b03e5Sespie 	  if (cl->conflicts)
3225*c87b03e5Sespie 	    BITMAP_XFREE (cl->conflicts);
3226*c87b03e5Sespie 	}
3227*c87b03e5Sespie       web_parts[i].sub_conflicts = NULL;
3228*c87b03e5Sespie     }
3229*c87b03e5Sespie 
3230*c87b03e5Sespie   wl_moves = NULL;
3231*c87b03e5Sespie 
3232*c87b03e5Sespie   free (id2web);
3233*c87b03e5Sespie   free (move_handled);
3234*c87b03e5Sespie   sbitmap_free (sup_igraph);
3235*c87b03e5Sespie   sbitmap_free (igraph);
3236*c87b03e5Sespie }
3237*c87b03e5Sespie 
3238*c87b03e5Sespie /* Free all memory for the interference graph structures.  */
3239*c87b03e5Sespie 
3240*c87b03e5Sespie void
ra_build_free_all(df)3241*c87b03e5Sespie ra_build_free_all (df)
3242*c87b03e5Sespie      struct df *df;
3243*c87b03e5Sespie {
3244*c87b03e5Sespie   unsigned int i;
3245*c87b03e5Sespie 
3246*c87b03e5Sespie   free_bb_info ();
3247*c87b03e5Sespie   free (copy_cache);
3248*c87b03e5Sespie   copy_cache = NULL;
3249*c87b03e5Sespie   for (i = 0; i < df->def_id + df->use_id; i++)
3250*c87b03e5Sespie     {
3251*c87b03e5Sespie       struct tagged_conflict *cl;
3252*c87b03e5Sespie       for (cl = web_parts[i].sub_conflicts; cl; cl = cl->next)
3253*c87b03e5Sespie 	{
3254*c87b03e5Sespie 	  if (cl->conflicts)
3255*c87b03e5Sespie 	    BITMAP_XFREE (cl->conflicts);
3256*c87b03e5Sespie 	}
3257*c87b03e5Sespie       web_parts[i].sub_conflicts = NULL;
3258*c87b03e5Sespie     }
3259*c87b03e5Sespie   sbitmap_free (live_over_abnormal);
3260*c87b03e5Sespie   free (web_parts);
3261*c87b03e5Sespie   web_parts = NULL;
3262*c87b03e5Sespie   if (last_check_uses)
3263*c87b03e5Sespie     sbitmap_free (last_check_uses);
3264*c87b03e5Sespie   last_check_uses = NULL;
3265*c87b03e5Sespie   free (def2web);
3266*c87b03e5Sespie   use2web = NULL;
3267*c87b03e5Sespie   def2web = NULL;
3268*c87b03e5Sespie }
3269*c87b03e5Sespie 
3270*c87b03e5Sespie #include "gt-ra-build.h"
3271*c87b03e5Sespie 
3272*c87b03e5Sespie /*
3273*c87b03e5Sespie vim:cinoptions={.5s,g0,p5,t0,(0,^-0.5s,n-0.5s:tw=78:cindent:sw=4:
3274*c87b03e5Sespie */
3275