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