xref: /openbsd-src/gnu/usr.bin/gcc/gcc/ra.h (revision c87b03e512fc05ed6e0222f6fb0ae86264b1d05b)
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 /* Double linked list to implement the per-type lists of webs
22*c87b03e5Sespie    and moves.  */
23*c87b03e5Sespie struct dlist
24*c87b03e5Sespie {
25*c87b03e5Sespie   struct dlist *prev;
26*c87b03e5Sespie   struct dlist *next;
27*c87b03e5Sespie   union
28*c87b03e5Sespie     {
29*c87b03e5Sespie       struct web *web;
30*c87b03e5Sespie       struct move *move;
31*c87b03e5Sespie     } value;
32*c87b03e5Sespie };
33*c87b03e5Sespie /* Simple helper macros for ease of misuse.  */
34*c87b03e5Sespie #define DLIST_WEB(l) ((l)->value.web)
35*c87b03e5Sespie #define DLIST_MOVE(l) ((l)->value.move)
36*c87b03e5Sespie 
37*c87b03e5Sespie /* Classification of a given node (i.e. what state it's in).  */
38*c87b03e5Sespie enum node_type
39*c87b03e5Sespie {
40*c87b03e5Sespie   INITIAL = 0, FREE,
41*c87b03e5Sespie   PRECOLORED,
42*c87b03e5Sespie   SIMPLIFY, SIMPLIFY_SPILL, SIMPLIFY_FAT, FREEZE, SPILL,
43*c87b03e5Sespie   SELECT,
44*c87b03e5Sespie   SPILLED, COALESCED, COLORED,
45*c87b03e5Sespie   LAST_NODE_TYPE
46*c87b03e5Sespie };
47*c87b03e5Sespie 
48*c87b03e5Sespie /* A list of conflict bitmaps, factorized on the exact part of
49*c87b03e5Sespie    the source, which conflicts with the DEFs, whose ID are noted in
50*c87b03e5Sespie    the bitmap.  This is used while building web-parts with conflicts.  */
51*c87b03e5Sespie struct tagged_conflict
52*c87b03e5Sespie {
53*c87b03e5Sespie   struct tagged_conflict *next;
54*c87b03e5Sespie   bitmap conflicts;
55*c87b03e5Sespie 
56*c87b03e5Sespie   /* If the part of source identified by size S, byteoffset O conflicts,
57*c87b03e5Sespie      then size_word == S | (O << 16).  */
58*c87b03e5Sespie   unsigned int size_word;
59*c87b03e5Sespie };
60*c87b03e5Sespie 
61*c87b03e5Sespie /* Such a structure is allocated initially for each def and use.
62*c87b03e5Sespie    In the process of building the interference graph web parts are
63*c87b03e5Sespie    connected together, if they have common instructions and reference the
64*c87b03e5Sespie    same register.  That way live ranges are build (by connecting defs and
65*c87b03e5Sespie    uses) and implicitely complete webs (by connecting web parts in common
66*c87b03e5Sespie    uses).  */
67*c87b03e5Sespie struct web_part
68*c87b03e5Sespie {
69*c87b03e5Sespie   /* The def or use for this web part.  */
70*c87b03e5Sespie   struct ref *ref;
71*c87b03e5Sespie   /* The uplink implementing the disjoint set.  */
72*c87b03e5Sespie   struct web_part *uplink;
73*c87b03e5Sespie 
74*c87b03e5Sespie   /* Here dynamic information associated with each def/use is saved.
75*c87b03e5Sespie      This all is only valid for root web parts (uplink==NULL).
76*c87b03e5Sespie      That's the information we need to merge, if web parts are unioned.  */
77*c87b03e5Sespie 
78*c87b03e5Sespie   /* Number of spanned insns containing any deaths.  */
79*c87b03e5Sespie   unsigned int spanned_deaths;
80*c87b03e5Sespie   /* The list of bitmaps of DEF ID's with which this part conflicts.  */
81*c87b03e5Sespie   struct tagged_conflict *sub_conflicts;
82*c87b03e5Sespie   /* If there's any call_insn, while this part is live.  */
83*c87b03e5Sespie   unsigned int crosses_call : 1;
84*c87b03e5Sespie };
85*c87b03e5Sespie 
86*c87b03e5Sespie /* Web structure used to store info about connected live ranges.
87*c87b03e5Sespie    This represents the nodes of the interference graph, which gets
88*c87b03e5Sespie    colored.  It can also hold subwebs, which are contained in webs
89*c87b03e5Sespie    and represent subregs.  */
90*c87b03e5Sespie struct web
91*c87b03e5Sespie {
92*c87b03e5Sespie   /* Unique web ID.  */
93*c87b03e5Sespie   unsigned int id;
94*c87b03e5Sespie 
95*c87b03e5Sespie   /* Register number of the live range's variable.  */
96*c87b03e5Sespie   unsigned int regno;
97*c87b03e5Sespie 
98*c87b03e5Sespie   /* How many insns containing deaths do we span?  */
99*c87b03e5Sespie   unsigned int span_deaths;
100*c87b03e5Sespie 
101*c87b03e5Sespie   /* Spill_temp indicates if this web was part of a web spilled in the
102*c87b03e5Sespie      last iteration, or or reasons why this shouldn't be spilled again.
103*c87b03e5Sespie      1 spill web, can't be spilled.
104*c87b03e5Sespie      2 big spill web (live over some deaths).  Discouraged, but not
105*c87b03e5Sespie        impossible to spill again.
106*c87b03e5Sespie      3 short web (spans no deaths), can't be spilled.  */
107*c87b03e5Sespie   unsigned int spill_temp;
108*c87b03e5Sespie 
109*c87b03e5Sespie   /* When coalescing we might change spill_temp.  If breaking aliases we
110*c87b03e5Sespie      need to restore it.  */
111*c87b03e5Sespie   unsigned int orig_spill_temp;
112*c87b03e5Sespie 
113*c87b03e5Sespie   /* Cost of spilling.  */
114*c87b03e5Sespie   unsigned HOST_WIDE_INT spill_cost;
115*c87b03e5Sespie   unsigned HOST_WIDE_INT orig_spill_cost;
116*c87b03e5Sespie 
117*c87b03e5Sespie   /* How many webs are aliased to us?  */
118*c87b03e5Sespie   unsigned int num_aliased;
119*c87b03e5Sespie 
120*c87b03e5Sespie   /* The color we got.  This is a hardreg number.  */
121*c87b03e5Sespie   int color;
122*c87b03e5Sespie   /* 1 + the color this web got in the last pass.  If it hadn't got a color,
123*c87b03e5Sespie      or we are in the first pass, or this web is a new one, this is zero.  */
124*c87b03e5Sespie   int old_color;
125*c87b03e5Sespie 
126*c87b03e5Sespie   /* Now follow some flags characterizing the web.  */
127*c87b03e5Sespie 
128*c87b03e5Sespie   /* Nonzero, if we should use usable_regs for this web, instead of
129*c87b03e5Sespie      preferred_class() or alternate_class().  */
130*c87b03e5Sespie   unsigned int use_my_regs:1;
131*c87b03e5Sespie 
132*c87b03e5Sespie   /* Nonzero if we selected this web as possible spill candidate in
133*c87b03e5Sespie      select_spill().  */
134*c87b03e5Sespie   unsigned int was_spilled:1;
135*c87b03e5Sespie 
136*c87b03e5Sespie   /* We need to distinguish also webs which are targets of coalescing
137*c87b03e5Sespie      (all x with some y, so that x==alias(y)), but the alias field is
138*c87b03e5Sespie      only set for sources of coalescing.  This flag is set for all webs
139*c87b03e5Sespie      involved in coalescing in some way.  */
140*c87b03e5Sespie   unsigned int is_coalesced:1;
141*c87b03e5Sespie 
142*c87b03e5Sespie   /* Nonzero, if this web (or subweb) doesn't correspond with any of
143*c87b03e5Sespie      the current functions actual use of reg rtx.  Happens e.g. with
144*c87b03e5Sespie      conflicts to a web, of which only a part was still undefined at the
145*c87b03e5Sespie      point of that conflict.  In this case we construct a subweb
146*c87b03e5Sespie      representing these yet undefined bits to have a target for the
147*c87b03e5Sespie      conflict.  Suppose e.g. this sequence:
148*c87b03e5Sespie      (set (reg:DI x) ...)
149*c87b03e5Sespie      (set (reg:SI y) ...)
150*c87b03e5Sespie      (set (subreg:SI (reg:DI x) 0) ...)
151*c87b03e5Sespie      (use (reg:DI x))
152*c87b03e5Sespie      Here x only partly conflicts with y.  Namely only (subreg:SI (reg:DI x)
153*c87b03e5Sespie      1) conflicts with it, but this rtx doesn't show up in the program.  For
154*c87b03e5Sespie      such things an "artificial" subweb is built, and this flag is true for
155*c87b03e5Sespie      them.  */
156*c87b03e5Sespie   unsigned int artificial:1;
157*c87b03e5Sespie 
158*c87b03e5Sespie   /* Nonzero if we span a call_insn.  */
159*c87b03e5Sespie   unsigned int crosses_call:1;
160*c87b03e5Sespie 
161*c87b03e5Sespie   /* Wether the web is involved in a move insn.  */
162*c87b03e5Sespie   unsigned int move_related:1;
163*c87b03e5Sespie 
164*c87b03e5Sespie   /* 1 when this web (or parts thereof) are live over an abnormal edge.  */
165*c87b03e5Sespie   unsigned int live_over_abnormal:1;
166*c87b03e5Sespie 
167*c87b03e5Sespie   /* Nonzero if this web is used in subregs where the mode change
168*c87b03e5Sespie      was illegal for hardregs in CLASS_CANNOT_CHANGE_MODE.  */
169*c87b03e5Sespie   unsigned int mode_changed:1;
170*c87b03e5Sespie 
171*c87b03e5Sespie   /* Nonzero, when this web stems from the last pass of the allocator,
172*c87b03e5Sespie      and all info is still valid (i.e. it wasn't spilled).  */
173*c87b03e5Sespie   unsigned int old_web:1;
174*c87b03e5Sespie 
175*c87b03e5Sespie   /* Used in rewrite_program2() to remember webs, which
176*c87b03e5Sespie      are already marked for (re)loading.  */
177*c87b03e5Sespie   unsigned int in_load:1;
178*c87b03e5Sespie 
179*c87b03e5Sespie   /* If in_load is != 0, then this is nonzero, if only one use was seen
180*c87b03e5Sespie      since insertion in loadlist.  Zero if more uses currently need a
181*c87b03e5Sespie      reload.  Used to differentiate between inserting register loads or
182*c87b03e5Sespie      directly substituting the stackref.  */
183*c87b03e5Sespie   unsigned int one_load:1;
184*c87b03e5Sespie 
185*c87b03e5Sespie   /* When using rewrite_program2() this flag gets set if some insns
186*c87b03e5Sespie      were inserted on behalf of this web.  IR spilling might ignore some
187*c87b03e5Sespie      deaths up to the def, so no code might be emitted and we need not to
188*c87b03e5Sespie      spill such a web again.  */
189*c87b03e5Sespie   unsigned int changed:1;
190*c87b03e5Sespie 
191*c87b03e5Sespie   /* With interference region spilling it's sometimes the case, that a
192*c87b03e5Sespie      bb border is also an IR border for webs, which were targets of moves,
193*c87b03e5Sespie      which are already removed due to coalescing.  All webs, which are
194*c87b03e5Sespie      a destination of such a removed move, have this flag set.  */
195*c87b03e5Sespie   unsigned int target_of_spilled_move:1;
196*c87b03e5Sespie 
197*c87b03e5Sespie   /* For optimistic coalescing we need to be able to break aliases, which
198*c87b03e5Sespie      includes restoring conflicts to those before coalescing.  This flag
199*c87b03e5Sespie      is set, if we have a list of conflicts before coalescing.  It's needed
200*c87b03e5Sespie      because that list is lazily constructed only when actually needed.  */
201*c87b03e5Sespie   unsigned int have_orig_conflicts:1;
202*c87b03e5Sespie 
203*c87b03e5Sespie   /* Current state of the node.  */
204*c87b03e5Sespie   ENUM_BITFIELD(node_type) type:5;
205*c87b03e5Sespie 
206*c87b03e5Sespie   /* A regclass, combined from preferred and alternate class, or calculated
207*c87b03e5Sespie      from usable_regs.  Used only for debugging, and to determine
208*c87b03e5Sespie      add_hardregs.  */
209*c87b03e5Sespie   ENUM_BITFIELD(reg_class) regclass:10;
210*c87b03e5Sespie 
211*c87b03e5Sespie   /* Additional consecutive hardregs needed for this web.  */
212*c87b03e5Sespie   int add_hardregs;
213*c87b03e5Sespie 
214*c87b03e5Sespie   /* Number of conflicts currently.  */
215*c87b03e5Sespie   int num_conflicts;
216*c87b03e5Sespie 
217*c87b03e5Sespie   /* Numbers of uses and defs, which belong to this web.  */
218*c87b03e5Sespie   unsigned int num_uses;
219*c87b03e5Sespie   unsigned int num_defs;
220*c87b03e5Sespie 
221*c87b03e5Sespie   /* The (reg:M a) or (subreg:M1 (reg:M2 a) x) rtx which this
222*c87b03e5Sespie      web is based on.  This is used to distinguish subreg webs
223*c87b03e5Sespie      from it's reg parents, and to get hold of the mode.  */
224*c87b03e5Sespie   rtx orig_x;
225*c87b03e5Sespie 
226*c87b03e5Sespie   /* If this web is a subweb, this point to the super web.  Otherwise
227*c87b03e5Sespie      it's NULL.  */
228*c87b03e5Sespie   struct web *parent_web;
229*c87b03e5Sespie 
230*c87b03e5Sespie   /* If this web is a subweb, but not the last one, this points to the
231*c87b03e5Sespie      next subweb of the same super web.  Otherwise it's NULL.  */
232*c87b03e5Sespie   struct web *subreg_next;
233*c87b03e5Sespie 
234*c87b03e5Sespie   /* The set of webs (or subwebs), this web conflicts with.  */
235*c87b03e5Sespie   struct conflict_link *conflict_list;
236*c87b03e5Sespie 
237*c87b03e5Sespie   /* If have_orig_conflicts is set this contains a copy of conflict_list,
238*c87b03e5Sespie      as it was right after building the interference graph.
239*c87b03e5Sespie      It's used for incremental i-graph building and for breaking
240*c87b03e5Sespie      coalescings again.  */
241*c87b03e5Sespie   struct conflict_link *orig_conflict_list;
242*c87b03e5Sespie 
243*c87b03e5Sespie   /* Bitmap of all conflicts which don't count this pass, because of
244*c87b03e5Sespie      non-intersecting hardregs of the conflicting webs.  See also
245*c87b03e5Sespie      record_conflict().  */
246*c87b03e5Sespie   bitmap useless_conflicts;
247*c87b03e5Sespie 
248*c87b03e5Sespie   /* Different sets of hard registers, for all usable registers, ...  */
249*c87b03e5Sespie   HARD_REG_SET usable_regs;
250*c87b03e5Sespie   /* ... the same before coalescing, ...  */
251*c87b03e5Sespie   HARD_REG_SET orig_usable_regs;
252*c87b03e5Sespie   /* ... colors of all already colored neighbors (used when biased coloring
253*c87b03e5Sespie      is active), and ...  */
254*c87b03e5Sespie   HARD_REG_SET bias_colors;
255*c87b03e5Sespie   /* ... colors of PRECOLORED webs this web is connected to by a move.  */
256*c87b03e5Sespie   HARD_REG_SET prefer_colors;
257*c87b03e5Sespie 
258*c87b03e5Sespie   /* Number of usable colors in usable_regs.  */
259*c87b03e5Sespie   int num_freedom;
260*c87b03e5Sespie 
261*c87b03e5Sespie   /* After successfull coloring the graph each web gets a new reg rtx,
262*c87b03e5Sespie      with which the original uses and defs are replaced.  This is it.  */
263*c87b03e5Sespie   rtx reg_rtx;
264*c87b03e5Sespie 
265*c87b03e5Sespie   /* While spilling this is the rtx of the home of spilled webs.
266*c87b03e5Sespie      It can be a mem ref (a stack slot), or a pseudo register.  */
267*c87b03e5Sespie   rtx stack_slot;
268*c87b03e5Sespie 
269*c87b03e5Sespie   /* Used in rewrite_program2() to remember the using
270*c87b03e5Sespie      insn last seen for webs needing (re)loads.  */
271*c87b03e5Sespie   rtx last_use_insn;
272*c87b03e5Sespie 
273*c87b03e5Sespie   /* If this web is rematerializable, this contains the RTL pattern
274*c87b03e5Sespie      usable as source for that.  Otherwise it's NULL.  */
275*c87b03e5Sespie   rtx pattern;
276*c87b03e5Sespie 
277*c87b03e5Sespie   /* All the defs and uses.  There are num_defs, resp.
278*c87b03e5Sespie      num_uses elements.  */
279*c87b03e5Sespie   struct ref **defs; /* [0..num_defs-1] */
280*c87b03e5Sespie   struct ref **uses; /* [0..num_uses-1] */
281*c87b03e5Sespie 
282*c87b03e5Sespie   /* The web to which this web is aliased (coalesced).  If NULL, this
283*c87b03e5Sespie      web is not coalesced into some other (but might still be a target
284*c87b03e5Sespie      for other webs).  */
285*c87b03e5Sespie   struct web *alias;
286*c87b03e5Sespie 
287*c87b03e5Sespie   /* With iterated coalescing this is a list of active moves this web
288*c87b03e5Sespie      is involved in.  */
289*c87b03e5Sespie   struct move_list *moves;
290*c87b03e5Sespie 
291*c87b03e5Sespie   /* The list implementation.  */
292*c87b03e5Sespie   struct dlist *dlink;
293*c87b03e5Sespie 
294*c87b03e5Sespie   /* While building webs, out of web-parts, this holds a (partial)
295*c87b03e5Sespie      list of all refs for this web seen so far.  */
296*c87b03e5Sespie   struct df_link *temp_refs;
297*c87b03e5Sespie };
298*c87b03e5Sespie 
299*c87b03e5Sespie /* For implementing a single linked list.  */
300*c87b03e5Sespie struct web_link
301*c87b03e5Sespie {
302*c87b03e5Sespie   struct web_link *next;
303*c87b03e5Sespie   struct web *web;
304*c87b03e5Sespie };
305*c87b03e5Sespie 
306*c87b03e5Sespie /* A subconflict is part of a conflict edge to track precisely,
307*c87b03e5Sespie    which parts of two webs conflict, in case not all of both webs do.  */
308*c87b03e5Sespie struct sub_conflict
309*c87b03e5Sespie {
310*c87b03e5Sespie   /* The next partial conflict.  For one such list the parent-web of
311*c87b03e5Sespie      all the S webs, resp. the parent of all the T webs are constant.  */
312*c87b03e5Sespie   struct sub_conflict *next;
313*c87b03e5Sespie   struct web *s;
314*c87b03e5Sespie   struct web *t;
315*c87b03e5Sespie };
316*c87b03e5Sespie 
317*c87b03e5Sespie /* This represents an edge in the conflict graph.  */
318*c87b03e5Sespie struct conflict_link
319*c87b03e5Sespie {
320*c87b03e5Sespie   struct conflict_link *next;
321*c87b03e5Sespie 
322*c87b03e5Sespie   /* The web we conflict with (the Target of the edge).  */
323*c87b03e5Sespie   struct web *t;
324*c87b03e5Sespie 
325*c87b03e5Sespie   /* If not the complete source web and T conflict, this points to
326*c87b03e5Sespie      the list of parts which really conflict.  */
327*c87b03e5Sespie   struct sub_conflict *sub;
328*c87b03e5Sespie };
329*c87b03e5Sespie 
330*c87b03e5Sespie /* For iterated coalescing the moves can be in these states.  */
331*c87b03e5Sespie enum move_type
332*c87b03e5Sespie {
333*c87b03e5Sespie   WORKLIST, MV_COALESCED, CONSTRAINED, FROZEN, ACTIVE,
334*c87b03e5Sespie   LAST_MOVE_TYPE
335*c87b03e5Sespie };
336*c87b03e5Sespie 
337*c87b03e5Sespie /* Structure of a move we are considering coalescing.  */
338*c87b03e5Sespie struct move
339*c87b03e5Sespie {
340*c87b03e5Sespie   rtx insn;
341*c87b03e5Sespie   struct web *source_web;
342*c87b03e5Sespie   struct web *target_web;
343*c87b03e5Sespie   enum move_type type;
344*c87b03e5Sespie   struct dlist *dlink;
345*c87b03e5Sespie };
346*c87b03e5Sespie 
347*c87b03e5Sespie /* List of moves.  */
348*c87b03e5Sespie struct move_list
349*c87b03e5Sespie {
350*c87b03e5Sespie   struct move_list *next;
351*c87b03e5Sespie   struct move *move;
352*c87b03e5Sespie };
353*c87b03e5Sespie 
354*c87b03e5Sespie /* To have fast access to the defs and uses per insn, we have one such
355*c87b03e5Sespie    structure per insn.  The difference to the normal df.c structures is,
356*c87b03e5Sespie    that it doesn't contain any NULL refs, which df.c produces in case
357*c87b03e5Sespie    an insn was modified and it only contains refs to pseudo regs, or to
358*c87b03e5Sespie    hardregs which matter for allocation, i.e. those not in
359*c87b03e5Sespie    never_use_colors.  */
360*c87b03e5Sespie struct ra_insn_info
361*c87b03e5Sespie {
362*c87b03e5Sespie   unsigned int num_defs, num_uses;
363*c87b03e5Sespie   struct ref **defs, **uses;
364*c87b03e5Sespie };
365*c87b03e5Sespie 
366*c87b03e5Sespie /* The above structures are stored in this array, indexed by UID...  */
367*c87b03e5Sespie extern struct ra_insn_info *insn_df;
368*c87b03e5Sespie /* ... and the size of that array, as we add insn after setting it up.  */
369*c87b03e5Sespie extern int insn_df_max_uid;
370*c87b03e5Sespie 
371*c87b03e5Sespie /* The interference graph.  */
372*c87b03e5Sespie extern sbitmap igraph;
373*c87b03e5Sespie /* And how to access it.  I and J are web indices.  If the bit
374*c87b03e5Sespie    igraph_index(I, J) is set, then they conflict.  Note, that
375*c87b03e5Sespie    if only parts of webs conflict, then also only those parts
376*c87b03e5Sespie    are noted in the I-graph (i.e. the parent webs not).  */
377*c87b03e5Sespie #define igraph_index(i, j) ((i) < (j) ? ((j)*((j)-1)/2)+(i) : ((i)*((i)-1)/2)+(j))
378*c87b03e5Sespie /* This is the bitmap of all (even partly) conflicting super webs.
379*c87b03e5Sespie    If bit I*num_webs+J or J*num_webs+I is set, then I and J (both being
380*c87b03e5Sespie    super web indices) conflict, maybe only partially.  Note the
381*c87b03e5Sespie    assymetry.  */
382*c87b03e5Sespie extern sbitmap sup_igraph;
383*c87b03e5Sespie 
384*c87b03e5Sespie /* After the first pass, and when interference region spilling is
385*c87b03e5Sespie    activated, bit I is set, when the insn with UID I contains some
386*c87b03e5Sespie    refs to pseudos which die at the insn.  */
387*c87b03e5Sespie extern sbitmap insns_with_deaths;
388*c87b03e5Sespie /* The size of that sbitmap.  */
389*c87b03e5Sespie extern int death_insns_max_uid;
390*c87b03e5Sespie 
391*c87b03e5Sespie /* All the web-parts.  There are exactly as many web-parts as there
392*c87b03e5Sespie    are register refs in the insn stream.  */
393*c87b03e5Sespie extern struct web_part *web_parts;
394*c87b03e5Sespie 
395*c87b03e5Sespie /* The number of all webs, including subwebs.  */
396*c87b03e5Sespie extern unsigned int num_webs;
397*c87b03e5Sespie /* The number of just the subwebs.  */
398*c87b03e5Sespie extern unsigned int num_subwebs;
399*c87b03e5Sespie /* The number of all webs, including subwebs.  */
400*c87b03e5Sespie extern unsigned int num_allwebs;
401*c87b03e5Sespie 
402*c87b03e5Sespie /* For easy access when given a web ID: id2web[W->id] == W.  */
403*c87b03e5Sespie extern struct web **id2web;
404*c87b03e5Sespie /* For each hardreg, the web which represents it.  */
405*c87b03e5Sespie extern struct web *hardreg2web[FIRST_PSEUDO_REGISTER];
406*c87b03e5Sespie 
407*c87b03e5Sespie /* Given the ID of a df_ref, which represent a DEF, def2web[ID] is
408*c87b03e5Sespie    the web, to which this def belongs.  */
409*c87b03e5Sespie extern struct web **def2web;
410*c87b03e5Sespie /* The same as def2web, just for uses.  */
411*c87b03e5Sespie extern struct web **use2web;
412*c87b03e5Sespie 
413*c87b03e5Sespie /* The list of all recognized and coalescable move insns.  */
414*c87b03e5Sespie extern struct move_list *wl_moves;
415*c87b03e5Sespie 
416*c87b03e5Sespie 
417*c87b03e5Sespie /* Some parts of the compiler which we run after colorizing
418*c87b03e5Sespie    clean reg_renumber[], so we need another place for the colors.
419*c87b03e5Sespie    This is copied to reg_renumber[] just before returning to toplev.  */
420*c87b03e5Sespie extern short *ra_reg_renumber;
421*c87b03e5Sespie /* The size of that array.  Some passes after coloring might have created
422*c87b03e5Sespie    new pseudos, which will get no color.  */
423*c87b03e5Sespie extern int ra_max_regno;
424*c87b03e5Sespie 
425*c87b03e5Sespie /* The dataflow structure of the current function, while regalloc
426*c87b03e5Sespie    runs.  */
427*c87b03e5Sespie extern struct df *df;
428*c87b03e5Sespie 
429*c87b03e5Sespie /* For each basic block B we have a bitmap of DF_REF_ID's of uses,
430*c87b03e5Sespie    which backward reach the end of B.  */
431*c87b03e5Sespie extern bitmap *live_at_end;
432*c87b03e5Sespie 
433*c87b03e5Sespie /* One pass is: collecting registers refs, buiding I-graph, spilling.
434*c87b03e5Sespie    And this is how often we already ran that for the current function.  */
435*c87b03e5Sespie extern int ra_pass;
436*c87b03e5Sespie 
437*c87b03e5Sespie /* The maximum pseudo regno, just before register allocation starts.
438*c87b03e5Sespie    While regalloc runs all pseudos with a larger number represent
439*c87b03e5Sespie    potentially stack slots or hardregs.  I call them stackwebs or
440*c87b03e5Sespie    stackpseudos.  */
441*c87b03e5Sespie extern unsigned int max_normal_pseudo;
442*c87b03e5Sespie 
443*c87b03e5Sespie /* One of the fixed colors.  It must be < FIRST_PSEUDO_REGISTER, because
444*c87b03e5Sespie    we sometimes want to check the color against a HARD_REG_SET.  It must
445*c87b03e5Sespie    be >= 0, because negative values mean "no color".
446*c87b03e5Sespie    This color is used for the above stackwebs, when they can't be colored.
447*c87b03e5Sespie    I.e. normally they would be spilled, but they already represent
448*c87b03e5Sespie    stackslots.  So they are colored with an invalid color.  It has
449*c87b03e5Sespie    the property that even webs which conflict can have that color at the
450*c87b03e5Sespie    same time.  I.e. a stackweb with that color really represents a
451*c87b03e5Sespie    stackslot.  */
452*c87b03e5Sespie extern int an_unusable_color;
453*c87b03e5Sespie 
454*c87b03e5Sespie /* While building the I-graph, every time insn UID is looked at,
455*c87b03e5Sespie    number_seen[UID] is incremented.  For debugging.  */
456*c87b03e5Sespie extern int *number_seen;
457*c87b03e5Sespie 
458*c87b03e5Sespie /* The different lists on which a web can be (based on the type).  */
459*c87b03e5Sespie extern struct dlist *web_lists[(int) LAST_NODE_TYPE];
460*c87b03e5Sespie #define WEBS(type) (web_lists[(int)(type)])
461*c87b03e5Sespie 
462*c87b03e5Sespie /* The largest DF_REF_ID of defs resp. uses, as it was in the
463*c87b03e5Sespie    last pass.  In the first pass this is zero.  Used to distinguish new
464*c87b03e5Sespie    from old refrences.  */
465*c87b03e5Sespie extern unsigned int last_def_id;
466*c87b03e5Sespie extern unsigned int last_use_id;
467*c87b03e5Sespie 
468*c87b03e5Sespie /* Similar for UIDs and number of webs.  */
469*c87b03e5Sespie extern int last_max_uid;
470*c87b03e5Sespie extern unsigned int last_num_webs;
471*c87b03e5Sespie 
472*c87b03e5Sespie /* If I is the ID of an old use, and last_check_uses[I] is set,
473*c87b03e5Sespie    then we must reevaluate it's flow while building the new I-graph.  */
474*c87b03e5Sespie extern sbitmap last_check_uses;
475*c87b03e5Sespie 
476*c87b03e5Sespie /* If nonzero, record_conflict() saves the current conflict list of
477*c87b03e5Sespie    webs in orig_conflict_list, when not already done so, and the conflict
478*c87b03e5Sespie    list is going to be changed.  It is set, after initially building the
479*c87b03e5Sespie    I-graph.  I.e. new conflicts due to coalescing trigger that copying.  */
480*c87b03e5Sespie extern unsigned int remember_conflicts;
481*c87b03e5Sespie 
482*c87b03e5Sespie /* The maximum UID right before calling regalloc().
483*c87b03e5Sespie    Used to detect any instructions inserted by the allocator.  */
484*c87b03e5Sespie extern int orig_max_uid;
485*c87b03e5Sespie 
486*c87b03e5Sespie /* A HARD_REG_SET of those color, which can't be used for coalescing.
487*c87b03e5Sespie    Includes e.g. fixed_regs.  */
488*c87b03e5Sespie extern HARD_REG_SET never_use_colors;
489*c87b03e5Sespie /* For each class C this is reg_class_contents[C] \ never_use_colors.  */
490*c87b03e5Sespie extern HARD_REG_SET usable_regs[N_REG_CLASSES];
491*c87b03e5Sespie /* For each class C the count of hardregs in usable_regs[C].  */
492*c87b03e5Sespie extern unsigned int num_free_regs[N_REG_CLASSES];
493*c87b03e5Sespie /* For each mode M the hardregs, which are MODE_OK for M, and have
494*c87b03e5Sespie    enough space behind them to hold an M value.  Additinally
495*c87b03e5Sespie    if reg R is OK for mode M, but it needs two hardregs, then R+1 will
496*c87b03e5Sespie    also be set here, even if R+1 itself is not OK for M.  I.e. this
497*c87b03e5Sespie    represent the possible resources which could be taken away be a value
498*c87b03e5Sespie    in mode M.  */
499*c87b03e5Sespie extern HARD_REG_SET hardregs_for_mode[NUM_MACHINE_MODES];
500*c87b03e5Sespie /* For 0 <= I <= 255, the number of bits set in I.  Used to calculate
501*c87b03e5Sespie    the number of set bits in a HARD_REG_SET.  */
502*c87b03e5Sespie extern unsigned char byte2bitcount[256];
503*c87b03e5Sespie 
504*c87b03e5Sespie /* Expressive helper macros.  */
505*c87b03e5Sespie #define ID2WEB(I) id2web[I]
506*c87b03e5Sespie #define NUM_REGS(W) (((W)->type == PRECOLORED) ? 1 : (W)->num_freedom)
507*c87b03e5Sespie #define SUBWEB_P(W) (GET_CODE ((W)->orig_x) == SUBREG)
508*c87b03e5Sespie 
509*c87b03e5Sespie /* Constant usable as debug area to ra_debug_msg.  */
510*c87b03e5Sespie #define DUMP_COSTS		0x0001
511*c87b03e5Sespie #define DUMP_WEBS		0x0002
512*c87b03e5Sespie #define DUMP_IGRAPH		0x0004
513*c87b03e5Sespie #define DUMP_PROCESS		0x0008
514*c87b03e5Sespie #define DUMP_COLORIZE		0x0010
515*c87b03e5Sespie #define DUMP_ASM		0x0020
516*c87b03e5Sespie #define DUMP_CONSTRAINTS	0x0040
517*c87b03e5Sespie #define DUMP_RESULTS		0x0080
518*c87b03e5Sespie #define DUMP_DF			0x0100
519*c87b03e5Sespie #define DUMP_RTL		0x0200
520*c87b03e5Sespie #define DUMP_FINAL_RTL		0x0400
521*c87b03e5Sespie #define DUMP_REGCLASS		0x0800
522*c87b03e5Sespie #define DUMP_SM			0x1000
523*c87b03e5Sespie #define DUMP_LAST_FLOW		0x2000
524*c87b03e5Sespie #define DUMP_LAST_RTL		0x4000
525*c87b03e5Sespie #define DUMP_REBUILD		0x8000
526*c87b03e5Sespie #define DUMP_IGRAPH_M		0x10000
527*c87b03e5Sespie #define DUMP_VALIDIFY		0x20000
528*c87b03e5Sespie #define DUMP_EVER		((unsigned int)-1)
529*c87b03e5Sespie #define DUMP_NEARLY_EVER	(DUMP_EVER - DUMP_COSTS - DUMP_IGRAPH_M)
530*c87b03e5Sespie 
531*c87b03e5Sespie /* All the wanted debug levels as ORing of the various DUMP_xxx
532*c87b03e5Sespie    constants.  */
533*c87b03e5Sespie extern unsigned int debug_new_regalloc;
534*c87b03e5Sespie 
535*c87b03e5Sespie /* Nonzero means we want biased coloring.  */
536*c87b03e5Sespie extern int flag_ra_biased;
537*c87b03e5Sespie 
538*c87b03e5Sespie /* Nonzero if we want to use improved (and slow) spilling.  This
539*c87b03e5Sespie    includes also interference region spilling (see below).  */
540*c87b03e5Sespie extern int flag_ra_improved_spilling;
541*c87b03e5Sespie 
542*c87b03e5Sespie /* Nonzero for using interference region spilling.  Zero for improved
543*c87b03e5Sespie    Chaintin style spilling (only at deaths).  */
544*c87b03e5Sespie extern int flag_ra_ir_spilling;
545*c87b03e5Sespie 
546*c87b03e5Sespie /* Nonzero if we use optimistic coalescing, zero for iterated
547*c87b03e5Sespie    coalescing.  */
548*c87b03e5Sespie extern int flag_ra_optimistic_coalescing;
549*c87b03e5Sespie 
550*c87b03e5Sespie /* Nonzero if we want to break aliases of spilled webs.  Forced to
551*c87b03e5Sespie    nonzero, when flag_ra_optimistic_coalescing is.  */
552*c87b03e5Sespie extern int flag_ra_break_aliases;
553*c87b03e5Sespie 
554*c87b03e5Sespie /* Nonzero if we want to merge the spill costs of webs which
555*c87b03e5Sespie    are coalesced.  */
556*c87b03e5Sespie extern int flag_ra_merge_spill_costs;
557*c87b03e5Sespie 
558*c87b03e5Sespie /* Nonzero if we want to spill at every use, instead of at deaths,
559*c87b03e5Sespie    or intereference region borders.  */
560*c87b03e5Sespie extern int flag_ra_spill_every_use;
561*c87b03e5Sespie 
562*c87b03e5Sespie /* Nonzero to output all notes in the debug dumps.  */
563*c87b03e5Sespie extern int flag_ra_dump_notes;
564*c87b03e5Sespie 
565*c87b03e5Sespie extern inline void * ra_alloc PARAMS ((size_t));
566*c87b03e5Sespie extern inline void * ra_calloc PARAMS ((size_t));
567*c87b03e5Sespie extern int hard_regs_count PARAMS ((HARD_REG_SET));
568*c87b03e5Sespie extern rtx ra_emit_move_insn PARAMS ((rtx, rtx));
569*c87b03e5Sespie extern void ra_debug_msg PARAMS ((unsigned int,
570*c87b03e5Sespie 			          const char *, ...)) ATTRIBUTE_PRINTF_2;
571*c87b03e5Sespie extern int hard_regs_intersect_p PARAMS ((HARD_REG_SET *, HARD_REG_SET *));
572*c87b03e5Sespie extern unsigned int rtx_to_bits PARAMS ((rtx));
573*c87b03e5Sespie extern struct web * find_subweb PARAMS ((struct web *, rtx));
574*c87b03e5Sespie extern struct web * find_subweb_2 PARAMS ((struct web *, unsigned int));
575*c87b03e5Sespie extern struct web * find_web_for_subweb_1 PARAMS ((struct web *));
576*c87b03e5Sespie 
577*c87b03e5Sespie #define find_web_for_subweb(w) (((w)->parent_web) \
578*c87b03e5Sespie 				? find_web_for_subweb_1 ((w)->parent_web) \
579*c87b03e5Sespie 				: (w))
580*c87b03e5Sespie 
581*c87b03e5Sespie extern void ra_build_realloc PARAMS ((struct df *));
582*c87b03e5Sespie extern void ra_build_free PARAMS ((void));
583*c87b03e5Sespie extern void ra_build_free_all PARAMS ((struct df *));
584*c87b03e5Sespie extern void ra_colorize_init PARAMS ((void));
585*c87b03e5Sespie extern void ra_colorize_free_all PARAMS ((void));
586*c87b03e5Sespie extern void ra_rewrite_init PARAMS ((void));
587*c87b03e5Sespie 
588*c87b03e5Sespie extern void ra_print_rtx PARAMS ((FILE *, rtx, int));
589*c87b03e5Sespie extern void ra_print_rtx_top PARAMS ((FILE *, rtx, int));
590*c87b03e5Sespie extern void ra_debug_rtx PARAMS ((rtx));
591*c87b03e5Sespie extern void ra_debug_insns PARAMS ((rtx, int));
592*c87b03e5Sespie extern void ra_debug_bbi PARAMS ((int));
593*c87b03e5Sespie extern void ra_print_rtl_with_bb PARAMS ((FILE *, rtx));
594*c87b03e5Sespie extern void dump_igraph PARAMS ((struct df *));
595*c87b03e5Sespie extern void dump_igraph_machine PARAMS ((void));
596*c87b03e5Sespie extern void dump_constraints PARAMS ((void));
597*c87b03e5Sespie extern void dump_cost PARAMS ((unsigned int));
598*c87b03e5Sespie extern void dump_graph_cost PARAMS ((unsigned int, const char *));
599*c87b03e5Sespie extern void dump_ra PARAMS ((struct df *));
600*c87b03e5Sespie extern void dump_number_seen PARAMS ((void));
601*c87b03e5Sespie extern void dump_static_insn_cost PARAMS ((FILE *, const char *,
602*c87b03e5Sespie 					   const char *));
603*c87b03e5Sespie extern void dump_web_conflicts PARAMS ((struct web *));
604*c87b03e5Sespie extern void dump_web_insns PARAMS ((struct web*));
605*c87b03e5Sespie extern int web_conflicts_p PARAMS ((struct web *, struct web *));
606*c87b03e5Sespie extern void debug_hard_reg_set PARAMS ((HARD_REG_SET));
607*c87b03e5Sespie 
608*c87b03e5Sespie extern void remove_list PARAMS ((struct dlist *, struct dlist **));
609*c87b03e5Sespie extern struct dlist * pop_list PARAMS ((struct dlist **));
610*c87b03e5Sespie extern void record_conflict PARAMS ((struct web *, struct web *));
611*c87b03e5Sespie extern int memref_is_stack_slot PARAMS ((rtx));
612*c87b03e5Sespie extern void build_i_graph PARAMS ((struct df *));
613*c87b03e5Sespie extern void put_web PARAMS ((struct web *, enum node_type));
614*c87b03e5Sespie extern void remove_web_from_list PARAMS ((struct web *));
615*c87b03e5Sespie extern void reset_lists PARAMS ((void));
616*c87b03e5Sespie extern struct web * alias PARAMS ((struct web *));
617*c87b03e5Sespie extern void merge_moves PARAMS ((struct web *, struct web *));
618*c87b03e5Sespie extern void ra_colorize_graph PARAMS ((struct df *));
619*c87b03e5Sespie 
620*c87b03e5Sespie extern void actual_spill PARAMS ((void));
621*c87b03e5Sespie extern void emit_colors PARAMS ((struct df *));
622*c87b03e5Sespie extern void delete_moves PARAMS ((void));
623*c87b03e5Sespie extern void setup_renumber PARAMS ((int));
624*c87b03e5Sespie extern void remove_suspicious_death_notes PARAMS ((void));
625