xref: /openbsd/gnu/usr.bin/gcc/gcc/global.c (revision c87b03e5)
1*c87b03e5Sespie /* Allocate registers for pseudo-registers that span basic blocks.
2*c87b03e5Sespie    Copyright (C) 1987, 1988, 1991, 1994, 1996, 1997, 1998,
3*c87b03e5Sespie    1999, 2000, 2002 Free Software Foundation, Inc.
4*c87b03e5Sespie 
5*c87b03e5Sespie This file is part of GCC.
6*c87b03e5Sespie 
7*c87b03e5Sespie GCC is free software; you can redistribute it and/or modify it under
8*c87b03e5Sespie the terms of the GNU General Public License as published by the Free
9*c87b03e5Sespie Software Foundation; either version 2, or (at your option) any later
10*c87b03e5Sespie 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
14*c87b03e5Sespie FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15*c87b03e5Sespie for more details.
16*c87b03e5Sespie 
17*c87b03e5Sespie You should have received a copy of the GNU General Public License
18*c87b03e5Sespie along with GCC; see the file COPYING.  If not, write to the Free
19*c87b03e5Sespie Software Foundation, 59 Temple Place - Suite 330, Boston, MA
20*c87b03e5Sespie 02111-1307, USA.  */
21*c87b03e5Sespie 
22*c87b03e5Sespie 
23*c87b03e5Sespie #include "config.h"
24*c87b03e5Sespie #include "system.h"
25*c87b03e5Sespie 
26*c87b03e5Sespie #include "machmode.h"
27*c87b03e5Sespie #include "hard-reg-set.h"
28*c87b03e5Sespie #include "rtl.h"
29*c87b03e5Sespie #include "tm_p.h"
30*c87b03e5Sespie #include "flags.h"
31*c87b03e5Sespie #include "basic-block.h"
32*c87b03e5Sespie #include "regs.h"
33*c87b03e5Sespie #include "function.h"
34*c87b03e5Sespie #include "insn-config.h"
35*c87b03e5Sespie #include "reload.h"
36*c87b03e5Sespie #include "output.h"
37*c87b03e5Sespie #include "toplev.h"
38*c87b03e5Sespie 
39*c87b03e5Sespie /* This pass of the compiler performs global register allocation.
40*c87b03e5Sespie    It assigns hard register numbers to all the pseudo registers
41*c87b03e5Sespie    that were not handled in local_alloc.  Assignments are recorded
42*c87b03e5Sespie    in the vector reg_renumber, not by changing the rtl code.
43*c87b03e5Sespie    (Such changes are made by final).  The entry point is
44*c87b03e5Sespie    the function global_alloc.
45*c87b03e5Sespie 
46*c87b03e5Sespie    After allocation is complete, the reload pass is run as a subroutine
47*c87b03e5Sespie    of this pass, so that when a pseudo reg loses its hard reg due to
48*c87b03e5Sespie    spilling it is possible to make a second attempt to find a hard
49*c87b03e5Sespie    reg for it.  The reload pass is independent in other respects
50*c87b03e5Sespie    and it is run even when stupid register allocation is in use.
51*c87b03e5Sespie 
52*c87b03e5Sespie    1. Assign allocation-numbers (allocnos) to the pseudo-registers
53*c87b03e5Sespie    still needing allocations and to the pseudo-registers currently
54*c87b03e5Sespie    allocated by local-alloc which may be spilled by reload.
55*c87b03e5Sespie    Set up tables reg_allocno and allocno_reg to map
56*c87b03e5Sespie    reg numbers to allocnos and vice versa.
57*c87b03e5Sespie    max_allocno gets the number of allocnos in use.
58*c87b03e5Sespie 
59*c87b03e5Sespie    2. Allocate a max_allocno by max_allocno conflict bit matrix and clear it.
60*c87b03e5Sespie    Allocate a max_allocno by FIRST_PSEUDO_REGISTER conflict matrix
61*c87b03e5Sespie    for conflicts between allocnos and explicit hard register use
62*c87b03e5Sespie    (which includes use of pseudo-registers allocated by local_alloc).
63*c87b03e5Sespie 
64*c87b03e5Sespie    3. For each basic block
65*c87b03e5Sespie     walk forward through the block, recording which
66*c87b03e5Sespie     pseudo-registers and which hardware registers are live.
67*c87b03e5Sespie     Build the conflict matrix between the pseudo-registers
68*c87b03e5Sespie     and another of pseudo-registers versus hardware registers.
69*c87b03e5Sespie     Also record the preferred hardware registers
70*c87b03e5Sespie     for each pseudo-register.
71*c87b03e5Sespie 
72*c87b03e5Sespie    4. Sort a table of the allocnos into order of
73*c87b03e5Sespie    desirability of the variables.
74*c87b03e5Sespie 
75*c87b03e5Sespie    5. Allocate the variables in that order; each if possible into
76*c87b03e5Sespie    a preferred register, else into another register.  */
77*c87b03e5Sespie 
78*c87b03e5Sespie /* Number of pseudo-registers which are candidates for allocation.  */
79*c87b03e5Sespie 
80*c87b03e5Sespie static int max_allocno;
81*c87b03e5Sespie 
82*c87b03e5Sespie /* Indexed by (pseudo) reg number, gives the allocno, or -1
83*c87b03e5Sespie    for pseudo registers which are not to be allocated.  */
84*c87b03e5Sespie 
85*c87b03e5Sespie static int *reg_allocno;
86*c87b03e5Sespie 
87*c87b03e5Sespie struct allocno
88*c87b03e5Sespie {
89*c87b03e5Sespie   int reg;
90*c87b03e5Sespie   /* Gives the number of consecutive hard registers needed by that
91*c87b03e5Sespie      pseudo reg.  */
92*c87b03e5Sespie   int size;
93*c87b03e5Sespie 
94*c87b03e5Sespie   /* Number of calls crossed by each allocno.  */
95*c87b03e5Sespie   int calls_crossed;
96*c87b03e5Sespie 
97*c87b03e5Sespie   /* Number of refs to each allocno.  */
98*c87b03e5Sespie   int n_refs;
99*c87b03e5Sespie 
100*c87b03e5Sespie   /* Frequency of uses of each allocno.  */
101*c87b03e5Sespie   int freq;
102*c87b03e5Sespie 
103*c87b03e5Sespie   /* Guess at live length of each allocno.
104*c87b03e5Sespie      This is actually the max of the live lengths of the regs.  */
105*c87b03e5Sespie   int live_length;
106*c87b03e5Sespie 
107*c87b03e5Sespie   /* Set of hard regs conflicting with allocno N.  */
108*c87b03e5Sespie 
109*c87b03e5Sespie   HARD_REG_SET hard_reg_conflicts;
110*c87b03e5Sespie 
111*c87b03e5Sespie   /* Set of hard regs preferred by allocno N.
112*c87b03e5Sespie      This is used to make allocnos go into regs that are copied to or from them,
113*c87b03e5Sespie      when possible, to reduce register shuffling.  */
114*c87b03e5Sespie 
115*c87b03e5Sespie   HARD_REG_SET hard_reg_preferences;
116*c87b03e5Sespie 
117*c87b03e5Sespie   /* Similar, but just counts register preferences made in simple copy
118*c87b03e5Sespie      operations, rather than arithmetic.  These are given priority because
119*c87b03e5Sespie      we can always eliminate an insn by using these, but using a register
120*c87b03e5Sespie      in the above list won't always eliminate an insn.  */
121*c87b03e5Sespie 
122*c87b03e5Sespie   HARD_REG_SET hard_reg_copy_preferences;
123*c87b03e5Sespie 
124*c87b03e5Sespie   /* Similar to hard_reg_preferences, but includes bits for subsequent
125*c87b03e5Sespie      registers when an allocno is multi-word.  The above variable is used for
126*c87b03e5Sespie      allocation while this is used to build reg_someone_prefers, below.  */
127*c87b03e5Sespie 
128*c87b03e5Sespie   HARD_REG_SET hard_reg_full_preferences;
129*c87b03e5Sespie 
130*c87b03e5Sespie   /* Set of hard registers that some later allocno has a preference for.  */
131*c87b03e5Sespie 
132*c87b03e5Sespie   HARD_REG_SET regs_someone_prefers;
133*c87b03e5Sespie 
134*c87b03e5Sespie #ifdef STACK_REGS
135*c87b03e5Sespie   /* Set to true if allocno can't be allocated in the stack register.  */
136*c87b03e5Sespie   bool no_stack_reg;
137*c87b03e5Sespie #endif
138*c87b03e5Sespie };
139*c87b03e5Sespie 
140*c87b03e5Sespie static struct allocno *allocno;
141*c87b03e5Sespie 
142*c87b03e5Sespie /* A vector of the integers from 0 to max_allocno-1,
143*c87b03e5Sespie    sorted in the order of first-to-be-allocated first.  */
144*c87b03e5Sespie 
145*c87b03e5Sespie static int *allocno_order;
146*c87b03e5Sespie 
147*c87b03e5Sespie /* Indexed by (pseudo) reg number, gives the number of another
148*c87b03e5Sespie    lower-numbered pseudo reg which can share a hard reg with this pseudo
149*c87b03e5Sespie    *even if the two pseudos would otherwise appear to conflict*.  */
150*c87b03e5Sespie 
151*c87b03e5Sespie static int *reg_may_share;
152*c87b03e5Sespie 
153*c87b03e5Sespie /* Define the number of bits in each element of `conflicts' and what
154*c87b03e5Sespie    type that element has.  We use the largest integer format on the
155*c87b03e5Sespie    host machine.  */
156*c87b03e5Sespie 
157*c87b03e5Sespie #define INT_BITS HOST_BITS_PER_WIDE_INT
158*c87b03e5Sespie #define INT_TYPE HOST_WIDE_INT
159*c87b03e5Sespie 
160*c87b03e5Sespie /* max_allocno by max_allocno array of bits,
161*c87b03e5Sespie    recording whether two allocno's conflict (can't go in the same
162*c87b03e5Sespie    hardware register).
163*c87b03e5Sespie 
164*c87b03e5Sespie    `conflicts' is symmetric after the call to mirror_conflicts.  */
165*c87b03e5Sespie 
166*c87b03e5Sespie static INT_TYPE *conflicts;
167*c87b03e5Sespie 
168*c87b03e5Sespie /* Number of ints require to hold max_allocno bits.
169*c87b03e5Sespie    This is the length of a row in `conflicts'.  */
170*c87b03e5Sespie 
171*c87b03e5Sespie static int allocno_row_words;
172*c87b03e5Sespie 
173*c87b03e5Sespie /* Two macros to test or store 1 in an element of `conflicts'.  */
174*c87b03e5Sespie 
175*c87b03e5Sespie #define CONFLICTP(I, J) \
176*c87b03e5Sespie  (conflicts[(I) * allocno_row_words + (unsigned) (J) / INT_BITS]	\
177*c87b03e5Sespie   & ((INT_TYPE) 1 << ((unsigned) (J) % INT_BITS)))
178*c87b03e5Sespie 
179*c87b03e5Sespie /* For any allocno set in ALLOCNO_SET, set ALLOCNO to that allocno,
180*c87b03e5Sespie    and execute CODE.  */
181*c87b03e5Sespie #define EXECUTE_IF_SET_IN_ALLOCNO_SET(ALLOCNO_SET, ALLOCNO, CODE)	\
182*c87b03e5Sespie do {									\
183*c87b03e5Sespie   int i_;								\
184*c87b03e5Sespie   int allocno_;								\
185*c87b03e5Sespie   INT_TYPE *p_ = (ALLOCNO_SET);						\
186*c87b03e5Sespie 									\
187*c87b03e5Sespie   for (i_ = allocno_row_words - 1, allocno_ = 0; i_ >= 0;		\
188*c87b03e5Sespie        i_--, allocno_ += INT_BITS)					\
189*c87b03e5Sespie     {									\
190*c87b03e5Sespie       unsigned INT_TYPE word_ = (unsigned INT_TYPE) *p_++;		\
191*c87b03e5Sespie 									\
192*c87b03e5Sespie       for ((ALLOCNO) = allocno_; word_; word_ >>= 1, (ALLOCNO)++)	\
193*c87b03e5Sespie 	{								\
194*c87b03e5Sespie 	  if (word_ & 1)						\
195*c87b03e5Sespie 	    {CODE;}							\
196*c87b03e5Sespie 	}								\
197*c87b03e5Sespie     }									\
198*c87b03e5Sespie } while (0)
199*c87b03e5Sespie 
200*c87b03e5Sespie /* This doesn't work for non-GNU C due to the way CODE is macro expanded.  */
201*c87b03e5Sespie #if 0
202*c87b03e5Sespie /* For any allocno that conflicts with IN_ALLOCNO, set OUT_ALLOCNO to
203*c87b03e5Sespie    the conflicting allocno, and execute CODE.  This macro assumes that
204*c87b03e5Sespie    mirror_conflicts has been run.  */
205*c87b03e5Sespie #define EXECUTE_IF_CONFLICT(IN_ALLOCNO, OUT_ALLOCNO, CODE)\
206*c87b03e5Sespie   EXECUTE_IF_SET_IN_ALLOCNO_SET (conflicts + (IN_ALLOCNO) * allocno_row_words,\
207*c87b03e5Sespie 				 OUT_ALLOCNO, (CODE))
208*c87b03e5Sespie #endif
209*c87b03e5Sespie 
210*c87b03e5Sespie /* Set of hard regs currently live (during scan of all insns).  */
211*c87b03e5Sespie 
212*c87b03e5Sespie static HARD_REG_SET hard_regs_live;
213*c87b03e5Sespie 
214*c87b03e5Sespie /* Set of registers that global-alloc isn't supposed to use.  */
215*c87b03e5Sespie 
216*c87b03e5Sespie static HARD_REG_SET no_global_alloc_regs;
217*c87b03e5Sespie 
218*c87b03e5Sespie /* Set of registers used so far.  */
219*c87b03e5Sespie 
220*c87b03e5Sespie static HARD_REG_SET regs_used_so_far;
221*c87b03e5Sespie 
222*c87b03e5Sespie /* Number of refs to each hard reg, as used by local alloc.
223*c87b03e5Sespie    It is zero for a reg that contains global pseudos or is explicitly used.  */
224*c87b03e5Sespie 
225*c87b03e5Sespie static int local_reg_n_refs[FIRST_PSEUDO_REGISTER];
226*c87b03e5Sespie 
227*c87b03e5Sespie /* Frequency of uses of given hard reg.  */
228*c87b03e5Sespie static int local_reg_freq[FIRST_PSEUDO_REGISTER];
229*c87b03e5Sespie 
230*c87b03e5Sespie /* Guess at live length of each hard reg, as used by local alloc.
231*c87b03e5Sespie    This is actually the sum of the live lengths of the specific regs.  */
232*c87b03e5Sespie 
233*c87b03e5Sespie static int local_reg_live_length[FIRST_PSEUDO_REGISTER];
234*c87b03e5Sespie 
235*c87b03e5Sespie /* Set to 1 a bit in a vector TABLE of HARD_REG_SETs, for vector
236*c87b03e5Sespie    element I, and hard register number J.  */
237*c87b03e5Sespie 
238*c87b03e5Sespie #define SET_REGBIT(TABLE, I, J)  SET_HARD_REG_BIT (allocno[I].TABLE, J)
239*c87b03e5Sespie 
240*c87b03e5Sespie /* Bit mask for allocnos live at current point in the scan.  */
241*c87b03e5Sespie 
242*c87b03e5Sespie static INT_TYPE *allocnos_live;
243*c87b03e5Sespie 
244*c87b03e5Sespie /* Test, set or clear bit number I in allocnos_live,
245*c87b03e5Sespie    a bit vector indexed by allocno.  */
246*c87b03e5Sespie 
247*c87b03e5Sespie #define SET_ALLOCNO_LIVE(I)				\
248*c87b03e5Sespie   (allocnos_live[(unsigned) (I) / INT_BITS]		\
249*c87b03e5Sespie      |= ((INT_TYPE) 1 << ((unsigned) (I) % INT_BITS)))
250*c87b03e5Sespie 
251*c87b03e5Sespie #define CLEAR_ALLOCNO_LIVE(I)				\
252*c87b03e5Sespie   (allocnos_live[(unsigned) (I) / INT_BITS]		\
253*c87b03e5Sespie      &= ~((INT_TYPE) 1 << ((unsigned) (I) % INT_BITS)))
254*c87b03e5Sespie 
255*c87b03e5Sespie /* This is turned off because it doesn't work right for DImode.
256*c87b03e5Sespie    (And it is only used for DImode, so the other cases are worthless.)
257*c87b03e5Sespie    The problem is that it isn't true that there is NO possibility of conflict;
258*c87b03e5Sespie    only that there is no conflict if the two pseudos get the exact same regs.
259*c87b03e5Sespie    If they were allocated with a partial overlap, there would be a conflict.
260*c87b03e5Sespie    We can't safely turn off the conflict unless we have another way to
261*c87b03e5Sespie    prevent the partial overlap.
262*c87b03e5Sespie 
263*c87b03e5Sespie    Idea: change hard_reg_conflicts so that instead of recording which
264*c87b03e5Sespie    hard regs the allocno may not overlap, it records where the allocno
265*c87b03e5Sespie    may not start.  Change both where it is used and where it is updated.
266*c87b03e5Sespie    Then there is a way to record that (reg:DI 108) may start at 10
267*c87b03e5Sespie    but not at 9 or 11.  There is still the question of how to record
268*c87b03e5Sespie    this semi-conflict between two pseudos.  */
269*c87b03e5Sespie #if 0
270*c87b03e5Sespie /* Reg pairs for which conflict after the current insn
271*c87b03e5Sespie    is inhibited by a REG_NO_CONFLICT note.
272*c87b03e5Sespie    If the table gets full, we ignore any other notes--that is conservative.  */
273*c87b03e5Sespie #define NUM_NO_CONFLICT_PAIRS 4
274*c87b03e5Sespie /* Number of pairs in use in this insn.  */
275*c87b03e5Sespie int n_no_conflict_pairs;
276*c87b03e5Sespie static struct { int allocno1, allocno2;}
277*c87b03e5Sespie   no_conflict_pairs[NUM_NO_CONFLICT_PAIRS];
278*c87b03e5Sespie #endif /* 0 */
279*c87b03e5Sespie 
280*c87b03e5Sespie /* Record all regs that are set in any one insn.
281*c87b03e5Sespie    Communication from mark_reg_{store,clobber} and global_conflicts.  */
282*c87b03e5Sespie 
283*c87b03e5Sespie static rtx *regs_set;
284*c87b03e5Sespie static int n_regs_set;
285*c87b03e5Sespie 
286*c87b03e5Sespie /* All registers that can be eliminated.  */
287*c87b03e5Sespie 
288*c87b03e5Sespie static HARD_REG_SET eliminable_regset;
289*c87b03e5Sespie 
290*c87b03e5Sespie static int allocno_compare	PARAMS ((const PTR, const PTR));
291*c87b03e5Sespie static void global_conflicts	PARAMS ((void));
292*c87b03e5Sespie static void mirror_conflicts	PARAMS ((void));
293*c87b03e5Sespie static void expand_preferences	PARAMS ((void));
294*c87b03e5Sespie static void prune_preferences	PARAMS ((void));
295*c87b03e5Sespie static void find_reg		PARAMS ((int, HARD_REG_SET, int, int, int));
296*c87b03e5Sespie static void record_one_conflict PARAMS ((int));
297*c87b03e5Sespie static void record_conflicts	PARAMS ((int *, int));
298*c87b03e5Sespie static void mark_reg_store	PARAMS ((rtx, rtx, void *));
299*c87b03e5Sespie static void mark_reg_clobber	PARAMS ((rtx, rtx, void *));
300*c87b03e5Sespie static void mark_reg_conflicts	PARAMS ((rtx));
301*c87b03e5Sespie static void mark_reg_death	PARAMS ((rtx));
302*c87b03e5Sespie static void mark_reg_live_nc	PARAMS ((int, enum machine_mode));
303*c87b03e5Sespie static void set_preference	PARAMS ((rtx, rtx));
304*c87b03e5Sespie static void dump_conflicts	PARAMS ((FILE *));
305*c87b03e5Sespie static void reg_becomes_live	PARAMS ((rtx, rtx, void *));
306*c87b03e5Sespie static void reg_dies		PARAMS ((int, enum machine_mode,
307*c87b03e5Sespie 				       struct insn_chain *));
308*c87b03e5Sespie 
309*c87b03e5Sespie /* Perform allocation of pseudo-registers not allocated by local_alloc.
310*c87b03e5Sespie    FILE is a file to output debugging information on,
311*c87b03e5Sespie    or zero if such output is not desired.
312*c87b03e5Sespie 
313*c87b03e5Sespie    Return value is nonzero if reload failed
314*c87b03e5Sespie    and we must not do any more for this function.  */
315*c87b03e5Sespie 
316*c87b03e5Sespie int
global_alloc(file)317*c87b03e5Sespie global_alloc (file)
318*c87b03e5Sespie      FILE *file;
319*c87b03e5Sespie {
320*c87b03e5Sespie   int retval;
321*c87b03e5Sespie #ifdef ELIMINABLE_REGS
322*c87b03e5Sespie   static const struct {const int from, to; } eliminables[] = ELIMINABLE_REGS;
323*c87b03e5Sespie #endif
324*c87b03e5Sespie   int need_fp
325*c87b03e5Sespie     = (! flag_omit_frame_pointer
326*c87b03e5Sespie #ifdef EXIT_IGNORE_STACK
327*c87b03e5Sespie        || (current_function_calls_alloca && EXIT_IGNORE_STACK)
328*c87b03e5Sespie #endif
329*c87b03e5Sespie        || FRAME_POINTER_REQUIRED);
330*c87b03e5Sespie 
331*c87b03e5Sespie   size_t i;
332*c87b03e5Sespie   rtx x;
333*c87b03e5Sespie 
334*c87b03e5Sespie   max_allocno = 0;
335*c87b03e5Sespie 
336*c87b03e5Sespie   /* A machine may have certain hard registers that
337*c87b03e5Sespie      are safe to use only within a basic block.  */
338*c87b03e5Sespie 
339*c87b03e5Sespie   CLEAR_HARD_REG_SET (no_global_alloc_regs);
340*c87b03e5Sespie 
341*c87b03e5Sespie   /* Build the regset of all eliminable registers and show we can't use those
342*c87b03e5Sespie      that we already know won't be eliminated.  */
343*c87b03e5Sespie #ifdef ELIMINABLE_REGS
344*c87b03e5Sespie   for (i = 0; i < ARRAY_SIZE (eliminables); i++)
345*c87b03e5Sespie     {
346*c87b03e5Sespie       SET_HARD_REG_BIT (eliminable_regset, eliminables[i].from);
347*c87b03e5Sespie 
348*c87b03e5Sespie       if (! CAN_ELIMINATE (eliminables[i].from, eliminables[i].to)
349*c87b03e5Sespie 	  || (eliminables[i].to == STACK_POINTER_REGNUM && need_fp))
350*c87b03e5Sespie 	SET_HARD_REG_BIT (no_global_alloc_regs, eliminables[i].from);
351*c87b03e5Sespie     }
352*c87b03e5Sespie #if FRAME_POINTER_REGNUM != HARD_FRAME_POINTER_REGNUM
353*c87b03e5Sespie   SET_HARD_REG_BIT (eliminable_regset, HARD_FRAME_POINTER_REGNUM);
354*c87b03e5Sespie   if (need_fp)
355*c87b03e5Sespie     SET_HARD_REG_BIT (no_global_alloc_regs, HARD_FRAME_POINTER_REGNUM);
356*c87b03e5Sespie #endif
357*c87b03e5Sespie 
358*c87b03e5Sespie #else
359*c87b03e5Sespie   SET_HARD_REG_BIT (eliminable_regset, FRAME_POINTER_REGNUM);
360*c87b03e5Sespie   if (need_fp)
361*c87b03e5Sespie     SET_HARD_REG_BIT (no_global_alloc_regs, FRAME_POINTER_REGNUM);
362*c87b03e5Sespie #endif
363*c87b03e5Sespie 
364*c87b03e5Sespie   /* Track which registers have already been used.  Start with registers
365*c87b03e5Sespie      explicitly in the rtl, then registers allocated by local register
366*c87b03e5Sespie      allocation.  */
367*c87b03e5Sespie 
368*c87b03e5Sespie   CLEAR_HARD_REG_SET (regs_used_so_far);
369*c87b03e5Sespie #ifdef LEAF_REGISTERS
370*c87b03e5Sespie   /* If we are doing the leaf function optimization, and this is a leaf
371*c87b03e5Sespie      function, it means that the registers that take work to save are those
372*c87b03e5Sespie      that need a register window.  So prefer the ones that can be used in
373*c87b03e5Sespie      a leaf function.  */
374*c87b03e5Sespie   {
375*c87b03e5Sespie     const char *cheap_regs;
376*c87b03e5Sespie     const char *const leaf_regs = LEAF_REGISTERS;
377*c87b03e5Sespie 
378*c87b03e5Sespie     if (only_leaf_regs_used () && leaf_function_p ())
379*c87b03e5Sespie       cheap_regs = leaf_regs;
380*c87b03e5Sespie     else
381*c87b03e5Sespie       cheap_regs = call_used_regs;
382*c87b03e5Sespie     for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
383*c87b03e5Sespie       if (regs_ever_live[i] || cheap_regs[i])
384*c87b03e5Sespie 	SET_HARD_REG_BIT (regs_used_so_far, i);
385*c87b03e5Sespie   }
386*c87b03e5Sespie #else
387*c87b03e5Sespie   /* We consider registers that do not have to be saved over calls as if
388*c87b03e5Sespie      they were already used since there is no cost in using them.  */
389*c87b03e5Sespie   for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
390*c87b03e5Sespie     if (regs_ever_live[i] || call_used_regs[i])
391*c87b03e5Sespie       SET_HARD_REG_BIT (regs_used_so_far, i);
392*c87b03e5Sespie #endif
393*c87b03e5Sespie 
394*c87b03e5Sespie   for (i = FIRST_PSEUDO_REGISTER; i < (size_t) max_regno; i++)
395*c87b03e5Sespie     if (reg_renumber[i] >= 0)
396*c87b03e5Sespie       SET_HARD_REG_BIT (regs_used_so_far, reg_renumber[i]);
397*c87b03e5Sespie 
398*c87b03e5Sespie   /* Establish mappings from register number to allocation number
399*c87b03e5Sespie      and vice versa.  In the process, count the allocnos.  */
400*c87b03e5Sespie 
401*c87b03e5Sespie   reg_allocno = (int *) xmalloc (max_regno * sizeof (int));
402*c87b03e5Sespie 
403*c87b03e5Sespie   for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
404*c87b03e5Sespie     reg_allocno[i] = -1;
405*c87b03e5Sespie 
406*c87b03e5Sespie   /* Initialize the shared-hard-reg mapping
407*c87b03e5Sespie      from the list of pairs that may share.  */
408*c87b03e5Sespie   reg_may_share = (int *) xcalloc (max_regno, sizeof (int));
409*c87b03e5Sespie   for (x = regs_may_share; x; x = XEXP (XEXP (x, 1), 1))
410*c87b03e5Sespie     {
411*c87b03e5Sespie       int r1 = REGNO (XEXP (x, 0));
412*c87b03e5Sespie       int r2 = REGNO (XEXP (XEXP (x, 1), 0));
413*c87b03e5Sespie       if (r1 > r2)
414*c87b03e5Sespie 	reg_may_share[r1] = r2;
415*c87b03e5Sespie       else
416*c87b03e5Sespie 	reg_may_share[r2] = r1;
417*c87b03e5Sespie     }
418*c87b03e5Sespie 
419*c87b03e5Sespie   for (i = FIRST_PSEUDO_REGISTER; i < (size_t) max_regno; i++)
420*c87b03e5Sespie     /* Note that reg_live_length[i] < 0 indicates a "constant" reg
421*c87b03e5Sespie        that we are supposed to refrain from putting in a hard reg.
422*c87b03e5Sespie        -2 means do make an allocno but don't allocate it.  */
423*c87b03e5Sespie     if (REG_N_REFS (i) != 0 && REG_LIVE_LENGTH (i) != -1
424*c87b03e5Sespie 	/* Don't allocate pseudos that cross calls,
425*c87b03e5Sespie 	   if this function receives a nonlocal goto.  */
426*c87b03e5Sespie 	&& (! current_function_has_nonlocal_label
427*c87b03e5Sespie 	    || REG_N_CALLS_CROSSED (i) == 0))
428*c87b03e5Sespie       {
429*c87b03e5Sespie 	if (reg_renumber[i] < 0 && reg_may_share[i] && reg_allocno[reg_may_share[i]] >= 0)
430*c87b03e5Sespie 	  reg_allocno[i] = reg_allocno[reg_may_share[i]];
431*c87b03e5Sespie 	else
432*c87b03e5Sespie 	  reg_allocno[i] = max_allocno++;
433*c87b03e5Sespie 	if (REG_LIVE_LENGTH (i) == 0)
434*c87b03e5Sespie 	  abort ();
435*c87b03e5Sespie       }
436*c87b03e5Sespie     else
437*c87b03e5Sespie       reg_allocno[i] = -1;
438*c87b03e5Sespie 
439*c87b03e5Sespie   allocno = (struct allocno *) xcalloc (max_allocno, sizeof (struct allocno));
440*c87b03e5Sespie 
441*c87b03e5Sespie   for (i = FIRST_PSEUDO_REGISTER; i < (size_t) max_regno; i++)
442*c87b03e5Sespie     if (reg_allocno[i] >= 0)
443*c87b03e5Sespie       {
444*c87b03e5Sespie 	int num = reg_allocno[i];
445*c87b03e5Sespie 	allocno[num].reg = i;
446*c87b03e5Sespie 	allocno[num].size = PSEUDO_REGNO_SIZE (i);
447*c87b03e5Sespie 	allocno[num].calls_crossed += REG_N_CALLS_CROSSED (i);
448*c87b03e5Sespie 	allocno[num].n_refs += REG_N_REFS (i);
449*c87b03e5Sespie 	allocno[num].freq += REG_FREQ (i);
450*c87b03e5Sespie 	if (allocno[num].live_length < REG_LIVE_LENGTH (i))
451*c87b03e5Sespie 	  allocno[num].live_length = REG_LIVE_LENGTH (i);
452*c87b03e5Sespie       }
453*c87b03e5Sespie 
454*c87b03e5Sespie   /* Calculate amount of usage of each hard reg by pseudos
455*c87b03e5Sespie      allocated by local-alloc.  This is to see if we want to
456*c87b03e5Sespie      override it.  */
457*c87b03e5Sespie   memset ((char *) local_reg_live_length, 0, sizeof local_reg_live_length);
458*c87b03e5Sespie   memset ((char *) local_reg_n_refs, 0, sizeof local_reg_n_refs);
459*c87b03e5Sespie   memset ((char *) local_reg_freq, 0, sizeof local_reg_freq);
460*c87b03e5Sespie   for (i = FIRST_PSEUDO_REGISTER; i < (size_t) max_regno; i++)
461*c87b03e5Sespie     if (reg_renumber[i] >= 0)
462*c87b03e5Sespie       {
463*c87b03e5Sespie 	int regno = reg_renumber[i];
464*c87b03e5Sespie 	int endregno = regno + HARD_REGNO_NREGS (regno, PSEUDO_REGNO_MODE (i));
465*c87b03e5Sespie 	int j;
466*c87b03e5Sespie 
467*c87b03e5Sespie 	for (j = regno; j < endregno; j++)
468*c87b03e5Sespie 	  {
469*c87b03e5Sespie 	    local_reg_n_refs[j] += REG_N_REFS (i);
470*c87b03e5Sespie 	    local_reg_freq[j] += REG_FREQ (i);
471*c87b03e5Sespie 	    local_reg_live_length[j] += REG_LIVE_LENGTH (i);
472*c87b03e5Sespie 	  }
473*c87b03e5Sespie       }
474*c87b03e5Sespie 
475*c87b03e5Sespie   /* We can't override local-alloc for a reg used not just by local-alloc.  */
476*c87b03e5Sespie   for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
477*c87b03e5Sespie     if (regs_ever_live[i])
478*c87b03e5Sespie       local_reg_n_refs[i] = 0, local_reg_freq[i] = 0;
479*c87b03e5Sespie 
480*c87b03e5Sespie   allocno_row_words = (max_allocno + INT_BITS - 1) / INT_BITS;
481*c87b03e5Sespie 
482*c87b03e5Sespie   /* We used to use alloca here, but the size of what it would try to
483*c87b03e5Sespie      allocate would occasionally cause it to exceed the stack limit and
484*c87b03e5Sespie      cause unpredictable core dumps.  Some examples were > 2Mb in size.  */
485*c87b03e5Sespie   conflicts = (INT_TYPE *) xcalloc (max_allocno * allocno_row_words,
486*c87b03e5Sespie 				    sizeof (INT_TYPE));
487*c87b03e5Sespie 
488*c87b03e5Sespie   allocnos_live = (INT_TYPE *) xmalloc (allocno_row_words * sizeof (INT_TYPE));
489*c87b03e5Sespie 
490*c87b03e5Sespie   /* If there is work to be done (at least one reg to allocate),
491*c87b03e5Sespie      perform global conflict analysis and allocate the regs.  */
492*c87b03e5Sespie 
493*c87b03e5Sespie   if (max_allocno > 0)
494*c87b03e5Sespie     {
495*c87b03e5Sespie       /* Scan all the insns and compute the conflicts among allocnos
496*c87b03e5Sespie 	 and between allocnos and hard regs.  */
497*c87b03e5Sespie 
498*c87b03e5Sespie       global_conflicts ();
499*c87b03e5Sespie 
500*c87b03e5Sespie       mirror_conflicts ();
501*c87b03e5Sespie 
502*c87b03e5Sespie       /* Eliminate conflicts between pseudos and eliminable registers.  If
503*c87b03e5Sespie 	 the register is not eliminated, the pseudo won't really be able to
504*c87b03e5Sespie 	 live in the eliminable register, so the conflict doesn't matter.
505*c87b03e5Sespie 	 If we do eliminate the register, the conflict will no longer exist.
506*c87b03e5Sespie 	 So in either case, we can ignore the conflict.  Likewise for
507*c87b03e5Sespie 	 preferences.  */
508*c87b03e5Sespie 
509*c87b03e5Sespie       for (i = 0; i < (size_t) max_allocno; i++)
510*c87b03e5Sespie 	{
511*c87b03e5Sespie 	  AND_COMPL_HARD_REG_SET (allocno[i].hard_reg_conflicts,
512*c87b03e5Sespie 				  eliminable_regset);
513*c87b03e5Sespie 	  AND_COMPL_HARD_REG_SET (allocno[i].hard_reg_copy_preferences,
514*c87b03e5Sespie 				  eliminable_regset);
515*c87b03e5Sespie 	  AND_COMPL_HARD_REG_SET (allocno[i].hard_reg_preferences,
516*c87b03e5Sespie 				  eliminable_regset);
517*c87b03e5Sespie 	}
518*c87b03e5Sespie 
519*c87b03e5Sespie       /* Try to expand the preferences by merging them between allocnos.  */
520*c87b03e5Sespie 
521*c87b03e5Sespie       expand_preferences ();
522*c87b03e5Sespie 
523*c87b03e5Sespie       /* Determine the order to allocate the remaining pseudo registers.  */
524*c87b03e5Sespie 
525*c87b03e5Sespie       allocno_order = (int *) xmalloc (max_allocno * sizeof (int));
526*c87b03e5Sespie       for (i = 0; i < (size_t) max_allocno; i++)
527*c87b03e5Sespie 	allocno_order[i] = i;
528*c87b03e5Sespie 
529*c87b03e5Sespie       /* Default the size to 1, since allocno_compare uses it to divide by.
530*c87b03e5Sespie 	 Also convert allocno_live_length of zero to -1.  A length of zero
531*c87b03e5Sespie 	 can occur when all the registers for that allocno have reg_live_length
532*c87b03e5Sespie 	 equal to -2.  In this case, we want to make an allocno, but not
533*c87b03e5Sespie 	 allocate it.  So avoid the divide-by-zero and set it to a low
534*c87b03e5Sespie 	 priority.  */
535*c87b03e5Sespie 
536*c87b03e5Sespie       for (i = 0; i < (size_t) max_allocno; i++)
537*c87b03e5Sespie 	{
538*c87b03e5Sespie 	  if (allocno[i].size == 0)
539*c87b03e5Sespie 	    allocno[i].size = 1;
540*c87b03e5Sespie 	  if (allocno[i].live_length == 0)
541*c87b03e5Sespie 	    allocno[i].live_length = -1;
542*c87b03e5Sespie 	}
543*c87b03e5Sespie 
544*c87b03e5Sespie       qsort (allocno_order, max_allocno, sizeof (int), allocno_compare);
545*c87b03e5Sespie 
546*c87b03e5Sespie       prune_preferences ();
547*c87b03e5Sespie 
548*c87b03e5Sespie       if (file)
549*c87b03e5Sespie 	dump_conflicts (file);
550*c87b03e5Sespie 
551*c87b03e5Sespie       /* Try allocating them, one by one, in that order,
552*c87b03e5Sespie 	 except for parameters marked with reg_live_length[regno] == -2.  */
553*c87b03e5Sespie 
554*c87b03e5Sespie       for (i = 0; i < (size_t) max_allocno; i++)
555*c87b03e5Sespie 	if (reg_renumber[allocno[allocno_order[i]].reg] < 0
556*c87b03e5Sespie 	    && REG_LIVE_LENGTH (allocno[allocno_order[i]].reg) >= 0)
557*c87b03e5Sespie 	  {
558*c87b03e5Sespie 	    /* If we have more than one register class,
559*c87b03e5Sespie 	       first try allocating in the class that is cheapest
560*c87b03e5Sespie 	       for this pseudo-reg.  If that fails, try any reg.  */
561*c87b03e5Sespie 	    if (N_REG_CLASSES > 1)
562*c87b03e5Sespie 	      {
563*c87b03e5Sespie 		find_reg (allocno_order[i], 0, 0, 0, 0);
564*c87b03e5Sespie 		if (reg_renumber[allocno[allocno_order[i]].reg] >= 0)
565*c87b03e5Sespie 		  continue;
566*c87b03e5Sespie 	      }
567*c87b03e5Sespie 	    if (reg_alternate_class (allocno[allocno_order[i]].reg) != NO_REGS)
568*c87b03e5Sespie 	      find_reg (allocno_order[i], 0, 1, 0, 0);
569*c87b03e5Sespie 	  }
570*c87b03e5Sespie 
571*c87b03e5Sespie       free (allocno_order);
572*c87b03e5Sespie     }
573*c87b03e5Sespie 
574*c87b03e5Sespie   /* Do the reloads now while the allocno data still exist, so that we can
575*c87b03e5Sespie      try to assign new hard regs to any pseudo regs that are spilled.  */
576*c87b03e5Sespie 
577*c87b03e5Sespie #if 0 /* We need to eliminate regs even if there is no rtl code,
578*c87b03e5Sespie 	 for the sake of debugging information.  */
579*c87b03e5Sespie   if (n_basic_blocks > 0)
580*c87b03e5Sespie #endif
581*c87b03e5Sespie     {
582*c87b03e5Sespie       build_insn_chain (get_insns ());
583*c87b03e5Sespie       retval = reload (get_insns (), 1);
584*c87b03e5Sespie     }
585*c87b03e5Sespie 
586*c87b03e5Sespie   /* Clean up.  */
587*c87b03e5Sespie   free (reg_allocno);
588*c87b03e5Sespie   free (reg_may_share);
589*c87b03e5Sespie   free (allocno);
590*c87b03e5Sespie   free (conflicts);
591*c87b03e5Sespie   free (allocnos_live);
592*c87b03e5Sespie 
593*c87b03e5Sespie   return retval;
594*c87b03e5Sespie }
595*c87b03e5Sespie 
596*c87b03e5Sespie /* Sort predicate for ordering the allocnos.
597*c87b03e5Sespie    Returns -1 (1) if *v1 should be allocated before (after) *v2.  */
598*c87b03e5Sespie 
599*c87b03e5Sespie static int
allocno_compare(v1p,v2p)600*c87b03e5Sespie allocno_compare (v1p, v2p)
601*c87b03e5Sespie      const PTR v1p;
602*c87b03e5Sespie      const PTR v2p;
603*c87b03e5Sespie {
604*c87b03e5Sespie   int v1 = *(const int *)v1p, v2 = *(const int *)v2p;
605*c87b03e5Sespie   /* Note that the quotient will never be bigger than
606*c87b03e5Sespie      the value of floor_log2 times the maximum number of
607*c87b03e5Sespie      times a register can occur in one insn (surely less than 100)
608*c87b03e5Sespie      weighted by the frequency (maximally REG_FREQ_MAX).
609*c87b03e5Sespie      Multiplying this by 10000/REG_FREQ_MAX can't overflow.  */
610*c87b03e5Sespie   int pri1
611*c87b03e5Sespie     = (((double) (floor_log2 (allocno[v1].n_refs) * allocno[v1].freq)
612*c87b03e5Sespie 	/ allocno[v1].live_length)
613*c87b03e5Sespie        * (10000 / REG_FREQ_MAX) * allocno[v1].size);
614*c87b03e5Sespie   int pri2
615*c87b03e5Sespie     = (((double) (floor_log2 (allocno[v2].n_refs) * allocno[v2].freq)
616*c87b03e5Sespie 	/ allocno[v2].live_length)
617*c87b03e5Sespie        * (10000 / REG_FREQ_MAX) * allocno[v2].size);
618*c87b03e5Sespie   if (pri2 - pri1)
619*c87b03e5Sespie     return pri2 - pri1;
620*c87b03e5Sespie 
621*c87b03e5Sespie   /* If regs are equally good, sort by allocno,
622*c87b03e5Sespie      so that the results of qsort leave nothing to chance.  */
623*c87b03e5Sespie   return v1 - v2;
624*c87b03e5Sespie }
625*c87b03e5Sespie 
626*c87b03e5Sespie /* Scan the rtl code and record all conflicts and register preferences in the
627*c87b03e5Sespie    conflict matrices and preference tables.  */
628*c87b03e5Sespie 
629*c87b03e5Sespie static void
global_conflicts()630*c87b03e5Sespie global_conflicts ()
631*c87b03e5Sespie {
632*c87b03e5Sespie   int i;
633*c87b03e5Sespie   basic_block b;
634*c87b03e5Sespie   rtx insn;
635*c87b03e5Sespie   int *block_start_allocnos;
636*c87b03e5Sespie 
637*c87b03e5Sespie   /* Make a vector that mark_reg_{store,clobber} will store in.  */
638*c87b03e5Sespie   regs_set = (rtx *) xmalloc (max_parallel * sizeof (rtx) * 2);
639*c87b03e5Sespie 
640*c87b03e5Sespie   block_start_allocnos = (int *) xmalloc (max_allocno * sizeof (int));
641*c87b03e5Sespie 
642*c87b03e5Sespie   FOR_EACH_BB (b)
643*c87b03e5Sespie     {
644*c87b03e5Sespie       memset ((char *) allocnos_live, 0, allocno_row_words * sizeof (INT_TYPE));
645*c87b03e5Sespie 
646*c87b03e5Sespie       /* Initialize table of registers currently live
647*c87b03e5Sespie 	 to the state at the beginning of this basic block.
648*c87b03e5Sespie 	 This also marks the conflicts among hard registers
649*c87b03e5Sespie 	 and any allocnos that are live.
650*c87b03e5Sespie 
651*c87b03e5Sespie 	 For pseudo-regs, there is only one bit for each one
652*c87b03e5Sespie 	 no matter how many hard regs it occupies.
653*c87b03e5Sespie 	 This is ok; we know the size from PSEUDO_REGNO_SIZE.
654*c87b03e5Sespie 	 For explicit hard regs, we cannot know the size that way
655*c87b03e5Sespie 	 since one hard reg can be used with various sizes.
656*c87b03e5Sespie 	 Therefore, we must require that all the hard regs
657*c87b03e5Sespie 	 implicitly live as part of a multi-word hard reg
658*c87b03e5Sespie 	 are explicitly marked in basic_block_live_at_start.  */
659*c87b03e5Sespie 
660*c87b03e5Sespie       {
661*c87b03e5Sespie 	regset old = b->global_live_at_start;
662*c87b03e5Sespie 	int ax = 0;
663*c87b03e5Sespie 
664*c87b03e5Sespie 	REG_SET_TO_HARD_REG_SET (hard_regs_live, old);
665*c87b03e5Sespie 	EXECUTE_IF_SET_IN_REG_SET (old, FIRST_PSEUDO_REGISTER, i,
666*c87b03e5Sespie 				   {
667*c87b03e5Sespie 				     int a = reg_allocno[i];
668*c87b03e5Sespie 				     if (a >= 0)
669*c87b03e5Sespie 				       {
670*c87b03e5Sespie 					 SET_ALLOCNO_LIVE (a);
671*c87b03e5Sespie 					 block_start_allocnos[ax++] = a;
672*c87b03e5Sespie 				       }
673*c87b03e5Sespie 				     else if ((a = reg_renumber[i]) >= 0)
674*c87b03e5Sespie 				       mark_reg_live_nc
675*c87b03e5Sespie 					 (a, PSEUDO_REGNO_MODE (i));
676*c87b03e5Sespie 				   });
677*c87b03e5Sespie 
678*c87b03e5Sespie 	/* Record that each allocno now live conflicts with each hard reg
679*c87b03e5Sespie 	   now live.
680*c87b03e5Sespie 
681*c87b03e5Sespie 	   It is not necessary to mark any conflicts between pseudos as
682*c87b03e5Sespie 	   this point, even for pseudos which are live at the start of
683*c87b03e5Sespie 	   the basic block.
684*c87b03e5Sespie 
685*c87b03e5Sespie 	     Given two pseudos X and Y and any point in the CFG P.
686*c87b03e5Sespie 
687*c87b03e5Sespie 	     On any path to point P where X and Y are live one of the
688*c87b03e5Sespie 	     following conditions must be true:
689*c87b03e5Sespie 
690*c87b03e5Sespie 		1. X is live at some instruction on the path that
691*c87b03e5Sespie 		   evaluates Y.
692*c87b03e5Sespie 
693*c87b03e5Sespie 		2. Y is live at some instruction on the path that
694*c87b03e5Sespie 		   evaluates X.
695*c87b03e5Sespie 
696*c87b03e5Sespie 		3. Either X or Y is not evaluted on the path to P
697*c87b03e5Sespie 		   (ie it is used uninitialized) and thus the
698*c87b03e5Sespie 		   conflict can be ignored.
699*c87b03e5Sespie 
700*c87b03e5Sespie 	    In cases #1 and #2 the conflict will be recorded when we
701*c87b03e5Sespie 	    scan the instruction that makes either X or Y become live.  */
702*c87b03e5Sespie 	record_conflicts (block_start_allocnos, ax);
703*c87b03e5Sespie 
704*c87b03e5Sespie #ifdef STACK_REGS
705*c87b03e5Sespie 	{
706*c87b03e5Sespie 	  /* Pseudos can't go in stack regs at the start of a basic block
707*c87b03e5Sespie 	     that is reached by an abnormal edge.  */
708*c87b03e5Sespie 
709*c87b03e5Sespie 	  edge e;
710*c87b03e5Sespie 	  for (e = b->pred; e ; e = e->pred_next)
711*c87b03e5Sespie 	    if (e->flags & EDGE_ABNORMAL)
712*c87b03e5Sespie 	      break;
713*c87b03e5Sespie 	  if (e != NULL)
714*c87b03e5Sespie 	    {
715*c87b03e5Sespie 	      EXECUTE_IF_SET_IN_ALLOCNO_SET (allocnos_live, ax,
716*c87b03e5Sespie 		{
717*c87b03e5Sespie 		  allocno[ax].no_stack_reg = 1;
718*c87b03e5Sespie 		});
719*c87b03e5Sespie 	      for (ax = FIRST_STACK_REG; ax <= LAST_STACK_REG; ax++)
720*c87b03e5Sespie 	        record_one_conflict (ax);
721*c87b03e5Sespie 	    }
722*c87b03e5Sespie 	}
723*c87b03e5Sespie #endif
724*c87b03e5Sespie       }
725*c87b03e5Sespie 
726*c87b03e5Sespie       insn = b->head;
727*c87b03e5Sespie 
728*c87b03e5Sespie       /* Scan the code of this basic block, noting which allocnos
729*c87b03e5Sespie 	 and hard regs are born or die.  When one is born,
730*c87b03e5Sespie 	 record a conflict with all others currently live.  */
731*c87b03e5Sespie 
732*c87b03e5Sespie       while (1)
733*c87b03e5Sespie 	{
734*c87b03e5Sespie 	  RTX_CODE code = GET_CODE (insn);
735*c87b03e5Sespie 	  rtx link;
736*c87b03e5Sespie 
737*c87b03e5Sespie 	  /* Make regs_set an empty set.  */
738*c87b03e5Sespie 
739*c87b03e5Sespie 	  n_regs_set = 0;
740*c87b03e5Sespie 
741*c87b03e5Sespie 	  if (code == INSN || code == CALL_INSN || code == JUMP_INSN)
742*c87b03e5Sespie 	    {
743*c87b03e5Sespie 
744*c87b03e5Sespie #if 0
745*c87b03e5Sespie 	      int i = 0;
746*c87b03e5Sespie 	      for (link = REG_NOTES (insn);
747*c87b03e5Sespie 		   link && i < NUM_NO_CONFLICT_PAIRS;
748*c87b03e5Sespie 		   link = XEXP (link, 1))
749*c87b03e5Sespie 		if (REG_NOTE_KIND (link) == REG_NO_CONFLICT)
750*c87b03e5Sespie 		  {
751*c87b03e5Sespie 		    no_conflict_pairs[i].allocno1
752*c87b03e5Sespie 		      = reg_allocno[REGNO (SET_DEST (PATTERN (insn)))];
753*c87b03e5Sespie 		    no_conflict_pairs[i].allocno2
754*c87b03e5Sespie 		      = reg_allocno[REGNO (XEXP (link, 0))];
755*c87b03e5Sespie 		    i++;
756*c87b03e5Sespie 		  }
757*c87b03e5Sespie #endif /* 0 */
758*c87b03e5Sespie 
759*c87b03e5Sespie 	      /* Mark any registers clobbered by INSN as live,
760*c87b03e5Sespie 		 so they conflict with the inputs.  */
761*c87b03e5Sespie 
762*c87b03e5Sespie 	      note_stores (PATTERN (insn), mark_reg_clobber, NULL);
763*c87b03e5Sespie 
764*c87b03e5Sespie 	      /* Mark any registers dead after INSN as dead now.  */
765*c87b03e5Sespie 
766*c87b03e5Sespie 	      for (link = REG_NOTES (insn); link; link = XEXP (link, 1))
767*c87b03e5Sespie 		if (REG_NOTE_KIND (link) == REG_DEAD)
768*c87b03e5Sespie 		  mark_reg_death (XEXP (link, 0));
769*c87b03e5Sespie 
770*c87b03e5Sespie 	      /* Mark any registers set in INSN as live,
771*c87b03e5Sespie 		 and mark them as conflicting with all other live regs.
772*c87b03e5Sespie 		 Clobbers are processed again, so they conflict with
773*c87b03e5Sespie 		 the registers that are set.  */
774*c87b03e5Sespie 
775*c87b03e5Sespie 	      note_stores (PATTERN (insn), mark_reg_store, NULL);
776*c87b03e5Sespie 
777*c87b03e5Sespie #ifdef AUTO_INC_DEC
778*c87b03e5Sespie 	      for (link = REG_NOTES (insn); link; link = XEXP (link, 1))
779*c87b03e5Sespie 		if (REG_NOTE_KIND (link) == REG_INC)
780*c87b03e5Sespie 		  mark_reg_store (XEXP (link, 0), NULL_RTX, NULL);
781*c87b03e5Sespie #endif
782*c87b03e5Sespie 
783*c87b03e5Sespie 	      /* If INSN has multiple outputs, then any reg that dies here
784*c87b03e5Sespie 		 and is used inside of an output
785*c87b03e5Sespie 		 must conflict with the other outputs.
786*c87b03e5Sespie 
787*c87b03e5Sespie 		 It is unsafe to use !single_set here since it will ignore an
788*c87b03e5Sespie 		 unused output.  Just because an output is unused does not mean
789*c87b03e5Sespie 		 the compiler can assume the side effect will not occur.
790*c87b03e5Sespie 		 Consider if REG appears in the address of an output and we
791*c87b03e5Sespie 		 reload the output.  If we allocate REG to the same hard
792*c87b03e5Sespie 		 register as an unused output we could set the hard register
793*c87b03e5Sespie 		 before the output reload insn.  */
794*c87b03e5Sespie 	      if (GET_CODE (PATTERN (insn)) == PARALLEL && multiple_sets (insn))
795*c87b03e5Sespie 		for (link = REG_NOTES (insn); link; link = XEXP (link, 1))
796*c87b03e5Sespie 		  if (REG_NOTE_KIND (link) == REG_DEAD)
797*c87b03e5Sespie 		    {
798*c87b03e5Sespie 		      int used_in_output = 0;
799*c87b03e5Sespie 		      int i;
800*c87b03e5Sespie 		      rtx reg = XEXP (link, 0);
801*c87b03e5Sespie 
802*c87b03e5Sespie 		      for (i = XVECLEN (PATTERN (insn), 0) - 1; i >= 0; i--)
803*c87b03e5Sespie 			{
804*c87b03e5Sespie 			  rtx set = XVECEXP (PATTERN (insn), 0, i);
805*c87b03e5Sespie 			  if (GET_CODE (set) == SET
806*c87b03e5Sespie 			      && GET_CODE (SET_DEST (set)) != REG
807*c87b03e5Sespie 			      && !rtx_equal_p (reg, SET_DEST (set))
808*c87b03e5Sespie 			      && reg_overlap_mentioned_p (reg, SET_DEST (set)))
809*c87b03e5Sespie 			    used_in_output = 1;
810*c87b03e5Sespie 			}
811*c87b03e5Sespie 		      if (used_in_output)
812*c87b03e5Sespie 			mark_reg_conflicts (reg);
813*c87b03e5Sespie 		    }
814*c87b03e5Sespie 
815*c87b03e5Sespie 	      /* Mark any registers set in INSN and then never used.  */
816*c87b03e5Sespie 
817*c87b03e5Sespie 	      while (n_regs_set-- > 0)
818*c87b03e5Sespie 		{
819*c87b03e5Sespie 		  rtx note = find_regno_note (insn, REG_UNUSED,
820*c87b03e5Sespie 					      REGNO (regs_set[n_regs_set]));
821*c87b03e5Sespie 		  if (note)
822*c87b03e5Sespie 		    mark_reg_death (XEXP (note, 0));
823*c87b03e5Sespie 		}
824*c87b03e5Sespie 	    }
825*c87b03e5Sespie 
826*c87b03e5Sespie 	  if (insn == b->end)
827*c87b03e5Sespie 	    break;
828*c87b03e5Sespie 	  insn = NEXT_INSN (insn);
829*c87b03e5Sespie 	}
830*c87b03e5Sespie     }
831*c87b03e5Sespie 
832*c87b03e5Sespie   /* Clean up.  */
833*c87b03e5Sespie   free (block_start_allocnos);
834*c87b03e5Sespie   free (regs_set);
835*c87b03e5Sespie }
836*c87b03e5Sespie /* Expand the preference information by looking for cases where one allocno
837*c87b03e5Sespie    dies in an insn that sets an allocno.  If those two allocnos don't conflict,
838*c87b03e5Sespie    merge any preferences between those allocnos.  */
839*c87b03e5Sespie 
840*c87b03e5Sespie static void
expand_preferences()841*c87b03e5Sespie expand_preferences ()
842*c87b03e5Sespie {
843*c87b03e5Sespie   rtx insn;
844*c87b03e5Sespie   rtx link;
845*c87b03e5Sespie   rtx set;
846*c87b03e5Sespie 
847*c87b03e5Sespie   /* We only try to handle the most common cases here.  Most of the cases
848*c87b03e5Sespie      where this wins are reg-reg copies.  */
849*c87b03e5Sespie 
850*c87b03e5Sespie   for (insn = get_insns (); insn; insn = NEXT_INSN (insn))
851*c87b03e5Sespie     if (INSN_P (insn)
852*c87b03e5Sespie 	&& (set = single_set (insn)) != 0
853*c87b03e5Sespie 	&& GET_CODE (SET_DEST (set)) == REG
854*c87b03e5Sespie 	&& reg_allocno[REGNO (SET_DEST (set))] >= 0)
855*c87b03e5Sespie       for (link = REG_NOTES (insn); link; link = XEXP (link, 1))
856*c87b03e5Sespie 	if (REG_NOTE_KIND (link) == REG_DEAD
857*c87b03e5Sespie 	    && GET_CODE (XEXP (link, 0)) == REG
858*c87b03e5Sespie 	    && reg_allocno[REGNO (XEXP (link, 0))] >= 0
859*c87b03e5Sespie 	    && ! CONFLICTP (reg_allocno[REGNO (SET_DEST (set))],
860*c87b03e5Sespie 			    reg_allocno[REGNO (XEXP (link, 0))]))
861*c87b03e5Sespie 	  {
862*c87b03e5Sespie 	    int a1 = reg_allocno[REGNO (SET_DEST (set))];
863*c87b03e5Sespie 	    int a2 = reg_allocno[REGNO (XEXP (link, 0))];
864*c87b03e5Sespie 
865*c87b03e5Sespie 	    if (XEXP (link, 0) == SET_SRC (set))
866*c87b03e5Sespie 	      {
867*c87b03e5Sespie 		IOR_HARD_REG_SET (allocno[a1].hard_reg_copy_preferences,
868*c87b03e5Sespie 				  allocno[a2].hard_reg_copy_preferences);
869*c87b03e5Sespie 		IOR_HARD_REG_SET (allocno[a2].hard_reg_copy_preferences,
870*c87b03e5Sespie 				  allocno[a1].hard_reg_copy_preferences);
871*c87b03e5Sespie 	      }
872*c87b03e5Sespie 
873*c87b03e5Sespie 	    IOR_HARD_REG_SET (allocno[a1].hard_reg_preferences,
874*c87b03e5Sespie 			      allocno[a2].hard_reg_preferences);
875*c87b03e5Sespie 	    IOR_HARD_REG_SET (allocno[a2].hard_reg_preferences,
876*c87b03e5Sespie 			      allocno[a1].hard_reg_preferences);
877*c87b03e5Sespie 	    IOR_HARD_REG_SET (allocno[a1].hard_reg_full_preferences,
878*c87b03e5Sespie 			      allocno[a2].hard_reg_full_preferences);
879*c87b03e5Sespie 	    IOR_HARD_REG_SET (allocno[a2].hard_reg_full_preferences,
880*c87b03e5Sespie 			      allocno[a1].hard_reg_full_preferences);
881*c87b03e5Sespie 	  }
882*c87b03e5Sespie }
883*c87b03e5Sespie 
884*c87b03e5Sespie /* Prune the preferences for global registers to exclude registers that cannot
885*c87b03e5Sespie    be used.
886*c87b03e5Sespie 
887*c87b03e5Sespie    Compute `regs_someone_prefers', which is a bitmask of the hard registers
888*c87b03e5Sespie    that are preferred by conflicting registers of lower priority.  If possible,
889*c87b03e5Sespie    we will avoid using these registers.  */
890*c87b03e5Sespie 
891*c87b03e5Sespie static void
prune_preferences()892*c87b03e5Sespie prune_preferences ()
893*c87b03e5Sespie {
894*c87b03e5Sespie   int i;
895*c87b03e5Sespie   int num;
896*c87b03e5Sespie   int *allocno_to_order = (int *) xmalloc (max_allocno * sizeof (int));
897*c87b03e5Sespie 
898*c87b03e5Sespie   /* Scan least most important to most important.
899*c87b03e5Sespie      For each allocno, remove from preferences registers that cannot be used,
900*c87b03e5Sespie      either because of conflicts or register type.  Then compute all registers
901*c87b03e5Sespie      preferred by each lower-priority register that conflicts.  */
902*c87b03e5Sespie 
903*c87b03e5Sespie   for (i = max_allocno - 1; i >= 0; i--)
904*c87b03e5Sespie     {
905*c87b03e5Sespie       HARD_REG_SET temp;
906*c87b03e5Sespie 
907*c87b03e5Sespie       num = allocno_order[i];
908*c87b03e5Sespie       allocno_to_order[num] = i;
909*c87b03e5Sespie       COPY_HARD_REG_SET (temp, allocno[num].hard_reg_conflicts);
910*c87b03e5Sespie 
911*c87b03e5Sespie       if (allocno[num].calls_crossed == 0)
912*c87b03e5Sespie 	IOR_HARD_REG_SET (temp, fixed_reg_set);
913*c87b03e5Sespie       else
914*c87b03e5Sespie 	IOR_HARD_REG_SET (temp,	call_used_reg_set);
915*c87b03e5Sespie 
916*c87b03e5Sespie       IOR_COMPL_HARD_REG_SET
917*c87b03e5Sespie 	(temp,
918*c87b03e5Sespie 	 reg_class_contents[(int) reg_preferred_class (allocno[num].reg)]);
919*c87b03e5Sespie 
920*c87b03e5Sespie       AND_COMPL_HARD_REG_SET (allocno[num].hard_reg_preferences, temp);
921*c87b03e5Sespie       AND_COMPL_HARD_REG_SET (allocno[num].hard_reg_copy_preferences, temp);
922*c87b03e5Sespie       AND_COMPL_HARD_REG_SET (allocno[num].hard_reg_full_preferences, temp);
923*c87b03e5Sespie     }
924*c87b03e5Sespie 
925*c87b03e5Sespie   for (i = max_allocno - 1; i >= 0; i--)
926*c87b03e5Sespie     {
927*c87b03e5Sespie       /* Merge in the preferences of lower-priority registers (they have
928*c87b03e5Sespie 	 already been pruned).  If we also prefer some of those registers,
929*c87b03e5Sespie 	 don't exclude them unless we are of a smaller size (in which case
930*c87b03e5Sespie 	 we want to give the lower-priority allocno the first chance for
931*c87b03e5Sespie 	 these registers).  */
932*c87b03e5Sespie       HARD_REG_SET temp, temp2;
933*c87b03e5Sespie       int allocno2;
934*c87b03e5Sespie 
935*c87b03e5Sespie       num = allocno_order[i];
936*c87b03e5Sespie 
937*c87b03e5Sespie       CLEAR_HARD_REG_SET (temp);
938*c87b03e5Sespie       CLEAR_HARD_REG_SET (temp2);
939*c87b03e5Sespie 
940*c87b03e5Sespie       EXECUTE_IF_SET_IN_ALLOCNO_SET (conflicts + num * allocno_row_words,
941*c87b03e5Sespie 				     allocno2,
942*c87b03e5Sespie 	{
943*c87b03e5Sespie 	  if (allocno_to_order[allocno2] > i)
944*c87b03e5Sespie 	    {
945*c87b03e5Sespie 	      if (allocno[allocno2].size <= allocno[num].size)
946*c87b03e5Sespie 		IOR_HARD_REG_SET (temp,
947*c87b03e5Sespie 				  allocno[allocno2].hard_reg_full_preferences);
948*c87b03e5Sespie 	      else
949*c87b03e5Sespie 		IOR_HARD_REG_SET (temp2,
950*c87b03e5Sespie 				  allocno[allocno2].hard_reg_full_preferences);
951*c87b03e5Sespie 	    }
952*c87b03e5Sespie 	});
953*c87b03e5Sespie 
954*c87b03e5Sespie       AND_COMPL_HARD_REG_SET (temp, allocno[num].hard_reg_full_preferences);
955*c87b03e5Sespie       IOR_HARD_REG_SET (temp, temp2);
956*c87b03e5Sespie       COPY_HARD_REG_SET (allocno[num].regs_someone_prefers, temp);
957*c87b03e5Sespie     }
958*c87b03e5Sespie   free (allocno_to_order);
959*c87b03e5Sespie }
960*c87b03e5Sespie 
961*c87b03e5Sespie /* Assign a hard register to allocno NUM; look for one that is the beginning
962*c87b03e5Sespie    of a long enough stretch of hard regs none of which conflicts with ALLOCNO.
963*c87b03e5Sespie    The registers marked in PREFREGS are tried first.
964*c87b03e5Sespie 
965*c87b03e5Sespie    LOSERS, if nonzero, is a HARD_REG_SET indicating registers that cannot
966*c87b03e5Sespie    be used for this allocation.
967*c87b03e5Sespie 
968*c87b03e5Sespie    If ALT_REGS_P is zero, consider only the preferred class of ALLOCNO's reg.
969*c87b03e5Sespie    Otherwise ignore that preferred class and use the alternate class.
970*c87b03e5Sespie 
971*c87b03e5Sespie    If ACCEPT_CALL_CLOBBERED is nonzero, accept a call-clobbered hard reg that
972*c87b03e5Sespie    will have to be saved and restored at calls.
973*c87b03e5Sespie 
974*c87b03e5Sespie    RETRYING is nonzero if this is called from retry_global_alloc.
975*c87b03e5Sespie 
976*c87b03e5Sespie    If we find one, record it in reg_renumber.
977*c87b03e5Sespie    If not, do nothing.  */
978*c87b03e5Sespie 
979*c87b03e5Sespie static void
find_reg(num,losers,alt_regs_p,accept_call_clobbered,retrying)980*c87b03e5Sespie find_reg (num, losers, alt_regs_p, accept_call_clobbered, retrying)
981*c87b03e5Sespie      int num;
982*c87b03e5Sespie      HARD_REG_SET losers;
983*c87b03e5Sespie      int alt_regs_p;
984*c87b03e5Sespie      int accept_call_clobbered;
985*c87b03e5Sespie      int retrying;
986*c87b03e5Sespie {
987*c87b03e5Sespie   int i, best_reg, pass;
988*c87b03e5Sespie   HARD_REG_SET used, used1, used2;
989*c87b03e5Sespie 
990*c87b03e5Sespie   enum reg_class class = (alt_regs_p
991*c87b03e5Sespie 			  ? reg_alternate_class (allocno[num].reg)
992*c87b03e5Sespie 			  : reg_preferred_class (allocno[num].reg));
993*c87b03e5Sespie   enum machine_mode mode = PSEUDO_REGNO_MODE (allocno[num].reg);
994*c87b03e5Sespie 
995*c87b03e5Sespie   if (accept_call_clobbered)
996*c87b03e5Sespie     COPY_HARD_REG_SET (used1, call_fixed_reg_set);
997*c87b03e5Sespie   else if (allocno[num].calls_crossed == 0)
998*c87b03e5Sespie     COPY_HARD_REG_SET (used1, fixed_reg_set);
999*c87b03e5Sespie   else
1000*c87b03e5Sespie     COPY_HARD_REG_SET (used1, call_used_reg_set);
1001*c87b03e5Sespie 
1002*c87b03e5Sespie   /* Some registers should not be allocated in global-alloc.  */
1003*c87b03e5Sespie   IOR_HARD_REG_SET (used1, no_global_alloc_regs);
1004*c87b03e5Sespie   if (losers)
1005*c87b03e5Sespie     IOR_HARD_REG_SET (used1, losers);
1006*c87b03e5Sespie 
1007*c87b03e5Sespie   IOR_COMPL_HARD_REG_SET (used1, reg_class_contents[(int) class]);
1008*c87b03e5Sespie   COPY_HARD_REG_SET (used2, used1);
1009*c87b03e5Sespie 
1010*c87b03e5Sespie   IOR_HARD_REG_SET (used1, allocno[num].hard_reg_conflicts);
1011*c87b03e5Sespie 
1012*c87b03e5Sespie #ifdef CANNOT_CHANGE_MODE_CLASS
1013*c87b03e5Sespie   cannot_change_mode_set_regs (&used1, mode, allocno[num].reg);
1014*c87b03e5Sespie #endif
1015*c87b03e5Sespie 
1016*c87b03e5Sespie   /* Try each hard reg to see if it fits.  Do this in two passes.
1017*c87b03e5Sespie      In the first pass, skip registers that are preferred by some other pseudo
1018*c87b03e5Sespie      to give it a better chance of getting one of those registers.  Only if
1019*c87b03e5Sespie      we can't get a register when excluding those do we take one of them.
1020*c87b03e5Sespie      However, we never allocate a register for the first time in pass 0.  */
1021*c87b03e5Sespie 
1022*c87b03e5Sespie   COPY_HARD_REG_SET (used, used1);
1023*c87b03e5Sespie   IOR_COMPL_HARD_REG_SET (used, regs_used_so_far);
1024*c87b03e5Sespie   IOR_HARD_REG_SET (used, allocno[num].regs_someone_prefers);
1025*c87b03e5Sespie 
1026*c87b03e5Sespie   best_reg = -1;
1027*c87b03e5Sespie   for (i = FIRST_PSEUDO_REGISTER, pass = 0;
1028*c87b03e5Sespie        pass <= 1 && i >= FIRST_PSEUDO_REGISTER;
1029*c87b03e5Sespie        pass++)
1030*c87b03e5Sespie     {
1031*c87b03e5Sespie       if (pass == 1)
1032*c87b03e5Sespie 	COPY_HARD_REG_SET (used, used1);
1033*c87b03e5Sespie       for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
1034*c87b03e5Sespie 	{
1035*c87b03e5Sespie #ifdef REG_ALLOC_ORDER
1036*c87b03e5Sespie 	  int regno = reg_alloc_order[i];
1037*c87b03e5Sespie #else
1038*c87b03e5Sespie 	  int regno = i;
1039*c87b03e5Sespie #endif
1040*c87b03e5Sespie 	  if (! TEST_HARD_REG_BIT (used, regno)
1041*c87b03e5Sespie 	      && HARD_REGNO_MODE_OK (regno, mode)
1042*c87b03e5Sespie 	      && (allocno[num].calls_crossed == 0
1043*c87b03e5Sespie 		  || accept_call_clobbered
1044*c87b03e5Sespie 		  || ! HARD_REGNO_CALL_PART_CLOBBERED (regno, mode)))
1045*c87b03e5Sespie 	    {
1046*c87b03e5Sespie 	      int j;
1047*c87b03e5Sespie 	      int lim = regno + HARD_REGNO_NREGS (regno, mode);
1048*c87b03e5Sespie 	      for (j = regno + 1;
1049*c87b03e5Sespie 		   (j < lim
1050*c87b03e5Sespie 		    && ! TEST_HARD_REG_BIT (used, j));
1051*c87b03e5Sespie 		   j++);
1052*c87b03e5Sespie 	      if (j == lim)
1053*c87b03e5Sespie 		{
1054*c87b03e5Sespie 		  best_reg = regno;
1055*c87b03e5Sespie 		  break;
1056*c87b03e5Sespie 		}
1057*c87b03e5Sespie #ifndef REG_ALLOC_ORDER
1058*c87b03e5Sespie 	      i = j;			/* Skip starting points we know will lose */
1059*c87b03e5Sespie #endif
1060*c87b03e5Sespie 	    }
1061*c87b03e5Sespie 	  }
1062*c87b03e5Sespie       }
1063*c87b03e5Sespie 
1064*c87b03e5Sespie   /* See if there is a preferred register with the same class as the register
1065*c87b03e5Sespie      we allocated above.  Making this restriction prevents register
1066*c87b03e5Sespie      preferencing from creating worse register allocation.
1067*c87b03e5Sespie 
1068*c87b03e5Sespie      Remove from the preferred registers and conflicting registers.  Note that
1069*c87b03e5Sespie      additional conflicts may have been added after `prune_preferences' was
1070*c87b03e5Sespie      called.
1071*c87b03e5Sespie 
1072*c87b03e5Sespie      First do this for those register with copy preferences, then all
1073*c87b03e5Sespie      preferred registers.  */
1074*c87b03e5Sespie 
1075*c87b03e5Sespie   AND_COMPL_HARD_REG_SET (allocno[num].hard_reg_copy_preferences, used);
1076*c87b03e5Sespie   GO_IF_HARD_REG_SUBSET (allocno[num].hard_reg_copy_preferences,
1077*c87b03e5Sespie 			 reg_class_contents[(int) NO_REGS], no_copy_prefs);
1078*c87b03e5Sespie 
1079*c87b03e5Sespie   if (best_reg >= 0)
1080*c87b03e5Sespie     {
1081*c87b03e5Sespie       for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
1082*c87b03e5Sespie 	if (TEST_HARD_REG_BIT (allocno[num].hard_reg_copy_preferences, i)
1083*c87b03e5Sespie 	    && HARD_REGNO_MODE_OK (i, mode)
1084*c87b03e5Sespie 	    && (allocno[num].calls_crossed == 0
1085*c87b03e5Sespie 		|| accept_call_clobbered
1086*c87b03e5Sespie 		|| ! HARD_REGNO_CALL_PART_CLOBBERED (i, mode))
1087*c87b03e5Sespie 	    && (REGNO_REG_CLASS (i) == REGNO_REG_CLASS (best_reg)
1088*c87b03e5Sespie 		|| reg_class_subset_p (REGNO_REG_CLASS (i),
1089*c87b03e5Sespie 				       REGNO_REG_CLASS (best_reg))
1090*c87b03e5Sespie 		|| reg_class_subset_p (REGNO_REG_CLASS (best_reg),
1091*c87b03e5Sespie 				       REGNO_REG_CLASS (i))))
1092*c87b03e5Sespie 	    {
1093*c87b03e5Sespie 	      int j;
1094*c87b03e5Sespie 	      int lim = i + HARD_REGNO_NREGS (i, mode);
1095*c87b03e5Sespie 	      for (j = i + 1;
1096*c87b03e5Sespie 		   (j < lim
1097*c87b03e5Sespie 		    && ! TEST_HARD_REG_BIT (used, j)
1098*c87b03e5Sespie 		    && (REGNO_REG_CLASS (j)
1099*c87b03e5Sespie 		    	== REGNO_REG_CLASS (best_reg + (j - i))
1100*c87b03e5Sespie 			|| reg_class_subset_p (REGNO_REG_CLASS (j),
1101*c87b03e5Sespie 					       REGNO_REG_CLASS (best_reg + (j - i)))
1102*c87b03e5Sespie 			|| reg_class_subset_p (REGNO_REG_CLASS (best_reg + (j - i)),
1103*c87b03e5Sespie 					       REGNO_REG_CLASS (j))));
1104*c87b03e5Sespie 		   j++);
1105*c87b03e5Sespie 	      if (j == lim)
1106*c87b03e5Sespie 		{
1107*c87b03e5Sespie 		  best_reg = i;
1108*c87b03e5Sespie 		  goto no_prefs;
1109*c87b03e5Sespie 		}
1110*c87b03e5Sespie 	    }
1111*c87b03e5Sespie     }
1112*c87b03e5Sespie  no_copy_prefs:
1113*c87b03e5Sespie 
1114*c87b03e5Sespie   AND_COMPL_HARD_REG_SET (allocno[num].hard_reg_preferences, used);
1115*c87b03e5Sespie   GO_IF_HARD_REG_SUBSET (allocno[num].hard_reg_preferences,
1116*c87b03e5Sespie 			 reg_class_contents[(int) NO_REGS], no_prefs);
1117*c87b03e5Sespie 
1118*c87b03e5Sespie   if (best_reg >= 0)
1119*c87b03e5Sespie     {
1120*c87b03e5Sespie       for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
1121*c87b03e5Sespie 	if (TEST_HARD_REG_BIT (allocno[num].hard_reg_preferences, i)
1122*c87b03e5Sespie 	    && HARD_REGNO_MODE_OK (i, mode)
1123*c87b03e5Sespie 	    && (allocno[num].calls_crossed == 0
1124*c87b03e5Sespie 		|| accept_call_clobbered
1125*c87b03e5Sespie 		|| ! HARD_REGNO_CALL_PART_CLOBBERED (i, mode))
1126*c87b03e5Sespie 	    && (REGNO_REG_CLASS (i) == REGNO_REG_CLASS (best_reg)
1127*c87b03e5Sespie 		|| reg_class_subset_p (REGNO_REG_CLASS (i),
1128*c87b03e5Sespie 				       REGNO_REG_CLASS (best_reg))
1129*c87b03e5Sespie 		|| reg_class_subset_p (REGNO_REG_CLASS (best_reg),
1130*c87b03e5Sespie 				       REGNO_REG_CLASS (i))))
1131*c87b03e5Sespie 	    {
1132*c87b03e5Sespie 	      int j;
1133*c87b03e5Sespie 	      int lim = i + HARD_REGNO_NREGS (i, mode);
1134*c87b03e5Sespie 	      for (j = i + 1;
1135*c87b03e5Sespie 		   (j < lim
1136*c87b03e5Sespie 		    && ! TEST_HARD_REG_BIT (used, j)
1137*c87b03e5Sespie 		    && (REGNO_REG_CLASS (j)
1138*c87b03e5Sespie 		    	== REGNO_REG_CLASS (best_reg + (j - i))
1139*c87b03e5Sespie 			|| reg_class_subset_p (REGNO_REG_CLASS (j),
1140*c87b03e5Sespie 					       REGNO_REG_CLASS (best_reg + (j - i)))
1141*c87b03e5Sespie 			|| reg_class_subset_p (REGNO_REG_CLASS (best_reg + (j - i)),
1142*c87b03e5Sespie 					       REGNO_REG_CLASS (j))));
1143*c87b03e5Sespie 		   j++);
1144*c87b03e5Sespie 	      if (j == lim)
1145*c87b03e5Sespie 		{
1146*c87b03e5Sespie 		  best_reg = i;
1147*c87b03e5Sespie 		  break;
1148*c87b03e5Sespie 		}
1149*c87b03e5Sespie 	    }
1150*c87b03e5Sespie     }
1151*c87b03e5Sespie  no_prefs:
1152*c87b03e5Sespie 
1153*c87b03e5Sespie   /* If we haven't succeeded yet, try with caller-saves.
1154*c87b03e5Sespie      We need not check to see if the current function has nonlocal
1155*c87b03e5Sespie      labels because we don't put any pseudos that are live over calls in
1156*c87b03e5Sespie      registers in that case.  */
1157*c87b03e5Sespie 
1158*c87b03e5Sespie   if (flag_caller_saves && best_reg < 0)
1159*c87b03e5Sespie     {
1160*c87b03e5Sespie       /* Did not find a register.  If it would be profitable to
1161*c87b03e5Sespie 	 allocate a call-clobbered register and save and restore it
1162*c87b03e5Sespie 	 around calls, do that.  */
1163*c87b03e5Sespie       if (! accept_call_clobbered
1164*c87b03e5Sespie 	  && allocno[num].calls_crossed != 0
1165*c87b03e5Sespie 	  && CALLER_SAVE_PROFITABLE (allocno[num].n_refs,
1166*c87b03e5Sespie 				     allocno[num].calls_crossed))
1167*c87b03e5Sespie 	{
1168*c87b03e5Sespie 	  HARD_REG_SET new_losers;
1169*c87b03e5Sespie 	  if (! losers)
1170*c87b03e5Sespie 	    CLEAR_HARD_REG_SET (new_losers);
1171*c87b03e5Sespie 	  else
1172*c87b03e5Sespie 	    COPY_HARD_REG_SET (new_losers, losers);
1173*c87b03e5Sespie 
1174*c87b03e5Sespie 	  IOR_HARD_REG_SET(new_losers, losing_caller_save_reg_set);
1175*c87b03e5Sespie 	  find_reg (num, new_losers, alt_regs_p, 1, retrying);
1176*c87b03e5Sespie 	  if (reg_renumber[allocno[num].reg] >= 0)
1177*c87b03e5Sespie 	    {
1178*c87b03e5Sespie 	      caller_save_needed = 1;
1179*c87b03e5Sespie 	      return;
1180*c87b03e5Sespie 	    }
1181*c87b03e5Sespie 	}
1182*c87b03e5Sespie     }
1183*c87b03e5Sespie 
1184*c87b03e5Sespie   /* If we haven't succeeded yet,
1185*c87b03e5Sespie      see if some hard reg that conflicts with us
1186*c87b03e5Sespie      was utilized poorly by local-alloc.
1187*c87b03e5Sespie      If so, kick out the regs that were put there by local-alloc
1188*c87b03e5Sespie      so we can use it instead.  */
1189*c87b03e5Sespie   if (best_reg < 0 && !retrying
1190*c87b03e5Sespie       /* Let's not bother with multi-reg allocnos.  */
1191*c87b03e5Sespie       && allocno[num].size == 1)
1192*c87b03e5Sespie     {
1193*c87b03e5Sespie       /* Count from the end, to find the least-used ones first.  */
1194*c87b03e5Sespie       for (i = FIRST_PSEUDO_REGISTER - 1; i >= 0; i--)
1195*c87b03e5Sespie 	{
1196*c87b03e5Sespie #ifdef REG_ALLOC_ORDER
1197*c87b03e5Sespie 	  int regno = reg_alloc_order[i];
1198*c87b03e5Sespie #else
1199*c87b03e5Sespie 	  int regno = i;
1200*c87b03e5Sespie #endif
1201*c87b03e5Sespie 
1202*c87b03e5Sespie 	  if (local_reg_n_refs[regno] != 0
1203*c87b03e5Sespie 	      /* Don't use a reg no good for this pseudo.  */
1204*c87b03e5Sespie 	      && ! TEST_HARD_REG_BIT (used2, regno)
1205*c87b03e5Sespie 	      && HARD_REGNO_MODE_OK (regno, mode)
1206*c87b03e5Sespie 	      /* The code below assumes that we need only a single
1207*c87b03e5Sespie 		 register, but the check of allocno[num].size above
1208*c87b03e5Sespie 		 was not enough.  Sometimes we need more than one
1209*c87b03e5Sespie 		 register for a single-word value.  */
1210*c87b03e5Sespie 	      && HARD_REGNO_NREGS (regno, mode) == 1
1211*c87b03e5Sespie 	      && (allocno[num].calls_crossed == 0
1212*c87b03e5Sespie 		  || accept_call_clobbered
1213*c87b03e5Sespie 		  || ! HARD_REGNO_CALL_PART_CLOBBERED (regno, mode))
1214*c87b03e5Sespie #ifdef CANNOT_CHANGE_MODE_CLASS
1215*c87b03e5Sespie 	      && ! invalid_mode_change_p (regno, REGNO_REG_CLASS (regno),
1216*c87b03e5Sespie 					  mode)
1217*c87b03e5Sespie #endif
1218*c87b03e5Sespie #ifdef STACK_REGS
1219*c87b03e5Sespie 	      && (!allocno[num].no_stack_reg
1220*c87b03e5Sespie 		  || regno < FIRST_STACK_REG || regno > LAST_STACK_REG)
1221*c87b03e5Sespie #endif
1222*c87b03e5Sespie 	      )
1223*c87b03e5Sespie 	    {
1224*c87b03e5Sespie 	      /* We explicitly evaluate the divide results into temporary
1225*c87b03e5Sespie 		 variables so as to avoid excess precision problems that occur
1226*c87b03e5Sespie 		 on an i386-unknown-sysv4.2 (unixware) host.  */
1227*c87b03e5Sespie 
1228*c87b03e5Sespie 	      double tmp1 = ((double) local_reg_freq[regno]
1229*c87b03e5Sespie 			    / local_reg_live_length[regno]);
1230*c87b03e5Sespie 	      double tmp2 = ((double) allocno[num].freq
1231*c87b03e5Sespie 			     / allocno[num].live_length);
1232*c87b03e5Sespie 
1233*c87b03e5Sespie 	      if (tmp1 < tmp2)
1234*c87b03e5Sespie 		{
1235*c87b03e5Sespie 		  /* Hard reg REGNO was used less in total by local regs
1236*c87b03e5Sespie 		     than it would be used by this one allocno!  */
1237*c87b03e5Sespie 		  int k;
1238*c87b03e5Sespie 		  for (k = 0; k < max_regno; k++)
1239*c87b03e5Sespie 		    if (reg_renumber[k] >= 0)
1240*c87b03e5Sespie 		      {
1241*c87b03e5Sespie 			int r = reg_renumber[k];
1242*c87b03e5Sespie 			int endregno
1243*c87b03e5Sespie 			  = r + HARD_REGNO_NREGS (r, PSEUDO_REGNO_MODE (k));
1244*c87b03e5Sespie 
1245*c87b03e5Sespie 			if (regno >= r && regno < endregno)
1246*c87b03e5Sespie 			  reg_renumber[k] = -1;
1247*c87b03e5Sespie 		      }
1248*c87b03e5Sespie 
1249*c87b03e5Sespie 		  best_reg = regno;
1250*c87b03e5Sespie 		  break;
1251*c87b03e5Sespie 		}
1252*c87b03e5Sespie 	    }
1253*c87b03e5Sespie 	}
1254*c87b03e5Sespie     }
1255*c87b03e5Sespie 
1256*c87b03e5Sespie   /* Did we find a register?  */
1257*c87b03e5Sespie 
1258*c87b03e5Sespie   if (best_reg >= 0)
1259*c87b03e5Sespie     {
1260*c87b03e5Sespie       int lim, j;
1261*c87b03e5Sespie       HARD_REG_SET this_reg;
1262*c87b03e5Sespie 
1263*c87b03e5Sespie       /* Yes.  Record it as the hard register of this pseudo-reg.  */
1264*c87b03e5Sespie       reg_renumber[allocno[num].reg] = best_reg;
1265*c87b03e5Sespie       /* Also of any pseudo-regs that share with it.  */
1266*c87b03e5Sespie       if (reg_may_share[allocno[num].reg])
1267*c87b03e5Sespie 	for (j = FIRST_PSEUDO_REGISTER; j < max_regno; j++)
1268*c87b03e5Sespie 	  if (reg_allocno[j] == num)
1269*c87b03e5Sespie 	    reg_renumber[j] = best_reg;
1270*c87b03e5Sespie 
1271*c87b03e5Sespie       /* Make a set of the hard regs being allocated.  */
1272*c87b03e5Sespie       CLEAR_HARD_REG_SET (this_reg);
1273*c87b03e5Sespie       lim = best_reg + HARD_REGNO_NREGS (best_reg, mode);
1274*c87b03e5Sespie       for (j = best_reg; j < lim; j++)
1275*c87b03e5Sespie 	{
1276*c87b03e5Sespie 	  SET_HARD_REG_BIT (this_reg, j);
1277*c87b03e5Sespie 	  SET_HARD_REG_BIT (regs_used_so_far, j);
1278*c87b03e5Sespie 	  /* This is no longer a reg used just by local regs.  */
1279*c87b03e5Sespie 	  local_reg_n_refs[j] = 0;
1280*c87b03e5Sespie 	  local_reg_freq[j] = 0;
1281*c87b03e5Sespie 	}
1282*c87b03e5Sespie       /* For each other pseudo-reg conflicting with this one,
1283*c87b03e5Sespie 	 mark it as conflicting with the hard regs this one occupies.  */
1284*c87b03e5Sespie       lim = num;
1285*c87b03e5Sespie       EXECUTE_IF_SET_IN_ALLOCNO_SET (conflicts + lim * allocno_row_words, j,
1286*c87b03e5Sespie 	{
1287*c87b03e5Sespie 	  IOR_HARD_REG_SET (allocno[j].hard_reg_conflicts, this_reg);
1288*c87b03e5Sespie 	});
1289*c87b03e5Sespie     }
1290*c87b03e5Sespie }
1291*c87b03e5Sespie 
1292*c87b03e5Sespie /* Called from `reload' to look for a hard reg to put pseudo reg REGNO in.
1293*c87b03e5Sespie    Perhaps it had previously seemed not worth a hard reg,
1294*c87b03e5Sespie    or perhaps its old hard reg has been commandeered for reloads.
1295*c87b03e5Sespie    FORBIDDEN_REGS indicates certain hard regs that may not be used, even if
1296*c87b03e5Sespie    they do not appear to be allocated.
1297*c87b03e5Sespie    If FORBIDDEN_REGS is zero, no regs are forbidden.  */
1298*c87b03e5Sespie 
1299*c87b03e5Sespie void
retry_global_alloc(regno,forbidden_regs)1300*c87b03e5Sespie retry_global_alloc (regno, forbidden_regs)
1301*c87b03e5Sespie      int regno;
1302*c87b03e5Sespie      HARD_REG_SET forbidden_regs;
1303*c87b03e5Sespie {
1304*c87b03e5Sespie   int alloc_no = reg_allocno[regno];
1305*c87b03e5Sespie   if (alloc_no >= 0)
1306*c87b03e5Sespie     {
1307*c87b03e5Sespie       /* If we have more than one register class,
1308*c87b03e5Sespie 	 first try allocating in the class that is cheapest
1309*c87b03e5Sespie 	 for this pseudo-reg.  If that fails, try any reg.  */
1310*c87b03e5Sespie       if (N_REG_CLASSES > 1)
1311*c87b03e5Sespie 	find_reg (alloc_no, forbidden_regs, 0, 0, 1);
1312*c87b03e5Sespie       if (reg_renumber[regno] < 0
1313*c87b03e5Sespie 	  && reg_alternate_class (regno) != NO_REGS)
1314*c87b03e5Sespie 	find_reg (alloc_no, forbidden_regs, 1, 0, 1);
1315*c87b03e5Sespie 
1316*c87b03e5Sespie       /* If we found a register, modify the RTL for the register to
1317*c87b03e5Sespie 	 show the hard register, and mark that register live.  */
1318*c87b03e5Sespie       if (reg_renumber[regno] >= 0)
1319*c87b03e5Sespie 	{
1320*c87b03e5Sespie 	  REGNO (regno_reg_rtx[regno]) = reg_renumber[regno];
1321*c87b03e5Sespie 	  mark_home_live (regno);
1322*c87b03e5Sespie 	}
1323*c87b03e5Sespie     }
1324*c87b03e5Sespie }
1325*c87b03e5Sespie 
1326*c87b03e5Sespie /* Record a conflict between register REGNO
1327*c87b03e5Sespie    and everything currently live.
1328*c87b03e5Sespie    REGNO must not be a pseudo reg that was allocated
1329*c87b03e5Sespie    by local_alloc; such numbers must be translated through
1330*c87b03e5Sespie    reg_renumber before calling here.  */
1331*c87b03e5Sespie 
1332*c87b03e5Sespie static void
record_one_conflict(regno)1333*c87b03e5Sespie record_one_conflict (regno)
1334*c87b03e5Sespie      int regno;
1335*c87b03e5Sespie {
1336*c87b03e5Sespie   int j;
1337*c87b03e5Sespie 
1338*c87b03e5Sespie   if (regno < FIRST_PSEUDO_REGISTER)
1339*c87b03e5Sespie     /* When a hard register becomes live,
1340*c87b03e5Sespie        record conflicts with live pseudo regs.  */
1341*c87b03e5Sespie     EXECUTE_IF_SET_IN_ALLOCNO_SET (allocnos_live, j,
1342*c87b03e5Sespie       {
1343*c87b03e5Sespie 	SET_HARD_REG_BIT (allocno[j].hard_reg_conflicts, regno);
1344*c87b03e5Sespie       });
1345*c87b03e5Sespie   else
1346*c87b03e5Sespie     /* When a pseudo-register becomes live,
1347*c87b03e5Sespie        record conflicts first with hard regs,
1348*c87b03e5Sespie        then with other pseudo regs.  */
1349*c87b03e5Sespie     {
1350*c87b03e5Sespie       int ialloc = reg_allocno[regno];
1351*c87b03e5Sespie       int ialloc_prod = ialloc * allocno_row_words;
1352*c87b03e5Sespie 
1353*c87b03e5Sespie       IOR_HARD_REG_SET (allocno[ialloc].hard_reg_conflicts, hard_regs_live);
1354*c87b03e5Sespie       for (j = allocno_row_words - 1; j >= 0; j--)
1355*c87b03e5Sespie 	{
1356*c87b03e5Sespie #if 0
1357*c87b03e5Sespie 	  int k;
1358*c87b03e5Sespie 	  for (k = 0; k < n_no_conflict_pairs; k++)
1359*c87b03e5Sespie 	    if (! ((j == no_conflict_pairs[k].allocno1
1360*c87b03e5Sespie 		    && ialloc == no_conflict_pairs[k].allocno2)
1361*c87b03e5Sespie 		   ||
1362*c87b03e5Sespie 		   (j == no_conflict_pairs[k].allocno2
1363*c87b03e5Sespie 		    && ialloc == no_conflict_pairs[k].allocno1)))
1364*c87b03e5Sespie #endif /* 0 */
1365*c87b03e5Sespie 	      conflicts[ialloc_prod + j] |= allocnos_live[j];
1366*c87b03e5Sespie 	}
1367*c87b03e5Sespie     }
1368*c87b03e5Sespie }
1369*c87b03e5Sespie 
1370*c87b03e5Sespie /* Record all allocnos currently live as conflicting
1371*c87b03e5Sespie    with all hard regs currently live.
1372*c87b03e5Sespie 
1373*c87b03e5Sespie    ALLOCNO_VEC is a vector of LEN allocnos, all allocnos that
1374*c87b03e5Sespie    are currently live.  Their bits are also flagged in allocnos_live.  */
1375*c87b03e5Sespie 
1376*c87b03e5Sespie static void
record_conflicts(allocno_vec,len)1377*c87b03e5Sespie record_conflicts (allocno_vec, len)
1378*c87b03e5Sespie      int *allocno_vec;
1379*c87b03e5Sespie      int len;
1380*c87b03e5Sespie {
1381*c87b03e5Sespie   int num;
1382*c87b03e5Sespie   int ialloc_prod;
1383*c87b03e5Sespie 
1384*c87b03e5Sespie   while (--len >= 0)
1385*c87b03e5Sespie     {
1386*c87b03e5Sespie       num = allocno_vec[len];
1387*c87b03e5Sespie       ialloc_prod = num * allocno_row_words;
1388*c87b03e5Sespie       IOR_HARD_REG_SET (allocno[num].hard_reg_conflicts, hard_regs_live);
1389*c87b03e5Sespie     }
1390*c87b03e5Sespie }
1391*c87b03e5Sespie 
1392*c87b03e5Sespie /* If CONFLICTP (i, j) is true, make sure CONFLICTP (j, i) is also true.  */
1393*c87b03e5Sespie static void
mirror_conflicts()1394*c87b03e5Sespie mirror_conflicts ()
1395*c87b03e5Sespie {
1396*c87b03e5Sespie   int i, j;
1397*c87b03e5Sespie   int rw = allocno_row_words;
1398*c87b03e5Sespie   int rwb = rw * INT_BITS;
1399*c87b03e5Sespie   INT_TYPE *p = conflicts;
1400*c87b03e5Sespie   INT_TYPE *q0 = conflicts, *q1, *q2;
1401*c87b03e5Sespie   unsigned INT_TYPE mask;
1402*c87b03e5Sespie 
1403*c87b03e5Sespie   for (i = max_allocno - 1, mask = 1; i >= 0; i--, mask <<= 1)
1404*c87b03e5Sespie     {
1405*c87b03e5Sespie       if (! mask)
1406*c87b03e5Sespie 	{
1407*c87b03e5Sespie 	  mask = 1;
1408*c87b03e5Sespie 	  q0++;
1409*c87b03e5Sespie 	}
1410*c87b03e5Sespie       for (j = allocno_row_words - 1, q1 = q0; j >= 0; j--, q1 += rwb)
1411*c87b03e5Sespie 	{
1412*c87b03e5Sespie 	  unsigned INT_TYPE word;
1413*c87b03e5Sespie 
1414*c87b03e5Sespie 	  for (word = (unsigned INT_TYPE) *p++, q2 = q1; word;
1415*c87b03e5Sespie 	       word >>= 1, q2 += rw)
1416*c87b03e5Sespie 	    {
1417*c87b03e5Sespie 	      if (word & 1)
1418*c87b03e5Sespie 		*q2 |= mask;
1419*c87b03e5Sespie 	    }
1420*c87b03e5Sespie 	}
1421*c87b03e5Sespie     }
1422*c87b03e5Sespie }
1423*c87b03e5Sespie 
1424*c87b03e5Sespie /* Handle the case where REG is set by the insn being scanned,
1425*c87b03e5Sespie    during the forward scan to accumulate conflicts.
1426*c87b03e5Sespie    Store a 1 in regs_live or allocnos_live for this register, record how many
1427*c87b03e5Sespie    consecutive hardware registers it actually needs,
1428*c87b03e5Sespie    and record a conflict with all other registers already live.
1429*c87b03e5Sespie 
1430*c87b03e5Sespie    Note that even if REG does not remain alive after this insn,
1431*c87b03e5Sespie    we must mark it here as live, to ensure a conflict between
1432*c87b03e5Sespie    REG and any other regs set in this insn that really do live.
1433*c87b03e5Sespie    This is because those other regs could be considered after this.
1434*c87b03e5Sespie 
1435*c87b03e5Sespie    REG might actually be something other than a register;
1436*c87b03e5Sespie    if so, we do nothing.
1437*c87b03e5Sespie 
1438*c87b03e5Sespie    SETTER is 0 if this register was modified by an auto-increment (i.e.,
1439*c87b03e5Sespie    a REG_INC note was found for it).  */
1440*c87b03e5Sespie 
1441*c87b03e5Sespie static void
mark_reg_store(reg,setter,data)1442*c87b03e5Sespie mark_reg_store (reg, setter, data)
1443*c87b03e5Sespie      rtx reg, setter;
1444*c87b03e5Sespie      void *data ATTRIBUTE_UNUSED;
1445*c87b03e5Sespie {
1446*c87b03e5Sespie   int regno;
1447*c87b03e5Sespie 
1448*c87b03e5Sespie   if (GET_CODE (reg) == SUBREG)
1449*c87b03e5Sespie     reg = SUBREG_REG (reg);
1450*c87b03e5Sespie 
1451*c87b03e5Sespie   if (GET_CODE (reg) != REG)
1452*c87b03e5Sespie     return;
1453*c87b03e5Sespie 
1454*c87b03e5Sespie   regs_set[n_regs_set++] = reg;
1455*c87b03e5Sespie 
1456*c87b03e5Sespie   if (setter && GET_CODE (setter) != CLOBBER)
1457*c87b03e5Sespie     set_preference (reg, SET_SRC (setter));
1458*c87b03e5Sespie 
1459*c87b03e5Sespie   regno = REGNO (reg);
1460*c87b03e5Sespie 
1461*c87b03e5Sespie   /* Either this is one of the max_allocno pseudo regs not allocated,
1462*c87b03e5Sespie      or it is or has a hardware reg.  First handle the pseudo-regs.  */
1463*c87b03e5Sespie   if (regno >= FIRST_PSEUDO_REGISTER)
1464*c87b03e5Sespie     {
1465*c87b03e5Sespie       if (reg_allocno[regno] >= 0)
1466*c87b03e5Sespie 	{
1467*c87b03e5Sespie 	  SET_ALLOCNO_LIVE (reg_allocno[regno]);
1468*c87b03e5Sespie 	  record_one_conflict (regno);
1469*c87b03e5Sespie 	}
1470*c87b03e5Sespie     }
1471*c87b03e5Sespie 
1472*c87b03e5Sespie   if (reg_renumber[regno] >= 0)
1473*c87b03e5Sespie     regno = reg_renumber[regno];
1474*c87b03e5Sespie 
1475*c87b03e5Sespie   /* Handle hardware regs (and pseudos allocated to hard regs).  */
1476*c87b03e5Sespie   if (regno < FIRST_PSEUDO_REGISTER && ! fixed_regs[regno])
1477*c87b03e5Sespie     {
1478*c87b03e5Sespie       int last = regno + HARD_REGNO_NREGS (regno, GET_MODE (reg));
1479*c87b03e5Sespie       while (regno < last)
1480*c87b03e5Sespie 	{
1481*c87b03e5Sespie 	  record_one_conflict (regno);
1482*c87b03e5Sespie 	  SET_HARD_REG_BIT (hard_regs_live, regno);
1483*c87b03e5Sespie 	  regno++;
1484*c87b03e5Sespie 	}
1485*c87b03e5Sespie     }
1486*c87b03e5Sespie }
1487*c87b03e5Sespie 
1488*c87b03e5Sespie /* Like mark_reg_set except notice just CLOBBERs; ignore SETs.  */
1489*c87b03e5Sespie 
1490*c87b03e5Sespie static void
mark_reg_clobber(reg,setter,data)1491*c87b03e5Sespie mark_reg_clobber (reg, setter, data)
1492*c87b03e5Sespie      rtx reg, setter;
1493*c87b03e5Sespie      void *data ATTRIBUTE_UNUSED;
1494*c87b03e5Sespie {
1495*c87b03e5Sespie   if (GET_CODE (setter) == CLOBBER)
1496*c87b03e5Sespie     mark_reg_store (reg, setter, data);
1497*c87b03e5Sespie }
1498*c87b03e5Sespie 
1499*c87b03e5Sespie /* Record that REG has conflicts with all the regs currently live.
1500*c87b03e5Sespie    Do not mark REG itself as live.  */
1501*c87b03e5Sespie 
1502*c87b03e5Sespie static void
mark_reg_conflicts(reg)1503*c87b03e5Sespie mark_reg_conflicts (reg)
1504*c87b03e5Sespie      rtx reg;
1505*c87b03e5Sespie {
1506*c87b03e5Sespie   int regno;
1507*c87b03e5Sespie 
1508*c87b03e5Sespie   if (GET_CODE (reg) == SUBREG)
1509*c87b03e5Sespie     reg = SUBREG_REG (reg);
1510*c87b03e5Sespie 
1511*c87b03e5Sespie   if (GET_CODE (reg) != REG)
1512*c87b03e5Sespie     return;
1513*c87b03e5Sespie 
1514*c87b03e5Sespie   regno = REGNO (reg);
1515*c87b03e5Sespie 
1516*c87b03e5Sespie   /* Either this is one of the max_allocno pseudo regs not allocated,
1517*c87b03e5Sespie      or it is or has a hardware reg.  First handle the pseudo-regs.  */
1518*c87b03e5Sespie   if (regno >= FIRST_PSEUDO_REGISTER)
1519*c87b03e5Sespie     {
1520*c87b03e5Sespie       if (reg_allocno[regno] >= 0)
1521*c87b03e5Sespie 	record_one_conflict (regno);
1522*c87b03e5Sespie     }
1523*c87b03e5Sespie 
1524*c87b03e5Sespie   if (reg_renumber[regno] >= 0)
1525*c87b03e5Sespie     regno = reg_renumber[regno];
1526*c87b03e5Sespie 
1527*c87b03e5Sespie   /* Handle hardware regs (and pseudos allocated to hard regs).  */
1528*c87b03e5Sespie   if (regno < FIRST_PSEUDO_REGISTER && ! fixed_regs[regno])
1529*c87b03e5Sespie     {
1530*c87b03e5Sespie       int last = regno + HARD_REGNO_NREGS (regno, GET_MODE (reg));
1531*c87b03e5Sespie       while (regno < last)
1532*c87b03e5Sespie 	{
1533*c87b03e5Sespie 	  record_one_conflict (regno);
1534*c87b03e5Sespie 	  regno++;
1535*c87b03e5Sespie 	}
1536*c87b03e5Sespie     }
1537*c87b03e5Sespie }
1538*c87b03e5Sespie 
1539*c87b03e5Sespie /* Mark REG as being dead (following the insn being scanned now).
1540*c87b03e5Sespie    Store a 0 in regs_live or allocnos_live for this register.  */
1541*c87b03e5Sespie 
1542*c87b03e5Sespie static void
mark_reg_death(reg)1543*c87b03e5Sespie mark_reg_death (reg)
1544*c87b03e5Sespie      rtx reg;
1545*c87b03e5Sespie {
1546*c87b03e5Sespie   int regno = REGNO (reg);
1547*c87b03e5Sespie 
1548*c87b03e5Sespie   /* Either this is one of the max_allocno pseudo regs not allocated,
1549*c87b03e5Sespie      or it is a hardware reg.  First handle the pseudo-regs.  */
1550*c87b03e5Sespie   if (regno >= FIRST_PSEUDO_REGISTER)
1551*c87b03e5Sespie     {
1552*c87b03e5Sespie       if (reg_allocno[regno] >= 0)
1553*c87b03e5Sespie 	CLEAR_ALLOCNO_LIVE (reg_allocno[regno]);
1554*c87b03e5Sespie     }
1555*c87b03e5Sespie 
1556*c87b03e5Sespie   /* For pseudo reg, see if it has been assigned a hardware reg.  */
1557*c87b03e5Sespie   if (reg_renumber[regno] >= 0)
1558*c87b03e5Sespie     regno = reg_renumber[regno];
1559*c87b03e5Sespie 
1560*c87b03e5Sespie   /* Handle hardware regs (and pseudos allocated to hard regs).  */
1561*c87b03e5Sespie   if (regno < FIRST_PSEUDO_REGISTER && ! fixed_regs[regno])
1562*c87b03e5Sespie     {
1563*c87b03e5Sespie       /* Pseudo regs already assigned hardware regs are treated
1564*c87b03e5Sespie 	 almost the same as explicit hardware regs.  */
1565*c87b03e5Sespie       int last = regno + HARD_REGNO_NREGS (regno, GET_MODE (reg));
1566*c87b03e5Sespie       while (regno < last)
1567*c87b03e5Sespie 	{
1568*c87b03e5Sespie 	  CLEAR_HARD_REG_BIT (hard_regs_live, regno);
1569*c87b03e5Sespie 	  regno++;
1570*c87b03e5Sespie 	}
1571*c87b03e5Sespie     }
1572*c87b03e5Sespie }
1573*c87b03e5Sespie 
1574*c87b03e5Sespie /* Mark hard reg REGNO as currently live, assuming machine mode MODE
1575*c87b03e5Sespie    for the value stored in it.  MODE determines how many consecutive
1576*c87b03e5Sespie    registers are actually in use.  Do not record conflicts;
1577*c87b03e5Sespie    it is assumed that the caller will do that.  */
1578*c87b03e5Sespie 
1579*c87b03e5Sespie static void
mark_reg_live_nc(regno,mode)1580*c87b03e5Sespie mark_reg_live_nc (regno, mode)
1581*c87b03e5Sespie      int regno;
1582*c87b03e5Sespie      enum machine_mode mode;
1583*c87b03e5Sespie {
1584*c87b03e5Sespie   int last = regno + HARD_REGNO_NREGS (regno, mode);
1585*c87b03e5Sespie   while (regno < last)
1586*c87b03e5Sespie     {
1587*c87b03e5Sespie       SET_HARD_REG_BIT (hard_regs_live, regno);
1588*c87b03e5Sespie       regno++;
1589*c87b03e5Sespie     }
1590*c87b03e5Sespie }
1591*c87b03e5Sespie 
1592*c87b03e5Sespie /* Try to set a preference for an allocno to a hard register.
1593*c87b03e5Sespie    We are passed DEST and SRC which are the operands of a SET.  It is known
1594*c87b03e5Sespie    that SRC is a register.  If SRC or the first operand of SRC is a register,
1595*c87b03e5Sespie    try to set a preference.  If one of the two is a hard register and the other
1596*c87b03e5Sespie    is a pseudo-register, mark the preference.
1597*c87b03e5Sespie 
1598*c87b03e5Sespie    Note that we are not as aggressive as local-alloc in trying to tie a
1599*c87b03e5Sespie    pseudo-register to a hard register.  */
1600*c87b03e5Sespie 
1601*c87b03e5Sespie static void
set_preference(dest,src)1602*c87b03e5Sespie set_preference (dest, src)
1603*c87b03e5Sespie      rtx dest, src;
1604*c87b03e5Sespie {
1605*c87b03e5Sespie   unsigned int src_regno, dest_regno;
1606*c87b03e5Sespie   /* Amount to add to the hard regno for SRC, or subtract from that for DEST,
1607*c87b03e5Sespie      to compensate for subregs in SRC or DEST.  */
1608*c87b03e5Sespie   int offset = 0;
1609*c87b03e5Sespie   unsigned int i;
1610*c87b03e5Sespie   int copy = 1;
1611*c87b03e5Sespie 
1612*c87b03e5Sespie   if (GET_RTX_FORMAT (GET_CODE (src))[0] == 'e')
1613*c87b03e5Sespie     src = XEXP (src, 0), copy = 0;
1614*c87b03e5Sespie 
1615*c87b03e5Sespie   /* Get the reg number for both SRC and DEST.
1616*c87b03e5Sespie      If neither is a reg, give up.  */
1617*c87b03e5Sespie 
1618*c87b03e5Sespie   if (GET_CODE (src) == REG)
1619*c87b03e5Sespie     src_regno = REGNO (src);
1620*c87b03e5Sespie   else if (GET_CODE (src) == SUBREG && GET_CODE (SUBREG_REG (src)) == REG)
1621*c87b03e5Sespie     {
1622*c87b03e5Sespie       src_regno = REGNO (SUBREG_REG (src));
1623*c87b03e5Sespie 
1624*c87b03e5Sespie       if (REGNO (SUBREG_REG (src)) < FIRST_PSEUDO_REGISTER)
1625*c87b03e5Sespie 	offset += subreg_regno_offset (REGNO (SUBREG_REG (src)),
1626*c87b03e5Sespie 				       GET_MODE (SUBREG_REG (src)),
1627*c87b03e5Sespie 				       SUBREG_BYTE (src),
1628*c87b03e5Sespie 				       GET_MODE (src));
1629*c87b03e5Sespie       else
1630*c87b03e5Sespie 	offset += (SUBREG_BYTE (src)
1631*c87b03e5Sespie 		   / REGMODE_NATURAL_SIZE (GET_MODE (src)));
1632*c87b03e5Sespie     }
1633*c87b03e5Sespie   else
1634*c87b03e5Sespie     return;
1635*c87b03e5Sespie 
1636*c87b03e5Sespie   if (GET_CODE (dest) == REG)
1637*c87b03e5Sespie     dest_regno = REGNO (dest);
1638*c87b03e5Sespie   else if (GET_CODE (dest) == SUBREG && GET_CODE (SUBREG_REG (dest)) == REG)
1639*c87b03e5Sespie     {
1640*c87b03e5Sespie       dest_regno = REGNO (SUBREG_REG (dest));
1641*c87b03e5Sespie 
1642*c87b03e5Sespie       if (REGNO (SUBREG_REG (dest)) < FIRST_PSEUDO_REGISTER)
1643*c87b03e5Sespie 	offset -= subreg_regno_offset (REGNO (SUBREG_REG (dest)),
1644*c87b03e5Sespie 				       GET_MODE (SUBREG_REG (dest)),
1645*c87b03e5Sespie 				       SUBREG_BYTE (dest),
1646*c87b03e5Sespie 				       GET_MODE (dest));
1647*c87b03e5Sespie       else
1648*c87b03e5Sespie 	offset -= (SUBREG_BYTE (dest)
1649*c87b03e5Sespie 		   / REGMODE_NATURAL_SIZE (GET_MODE (dest)));
1650*c87b03e5Sespie     }
1651*c87b03e5Sespie   else
1652*c87b03e5Sespie     return;
1653*c87b03e5Sespie 
1654*c87b03e5Sespie   /* Convert either or both to hard reg numbers.  */
1655*c87b03e5Sespie 
1656*c87b03e5Sespie   if (reg_renumber[src_regno] >= 0)
1657*c87b03e5Sespie     src_regno = reg_renumber[src_regno];
1658*c87b03e5Sespie 
1659*c87b03e5Sespie   if (reg_renumber[dest_regno] >= 0)
1660*c87b03e5Sespie     dest_regno = reg_renumber[dest_regno];
1661*c87b03e5Sespie 
1662*c87b03e5Sespie   /* Now if one is a hard reg and the other is a global pseudo
1663*c87b03e5Sespie      then give the other a preference.  */
1664*c87b03e5Sespie 
1665*c87b03e5Sespie   if (dest_regno < FIRST_PSEUDO_REGISTER && src_regno >= FIRST_PSEUDO_REGISTER
1666*c87b03e5Sespie       && reg_allocno[src_regno] >= 0)
1667*c87b03e5Sespie     {
1668*c87b03e5Sespie       dest_regno -= offset;
1669*c87b03e5Sespie       if (dest_regno < FIRST_PSEUDO_REGISTER)
1670*c87b03e5Sespie 	{
1671*c87b03e5Sespie 	  if (copy)
1672*c87b03e5Sespie 	    SET_REGBIT (hard_reg_copy_preferences,
1673*c87b03e5Sespie 			reg_allocno[src_regno], dest_regno);
1674*c87b03e5Sespie 
1675*c87b03e5Sespie 	  SET_REGBIT (hard_reg_preferences,
1676*c87b03e5Sespie 		      reg_allocno[src_regno], dest_regno);
1677*c87b03e5Sespie 	  for (i = dest_regno;
1678*c87b03e5Sespie 	       i < dest_regno + HARD_REGNO_NREGS (dest_regno, GET_MODE (dest));
1679*c87b03e5Sespie 	       i++)
1680*c87b03e5Sespie 	    SET_REGBIT (hard_reg_full_preferences, reg_allocno[src_regno], i);
1681*c87b03e5Sespie 	}
1682*c87b03e5Sespie     }
1683*c87b03e5Sespie 
1684*c87b03e5Sespie   if (src_regno < FIRST_PSEUDO_REGISTER && dest_regno >= FIRST_PSEUDO_REGISTER
1685*c87b03e5Sespie       && reg_allocno[dest_regno] >= 0)
1686*c87b03e5Sespie     {
1687*c87b03e5Sespie       src_regno += offset;
1688*c87b03e5Sespie       if (src_regno < FIRST_PSEUDO_REGISTER)
1689*c87b03e5Sespie 	{
1690*c87b03e5Sespie 	  if (copy)
1691*c87b03e5Sespie 	    SET_REGBIT (hard_reg_copy_preferences,
1692*c87b03e5Sespie 			reg_allocno[dest_regno], src_regno);
1693*c87b03e5Sespie 
1694*c87b03e5Sespie 	  SET_REGBIT (hard_reg_preferences,
1695*c87b03e5Sespie 		      reg_allocno[dest_regno], src_regno);
1696*c87b03e5Sespie 	  for (i = src_regno;
1697*c87b03e5Sespie 	       i < src_regno + HARD_REGNO_NREGS (src_regno, GET_MODE (src));
1698*c87b03e5Sespie 	       i++)
1699*c87b03e5Sespie 	    SET_REGBIT (hard_reg_full_preferences, reg_allocno[dest_regno], i);
1700*c87b03e5Sespie 	}
1701*c87b03e5Sespie     }
1702*c87b03e5Sespie }
1703*c87b03e5Sespie 
1704*c87b03e5Sespie /* Indicate that hard register number FROM was eliminated and replaced with
1705*c87b03e5Sespie    an offset from hard register number TO.  The status of hard registers live
1706*c87b03e5Sespie    at the start of a basic block is updated by replacing a use of FROM with
1707*c87b03e5Sespie    a use of TO.  */
1708*c87b03e5Sespie 
1709*c87b03e5Sespie void
mark_elimination(from,to)1710*c87b03e5Sespie mark_elimination (from, to)
1711*c87b03e5Sespie      int from, to;
1712*c87b03e5Sespie {
1713*c87b03e5Sespie   basic_block bb;
1714*c87b03e5Sespie 
1715*c87b03e5Sespie   FOR_EACH_BB (bb)
1716*c87b03e5Sespie     {
1717*c87b03e5Sespie       regset r = bb->global_live_at_start;
1718*c87b03e5Sespie       if (REGNO_REG_SET_P (r, from))
1719*c87b03e5Sespie 	{
1720*c87b03e5Sespie 	  CLEAR_REGNO_REG_SET (r, from);
1721*c87b03e5Sespie 	  SET_REGNO_REG_SET (r, to);
1722*c87b03e5Sespie 	}
1723*c87b03e5Sespie     }
1724*c87b03e5Sespie }
1725*c87b03e5Sespie 
1726*c87b03e5Sespie /* Used for communication between the following functions.  Holds the
1727*c87b03e5Sespie    current life information.  */
1728*c87b03e5Sespie static regset live_relevant_regs;
1729*c87b03e5Sespie 
1730*c87b03e5Sespie /* Record in live_relevant_regs and REGS_SET that register REG became live.
1731*c87b03e5Sespie    This is called via note_stores.  */
1732*c87b03e5Sespie static void
reg_becomes_live(reg,setter,regs_set)1733*c87b03e5Sespie reg_becomes_live (reg, setter, regs_set)
1734*c87b03e5Sespie      rtx reg;
1735*c87b03e5Sespie      rtx setter ATTRIBUTE_UNUSED;
1736*c87b03e5Sespie      void *regs_set;
1737*c87b03e5Sespie {
1738*c87b03e5Sespie   int regno;
1739*c87b03e5Sespie 
1740*c87b03e5Sespie   if (GET_CODE (reg) == SUBREG)
1741*c87b03e5Sespie     reg = SUBREG_REG (reg);
1742*c87b03e5Sespie 
1743*c87b03e5Sespie   if (GET_CODE (reg) != REG)
1744*c87b03e5Sespie     return;
1745*c87b03e5Sespie 
1746*c87b03e5Sespie   regno = REGNO (reg);
1747*c87b03e5Sespie   if (regno < FIRST_PSEUDO_REGISTER)
1748*c87b03e5Sespie     {
1749*c87b03e5Sespie       int nregs = HARD_REGNO_NREGS (regno, GET_MODE (reg));
1750*c87b03e5Sespie       while (nregs-- > 0)
1751*c87b03e5Sespie 	{
1752*c87b03e5Sespie 	  SET_REGNO_REG_SET (live_relevant_regs, regno);
1753*c87b03e5Sespie 	  if (! fixed_regs[regno])
1754*c87b03e5Sespie 	    SET_REGNO_REG_SET ((regset) regs_set, regno);
1755*c87b03e5Sespie 	  regno++;
1756*c87b03e5Sespie 	}
1757*c87b03e5Sespie     }
1758*c87b03e5Sespie   else if (reg_renumber[regno] >= 0)
1759*c87b03e5Sespie     {
1760*c87b03e5Sespie       SET_REGNO_REG_SET (live_relevant_regs, regno);
1761*c87b03e5Sespie       SET_REGNO_REG_SET ((regset) regs_set, regno);
1762*c87b03e5Sespie     }
1763*c87b03e5Sespie }
1764*c87b03e5Sespie 
1765*c87b03e5Sespie /* Record in live_relevant_regs that register REGNO died.  */
1766*c87b03e5Sespie static void
reg_dies(regno,mode,chain)1767*c87b03e5Sespie reg_dies (regno, mode, chain)
1768*c87b03e5Sespie      int regno;
1769*c87b03e5Sespie      enum machine_mode mode;
1770*c87b03e5Sespie      struct insn_chain *chain;
1771*c87b03e5Sespie {
1772*c87b03e5Sespie   if (regno < FIRST_PSEUDO_REGISTER)
1773*c87b03e5Sespie     {
1774*c87b03e5Sespie       int nregs = HARD_REGNO_NREGS (regno, mode);
1775*c87b03e5Sespie       while (nregs-- > 0)
1776*c87b03e5Sespie 	{
1777*c87b03e5Sespie 	  CLEAR_REGNO_REG_SET (live_relevant_regs, regno);
1778*c87b03e5Sespie 	  if (! fixed_regs[regno])
1779*c87b03e5Sespie 	    SET_REGNO_REG_SET (&chain->dead_or_set, regno);
1780*c87b03e5Sespie 	  regno++;
1781*c87b03e5Sespie 	}
1782*c87b03e5Sespie     }
1783*c87b03e5Sespie   else
1784*c87b03e5Sespie     {
1785*c87b03e5Sespie       CLEAR_REGNO_REG_SET (live_relevant_regs, regno);
1786*c87b03e5Sespie       if (reg_renumber[regno] >= 0)
1787*c87b03e5Sespie 	SET_REGNO_REG_SET (&chain->dead_or_set, regno);
1788*c87b03e5Sespie     }
1789*c87b03e5Sespie }
1790*c87b03e5Sespie 
1791*c87b03e5Sespie /* Walk the insns of the current function and build reload_insn_chain,
1792*c87b03e5Sespie    and record register life information.  */
1793*c87b03e5Sespie void
build_insn_chain(first)1794*c87b03e5Sespie build_insn_chain (first)
1795*c87b03e5Sespie      rtx first;
1796*c87b03e5Sespie {
1797*c87b03e5Sespie   struct insn_chain **p = &reload_insn_chain;
1798*c87b03e5Sespie   struct insn_chain *prev = 0;
1799*c87b03e5Sespie   basic_block b = ENTRY_BLOCK_PTR->next_bb;
1800*c87b03e5Sespie   regset_head live_relevant_regs_head;
1801*c87b03e5Sespie 
1802*c87b03e5Sespie   live_relevant_regs = INITIALIZE_REG_SET (live_relevant_regs_head);
1803*c87b03e5Sespie 
1804*c87b03e5Sespie   for (; first; first = NEXT_INSN (first))
1805*c87b03e5Sespie     {
1806*c87b03e5Sespie       struct insn_chain *c;
1807*c87b03e5Sespie 
1808*c87b03e5Sespie       if (first == b->head)
1809*c87b03e5Sespie 	{
1810*c87b03e5Sespie 	  int i;
1811*c87b03e5Sespie 
1812*c87b03e5Sespie 	  CLEAR_REG_SET (live_relevant_regs);
1813*c87b03e5Sespie 
1814*c87b03e5Sespie 	  EXECUTE_IF_SET_IN_BITMAP
1815*c87b03e5Sespie 	    (b->global_live_at_start, 0, i,
1816*c87b03e5Sespie 	     {
1817*c87b03e5Sespie 	       if (i < FIRST_PSEUDO_REGISTER
1818*c87b03e5Sespie 		   ? ! TEST_HARD_REG_BIT (eliminable_regset, i)
1819*c87b03e5Sespie 		   : reg_renumber[i] >= 0)
1820*c87b03e5Sespie 		 SET_REGNO_REG_SET (live_relevant_regs, i);
1821*c87b03e5Sespie 	     });
1822*c87b03e5Sespie 	}
1823*c87b03e5Sespie 
1824*c87b03e5Sespie       if (GET_CODE (first) != NOTE && GET_CODE (first) != BARRIER)
1825*c87b03e5Sespie 	{
1826*c87b03e5Sespie 	  c = new_insn_chain ();
1827*c87b03e5Sespie 	  c->prev = prev;
1828*c87b03e5Sespie 	  prev = c;
1829*c87b03e5Sespie 	  *p = c;
1830*c87b03e5Sespie 	  p = &c->next;
1831*c87b03e5Sespie 	  c->insn = first;
1832*c87b03e5Sespie 	  c->block = b->index;
1833*c87b03e5Sespie 
1834*c87b03e5Sespie 	  if (INSN_P (first))
1835*c87b03e5Sespie 	    {
1836*c87b03e5Sespie 	      rtx link;
1837*c87b03e5Sespie 
1838*c87b03e5Sespie 	      /* Mark the death of everything that dies in this instruction.  */
1839*c87b03e5Sespie 
1840*c87b03e5Sespie 	      for (link = REG_NOTES (first); link; link = XEXP (link, 1))
1841*c87b03e5Sespie 		if (REG_NOTE_KIND (link) == REG_DEAD
1842*c87b03e5Sespie 		    && GET_CODE (XEXP (link, 0)) == REG)
1843*c87b03e5Sespie 		  reg_dies (REGNO (XEXP (link, 0)), GET_MODE (XEXP (link, 0)),
1844*c87b03e5Sespie 			    c);
1845*c87b03e5Sespie 
1846*c87b03e5Sespie 	      COPY_REG_SET (&c->live_throughout, live_relevant_regs);
1847*c87b03e5Sespie 
1848*c87b03e5Sespie 	      /* Mark everything born in this instruction as live.  */
1849*c87b03e5Sespie 
1850*c87b03e5Sespie 	      note_stores (PATTERN (first), reg_becomes_live,
1851*c87b03e5Sespie 			   &c->dead_or_set);
1852*c87b03e5Sespie 	    }
1853*c87b03e5Sespie 	  else
1854*c87b03e5Sespie 	    COPY_REG_SET (&c->live_throughout, live_relevant_regs);
1855*c87b03e5Sespie 
1856*c87b03e5Sespie 	  if (INSN_P (first))
1857*c87b03e5Sespie 	    {
1858*c87b03e5Sespie 	      rtx link;
1859*c87b03e5Sespie 
1860*c87b03e5Sespie 	      /* Mark anything that is set in this insn and then unused as dying.  */
1861*c87b03e5Sespie 
1862*c87b03e5Sespie 	      for (link = REG_NOTES (first); link; link = XEXP (link, 1))
1863*c87b03e5Sespie 		if (REG_NOTE_KIND (link) == REG_UNUSED
1864*c87b03e5Sespie 		    && GET_CODE (XEXP (link, 0)) == REG)
1865*c87b03e5Sespie 		  reg_dies (REGNO (XEXP (link, 0)), GET_MODE (XEXP (link, 0)),
1866*c87b03e5Sespie 			    c);
1867*c87b03e5Sespie 	    }
1868*c87b03e5Sespie 	}
1869*c87b03e5Sespie 
1870*c87b03e5Sespie       if (first == b->end)
1871*c87b03e5Sespie 	b = b->next_bb;
1872*c87b03e5Sespie 
1873*c87b03e5Sespie       /* Stop after we pass the end of the last basic block.  Verify that
1874*c87b03e5Sespie 	 no real insns are after the end of the last basic block.
1875*c87b03e5Sespie 
1876*c87b03e5Sespie 	 We may want to reorganize the loop somewhat since this test should
1877*c87b03e5Sespie 	 always be the right exit test.  Allow an ADDR_VEC or ADDR_DIF_VEC if
1878*c87b03e5Sespie 	 the previous real insn is a JUMP_INSN.  */
1879*c87b03e5Sespie       if (b == EXIT_BLOCK_PTR)
1880*c87b03e5Sespie 	{
1881*c87b03e5Sespie 	  for (first = NEXT_INSN (first) ; first; first = NEXT_INSN (first))
1882*c87b03e5Sespie 	    if (INSN_P (first)
1883*c87b03e5Sespie 		&& GET_CODE (PATTERN (first)) != USE
1884*c87b03e5Sespie 		&& ! ((GET_CODE (PATTERN (first)) == ADDR_VEC
1885*c87b03e5Sespie 		       || GET_CODE (PATTERN (first)) == ADDR_DIFF_VEC)
1886*c87b03e5Sespie 		      && prev_real_insn (first) != 0
1887*c87b03e5Sespie 		      && GET_CODE (prev_real_insn (first)) == JUMP_INSN))
1888*c87b03e5Sespie 	      abort ();
1889*c87b03e5Sespie 	  break;
1890*c87b03e5Sespie 	}
1891*c87b03e5Sespie     }
1892*c87b03e5Sespie   FREE_REG_SET (live_relevant_regs);
1893*c87b03e5Sespie   *p = 0;
1894*c87b03e5Sespie }
1895*c87b03e5Sespie 
1896*c87b03e5Sespie /* Print debugging trace information if -dg switch is given,
1897*c87b03e5Sespie    showing the information on which the allocation decisions are based.  */
1898*c87b03e5Sespie 
1899*c87b03e5Sespie static void
dump_conflicts(file)1900*c87b03e5Sespie dump_conflicts (file)
1901*c87b03e5Sespie      FILE *file;
1902*c87b03e5Sespie {
1903*c87b03e5Sespie   int i;
1904*c87b03e5Sespie   int has_preferences;
1905*c87b03e5Sespie   int nregs;
1906*c87b03e5Sespie   nregs = 0;
1907*c87b03e5Sespie   for (i = 0; i < max_allocno; i++)
1908*c87b03e5Sespie     {
1909*c87b03e5Sespie       if (reg_renumber[allocno[allocno_order[i]].reg] >= 0)
1910*c87b03e5Sespie 	continue;
1911*c87b03e5Sespie       nregs++;
1912*c87b03e5Sespie     }
1913*c87b03e5Sespie   fprintf (file, ";; %d regs to allocate:", nregs);
1914*c87b03e5Sespie   for (i = 0; i < max_allocno; i++)
1915*c87b03e5Sespie     {
1916*c87b03e5Sespie       int j;
1917*c87b03e5Sespie       if (reg_renumber[allocno[allocno_order[i]].reg] >= 0)
1918*c87b03e5Sespie 	continue;
1919*c87b03e5Sespie       fprintf (file, " %d", allocno[allocno_order[i]].reg);
1920*c87b03e5Sespie       for (j = 0; j < max_regno; j++)
1921*c87b03e5Sespie 	if (reg_allocno[j] == allocno_order[i]
1922*c87b03e5Sespie 	    && j != allocno[allocno_order[i]].reg)
1923*c87b03e5Sespie 	  fprintf (file, "+%d", j);
1924*c87b03e5Sespie       if (allocno[allocno_order[i]].size != 1)
1925*c87b03e5Sespie 	fprintf (file, " (%d)", allocno[allocno_order[i]].size);
1926*c87b03e5Sespie     }
1927*c87b03e5Sespie   fprintf (file, "\n");
1928*c87b03e5Sespie 
1929*c87b03e5Sespie   for (i = 0; i < max_allocno; i++)
1930*c87b03e5Sespie     {
1931*c87b03e5Sespie       int j;
1932*c87b03e5Sespie       fprintf (file, ";; %d conflicts:", allocno[i].reg);
1933*c87b03e5Sespie       for (j = 0; j < max_allocno; j++)
1934*c87b03e5Sespie 	if (CONFLICTP (j, i))
1935*c87b03e5Sespie 	  fprintf (file, " %d", allocno[j].reg);
1936*c87b03e5Sespie       for (j = 0; j < FIRST_PSEUDO_REGISTER; j++)
1937*c87b03e5Sespie 	if (TEST_HARD_REG_BIT (allocno[i].hard_reg_conflicts, j))
1938*c87b03e5Sespie 	  fprintf (file, " %d", j);
1939*c87b03e5Sespie       fprintf (file, "\n");
1940*c87b03e5Sespie 
1941*c87b03e5Sespie       has_preferences = 0;
1942*c87b03e5Sespie       for (j = 0; j < FIRST_PSEUDO_REGISTER; j++)
1943*c87b03e5Sespie 	if (TEST_HARD_REG_BIT (allocno[i].hard_reg_preferences, j))
1944*c87b03e5Sespie 	  has_preferences = 1;
1945*c87b03e5Sespie 
1946*c87b03e5Sespie       if (! has_preferences)
1947*c87b03e5Sespie 	continue;
1948*c87b03e5Sespie       fprintf (file, ";; %d preferences:", allocno[i].reg);
1949*c87b03e5Sespie       for (j = 0; j < FIRST_PSEUDO_REGISTER; j++)
1950*c87b03e5Sespie 	if (TEST_HARD_REG_BIT (allocno[i].hard_reg_preferences, j))
1951*c87b03e5Sespie 	  fprintf (file, " %d", j);
1952*c87b03e5Sespie       fprintf (file, "\n");
1953*c87b03e5Sespie     }
1954*c87b03e5Sespie   fprintf (file, "\n");
1955*c87b03e5Sespie }
1956*c87b03e5Sespie 
1957*c87b03e5Sespie void
dump_global_regs(file)1958*c87b03e5Sespie dump_global_regs (file)
1959*c87b03e5Sespie      FILE *file;
1960*c87b03e5Sespie {
1961*c87b03e5Sespie   int i, j;
1962*c87b03e5Sespie 
1963*c87b03e5Sespie   fprintf (file, ";; Register dispositions:\n");
1964*c87b03e5Sespie   for (i = FIRST_PSEUDO_REGISTER, j = 0; i < max_regno; i++)
1965*c87b03e5Sespie     if (reg_renumber[i] >= 0)
1966*c87b03e5Sespie       {
1967*c87b03e5Sespie 	fprintf (file, "%d in %d  ", i, reg_renumber[i]);
1968*c87b03e5Sespie 	if (++j % 6 == 0)
1969*c87b03e5Sespie 	  fprintf (file, "\n");
1970*c87b03e5Sespie       }
1971*c87b03e5Sespie 
1972*c87b03e5Sespie   fprintf (file, "\n\n;; Hard regs used: ");
1973*c87b03e5Sespie   for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
1974*c87b03e5Sespie     if (regs_ever_live[i])
1975*c87b03e5Sespie       fprintf (file, " %d", i);
1976*c87b03e5Sespie   fprintf (file, "\n\n");
1977*c87b03e5Sespie }
1978