reorg.c revision 117395
1162674Spiso/* Perform instruction reorganizations for delay slot filling.
2162674Spiso   Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998,
3162674Spiso   1999, 2000, 2001, 2002 Free Software Foundation, Inc.
4162674Spiso   Contributed by Richard Kenner (kenner@vlsi1.ultra.nyu.edu).
5162674Spiso   Hacked by Michael Tiemann (tiemann@cygnus.com).
6162674Spiso
7162674SpisoThis file is part of GCC.
8162674Spiso
9162674SpisoGCC is free software; you can redistribute it and/or modify it under
10162674Spisothe terms of the GNU General Public License as published by the Free
11162674SpisoSoftware Foundation; either version 2, or (at your option) any later
12162674Spisoversion.
13162674Spiso
14162674SpisoGCC is distributed in the hope that it will be useful, but WITHOUT ANY
15162674SpisoWARRANTY; without even the implied warranty of MERCHANTABILITY or
16162674SpisoFITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17162674Spisofor more details.
18162674Spiso
19162674SpisoYou should have received a copy of the GNU General Public License
20162674Spisoalong with GCC; see the file COPYING.  If not, write to the Free
21162674SpisoSoftware Foundation, 59 Temple Place - Suite 330, Boston, MA
22162674Spiso02111-1307, USA.  */
23162674Spiso
24162674Spiso/* Instruction reorganization pass.
25162674Spiso
26162674Spiso   This pass runs after register allocation and final jump
27162674Spiso   optimization.  It should be the last pass to run before peephole.
28162674Spiso   It serves primarily to fill delay slots of insns, typically branch
29162674Spiso   and call insns.  Other insns typically involve more complicated
30259858Sglebius   interactions of data dependencies and resource constraints, and
31162674Spiso   are better handled by scheduling before register allocation (by the
32162674Spiso   function `schedule_insns').
33162674Spiso
34162674Spiso   The Branch Penalty is the number of extra cycles that are needed to
35162674Spiso   execute a branch insn.  On an ideal machine, branches take a single
36162674Spiso   cycle, and the Branch Penalty is 0.  Several RISC machines approach
37162674Spiso   branch delays differently:
38162674Spiso
39162674Spiso   The MIPS and AMD 29000 have a single branch delay slot.  Most insns
40162674Spiso   (except other branches) can be used to fill this slot.  When the
41162674Spiso   slot is filled, two insns execute in two cycles, reducing the
42162674Spiso   branch penalty to zero.
43162674Spiso
44162674Spiso   The Motorola 88000 conditionally exposes its branch delay slot,
45162674Spiso   so code is shorter when it is turned off, but will run faster
46162674Spiso   when useful insns are scheduled there.
47162674Spiso
48162674Spiso   The IBM ROMP has two forms of branch and call insns, both with and
49162674Spiso   without a delay slot.  Much like the 88k, insns not using the delay
50162674Spiso   slot can be shorted (2 bytes vs. 4 bytes), but will run slowed.
51162674Spiso
52162674Spiso   The SPARC always has a branch delay slot, but its effects can be
53162674Spiso   annulled when the branch is not taken.  This means that failing to
54162674Spiso   find other sources of insns, we can hoist an insn from the branch
55162674Spiso   target that would only be safe to execute knowing that the branch
56162674Spiso   is taken.
57162674Spiso
58162674Spiso   The HP-PA always has a branch delay slot.  For unconditional branches
59162674Spiso   its effects can be annulled when the branch is taken.  The effects
60162674Spiso   of the delay slot in a conditional branch can be nullified for forward
61162674Spiso   taken branches, or for untaken backward branches.  This means
62259858Sglebius   we can hoist insns from the fall-through path for forward branches or
63190841Spiso   steal insns from the target of backward branches.
64162674Spiso
65162674Spiso   The TMS320C3x and C4x have three branch delay slots.  When the three
66259858Sglebius   slots are filled, the branch penalty is zero.  Most insns can fill the
67259858Sglebius   delay slots except jump insns.
68162674Spiso
69162674Spiso   Three techniques for filling delay slots have been implemented so far:
70259858Sglebius
71162674Spiso   (1) `fill_simple_delay_slots' is the simplest, most efficient way
72162674Spiso   to fill delay slots.  This pass first looks for insns which come
73259858Sglebius   from before the branch and which are safe to execute after the
74259858Sglebius   branch.  Then it searches after the insn requiring delay slots or,
75162674Spiso   in the case of a branch, for insns that are after the point at
76162674Spiso   which the branch merges into the fallthrough code, if such a point
77162674Spiso   exists.  When such insns are found, the branch penalty decreases
78162674Spiso   and no code expansion takes place.
79162674Spiso
80162674Spiso   (2) `fill_eager_delay_slots' is more complicated: it is used for
81162674Spiso   scheduling conditional jumps, or for scheduling jumps which cannot
82162674Spiso   be filled using (1).  A machine need not have annulled jumps to use
83259858Sglebius   this strategy, but it helps (by keeping more options open).
84259858Sglebius   `fill_eager_delay_slots' tries to guess the direction the branch
85162674Spiso   will go; if it guesses right 100% of the time, it can reduce the
86162674Spiso   branch penalty as much as `fill_simple_delay_slots' does.  If it
87162674Spiso   guesses wrong 100% of the time, it might as well schedule nops (or
88259858Sglebius   on the m88k, unexpose the branch slot).  When
89162674Spiso   `fill_eager_delay_slots' takes insns from the fall-through path of
90162674Spiso   the jump, usually there is no code expansion; when it takes insns
91162674Spiso   from the branch target, there is code expansion if it is not the
92162674Spiso   only way to reach that target.
93162674Spiso
94162674Spiso   (3) `relax_delay_slots' uses a set of rules to simplify code that
95162674Spiso   has been reorganized by (1) and (2).  It finds cases where
96259858Sglebius   conditional test can be eliminated, jumps can be threaded, extra
97259858Sglebius   insns can be eliminated, etc.  It is the job of (1) and (2) to do a
98259858Sglebius   good job of scheduling locally; `relax_delay_slots' takes care of
99162674Spiso   making the various individual schedules work well together.  It is
100259858Sglebius   especially tuned to handle the control flow interactions of branch
101162674Spiso   insns.  It does nothing for insns with delay slots that do not
102162674Spiso   branch.
103162674Spiso
104162674Spiso   On machines that use CC0, we are very conservative.  We will not make
105259858Sglebius   a copy of an insn involving CC0 since we want to maintain a 1-1
106259858Sglebius   correspondence between the insn that sets and uses CC0.  The insns are
107259858Sglebius   allowed to be separated by placing an insn that sets CC0 (but not an insn
108259858Sglebius   that uses CC0; we could do this, but it doesn't seem worthwhile) in a
109259858Sglebius   delay slot.  In that case, we point each insn at the other with REG_CC_USER
110162674Spiso   and REG_CC_SETTER notes.  Note that these restrictions affect very few
111259858Sglebius   machines because most RISC machines with delay slots will not use CC0
112162674Spiso   (the RT is the only known exception at this point).
113162674Spiso
114162674Spiso   Not yet implemented:
115162674Spiso
116162674Spiso   The Acorn Risc Machine can conditionally execute most insns, so
117162674Spiso   it is profitable to move single insns into a position to execute
118162674Spiso   based on the condition code of the previous insn.
119162674Spiso
120259858Sglebius   The HP-PA can conditionally nullify insns, providing a similar
121162674Spiso   effect to the ARM, differing mostly in which insn is "in charge".  */
122162674Spiso
123162674Spiso#include "config.h"
124162674Spiso#include "system.h"
125162674Spiso#include "toplev.h"
126162674Spiso#include "rtl.h"
127162674Spiso#include "tm_p.h"
128162674Spiso#include "expr.h"
129162674Spiso#include "function.h"
130162674Spiso#include "insn-config.h"
131162674Spiso#include "conditions.h"
132162674Spiso#include "hard-reg-set.h"
133162674Spiso#include "basic-block.h"
134162674Spiso#include "regs.h"
135162674Spiso#include "recog.h"
136162674Spiso#include "flags.h"
137162674Spiso#include "output.h"
138162674Spiso#include "obstack.h"
139162674Spiso#include "insn-attr.h"
140162674Spiso#include "resource.h"
141162674Spiso#include "except.h"
142162674Spiso#include "params.h"
143162674Spiso
144162674Spiso#ifdef DELAY_SLOTS
145162674Spiso
146162674Spiso#ifndef ANNUL_IFTRUE_SLOTS
147162674Spiso#define eligible_for_annul_true(INSN, SLOTS, TRIAL, FLAGS) 0
148162674Spiso#endif
149162674Spiso#ifndef ANNUL_IFFALSE_SLOTS
150162674Spiso#define eligible_for_annul_false(INSN, SLOTS, TRIAL, FLAGS) 0
151162674Spiso#endif
152162674Spiso
153162674Spiso/* Insns which have delay slots that have not yet been filled.  */
154
155static struct obstack unfilled_slots_obstack;
156static rtx *unfilled_firstobj;
157
158/* Define macros to refer to the first and last slot containing unfilled
159   insns.  These are used because the list may move and its address
160   should be recomputed at each use.  */
161
162#define unfilled_slots_base	\
163  ((rtx *) obstack_base (&unfilled_slots_obstack))
164
165#define unfilled_slots_next	\
166  ((rtx *) obstack_next_free (&unfilled_slots_obstack))
167
168/* Points to the label before the end of the function.  */
169static rtx end_of_function_label;
170
171/* Mapping between INSN_UID's and position in the code since INSN_UID's do
172   not always monotonically increase.  */
173static int *uid_to_ruid;
174
175/* Highest valid index in `uid_to_ruid'.  */
176static int max_uid;
177
178static int stop_search_p		PARAMS ((rtx, int));
179static int resource_conflicts_p		PARAMS ((struct resources *,
180					       struct resources *));
181static int insn_references_resource_p	PARAMS ((rtx, struct resources *, int));
182static int insn_sets_resource_p		PARAMS ((rtx, struct resources *, int));
183static rtx find_end_label		PARAMS ((void));
184static rtx emit_delay_sequence		PARAMS ((rtx, rtx, int));
185static rtx add_to_delay_list		PARAMS ((rtx, rtx));
186static rtx delete_from_delay_slot	PARAMS ((rtx));
187static void delete_scheduled_jump	PARAMS ((rtx));
188static void note_delay_statistics	PARAMS ((int, int));
189#if defined(ANNUL_IFFALSE_SLOTS) || defined(ANNUL_IFTRUE_SLOTS)
190static rtx optimize_skip		PARAMS ((rtx));
191#endif
192static int get_jump_flags		PARAMS ((rtx, rtx));
193static int rare_destination		PARAMS ((rtx));
194static int mostly_true_jump		PARAMS ((rtx, rtx));
195static rtx get_branch_condition		PARAMS ((rtx, rtx));
196static int condition_dominates_p	PARAMS ((rtx, rtx));
197static int redirect_with_delay_slots_safe_p PARAMS ((rtx, rtx, rtx));
198static int redirect_with_delay_list_safe_p PARAMS ((rtx, rtx, rtx));
199static int check_annul_list_true_false	PARAMS ((int, rtx));
200static rtx steal_delay_list_from_target PARAMS ((rtx, rtx, rtx, rtx,
201					       struct resources *,
202					       struct resources *,
203					       struct resources *,
204					       int, int *, int *, rtx *));
205static rtx steal_delay_list_from_fallthrough PARAMS ((rtx, rtx, rtx, rtx,
206						    struct resources *,
207						    struct resources *,
208						    struct resources *,
209						    int, int *, int *));
210static void try_merge_delay_insns	PARAMS ((rtx, rtx));
211static rtx redundant_insn		PARAMS ((rtx, rtx, rtx));
212static int own_thread_p			PARAMS ((rtx, rtx, int));
213static void update_block		PARAMS ((rtx, rtx));
214static int reorg_redirect_jump		PARAMS ((rtx, rtx));
215static void update_reg_dead_notes	PARAMS ((rtx, rtx));
216static void fix_reg_dead_note		PARAMS ((rtx, rtx));
217static void update_reg_unused_notes	PARAMS ((rtx, rtx));
218static void fill_simple_delay_slots	PARAMS ((int));
219static rtx fill_slots_from_thread	PARAMS ((rtx, rtx, rtx, rtx, int, int,
220					       int, int, int *, rtx));
221static void fill_eager_delay_slots	PARAMS ((void));
222static void relax_delay_slots		PARAMS ((rtx));
223#ifdef HAVE_return
224static void make_return_insns		PARAMS ((rtx));
225#endif
226
227/* Return TRUE if this insn should stop the search for insn to fill delay
228   slots.  LABELS_P indicates that labels should terminate the search.
229   In all cases, jumps terminate the search.  */
230
231static int
232stop_search_p (insn, labels_p)
233     rtx insn;
234     int labels_p;
235{
236  if (insn == 0)
237    return 1;
238
239  switch (GET_CODE (insn))
240    {
241    case NOTE:
242    case CALL_INSN:
243      return 0;
244
245    case CODE_LABEL:
246      return labels_p;
247
248    case JUMP_INSN:
249    case BARRIER:
250      return 1;
251
252    case INSN:
253      /* OK unless it contains a delay slot or is an `asm' insn of some type.
254	 We don't know anything about these.  */
255      return (GET_CODE (PATTERN (insn)) == SEQUENCE
256	      || GET_CODE (PATTERN (insn)) == ASM_INPUT
257	      || asm_noperands (PATTERN (insn)) >= 0);
258
259    default:
260      abort ();
261    }
262}
263
264/* Return TRUE if any resources are marked in both RES1 and RES2 or if either
265   resource set contains a volatile memory reference.  Otherwise, return FALSE.  */
266
267static int
268resource_conflicts_p (res1, res2)
269     struct resources *res1, *res2;
270{
271  if ((res1->cc && res2->cc) || (res1->memory && res2->memory)
272      || (res1->unch_memory && res2->unch_memory)
273      || res1->volatil || res2->volatil)
274    return 1;
275
276#ifdef HARD_REG_SET
277  return (res1->regs & res2->regs) != HARD_CONST (0);
278#else
279  {
280    int i;
281
282    for (i = 0; i < HARD_REG_SET_LONGS; i++)
283      if ((res1->regs[i] & res2->regs[i]) != 0)
284	return 1;
285    return 0;
286  }
287#endif
288}
289
290/* Return TRUE if any resource marked in RES, a `struct resources', is
291   referenced by INSN.  If INCLUDE_DELAYED_EFFECTS is set, return if the called
292   routine is using those resources.
293
294   We compute this by computing all the resources referenced by INSN and
295   seeing if this conflicts with RES.  It might be faster to directly check
296   ourselves, and this is the way it used to work, but it means duplicating
297   a large block of complex code.  */
298
299static int
300insn_references_resource_p (insn, res, include_delayed_effects)
301     rtx insn;
302     struct resources *res;
303     int include_delayed_effects;
304{
305  struct resources insn_res;
306
307  CLEAR_RESOURCE (&insn_res);
308  mark_referenced_resources (insn, &insn_res, include_delayed_effects);
309  return resource_conflicts_p (&insn_res, res);
310}
311
312/* Return TRUE if INSN modifies resources that are marked in RES.
313   INCLUDE_DELAYED_EFFECTS is set if the actions of that routine should be
314   included.   CC0 is only modified if it is explicitly set; see comments
315   in front of mark_set_resources for details.  */
316
317static int
318insn_sets_resource_p (insn, res, include_delayed_effects)
319     rtx insn;
320     struct resources *res;
321     int include_delayed_effects;
322{
323  struct resources insn_sets;
324
325  CLEAR_RESOURCE (&insn_sets);
326  mark_set_resources (insn, &insn_sets, 0, include_delayed_effects);
327  return resource_conflicts_p (&insn_sets, res);
328}
329
330/* Find a label at the end of the function or before a RETURN.  If there is
331   none, make one.  */
332
333static rtx
334find_end_label ()
335{
336  rtx insn;
337
338  /* If we found one previously, return it.  */
339  if (end_of_function_label)
340    return end_of_function_label;
341
342  /* Otherwise, see if there is a label at the end of the function.  If there
343     is, it must be that RETURN insns aren't needed, so that is our return
344     label and we don't have to do anything else.  */
345
346  insn = get_last_insn ();
347  while (GET_CODE (insn) == NOTE
348	 || (GET_CODE (insn) == INSN
349	     && (GET_CODE (PATTERN (insn)) == USE
350		 || GET_CODE (PATTERN (insn)) == CLOBBER)))
351    insn = PREV_INSN (insn);
352
353  /* When a target threads its epilogue we might already have a
354     suitable return insn.  If so put a label before it for the
355     end_of_function_label.  */
356  if (GET_CODE (insn) == BARRIER
357      && GET_CODE (PREV_INSN (insn)) == JUMP_INSN
358      && GET_CODE (PATTERN (PREV_INSN (insn))) == RETURN)
359    {
360      rtx temp = PREV_INSN (PREV_INSN (insn));
361      end_of_function_label = gen_label_rtx ();
362      LABEL_NUSES (end_of_function_label) = 0;
363
364      /* Put the label before an USE insns that may proceed the RETURN insn.  */
365      while (GET_CODE (temp) == USE)
366	temp = PREV_INSN (temp);
367
368      emit_label_after (end_of_function_label, temp);
369    }
370
371  else if (GET_CODE (insn) == CODE_LABEL)
372    end_of_function_label = insn;
373  else
374    {
375      end_of_function_label = gen_label_rtx ();
376      LABEL_NUSES (end_of_function_label) = 0;
377      /* If the basic block reorder pass moves the return insn to
378	 some other place try to locate it again and put our
379	 end_of_function_label there.  */
380      while (insn && ! (GET_CODE (insn) == JUMP_INSN
381		        && (GET_CODE (PATTERN (insn)) == RETURN)))
382	insn = PREV_INSN (insn);
383      if (insn)
384	{
385	  insn = PREV_INSN (insn);
386
387	  /* Put the label before an USE insns that may proceed the
388	     RETURN insn.  */
389	  while (GET_CODE (insn) == USE)
390	    insn = PREV_INSN (insn);
391
392	  emit_label_after (end_of_function_label, insn);
393	}
394      else
395	{
396	  /* Otherwise, make a new label and emit a RETURN and BARRIER,
397	     if needed.  */
398	  emit_label (end_of_function_label);
399#ifdef HAVE_return
400	  if (HAVE_return)
401	    {
402	      /* The return we make may have delay slots too.  */
403	      rtx insn = gen_return ();
404	      insn = emit_jump_insn (insn);
405	      emit_barrier ();
406	      if (num_delay_slots (insn) > 0)
407		obstack_ptr_grow (&unfilled_slots_obstack, insn);
408	    }
409#endif
410	}
411    }
412
413  /* Show one additional use for this label so it won't go away until
414     we are done.  */
415  ++LABEL_NUSES (end_of_function_label);
416
417  return end_of_function_label;
418}
419
420/* Put INSN and LIST together in a SEQUENCE rtx of LENGTH, and replace
421   the pattern of INSN with the SEQUENCE.
422
423   Chain the insns so that NEXT_INSN of each insn in the sequence points to
424   the next and NEXT_INSN of the last insn in the sequence points to
425   the first insn after the sequence.  Similarly for PREV_INSN.  This makes
426   it easier to scan all insns.
427
428   Returns the SEQUENCE that replaces INSN.  */
429
430static rtx
431emit_delay_sequence (insn, list, length)
432     rtx insn;
433     rtx list;
434     int length;
435{
436  int i = 1;
437  rtx li;
438  int had_barrier = 0;
439
440  /* Allocate the rtvec to hold the insns and the SEQUENCE.  */
441  rtvec seqv = rtvec_alloc (length + 1);
442  rtx seq = gen_rtx_SEQUENCE (VOIDmode, seqv);
443  rtx seq_insn = make_insn_raw (seq);
444  rtx first = get_insns ();
445  rtx last = get_last_insn ();
446
447  /* Make a copy of the insn having delay slots.  */
448  rtx delay_insn = copy_rtx (insn);
449
450  /* If INSN is followed by a BARRIER, delete the BARRIER since it will only
451     confuse further processing.  Update LAST in case it was the last insn.
452     We will put the BARRIER back in later.  */
453  if (NEXT_INSN (insn) && GET_CODE (NEXT_INSN (insn)) == BARRIER)
454    {
455      delete_related_insns (NEXT_INSN (insn));
456      last = get_last_insn ();
457      had_barrier = 1;
458    }
459
460  /* Splice our SEQUENCE into the insn stream where INSN used to be.  */
461  NEXT_INSN (seq_insn) = NEXT_INSN (insn);
462  PREV_INSN (seq_insn) = PREV_INSN (insn);
463
464  if (insn != last)
465    PREV_INSN (NEXT_INSN (seq_insn)) = seq_insn;
466
467  if (insn != first)
468    NEXT_INSN (PREV_INSN (seq_insn)) = seq_insn;
469
470  /* Note the calls to set_new_first_and_last_insn must occur after
471     SEQ_INSN has been completely spliced into the insn stream.
472
473     Otherwise CUR_INSN_UID will get set to an incorrect value because
474     set_new_first_and_last_insn will not find SEQ_INSN in the chain.  */
475  if (insn == last)
476    set_new_first_and_last_insn (first, seq_insn);
477
478  if (insn == first)
479    set_new_first_and_last_insn (seq_insn, last);
480
481  /* Build our SEQUENCE and rebuild the insn chain.  */
482  XVECEXP (seq, 0, 0) = delay_insn;
483  INSN_DELETED_P (delay_insn) = 0;
484  PREV_INSN (delay_insn) = PREV_INSN (seq_insn);
485
486  for (li = list; li; li = XEXP (li, 1), i++)
487    {
488      rtx tem = XEXP (li, 0);
489      rtx note, next;
490
491      /* Show that this copy of the insn isn't deleted.  */
492      INSN_DELETED_P (tem) = 0;
493
494      XVECEXP (seq, 0, i) = tem;
495      PREV_INSN (tem) = XVECEXP (seq, 0, i - 1);
496      NEXT_INSN (XVECEXP (seq, 0, i - 1)) = tem;
497
498      for (note = REG_NOTES (tem); note; note = next)
499	{
500	  next = XEXP (note, 1);
501	  switch (REG_NOTE_KIND (note))
502	    {
503	    case REG_DEAD:
504	      /* Remove any REG_DEAD notes because we can't rely on them now
505		 that the insn has been moved.  */
506	      remove_note (tem, note);
507	      break;
508
509	    case REG_LABEL:
510	      /* Keep the label reference count up to date.  */
511	      if (GET_CODE (XEXP (note, 0)) == CODE_LABEL)
512		LABEL_NUSES (XEXP (note, 0)) ++;
513	      break;
514
515	    default:
516	      break;
517	    }
518	}
519    }
520
521  NEXT_INSN (XVECEXP (seq, 0, length)) = NEXT_INSN (seq_insn);
522
523  /* If the previous insn is a SEQUENCE, update the NEXT_INSN pointer on the
524     last insn in that SEQUENCE to point to us.  Similarly for the first
525     insn in the following insn if it is a SEQUENCE.  */
526
527  if (PREV_INSN (seq_insn) && GET_CODE (PREV_INSN (seq_insn)) == INSN
528      && GET_CODE (PATTERN (PREV_INSN (seq_insn))) == SEQUENCE)
529    NEXT_INSN (XVECEXP (PATTERN (PREV_INSN (seq_insn)), 0,
530			XVECLEN (PATTERN (PREV_INSN (seq_insn)), 0) - 1))
531      = seq_insn;
532
533  if (NEXT_INSN (seq_insn) && GET_CODE (NEXT_INSN (seq_insn)) == INSN
534      && GET_CODE (PATTERN (NEXT_INSN (seq_insn))) == SEQUENCE)
535    PREV_INSN (XVECEXP (PATTERN (NEXT_INSN (seq_insn)), 0, 0)) = seq_insn;
536
537  /* If there used to be a BARRIER, put it back.  */
538  if (had_barrier)
539    emit_barrier_after (seq_insn);
540
541  if (i != length + 1)
542    abort ();
543
544  return seq_insn;
545}
546
547/* Add INSN to DELAY_LIST and return the head of the new list.  The list must
548   be in the order in which the insns are to be executed.  */
549
550static rtx
551add_to_delay_list (insn, delay_list)
552     rtx insn;
553     rtx delay_list;
554{
555  /* If we have an empty list, just make a new list element.  If
556     INSN has its block number recorded, clear it since we may
557     be moving the insn to a new block.  */
558
559  if (delay_list == 0)
560    {
561      clear_hashed_info_for_insn (insn);
562      return gen_rtx_INSN_LIST (VOIDmode, insn, NULL_RTX);
563    }
564
565  /* Otherwise this must be an INSN_LIST.  Add INSN to the end of the
566     list.  */
567  XEXP (delay_list, 1) = add_to_delay_list (insn, XEXP (delay_list, 1));
568
569  return delay_list;
570}
571
572/* Delete INSN from the delay slot of the insn that it is in, which may
573   produce an insn with no delay slots.  Return the new insn.  */
574
575static rtx
576delete_from_delay_slot (insn)
577     rtx insn;
578{
579  rtx trial, seq_insn, seq, prev;
580  rtx delay_list = 0;
581  int i;
582
583  /* We first must find the insn containing the SEQUENCE with INSN in its
584     delay slot.  Do this by finding an insn, TRIAL, where
585     PREV_INSN (NEXT_INSN (TRIAL)) != TRIAL.  */
586
587  for (trial = insn;
588       PREV_INSN (NEXT_INSN (trial)) == trial;
589       trial = NEXT_INSN (trial))
590    ;
591
592  seq_insn = PREV_INSN (NEXT_INSN (trial));
593  seq = PATTERN (seq_insn);
594
595  /* Create a delay list consisting of all the insns other than the one
596     we are deleting (unless we were the only one).  */
597  if (XVECLEN (seq, 0) > 2)
598    for (i = 1; i < XVECLEN (seq, 0); i++)
599      if (XVECEXP (seq, 0, i) != insn)
600	delay_list = add_to_delay_list (XVECEXP (seq, 0, i), delay_list);
601
602  /* Delete the old SEQUENCE, re-emit the insn that used to have the delay
603     list, and rebuild the delay list if non-empty.  */
604  prev = PREV_INSN (seq_insn);
605  trial = XVECEXP (seq, 0, 0);
606  delete_related_insns (seq_insn);
607  add_insn_after (trial, prev);
608
609  if (GET_CODE (trial) == JUMP_INSN
610      && (simplejump_p (trial) || GET_CODE (PATTERN (trial)) == RETURN))
611    emit_barrier_after (trial);
612
613  /* If there are any delay insns, remit them.  Otherwise clear the
614     annul flag.  */
615  if (delay_list)
616    trial = emit_delay_sequence (trial, delay_list, XVECLEN (seq, 0) - 2);
617  else if (GET_CODE (trial) == JUMP_INSN
618	   || GET_CODE (trial) == CALL_INSN
619	   || GET_CODE (trial) == INSN)
620    INSN_ANNULLED_BRANCH_P (trial) = 0;
621
622  INSN_FROM_TARGET_P (insn) = 0;
623
624  /* Show we need to fill this insn again.  */
625  obstack_ptr_grow (&unfilled_slots_obstack, trial);
626
627  return trial;
628}
629
630/* Delete INSN, a JUMP_INSN.  If it is a conditional jump, we must track down
631   the insn that sets CC0 for it and delete it too.  */
632
633static void
634delete_scheduled_jump (insn)
635     rtx insn;
636{
637  /* Delete the insn that sets cc0 for us.  On machines without cc0, we could
638     delete the insn that sets the condition code, but it is hard to find it.
639     Since this case is rare anyway, don't bother trying; there would likely
640     be other insns that became dead anyway, which we wouldn't know to
641     delete.  */
642
643#ifdef HAVE_cc0
644  if (reg_mentioned_p (cc0_rtx, insn))
645    {
646      rtx note = find_reg_note (insn, REG_CC_SETTER, NULL_RTX);
647
648      /* If a reg-note was found, it points to an insn to set CC0.  This
649	 insn is in the delay list of some other insn.  So delete it from
650	 the delay list it was in.  */
651      if (note)
652	{
653	  if (! FIND_REG_INC_NOTE (XEXP (note, 0), NULL_RTX)
654	      && sets_cc0_p (PATTERN (XEXP (note, 0))) == 1)
655	    delete_from_delay_slot (XEXP (note, 0));
656	}
657      else
658	{
659	  /* The insn setting CC0 is our previous insn, but it may be in
660	     a delay slot.  It will be the last insn in the delay slot, if
661	     it is.  */
662	  rtx trial = previous_insn (insn);
663	  if (GET_CODE (trial) == NOTE)
664	    trial = prev_nonnote_insn (trial);
665	  if (sets_cc0_p (PATTERN (trial)) != 1
666	      || FIND_REG_INC_NOTE (trial, NULL_RTX))
667	    return;
668	  if (PREV_INSN (NEXT_INSN (trial)) == trial)
669	    delete_related_insns (trial);
670	  else
671	    delete_from_delay_slot (trial);
672	}
673    }
674#endif
675
676  delete_related_insns (insn);
677}
678
679/* Counters for delay-slot filling.  */
680
681#define NUM_REORG_FUNCTIONS 2
682#define MAX_DELAY_HISTOGRAM 3
683#define MAX_REORG_PASSES 2
684
685static int num_insns_needing_delays[NUM_REORG_FUNCTIONS][MAX_REORG_PASSES];
686
687static int num_filled_delays[NUM_REORG_FUNCTIONS][MAX_DELAY_HISTOGRAM+1][MAX_REORG_PASSES];
688
689static int reorg_pass_number;
690
691static void
692note_delay_statistics (slots_filled, index)
693     int slots_filled, index;
694{
695  num_insns_needing_delays[index][reorg_pass_number]++;
696  if (slots_filled > MAX_DELAY_HISTOGRAM)
697    slots_filled = MAX_DELAY_HISTOGRAM;
698  num_filled_delays[index][slots_filled][reorg_pass_number]++;
699}
700
701#if defined(ANNUL_IFFALSE_SLOTS) || defined(ANNUL_IFTRUE_SLOTS)
702
703/* Optimize the following cases:
704
705   1.  When a conditional branch skips over only one instruction,
706       use an annulling branch and put that insn in the delay slot.
707       Use either a branch that annuls when the condition if true or
708       invert the test with a branch that annuls when the condition is
709       false.  This saves insns, since otherwise we must copy an insn
710       from the L1 target.
711
712        (orig)		 (skip)		(otherwise)
713	Bcc.n L1	Bcc',a L1	Bcc,a L1'
714	insn		insn		insn2
715      L1:	      L1:	      L1:
716	insn2		insn2		insn2
717	insn3		insn3	      L1':
718					insn3
719
720   2.  When a conditional branch skips over only one instruction,
721       and after that, it unconditionally branches somewhere else,
722       perform the similar optimization. This saves executing the
723       second branch in the case where the inverted condition is true.
724
725	Bcc.n L1	Bcc',a L2
726	insn		insn
727      L1:	      L1:
728	Bra L2		Bra L2
729
730   INSN is a JUMP_INSN.
731
732   This should be expanded to skip over N insns, where N is the number
733   of delay slots required.  */
734
735static rtx
736optimize_skip (insn)
737     rtx insn;
738{
739  rtx trial = next_nonnote_insn (insn);
740  rtx next_trial = next_active_insn (trial);
741  rtx delay_list = 0;
742  rtx target_label;
743  int flags;
744
745  flags = get_jump_flags (insn, JUMP_LABEL (insn));
746
747  if (trial == 0
748      || GET_CODE (trial) != INSN
749      || GET_CODE (PATTERN (trial)) == SEQUENCE
750      || recog_memoized (trial) < 0
751      || (! eligible_for_annul_false (insn, 0, trial, flags)
752	  && ! eligible_for_annul_true (insn, 0, trial, flags))
753      || can_throw_internal (trial))
754    return 0;
755
756  /* There are two cases where we are just executing one insn (we assume
757     here that a branch requires only one insn; this should be generalized
758     at some point):  Where the branch goes around a single insn or where
759     we have one insn followed by a branch to the same label we branch to.
760     In both of these cases, inverting the jump and annulling the delay
761     slot give the same effect in fewer insns.  */
762  if ((next_trial == next_active_insn (JUMP_LABEL (insn))
763       && ! (next_trial == 0 && current_function_epilogue_delay_list != 0))
764      || (next_trial != 0
765	  && GET_CODE (next_trial) == JUMP_INSN
766	  && JUMP_LABEL (insn) == JUMP_LABEL (next_trial)
767	  && (simplejump_p (next_trial)
768	      || GET_CODE (PATTERN (next_trial)) == RETURN)))
769    {
770      if (eligible_for_annul_false (insn, 0, trial, flags))
771	{
772	  if (invert_jump (insn, JUMP_LABEL (insn), 1))
773	    INSN_FROM_TARGET_P (trial) = 1;
774	  else if (! eligible_for_annul_true (insn, 0, trial, flags))
775	    return 0;
776	}
777
778      delay_list = add_to_delay_list (trial, NULL_RTX);
779      next_trial = next_active_insn (trial);
780      update_block (trial, trial);
781      delete_related_insns (trial);
782
783      /* Also, if we are targeting an unconditional
784	 branch, thread our jump to the target of that branch.  Don't
785	 change this into a RETURN here, because it may not accept what
786	 we have in the delay slot.  We'll fix this up later.  */
787      if (next_trial && GET_CODE (next_trial) == JUMP_INSN
788	  && (simplejump_p (next_trial)
789	      || GET_CODE (PATTERN (next_trial)) == RETURN))
790	{
791	  target_label = JUMP_LABEL (next_trial);
792	  if (target_label == 0)
793	    target_label = find_end_label ();
794
795	  /* Recompute the flags based on TARGET_LABEL since threading
796	     the jump to TARGET_LABEL may change the direction of the
797	     jump (which may change the circumstances in which the
798	     delay slot is nullified).  */
799	  flags = get_jump_flags (insn, target_label);
800	  if (eligible_for_annul_true (insn, 0, trial, flags))
801	    reorg_redirect_jump (insn, target_label);
802	}
803
804      INSN_ANNULLED_BRANCH_P (insn) = 1;
805    }
806
807  return delay_list;
808}
809#endif
810
811/*  Encode and return branch direction and prediction information for
812    INSN assuming it will jump to LABEL.
813
814    Non conditional branches return no direction information and
815    are predicted as very likely taken.  */
816
817static int
818get_jump_flags (insn, label)
819     rtx insn, label;
820{
821  int flags;
822
823  /* get_jump_flags can be passed any insn with delay slots, these may
824     be INSNs, CALL_INSNs, or JUMP_INSNs.  Only JUMP_INSNs have branch
825     direction information, and only if they are conditional jumps.
826
827     If LABEL is zero, then there is no way to determine the branch
828     direction.  */
829  if (GET_CODE (insn) == JUMP_INSN
830      && (condjump_p (insn) || condjump_in_parallel_p (insn))
831      && INSN_UID (insn) <= max_uid
832      && label != 0
833      && INSN_UID (label) <= max_uid)
834    flags
835      = (uid_to_ruid[INSN_UID (label)] > uid_to_ruid[INSN_UID (insn)])
836	 ? ATTR_FLAG_forward : ATTR_FLAG_backward;
837  /* No valid direction information.  */
838  else
839    flags = 0;
840
841  /* If insn is a conditional branch call mostly_true_jump to get
842     determine the branch prediction.
843
844     Non conditional branches are predicted as very likely taken.  */
845  if (GET_CODE (insn) == JUMP_INSN
846      && (condjump_p (insn) || condjump_in_parallel_p (insn)))
847    {
848      int prediction;
849
850      prediction = mostly_true_jump (insn, get_branch_condition (insn, label));
851      switch (prediction)
852	{
853	case 2:
854	  flags |= (ATTR_FLAG_very_likely | ATTR_FLAG_likely);
855	  break;
856	case 1:
857	  flags |= ATTR_FLAG_likely;
858	  break;
859	case 0:
860	  flags |= ATTR_FLAG_unlikely;
861	  break;
862	case -1:
863	  flags |= (ATTR_FLAG_very_unlikely | ATTR_FLAG_unlikely);
864	  break;
865
866	default:
867	  abort ();
868	}
869    }
870  else
871    flags |= (ATTR_FLAG_very_likely | ATTR_FLAG_likely);
872
873  return flags;
874}
875
876/* Return 1 if INSN is a destination that will be branched to rarely (the
877   return point of a function); return 2 if DEST will be branched to very
878   rarely (a call to a function that doesn't return).  Otherwise,
879   return 0.  */
880
881static int
882rare_destination (insn)
883     rtx insn;
884{
885  int jump_count = 0;
886  rtx next;
887
888  for (; insn; insn = next)
889    {
890      if (GET_CODE (insn) == INSN && GET_CODE (PATTERN (insn)) == SEQUENCE)
891	insn = XVECEXP (PATTERN (insn), 0, 0);
892
893      next = NEXT_INSN (insn);
894
895      switch (GET_CODE (insn))
896	{
897	case CODE_LABEL:
898	  return 0;
899	case BARRIER:
900	  /* A BARRIER can either be after a JUMP_INSN or a CALL_INSN.  We
901	     don't scan past JUMP_INSNs, so any barrier we find here must
902	     have been after a CALL_INSN and hence mean the call doesn't
903	     return.  */
904	  return 2;
905	case JUMP_INSN:
906	  if (GET_CODE (PATTERN (insn)) == RETURN)
907	    return 1;
908	  else if (simplejump_p (insn)
909		   && jump_count++ < 10)
910	    next = JUMP_LABEL (insn);
911	  else
912	    return 0;
913
914	default:
915	  break;
916	}
917    }
918
919  /* If we got here it means we hit the end of the function.  So this
920     is an unlikely destination.  */
921
922  return 1;
923}
924
925/* Return truth value of the statement that this branch
926   is mostly taken.  If we think that the branch is extremely likely
927   to be taken, we return 2.  If the branch is slightly more likely to be
928   taken, return 1.  If the branch is slightly less likely to be taken,
929   return 0 and if the branch is highly unlikely to be taken, return -1.
930
931   CONDITION, if nonzero, is the condition that JUMP_INSN is testing.  */
932
933static int
934mostly_true_jump (jump_insn, condition)
935     rtx jump_insn, condition;
936{
937  rtx target_label = JUMP_LABEL (jump_insn);
938  rtx insn, note;
939  int rare_dest = rare_destination (target_label);
940  int rare_fallthrough = rare_destination (NEXT_INSN (jump_insn));
941
942  /* If branch probabilities are available, then use that number since it
943     always gives a correct answer.  */
944  note = find_reg_note (jump_insn, REG_BR_PROB, 0);
945  if (note)
946    {
947      int prob = INTVAL (XEXP (note, 0));
948
949      if (prob >= REG_BR_PROB_BASE * 9 / 10)
950	return 2;
951      else if (prob >= REG_BR_PROB_BASE / 2)
952	return 1;
953      else if (prob >= REG_BR_PROB_BASE / 10)
954	return 0;
955      else
956	return -1;
957    }
958
959  /* ??? Ought to use estimate_probability instead.  */
960
961  /* If this is a branch outside a loop, it is highly unlikely.  */
962  if (GET_CODE (PATTERN (jump_insn)) == SET
963      && GET_CODE (SET_SRC (PATTERN (jump_insn))) == IF_THEN_ELSE
964      && ((GET_CODE (XEXP (SET_SRC (PATTERN (jump_insn)), 1)) == LABEL_REF
965	   && LABEL_OUTSIDE_LOOP_P (XEXP (SET_SRC (PATTERN (jump_insn)), 1)))
966	  || (GET_CODE (XEXP (SET_SRC (PATTERN (jump_insn)), 2)) == LABEL_REF
967	      && LABEL_OUTSIDE_LOOP_P (XEXP (SET_SRC (PATTERN (jump_insn)), 2)))))
968    return -1;
969
970  if (target_label)
971    {
972      /* If this is the test of a loop, it is very likely true.  We scan
973	 backwards from the target label.  If we find a NOTE_INSN_LOOP_BEG
974	 before the next real insn, we assume the branch is to the top of
975	 the loop.  */
976      for (insn = PREV_INSN (target_label);
977	   insn && GET_CODE (insn) == NOTE;
978	   insn = PREV_INSN (insn))
979	if (NOTE_LINE_NUMBER (insn) == NOTE_INSN_LOOP_BEG)
980	  return 2;
981
982      /* If this is a jump to the test of a loop, it is likely true.  We scan
983	 forwards from the target label.  If we find a NOTE_INSN_LOOP_VTOP
984	 before the next real insn, we assume the branch is to the loop branch
985	 test.  */
986      for (insn = NEXT_INSN (target_label);
987	   insn && GET_CODE (insn) == NOTE;
988	   insn = PREV_INSN (insn))
989	if (NOTE_LINE_NUMBER (insn) == NOTE_INSN_LOOP_VTOP)
990	  return 1;
991    }
992
993  /* Look at the relative rarities of the fallthrough and destination.  If
994     they differ, we can predict the branch that way.  */
995
996  switch (rare_fallthrough - rare_dest)
997    {
998    case -2:
999      return -1;
1000    case -1:
1001      return 0;
1002    case 0:
1003      break;
1004    case 1:
1005      return 1;
1006    case 2:
1007      return 2;
1008    }
1009
1010  /* If we couldn't figure out what this jump was, assume it won't be
1011     taken.  This should be rare.  */
1012  if (condition == 0)
1013    return 0;
1014
1015  /* EQ tests are usually false and NE tests are usually true.  Also,
1016     most quantities are positive, so we can make the appropriate guesses
1017     about signed comparisons against zero.  */
1018  switch (GET_CODE (condition))
1019    {
1020    case CONST_INT:
1021      /* Unconditional branch.  */
1022      return 1;
1023    case EQ:
1024      return 0;
1025    case NE:
1026      return 1;
1027    case LE:
1028    case LT:
1029      if (XEXP (condition, 1) == const0_rtx)
1030	return 0;
1031      break;
1032    case GE:
1033    case GT:
1034      if (XEXP (condition, 1) == const0_rtx)
1035	return 1;
1036      break;
1037
1038    default:
1039      break;
1040    }
1041
1042  /* Predict backward branches usually take, forward branches usually not.  If
1043     we don't know whether this is forward or backward, assume the branch
1044     will be taken, since most are.  */
1045  return (target_label == 0 || INSN_UID (jump_insn) > max_uid
1046	  || INSN_UID (target_label) > max_uid
1047	  || (uid_to_ruid[INSN_UID (jump_insn)]
1048	      > uid_to_ruid[INSN_UID (target_label)]));
1049}
1050
1051/* Return the condition under which INSN will branch to TARGET.  If TARGET
1052   is zero, return the condition under which INSN will return.  If INSN is
1053   an unconditional branch, return const_true_rtx.  If INSN isn't a simple
1054   type of jump, or it doesn't go to TARGET, return 0.  */
1055
1056static rtx
1057get_branch_condition (insn, target)
1058     rtx insn;
1059     rtx target;
1060{
1061  rtx pat = PATTERN (insn);
1062  rtx src;
1063
1064  if (condjump_in_parallel_p (insn))
1065    pat = XVECEXP (pat, 0, 0);
1066
1067  if (GET_CODE (pat) == RETURN)
1068    return target == 0 ? const_true_rtx : 0;
1069
1070  else if (GET_CODE (pat) != SET || SET_DEST (pat) != pc_rtx)
1071    return 0;
1072
1073  src = SET_SRC (pat);
1074  if (GET_CODE (src) == LABEL_REF && XEXP (src, 0) == target)
1075    return const_true_rtx;
1076
1077  else if (GET_CODE (src) == IF_THEN_ELSE
1078	   && ((target == 0 && GET_CODE (XEXP (src, 1)) == RETURN)
1079	       || (GET_CODE (XEXP (src, 1)) == LABEL_REF
1080		   && XEXP (XEXP (src, 1), 0) == target))
1081	   && XEXP (src, 2) == pc_rtx)
1082    return XEXP (src, 0);
1083
1084  else if (GET_CODE (src) == IF_THEN_ELSE
1085	   && ((target == 0 && GET_CODE (XEXP (src, 2)) == RETURN)
1086	       || (GET_CODE (XEXP (src, 2)) == LABEL_REF
1087		   && XEXP (XEXP (src, 2), 0) == target))
1088	   && XEXP (src, 1) == pc_rtx)
1089    {
1090      enum rtx_code rev;
1091      rev = reversed_comparison_code (XEXP (src, 0), insn);
1092      if (rev != UNKNOWN)
1093	return gen_rtx_fmt_ee (rev, GET_MODE (XEXP (src, 0)),
1094			       XEXP (XEXP (src, 0), 0),
1095			       XEXP (XEXP (src, 0), 1));
1096    }
1097
1098  return 0;
1099}
1100
1101/* Return nonzero if CONDITION is more strict than the condition of
1102   INSN, i.e., if INSN will always branch if CONDITION is true.  */
1103
1104static int
1105condition_dominates_p (condition, insn)
1106     rtx condition;
1107     rtx insn;
1108{
1109  rtx other_condition = get_branch_condition (insn, JUMP_LABEL (insn));
1110  enum rtx_code code = GET_CODE (condition);
1111  enum rtx_code other_code;
1112
1113  if (rtx_equal_p (condition, other_condition)
1114      || other_condition == const_true_rtx)
1115    return 1;
1116
1117  else if (condition == const_true_rtx || other_condition == 0)
1118    return 0;
1119
1120  other_code = GET_CODE (other_condition);
1121  if (GET_RTX_LENGTH (code) != 2 || GET_RTX_LENGTH (other_code) != 2
1122      || ! rtx_equal_p (XEXP (condition, 0), XEXP (other_condition, 0))
1123      || ! rtx_equal_p (XEXP (condition, 1), XEXP (other_condition, 1)))
1124    return 0;
1125
1126  return comparison_dominates_p (code, other_code);
1127}
1128
1129/* Return nonzero if redirecting JUMP to NEWLABEL does not invalidate
1130   any insns already in the delay slot of JUMP.  */
1131
1132static int
1133redirect_with_delay_slots_safe_p (jump, newlabel, seq)
1134     rtx jump, newlabel, seq;
1135{
1136  int flags, i;
1137  rtx pat = PATTERN (seq);
1138
1139  /* Make sure all the delay slots of this jump would still
1140     be valid after threading the jump.  If they are still
1141     valid, then return nonzero.  */
1142
1143  flags = get_jump_flags (jump, newlabel);
1144  for (i = 1; i < XVECLEN (pat, 0); i++)
1145    if (! (
1146#ifdef ANNUL_IFFALSE_SLOTS
1147	   (INSN_ANNULLED_BRANCH_P (jump)
1148	    && INSN_FROM_TARGET_P (XVECEXP (pat, 0, i)))
1149	   ? eligible_for_annul_false (jump, i - 1,
1150				       XVECEXP (pat, 0, i), flags) :
1151#endif
1152#ifdef ANNUL_IFTRUE_SLOTS
1153	   (INSN_ANNULLED_BRANCH_P (jump)
1154	    && ! INSN_FROM_TARGET_P (XVECEXP (pat, 0, i)))
1155	   ? eligible_for_annul_true (jump, i - 1,
1156				      XVECEXP (pat, 0, i), flags) :
1157#endif
1158	   eligible_for_delay (jump, i - 1, XVECEXP (pat, 0, i), flags)))
1159      break;
1160
1161  return (i == XVECLEN (pat, 0));
1162}
1163
1164/* Return nonzero if redirecting JUMP to NEWLABEL does not invalidate
1165   any insns we wish to place in the delay slot of JUMP.  */
1166
1167static int
1168redirect_with_delay_list_safe_p (jump, newlabel, delay_list)
1169     rtx jump, newlabel, delay_list;
1170{
1171  int flags, i;
1172  rtx li;
1173
1174  /* Make sure all the insns in DELAY_LIST would still be
1175     valid after threading the jump.  If they are still
1176     valid, then return nonzero.  */
1177
1178  flags = get_jump_flags (jump, newlabel);
1179  for (li = delay_list, i = 0; li; li = XEXP (li, 1), i++)
1180    if (! (
1181#ifdef ANNUL_IFFALSE_SLOTS
1182	   (INSN_ANNULLED_BRANCH_P (jump)
1183	    && INSN_FROM_TARGET_P (XEXP (li, 0)))
1184	   ? eligible_for_annul_false (jump, i, XEXP (li, 0), flags) :
1185#endif
1186#ifdef ANNUL_IFTRUE_SLOTS
1187	   (INSN_ANNULLED_BRANCH_P (jump)
1188	    && ! INSN_FROM_TARGET_P (XEXP (li, 0)))
1189	   ? eligible_for_annul_true (jump, i, XEXP (li, 0), flags) :
1190#endif
1191	   eligible_for_delay (jump, i, XEXP (li, 0), flags)))
1192      break;
1193
1194  return (li == NULL);
1195}
1196
1197/* DELAY_LIST is a list of insns that have already been placed into delay
1198   slots.  See if all of them have the same annulling status as ANNUL_TRUE_P.
1199   If not, return 0; otherwise return 1.  */
1200
1201static int
1202check_annul_list_true_false (annul_true_p, delay_list)
1203     int annul_true_p;
1204     rtx delay_list;
1205{
1206  rtx temp;
1207
1208  if (delay_list)
1209    {
1210      for (temp = delay_list; temp; temp = XEXP (temp, 1))
1211	{
1212	  rtx trial = XEXP (temp, 0);
1213
1214	  if ((annul_true_p && INSN_FROM_TARGET_P (trial))
1215	      || (!annul_true_p && !INSN_FROM_TARGET_P (trial)))
1216	    return 0;
1217	}
1218    }
1219
1220  return 1;
1221}
1222
1223/* INSN branches to an insn whose pattern SEQ is a SEQUENCE.  Given that
1224   the condition tested by INSN is CONDITION and the resources shown in
1225   OTHER_NEEDED are needed after INSN, see whether INSN can take all the insns
1226   from SEQ's delay list, in addition to whatever insns it may execute
1227   (in DELAY_LIST).   SETS and NEEDED are denote resources already set and
1228   needed while searching for delay slot insns.  Return the concatenated
1229   delay list if possible, otherwise, return 0.
1230
1231   SLOTS_TO_FILL is the total number of slots required by INSN, and
1232   PSLOTS_FILLED points to the number filled so far (also the number of
1233   insns in DELAY_LIST).  It is updated with the number that have been
1234   filled from the SEQUENCE, if any.
1235
1236   PANNUL_P points to a nonzero value if we already know that we need
1237   to annul INSN.  If this routine determines that annulling is needed,
1238   it may set that value nonzero.
1239
1240   PNEW_THREAD points to a location that is to receive the place at which
1241   execution should continue.  */
1242
1243static rtx
1244steal_delay_list_from_target (insn, condition, seq, delay_list,
1245			      sets, needed, other_needed,
1246			      slots_to_fill, pslots_filled, pannul_p,
1247			      pnew_thread)
1248     rtx insn, condition;
1249     rtx seq;
1250     rtx delay_list;
1251     struct resources *sets, *needed, *other_needed;
1252     int slots_to_fill;
1253     int *pslots_filled;
1254     int *pannul_p;
1255     rtx *pnew_thread;
1256{
1257  rtx temp;
1258  int slots_remaining = slots_to_fill - *pslots_filled;
1259  int total_slots_filled = *pslots_filled;
1260  rtx new_delay_list = 0;
1261  int must_annul = *pannul_p;
1262  int used_annul = 0;
1263  int i;
1264  struct resources cc_set;
1265
1266  /* We can't do anything if there are more delay slots in SEQ than we
1267     can handle, or if we don't know that it will be a taken branch.
1268     We know that it will be a taken branch if it is either an unconditional
1269     branch or a conditional branch with a stricter branch condition.
1270
1271     Also, exit if the branch has more than one set, since then it is computing
1272     other results that can't be ignored, e.g. the HPPA mov&branch instruction.
1273     ??? It may be possible to move other sets into INSN in addition to
1274     moving the instructions in the delay slots.
1275
1276     We can not steal the delay list if one of the instructions in the
1277     current delay_list modifies the condition codes and the jump in the
1278     sequence is a conditional jump. We can not do this because we can
1279     not change the direction of the jump because the condition codes
1280     will effect the direction of the jump in the sequence.  */
1281
1282  CLEAR_RESOURCE (&cc_set);
1283  for (temp = delay_list; temp; temp = XEXP (temp, 1))
1284    {
1285      rtx trial = XEXP (temp, 0);
1286
1287      mark_set_resources (trial, &cc_set, 0, MARK_SRC_DEST_CALL);
1288      if (insn_references_resource_p (XVECEXP (seq , 0, 0), &cc_set, 0))
1289	return delay_list;
1290    }
1291
1292  if (XVECLEN (seq, 0) - 1 > slots_remaining
1293      || ! condition_dominates_p (condition, XVECEXP (seq, 0, 0))
1294      || ! single_set (XVECEXP (seq, 0, 0)))
1295    return delay_list;
1296
1297#ifdef MD_CAN_REDIRECT_BRANCH
1298  /* On some targets, branches with delay slots can have a limited
1299     displacement.  Give the back end a chance to tell us we can't do
1300     this.  */
1301  if (! MD_CAN_REDIRECT_BRANCH (insn, XVECEXP (seq, 0, 0)))
1302    return delay_list;
1303#endif
1304
1305  for (i = 1; i < XVECLEN (seq, 0); i++)
1306    {
1307      rtx trial = XVECEXP (seq, 0, i);
1308      int flags;
1309
1310      if (insn_references_resource_p (trial, sets, 0)
1311	  || insn_sets_resource_p (trial, needed, 0)
1312	  || insn_sets_resource_p (trial, sets, 0)
1313#ifdef HAVE_cc0
1314	  /* If TRIAL sets CC0, we can't copy it, so we can't steal this
1315	     delay list.  */
1316	  || find_reg_note (trial, REG_CC_USER, NULL_RTX)
1317#endif
1318	  /* If TRIAL is from the fallthrough code of an annulled branch insn
1319	     in SEQ, we cannot use it.  */
1320	  || (INSN_ANNULLED_BRANCH_P (XVECEXP (seq, 0, 0))
1321	      && ! INSN_FROM_TARGET_P (trial)))
1322	return delay_list;
1323
1324      /* If this insn was already done (usually in a previous delay slot),
1325	 pretend we put it in our delay slot.  */
1326      if (redundant_insn (trial, insn, new_delay_list))
1327	continue;
1328
1329      /* We will end up re-vectoring this branch, so compute flags
1330	 based on jumping to the new label.  */
1331      flags = get_jump_flags (insn, JUMP_LABEL (XVECEXP (seq, 0, 0)));
1332
1333      if (! must_annul
1334	  && ((condition == const_true_rtx
1335	       || (! insn_sets_resource_p (trial, other_needed, 0)
1336		   && ! may_trap_p (PATTERN (trial)))))
1337	  ? eligible_for_delay (insn, total_slots_filled, trial, flags)
1338	  : (must_annul || (delay_list == NULL && new_delay_list == NULL))
1339	     && (must_annul = 1,
1340	         check_annul_list_true_false (0, delay_list)
1341	         && check_annul_list_true_false (0, new_delay_list)
1342	         && eligible_for_annul_false (insn, total_slots_filled,
1343					      trial, flags)))
1344	{
1345	  if (must_annul)
1346	    used_annul = 1;
1347	  temp = copy_rtx (trial);
1348	  INSN_FROM_TARGET_P (temp) = 1;
1349	  new_delay_list = add_to_delay_list (temp, new_delay_list);
1350	  total_slots_filled++;
1351
1352	  if (--slots_remaining == 0)
1353	    break;
1354	}
1355      else
1356	return delay_list;
1357    }
1358
1359  /* Show the place to which we will be branching.  */
1360  *pnew_thread = next_active_insn (JUMP_LABEL (XVECEXP (seq, 0, 0)));
1361
1362  /* Add any new insns to the delay list and update the count of the
1363     number of slots filled.  */
1364  *pslots_filled = total_slots_filled;
1365  if (used_annul)
1366    *pannul_p = 1;
1367
1368  if (delay_list == 0)
1369    return new_delay_list;
1370
1371  for (temp = new_delay_list; temp; temp = XEXP (temp, 1))
1372    delay_list = add_to_delay_list (XEXP (temp, 0), delay_list);
1373
1374  return delay_list;
1375}
1376
1377/* Similar to steal_delay_list_from_target except that SEQ is on the
1378   fallthrough path of INSN.  Here we only do something if the delay insn
1379   of SEQ is an unconditional branch.  In that case we steal its delay slot
1380   for INSN since unconditional branches are much easier to fill.  */
1381
1382static rtx
1383steal_delay_list_from_fallthrough (insn, condition, seq,
1384				   delay_list, sets, needed, other_needed,
1385				   slots_to_fill, pslots_filled, pannul_p)
1386     rtx insn, condition;
1387     rtx seq;
1388     rtx delay_list;
1389     struct resources *sets, *needed, *other_needed;
1390     int slots_to_fill;
1391     int *pslots_filled;
1392     int *pannul_p;
1393{
1394  int i;
1395  int flags;
1396  int must_annul = *pannul_p;
1397  int used_annul = 0;
1398
1399  flags = get_jump_flags (insn, JUMP_LABEL (insn));
1400
1401  /* We can't do anything if SEQ's delay insn isn't an
1402     unconditional branch.  */
1403
1404  if (! simplejump_p (XVECEXP (seq, 0, 0))
1405      && GET_CODE (PATTERN (XVECEXP (seq, 0, 0))) != RETURN)
1406    return delay_list;
1407
1408  for (i = 1; i < XVECLEN (seq, 0); i++)
1409    {
1410      rtx trial = XVECEXP (seq, 0, i);
1411
1412      /* If TRIAL sets CC0, stealing it will move it too far from the use
1413	 of CC0.  */
1414      if (insn_references_resource_p (trial, sets, 0)
1415	  || insn_sets_resource_p (trial, needed, 0)
1416	  || insn_sets_resource_p (trial, sets, 0)
1417#ifdef HAVE_cc0
1418	  || sets_cc0_p (PATTERN (trial))
1419#endif
1420	  )
1421
1422	break;
1423
1424      /* If this insn was already done, we don't need it.  */
1425      if (redundant_insn (trial, insn, delay_list))
1426	{
1427	  delete_from_delay_slot (trial);
1428	  continue;
1429	}
1430
1431      if (! must_annul
1432	  && ((condition == const_true_rtx
1433	       || (! insn_sets_resource_p (trial, other_needed, 0)
1434		   && ! may_trap_p (PATTERN (trial)))))
1435	  ? eligible_for_delay (insn, *pslots_filled, trial, flags)
1436	  : (must_annul || delay_list == NULL) && (must_annul = 1,
1437	     check_annul_list_true_false (1, delay_list)
1438	     && eligible_for_annul_true (insn, *pslots_filled, trial, flags)))
1439	{
1440	  if (must_annul)
1441	    used_annul = 1;
1442	  delete_from_delay_slot (trial);
1443	  delay_list = add_to_delay_list (trial, delay_list);
1444
1445	  if (++(*pslots_filled) == slots_to_fill)
1446	    break;
1447	}
1448      else
1449	break;
1450    }
1451
1452  if (used_annul)
1453    *pannul_p = 1;
1454  return delay_list;
1455}
1456
1457/* Try merging insns starting at THREAD which match exactly the insns in
1458   INSN's delay list.
1459
1460   If all insns were matched and the insn was previously annulling, the
1461   annul bit will be cleared.
1462
1463   For each insn that is merged, if the branch is or will be non-annulling,
1464   we delete the merged insn.  */
1465
1466static void
1467try_merge_delay_insns (insn, thread)
1468     rtx insn, thread;
1469{
1470  rtx trial, next_trial;
1471  rtx delay_insn = XVECEXP (PATTERN (insn), 0, 0);
1472  int annul_p = INSN_ANNULLED_BRANCH_P (delay_insn);
1473  int slot_number = 1;
1474  int num_slots = XVECLEN (PATTERN (insn), 0);
1475  rtx next_to_match = XVECEXP (PATTERN (insn), 0, slot_number);
1476  struct resources set, needed;
1477  rtx merged_insns = 0;
1478  int i;
1479  int flags;
1480
1481  flags = get_jump_flags (delay_insn, JUMP_LABEL (delay_insn));
1482
1483  CLEAR_RESOURCE (&needed);
1484  CLEAR_RESOURCE (&set);
1485
1486  /* If this is not an annulling branch, take into account anything needed in
1487     INSN's delay slot.  This prevents two increments from being incorrectly
1488     folded into one.  If we are annulling, this would be the correct
1489     thing to do.  (The alternative, looking at things set in NEXT_TO_MATCH
1490     will essentially disable this optimization.  This method is somewhat of
1491     a kludge, but I don't see a better way.)  */
1492  if (! annul_p)
1493    for (i = 1 ; i < num_slots; i++)
1494      if (XVECEXP (PATTERN (insn), 0, i))
1495	mark_referenced_resources (XVECEXP (PATTERN (insn), 0, i), &needed, 1);
1496
1497  for (trial = thread; !stop_search_p (trial, 1); trial = next_trial)
1498    {
1499      rtx pat = PATTERN (trial);
1500      rtx oldtrial = trial;
1501
1502      next_trial = next_nonnote_insn (trial);
1503
1504      /* TRIAL must be a CALL_INSN or INSN.  Skip USE and CLOBBER.  */
1505      if (GET_CODE (trial) == INSN
1506	  && (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER))
1507	continue;
1508
1509      if (GET_CODE (next_to_match) == GET_CODE (trial)
1510#ifdef HAVE_cc0
1511	  /* We can't share an insn that sets cc0.  */
1512	  && ! sets_cc0_p (pat)
1513#endif
1514	  && ! insn_references_resource_p (trial, &set, 1)
1515	  && ! insn_sets_resource_p (trial, &set, 1)
1516	  && ! insn_sets_resource_p (trial, &needed, 1)
1517	  && (trial = try_split (pat, trial, 0)) != 0
1518	  /* Update next_trial, in case try_split succeeded.  */
1519	  && (next_trial = next_nonnote_insn (trial))
1520	  /* Likewise THREAD.  */
1521	  && (thread = oldtrial == thread ? trial : thread)
1522	  && rtx_equal_p (PATTERN (next_to_match), PATTERN (trial))
1523	  /* Have to test this condition if annul condition is different
1524	     from (and less restrictive than) non-annulling one.  */
1525	  && eligible_for_delay (delay_insn, slot_number - 1, trial, flags))
1526	{
1527
1528	  if (! annul_p)
1529	    {
1530	      update_block (trial, thread);
1531	      if (trial == thread)
1532		thread = next_active_insn (thread);
1533
1534	      delete_related_insns (trial);
1535	      INSN_FROM_TARGET_P (next_to_match) = 0;
1536	    }
1537	  else
1538	    merged_insns = gen_rtx_INSN_LIST (VOIDmode, trial, merged_insns);
1539
1540	  if (++slot_number == num_slots)
1541	    break;
1542
1543	  next_to_match = XVECEXP (PATTERN (insn), 0, slot_number);
1544	}
1545
1546      mark_set_resources (trial, &set, 0, MARK_SRC_DEST_CALL);
1547      mark_referenced_resources (trial, &needed, 1);
1548    }
1549
1550  /* See if we stopped on a filled insn.  If we did, try to see if its
1551     delay slots match.  */
1552  if (slot_number != num_slots
1553      && trial && GET_CODE (trial) == INSN
1554      && GET_CODE (PATTERN (trial)) == SEQUENCE
1555      && ! INSN_ANNULLED_BRANCH_P (XVECEXP (PATTERN (trial), 0, 0)))
1556    {
1557      rtx pat = PATTERN (trial);
1558      rtx filled_insn = XVECEXP (pat, 0, 0);
1559
1560      /* Account for resources set/needed by the filled insn.  */
1561      mark_set_resources (filled_insn, &set, 0, MARK_SRC_DEST_CALL);
1562      mark_referenced_resources (filled_insn, &needed, 1);
1563
1564      for (i = 1; i < XVECLEN (pat, 0); i++)
1565	{
1566	  rtx dtrial = XVECEXP (pat, 0, i);
1567
1568	  if (! insn_references_resource_p (dtrial, &set, 1)
1569	      && ! insn_sets_resource_p (dtrial, &set, 1)
1570	      && ! insn_sets_resource_p (dtrial, &needed, 1)
1571#ifdef HAVE_cc0
1572	      && ! sets_cc0_p (PATTERN (dtrial))
1573#endif
1574	      && rtx_equal_p (PATTERN (next_to_match), PATTERN (dtrial))
1575	      && eligible_for_delay (delay_insn, slot_number - 1, dtrial, flags))
1576	    {
1577	      if (! annul_p)
1578		{
1579		  rtx new;
1580
1581		  update_block (dtrial, thread);
1582		  new = delete_from_delay_slot (dtrial);
1583	          if (INSN_DELETED_P (thread))
1584		    thread = new;
1585		  INSN_FROM_TARGET_P (next_to_match) = 0;
1586		}
1587	      else
1588		merged_insns = gen_rtx_INSN_LIST (SImode, dtrial,
1589						  merged_insns);
1590
1591	      if (++slot_number == num_slots)
1592		break;
1593
1594	      next_to_match = XVECEXP (PATTERN (insn), 0, slot_number);
1595	    }
1596	  else
1597	    {
1598	      /* Keep track of the set/referenced resources for the delay
1599		 slots of any trial insns we encounter.  */
1600	      mark_set_resources (dtrial, &set, 0, MARK_SRC_DEST_CALL);
1601	      mark_referenced_resources (dtrial, &needed, 1);
1602	    }
1603	}
1604    }
1605
1606  /* If all insns in the delay slot have been matched and we were previously
1607     annulling the branch, we need not any more.  In that case delete all the
1608     merged insns.  Also clear the INSN_FROM_TARGET_P bit of each insn in
1609     the delay list so that we know that it isn't only being used at the
1610     target.  */
1611  if (slot_number == num_slots && annul_p)
1612    {
1613      for (; merged_insns; merged_insns = XEXP (merged_insns, 1))
1614	{
1615	  if (GET_MODE (merged_insns) == SImode)
1616	    {
1617	      rtx new;
1618
1619	      update_block (XEXP (merged_insns, 0), thread);
1620	      new = delete_from_delay_slot (XEXP (merged_insns, 0));
1621	      if (INSN_DELETED_P (thread))
1622		thread = new;
1623	    }
1624	  else
1625	    {
1626	      update_block (XEXP (merged_insns, 0), thread);
1627	      delete_related_insns (XEXP (merged_insns, 0));
1628	    }
1629	}
1630
1631      INSN_ANNULLED_BRANCH_P (delay_insn) = 0;
1632
1633      for (i = 0; i < XVECLEN (PATTERN (insn), 0); i++)
1634	INSN_FROM_TARGET_P (XVECEXP (PATTERN (insn), 0, i)) = 0;
1635    }
1636}
1637
1638/* See if INSN is redundant with an insn in front of TARGET.  Often this
1639   is called when INSN is a candidate for a delay slot of TARGET.
1640   DELAY_LIST are insns that will be placed in delay slots of TARGET in front
1641   of INSN.  Often INSN will be redundant with an insn in a delay slot of
1642   some previous insn.  This happens when we have a series of branches to the
1643   same label; in that case the first insn at the target might want to go
1644   into each of the delay slots.
1645
1646   If we are not careful, this routine can take up a significant fraction
1647   of the total compilation time (4%), but only wins rarely.  Hence we
1648   speed this routine up by making two passes.  The first pass goes back
1649   until it hits a label and sees if it find an insn with an identical
1650   pattern.  Only in this (relatively rare) event does it check for
1651   data conflicts.
1652
1653   We do not split insns we encounter.  This could cause us not to find a
1654   redundant insn, but the cost of splitting seems greater than the possible
1655   gain in rare cases.  */
1656
1657static rtx
1658redundant_insn (insn, target, delay_list)
1659     rtx insn;
1660     rtx target;
1661     rtx delay_list;
1662{
1663  rtx target_main = target;
1664  rtx ipat = PATTERN (insn);
1665  rtx trial, pat;
1666  struct resources needed, set;
1667  int i;
1668  unsigned insns_to_search;
1669
1670  /* If INSN has any REG_UNUSED notes, it can't match anything since we
1671     are allowed to not actually assign to such a register.  */
1672  if (find_reg_note (insn, REG_UNUSED, NULL_RTX) != 0)
1673    return 0;
1674
1675  /* Scan backwards looking for a match.  */
1676  for (trial = PREV_INSN (target),
1677	 insns_to_search = MAX_DELAY_SLOT_INSN_SEARCH;
1678       trial && insns_to_search > 0;
1679       trial = PREV_INSN (trial), --insns_to_search)
1680    {
1681      if (GET_CODE (trial) == CODE_LABEL)
1682	return 0;
1683
1684      if (! INSN_P (trial))
1685	continue;
1686
1687      pat = PATTERN (trial);
1688      if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER)
1689	continue;
1690
1691      if (GET_CODE (pat) == SEQUENCE)
1692	{
1693	  /* Stop for a CALL and its delay slots because it is difficult to
1694	     track its resource needs correctly.  */
1695	  if (GET_CODE (XVECEXP (pat, 0, 0)) == CALL_INSN)
1696	    return 0;
1697
1698	  /* Stop for an INSN or JUMP_INSN with delayed effects and its delay
1699	     slots because it is difficult to track its resource needs
1700	     correctly.  */
1701
1702#ifdef INSN_SETS_ARE_DELAYED
1703	  if (INSN_SETS_ARE_DELAYED (XVECEXP (pat, 0, 0)))
1704	    return 0;
1705#endif
1706
1707#ifdef INSN_REFERENCES_ARE_DELAYED
1708	  if (INSN_REFERENCES_ARE_DELAYED (XVECEXP (pat, 0, 0)))
1709	    return 0;
1710#endif
1711
1712	  /* See if any of the insns in the delay slot match, updating
1713	     resource requirements as we go.  */
1714	  for (i = XVECLEN (pat, 0) - 1; i > 0; i--)
1715	    if (GET_CODE (XVECEXP (pat, 0, i)) == GET_CODE (insn)
1716		&& rtx_equal_p (PATTERN (XVECEXP (pat, 0, i)), ipat)
1717		&& ! find_reg_note (XVECEXP (pat, 0, i), REG_UNUSED, NULL_RTX))
1718	      break;
1719
1720	  /* If found a match, exit this loop early.  */
1721	  if (i > 0)
1722	    break;
1723	}
1724
1725      else if (GET_CODE (trial) == GET_CODE (insn) && rtx_equal_p (pat, ipat)
1726	       && ! find_reg_note (trial, REG_UNUSED, NULL_RTX))
1727	break;
1728    }
1729
1730  /* If we didn't find an insn that matches, return 0.  */
1731  if (trial == 0)
1732    return 0;
1733
1734  /* See what resources this insn sets and needs.  If they overlap, or
1735     if this insn references CC0, it can't be redundant.  */
1736
1737  CLEAR_RESOURCE (&needed);
1738  CLEAR_RESOURCE (&set);
1739  mark_set_resources (insn, &set, 0, MARK_SRC_DEST_CALL);
1740  mark_referenced_resources (insn, &needed, 1);
1741
1742  /* If TARGET is a SEQUENCE, get the main insn.  */
1743  if (GET_CODE (target) == INSN && GET_CODE (PATTERN (target)) == SEQUENCE)
1744    target_main = XVECEXP (PATTERN (target), 0, 0);
1745
1746  if (resource_conflicts_p (&needed, &set)
1747#ifdef HAVE_cc0
1748      || reg_mentioned_p (cc0_rtx, ipat)
1749#endif
1750      /* The insn requiring the delay may not set anything needed or set by
1751	 INSN.  */
1752      || insn_sets_resource_p (target_main, &needed, 1)
1753      || insn_sets_resource_p (target_main, &set, 1))
1754    return 0;
1755
1756  /* Insns we pass may not set either NEEDED or SET, so merge them for
1757     simpler tests.  */
1758  needed.memory |= set.memory;
1759  needed.unch_memory |= set.unch_memory;
1760  IOR_HARD_REG_SET (needed.regs, set.regs);
1761
1762  /* This insn isn't redundant if it conflicts with an insn that either is
1763     or will be in a delay slot of TARGET.  */
1764
1765  while (delay_list)
1766    {
1767      if (insn_sets_resource_p (XEXP (delay_list, 0), &needed, 1))
1768	return 0;
1769      delay_list = XEXP (delay_list, 1);
1770    }
1771
1772  if (GET_CODE (target) == INSN && GET_CODE (PATTERN (target)) == SEQUENCE)
1773    for (i = 1; i < XVECLEN (PATTERN (target), 0); i++)
1774      if (insn_sets_resource_p (XVECEXP (PATTERN (target), 0, i), &needed, 1))
1775	return 0;
1776
1777  /* Scan backwards until we reach a label or an insn that uses something
1778     INSN sets or sets something insn uses or sets.  */
1779
1780  for (trial = PREV_INSN (target),
1781	 insns_to_search = MAX_DELAY_SLOT_INSN_SEARCH;
1782       trial && GET_CODE (trial) != CODE_LABEL && insns_to_search > 0;
1783       trial = PREV_INSN (trial), --insns_to_search)
1784    {
1785      if (GET_CODE (trial) != INSN && GET_CODE (trial) != CALL_INSN
1786	  && GET_CODE (trial) != JUMP_INSN)
1787	continue;
1788
1789      pat = PATTERN (trial);
1790      if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER)
1791	continue;
1792
1793      if (GET_CODE (pat) == SEQUENCE)
1794	{
1795	  /* If this is a CALL_INSN and its delay slots, it is hard to track
1796	     the resource needs properly, so give up.  */
1797	  if (GET_CODE (XVECEXP (pat, 0, 0)) == CALL_INSN)
1798	    return 0;
1799
1800	  /* If this is an INSN or JUMP_INSN with delayed effects, it
1801	     is hard to track the resource needs properly, so give up.  */
1802
1803#ifdef INSN_SETS_ARE_DELAYED
1804	  if (INSN_SETS_ARE_DELAYED (XVECEXP (pat, 0, 0)))
1805	    return 0;
1806#endif
1807
1808#ifdef INSN_REFERENCES_ARE_DELAYED
1809	  if (INSN_REFERENCES_ARE_DELAYED (XVECEXP (pat, 0, 0)))
1810	    return 0;
1811#endif
1812
1813	  /* See if any of the insns in the delay slot match, updating
1814	     resource requirements as we go.  */
1815	  for (i = XVECLEN (pat, 0) - 1; i > 0; i--)
1816	    {
1817	      rtx candidate = XVECEXP (pat, 0, i);
1818
1819	      /* If an insn will be annulled if the branch is false, it isn't
1820		 considered as a possible duplicate insn.  */
1821	      if (rtx_equal_p (PATTERN (candidate), ipat)
1822		  && ! (INSN_ANNULLED_BRANCH_P (XVECEXP (pat, 0, 0))
1823			&& INSN_FROM_TARGET_P (candidate)))
1824		{
1825		  /* Show that this insn will be used in the sequel.  */
1826		  INSN_FROM_TARGET_P (candidate) = 0;
1827		  return candidate;
1828		}
1829
1830	      /* Unless this is an annulled insn from the target of a branch,
1831		 we must stop if it sets anything needed or set by INSN.  */
1832	      if ((! INSN_ANNULLED_BRANCH_P (XVECEXP (pat, 0, 0))
1833		   || ! INSN_FROM_TARGET_P (candidate))
1834		  && insn_sets_resource_p (candidate, &needed, 1))
1835		return 0;
1836	    }
1837
1838	  /* If the insn requiring the delay slot conflicts with INSN, we
1839	     must stop.  */
1840	  if (insn_sets_resource_p (XVECEXP (pat, 0, 0), &needed, 1))
1841	    return 0;
1842	}
1843      else
1844	{
1845	  /* See if TRIAL is the same as INSN.  */
1846	  pat = PATTERN (trial);
1847	  if (rtx_equal_p (pat, ipat))
1848	    return trial;
1849
1850	  /* Can't go any further if TRIAL conflicts with INSN.  */
1851	  if (insn_sets_resource_p (trial, &needed, 1))
1852	    return 0;
1853	}
1854    }
1855
1856  return 0;
1857}
1858
1859/* Return 1 if THREAD can only be executed in one way.  If LABEL is nonzero,
1860   it is the target of the branch insn being scanned.  If ALLOW_FALLTHROUGH
1861   is nonzero, we are allowed to fall into this thread; otherwise, we are
1862   not.
1863
1864   If LABEL is used more than one or we pass a label other than LABEL before
1865   finding an active insn, we do not own this thread.  */
1866
1867static int
1868own_thread_p (thread, label, allow_fallthrough)
1869     rtx thread;
1870     rtx label;
1871     int allow_fallthrough;
1872{
1873  rtx active_insn;
1874  rtx insn;
1875
1876  /* We don't own the function end.  */
1877  if (thread == 0)
1878    return 0;
1879
1880  /* Get the first active insn, or THREAD, if it is an active insn.  */
1881  active_insn = next_active_insn (PREV_INSN (thread));
1882
1883  for (insn = thread; insn != active_insn; insn = NEXT_INSN (insn))
1884    if (GET_CODE (insn) == CODE_LABEL
1885	&& (insn != label || LABEL_NUSES (insn) != 1))
1886      return 0;
1887
1888  if (allow_fallthrough)
1889    return 1;
1890
1891  /* Ensure that we reach a BARRIER before any insn or label.  */
1892  for (insn = prev_nonnote_insn (thread);
1893       insn == 0 || GET_CODE (insn) != BARRIER;
1894       insn = prev_nonnote_insn (insn))
1895    if (insn == 0
1896	|| GET_CODE (insn) == CODE_LABEL
1897	|| (GET_CODE (insn) == INSN
1898	    && GET_CODE (PATTERN (insn)) != USE
1899	    && GET_CODE (PATTERN (insn)) != CLOBBER))
1900      return 0;
1901
1902  return 1;
1903}
1904
1905/* Called when INSN is being moved from a location near the target of a jump.
1906   We leave a marker of the form (use (INSN)) immediately in front
1907   of WHERE for mark_target_live_regs.  These markers will be deleted when
1908   reorg finishes.
1909
1910   We used to try to update the live status of registers if WHERE is at
1911   the start of a basic block, but that can't work since we may remove a
1912   BARRIER in relax_delay_slots.  */
1913
1914static void
1915update_block (insn, where)
1916     rtx insn;
1917     rtx where;
1918{
1919  /* Ignore if this was in a delay slot and it came from the target of
1920     a branch.  */
1921  if (INSN_FROM_TARGET_P (insn))
1922    return;
1923
1924  emit_insn_before (gen_rtx_USE (VOIDmode, insn), where);
1925
1926  /* INSN might be making a value live in a block where it didn't use to
1927     be.  So recompute liveness information for this block.  */
1928
1929  incr_ticks_for_insn (insn);
1930}
1931
1932/* Similar to REDIRECT_JUMP except that we update the BB_TICKS entry for
1933   the basic block containing the jump.  */
1934
1935static int
1936reorg_redirect_jump (jump, nlabel)
1937     rtx jump;
1938     rtx nlabel;
1939{
1940  incr_ticks_for_insn (jump);
1941  return redirect_jump (jump, nlabel, 1);
1942}
1943
1944/* Called when INSN is being moved forward into a delay slot of DELAYED_INSN.
1945   We check every instruction between INSN and DELAYED_INSN for REG_DEAD notes
1946   that reference values used in INSN.  If we find one, then we move the
1947   REG_DEAD note to INSN.
1948
1949   This is needed to handle the case where an later insn (after INSN) has a
1950   REG_DEAD note for a register used by INSN, and this later insn subsequently
1951   gets moved before a CODE_LABEL because it is a redundant insn.  In this
1952   case, mark_target_live_regs may be confused into thinking the register
1953   is dead because it sees a REG_DEAD note immediately before a CODE_LABEL.  */
1954
1955static void
1956update_reg_dead_notes (insn, delayed_insn)
1957     rtx insn, delayed_insn;
1958{
1959  rtx p, link, next;
1960
1961  for (p = next_nonnote_insn (insn); p != delayed_insn;
1962       p = next_nonnote_insn (p))
1963    for (link = REG_NOTES (p); link; link = next)
1964      {
1965	next = XEXP (link, 1);
1966
1967	if (REG_NOTE_KIND (link) != REG_DEAD
1968	    || GET_CODE (XEXP (link, 0)) != REG)
1969	  continue;
1970
1971	if (reg_referenced_p (XEXP (link, 0), PATTERN (insn)))
1972	  {
1973	    /* Move the REG_DEAD note from P to INSN.  */
1974	    remove_note (p, link);
1975	    XEXP (link, 1) = REG_NOTES (insn);
1976	    REG_NOTES (insn) = link;
1977	  }
1978      }
1979}
1980
1981/* Called when an insn redundant with start_insn is deleted.  If there
1982   is a REG_DEAD note for the target of start_insn between start_insn
1983   and stop_insn, then the REG_DEAD note needs to be deleted since the
1984   value no longer dies there.
1985
1986   If the REG_DEAD note isn't deleted, then mark_target_live_regs may be
1987   confused into thinking the register is dead.  */
1988
1989static void
1990fix_reg_dead_note (start_insn, stop_insn)
1991     rtx start_insn, stop_insn;
1992{
1993  rtx p, link, next;
1994
1995  for (p = next_nonnote_insn (start_insn); p != stop_insn;
1996       p = next_nonnote_insn (p))
1997    for (link = REG_NOTES (p); link; link = next)
1998      {
1999	next = XEXP (link, 1);
2000
2001	if (REG_NOTE_KIND (link) != REG_DEAD
2002	    || GET_CODE (XEXP (link, 0)) != REG)
2003	  continue;
2004
2005	if (reg_set_p (XEXP (link, 0), PATTERN (start_insn)))
2006	  {
2007	    remove_note (p, link);
2008	    return;
2009	  }
2010      }
2011}
2012
2013/* Delete any REG_UNUSED notes that exist on INSN but not on REDUNDANT_INSN.
2014
2015   This handles the case of udivmodXi4 instructions which optimize their
2016   output depending on whether any REG_UNUSED notes are present.
2017   we must make sure that INSN calculates as many results as REDUNDANT_INSN
2018   does.  */
2019
2020static void
2021update_reg_unused_notes (insn, redundant_insn)
2022     rtx insn, redundant_insn;
2023{
2024  rtx link, next;
2025
2026  for (link = REG_NOTES (insn); link; link = next)
2027    {
2028      next = XEXP (link, 1);
2029
2030      if (REG_NOTE_KIND (link) != REG_UNUSED
2031	  || GET_CODE (XEXP (link, 0)) != REG)
2032	continue;
2033
2034      if (! find_regno_note (redundant_insn, REG_UNUSED,
2035			     REGNO (XEXP (link, 0))))
2036	remove_note (insn, link);
2037    }
2038}
2039
2040/* Scan a function looking for insns that need a delay slot and find insns to
2041   put into the delay slot.
2042
2043   NON_JUMPS_P is nonzero if we are to only try to fill non-jump insns (such
2044   as calls).  We do these first since we don't want jump insns (that are
2045   easier to fill) to get the only insns that could be used for non-jump insns.
2046   When it is zero, only try to fill JUMP_INSNs.
2047
2048   When slots are filled in this manner, the insns (including the
2049   delay_insn) are put together in a SEQUENCE rtx.  In this fashion,
2050   it is possible to tell whether a delay slot has really been filled
2051   or not.  `final' knows how to deal with this, by communicating
2052   through FINAL_SEQUENCE.  */
2053
2054static void
2055fill_simple_delay_slots (non_jumps_p)
2056     int non_jumps_p;
2057{
2058  rtx insn, pat, trial, next_trial;
2059  int i;
2060  int num_unfilled_slots = unfilled_slots_next - unfilled_slots_base;
2061  struct resources needed, set;
2062  int slots_to_fill, slots_filled;
2063  rtx delay_list;
2064
2065  for (i = 0; i < num_unfilled_slots; i++)
2066    {
2067      int flags;
2068      /* Get the next insn to fill.  If it has already had any slots assigned,
2069	 we can't do anything with it.  Maybe we'll improve this later.  */
2070
2071      insn = unfilled_slots_base[i];
2072      if (insn == 0
2073	  || INSN_DELETED_P (insn)
2074	  || (GET_CODE (insn) == INSN
2075	      && GET_CODE (PATTERN (insn)) == SEQUENCE)
2076	  || (GET_CODE (insn) == JUMP_INSN && non_jumps_p)
2077	  || (GET_CODE (insn) != JUMP_INSN && ! non_jumps_p))
2078	continue;
2079
2080      /* It may have been that this insn used to need delay slots, but
2081	 now doesn't; ignore in that case.  This can happen, for example,
2082	 on the HP PA RISC, where the number of delay slots depends on
2083	 what insns are nearby.  */
2084      slots_to_fill = num_delay_slots (insn);
2085
2086      /* Some machine description have defined instructions to have
2087	 delay slots only in certain circumstances which may depend on
2088	 nearby insns (which change due to reorg's actions).
2089
2090	 For example, the PA port normally has delay slots for unconditional
2091	 jumps.
2092
2093	 However, the PA port claims such jumps do not have a delay slot
2094	 if they are immediate successors of certain CALL_INSNs.  This
2095	 allows the port to favor filling the delay slot of the call with
2096	 the unconditional jump.  */
2097      if (slots_to_fill == 0)
2098	continue;
2099
2100      /* This insn needs, or can use, some delay slots.  SLOTS_TO_FILL
2101	 says how many.  After initialization, first try optimizing
2102
2103	 call _foo		call _foo
2104	 nop			add %o7,.-L1,%o7
2105	 b,a L1
2106	 nop
2107
2108	 If this case applies, the delay slot of the call is filled with
2109	 the unconditional jump.  This is done first to avoid having the
2110	 delay slot of the call filled in the backward scan.  Also, since
2111	 the unconditional jump is likely to also have a delay slot, that
2112	 insn must exist when it is subsequently scanned.
2113
2114	 This is tried on each insn with delay slots as some machines
2115	 have insns which perform calls, but are not represented as
2116	 CALL_INSNs.  */
2117
2118      slots_filled = 0;
2119      delay_list = 0;
2120
2121      if (GET_CODE (insn) == JUMP_INSN)
2122	flags = get_jump_flags (insn, JUMP_LABEL (insn));
2123      else
2124	flags = get_jump_flags (insn, NULL_RTX);
2125
2126      if ((trial = next_active_insn (insn))
2127	  && GET_CODE (trial) == JUMP_INSN
2128	  && simplejump_p (trial)
2129	  && eligible_for_delay (insn, slots_filled, trial, flags)
2130	  && no_labels_between_p (insn, trial)
2131	  && ! can_throw_internal (trial))
2132	{
2133	  rtx *tmp;
2134	  slots_filled++;
2135	  delay_list = add_to_delay_list (trial, delay_list);
2136
2137	  /* TRIAL may have had its delay slot filled, then unfilled.  When
2138	     the delay slot is unfilled, TRIAL is placed back on the unfilled
2139	     slots obstack.  Unfortunately, it is placed on the end of the
2140	     obstack, not in its original location.  Therefore, we must search
2141	     from entry i + 1 to the end of the unfilled slots obstack to
2142	     try and find TRIAL.  */
2143	  tmp = &unfilled_slots_base[i + 1];
2144	  while (*tmp != trial && tmp != unfilled_slots_next)
2145	    tmp++;
2146
2147	  /* Remove the unconditional jump from consideration for delay slot
2148	     filling and unthread it.  */
2149	  if (*tmp == trial)
2150	    *tmp = 0;
2151	  {
2152	    rtx next = NEXT_INSN (trial);
2153	    rtx prev = PREV_INSN (trial);
2154	    if (prev)
2155	      NEXT_INSN (prev) = next;
2156	    if (next)
2157	      PREV_INSN (next) = prev;
2158	  }
2159	}
2160
2161      /* Now, scan backwards from the insn to search for a potential
2162	 delay-slot candidate.  Stop searching when a label or jump is hit.
2163
2164	 For each candidate, if it is to go into the delay slot (moved
2165	 forward in execution sequence), it must not need or set any resources
2166	 that were set by later insns and must not set any resources that
2167	 are needed for those insns.
2168
2169	 The delay slot insn itself sets resources unless it is a call
2170	 (in which case the called routine, not the insn itself, is doing
2171	 the setting).  */
2172
2173      if (slots_filled < slots_to_fill)
2174	{
2175	  CLEAR_RESOURCE (&needed);
2176	  CLEAR_RESOURCE (&set);
2177	  mark_set_resources (insn, &set, 0, MARK_SRC_DEST);
2178	  mark_referenced_resources (insn, &needed, 0);
2179
2180	  for (trial = prev_nonnote_insn (insn); ! stop_search_p (trial, 1);
2181	       trial = next_trial)
2182	    {
2183	      next_trial = prev_nonnote_insn (trial);
2184
2185	      /* This must be an INSN or CALL_INSN.  */
2186	      pat = PATTERN (trial);
2187
2188	      /* USE and CLOBBER at this level was just for flow; ignore it.  */
2189	      if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER)
2190		continue;
2191
2192	      /* Check for resource conflict first, to avoid unnecessary
2193		 splitting.  */
2194	      if (! insn_references_resource_p (trial, &set, 1)
2195		  && ! insn_sets_resource_p (trial, &set, 1)
2196		  && ! insn_sets_resource_p (trial, &needed, 1)
2197#ifdef HAVE_cc0
2198		  /* Can't separate set of cc0 from its use.  */
2199		  && ! (reg_mentioned_p (cc0_rtx, pat) && ! sets_cc0_p (pat))
2200#endif
2201		  && ! can_throw_internal (trial))
2202		{
2203		  trial = try_split (pat, trial, 1);
2204		  next_trial = prev_nonnote_insn (trial);
2205		  if (eligible_for_delay (insn, slots_filled, trial, flags))
2206		    {
2207		      /* In this case, we are searching backward, so if we
2208			 find insns to put on the delay list, we want
2209			 to put them at the head, rather than the
2210			 tail, of the list.  */
2211
2212		      update_reg_dead_notes (trial, insn);
2213		      delay_list = gen_rtx_INSN_LIST (VOIDmode,
2214						      trial, delay_list);
2215		      update_block (trial, trial);
2216		      delete_related_insns (trial);
2217		      if (slots_to_fill == ++slots_filled)
2218			break;
2219		      continue;
2220		    }
2221		}
2222
2223	      mark_set_resources (trial, &set, 0, MARK_SRC_DEST_CALL);
2224	      mark_referenced_resources (trial, &needed, 1);
2225	    }
2226	}
2227
2228      /* If all needed slots haven't been filled, we come here.  */
2229
2230      /* Try to optimize case of jumping around a single insn.  */
2231#if defined(ANNUL_IFFALSE_SLOTS) || defined(ANNUL_IFTRUE_SLOTS)
2232      if (slots_filled != slots_to_fill
2233	  && delay_list == 0
2234	  && GET_CODE (insn) == JUMP_INSN
2235	  && (condjump_p (insn) || condjump_in_parallel_p (insn)))
2236	{
2237	  delay_list = optimize_skip (insn);
2238	  if (delay_list)
2239	    slots_filled += 1;
2240	}
2241#endif
2242
2243      /* Try to get insns from beyond the insn needing the delay slot.
2244	 These insns can neither set or reference resources set in insns being
2245	 skipped, cannot set resources in the insn being skipped, and, if this
2246	 is a CALL_INSN (or a CALL_INSN is passed), cannot trap (because the
2247	 call might not return).
2248
2249	 There used to be code which continued past the target label if
2250	 we saw all uses of the target label.  This code did not work,
2251	 because it failed to account for some instructions which were
2252	 both annulled and marked as from the target.  This can happen as a
2253	 result of optimize_skip.  Since this code was redundant with
2254	 fill_eager_delay_slots anyways, it was just deleted.  */
2255
2256      if (slots_filled != slots_to_fill
2257	  /* If this instruction could throw an exception which is
2258	     caught in the same function, then it's not safe to fill
2259	     the delay slot with an instruction from beyond this
2260	     point.  For example, consider:
2261
2262               int i = 2;
2263
2264	       try {
2265                 f();
2266	         i = 3;
2267               } catch (...) {}
2268
2269               return i;
2270
2271	     Even though `i' is a local variable, we must be sure not
2272	     to put `i = 3' in the delay slot if `f' might throw an
2273	     exception.
2274
2275	     Presumably, we should also check to see if we could get
2276	     back to this function via `setjmp'.  */
2277	  && ! can_throw_internal (insn)
2278	  && (GET_CODE (insn) != JUMP_INSN
2279	      || ((condjump_p (insn) || condjump_in_parallel_p (insn))
2280		  && ! simplejump_p (insn)
2281		  && JUMP_LABEL (insn) != 0)))
2282	{
2283	  /* Invariant: If insn is a JUMP_INSN, the insn's jump
2284	     label.  Otherwise, zero.  */
2285	  rtx target = 0;
2286	  int maybe_never = 0;
2287	  rtx pat, trial_delay;
2288
2289	  CLEAR_RESOURCE (&needed);
2290	  CLEAR_RESOURCE (&set);
2291
2292	  if (GET_CODE (insn) == CALL_INSN)
2293	    {
2294	      mark_set_resources (insn, &set, 0, MARK_SRC_DEST_CALL);
2295	      mark_referenced_resources (insn, &needed, 1);
2296	      maybe_never = 1;
2297	    }
2298	  else
2299	    {
2300	      mark_set_resources (insn, &set, 0, MARK_SRC_DEST_CALL);
2301	      mark_referenced_resources (insn, &needed, 1);
2302	      if (GET_CODE (insn) == JUMP_INSN)
2303		target = JUMP_LABEL (insn);
2304	    }
2305
2306	  if (target == 0)
2307	    for (trial = next_nonnote_insn (insn); trial; trial = next_trial)
2308	      {
2309		next_trial = next_nonnote_insn (trial);
2310
2311		if (GET_CODE (trial) == CODE_LABEL
2312		    || GET_CODE (trial) == BARRIER)
2313		  break;
2314
2315		/* We must have an INSN, JUMP_INSN, or CALL_INSN.  */
2316		pat = PATTERN (trial);
2317
2318		/* Stand-alone USE and CLOBBER are just for flow.  */
2319		if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER)
2320		  continue;
2321
2322		/* If this already has filled delay slots, get the insn needing
2323		   the delay slots.  */
2324		if (GET_CODE (pat) == SEQUENCE)
2325		  trial_delay = XVECEXP (pat, 0, 0);
2326		else
2327		  trial_delay = trial;
2328
2329		/* Stop our search when seeing an unconditional jump.  */
2330		if (GET_CODE (trial_delay) == JUMP_INSN)
2331		  break;
2332
2333		/* See if we have a resource problem before we try to
2334		   split.  */
2335		if (GET_CODE (pat) != SEQUENCE
2336		    && ! insn_references_resource_p (trial, &set, 1)
2337		    && ! insn_sets_resource_p (trial, &set, 1)
2338		    && ! insn_sets_resource_p (trial, &needed, 1)
2339#ifdef HAVE_cc0
2340		    && ! (reg_mentioned_p (cc0_rtx, pat) && ! sets_cc0_p (pat))
2341#endif
2342		    && ! (maybe_never && may_trap_p (pat))
2343		    && (trial = try_split (pat, trial, 0))
2344		    && eligible_for_delay (insn, slots_filled, trial, flags)
2345		    && ! can_throw_internal(trial))
2346		  {
2347		    next_trial = next_nonnote_insn (trial);
2348		    delay_list = add_to_delay_list (trial, delay_list);
2349
2350#ifdef HAVE_cc0
2351		    if (reg_mentioned_p (cc0_rtx, pat))
2352		      link_cc0_insns (trial);
2353#endif
2354
2355		    delete_related_insns (trial);
2356		    if (slots_to_fill == ++slots_filled)
2357		      break;
2358		    continue;
2359		  }
2360
2361		mark_set_resources (trial, &set, 0, MARK_SRC_DEST_CALL);
2362		mark_referenced_resources (trial, &needed, 1);
2363
2364		/* Ensure we don't put insns between the setting of cc and the
2365		   comparison by moving a setting of cc into an earlier delay
2366		   slot since these insns could clobber the condition code.  */
2367		set.cc = 1;
2368
2369		/* If this is a call or jump, we might not get here.  */
2370		if (GET_CODE (trial_delay) == CALL_INSN
2371		    || GET_CODE (trial_delay) == JUMP_INSN)
2372		  maybe_never = 1;
2373	      }
2374
2375	  /* If there are slots left to fill and our search was stopped by an
2376	     unconditional branch, try the insn at the branch target.  We can
2377	     redirect the branch if it works.
2378
2379	     Don't do this if the insn at the branch target is a branch.  */
2380	  if (slots_to_fill != slots_filled
2381	      && trial
2382	      && GET_CODE (trial) == JUMP_INSN
2383	      && simplejump_p (trial)
2384	      && (target == 0 || JUMP_LABEL (trial) == target)
2385	      && (next_trial = next_active_insn (JUMP_LABEL (trial))) != 0
2386	      && ! (GET_CODE (next_trial) == INSN
2387		    && GET_CODE (PATTERN (next_trial)) == SEQUENCE)
2388	      && GET_CODE (next_trial) != JUMP_INSN
2389	      && ! insn_references_resource_p (next_trial, &set, 1)
2390	      && ! insn_sets_resource_p (next_trial, &set, 1)
2391	      && ! insn_sets_resource_p (next_trial, &needed, 1)
2392#ifdef HAVE_cc0
2393	      && ! reg_mentioned_p (cc0_rtx, PATTERN (next_trial))
2394#endif
2395	      && ! (maybe_never && may_trap_p (PATTERN (next_trial)))
2396	      && (next_trial = try_split (PATTERN (next_trial), next_trial, 0))
2397	      && eligible_for_delay (insn, slots_filled, next_trial, flags)
2398	      && ! can_throw_internal (trial))
2399	    {
2400	      rtx new_label = next_active_insn (next_trial);
2401
2402	      if (new_label != 0)
2403		new_label = get_label_before (new_label);
2404	      else
2405		new_label = find_end_label ();
2406
2407	      delay_list
2408		= add_to_delay_list (copy_rtx (next_trial), delay_list);
2409	      slots_filled++;
2410	      reorg_redirect_jump (trial, new_label);
2411
2412	      /* If we merged because we both jumped to the same place,
2413		 redirect the original insn also.  */
2414	      if (target)
2415		reorg_redirect_jump (insn, new_label);
2416	    }
2417	}
2418
2419      /* If this is an unconditional jump, then try to get insns from the
2420	 target of the jump.  */
2421      if (GET_CODE (insn) == JUMP_INSN
2422	  && simplejump_p (insn)
2423	  && slots_filled != slots_to_fill)
2424	delay_list
2425	  = fill_slots_from_thread (insn, const_true_rtx,
2426				    next_active_insn (JUMP_LABEL (insn)),
2427				    NULL, 1, 1,
2428				    own_thread_p (JUMP_LABEL (insn),
2429						  JUMP_LABEL (insn), 0),
2430				    slots_to_fill, &slots_filled,
2431				    delay_list);
2432
2433      if (delay_list)
2434	unfilled_slots_base[i]
2435	  = emit_delay_sequence (insn, delay_list, slots_filled);
2436
2437      if (slots_to_fill == slots_filled)
2438	unfilled_slots_base[i] = 0;
2439
2440      note_delay_statistics (slots_filled, 0);
2441    }
2442
2443#ifdef DELAY_SLOTS_FOR_EPILOGUE
2444  /* See if the epilogue needs any delay slots.  Try to fill them if so.
2445     The only thing we can do is scan backwards from the end of the
2446     function.  If we did this in a previous pass, it is incorrect to do it
2447     again.  */
2448  if (current_function_epilogue_delay_list)
2449    return;
2450
2451  slots_to_fill = DELAY_SLOTS_FOR_EPILOGUE;
2452  if (slots_to_fill == 0)
2453    return;
2454
2455  slots_filled = 0;
2456  CLEAR_RESOURCE (&set);
2457
2458  /* The frame pointer and stack pointer are needed at the beginning of
2459     the epilogue, so instructions setting them can not be put in the
2460     epilogue delay slot.  However, everything else needed at function
2461     end is safe, so we don't want to use end_of_function_needs here.  */
2462  CLEAR_RESOURCE (&needed);
2463  if (frame_pointer_needed)
2464    {
2465      SET_HARD_REG_BIT (needed.regs, FRAME_POINTER_REGNUM);
2466#if HARD_FRAME_POINTER_REGNUM != FRAME_POINTER_REGNUM
2467      SET_HARD_REG_BIT (needed.regs, HARD_FRAME_POINTER_REGNUM);
2468#endif
2469#ifdef EXIT_IGNORE_STACK
2470      if (! EXIT_IGNORE_STACK
2471	  || current_function_sp_is_unchanging)
2472#endif
2473	SET_HARD_REG_BIT (needed.regs, STACK_POINTER_REGNUM);
2474    }
2475  else
2476    SET_HARD_REG_BIT (needed.regs, STACK_POINTER_REGNUM);
2477
2478#ifdef EPILOGUE_USES
2479  for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
2480    {
2481      if (EPILOGUE_USES (i))
2482	SET_HARD_REG_BIT (needed.regs, i);
2483    }
2484#endif
2485
2486  for (trial = get_last_insn (); ! stop_search_p (trial, 1);
2487       trial = PREV_INSN (trial))
2488    {
2489      if (GET_CODE (trial) == NOTE)
2490	continue;
2491      pat = PATTERN (trial);
2492      if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER)
2493	continue;
2494
2495      if (! insn_references_resource_p (trial, &set, 1)
2496	  && ! insn_sets_resource_p (trial, &needed, 1)
2497	  && ! insn_sets_resource_p (trial, &set, 1)
2498#ifdef HAVE_cc0
2499	  /* Don't want to mess with cc0 here.  */
2500	  && ! reg_mentioned_p (cc0_rtx, pat)
2501#endif
2502	  && ! can_throw_internal (trial))
2503	{
2504	  trial = try_split (pat, trial, 1);
2505	  if (ELIGIBLE_FOR_EPILOGUE_DELAY (trial, slots_filled))
2506	    {
2507	      /* Here as well we are searching backward, so put the
2508		 insns we find on the head of the list.  */
2509
2510	      current_function_epilogue_delay_list
2511		= gen_rtx_INSN_LIST (VOIDmode, trial,
2512				     current_function_epilogue_delay_list);
2513	      mark_end_of_function_resources (trial, 1);
2514	      update_block (trial, trial);
2515	      delete_related_insns (trial);
2516
2517	      /* Clear deleted bit so final.c will output the insn.  */
2518	      INSN_DELETED_P (trial) = 0;
2519
2520	      if (slots_to_fill == ++slots_filled)
2521		break;
2522	      continue;
2523	    }
2524	}
2525
2526      mark_set_resources (trial, &set, 0, MARK_SRC_DEST_CALL);
2527      mark_referenced_resources (trial, &needed, 1);
2528    }
2529
2530  note_delay_statistics (slots_filled, 0);
2531#endif
2532}
2533
2534/* Try to find insns to place in delay slots.
2535
2536   INSN is the jump needing SLOTS_TO_FILL delay slots.  It tests CONDITION
2537   or is an unconditional branch if CONDITION is const_true_rtx.
2538   *PSLOTS_FILLED is updated with the number of slots that we have filled.
2539
2540   THREAD is a flow-of-control, either the insns to be executed if the
2541   branch is true or if the branch is false, THREAD_IF_TRUE says which.
2542
2543   OPPOSITE_THREAD is the thread in the opposite direction.  It is used
2544   to see if any potential delay slot insns set things needed there.
2545
2546   LIKELY is nonzero if it is extremely likely that the branch will be
2547   taken and THREAD_IF_TRUE is set.  This is used for the branch at the
2548   end of a loop back up to the top.
2549
2550   OWN_THREAD and OWN_OPPOSITE_THREAD are true if we are the only user of the
2551   thread.  I.e., it is the fallthrough code of our jump or the target of the
2552   jump when we are the only jump going there.
2553
2554   If OWN_THREAD is false, it must be the "true" thread of a jump.  In that
2555   case, we can only take insns from the head of the thread for our delay
2556   slot.  We then adjust the jump to point after the insns we have taken.  */
2557
2558static rtx
2559fill_slots_from_thread (insn, condition, thread, opposite_thread, likely,
2560			thread_if_true, own_thread,
2561			slots_to_fill, pslots_filled, delay_list)
2562     rtx insn;
2563     rtx condition;
2564     rtx thread, opposite_thread;
2565     int likely;
2566     int thread_if_true;
2567     int own_thread;
2568     int slots_to_fill, *pslots_filled;
2569     rtx delay_list;
2570{
2571  rtx new_thread;
2572  struct resources opposite_needed, set, needed;
2573  rtx trial;
2574  int lose = 0;
2575  int must_annul = 0;
2576  int flags;
2577
2578  /* Validate our arguments.  */
2579  if ((condition == const_true_rtx && ! thread_if_true)
2580      || (! own_thread && ! thread_if_true))
2581    abort ();
2582
2583  flags = get_jump_flags (insn, JUMP_LABEL (insn));
2584
2585  /* If our thread is the end of subroutine, we can't get any delay
2586     insns from that.  */
2587  if (thread == 0)
2588    return delay_list;
2589
2590  /* If this is an unconditional branch, nothing is needed at the
2591     opposite thread.  Otherwise, compute what is needed there.  */
2592  if (condition == const_true_rtx)
2593    CLEAR_RESOURCE (&opposite_needed);
2594  else
2595    mark_target_live_regs (get_insns (), opposite_thread, &opposite_needed);
2596
2597  /* If the insn at THREAD can be split, do it here to avoid having to
2598     update THREAD and NEW_THREAD if it is done in the loop below.  Also
2599     initialize NEW_THREAD.  */
2600
2601  new_thread = thread = try_split (PATTERN (thread), thread, 0);
2602
2603  /* Scan insns at THREAD.  We are looking for an insn that can be removed
2604     from THREAD (it neither sets nor references resources that were set
2605     ahead of it and it doesn't set anything needs by the insns ahead of
2606     it) and that either can be placed in an annulling insn or aren't
2607     needed at OPPOSITE_THREAD.  */
2608
2609  CLEAR_RESOURCE (&needed);
2610  CLEAR_RESOURCE (&set);
2611
2612  /* If we do not own this thread, we must stop as soon as we find
2613     something that we can't put in a delay slot, since all we can do
2614     is branch into THREAD at a later point.  Therefore, labels stop
2615     the search if this is not the `true' thread.  */
2616
2617  for (trial = thread;
2618       ! stop_search_p (trial, ! thread_if_true) && (! lose || own_thread);
2619       trial = next_nonnote_insn (trial))
2620    {
2621      rtx pat, old_trial;
2622
2623      /* If we have passed a label, we no longer own this thread.  */
2624      if (GET_CODE (trial) == CODE_LABEL)
2625	{
2626	  own_thread = 0;
2627	  continue;
2628	}
2629
2630      pat = PATTERN (trial);
2631      if (GET_CODE (pat) == USE || GET_CODE (pat) == CLOBBER)
2632	continue;
2633
2634      /* If TRIAL conflicts with the insns ahead of it, we lose.  Also,
2635	 don't separate or copy insns that set and use CC0.  */
2636      if (! insn_references_resource_p (trial, &set, 1)
2637	  && ! insn_sets_resource_p (trial, &set, 1)
2638	  && ! insn_sets_resource_p (trial, &needed, 1)
2639#ifdef HAVE_cc0
2640	  && ! (reg_mentioned_p (cc0_rtx, pat)
2641		&& (! own_thread || ! sets_cc0_p (pat)))
2642#endif
2643	  && ! can_throw_internal (trial))
2644	{
2645	  rtx prior_insn;
2646
2647	  /* If TRIAL is redundant with some insn before INSN, we don't
2648	     actually need to add it to the delay list; we can merely pretend
2649	     we did.  */
2650	  if ((prior_insn = redundant_insn (trial, insn, delay_list)))
2651	    {
2652	      fix_reg_dead_note (prior_insn, insn);
2653	      if (own_thread)
2654		{
2655		  update_block (trial, thread);
2656		  if (trial == thread)
2657		    {
2658		      thread = next_active_insn (thread);
2659		      if (new_thread == trial)
2660			new_thread = thread;
2661		    }
2662
2663		  delete_related_insns (trial);
2664		}
2665	      else
2666		{
2667		  update_reg_unused_notes (prior_insn, trial);
2668		  new_thread = next_active_insn (trial);
2669		}
2670
2671	      continue;
2672	    }
2673
2674	  /* There are two ways we can win:  If TRIAL doesn't set anything
2675	     needed at the opposite thread and can't trap, or if it can
2676	     go into an annulled delay slot.  */
2677	  if (!must_annul
2678	      && (condition == const_true_rtx
2679	          || (! insn_sets_resource_p (trial, &opposite_needed, 1)
2680		      && ! may_trap_p (pat))))
2681	    {
2682	      old_trial = trial;
2683	      trial = try_split (pat, trial, 0);
2684	      if (new_thread == old_trial)
2685		new_thread = trial;
2686	      if (thread == old_trial)
2687		thread = trial;
2688	      pat = PATTERN (trial);
2689	      if (eligible_for_delay (insn, *pslots_filled, trial, flags))
2690		goto winner;
2691	    }
2692	  else if (0
2693#ifdef ANNUL_IFTRUE_SLOTS
2694		   || ! thread_if_true
2695#endif
2696#ifdef ANNUL_IFFALSE_SLOTS
2697		   || thread_if_true
2698#endif
2699		   )
2700	    {
2701	      old_trial = trial;
2702	      trial = try_split (pat, trial, 0);
2703	      if (new_thread == old_trial)
2704		new_thread = trial;
2705	      if (thread == old_trial)
2706		thread = trial;
2707	      pat = PATTERN (trial);
2708	      if ((must_annul || delay_list == NULL) && (thread_if_true
2709		   ? check_annul_list_true_false (0, delay_list)
2710		     && eligible_for_annul_false (insn, *pslots_filled, trial, flags)
2711		   : check_annul_list_true_false (1, delay_list)
2712		     && eligible_for_annul_true (insn, *pslots_filled, trial, flags)))
2713		{
2714		  rtx temp;
2715
2716		  must_annul = 1;
2717		winner:
2718
2719#ifdef HAVE_cc0
2720		  if (reg_mentioned_p (cc0_rtx, pat))
2721		    link_cc0_insns (trial);
2722#endif
2723
2724		  /* If we own this thread, delete the insn.  If this is the
2725		     destination of a branch, show that a basic block status
2726		     may have been updated.  In any case, mark the new
2727		     starting point of this thread.  */
2728		  if (own_thread)
2729		    {
2730		      rtx note;
2731
2732		      update_block (trial, thread);
2733		      if (trial == thread)
2734			{
2735			  thread = next_active_insn (thread);
2736			  if (new_thread == trial)
2737			    new_thread = thread;
2738			}
2739
2740		      /* We are moving this insn, not deleting it.  We must
2741			 temporarily increment the use count on any referenced
2742			 label lest it be deleted by delete_related_insns.  */
2743		      note = find_reg_note (trial, REG_LABEL, 0);
2744		      /* REG_LABEL could be NOTE_INSN_DELETED_LABEL too.  */
2745		      if (note && GET_CODE (XEXP (note, 0)) == CODE_LABEL)
2746			LABEL_NUSES (XEXP (note, 0))++;
2747
2748		      delete_related_insns (trial);
2749
2750		      if (note && GET_CODE (XEXP (note, 0)) == CODE_LABEL)
2751			LABEL_NUSES (XEXP (note, 0))--;
2752		    }
2753		  else
2754		    new_thread = next_active_insn (trial);
2755
2756		  temp = own_thread ? trial : copy_rtx (trial);
2757		  if (thread_if_true)
2758		    INSN_FROM_TARGET_P (temp) = 1;
2759
2760		  delay_list = add_to_delay_list (temp, delay_list);
2761
2762		  if (slots_to_fill == ++(*pslots_filled))
2763		    {
2764		      /* Even though we have filled all the slots, we
2765			 may be branching to a location that has a
2766			 redundant insn.  Skip any if so.  */
2767		      while (new_thread && ! own_thread
2768			     && ! insn_sets_resource_p (new_thread, &set, 1)
2769			     && ! insn_sets_resource_p (new_thread, &needed, 1)
2770			     && ! insn_references_resource_p (new_thread,
2771							      &set, 1)
2772			     && (prior_insn
2773				 = redundant_insn (new_thread, insn,
2774						   delay_list)))
2775			{
2776			  /* We know we do not own the thread, so no need
2777			     to call update_block and delete_insn.  */
2778			  fix_reg_dead_note (prior_insn, insn);
2779			  update_reg_unused_notes (prior_insn, new_thread);
2780			  new_thread = next_active_insn (new_thread);
2781			}
2782		      break;
2783		    }
2784
2785		  continue;
2786		}
2787	    }
2788	}
2789
2790      /* This insn can't go into a delay slot.  */
2791      lose = 1;
2792      mark_set_resources (trial, &set, 0, MARK_SRC_DEST_CALL);
2793      mark_referenced_resources (trial, &needed, 1);
2794
2795      /* Ensure we don't put insns between the setting of cc and the comparison
2796	 by moving a setting of cc into an earlier delay slot since these insns
2797	 could clobber the condition code.  */
2798      set.cc = 1;
2799
2800      /* If this insn is a register-register copy and the next insn has
2801	 a use of our destination, change it to use our source.  That way,
2802	 it will become a candidate for our delay slot the next time
2803	 through this loop.  This case occurs commonly in loops that
2804	 scan a list.
2805
2806	 We could check for more complex cases than those tested below,
2807	 but it doesn't seem worth it.  It might also be a good idea to try
2808	 to swap the two insns.  That might do better.
2809
2810	 We can't do this if the next insn modifies our destination, because
2811	 that would make the replacement into the insn invalid.  We also can't
2812	 do this if it modifies our source, because it might be an earlyclobber
2813	 operand.  This latter test also prevents updating the contents of
2814	 a PRE_INC.  */
2815
2816      if (GET_CODE (trial) == INSN && GET_CODE (pat) == SET
2817	  && GET_CODE (SET_SRC (pat)) == REG
2818	  && GET_CODE (SET_DEST (pat)) == REG)
2819	{
2820	  rtx next = next_nonnote_insn (trial);
2821
2822	  if (next && GET_CODE (next) == INSN
2823	      && GET_CODE (PATTERN (next)) != USE
2824	      && ! reg_set_p (SET_DEST (pat), next)
2825	      && ! reg_set_p (SET_SRC (pat), next)
2826	      && reg_referenced_p (SET_DEST (pat), PATTERN (next))
2827	      && ! modified_in_p (SET_DEST (pat), next))
2828	    validate_replace_rtx (SET_DEST (pat), SET_SRC (pat), next);
2829	}
2830    }
2831
2832  /* If we stopped on a branch insn that has delay slots, see if we can
2833     steal some of the insns in those slots.  */
2834  if (trial && GET_CODE (trial) == INSN
2835      && GET_CODE (PATTERN (trial)) == SEQUENCE
2836      && GET_CODE (XVECEXP (PATTERN (trial), 0, 0)) == JUMP_INSN)
2837    {
2838      /* If this is the `true' thread, we will want to follow the jump,
2839	 so we can only do this if we have taken everything up to here.  */
2840      if (thread_if_true && trial == new_thread)
2841	{
2842	  delay_list
2843	    = steal_delay_list_from_target (insn, condition, PATTERN (trial),
2844					    delay_list, &set, &needed,
2845					    &opposite_needed, slots_to_fill,
2846					    pslots_filled, &must_annul,
2847					    &new_thread);
2848	  /* If we owned the thread and are told that it branched
2849	     elsewhere, make sure we own the thread at the new location.  */
2850	  if (own_thread && trial != new_thread)
2851	    own_thread = own_thread_p (new_thread, new_thread, 0);
2852	}
2853      else if (! thread_if_true)
2854	delay_list
2855	  = steal_delay_list_from_fallthrough (insn, condition,
2856					       PATTERN (trial),
2857					       delay_list, &set, &needed,
2858					       &opposite_needed, slots_to_fill,
2859					       pslots_filled, &must_annul);
2860    }
2861
2862  /* If we haven't found anything for this delay slot and it is very
2863     likely that the branch will be taken, see if the insn at our target
2864     increments or decrements a register with an increment that does not
2865     depend on the destination register.  If so, try to place the opposite
2866     arithmetic insn after the jump insn and put the arithmetic insn in the
2867     delay slot.  If we can't do this, return.  */
2868  if (delay_list == 0 && likely && new_thread
2869      && GET_CODE (new_thread) == INSN
2870      && GET_CODE (PATTERN (new_thread)) != ASM_INPUT
2871      && asm_noperands (PATTERN (new_thread)) < 0)
2872    {
2873      rtx pat = PATTERN (new_thread);
2874      rtx dest;
2875      rtx src;
2876
2877      trial = new_thread;
2878      pat = PATTERN (trial);
2879
2880      if (GET_CODE (trial) != INSN
2881	  || GET_CODE (pat) != SET
2882	  || ! eligible_for_delay (insn, 0, trial, flags)
2883	  || can_throw_internal (trial))
2884	return 0;
2885
2886      dest = SET_DEST (pat), src = SET_SRC (pat);
2887      if ((GET_CODE (src) == PLUS || GET_CODE (src) == MINUS)
2888	  && rtx_equal_p (XEXP (src, 0), dest)
2889	  && ! reg_overlap_mentioned_p (dest, XEXP (src, 1))
2890	  && ! side_effects_p (pat))
2891	{
2892	  rtx other = XEXP (src, 1);
2893	  rtx new_arith;
2894	  rtx ninsn;
2895
2896	  /* If this is a constant adjustment, use the same code with
2897	     the negated constant.  Otherwise, reverse the sense of the
2898	     arithmetic.  */
2899	  if (GET_CODE (other) == CONST_INT)
2900	    new_arith = gen_rtx_fmt_ee (GET_CODE (src), GET_MODE (src), dest,
2901					negate_rtx (GET_MODE (src), other));
2902	  else
2903	    new_arith = gen_rtx_fmt_ee (GET_CODE (src) == PLUS ? MINUS : PLUS,
2904					GET_MODE (src), dest, other);
2905
2906	  ninsn = emit_insn_after (gen_rtx_SET (VOIDmode, dest, new_arith),
2907				   insn);
2908
2909	  if (recog_memoized (ninsn) < 0
2910	      || (extract_insn (ninsn), ! constrain_operands (1)))
2911	    {
2912	      delete_related_insns (ninsn);
2913	      return 0;
2914	    }
2915
2916	  if (own_thread)
2917	    {
2918	      update_block (trial, thread);
2919	      if (trial == thread)
2920		{
2921		  thread = next_active_insn (thread);
2922		  if (new_thread == trial)
2923		    new_thread = thread;
2924		}
2925	      delete_related_insns (trial);
2926	    }
2927	  else
2928	    new_thread = next_active_insn (trial);
2929
2930	  ninsn = own_thread ? trial : copy_rtx (trial);
2931	  if (thread_if_true)
2932	    INSN_FROM_TARGET_P (ninsn) = 1;
2933
2934	  delay_list = add_to_delay_list (ninsn, NULL_RTX);
2935	  (*pslots_filled)++;
2936	}
2937    }
2938
2939  if (delay_list && must_annul)
2940    INSN_ANNULLED_BRANCH_P (insn) = 1;
2941
2942  /* If we are to branch into the middle of this thread, find an appropriate
2943     label or make a new one if none, and redirect INSN to it.  If we hit the
2944     end of the function, use the end-of-function label.  */
2945  if (new_thread != thread)
2946    {
2947      rtx label;
2948
2949      if (! thread_if_true)
2950	abort ();
2951
2952      if (new_thread && GET_CODE (new_thread) == JUMP_INSN
2953	  && (simplejump_p (new_thread)
2954	      || GET_CODE (PATTERN (new_thread)) == RETURN)
2955	  && redirect_with_delay_list_safe_p (insn,
2956					      JUMP_LABEL (new_thread),
2957					      delay_list))
2958	new_thread = follow_jumps (JUMP_LABEL (new_thread));
2959
2960      if (new_thread == 0)
2961	label = find_end_label ();
2962      else if (GET_CODE (new_thread) == CODE_LABEL)
2963	label = new_thread;
2964      else
2965	label = get_label_before (new_thread);
2966
2967      reorg_redirect_jump (insn, label);
2968    }
2969
2970  return delay_list;
2971}
2972
2973/* Make another attempt to find insns to place in delay slots.
2974
2975   We previously looked for insns located in front of the delay insn
2976   and, for non-jump delay insns, located behind the delay insn.
2977
2978   Here only try to schedule jump insns and try to move insns from either
2979   the target or the following insns into the delay slot.  If annulling is
2980   supported, we will be likely to do this.  Otherwise, we can do this only
2981   if safe.  */
2982
2983static void
2984fill_eager_delay_slots ()
2985{
2986  rtx insn;
2987  int i;
2988  int num_unfilled_slots = unfilled_slots_next - unfilled_slots_base;
2989
2990  for (i = 0; i < num_unfilled_slots; i++)
2991    {
2992      rtx condition;
2993      rtx target_label, insn_at_target, fallthrough_insn;
2994      rtx delay_list = 0;
2995      int own_target;
2996      int own_fallthrough;
2997      int prediction, slots_to_fill, slots_filled;
2998
2999      insn = unfilled_slots_base[i];
3000      if (insn == 0
3001	  || INSN_DELETED_P (insn)
3002	  || GET_CODE (insn) != JUMP_INSN
3003	  || ! (condjump_p (insn) || condjump_in_parallel_p (insn)))
3004	continue;
3005
3006      slots_to_fill = num_delay_slots (insn);
3007      /* Some machine description have defined instructions to have
3008	 delay slots only in certain circumstances which may depend on
3009	 nearby insns (which change due to reorg's actions).
3010
3011 	 For example, the PA port normally has delay slots for unconditional
3012	 jumps.
3013
3014	 However, the PA port claims such jumps do not have a delay slot
3015	 if they are immediate successors of certain CALL_INSNs.  This
3016	 allows the port to favor filling the delay slot of the call with
3017	 the unconditional jump.  */
3018      if (slots_to_fill == 0)
3019	continue;
3020
3021      slots_filled = 0;
3022      target_label = JUMP_LABEL (insn);
3023      condition = get_branch_condition (insn, target_label);
3024
3025      if (condition == 0)
3026	continue;
3027
3028      /* Get the next active fallthrough and target insns and see if we own
3029	 them.  Then see whether the branch is likely true.  We don't need
3030	 to do a lot of this for unconditional branches.  */
3031
3032      insn_at_target = next_active_insn (target_label);
3033      own_target = own_thread_p (target_label, target_label, 0);
3034
3035      if (condition == const_true_rtx)
3036	{
3037	  own_fallthrough = 0;
3038	  fallthrough_insn = 0;
3039	  prediction = 2;
3040	}
3041      else
3042	{
3043	  fallthrough_insn = next_active_insn (insn);
3044	  own_fallthrough = own_thread_p (NEXT_INSN (insn), NULL_RTX, 1);
3045	  prediction = mostly_true_jump (insn, condition);
3046	}
3047
3048      /* If this insn is expected to branch, first try to get insns from our
3049	 target, then our fallthrough insns.  If it is not expected to branch,
3050	 try the other order.  */
3051
3052      if (prediction > 0)
3053	{
3054	  delay_list
3055	    = fill_slots_from_thread (insn, condition, insn_at_target,
3056				      fallthrough_insn, prediction == 2, 1,
3057				      own_target,
3058				      slots_to_fill, &slots_filled, delay_list);
3059
3060	  if (delay_list == 0 && own_fallthrough)
3061	    {
3062	      /* Even though we didn't find anything for delay slots,
3063		 we might have found a redundant insn which we deleted
3064		 from the thread that was filled.  So we have to recompute
3065		 the next insn at the target.  */
3066	      target_label = JUMP_LABEL (insn);
3067	      insn_at_target = next_active_insn (target_label);
3068
3069	      delay_list
3070		= fill_slots_from_thread (insn, condition, fallthrough_insn,
3071					  insn_at_target, 0, 0,
3072					  own_fallthrough,
3073					  slots_to_fill, &slots_filled,
3074					  delay_list);
3075	    }
3076	}
3077      else
3078	{
3079	  if (own_fallthrough)
3080	    delay_list
3081	      = fill_slots_from_thread (insn, condition, fallthrough_insn,
3082					insn_at_target, 0, 0,
3083					own_fallthrough,
3084					slots_to_fill, &slots_filled,
3085					delay_list);
3086
3087	  if (delay_list == 0)
3088	    delay_list
3089	      = fill_slots_from_thread (insn, condition, insn_at_target,
3090					next_active_insn (insn), 0, 1,
3091					own_target,
3092					slots_to_fill, &slots_filled,
3093					delay_list);
3094	}
3095
3096      if (delay_list)
3097	unfilled_slots_base[i]
3098	  = emit_delay_sequence (insn, delay_list, slots_filled);
3099
3100      if (slots_to_fill == slots_filled)
3101	unfilled_slots_base[i] = 0;
3102
3103      note_delay_statistics (slots_filled, 1);
3104    }
3105}
3106
3107/* Once we have tried two ways to fill a delay slot, make a pass over the
3108   code to try to improve the results and to do such things as more jump
3109   threading.  */
3110
3111static void
3112relax_delay_slots (first)
3113     rtx first;
3114{
3115  rtx insn, next, pat;
3116  rtx trial, delay_insn, target_label;
3117
3118  /* Look at every JUMP_INSN and see if we can improve it.  */
3119  for (insn = first; insn; insn = next)
3120    {
3121      rtx other;
3122
3123      next = next_active_insn (insn);
3124
3125      /* If this is a jump insn, see if it now jumps to a jump, jumps to
3126	 the next insn, or jumps to a label that is not the last of a
3127	 group of consecutive labels.  */
3128      if (GET_CODE (insn) == JUMP_INSN
3129	  && (condjump_p (insn) || condjump_in_parallel_p (insn))
3130	  && (target_label = JUMP_LABEL (insn)) != 0)
3131	{
3132	  target_label = follow_jumps (target_label);
3133	  target_label = prev_label (next_active_insn (target_label));
3134
3135	  if (target_label == 0)
3136	    target_label = find_end_label ();
3137
3138	  if (next_active_insn (target_label) == next
3139	      && ! condjump_in_parallel_p (insn))
3140	    {
3141	      delete_jump (insn);
3142	      continue;
3143	    }
3144
3145	  if (target_label != JUMP_LABEL (insn))
3146	    reorg_redirect_jump (insn, target_label);
3147
3148	  /* See if this jump branches around an unconditional jump.
3149	     If so, invert this jump and point it to the target of the
3150	     second jump.  */
3151	  if (next && GET_CODE (next) == JUMP_INSN
3152	      && (simplejump_p (next) || GET_CODE (PATTERN (next)) == RETURN)
3153	      && next_active_insn (target_label) == next_active_insn (next)
3154	      && no_labels_between_p (insn, next))
3155	    {
3156	      rtx label = JUMP_LABEL (next);
3157
3158	      /* Be careful how we do this to avoid deleting code or
3159		 labels that are momentarily dead.  See similar optimization
3160		 in jump.c.
3161
3162		 We also need to ensure we properly handle the case when
3163		 invert_jump fails.  */
3164
3165	      ++LABEL_NUSES (target_label);
3166	      if (label)
3167		++LABEL_NUSES (label);
3168
3169	      if (invert_jump (insn, label, 1))
3170		{
3171		  delete_related_insns (next);
3172		  next = insn;
3173		}
3174
3175	      if (label)
3176		--LABEL_NUSES (label);
3177
3178	      if (--LABEL_NUSES (target_label) == 0)
3179		delete_related_insns (target_label);
3180
3181	      continue;
3182	    }
3183	}
3184
3185      /* If this is an unconditional jump and the previous insn is a
3186	 conditional jump, try reversing the condition of the previous
3187	 insn and swapping our targets.  The next pass might be able to
3188	 fill the slots.
3189
3190	 Don't do this if we expect the conditional branch to be true, because
3191	 we would then be making the more common case longer.  */
3192
3193      if (GET_CODE (insn) == JUMP_INSN
3194	  && (simplejump_p (insn) || GET_CODE (PATTERN (insn)) == RETURN)
3195	  && (other = prev_active_insn (insn)) != 0
3196	  && (condjump_p (other) || condjump_in_parallel_p (other))
3197	  && no_labels_between_p (other, insn)
3198	  && 0 > mostly_true_jump (other,
3199				   get_branch_condition (other,
3200							 JUMP_LABEL (other))))
3201	{
3202	  rtx other_target = JUMP_LABEL (other);
3203	  target_label = JUMP_LABEL (insn);
3204
3205	  if (invert_jump (other, target_label, 0))
3206	    reorg_redirect_jump (insn, other_target);
3207	}
3208
3209      /* Now look only at cases where we have filled a delay slot.  */
3210      if (GET_CODE (insn) != INSN
3211	  || GET_CODE (PATTERN (insn)) != SEQUENCE)
3212	continue;
3213
3214      pat = PATTERN (insn);
3215      delay_insn = XVECEXP (pat, 0, 0);
3216
3217      /* See if the first insn in the delay slot is redundant with some
3218	 previous insn.  Remove it from the delay slot if so; then set up
3219	 to reprocess this insn.  */
3220      if (redundant_insn (XVECEXP (pat, 0, 1), delay_insn, 0))
3221	{
3222	  delete_from_delay_slot (XVECEXP (pat, 0, 1));
3223	  next = prev_active_insn (next);
3224	  continue;
3225	}
3226
3227      /* See if we have a RETURN insn with a filled delay slot followed
3228	 by a RETURN insn with an unfilled a delay slot.  If so, we can delete
3229	 the first RETURN (but not it's delay insn).  This gives the same
3230	 effect in fewer instructions.
3231
3232	 Only do so if optimizing for size since this results in slower, but
3233	 smaller code.  */
3234      if (optimize_size
3235	  && GET_CODE (PATTERN (delay_insn)) == RETURN
3236	  && next
3237	  && GET_CODE (next) == JUMP_INSN
3238	  && GET_CODE (PATTERN (next)) == RETURN)
3239	{
3240	  rtx after;
3241	  int i;
3242
3243	  /* Delete the RETURN and just execute the delay list insns.
3244
3245	     We do this by deleting the INSN containing the SEQUENCE, then
3246	     re-emitting the insns separately, and then deleting the RETURN.
3247	     This allows the count of the jump target to be properly
3248	     decremented.  */
3249
3250	  /* Clear the from target bit, since these insns are no longer
3251	     in delay slots.  */
3252	  for (i = 0; i < XVECLEN (pat, 0); i++)
3253	    INSN_FROM_TARGET_P (XVECEXP (pat, 0, i)) = 0;
3254
3255	  trial = PREV_INSN (insn);
3256	  delete_related_insns (insn);
3257	  if (GET_CODE (pat) != SEQUENCE)
3258	    abort ();
3259	  after = trial;
3260	  for (i = 0; i < XVECLEN (pat, 0); i++)
3261	    {
3262	      rtx this_insn = XVECEXP (pat, 0, i);
3263	      add_insn_after (this_insn, after);
3264	      after = this_insn;
3265	    }
3266	  delete_scheduled_jump (delay_insn);
3267	  continue;
3268	}
3269
3270      /* Now look only at the cases where we have a filled JUMP_INSN.  */
3271      if (GET_CODE (XVECEXP (PATTERN (insn), 0, 0)) != JUMP_INSN
3272	  || ! (condjump_p (XVECEXP (PATTERN (insn), 0, 0))
3273		|| condjump_in_parallel_p (XVECEXP (PATTERN (insn), 0, 0))))
3274	continue;
3275
3276      target_label = JUMP_LABEL (delay_insn);
3277
3278      if (target_label)
3279	{
3280	  /* If this jump goes to another unconditional jump, thread it, but
3281	     don't convert a jump into a RETURN here.  */
3282	  trial = follow_jumps (target_label);
3283	  /* We use next_real_insn instead of next_active_insn, so that
3284	     the special USE insns emitted by reorg won't be ignored.
3285	     If they are ignored, then they will get deleted if target_label
3286	     is now unreachable, and that would cause mark_target_live_regs
3287	     to fail.  */
3288	  trial = prev_label (next_real_insn (trial));
3289	  if (trial == 0 && target_label != 0)
3290	    trial = find_end_label ();
3291
3292	  if (trial != target_label
3293	      && redirect_with_delay_slots_safe_p (delay_insn, trial, insn))
3294	    {
3295	      reorg_redirect_jump (delay_insn, trial);
3296	      target_label = trial;
3297	    }
3298
3299	  /* If the first insn at TARGET_LABEL is redundant with a previous
3300	     insn, redirect the jump to the following insn process again.  */
3301	  trial = next_active_insn (target_label);
3302	  if (trial && GET_CODE (PATTERN (trial)) != SEQUENCE
3303	      && redundant_insn (trial, insn, 0)
3304	      && ! can_throw_internal (trial))
3305	    {
3306	      rtx tmp;
3307
3308	      /* Figure out where to emit the special USE insn so we don't
3309		 later incorrectly compute register live/death info.  */
3310	      tmp = next_active_insn (trial);
3311	      if (tmp == 0)
3312		tmp = find_end_label ();
3313
3314	      /* Insert the special USE insn and update dataflow info.  */
3315	      update_block (trial, tmp);
3316
3317	      /* Now emit a label before the special USE insn, and
3318		 redirect our jump to the new label.  */
3319	      target_label = get_label_before (PREV_INSN (tmp));
3320	      reorg_redirect_jump (delay_insn, target_label);
3321	      next = insn;
3322	      continue;
3323	    }
3324
3325	  /* Similarly, if it is an unconditional jump with one insn in its
3326	     delay list and that insn is redundant, thread the jump.  */
3327	  if (trial && GET_CODE (PATTERN (trial)) == SEQUENCE
3328	      && XVECLEN (PATTERN (trial), 0) == 2
3329	      && GET_CODE (XVECEXP (PATTERN (trial), 0, 0)) == JUMP_INSN
3330	      && (simplejump_p (XVECEXP (PATTERN (trial), 0, 0))
3331		  || GET_CODE (PATTERN (XVECEXP (PATTERN (trial), 0, 0))) == RETURN)
3332	      && redundant_insn (XVECEXP (PATTERN (trial), 0, 1), insn, 0))
3333	    {
3334	      target_label = JUMP_LABEL (XVECEXP (PATTERN (trial), 0, 0));
3335	      if (target_label == 0)
3336		target_label = find_end_label ();
3337
3338	      if (redirect_with_delay_slots_safe_p (delay_insn, target_label,
3339						    insn))
3340		{
3341		  reorg_redirect_jump (delay_insn, target_label);
3342		  next = insn;
3343		  continue;
3344		}
3345	    }
3346	}
3347
3348      if (! INSN_ANNULLED_BRANCH_P (delay_insn)
3349	  && prev_active_insn (target_label) == insn
3350	  && ! condjump_in_parallel_p (delay_insn)
3351#ifdef HAVE_cc0
3352	  /* If the last insn in the delay slot sets CC0 for some insn,
3353	     various code assumes that it is in a delay slot.  We could
3354	     put it back where it belonged and delete the register notes,
3355	     but it doesn't seem worthwhile in this uncommon case.  */
3356	  && ! find_reg_note (XVECEXP (pat, 0, XVECLEN (pat, 0) - 1),
3357			      REG_CC_USER, NULL_RTX)
3358#endif
3359	  )
3360	{
3361	  rtx after;
3362	  int i;
3363
3364	  /* All this insn does is execute its delay list and jump to the
3365	     following insn.  So delete the jump and just execute the delay
3366	     list insns.
3367
3368	     We do this by deleting the INSN containing the SEQUENCE, then
3369	     re-emitting the insns separately, and then deleting the jump.
3370	     This allows the count of the jump target to be properly
3371	     decremented.  */
3372
3373	  /* Clear the from target bit, since these insns are no longer
3374	     in delay slots.  */
3375	  for (i = 0; i < XVECLEN (pat, 0); i++)
3376	    INSN_FROM_TARGET_P (XVECEXP (pat, 0, i)) = 0;
3377
3378	  trial = PREV_INSN (insn);
3379	  delete_related_insns (insn);
3380	  if (GET_CODE (pat) != SEQUENCE)
3381	    abort ();
3382	  after = trial;
3383	  for (i = 0; i < XVECLEN (pat, 0); i++)
3384	    {
3385	      rtx this_insn = XVECEXP (pat, 0, i);
3386	      add_insn_after (this_insn, after);
3387	      after = this_insn;
3388	    }
3389	  delete_scheduled_jump (delay_insn);
3390	  continue;
3391	}
3392
3393      /* See if this is an unconditional jump around a single insn which is
3394	 identical to the one in its delay slot.  In this case, we can just
3395	 delete the branch and the insn in its delay slot.  */
3396      if (next && GET_CODE (next) == INSN
3397	  && prev_label (next_active_insn (next)) == target_label
3398	  && simplejump_p (insn)
3399	  && XVECLEN (pat, 0) == 2
3400	  && rtx_equal_p (PATTERN (next), PATTERN (XVECEXP (pat, 0, 1))))
3401	{
3402	  delete_related_insns (insn);
3403	  continue;
3404	}
3405
3406      /* See if this jump (with its delay slots) branches around another
3407	 jump (without delay slots).  If so, invert this jump and point
3408	 it to the target of the second jump.  We cannot do this for
3409	 annulled jumps, though.  Again, don't convert a jump to a RETURN
3410	 here.  */
3411      if (! INSN_ANNULLED_BRANCH_P (delay_insn)
3412	  && next && GET_CODE (next) == JUMP_INSN
3413	  && (simplejump_p (next) || GET_CODE (PATTERN (next)) == RETURN)
3414	  && next_active_insn (target_label) == next_active_insn (next)
3415	  && no_labels_between_p (insn, next))
3416	{
3417	  rtx label = JUMP_LABEL (next);
3418	  rtx old_label = JUMP_LABEL (delay_insn);
3419
3420	  if (label == 0)
3421	    label = find_end_label ();
3422
3423	  /* find_end_label can generate a new label. Check this first.  */
3424	  if (no_labels_between_p (insn, next)
3425	      && redirect_with_delay_slots_safe_p (delay_insn, label, insn))
3426	    {
3427	      /* Be careful how we do this to avoid deleting code or labels
3428		 that are momentarily dead.  See similar optimization in
3429		 jump.c  */
3430	      if (old_label)
3431		++LABEL_NUSES (old_label);
3432
3433	      if (invert_jump (delay_insn, label, 1))
3434		{
3435		  int i;
3436
3437		  /* Must update the INSN_FROM_TARGET_P bits now that
3438		     the branch is reversed, so that mark_target_live_regs
3439		     will handle the delay slot insn correctly.  */
3440		  for (i = 1; i < XVECLEN (PATTERN (insn), 0); i++)
3441		    {
3442		      rtx slot = XVECEXP (PATTERN (insn), 0, i);
3443		      INSN_FROM_TARGET_P (slot) = ! INSN_FROM_TARGET_P (slot);
3444		    }
3445
3446		  delete_related_insns (next);
3447		  next = insn;
3448		}
3449
3450	      if (old_label && --LABEL_NUSES (old_label) == 0)
3451		delete_related_insns (old_label);
3452	      continue;
3453	    }
3454	}
3455
3456      /* If we own the thread opposite the way this insn branches, see if we
3457	 can merge its delay slots with following insns.  */
3458      if (INSN_FROM_TARGET_P (XVECEXP (pat, 0, 1))
3459	  && own_thread_p (NEXT_INSN (insn), 0, 1))
3460	try_merge_delay_insns (insn, next);
3461      else if (! INSN_FROM_TARGET_P (XVECEXP (pat, 0, 1))
3462	       && own_thread_p (target_label, target_label, 0))
3463	try_merge_delay_insns (insn, next_active_insn (target_label));
3464
3465      /* If we get here, we haven't deleted INSN.  But we may have deleted
3466	 NEXT, so recompute it.  */
3467      next = next_active_insn (insn);
3468    }
3469}
3470
3471#ifdef HAVE_return
3472
3473/* Look for filled jumps to the end of function label.  We can try to convert
3474   them into RETURN insns if the insns in the delay slot are valid for the
3475   RETURN as well.  */
3476
3477static void
3478make_return_insns (first)
3479     rtx first;
3480{
3481  rtx insn, jump_insn, pat;
3482  rtx real_return_label = end_of_function_label;
3483  int slots, i;
3484
3485#ifdef DELAY_SLOTS_FOR_EPILOGUE
3486  /* If a previous pass filled delay slots in the epilogue, things get a
3487     bit more complicated, as those filler insns would generally (without
3488     data flow analysis) have to be executed after any existing branch
3489     delay slot filler insns.  It is also unknown whether such a
3490     transformation would actually be profitable.  Note that the existing
3491     code only cares for branches with (some) filled delay slots.  */
3492  if (current_function_epilogue_delay_list != NULL)
3493    return;
3494#endif
3495
3496  /* See if there is a RETURN insn in the function other than the one we
3497     made for END_OF_FUNCTION_LABEL.  If so, set up anything we can't change
3498     into a RETURN to jump to it.  */
3499  for (insn = first; insn; insn = NEXT_INSN (insn))
3500    if (GET_CODE (insn) == JUMP_INSN && GET_CODE (PATTERN (insn)) == RETURN)
3501      {
3502	real_return_label = get_label_before (insn);
3503	break;
3504      }
3505
3506  /* Show an extra usage of REAL_RETURN_LABEL so it won't go away if it
3507     was equal to END_OF_FUNCTION_LABEL.  */
3508  LABEL_NUSES (real_return_label)++;
3509
3510  /* Clear the list of insns to fill so we can use it.  */
3511  obstack_free (&unfilled_slots_obstack, unfilled_firstobj);
3512
3513  for (insn = first; insn; insn = NEXT_INSN (insn))
3514    {
3515      int flags;
3516
3517      /* Only look at filled JUMP_INSNs that go to the end of function
3518	 label.  */
3519      if (GET_CODE (insn) != INSN
3520	  || GET_CODE (PATTERN (insn)) != SEQUENCE
3521	  || GET_CODE (XVECEXP (PATTERN (insn), 0, 0)) != JUMP_INSN
3522	  || JUMP_LABEL (XVECEXP (PATTERN (insn), 0, 0)) != end_of_function_label)
3523	continue;
3524
3525      pat = PATTERN (insn);
3526      jump_insn = XVECEXP (pat, 0, 0);
3527
3528      /* If we can't make the jump into a RETURN, try to redirect it to the best
3529	 RETURN and go on to the next insn.  */
3530      if (! reorg_redirect_jump (jump_insn, NULL_RTX))
3531	{
3532	  /* Make sure redirecting the jump will not invalidate the delay
3533	     slot insns.  */
3534	  if (redirect_with_delay_slots_safe_p (jump_insn,
3535						real_return_label,
3536						insn))
3537	    reorg_redirect_jump (jump_insn, real_return_label);
3538	  continue;
3539	}
3540
3541      /* See if this RETURN can accept the insns current in its delay slot.
3542	 It can if it has more or an equal number of slots and the contents
3543	 of each is valid.  */
3544
3545      flags = get_jump_flags (jump_insn, JUMP_LABEL (jump_insn));
3546      slots = num_delay_slots (jump_insn);
3547      if (slots >= XVECLEN (pat, 0) - 1)
3548	{
3549	  for (i = 1; i < XVECLEN (pat, 0); i++)
3550	    if (! (
3551#ifdef ANNUL_IFFALSE_SLOTS
3552		   (INSN_ANNULLED_BRANCH_P (jump_insn)
3553		    && INSN_FROM_TARGET_P (XVECEXP (pat, 0, i)))
3554		   ? eligible_for_annul_false (jump_insn, i - 1,
3555					       XVECEXP (pat, 0, i), flags) :
3556#endif
3557#ifdef ANNUL_IFTRUE_SLOTS
3558		   (INSN_ANNULLED_BRANCH_P (jump_insn)
3559		    && ! INSN_FROM_TARGET_P (XVECEXP (pat, 0, i)))
3560		   ? eligible_for_annul_true (jump_insn, i - 1,
3561					      XVECEXP (pat, 0, i), flags) :
3562#endif
3563		   eligible_for_delay (jump_insn, i - 1,
3564				       XVECEXP (pat, 0, i), flags)))
3565	      break;
3566	}
3567      else
3568	i = 0;
3569
3570      if (i == XVECLEN (pat, 0))
3571	continue;
3572
3573      /* We have to do something with this insn.  If it is an unconditional
3574	 RETURN, delete the SEQUENCE and output the individual insns,
3575	 followed by the RETURN.  Then set things up so we try to find
3576	 insns for its delay slots, if it needs some.  */
3577      if (GET_CODE (PATTERN (jump_insn)) == RETURN)
3578	{
3579	  rtx prev = PREV_INSN (insn);
3580
3581	  delete_related_insns (insn);
3582	  for (i = 1; i < XVECLEN (pat, 0); i++)
3583	    prev = emit_insn_after (PATTERN (XVECEXP (pat, 0, i)), prev);
3584
3585	  insn = emit_jump_insn_after (PATTERN (jump_insn), prev);
3586	  emit_barrier_after (insn);
3587
3588	  if (slots)
3589	    obstack_ptr_grow (&unfilled_slots_obstack, insn);
3590	}
3591      else
3592	/* It is probably more efficient to keep this with its current
3593	   delay slot as a branch to a RETURN.  */
3594	reorg_redirect_jump (jump_insn, real_return_label);
3595    }
3596
3597  /* Now delete REAL_RETURN_LABEL if we never used it.  Then try to fill any
3598     new delay slots we have created.  */
3599  if (--LABEL_NUSES (real_return_label) == 0)
3600    delete_related_insns (real_return_label);
3601
3602  fill_simple_delay_slots (1);
3603  fill_simple_delay_slots (0);
3604}
3605#endif
3606
3607/* Try to find insns to place in delay slots.  */
3608
3609void
3610dbr_schedule (first, file)
3611     rtx first;
3612     FILE *file;
3613{
3614  rtx insn, next, epilogue_insn = 0;
3615  int i;
3616#if 0
3617  int old_flag_no_peephole = flag_no_peephole;
3618
3619  /* Execute `final' once in prescan mode to delete any insns that won't be
3620     used.  Don't let final try to do any peephole optimization--it will
3621     ruin dataflow information for this pass.  */
3622
3623  flag_no_peephole = 1;
3624  final (first, 0, NO_DEBUG, 1, 1);
3625  flag_no_peephole = old_flag_no_peephole;
3626#endif
3627
3628  /* If the current function has no insns other than the prologue and
3629     epilogue, then do not try to fill any delay slots.  */
3630  if (n_basic_blocks == 0)
3631    return;
3632
3633  /* Find the highest INSN_UID and allocate and initialize our map from
3634     INSN_UID's to position in code.  */
3635  for (max_uid = 0, insn = first; insn; insn = NEXT_INSN (insn))
3636    {
3637      if (INSN_UID (insn) > max_uid)
3638	max_uid = INSN_UID (insn);
3639      if (GET_CODE (insn) == NOTE
3640	  && NOTE_LINE_NUMBER (insn) == NOTE_INSN_EPILOGUE_BEG)
3641	epilogue_insn = insn;
3642    }
3643
3644  uid_to_ruid = (int *) xmalloc ((max_uid + 1) * sizeof (int));
3645  for (i = 0, insn = first; insn; i++, insn = NEXT_INSN (insn))
3646    uid_to_ruid[INSN_UID (insn)] = i;
3647
3648  /* Initialize the list of insns that need filling.  */
3649  if (unfilled_firstobj == 0)
3650    {
3651      gcc_obstack_init (&unfilled_slots_obstack);
3652      unfilled_firstobj = (rtx *) obstack_alloc (&unfilled_slots_obstack, 0);
3653    }
3654
3655  for (insn = next_active_insn (first); insn; insn = next_active_insn (insn))
3656    {
3657      rtx target;
3658
3659      INSN_ANNULLED_BRANCH_P (insn) = 0;
3660      INSN_FROM_TARGET_P (insn) = 0;
3661
3662      /* Skip vector tables.  We can't get attributes for them.  */
3663      if (GET_CODE (insn) == JUMP_INSN
3664	  && (GET_CODE (PATTERN (insn)) == ADDR_VEC
3665	      || GET_CODE (PATTERN (insn)) == ADDR_DIFF_VEC))
3666	continue;
3667
3668      if (num_delay_slots (insn) > 0)
3669	obstack_ptr_grow (&unfilled_slots_obstack, insn);
3670
3671      /* Ensure all jumps go to the last of a set of consecutive labels.  */
3672      if (GET_CODE (insn) == JUMP_INSN
3673	  && (condjump_p (insn) || condjump_in_parallel_p (insn))
3674	  && JUMP_LABEL (insn) != 0
3675	  && ((target = prev_label (next_active_insn (JUMP_LABEL (insn))))
3676	      != JUMP_LABEL (insn)))
3677	redirect_jump (insn, target, 1);
3678    }
3679
3680  init_resource_info (epilogue_insn);
3681
3682  /* Show we haven't computed an end-of-function label yet.  */
3683  end_of_function_label = 0;
3684
3685  /* Initialize the statistics for this function.  */
3686  memset ((char *) num_insns_needing_delays, 0, sizeof num_insns_needing_delays);
3687  memset ((char *) num_filled_delays, 0, sizeof num_filled_delays);
3688
3689  /* Now do the delay slot filling.  Try everything twice in case earlier
3690     changes make more slots fillable.  */
3691
3692  for (reorg_pass_number = 0;
3693       reorg_pass_number < MAX_REORG_PASSES;
3694       reorg_pass_number++)
3695    {
3696      fill_simple_delay_slots (1);
3697      fill_simple_delay_slots (0);
3698      fill_eager_delay_slots ();
3699      relax_delay_slots (first);
3700    }
3701
3702  /* Delete any USE insns made by update_block; subsequent passes don't need
3703     them or know how to deal with them.  */
3704  for (insn = first; insn; insn = next)
3705    {
3706      next = NEXT_INSN (insn);
3707
3708      if (GET_CODE (insn) == INSN && GET_CODE (PATTERN (insn)) == USE
3709	  && INSN_P (XEXP (PATTERN (insn), 0)))
3710	next = delete_related_insns (insn);
3711    }
3712
3713  /* If we made an end of function label, indicate that it is now
3714     safe to delete it by undoing our prior adjustment to LABEL_NUSES.
3715     If it is now unused, delete it.  */
3716  if (end_of_function_label && --LABEL_NUSES (end_of_function_label) == 0)
3717    delete_related_insns (end_of_function_label);
3718
3719#ifdef HAVE_return
3720  if (HAVE_return && end_of_function_label != 0)
3721    make_return_insns (first);
3722#endif
3723
3724  obstack_free (&unfilled_slots_obstack, unfilled_firstobj);
3725
3726  /* It is not clear why the line below is needed, but it does seem to be.  */
3727  unfilled_firstobj = (rtx *) obstack_alloc (&unfilled_slots_obstack, 0);
3728
3729  if (file)
3730    {
3731      int i, j, need_comma;
3732      int total_delay_slots[MAX_DELAY_HISTOGRAM + 1];
3733      int total_annul_slots[MAX_DELAY_HISTOGRAM + 1];
3734
3735      for (reorg_pass_number = 0;
3736	   reorg_pass_number < MAX_REORG_PASSES;
3737	   reorg_pass_number++)
3738	{
3739	  fprintf (file, ";; Reorg pass #%d:\n", reorg_pass_number + 1);
3740	  for (i = 0; i < NUM_REORG_FUNCTIONS; i++)
3741	    {
3742	      need_comma = 0;
3743	      fprintf (file, ";; Reorg function #%d\n", i);
3744
3745	      fprintf (file, ";; %d insns needing delay slots\n;; ",
3746		       num_insns_needing_delays[i][reorg_pass_number]);
3747
3748	      for (j = 0; j < MAX_DELAY_HISTOGRAM + 1; j++)
3749		if (num_filled_delays[i][j][reorg_pass_number])
3750		  {
3751		    if (need_comma)
3752		      fprintf (file, ", ");
3753		    need_comma = 1;
3754		    fprintf (file, "%d got %d delays",
3755			     num_filled_delays[i][j][reorg_pass_number], j);
3756		  }
3757	      fprintf (file, "\n");
3758	    }
3759	}
3760      memset ((char *) total_delay_slots, 0, sizeof total_delay_slots);
3761      memset ((char *) total_annul_slots, 0, sizeof total_annul_slots);
3762      for (insn = first; insn; insn = NEXT_INSN (insn))
3763	{
3764	  if (! INSN_DELETED_P (insn)
3765	      && GET_CODE (insn) == INSN
3766	      && GET_CODE (PATTERN (insn)) != USE
3767	      && GET_CODE (PATTERN (insn)) != CLOBBER)
3768	    {
3769	      if (GET_CODE (PATTERN (insn)) == SEQUENCE)
3770		{
3771		  j = XVECLEN (PATTERN (insn), 0) - 1;
3772		  if (j > MAX_DELAY_HISTOGRAM)
3773		    j = MAX_DELAY_HISTOGRAM;
3774		  if (INSN_ANNULLED_BRANCH_P (XVECEXP (PATTERN (insn), 0, 0)))
3775		    total_annul_slots[j]++;
3776		  else
3777		    total_delay_slots[j]++;
3778		}
3779	      else if (num_delay_slots (insn) > 0)
3780		total_delay_slots[0]++;
3781	    }
3782	}
3783      fprintf (file, ";; Reorg totals: ");
3784      need_comma = 0;
3785      for (j = 0; j < MAX_DELAY_HISTOGRAM + 1; j++)
3786	{
3787	  if (total_delay_slots[j])
3788	    {
3789	      if (need_comma)
3790		fprintf (file, ", ");
3791	      need_comma = 1;
3792	      fprintf (file, "%d got %d delays", total_delay_slots[j], j);
3793	    }
3794	}
3795      fprintf (file, "\n");
3796#if defined (ANNUL_IFTRUE_SLOTS) || defined (ANNUL_IFFALSE_SLOTS)
3797      fprintf (file, ";; Reorg annuls: ");
3798      need_comma = 0;
3799      for (j = 0; j < MAX_DELAY_HISTOGRAM + 1; j++)
3800	{
3801	  if (total_annul_slots[j])
3802	    {
3803	      if (need_comma)
3804		fprintf (file, ", ");
3805	      need_comma = 1;
3806	      fprintf (file, "%d got %d delays", total_annul_slots[j], j);
3807	    }
3808	}
3809      fprintf (file, "\n");
3810#endif
3811      fprintf (file, "\n");
3812    }
3813
3814  /* For all JUMP insns, fill in branch prediction notes, so that during
3815     assembler output a target can set branch prediction bits in the code.
3816     We have to do this now, as up until this point the destinations of
3817     JUMPS can be moved around and changed, but past right here that cannot
3818     happen.  */
3819  for (insn = first; insn; insn = NEXT_INSN (insn))
3820    {
3821      int pred_flags;
3822
3823      if (GET_CODE (insn) == INSN)
3824	{
3825	  rtx pat = PATTERN (insn);
3826
3827	  if (GET_CODE (pat) == SEQUENCE)
3828	    insn = XVECEXP (pat, 0, 0);
3829	}
3830      if (GET_CODE (insn) != JUMP_INSN)
3831	continue;
3832
3833      pred_flags = get_jump_flags (insn, JUMP_LABEL (insn));
3834      REG_NOTES (insn) = gen_rtx_EXPR_LIST (REG_BR_PRED,
3835					    GEN_INT (pred_flags),
3836					    REG_NOTES (insn));
3837    }
3838  free_resource_info ();
3839  free (uid_to_ruid);
3840}
3841#endif /* DELAY_SLOTS */
3842