1/* Instruction scheduling pass.
2   Copyright (C) 1992, 93-98, 1999 Free Software Foundation, Inc.
3   Contributed by Michael Tiemann (tiemann@cygnus.com) Enhanced by,
4   and currently maintained by, Jim Wilson (wilson@cygnus.com)
5
6   This file is part of GNU CC.
7
8   GNU CC is free software; you can redistribute it and/or modify it
9   under the terms of the GNU General Public License as published by
10   the Free Software Foundation; either version 2, or (at your option)
11   any later version.
12
13   GNU CC is distributed in the hope that it will be useful, but
14   WITHOUT ANY WARRANTY; without even the implied warranty of
15   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
16   General Public License for more details.
17
18   You should have received a copy of the GNU General Public License
19   along with GNU CC; see the file COPYING.  If not, write to the Free
20   the Free Software Foundation, 59 Temple Place - Suite 330,
21   Boston, MA 02111-1307, USA.  */
22
23
24/* Instruction scheduling pass.
25
26   This pass implements list scheduling within basic blocks.  It is
27   run twice: (1) after flow analysis, but before register allocation,
28   and (2) after register allocation.
29
30   The first run performs interblock scheduling, moving insns between
31   different blocks in the same "region", and the second runs only
32   basic block scheduling.
33
34   Interblock motions performed are useful motions and speculative
35   motions, including speculative loads.  Motions requiring code
36   duplication are not supported.  The identification of motion type
37   and the check for validity of speculative motions requires
38   construction and analysis of the function's control flow graph.
39   The scheduler works as follows:
40
41   We compute insn priorities based on data dependencies.  Flow
42   analysis only creates a fraction of the data-dependencies we must
43   observe: namely, only those dependencies which the combiner can be
44   expected to use.  For this pass, we must therefore create the
45   remaining dependencies we need to observe: register dependencies,
46   memory dependencies, dependencies to keep function calls in order,
47   and the dependence between a conditional branch and the setting of
48   condition codes are all dealt with here.
49
50   The scheduler first traverses the data flow graph, starting with
51   the last instruction, and proceeding to the first, assigning values
52   to insn_priority as it goes.  This sorts the instructions
53   topologically by data dependence.
54
55   Once priorities have been established, we order the insns using
56   list scheduling.  This works as follows: starting with a list of
57   all the ready insns, and sorted according to priority number, we
58   schedule the insn from the end of the list by placing its
59   predecessors in the list according to their priority order.  We
60   consider this insn scheduled by setting the pointer to the "end" of
61   the list to point to the previous insn.  When an insn has no
62   predecessors, we either queue it until sufficient time has elapsed
63   or add it to the ready list.  As the instructions are scheduled or
64   when stalls are introduced, the queue advances and dumps insns into
65   the ready list.  When all insns down to the lowest priority have
66   been scheduled, the critical path of the basic block has been made
67   as short as possible.  The remaining insns are then scheduled in
68   remaining slots.
69
70   Function unit conflicts are resolved during forward list scheduling
71   by tracking the time when each insn is committed to the schedule
72   and from that, the time the function units it uses must be free.
73   As insns on the ready list are considered for scheduling, those
74   that would result in a blockage of the already committed insns are
75   queued until no blockage will result.
76
77   The following list shows the order in which we want to break ties
78   among insns in the ready list:
79
80   1.  choose insn with the longest path to end of bb, ties
81   broken by
82   2.  choose insn with least contribution to register pressure,
83   ties broken by
84   3.  prefer in-block upon interblock motion, ties broken by
85   4.  prefer useful upon speculative motion, ties broken by
86   5.  choose insn with largest control flow probability, ties
87   broken by
88   6.  choose insn with the least dependences upon the previously
89   scheduled insn, or finally
90   7   choose the insn which has the most insns dependent on it.
91   8.  choose insn with lowest UID.
92
93   Memory references complicate matters.  Only if we can be certain
94   that memory references are not part of the data dependency graph
95   (via true, anti, or output dependence), can we move operations past
96   memory references.  To first approximation, reads can be done
97   independently, while writes introduce dependencies.  Better
98   approximations will yield fewer dependencies.
99
100   Before reload, an extended analysis of interblock data dependences
101   is required for interblock scheduling.  This is performed in
102   compute_block_backward_dependences ().
103
104   Dependencies set up by memory references are treated in exactly the
105   same way as other dependencies, by using LOG_LINKS backward
106   dependences.  LOG_LINKS are translated into INSN_DEPEND forward
107   dependences for the purpose of forward list scheduling.
108
109   Having optimized the critical path, we may have also unduly
110   extended the lifetimes of some registers.  If an operation requires
111   that constants be loaded into registers, it is certainly desirable
112   to load those constants as early as necessary, but no earlier.
113   I.e., it will not do to load up a bunch of registers at the
114   beginning of a basic block only to use them at the end, if they
115   could be loaded later, since this may result in excessive register
116   utilization.
117
118   Note that since branches are never in basic blocks, but only end
119   basic blocks, this pass will not move branches.  But that is ok,
120   since we can use GNU's delayed branch scheduling pass to take care
121   of this case.
122
123   Also note that no further optimizations based on algebraic
124   identities are performed, so this pass would be a good one to
125   perform instruction splitting, such as breaking up a multiply
126   instruction into shifts and adds where that is profitable.
127
128   Given the memory aliasing analysis that this pass should perform,
129   it should be possible to remove redundant stores to memory, and to
130   load values from registers instead of hitting memory.
131
132   Before reload, speculative insns are moved only if a 'proof' exists
133   that no exception will be caused by this, and if no live registers
134   exist that inhibit the motion (live registers constraints are not
135   represented by data dependence edges).
136
137   This pass must update information that subsequent passes expect to
138   be correct.  Namely: reg_n_refs, reg_n_sets, reg_n_deaths,
139   reg_n_calls_crossed, and reg_live_length.  Also, BLOCK_HEAD,
140   BLOCK_END.
141
142   The information in the line number notes is carefully retained by
143   this pass.  Notes that refer to the starting and ending of
144   exception regions are also carefully retained by this pass.  All
145   other NOTE insns are grouped in their same relative order at the
146   beginning of basic blocks and regions that have been scheduled.
147
148   The main entry point for this pass is schedule_insns(), called for
149   each function.  The work of the scheduler is organized in three
150   levels: (1) function level: insns are subject to splitting,
151   control-flow-graph is constructed, regions are computed (after
152   reload, each region is of one block), (2) region level: control
153   flow graph attributes required for interblock scheduling are
154   computed (dominators, reachability, etc.), data dependences and
155   priorities are computed, and (3) block level: insns in the block
156   are actually scheduled.  */
157
158#include "config.h"
159#include "system.h"
160#include "toplev.h"
161#include "rtl.h"
162#include "basic-block.h"
163#include "regs.h"
164#include "hard-reg-set.h"
165#include "flags.h"
166#include "insn-config.h"
167#include "insn-attr.h"
168#include "except.h"
169#include "toplev.h"
170#include "recog.h"
171
172extern char *reg_known_equiv_p;
173extern rtx *reg_known_value;
174
175#ifdef INSN_SCHEDULING
176
177/* target_units bitmask has 1 for each unit in the cpu.  It should be
178   possible to compute this variable from the machine description.
179   But currently it is computed by examinning the insn list.  Since
180   this is only needed for visualization, it seems an acceptable
181   solution.  (For understanding the mapping of bits to units, see
182   definition of function_units[] in "insn-attrtab.c") */
183
184static int target_units = 0;
185
186/* issue_rate is the number of insns that can be scheduled in the same
187   machine cycle.  It can be defined in the config/mach/mach.h file,
188   otherwise we set it to 1.  */
189
190static int issue_rate;
191
192#ifndef ISSUE_RATE
193#define ISSUE_RATE 1
194#endif
195
196/* sched-verbose controls the amount of debugging output the
197   scheduler prints.  It is controlled by -fsched-verbose-N:
198   N>0 and no -DSR : the output is directed to stderr.
199   N>=10 will direct the printouts to stderr (regardless of -dSR).
200   N=1: same as -dSR.
201   N=2: bb's probabilities, detailed ready list info, unit/insn info.
202   N=3: rtl at abort point, control-flow, regions info.
203   N=5: dependences info.  */
204
205#define MAX_RGN_BLOCKS 10
206#define MAX_RGN_INSNS 100
207
208static int sched_verbose_param = 0;
209static int sched_verbose = 0;
210
211/* nr_inter/spec counts interblock/speculative motion for the function */
212static int nr_inter, nr_spec;
213
214
215/* debugging file. all printouts are sent to dump, which is always set,
216   either to stderr, or to the dump listing file (-dRS).  */
217static FILE *dump = 0;
218
219/* fix_sched_param() is called from toplev.c upon detection
220   of the -fsched-***-N options.  */
221
222void
223fix_sched_param (param, val)
224     char *param, *val;
225{
226  if (!strcmp (param, "verbose"))
227    sched_verbose_param = atoi (val);
228  else
229    warning ("fix_sched_param: unknown param: %s", param);
230}
231
232
233/* Arrays set up by scheduling for the same respective purposes as
234   similar-named arrays set up by flow analysis.  We work with these
235   arrays during the scheduling pass so we can compare values against
236   unscheduled code.
237
238   Values of these arrays are copied at the end of this pass into the
239   arrays set up by flow analysis.  */
240static int *sched_reg_n_calls_crossed;
241static int *sched_reg_live_length;
242static int *sched_reg_basic_block;
243
244/* We need to know the current block number during the post scheduling
245   update of live register information so that we can also update
246   REG_BASIC_BLOCK if a register changes blocks.  */
247static int current_block_num;
248
249/* Element N is the next insn that sets (hard or pseudo) register
250   N within the current basic block; or zero, if there is no
251   such insn.  Needed for new registers which may be introduced
252   by splitting insns.  */
253static rtx *reg_last_uses;
254static rtx *reg_last_sets;
255static rtx *reg_last_clobbers;
256static regset reg_pending_sets;
257static regset reg_pending_clobbers;
258static int reg_pending_sets_all;
259
260/* Vector indexed by INSN_UID giving the original ordering of the insns.  */
261static int *insn_luid;
262#define INSN_LUID(INSN) (insn_luid[INSN_UID (INSN)])
263
264/* Vector indexed by INSN_UID giving each instruction a priority.  */
265static int *insn_priority;
266#define INSN_PRIORITY(INSN) (insn_priority[INSN_UID (INSN)])
267
268static short *insn_costs;
269#define INSN_COST(INSN)	insn_costs[INSN_UID (INSN)]
270
271/* Vector indexed by INSN_UID giving an encoding of the function units
272   used.  */
273static short *insn_units;
274#define INSN_UNIT(INSN)	insn_units[INSN_UID (INSN)]
275
276/* Vector indexed by INSN_UID giving each instruction a register-weight.
277   This weight is an estimation of the insn contribution to registers pressure.  */
278static int *insn_reg_weight;
279#define INSN_REG_WEIGHT(INSN) (insn_reg_weight[INSN_UID (INSN)])
280
281/* Vector indexed by INSN_UID giving list of insns which
282   depend upon INSN.  Unlike LOG_LINKS, it represents forward dependences.  */
283static rtx *insn_depend;
284#define INSN_DEPEND(INSN) insn_depend[INSN_UID (INSN)]
285
286/* Vector indexed by INSN_UID. Initialized to the number of incoming
287   edges in forward dependence graph (= number of LOG_LINKS).  As
288   scheduling procedes, dependence counts are decreased.  An
289   instruction moves to the ready list when its counter is zero.  */
290static int *insn_dep_count;
291#define INSN_DEP_COUNT(INSN) (insn_dep_count[INSN_UID (INSN)])
292
293/* Vector indexed by INSN_UID giving an encoding of the blockage range
294   function.  The unit and the range are encoded.  */
295static unsigned int *insn_blockage;
296#define INSN_BLOCKAGE(INSN) insn_blockage[INSN_UID (INSN)]
297#define UNIT_BITS 5
298#define BLOCKAGE_MASK ((1 << BLOCKAGE_BITS) - 1)
299#define ENCODE_BLOCKAGE(U, R)				\
300(((U) << BLOCKAGE_BITS					\
301  | MIN_BLOCKAGE_COST (R)) << BLOCKAGE_BITS		\
302 | MAX_BLOCKAGE_COST (R))
303#define UNIT_BLOCKED(B) ((B) >> (2 * BLOCKAGE_BITS))
304#define BLOCKAGE_RANGE(B)                                                \
305  (((((B) >> BLOCKAGE_BITS) & BLOCKAGE_MASK) << (HOST_BITS_PER_INT / 2)) \
306   | ((B) & BLOCKAGE_MASK))
307
308/* Encodings of the `<name>_unit_blockage_range' function.  */
309#define MIN_BLOCKAGE_COST(R) ((R) >> (HOST_BITS_PER_INT / 2))
310#define MAX_BLOCKAGE_COST(R) ((R) & ((1 << (HOST_BITS_PER_INT / 2)) - 1))
311
312#define DONE_PRIORITY	-1
313#define MAX_PRIORITY	0x7fffffff
314#define TAIL_PRIORITY	0x7ffffffe
315#define LAUNCH_PRIORITY	0x7f000001
316#define DONE_PRIORITY_P(INSN) (INSN_PRIORITY (INSN) < 0)
317#define LOW_PRIORITY_P(INSN) ((INSN_PRIORITY (INSN) & 0x7f000000) == 0)
318
319/* Vector indexed by INSN_UID giving number of insns referring to this insn.  */
320static int *insn_ref_count;
321#define INSN_REF_COUNT(INSN) (insn_ref_count[INSN_UID (INSN)])
322
323/* Vector indexed by INSN_UID giving line-number note in effect for each
324   insn.  For line-number notes, this indicates whether the note may be
325   reused.  */
326static rtx *line_note;
327#define LINE_NOTE(INSN) (line_note[INSN_UID (INSN)])
328
329/* Vector indexed by basic block number giving the starting line-number
330   for each basic block.  */
331static rtx *line_note_head;
332
333/* List of important notes we must keep around.  This is a pointer to the
334   last element in the list.  */
335static rtx note_list;
336
337/* Regsets telling whether a given register is live or dead before the last
338   scheduled insn.  Must scan the instructions once before scheduling to
339   determine what registers are live or dead at the end of the block.  */
340static regset bb_live_regs;
341
342/* Regset telling whether a given register is live after the insn currently
343   being scheduled.  Before processing an insn, this is equal to bb_live_regs
344   above.  This is used so that we can find registers that are newly born/dead
345   after processing an insn.  */
346static regset old_live_regs;
347
348/* The chain of REG_DEAD notes.  REG_DEAD notes are removed from all insns
349   during the initial scan and reused later.  If there are not exactly as
350   many REG_DEAD notes in the post scheduled code as there were in the
351   prescheduled code then we trigger an abort because this indicates a bug.  */
352static rtx dead_notes;
353
354/* Queues, etc.  */
355
356/* An instruction is ready to be scheduled when all insns preceding it
357   have already been scheduled.  It is important to ensure that all
358   insns which use its result will not be executed until its result
359   has been computed.  An insn is maintained in one of four structures:
360
361   (P) the "Pending" set of insns which cannot be scheduled until
362   their dependencies have been satisfied.
363   (Q) the "Queued" set of insns that can be scheduled when sufficient
364   time has passed.
365   (R) the "Ready" list of unscheduled, uncommitted insns.
366   (S) the "Scheduled" list of insns.
367
368   Initially, all insns are either "Pending" or "Ready" depending on
369   whether their dependencies are satisfied.
370
371   Insns move from the "Ready" list to the "Scheduled" list as they
372   are committed to the schedule.  As this occurs, the insns in the
373   "Pending" list have their dependencies satisfied and move to either
374   the "Ready" list or the "Queued" set depending on whether
375   sufficient time has passed to make them ready.  As time passes,
376   insns move from the "Queued" set to the "Ready" list.  Insns may
377   move from the "Ready" list to the "Queued" set if they are blocked
378   due to a function unit conflict.
379
380   The "Pending" list (P) are the insns in the INSN_DEPEND of the unscheduled
381   insns, i.e., those that are ready, queued, and pending.
382   The "Queued" set (Q) is implemented by the variable `insn_queue'.
383   The "Ready" list (R) is implemented by the variables `ready' and
384   `n_ready'.
385   The "Scheduled" list (S) is the new insn chain built by this pass.
386
387   The transition (R->S) is implemented in the scheduling loop in
388   `schedule_block' when the best insn to schedule is chosen.
389   The transition (R->Q) is implemented in `queue_insn' when an
390   insn is found to have a function unit conflict with the already
391   committed insns.
392   The transitions (P->R and P->Q) are implemented in `schedule_insn' as
393   insns move from the ready list to the scheduled list.
394   The transition (Q->R) is implemented in 'queue_to_insn' as time
395   passes or stalls are introduced.  */
396
397/* Implement a circular buffer to delay instructions until sufficient
398   time has passed.  INSN_QUEUE_SIZE is a power of two larger than
399   MAX_BLOCKAGE and MAX_READY_COST computed by genattr.c.  This is the
400   longest time an isnsn may be queued.  */
401static rtx insn_queue[INSN_QUEUE_SIZE];
402static int q_ptr = 0;
403static int q_size = 0;
404#define NEXT_Q(X) (((X)+1) & (INSN_QUEUE_SIZE-1))
405#define NEXT_Q_AFTER(X, C) (((X)+C) & (INSN_QUEUE_SIZE-1))
406
407/* Vector indexed by INSN_UID giving the minimum clock tick at which
408   the insn becomes ready.  This is used to note timing constraints for
409   insns in the pending list.  */
410static int *insn_tick;
411#define INSN_TICK(INSN) (insn_tick[INSN_UID (INSN)])
412
413/* Data structure for keeping track of register information
414   during that register's life.  */
415
416struct sometimes
417  {
418    int regno;
419    int live_length;
420    int calls_crossed;
421  };
422
423/* Forward declarations.  */
424static void add_dependence PROTO ((rtx, rtx, enum reg_note));
425static void remove_dependence PROTO ((rtx, rtx));
426static rtx find_insn_list PROTO ((rtx, rtx));
427static int insn_unit PROTO ((rtx));
428static unsigned int blockage_range PROTO ((int, rtx));
429static void clear_units PROTO ((void));
430static int actual_hazard_this_instance PROTO ((int, int, rtx, int, int));
431static void schedule_unit PROTO ((int, rtx, int));
432static int actual_hazard PROTO ((int, rtx, int, int));
433static int potential_hazard PROTO ((int, rtx, int));
434static int insn_cost PROTO ((rtx, rtx, rtx));
435static int priority PROTO ((rtx));
436static void free_pending_lists PROTO ((void));
437static void add_insn_mem_dependence PROTO ((rtx *, rtx *, rtx, rtx));
438static void flush_pending_lists PROTO ((rtx, int));
439static void sched_analyze_1 PROTO ((rtx, rtx));
440static void sched_analyze_2 PROTO ((rtx, rtx));
441static void sched_analyze_insn PROTO ((rtx, rtx, rtx));
442static void sched_analyze PROTO ((rtx, rtx));
443static void sched_note_set PROTO ((rtx, int));
444static int rank_for_schedule PROTO ((const GENERIC_PTR, const GENERIC_PTR));
445static void swap_sort PROTO ((rtx *, int));
446static void queue_insn PROTO ((rtx, int));
447static int schedule_insn PROTO ((rtx, rtx *, int, int));
448static void create_reg_dead_note PROTO ((rtx, rtx));
449static void attach_deaths PROTO ((rtx, rtx, int));
450static void attach_deaths_insn PROTO ((rtx));
451static int new_sometimes_live PROTO ((struct sometimes *, int, int));
452static void finish_sometimes_live PROTO ((struct sometimes *, int));
453static int schedule_block PROTO ((int, int));
454static void split_hard_reg_notes PROTO ((rtx, rtx, rtx));
455static void new_insn_dead_notes PROTO ((rtx, rtx, rtx, rtx));
456static void update_n_sets PROTO ((rtx, int));
457static char *safe_concat PROTO ((char *, char *, char *));
458static int insn_issue_delay PROTO ((rtx));
459static int birthing_insn_p PROTO ((rtx));
460static void adjust_priority PROTO ((rtx));
461
462/* Mapping of insns to their original block prior to scheduling.  */
463static int *insn_orig_block;
464#define INSN_BLOCK(insn) (insn_orig_block[INSN_UID (insn)])
465
466/* Some insns (e.g. call) are not allowed to move across blocks.  */
467static char *cant_move;
468#define CANT_MOVE(insn) (cant_move[INSN_UID (insn)])
469
470/* Control flow graph edges are kept in circular lists.  */
471typedef struct
472  {
473    int from_block;
474    int to_block;
475    int next_in;
476    int next_out;
477  }
478haifa_edge;
479static haifa_edge *edge_table;
480
481#define NEXT_IN(edge) (edge_table[edge].next_in)
482#define NEXT_OUT(edge) (edge_table[edge].next_out)
483#define FROM_BLOCK(edge) (edge_table[edge].from_block)
484#define TO_BLOCK(edge) (edge_table[edge].to_block)
485
486/* Number of edges in the control flow graph.  (in fact larger than
487   that by 1, since edge 0 is unused.) */
488static int nr_edges;
489
490/* Circular list of incoming/outgoing edges of a block */
491static int *in_edges;
492static int *out_edges;
493
494#define IN_EDGES(block) (in_edges[block])
495#define OUT_EDGES(block) (out_edges[block])
496
497/* List of labels which cannot be deleted, needed for control
498   flow graph construction.  */
499extern rtx forced_labels;
500
501
502static int is_cfg_nonregular PROTO ((void));
503static int build_control_flow PROTO ((int_list_ptr *, int_list_ptr *,
504				      int *, int *));
505static void new_edge PROTO ((int, int));
506
507
508/* A region is the main entity for interblock scheduling: insns
509   are allowed to move between blocks in the same region, along
510   control flow graph edges, in the 'up' direction.  */
511typedef struct
512  {
513    int rgn_nr_blocks;		/* number of blocks in region */
514    int rgn_blocks;		/* blocks in the region (actually index in rgn_bb_table) */
515  }
516region;
517
518/* Number of regions in the procedure */
519static int nr_regions;
520
521/* Table of region descriptions */
522static region *rgn_table;
523
524/* Array of lists of regions' blocks */
525static int *rgn_bb_table;
526
527/* Topological order of blocks in the region (if b2 is reachable from
528   b1, block_to_bb[b2] > block_to_bb[b1]).
529   Note: A basic block is always referred to by either block or b,
530   while its topological order name (in the region) is refered to by
531   bb.
532 */
533static int *block_to_bb;
534
535/* The number of the region containing a block.  */
536static int *containing_rgn;
537
538#define RGN_NR_BLOCKS(rgn) (rgn_table[rgn].rgn_nr_blocks)
539#define RGN_BLOCKS(rgn) (rgn_table[rgn].rgn_blocks)
540#define BLOCK_TO_BB(block) (block_to_bb[block])
541#define CONTAINING_RGN(block) (containing_rgn[block])
542
543void debug_regions PROTO ((void));
544static void find_single_block_region PROTO ((void));
545static void find_rgns PROTO ((int_list_ptr *, int_list_ptr *,
546			      int *, int *, sbitmap *));
547static int too_large PROTO ((int, int *, int *));
548
549extern void debug_live PROTO ((int, int));
550
551/* Blocks of the current region being scheduled.  */
552static int current_nr_blocks;
553static int current_blocks;
554
555/* The mapping from bb to block */
556#define BB_TO_BLOCK(bb) (rgn_bb_table[current_blocks + (bb)])
557
558
559/* Bit vectors and bitset operations are needed for computations on
560   the control flow graph.  */
561
562typedef unsigned HOST_WIDE_INT *bitset;
563typedef struct
564  {
565    int *first_member;		/* pointer to the list start in bitlst_table.  */
566    int nr_members;		/* the number of members of the bit list.     */
567  }
568bitlst;
569
570static int bitlst_table_last;
571static int bitlst_table_size;
572static int *bitlst_table;
573
574static char bitset_member PROTO ((bitset, int, int));
575static void extract_bitlst PROTO ((bitset, int, bitlst *));
576
577/* target info declarations.
578
579   The block currently being scheduled is referred to as the "target" block,
580   while other blocks in the region from which insns can be moved to the
581   target are called "source" blocks.  The candidate structure holds info
582   about such sources: are they valid?  Speculative?  Etc.  */
583typedef bitlst bblst;
584typedef struct
585  {
586    char is_valid;
587    char is_speculative;
588    int src_prob;
589    bblst split_bbs;
590    bblst update_bbs;
591  }
592candidate;
593
594static candidate *candidate_table;
595
596/* A speculative motion requires checking live information on the path
597   from 'source' to 'target'.  The split blocks are those to be checked.
598   After a speculative motion, live information should be modified in
599   the 'update' blocks.
600
601   Lists of split and update blocks for  each candidate of the current
602   target  are  in  array bblst_table */
603static int *bblst_table, bblst_size, bblst_last;
604
605#define IS_VALID(src) ( candidate_table[src].is_valid )
606#define IS_SPECULATIVE(src) ( candidate_table[src].is_speculative )
607#define SRC_PROB(src) ( candidate_table[src].src_prob )
608
609/* The bb being currently scheduled.  */
610static int target_bb;
611
612/* List of edges.  */
613typedef bitlst edgelst;
614
615/* target info functions */
616static void split_edges PROTO ((int, int, edgelst *));
617static void compute_trg_info PROTO ((int));
618void debug_candidate PROTO ((int));
619void debug_candidates PROTO ((int));
620
621
622/* Bit-set of bbs, where bit 'i' stands for bb 'i'.  */
623typedef bitset bbset;
624
625/* Number of words of the bbset.  */
626static int bbset_size;
627
628/* Dominators array: dom[i] contains the bbset of dominators of
629   bb i in the region.  */
630static bbset *dom;
631
632/* bb 0 is the only region entry */
633#define IS_RGN_ENTRY(bb) (!bb)
634
635/* Is bb_src dominated by bb_trg.  */
636#define IS_DOMINATED(bb_src, bb_trg)                                 \
637( bitset_member (dom[bb_src], bb_trg, bbset_size) )
638
639/* Probability: Prob[i] is a float in [0, 1] which is the probability
640   of bb i relative to the region entry.  */
641static float *prob;
642
643/*  The probability of bb_src, relative to bb_trg.  Note, that while the
644   'prob[bb]' is a float in [0, 1], this macro returns an integer
645   in [0, 100].  */
646#define GET_SRC_PROB(bb_src, bb_trg) ((int) (100.0 * (prob[bb_src] / \
647						      prob[bb_trg])))
648
649/* Bit-set of edges, where bit i stands for edge i.  */
650typedef bitset edgeset;
651
652/* Number of edges in the region.  */
653static int rgn_nr_edges;
654
655/* Array of size rgn_nr_edges.    */
656static int *rgn_edges;
657
658/* Number of words in an edgeset.    */
659static int edgeset_size;
660
661/* Mapping from each edge in the graph to its number in the rgn.  */
662static int *edge_to_bit;
663#define EDGE_TO_BIT(edge) (edge_to_bit[edge])
664
665/* The split edges of a source bb is different for each target
666   bb.  In order to compute this efficiently, the 'potential-split edges'
667   are computed for each bb prior to scheduling a region.  This is actually
668   the split edges of each bb relative to the region entry.
669
670   pot_split[bb] is the set of potential split edges of bb.  */
671static edgeset *pot_split;
672
673/* For every bb, a set of its ancestor edges.  */
674static edgeset *ancestor_edges;
675
676static void compute_dom_prob_ps PROTO ((int));
677
678#define ABS_VALUE(x) (((x)<0)?(-(x)):(x))
679#define INSN_PROBABILITY(INSN) (SRC_PROB (BLOCK_TO_BB (INSN_BLOCK (INSN))))
680#define IS_SPECULATIVE_INSN(INSN) (IS_SPECULATIVE (BLOCK_TO_BB (INSN_BLOCK (INSN))))
681#define INSN_BB(INSN) (BLOCK_TO_BB (INSN_BLOCK (INSN)))
682
683/* parameters affecting the decision of rank_for_schedule() */
684#define MIN_DIFF_PRIORITY 2
685#define MIN_PROBABILITY 40
686#define MIN_PROB_DIFF 10
687
688/* speculative scheduling functions */
689static int check_live_1 PROTO ((int, rtx));
690static void update_live_1 PROTO ((int, rtx));
691static int check_live PROTO ((rtx, int));
692static void update_live PROTO ((rtx, int));
693static void set_spec_fed PROTO ((rtx));
694static int is_pfree PROTO ((rtx, int, int));
695static int find_conditional_protection PROTO ((rtx, int));
696static int is_conditionally_protected PROTO ((rtx, int, int));
697static int may_trap_exp PROTO ((rtx, int));
698static int haifa_classify_insn PROTO ((rtx));
699static int is_prisky PROTO ((rtx, int, int));
700static int is_exception_free PROTO ((rtx, int, int));
701
702static char find_insn_mem_list PROTO ((rtx, rtx, rtx, rtx));
703static void compute_block_forward_dependences PROTO ((int));
704static void init_rgn_data_dependences PROTO ((int));
705static void add_branch_dependences PROTO ((rtx, rtx));
706static void compute_block_backward_dependences PROTO ((int));
707void debug_dependencies PROTO ((void));
708
709/* Notes handling mechanism:
710   =========================
711   Generally, NOTES are saved before scheduling and restored after scheduling.
712   The scheduler distinguishes between three types of notes:
713
714   (1) LINE_NUMBER notes, generated and used for debugging.  Here,
715   before scheduling a region, a pointer to the LINE_NUMBER note is
716   added to the insn following it (in save_line_notes()), and the note
717   is removed (in rm_line_notes() and unlink_line_notes()).  After
718   scheduling the region, this pointer is used for regeneration of
719   the LINE_NUMBER note (in restore_line_notes()).
720
721   (2) LOOP_BEGIN, LOOP_END, SETJMP, EHREGION_BEG, EHREGION_END notes:
722   Before scheduling a region, a pointer to the note is added to the insn
723   that follows or precedes it.  (This happens as part of the data dependence
724   computation).  After scheduling an insn, the pointer contained in it is
725   used for regenerating the corresponding note (in reemit_notes).
726
727   (3) All other notes (e.g. INSN_DELETED):  Before scheduling a block,
728   these notes are put in a list (in rm_other_notes() and
729   unlink_other_notes ()).  After scheduling the block, these notes are
730   inserted at the beginning of the block (in schedule_block()).  */
731
732static rtx unlink_other_notes PROTO ((rtx, rtx));
733static rtx unlink_line_notes PROTO ((rtx, rtx));
734static void rm_line_notes PROTO ((int));
735static void save_line_notes PROTO ((int));
736static void restore_line_notes PROTO ((int));
737static void rm_redundant_line_notes PROTO ((void));
738static void rm_other_notes PROTO ((rtx, rtx));
739static rtx reemit_notes PROTO ((rtx, rtx));
740
741static void get_block_head_tail PROTO ((int, rtx *, rtx *));
742
743static void find_pre_sched_live PROTO ((int));
744static void find_post_sched_live PROTO ((int));
745static void update_reg_usage PROTO ((void));
746static int queue_to_ready PROTO ((rtx [], int));
747
748static void debug_ready_list PROTO ((rtx[], int));
749static void init_target_units PROTO ((void));
750static void insn_print_units PROTO ((rtx));
751static int get_visual_tbl_length PROTO ((void));
752static void init_block_visualization PROTO ((void));
753static void print_block_visualization PROTO ((int, char *));
754static void visualize_scheduled_insns PROTO ((int, int));
755static void visualize_no_unit PROTO ((rtx));
756static void visualize_stall_cycles PROTO ((int, int));
757static void print_exp PROTO ((char *, rtx, int));
758static void print_value PROTO ((char *, rtx, int));
759static void print_pattern PROTO ((char *, rtx, int));
760static void print_insn PROTO ((char *, rtx, int));
761void debug_reg_vector PROTO ((regset));
762
763static rtx move_insn1 PROTO ((rtx, rtx));
764static rtx move_insn PROTO ((rtx, rtx));
765static rtx group_leader PROTO ((rtx));
766static int set_priorities PROTO ((int));
767static void init_rtx_vector PROTO ((rtx **, rtx *, int, int));
768static void schedule_region PROTO ((int));
769
770#endif /* INSN_SCHEDULING */
771
772#define SIZE_FOR_MODE(X) (GET_MODE_SIZE (GET_MODE (X)))
773
774/* Helper functions for instruction scheduling.  */
775
776/* An INSN_LIST containing all INSN_LISTs allocated but currently unused.  */
777static rtx unused_insn_list;
778
779/* An EXPR_LIST containing all EXPR_LISTs allocated but currently unused.  */
780static rtx unused_expr_list;
781
782static void free_list PROTO ((rtx *, rtx *));
783static rtx alloc_INSN_LIST PROTO ((rtx, rtx));
784static rtx alloc_EXPR_LIST PROTO ((int, rtx, rtx));
785
786static void
787free_list (listp, unused_listp)
788     rtx *listp, *unused_listp;
789{
790  register rtx link, prev_link;
791
792  if (*listp == 0)
793    return;
794
795  prev_link = *listp;
796  link = XEXP (prev_link, 1);
797
798  while (link)
799    {
800      prev_link = link;
801      link = XEXP (link, 1);
802    }
803
804  XEXP (prev_link, 1) = *unused_listp;
805  *unused_listp = *listp;
806  *listp = 0;
807}
808
809static rtx
810alloc_INSN_LIST (val, next)
811     rtx val, next;
812{
813  rtx r;
814
815  if (unused_insn_list)
816    {
817      r = unused_insn_list;
818      unused_insn_list = XEXP (r, 1);
819      XEXP (r, 0) = val;
820      XEXP (r, 1) = next;
821      PUT_REG_NOTE_KIND (r, VOIDmode);
822    }
823  else
824    r = gen_rtx_INSN_LIST (VOIDmode, val, next);
825
826  return r;
827}
828
829static rtx
830alloc_EXPR_LIST (kind, val, next)
831     int kind;
832     rtx val, next;
833{
834  rtx r;
835
836  if (unused_expr_list)
837    {
838      r = unused_expr_list;
839      unused_expr_list = XEXP (r, 1);
840      XEXP (r, 0) = val;
841      XEXP (r, 1) = next;
842      PUT_REG_NOTE_KIND (r, kind);
843    }
844  else
845    r = gen_rtx_EXPR_LIST (kind, val, next);
846
847  return r;
848}
849
850/* Add ELEM wrapped in an INSN_LIST with reg note kind DEP_TYPE to the
851   LOG_LINKS of INSN, if not already there.  DEP_TYPE indicates the type
852   of dependence that this link represents.  */
853
854static void
855add_dependence (insn, elem, dep_type)
856     rtx insn;
857     rtx elem;
858     enum reg_note dep_type;
859{
860  rtx link, next;
861
862  /* Don't depend an insn on itself.  */
863  if (insn == elem)
864    return;
865
866  /* We can get a dependency on deleted insns due to optimizations in
867     the register allocation and reloading or due to splitting.  Any
868     such dependency is useless and can be ignored.  */
869  if (GET_CODE (elem) == NOTE)
870    return;
871
872  /* If elem is part of a sequence that must be scheduled together, then
873     make the dependence point to the last insn of the sequence.
874     When HAVE_cc0, it is possible for NOTEs to exist between users and
875     setters of the condition codes, so we must skip past notes here.
876     Otherwise, NOTEs are impossible here.  */
877
878  next = NEXT_INSN (elem);
879
880#ifdef HAVE_cc0
881  while (next && GET_CODE (next) == NOTE)
882    next = NEXT_INSN (next);
883#endif
884
885  if (next && SCHED_GROUP_P (next)
886      && GET_CODE (next) != CODE_LABEL)
887    {
888      /* Notes will never intervene here though, so don't bother checking
889         for them.  */
890      /* We must reject CODE_LABELs, so that we don't get confused by one
891         that has LABEL_PRESERVE_P set, which is represented by the same
892         bit in the rtl as SCHED_GROUP_P.  A CODE_LABEL can never be
893         SCHED_GROUP_P.  */
894      while (NEXT_INSN (next) && SCHED_GROUP_P (NEXT_INSN (next))
895	     && GET_CODE (NEXT_INSN (next)) != CODE_LABEL)
896	next = NEXT_INSN (next);
897
898      /* Again, don't depend an insn on itself.  */
899      if (insn == next)
900	return;
901
902      /* Make the dependence to NEXT, the last insn of the group, instead
903         of the original ELEM.  */
904      elem = next;
905    }
906
907#ifdef INSN_SCHEDULING
908  /* (This code is guarded by INSN_SCHEDULING, otherwise INSN_BB is undefined.)
909     No need for interblock dependences with calls, since
910     calls are not moved between blocks.   Note: the edge where
911     elem is a CALL is still required.  */
912  if (GET_CODE (insn) == CALL_INSN
913      && (INSN_BB (elem) != INSN_BB (insn)))
914    return;
915
916#endif
917
918  /* Check that we don't already have this dependence.  */
919  for (link = LOG_LINKS (insn); link; link = XEXP (link, 1))
920    if (XEXP (link, 0) == elem)
921      {
922	/* If this is a more restrictive type of dependence than the existing
923	   one, then change the existing dependence to this type.  */
924	if ((int) dep_type < (int) REG_NOTE_KIND (link))
925	  PUT_REG_NOTE_KIND (link, dep_type);
926	return;
927      }
928  /* Might want to check one level of transitivity to save conses.  */
929
930  link = alloc_INSN_LIST (elem, LOG_LINKS (insn));
931  LOG_LINKS (insn) = link;
932
933  /* Insn dependency, not data dependency.  */
934  PUT_REG_NOTE_KIND (link, dep_type);
935}
936
937/* Remove ELEM wrapped in an INSN_LIST from the LOG_LINKS
938   of INSN.  Abort if not found.  */
939
940static void
941remove_dependence (insn, elem)
942     rtx insn;
943     rtx elem;
944{
945  rtx prev, link, next;
946  int found = 0;
947
948  for (prev = 0, link = LOG_LINKS (insn); link; link = next)
949    {
950      next = XEXP (link, 1);
951      if (XEXP (link, 0) == elem)
952	{
953	  if (prev)
954	    XEXP (prev, 1) = next;
955	  else
956	    LOG_LINKS (insn) = next;
957
958	  XEXP (link, 1) = unused_insn_list;
959	  unused_insn_list = link;
960
961	  found = 1;
962	}
963      else
964	prev = link;
965    }
966
967  if (!found)
968    abort ();
969  return;
970}
971
972#ifndef INSN_SCHEDULING
973void
974schedule_insns (dump_file)
975     FILE *dump_file;
976{
977}
978#else
979#ifndef __GNUC__
980#define __inline
981#endif
982
983#ifndef HAIFA_INLINE
984#define HAIFA_INLINE __inline
985#endif
986
987/* Computation of memory dependencies.  */
988
989/* The *_insns and *_mems are paired lists.  Each pending memory operation
990   will have a pointer to the MEM rtx on one list and a pointer to the
991   containing insn on the other list in the same place in the list.  */
992
993/* We can't use add_dependence like the old code did, because a single insn
994   may have multiple memory accesses, and hence needs to be on the list
995   once for each memory access.  Add_dependence won't let you add an insn
996   to a list more than once.  */
997
998/* An INSN_LIST containing all insns with pending read operations.  */
999static rtx pending_read_insns;
1000
1001/* An EXPR_LIST containing all MEM rtx's which are pending reads.  */
1002static rtx pending_read_mems;
1003
1004/* An INSN_LIST containing all insns with pending write operations.  */
1005static rtx pending_write_insns;
1006
1007/* An EXPR_LIST containing all MEM rtx's which are pending writes.  */
1008static rtx pending_write_mems;
1009
1010/* Indicates the combined length of the two pending lists.  We must prevent
1011   these lists from ever growing too large since the number of dependencies
1012   produced is at least O(N*N), and execution time is at least O(4*N*N), as
1013   a function of the length of these pending lists.  */
1014
1015static int pending_lists_length;
1016
1017/* The last insn upon which all memory references must depend.
1018   This is an insn which flushed the pending lists, creating a dependency
1019   between it and all previously pending memory references.  This creates
1020   a barrier (or a checkpoint) which no memory reference is allowed to cross.
1021
1022   This includes all non constant CALL_INSNs.  When we do interprocedural
1023   alias analysis, this restriction can be relaxed.
1024   This may also be an INSN that writes memory if the pending lists grow
1025   too large.  */
1026
1027static rtx last_pending_memory_flush;
1028
1029/* The last function call we have seen.  All hard regs, and, of course,
1030   the last function call, must depend on this.  */
1031
1032static rtx last_function_call;
1033
1034/* The LOG_LINKS field of this is a list of insns which use a pseudo register
1035   that does not already cross a call.  We create dependencies between each
1036   of those insn and the next call insn, to ensure that they won't cross a call
1037   after scheduling is done.  */
1038
1039static rtx sched_before_next_call;
1040
1041/* Pointer to the last instruction scheduled.  Used by rank_for_schedule,
1042   so that insns independent of the last scheduled insn will be preferred
1043   over dependent instructions.  */
1044
1045static rtx last_scheduled_insn;
1046
1047/* Data structures for the computation of data dependences in a regions.  We
1048   keep one copy of each of the declared above variables for each bb in the
1049   region.  Before analyzing the data dependences for a bb, its variables
1050   are initialized as a function of the variables of its predecessors.  When
1051   the analysis for a bb completes, we save the contents of each variable X
1052   to a corresponding bb_X[bb] variable.  For example, pending_read_insns is
1053   copied to bb_pending_read_insns[bb].  Another change is that few
1054   variables are now a list of insns rather than a single insn:
1055   last_pending_memory_flash, last_function_call, reg_last_sets.  The
1056   manipulation of these variables was changed appropriately.  */
1057
1058static rtx **bb_reg_last_uses;
1059static rtx **bb_reg_last_sets;
1060static rtx **bb_reg_last_clobbers;
1061
1062static rtx *bb_pending_read_insns;
1063static rtx *bb_pending_read_mems;
1064static rtx *bb_pending_write_insns;
1065static rtx *bb_pending_write_mems;
1066static int *bb_pending_lists_length;
1067
1068static rtx *bb_last_pending_memory_flush;
1069static rtx *bb_last_function_call;
1070static rtx *bb_sched_before_next_call;
1071
1072/* functions for construction of the control flow graph.  */
1073
1074/* Return 1 if control flow graph should not be constructed, 0 otherwise.
1075
1076   We decide not to build the control flow graph if there is possibly more
1077   than one entry to the function, if computed branches exist, of if we
1078   have nonlocal gotos.  */
1079
1080static int
1081is_cfg_nonregular ()
1082{
1083  int b;
1084  rtx insn;
1085  RTX_CODE code;
1086
1087  /* If we have a label that could be the target of a nonlocal goto, then
1088     the cfg is not well structured.  */
1089  if (nonlocal_goto_handler_labels)
1090    return 1;
1091
1092  /* If we have any forced labels, then the cfg is not well structured.  */
1093  if (forced_labels)
1094    return 1;
1095
1096  /* If this function has a computed jump, then we consider the cfg
1097     not well structured.  */
1098  if (current_function_has_computed_jump)
1099    return 1;
1100
1101  /* If we have exception handlers, then we consider the cfg not well
1102     structured.  ?!?  We should be able to handle this now that flow.c
1103     computes an accurate cfg for EH.  */
1104  if (exception_handler_labels)
1105    return 1;
1106
1107  /* If we have non-jumping insns which refer to labels, then we consider
1108     the cfg not well structured.  */
1109  /* check for labels referred to other thn by jumps */
1110  for (b = 0; b < n_basic_blocks; b++)
1111    for (insn = BLOCK_HEAD (b);; insn = NEXT_INSN (insn))
1112      {
1113	code = GET_CODE (insn);
1114	if (GET_RTX_CLASS (code) == 'i')
1115	  {
1116	    rtx note;
1117
1118	    for (note = REG_NOTES (insn); note; note = XEXP (note, 1))
1119	      if (REG_NOTE_KIND (note) == REG_LABEL)
1120		return 1;
1121	  }
1122
1123	if (insn == BLOCK_END (b))
1124	  break;
1125      }
1126
1127  /* All the tests passed.  Consider the cfg well structured.  */
1128  return 0;
1129}
1130
1131/* Build the control flow graph and set nr_edges.
1132
1133   Instead of trying to build a cfg ourselves, we rely on flow to
1134   do it for us.  Stamp out useless code (and bug) duplication.
1135
1136   Return nonzero if an irregularity in the cfg is found which would
1137   prevent cross block scheduling.  */
1138
1139static int
1140build_control_flow (s_preds, s_succs, num_preds, num_succs)
1141     int_list_ptr *s_preds;
1142     int_list_ptr *s_succs;
1143     int *num_preds;
1144     int *num_succs;
1145{
1146  int i;
1147  int_list_ptr succ;
1148  int unreachable;
1149
1150  /* Count the number of edges in the cfg.  */
1151  nr_edges = 0;
1152  unreachable = 0;
1153  for (i = 0; i < n_basic_blocks; i++)
1154    {
1155      nr_edges += num_succs[i];
1156
1157      /* Unreachable loops with more than one basic block are detected
1158	 during the DFS traversal in find_rgns.
1159
1160	 Unreachable loops with a single block are detected here.  This
1161	 test is redundant with the one in find_rgns, but it's much
1162	 cheaper to go ahead and catch the trivial case here.  */
1163      if (num_preds[i] == 0
1164	  || (num_preds[i] == 1 && INT_LIST_VAL (s_preds[i]) == i))
1165	unreachable = 1;
1166    }
1167
1168  /* Account for entry/exit edges.  */
1169  nr_edges += 2;
1170
1171  in_edges = (int *) xmalloc (n_basic_blocks * sizeof (int));
1172  out_edges = (int *) xmalloc (n_basic_blocks * sizeof (int));
1173  bzero ((char *) in_edges, n_basic_blocks * sizeof (int));
1174  bzero ((char *) out_edges, n_basic_blocks * sizeof (int));
1175
1176  edge_table = (haifa_edge *) xmalloc ((nr_edges) * sizeof (haifa_edge));
1177  bzero ((char *) edge_table, ((nr_edges) * sizeof (haifa_edge)));
1178
1179  nr_edges = 0;
1180  for (i = 0; i < n_basic_blocks; i++)
1181    for (succ = s_succs[i]; succ; succ = succ->next)
1182      {
1183	if (INT_LIST_VAL (succ) != EXIT_BLOCK)
1184	  new_edge (i, INT_LIST_VAL (succ));
1185      }
1186
1187  /* increment by 1, since edge 0 is unused.  */
1188  nr_edges++;
1189
1190  return unreachable;
1191}
1192
1193
1194/* Record an edge in the control flow graph from SOURCE to TARGET.
1195
1196   In theory, this is redundant with the s_succs computed above, but
1197   we have not converted all of haifa to use information from the
1198   integer lists.  */
1199
1200static void
1201new_edge (source, target)
1202     int source, target;
1203{
1204  int e, next_edge;
1205  int curr_edge, fst_edge;
1206
1207  /* check for duplicates */
1208  fst_edge = curr_edge = OUT_EDGES (source);
1209  while (curr_edge)
1210    {
1211      if (FROM_BLOCK (curr_edge) == source
1212	  && TO_BLOCK (curr_edge) == target)
1213	{
1214	  return;
1215	}
1216
1217      curr_edge = NEXT_OUT (curr_edge);
1218
1219      if (fst_edge == curr_edge)
1220	break;
1221    }
1222
1223  e = ++nr_edges;
1224
1225  FROM_BLOCK (e) = source;
1226  TO_BLOCK (e) = target;
1227
1228  if (OUT_EDGES (source))
1229    {
1230      next_edge = NEXT_OUT (OUT_EDGES (source));
1231      NEXT_OUT (OUT_EDGES (source)) = e;
1232      NEXT_OUT (e) = next_edge;
1233    }
1234  else
1235    {
1236      OUT_EDGES (source) = e;
1237      NEXT_OUT (e) = e;
1238    }
1239
1240  if (IN_EDGES (target))
1241    {
1242      next_edge = NEXT_IN (IN_EDGES (target));
1243      NEXT_IN (IN_EDGES (target)) = e;
1244      NEXT_IN (e) = next_edge;
1245    }
1246  else
1247    {
1248      IN_EDGES (target) = e;
1249      NEXT_IN (e) = e;
1250    }
1251}
1252
1253
1254/* BITSET macros for operations on the control flow graph.  */
1255
1256/* Compute  bitwise union  of two  bitsets.  */
1257#define BITSET_UNION(set1, set2, len)                                \
1258do { register bitset tp = set1, sp = set2;                           \
1259     register int i;                                                 \
1260     for (i = 0; i < len; i++)                                       \
1261       *(tp++) |= *(sp++); } while (0)
1262
1263/* Compute  bitwise intersection  of two  bitsets.  */
1264#define BITSET_INTER(set1, set2, len)                                \
1265do { register bitset tp = set1, sp = set2;                           \
1266     register int i;                                                 \
1267     for (i = 0; i < len; i++)                                       \
1268       *(tp++) &= *(sp++); } while (0)
1269
1270/* Compute bitwise   difference of  two bitsets.  */
1271#define BITSET_DIFFER(set1, set2, len)                               \
1272do { register bitset tp = set1, sp = set2;                           \
1273     register int i;                                                 \
1274     for (i = 0; i < len; i++)                                       \
1275       *(tp++) &= ~*(sp++); } while (0)
1276
1277/* Inverts every bit of bitset 'set' */
1278#define BITSET_INVERT(set, len)                                      \
1279do { register bitset tmpset = set;                                   \
1280     register int i;                                                 \
1281     for (i = 0; i < len; i++, tmpset++)                             \
1282       *tmpset = ~*tmpset; } while (0)
1283
1284/* Turn on the index'th bit in bitset set.  */
1285#define BITSET_ADD(set, index, len)                                  \
1286{                                                                    \
1287  if (index >= HOST_BITS_PER_WIDE_INT * len)                         \
1288    abort ();                                                        \
1289  else                                                               \
1290    set[index/HOST_BITS_PER_WIDE_INT] |=			     \
1291      1 << (index % HOST_BITS_PER_WIDE_INT);                         \
1292}
1293
1294/* Turn off the index'th bit in set.  */
1295#define BITSET_REMOVE(set, index, len)                               \
1296{                                                                    \
1297  if (index >= HOST_BITS_PER_WIDE_INT * len)                         \
1298    abort ();                                                        \
1299  else                                                               \
1300    set[index/HOST_BITS_PER_WIDE_INT] &=			     \
1301      ~(1 << (index%HOST_BITS_PER_WIDE_INT));                        \
1302}
1303
1304
1305/* Check if the index'th bit in bitset  set is on.  */
1306
1307static char
1308bitset_member (set, index, len)
1309     bitset set;
1310     int index, len;
1311{
1312  if (index >= HOST_BITS_PER_WIDE_INT * len)
1313    abort ();
1314  return (set[index / HOST_BITS_PER_WIDE_INT] &
1315	  1 << (index % HOST_BITS_PER_WIDE_INT)) ? 1 : 0;
1316}
1317
1318
1319/* Translate a bit-set SET to a list BL of the bit-set members.  */
1320
1321static void
1322extract_bitlst (set, len, bl)
1323     bitset set;
1324     int len;
1325     bitlst *bl;
1326{
1327  int i, j, offset;
1328  unsigned HOST_WIDE_INT word;
1329
1330  /* bblst table space is reused in each call to extract_bitlst */
1331  bitlst_table_last = 0;
1332
1333  bl->first_member = &bitlst_table[bitlst_table_last];
1334  bl->nr_members = 0;
1335
1336  for (i = 0; i < len; i++)
1337    {
1338      word = set[i];
1339      offset = i * HOST_BITS_PER_WIDE_INT;
1340      for (j = 0; word; j++)
1341	{
1342	  if (word & 1)
1343	    {
1344	      bitlst_table[bitlst_table_last++] = offset;
1345	      (bl->nr_members)++;
1346	    }
1347	  word >>= 1;
1348	  ++offset;
1349	}
1350    }
1351
1352}
1353
1354
1355/* functions for the construction of regions */
1356
1357/* Print the regions, for debugging purposes.  Callable from debugger.  */
1358
1359void
1360debug_regions ()
1361{
1362  int rgn, bb;
1363
1364  fprintf (dump, "\n;;   ------------ REGIONS ----------\n\n");
1365  for (rgn = 0; rgn < nr_regions; rgn++)
1366    {
1367      fprintf (dump, ";;\trgn %d nr_blocks %d:\n", rgn,
1368	       rgn_table[rgn].rgn_nr_blocks);
1369      fprintf (dump, ";;\tbb/block: ");
1370
1371      for (bb = 0; bb < rgn_table[rgn].rgn_nr_blocks; bb++)
1372	{
1373	  current_blocks = RGN_BLOCKS (rgn);
1374
1375	  if (bb != BLOCK_TO_BB (BB_TO_BLOCK (bb)))
1376	    abort ();
1377
1378	  fprintf (dump, " %d/%d ", bb, BB_TO_BLOCK (bb));
1379	}
1380
1381      fprintf (dump, "\n\n");
1382    }
1383}
1384
1385
1386/* Build a single block region for each basic block in the function.
1387   This allows for using the same code for interblock and basic block
1388   scheduling.  */
1389
1390static void
1391find_single_block_region ()
1392{
1393  int i;
1394
1395  for (i = 0; i < n_basic_blocks; i++)
1396    {
1397      rgn_bb_table[i] = i;
1398      RGN_NR_BLOCKS (i) = 1;
1399      RGN_BLOCKS (i) = i;
1400      CONTAINING_RGN (i) = i;
1401      BLOCK_TO_BB (i) = 0;
1402    }
1403  nr_regions = n_basic_blocks;
1404}
1405
1406
1407/* Update number of blocks and the estimate for number of insns
1408   in the region.  Return 1 if the region is "too large" for interblock
1409   scheduling (compile time considerations), otherwise return 0.  */
1410
1411static int
1412too_large (block, num_bbs, num_insns)
1413     int block, *num_bbs, *num_insns;
1414{
1415  (*num_bbs)++;
1416  (*num_insns) += (INSN_LUID (BLOCK_END (block)) -
1417		   INSN_LUID (BLOCK_HEAD (block)));
1418  if ((*num_bbs > MAX_RGN_BLOCKS) || (*num_insns > MAX_RGN_INSNS))
1419    return 1;
1420  else
1421    return 0;
1422}
1423
1424
1425/* Update_loop_relations(blk, hdr): Check if the loop headed by max_hdr[blk]
1426   is still an inner loop.  Put in max_hdr[blk] the header of the most inner
1427   loop containing blk.  */
1428#define UPDATE_LOOP_RELATIONS(blk, hdr)                              \
1429{                                                                    \
1430  if (max_hdr[blk] == -1)                                            \
1431    max_hdr[blk] = hdr;                                              \
1432  else if (dfs_nr[max_hdr[blk]] > dfs_nr[hdr])                       \
1433         RESET_BIT (inner, hdr);                                     \
1434  else if (dfs_nr[max_hdr[blk]] < dfs_nr[hdr])                       \
1435         {                                                           \
1436            RESET_BIT (inner,max_hdr[blk]);			     \
1437            max_hdr[blk] = hdr;                                      \
1438         }                                                           \
1439}
1440
1441
1442/* Find regions for interblock scheduling.
1443
1444   A region for scheduling can be:
1445
1446     * A loop-free procedure, or
1447
1448     * A reducible inner loop, or
1449
1450     * A basic block not contained in any other region.
1451
1452
1453   ?!? In theory we could build other regions based on extended basic
1454   blocks or reverse extended basic blocks.  Is it worth the trouble?
1455
1456   Loop blocks that form a region are put into the region's block list
1457   in topological order.
1458
1459   This procedure stores its results into the following global (ick) variables
1460
1461     * rgn_nr
1462     * rgn_table
1463     * rgn_bb_table
1464     * block_to_bb
1465     * containing region
1466
1467
1468   We use dominator relationships to avoid making regions out of non-reducible
1469   loops.
1470
1471   This procedure needs to be converted to work on pred/succ lists instead
1472   of edge tables.  That would simplify it somewhat.  */
1473
1474static void
1475find_rgns (s_preds, s_succs, num_preds, num_succs, dom)
1476     int_list_ptr *s_preds;
1477     int_list_ptr *s_succs;
1478     int *num_preds;
1479     int *num_succs;
1480     sbitmap *dom;
1481{
1482  int *max_hdr, *dfs_nr, *stack, *queue, *degree;
1483  char no_loops = 1;
1484  int node, child, loop_head, i, head, tail;
1485  int count = 0, sp, idx = 0, current_edge = out_edges[0];
1486  int num_bbs, num_insns, unreachable;
1487  int too_large_failure;
1488
1489  /* Note if an edge has been passed.  */
1490  sbitmap passed;
1491
1492  /* Note if a block is a natural loop header.  */
1493  sbitmap header;
1494
1495  /* Note if a block is an natural inner loop header.  */
1496  sbitmap inner;
1497
1498  /* Note if a block is in the block queue. */
1499  sbitmap in_queue;
1500
1501  /* Note if a block is in the block queue. */
1502  sbitmap in_stack;
1503
1504  /* Perform a DFS traversal of the cfg.  Identify loop headers, inner loops
1505     and a mapping from block to its loop header (if the block is contained
1506     in a loop, else -1).
1507
1508     Store results in HEADER, INNER, and MAX_HDR respectively, these will
1509     be used as inputs to the second traversal.
1510
1511     STACK, SP and DFS_NR are only used during the first traversal.  */
1512
1513  /* Allocate and initialize variables for the first traversal.  */
1514  max_hdr = (int *) alloca (n_basic_blocks * sizeof (int));
1515  dfs_nr = (int *) alloca (n_basic_blocks * sizeof (int));
1516  bzero ((char *) dfs_nr, n_basic_blocks * sizeof (int));
1517  stack = (int *) alloca (nr_edges * sizeof (int));
1518
1519  inner = sbitmap_alloc (n_basic_blocks);
1520  sbitmap_ones (inner);
1521
1522  header = sbitmap_alloc (n_basic_blocks);
1523  sbitmap_zero (header);
1524
1525  passed = sbitmap_alloc (nr_edges);
1526  sbitmap_zero (passed);
1527
1528  in_queue = sbitmap_alloc (n_basic_blocks);
1529  sbitmap_zero (in_queue);
1530
1531  in_stack = sbitmap_alloc (n_basic_blocks);
1532  sbitmap_zero (in_stack);
1533
1534  for (i = 0; i < n_basic_blocks; i++)
1535    max_hdr[i] = -1;
1536
1537  /* DFS traversal to find inner loops in the cfg.  */
1538
1539  sp = -1;
1540  while (1)
1541    {
1542      if (current_edge == 0 || TEST_BIT (passed, current_edge))
1543	{
1544	  /* We have reached a leaf node or a node that was already
1545	     processed.  Pop edges off the stack until we find
1546	     an edge that has not yet been processed.  */
1547	  while (sp >= 0
1548		 && (current_edge == 0 || TEST_BIT (passed, current_edge)))
1549	    {
1550	      /* Pop entry off the stack.  */
1551	      current_edge = stack[sp--];
1552	      node = FROM_BLOCK (current_edge);
1553	      child = TO_BLOCK (current_edge);
1554	      RESET_BIT (in_stack, child);
1555	      if (max_hdr[child] >= 0 && TEST_BIT (in_stack, max_hdr[child]))
1556		UPDATE_LOOP_RELATIONS (node, max_hdr[child]);
1557	      current_edge = NEXT_OUT (current_edge);
1558	    }
1559
1560	  /* See if have finished the DFS tree traversal.  */
1561	  if (sp < 0 && TEST_BIT (passed, current_edge))
1562	    break;
1563
1564	  /* Nope, continue the traversal with the popped node.  */
1565	  continue;
1566	}
1567
1568      /* Process a node.  */
1569      node = FROM_BLOCK (current_edge);
1570      child = TO_BLOCK (current_edge);
1571      SET_BIT (in_stack, node);
1572      dfs_nr[node] = ++count;
1573
1574      /* If the successor is in the stack, then we've found a loop.
1575	 Mark the loop, if it is not a natural loop, then it will
1576	 be rejected during the second traversal.  */
1577      if (TEST_BIT (in_stack, child))
1578	{
1579	  no_loops = 0;
1580	  SET_BIT (header, child);
1581	  UPDATE_LOOP_RELATIONS (node, child);
1582	  SET_BIT (passed, current_edge);
1583	  current_edge = NEXT_OUT (current_edge);
1584	  continue;
1585	}
1586
1587      /* If the child was already visited, then there is no need to visit
1588	 it again.  Just update the loop relationships and restart
1589	 with a new edge.  */
1590      if (dfs_nr[child])
1591	{
1592	  if (max_hdr[child] >= 0 && TEST_BIT (in_stack, max_hdr[child]))
1593	    UPDATE_LOOP_RELATIONS (node, max_hdr[child]);
1594	  SET_BIT (passed, current_edge);
1595	  current_edge = NEXT_OUT (current_edge);
1596	  continue;
1597	}
1598
1599      /* Push an entry on the stack and continue DFS traversal.  */
1600      stack[++sp] = current_edge;
1601      SET_BIT (passed, current_edge);
1602      current_edge = OUT_EDGES (child);
1603    }
1604
1605  /* Another check for unreachable blocks.  The earlier test in
1606     is_cfg_nonregular only finds unreachable blocks that do not
1607     form a loop.
1608
1609     The DFS traversal will mark every block that is reachable from
1610     the entry node by placing a nonzero value in dfs_nr.  Thus if
1611     dfs_nr is zero for any block, then it must be unreachable.  */
1612  unreachable = 0;
1613  for (i = 0; i < n_basic_blocks; i++)
1614    if (dfs_nr[i] == 0)
1615      {
1616	unreachable = 1;
1617	break;
1618      }
1619
1620  /* Gross.  To avoid wasting memory, the second pass uses the dfs_nr array
1621     to hold degree counts.  */
1622  degree = dfs_nr;
1623
1624  /* Compute the in-degree of every block in the graph */
1625  for (i = 0; i < n_basic_blocks; i++)
1626    degree[i] = num_preds[i];
1627
1628  /* Do not perform region scheduling if there are any unreachable
1629     blocks.  */
1630  if (!unreachable)
1631    {
1632      if (no_loops)
1633	SET_BIT (header, 0);
1634
1635      /* Second travsersal:find reducible inner loops and topologically sort
1636	 block of each region.  */
1637
1638      queue = (int *) alloca (n_basic_blocks * sizeof (int));
1639
1640      /* Find blocks which are inner loop headers.  We still have non-reducible
1641	 loops to consider at this point.  */
1642      for (i = 0; i < n_basic_blocks; i++)
1643	{
1644	  if (TEST_BIT (header, i) && TEST_BIT (inner, i))
1645	    {
1646	      int_list_ptr ps;
1647	      int j;
1648
1649	      /* Now check that the loop is reducible.  We do this separate
1650		 from finding inner loops so that we do not find a reducible
1651		 loop which contains an inner  non-reducible loop.
1652
1653		 A simple way to find reducible/natrual loops is to verify
1654		 that each block in the loop is dominated by the loop
1655		 header.
1656
1657		 If there exists a block that is not dominated by the loop
1658		 header, then the block is reachable from outside the loop
1659		 and thus the loop is not a natural loop.  */
1660	      for (j = 0; j < n_basic_blocks; j++)
1661		{
1662		  /* First identify blocks in the loop, except for the loop
1663		     entry block.  */
1664		  if (i == max_hdr[j] && i != j)
1665		    {
1666		      /* Now verify that the block is dominated by the loop
1667			 header.  */
1668		      if (!TEST_BIT (dom[j], i))
1669			break;
1670		    }
1671		}
1672
1673	      /* If we exited the loop early, then I is the header of a non
1674		 reducible loop and we should quit processing it now.  */
1675	      if (j != n_basic_blocks)
1676		continue;
1677
1678	      /* I is a header of an inner loop, or block 0 in a subroutine
1679		 with no loops at all.  */
1680	      head = tail = -1;
1681	      too_large_failure = 0;
1682	      loop_head = max_hdr[i];
1683
1684	      /* Decrease degree of all I's successors for topological
1685		 ordering.  */
1686	      for (ps = s_succs[i]; ps; ps = ps->next)
1687		if (INT_LIST_VAL (ps) != EXIT_BLOCK
1688		    && INT_LIST_VAL (ps) != ENTRY_BLOCK)
1689		  --degree[INT_LIST_VAL(ps)];
1690
1691	      /* Estimate # insns, and count # blocks in the region.  */
1692	      num_bbs = 1;
1693	      num_insns	= (INSN_LUID (BLOCK_END (i))
1694			   - INSN_LUID (BLOCK_HEAD (i)));
1695
1696
1697	      /* Find all loop latches (blocks which back edges to the loop
1698		 header) or all the leaf blocks in the cfg has no loops.
1699
1700		 Place those blocks into the queue.  */
1701	      if (no_loops)
1702		{
1703		  for (j = 0; j < n_basic_blocks; j++)
1704		    /* Leaf nodes have only a single successor which must
1705		       be EXIT_BLOCK.  */
1706		    if (num_succs[j] == 1
1707			&& INT_LIST_VAL (s_succs[j]) == EXIT_BLOCK)
1708		      {
1709			queue[++tail] = j;
1710			SET_BIT (in_queue, j);
1711
1712			if (too_large (j, &num_bbs, &num_insns))
1713			  {
1714			    too_large_failure = 1;
1715			    break;
1716			  }
1717		      }
1718		}
1719	      else
1720		{
1721		  int_list_ptr ps;
1722
1723		  for (ps = s_preds[i]; ps; ps = ps->next)
1724		    {
1725		      node = INT_LIST_VAL (ps);
1726
1727		      if (node == ENTRY_BLOCK || node == EXIT_BLOCK)
1728			continue;
1729
1730		      if (max_hdr[node] == loop_head && node != i)
1731			{
1732			  /* This is a loop latch.  */
1733			  queue[++tail] = node;
1734			  SET_BIT (in_queue, node);
1735
1736			  if (too_large (node, &num_bbs, &num_insns))
1737			    {
1738			      too_large_failure = 1;
1739			      break;
1740			    }
1741			}
1742
1743		    }
1744		}
1745
1746	      /* Now add all the blocks in the loop to the queue.
1747
1748	     We know the loop is a natural loop; however the algorithm
1749	     above will not always mark certain blocks as being in the
1750	     loop.  Consider:
1751		node   children
1752		 a	  b,c
1753		 b	  c
1754		 c	  a,d
1755		 d	  b
1756
1757
1758	     The algorithm in the DFS traversal may not mark B & D as part
1759	     of the loop (ie they will not have max_hdr set to A).
1760
1761	     We know they can not be loop latches (else they would have
1762	     had max_hdr set since they'd have a backedge to a dominator
1763	     block).  So we don't need them on the initial queue.
1764
1765	     We know they are part of the loop because they are dominated
1766	     by the loop header and can be reached by a backwards walk of
1767	     the edges starting with nodes on the initial queue.
1768
1769	     It is safe and desirable to include those nodes in the
1770	     loop/scheduling region.  To do so we would need to decrease
1771	     the degree of a node if it is the target of a backedge
1772	     within the loop itself as the node is placed in the queue.
1773
1774	     We do not do this because I'm not sure that the actual
1775	     scheduling code will properly handle this case. ?!? */
1776
1777	      while (head < tail && !too_large_failure)
1778		{
1779		  int_list_ptr ps;
1780		  child = queue[++head];
1781
1782		  for (ps = s_preds[child]; ps; ps = ps->next)
1783		    {
1784		      node = INT_LIST_VAL (ps);
1785
1786		      /* See discussion above about nodes not marked as in
1787			 this loop during the initial DFS traversal.  */
1788		      if (node == ENTRY_BLOCK || node == EXIT_BLOCK
1789			  || max_hdr[node] != loop_head)
1790			{
1791			  tail = -1;
1792			  break;
1793			}
1794		      else if (!TEST_BIT (in_queue, node) && node != i)
1795			{
1796			  queue[++tail] = node;
1797			  SET_BIT (in_queue, node);
1798
1799			  if (too_large (node, &num_bbs, &num_insns))
1800			    {
1801			      too_large_failure = 1;
1802			      break;
1803			    }
1804			}
1805		    }
1806		}
1807
1808	      if (tail >= 0 && !too_large_failure)
1809		{
1810		  /* Place the loop header into list of region blocks.  */
1811		  degree[i] = -1;
1812		  rgn_bb_table[idx] = i;
1813		  RGN_NR_BLOCKS (nr_regions) = num_bbs;
1814		  RGN_BLOCKS (nr_regions) = idx++;
1815		  CONTAINING_RGN (i) = nr_regions;
1816		  BLOCK_TO_BB (i) = count = 0;
1817
1818		  /* Remove blocks from queue[] when their in degree becomes
1819		 zero.  Repeat until no blocks are left on the list.  This
1820		 produces a topological list of blocks in the region.  */
1821		  while (tail >= 0)
1822		    {
1823		      int_list_ptr ps;
1824
1825		      if (head < 0)
1826			head = tail;
1827		      child = queue[head];
1828		      if (degree[child] == 0)
1829			{
1830			  degree[child] = -1;
1831			  rgn_bb_table[idx++] = child;
1832			  BLOCK_TO_BB (child) = ++count;
1833			  CONTAINING_RGN (child) = nr_regions;
1834			  queue[head] = queue[tail--];
1835
1836			  for (ps = s_succs[child]; ps; ps = ps->next)
1837			    if (INT_LIST_VAL (ps) != ENTRY_BLOCK
1838				&& INT_LIST_VAL (ps) != EXIT_BLOCK)
1839			      --degree[INT_LIST_VAL (ps)];
1840			}
1841		      else
1842			--head;
1843		    }
1844		  ++nr_regions;
1845		}
1846	    }
1847	}
1848    }
1849
1850  /* Any block that did not end up in a region is placed into a region
1851     by itself.  */
1852  for (i = 0; i < n_basic_blocks; i++)
1853    if (degree[i] >= 0)
1854      {
1855	rgn_bb_table[idx] = i;
1856	RGN_NR_BLOCKS (nr_regions) = 1;
1857	RGN_BLOCKS (nr_regions) = idx++;
1858	CONTAINING_RGN (i) = nr_regions++;
1859	BLOCK_TO_BB (i) = 0;
1860      }
1861
1862  free (passed);
1863  free (header);
1864  free (inner);
1865  free (in_queue);
1866  free (in_stack);
1867}
1868
1869
1870/* functions for regions scheduling information */
1871
1872/* Compute dominators, probability, and potential-split-edges of bb.
1873   Assume that these values were already computed for bb's predecessors.  */
1874
1875static void
1876compute_dom_prob_ps (bb)
1877     int bb;
1878{
1879  int nxt_in_edge, fst_in_edge, pred;
1880  int fst_out_edge, nxt_out_edge, nr_out_edges, nr_rgn_out_edges;
1881
1882  prob[bb] = 0.0;
1883  if (IS_RGN_ENTRY (bb))
1884    {
1885      BITSET_ADD (dom[bb], 0, bbset_size);
1886      prob[bb] = 1.0;
1887      return;
1888    }
1889
1890  fst_in_edge = nxt_in_edge = IN_EDGES (BB_TO_BLOCK (bb));
1891
1892  /* intialize dom[bb] to '111..1' */
1893  BITSET_INVERT (dom[bb], bbset_size);
1894
1895  do
1896    {
1897      pred = FROM_BLOCK (nxt_in_edge);
1898      BITSET_INTER (dom[bb], dom[BLOCK_TO_BB (pred)], bbset_size);
1899
1900      BITSET_UNION (ancestor_edges[bb], ancestor_edges[BLOCK_TO_BB (pred)],
1901		    edgeset_size);
1902
1903      BITSET_ADD (ancestor_edges[bb], EDGE_TO_BIT (nxt_in_edge), edgeset_size);
1904
1905      nr_out_edges = 1;
1906      nr_rgn_out_edges = 0;
1907      fst_out_edge = OUT_EDGES (pred);
1908      nxt_out_edge = NEXT_OUT (fst_out_edge);
1909      BITSET_UNION (pot_split[bb], pot_split[BLOCK_TO_BB (pred)],
1910		    edgeset_size);
1911
1912      BITSET_ADD (pot_split[bb], EDGE_TO_BIT (fst_out_edge), edgeset_size);
1913
1914      /* the successor doesn't belong the region? */
1915      if (CONTAINING_RGN (TO_BLOCK (fst_out_edge)) !=
1916	  CONTAINING_RGN (BB_TO_BLOCK (bb)))
1917	++nr_rgn_out_edges;
1918
1919      while (fst_out_edge != nxt_out_edge)
1920	{
1921	  ++nr_out_edges;
1922	  /* the successor doesn't belong the region? */
1923	  if (CONTAINING_RGN (TO_BLOCK (nxt_out_edge)) !=
1924	      CONTAINING_RGN (BB_TO_BLOCK (bb)))
1925	    ++nr_rgn_out_edges;
1926	  BITSET_ADD (pot_split[bb], EDGE_TO_BIT (nxt_out_edge), edgeset_size);
1927	  nxt_out_edge = NEXT_OUT (nxt_out_edge);
1928
1929	}
1930
1931      /* now nr_rgn_out_edges is the number of region-exit edges from pred,
1932         and nr_out_edges will be the number of pred out edges not leaving
1933         the region.  */
1934      nr_out_edges -= nr_rgn_out_edges;
1935      if (nr_rgn_out_edges > 0)
1936	prob[bb] += 0.9 * prob[BLOCK_TO_BB (pred)] / nr_out_edges;
1937      else
1938	prob[bb] += prob[BLOCK_TO_BB (pred)] / nr_out_edges;
1939      nxt_in_edge = NEXT_IN (nxt_in_edge);
1940    }
1941  while (fst_in_edge != nxt_in_edge);
1942
1943  BITSET_ADD (dom[bb], bb, bbset_size);
1944  BITSET_DIFFER (pot_split[bb], ancestor_edges[bb], edgeset_size);
1945
1946  if (sched_verbose >= 2)
1947    fprintf (dump, ";;  bb_prob(%d, %d) = %3d\n", bb, BB_TO_BLOCK (bb), (int) (100.0 * prob[bb]));
1948}				/* compute_dom_prob_ps */
1949
1950/* functions for target info */
1951
1952/* Compute in BL the list of split-edges of bb_src relatively to bb_trg.
1953   Note that bb_trg dominates bb_src.  */
1954
1955static void
1956split_edges (bb_src, bb_trg, bl)
1957     int bb_src;
1958     int bb_trg;
1959     edgelst *bl;
1960{
1961  int es = edgeset_size;
1962  edgeset src = (edgeset) alloca (es * sizeof (HOST_WIDE_INT));
1963
1964  while (es--)
1965    src[es] = (pot_split[bb_src])[es];
1966  BITSET_DIFFER (src, pot_split[bb_trg], edgeset_size);
1967  extract_bitlst (src, edgeset_size, bl);
1968}
1969
1970
1971/* Find the valid candidate-source-blocks for the target block TRG, compute
1972   their probability, and check if they are speculative or not.
1973   For speculative sources, compute their update-blocks and split-blocks.  */
1974
1975static void
1976compute_trg_info (trg)
1977     int trg;
1978{
1979  register candidate *sp;
1980  edgelst el;
1981  int check_block, update_idx;
1982  int i, j, k, fst_edge, nxt_edge;
1983
1984  /* define some of the fields for the target bb as well */
1985  sp = candidate_table + trg;
1986  sp->is_valid = 1;
1987  sp->is_speculative = 0;
1988  sp->src_prob = 100;
1989
1990  for (i = trg + 1; i < current_nr_blocks; i++)
1991    {
1992      sp = candidate_table + i;
1993
1994      sp->is_valid = IS_DOMINATED (i, trg);
1995      if (sp->is_valid)
1996	{
1997	  sp->src_prob = GET_SRC_PROB (i, trg);
1998	  sp->is_valid = (sp->src_prob >= MIN_PROBABILITY);
1999	}
2000
2001      if (sp->is_valid)
2002	{
2003	  split_edges (i, trg, &el);
2004	  sp->is_speculative = (el.nr_members) ? 1 : 0;
2005	  if (sp->is_speculative && !flag_schedule_speculative)
2006	    sp->is_valid = 0;
2007	}
2008
2009      if (sp->is_valid)
2010	{
2011	  sp->split_bbs.first_member = &bblst_table[bblst_last];
2012	  sp->split_bbs.nr_members = el.nr_members;
2013	  for (j = 0; j < el.nr_members; bblst_last++, j++)
2014	    bblst_table[bblst_last] =
2015	      TO_BLOCK (rgn_edges[el.first_member[j]]);
2016	  sp->update_bbs.first_member = &bblst_table[bblst_last];
2017	  update_idx = 0;
2018	  for (j = 0; j < el.nr_members; j++)
2019	    {
2020	      check_block = FROM_BLOCK (rgn_edges[el.first_member[j]]);
2021	      fst_edge = nxt_edge = OUT_EDGES (check_block);
2022	      do
2023		{
2024		  for (k = 0; k < el.nr_members; k++)
2025		    if (EDGE_TO_BIT (nxt_edge) == el.first_member[k])
2026		      break;
2027
2028		  if (k >= el.nr_members)
2029		    {
2030		      bblst_table[bblst_last++] = TO_BLOCK (nxt_edge);
2031		      update_idx++;
2032		    }
2033
2034		  nxt_edge = NEXT_OUT (nxt_edge);
2035		}
2036	      while (fst_edge != nxt_edge);
2037	    }
2038	  sp->update_bbs.nr_members = update_idx;
2039
2040	}
2041      else
2042	{
2043	  sp->split_bbs.nr_members = sp->update_bbs.nr_members = 0;
2044
2045	  sp->is_speculative = 0;
2046	  sp->src_prob = 0;
2047	}
2048    }
2049}				/* compute_trg_info */
2050
2051
2052/* Print candidates info, for debugging purposes.  Callable from debugger.  */
2053
2054void
2055debug_candidate (i)
2056     int i;
2057{
2058  if (!candidate_table[i].is_valid)
2059    return;
2060
2061  if (candidate_table[i].is_speculative)
2062    {
2063      int j;
2064      fprintf (dump, "src b %d bb %d speculative \n", BB_TO_BLOCK (i), i);
2065
2066      fprintf (dump, "split path: ");
2067      for (j = 0; j < candidate_table[i].split_bbs.nr_members; j++)
2068	{
2069	  int b = candidate_table[i].split_bbs.first_member[j];
2070
2071	  fprintf (dump, " %d ", b);
2072	}
2073      fprintf (dump, "\n");
2074
2075      fprintf (dump, "update path: ");
2076      for (j = 0; j < candidate_table[i].update_bbs.nr_members; j++)
2077	{
2078	  int b = candidate_table[i].update_bbs.first_member[j];
2079
2080	  fprintf (dump, " %d ", b);
2081	}
2082      fprintf (dump, "\n");
2083    }
2084  else
2085    {
2086      fprintf (dump, " src %d equivalent\n", BB_TO_BLOCK (i));
2087    }
2088}
2089
2090
2091/* Print candidates info, for debugging purposes.  Callable from debugger.  */
2092
2093void
2094debug_candidates (trg)
2095     int trg;
2096{
2097  int i;
2098
2099  fprintf (dump, "----------- candidate table: target: b=%d bb=%d ---\n",
2100	   BB_TO_BLOCK (trg), trg);
2101  for (i = trg + 1; i < current_nr_blocks; i++)
2102    debug_candidate (i);
2103}
2104
2105
2106/* functions for speculative scheduing */
2107
2108/* Return 0 if x is a set of a register alive in the beginning of one
2109   of the split-blocks of src, otherwise return 1.  */
2110
2111static int
2112check_live_1 (src, x)
2113     int src;
2114     rtx x;
2115{
2116  register int i;
2117  register int regno;
2118  register rtx reg = SET_DEST (x);
2119
2120  if (reg == 0)
2121    return 1;
2122
2123  while (GET_CODE (reg) == SUBREG || GET_CODE (reg) == ZERO_EXTRACT
2124	 || GET_CODE (reg) == SIGN_EXTRACT
2125	 || GET_CODE (reg) == STRICT_LOW_PART)
2126    reg = XEXP (reg, 0);
2127
2128  if (GET_CODE (reg) == PARALLEL
2129      && GET_MODE (reg) == BLKmode)
2130    {
2131      register int i;
2132      for (i = XVECLEN (reg, 0) - 1; i >= 0; i--)
2133	if (check_live_1 (src, XVECEXP (reg, 0, i)))
2134	  return 1;
2135      return 0;
2136    }
2137
2138  if (GET_CODE (reg) != REG)
2139    return 1;
2140
2141  regno = REGNO (reg);
2142
2143  if (regno < FIRST_PSEUDO_REGISTER && global_regs[regno])
2144    {
2145      /* Global registers are assumed live */
2146      return 0;
2147    }
2148  else
2149    {
2150      if (regno < FIRST_PSEUDO_REGISTER)
2151	{
2152	  /* check for hard registers */
2153	  int j = HARD_REGNO_NREGS (regno, GET_MODE (reg));
2154	  while (--j >= 0)
2155	    {
2156	      for (i = 0; i < candidate_table[src].split_bbs.nr_members; i++)
2157		{
2158		  int b = candidate_table[src].split_bbs.first_member[i];
2159
2160		  if (REGNO_REG_SET_P (BASIC_BLOCK (b)->global_live_at_start,
2161				       regno + j))
2162		    {
2163		      return 0;
2164		    }
2165		}
2166	    }
2167	}
2168      else
2169	{
2170	  /* check for psuedo registers */
2171	  for (i = 0; i < candidate_table[src].split_bbs.nr_members; i++)
2172	    {
2173	      int b = candidate_table[src].split_bbs.first_member[i];
2174
2175	      if (REGNO_REG_SET_P (BASIC_BLOCK (b)->global_live_at_start, regno))
2176		{
2177		  return 0;
2178		}
2179	    }
2180	}
2181    }
2182
2183  return 1;
2184}
2185
2186
2187/* If x is a set of a register R, mark that R is alive in the beginning
2188   of every update-block of src.  */
2189
2190static void
2191update_live_1 (src, x)
2192     int src;
2193     rtx x;
2194{
2195  register int i;
2196  register int regno;
2197  register rtx reg = SET_DEST (x);
2198
2199  if (reg == 0)
2200    return;
2201
2202  while (GET_CODE (reg) == SUBREG || GET_CODE (reg) == ZERO_EXTRACT
2203	 || GET_CODE (reg) == SIGN_EXTRACT
2204	 || GET_CODE (reg) == STRICT_LOW_PART)
2205    reg = XEXP (reg, 0);
2206
2207  if (GET_CODE (reg) == PARALLEL
2208      && GET_MODE (reg) == BLKmode)
2209    {
2210      register int i;
2211      for (i = XVECLEN (reg, 0) - 1; i >= 0; i--)
2212	update_live_1 (src, XVECEXP (reg, 0, i));
2213      return;
2214    }
2215
2216  if (GET_CODE (reg) != REG)
2217    return;
2218
2219  /* Global registers are always live, so the code below does not apply
2220     to them.  */
2221
2222  regno = REGNO (reg);
2223
2224  if (regno >= FIRST_PSEUDO_REGISTER || !global_regs[regno])
2225    {
2226      if (regno < FIRST_PSEUDO_REGISTER)
2227	{
2228	  int j = HARD_REGNO_NREGS (regno, GET_MODE (reg));
2229	  while (--j >= 0)
2230	    {
2231	      for (i = 0; i < candidate_table[src].update_bbs.nr_members; i++)
2232		{
2233		  int b = candidate_table[src].update_bbs.first_member[i];
2234
2235		  SET_REGNO_REG_SET (BASIC_BLOCK (b)->global_live_at_start,
2236				     regno + j);
2237		}
2238	    }
2239	}
2240      else
2241	{
2242	  for (i = 0; i < candidate_table[src].update_bbs.nr_members; i++)
2243	    {
2244	      int b = candidate_table[src].update_bbs.first_member[i];
2245
2246	      SET_REGNO_REG_SET (BASIC_BLOCK (b)->global_live_at_start, regno);
2247	    }
2248	}
2249    }
2250}
2251
2252
2253/* Return 1 if insn can be speculatively moved from block src to trg,
2254   otherwise return 0.  Called before first insertion of insn to
2255   ready-list or before the scheduling.  */
2256
2257static int
2258check_live (insn, src)
2259     rtx insn;
2260     int src;
2261{
2262  /* find the registers set by instruction */
2263  if (GET_CODE (PATTERN (insn)) == SET
2264      || GET_CODE (PATTERN (insn)) == CLOBBER)
2265    return check_live_1 (src, PATTERN (insn));
2266  else if (GET_CODE (PATTERN (insn)) == PARALLEL)
2267    {
2268      int j;
2269      for (j = XVECLEN (PATTERN (insn), 0) - 1; j >= 0; j--)
2270	if ((GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == SET
2271	     || GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == CLOBBER)
2272	    && !check_live_1 (src, XVECEXP (PATTERN (insn), 0, j)))
2273	  return 0;
2274
2275      return 1;
2276    }
2277
2278  return 1;
2279}
2280
2281
2282/* Update the live registers info after insn was moved speculatively from
2283   block src to trg.  */
2284
2285static void
2286update_live (insn, src)
2287     rtx insn;
2288     int src;
2289{
2290  /* find the registers set by instruction */
2291  if (GET_CODE (PATTERN (insn)) == SET
2292      || GET_CODE (PATTERN (insn)) == CLOBBER)
2293    update_live_1 (src, PATTERN (insn));
2294  else if (GET_CODE (PATTERN (insn)) == PARALLEL)
2295    {
2296      int j;
2297      for (j = XVECLEN (PATTERN (insn), 0) - 1; j >= 0; j--)
2298	if (GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == SET
2299	    || GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == CLOBBER)
2300	  update_live_1 (src, XVECEXP (PATTERN (insn), 0, j));
2301    }
2302}
2303
2304/* Exception Free Loads:
2305
2306   We define five classes of speculative loads: IFREE, IRISKY,
2307   PFREE, PRISKY, and MFREE.
2308
2309   IFREE loads are loads that are proved to be exception-free, just
2310   by examining the load insn.  Examples for such loads are loads
2311   from TOC and loads of global data.
2312
2313   IRISKY loads are loads that are proved to be exception-risky,
2314   just by examining the load insn.  Examples for such loads are
2315   volatile loads and loads from shared memory.
2316
2317   PFREE loads are loads for which we can prove, by examining other
2318   insns, that they are exception-free.  Currently, this class consists
2319   of loads for which we are able to find a "similar load", either in
2320   the target block, or, if only one split-block exists, in that split
2321   block.  Load2 is similar to load1 if both have same single base
2322   register.  We identify only part of the similar loads, by finding
2323   an insn upon which both load1 and load2 have a DEF-USE dependence.
2324
2325   PRISKY loads are loads for which we can prove, by examining other
2326   insns, that they are exception-risky.  Currently we have two proofs for
2327   such loads.  The first proof detects loads that are probably guarded by a
2328   test on the memory address.  This proof is based on the
2329   backward and forward data dependence information for the region.
2330   Let load-insn be the examined load.
2331   Load-insn is PRISKY iff ALL the following hold:
2332
2333   - insn1 is not in the same block as load-insn
2334   - there is a DEF-USE dependence chain (insn1, ..., load-insn)
2335   - test-insn is either a compare or a branch, not in the same block as load-insn
2336   - load-insn is reachable from test-insn
2337   - there is a DEF-USE dependence chain (insn1, ..., test-insn)
2338
2339   This proof might fail when the compare and the load are fed
2340   by an insn not in the region.  To solve this, we will add to this
2341   group all loads that have no input DEF-USE dependence.
2342
2343   The second proof detects loads that are directly or indirectly
2344   fed by a speculative load.  This proof is affected by the
2345   scheduling process.  We will use the flag  fed_by_spec_load.
2346   Initially, all insns have this flag reset.  After a speculative
2347   motion of an insn, if insn is either a load, or marked as
2348   fed_by_spec_load, we will also mark as fed_by_spec_load every
2349   insn1 for which a DEF-USE dependence (insn, insn1) exists.  A
2350   load which is fed_by_spec_load is also PRISKY.
2351
2352   MFREE (maybe-free) loads are all the remaining loads. They may be
2353   exception-free, but we cannot prove it.
2354
2355   Now, all loads in IFREE and PFREE classes are considered
2356   exception-free, while all loads in IRISKY and PRISKY classes are
2357   considered exception-risky.  As for loads in the MFREE class,
2358   these are considered either exception-free or exception-risky,
2359   depending on whether we are pessimistic or optimistic.  We have
2360   to take the pessimistic approach to assure the safety of
2361   speculative scheduling, but we can take the optimistic approach
2362   by invoking the -fsched_spec_load_dangerous option.  */
2363
2364enum INSN_TRAP_CLASS
2365{
2366  TRAP_FREE = 0, IFREE = 1, PFREE_CANDIDATE = 2,
2367  PRISKY_CANDIDATE = 3, IRISKY = 4, TRAP_RISKY = 5
2368};
2369
2370#define WORST_CLASS(class1, class2) \
2371((class1 > class2) ? class1 : class2)
2372
2373/* Indexed by INSN_UID, and set if there's DEF-USE dependence between */
2374/* some speculatively moved load insn and this one.  */
2375char *fed_by_spec_load;
2376char *is_load_insn;
2377
2378/* Non-zero if block bb_to is equal to, or reachable from block bb_from.  */
2379#define IS_REACHABLE(bb_from, bb_to)					\
2380(bb_from == bb_to                                                       \
2381   || IS_RGN_ENTRY (bb_from)						\
2382   || (bitset_member (ancestor_edges[bb_to],				\
2383		      EDGE_TO_BIT (IN_EDGES (BB_TO_BLOCK (bb_from))),	\
2384		      edgeset_size)))
2385#define FED_BY_SPEC_LOAD(insn) (fed_by_spec_load[INSN_UID (insn)])
2386#define IS_LOAD_INSN(insn) (is_load_insn[INSN_UID (insn)])
2387
2388/* Non-zero iff the address is comprised from at most 1 register */
2389#define CONST_BASED_ADDRESS_P(x)			\
2390  (GET_CODE (x) == REG					\
2391   || ((GET_CODE (x) == PLUS || GET_CODE (x) == MINUS   \
2392	|| (GET_CODE (x) == LO_SUM))	                \
2393       && (GET_CODE (XEXP (x, 0)) == CONST_INT		\
2394	   || GET_CODE (XEXP (x, 1)) == CONST_INT)))
2395
2396/* Turns on the fed_by_spec_load flag for insns fed by load_insn.  */
2397
2398static void
2399set_spec_fed (load_insn)
2400     rtx load_insn;
2401{
2402  rtx link;
2403
2404  for (link = INSN_DEPEND (load_insn); link; link = XEXP (link, 1))
2405    if (GET_MODE (link) == VOIDmode)
2406      FED_BY_SPEC_LOAD (XEXP (link, 0)) = 1;
2407}				/* set_spec_fed */
2408
2409/* On the path from the insn to load_insn_bb, find a conditional branch */
2410/* depending on insn, that guards the speculative load.  */
2411
2412static int
2413find_conditional_protection (insn, load_insn_bb)
2414     rtx insn;
2415     int load_insn_bb;
2416{
2417  rtx link;
2418
2419  /* iterate through DEF-USE forward dependences */
2420  for (link = INSN_DEPEND (insn); link; link = XEXP (link, 1))
2421    {
2422      rtx next = XEXP (link, 0);
2423      if ((CONTAINING_RGN (INSN_BLOCK (next)) ==
2424	   CONTAINING_RGN (BB_TO_BLOCK (load_insn_bb)))
2425	  && IS_REACHABLE (INSN_BB (next), load_insn_bb)
2426	  && load_insn_bb != INSN_BB (next)
2427	  && GET_MODE (link) == VOIDmode
2428	  && (GET_CODE (next) == JUMP_INSN
2429	      || find_conditional_protection (next, load_insn_bb)))
2430	return 1;
2431    }
2432  return 0;
2433}				/* find_conditional_protection */
2434
2435/* Returns 1 if the same insn1 that participates in the computation
2436   of load_insn's address is feeding a conditional branch that is
2437   guarding on load_insn. This is true if we find a the two DEF-USE
2438   chains:
2439   insn1 -> ... -> conditional-branch
2440   insn1 -> ... -> load_insn,
2441   and if a flow path exist:
2442   insn1 -> ... -> conditional-branch -> ... -> load_insn,
2443   and if insn1 is on the path
2444   region-entry -> ... -> bb_trg -> ... load_insn.
2445
2446   Locate insn1 by climbing on LOG_LINKS from load_insn.
2447   Locate the branch by following INSN_DEPEND from insn1.  */
2448
2449static int
2450is_conditionally_protected (load_insn, bb_src, bb_trg)
2451     rtx load_insn;
2452     int bb_src, bb_trg;
2453{
2454  rtx link;
2455
2456  for (link = LOG_LINKS (load_insn); link; link = XEXP (link, 1))
2457    {
2458      rtx insn1 = XEXP (link, 0);
2459
2460      /* must be a DEF-USE dependence upon non-branch */
2461      if (GET_MODE (link) != VOIDmode
2462	  || GET_CODE (insn1) == JUMP_INSN)
2463	continue;
2464
2465      /* must exist a path: region-entry -> ... -> bb_trg -> ... load_insn */
2466      if (INSN_BB (insn1) == bb_src
2467	  || (CONTAINING_RGN (INSN_BLOCK (insn1))
2468	      != CONTAINING_RGN (BB_TO_BLOCK (bb_src)))
2469	  || (!IS_REACHABLE (bb_trg, INSN_BB (insn1))
2470	      && !IS_REACHABLE (INSN_BB (insn1), bb_trg)))
2471	continue;
2472
2473      /* now search for the conditional-branch */
2474      if (find_conditional_protection (insn1, bb_src))
2475	return 1;
2476
2477      /* recursive step: search another insn1, "above" current insn1.  */
2478      return is_conditionally_protected (insn1, bb_src, bb_trg);
2479    }
2480
2481  /* the chain does not exsist */
2482  return 0;
2483}				/* is_conditionally_protected */
2484
2485/* Returns 1 if a clue for "similar load" 'insn2' is found, and hence
2486   load_insn can move speculatively from bb_src to bb_trg.  All the
2487   following must hold:
2488
2489   (1) both loads have 1 base register (PFREE_CANDIDATEs).
2490   (2) load_insn and load1 have a def-use dependence upon
2491   the same insn 'insn1'.
2492   (3) either load2 is in bb_trg, or:
2493   - there's only one split-block, and
2494   - load1 is on the escape path, and
2495
2496   From all these we can conclude that the two loads access memory
2497   addresses that differ at most by a constant, and hence if moving
2498   load_insn would cause an exception, it would have been caused by
2499   load2 anyhow.  */
2500
2501static int
2502is_pfree (load_insn, bb_src, bb_trg)
2503     rtx load_insn;
2504     int bb_src, bb_trg;
2505{
2506  rtx back_link;
2507  register candidate *candp = candidate_table + bb_src;
2508
2509  if (candp->split_bbs.nr_members != 1)
2510    /* must have exactly one escape block */
2511    return 0;
2512
2513  for (back_link = LOG_LINKS (load_insn);
2514       back_link; back_link = XEXP (back_link, 1))
2515    {
2516      rtx insn1 = XEXP (back_link, 0);
2517
2518      if (GET_MODE (back_link) == VOIDmode)
2519	{
2520	  /* found a DEF-USE dependence (insn1, load_insn) */
2521	  rtx fore_link;
2522
2523	  for (fore_link = INSN_DEPEND (insn1);
2524	       fore_link; fore_link = XEXP (fore_link, 1))
2525	    {
2526	      rtx insn2 = XEXP (fore_link, 0);
2527	      if (GET_MODE (fore_link) == VOIDmode)
2528		{
2529		  /* found a DEF-USE dependence (insn1, insn2) */
2530		  if (haifa_classify_insn (insn2) != PFREE_CANDIDATE)
2531		    /* insn2 not guaranteed to be a 1 base reg load */
2532		    continue;
2533
2534		  if (INSN_BB (insn2) == bb_trg)
2535		    /* insn2 is the similar load, in the target block */
2536		    return 1;
2537
2538		  if (*(candp->split_bbs.first_member) == INSN_BLOCK (insn2))
2539		    /* insn2 is a similar load, in a split-block */
2540		    return 1;
2541		}
2542	    }
2543	}
2544    }
2545
2546  /* couldn't find a similar load */
2547  return 0;
2548}				/* is_pfree */
2549
2550/* Returns a class that insn with GET_DEST(insn)=x may belong to,
2551   as found by analyzing insn's expression.  */
2552
2553static int
2554may_trap_exp (x, is_store)
2555     rtx x;
2556     int is_store;
2557{
2558  enum rtx_code code;
2559
2560  if (x == 0)
2561    return TRAP_FREE;
2562  code = GET_CODE (x);
2563  if (is_store)
2564    {
2565      if (code == MEM)
2566	return TRAP_RISKY;
2567      else
2568	return TRAP_FREE;
2569    }
2570  if (code == MEM)
2571    {
2572      /* The insn uses memory */
2573      /* a volatile load */
2574      if (MEM_VOLATILE_P (x))
2575	return IRISKY;
2576      /* an exception-free load */
2577      if (!may_trap_p (x))
2578	return IFREE;
2579      /* a load with 1 base register, to be further checked */
2580      if (CONST_BASED_ADDRESS_P (XEXP (x, 0)))
2581	return PFREE_CANDIDATE;
2582      /* no info on the load, to be further checked */
2583      return PRISKY_CANDIDATE;
2584    }
2585  else
2586    {
2587      char *fmt;
2588      int i, insn_class = TRAP_FREE;
2589
2590      /* neither store nor load, check if it may cause a trap */
2591      if (may_trap_p (x))
2592	return TRAP_RISKY;
2593      /* recursive step: walk the insn...  */
2594      fmt = GET_RTX_FORMAT (code);
2595      for (i = GET_RTX_LENGTH (code) - 1; i >= 0; i--)
2596	{
2597	  if (fmt[i] == 'e')
2598	    {
2599	      int tmp_class = may_trap_exp (XEXP (x, i), is_store);
2600	      insn_class = WORST_CLASS (insn_class, tmp_class);
2601	    }
2602	  else if (fmt[i] == 'E')
2603	    {
2604	      int j;
2605	      for (j = 0; j < XVECLEN (x, i); j++)
2606		{
2607		  int tmp_class = may_trap_exp (XVECEXP (x, i, j), is_store);
2608		  insn_class = WORST_CLASS (insn_class, tmp_class);
2609		  if (insn_class == TRAP_RISKY || insn_class == IRISKY)
2610		    break;
2611		}
2612	    }
2613	  if (insn_class == TRAP_RISKY || insn_class == IRISKY)
2614	    break;
2615	}
2616      return insn_class;
2617    }
2618}				/* may_trap_exp */
2619
2620
2621/* Classifies insn for the purpose of verifying that it can be
2622   moved speculatively, by examining it's patterns, returning:
2623   TRAP_RISKY: store, or risky non-load insn (e.g. division by variable).
2624   TRAP_FREE: non-load insn.
2625   IFREE: load from a globaly safe location.
2626   IRISKY: volatile load.
2627   PFREE_CANDIDATE, PRISKY_CANDIDATE: load that need to be checked for
2628   being either PFREE or PRISKY.  */
2629
2630static int
2631haifa_classify_insn (insn)
2632     rtx insn;
2633{
2634  rtx pat = PATTERN (insn);
2635  int tmp_class = TRAP_FREE;
2636  int insn_class = TRAP_FREE;
2637  enum rtx_code code;
2638
2639  if (GET_CODE (pat) == PARALLEL)
2640    {
2641      int i, len = XVECLEN (pat, 0);
2642
2643      for (i = len - 1; i >= 0; i--)
2644	{
2645	  code = GET_CODE (XVECEXP (pat, 0, i));
2646	  switch (code)
2647	    {
2648	    case CLOBBER:
2649	      /* test if it is a 'store' */
2650	      tmp_class = may_trap_exp (XEXP (XVECEXP (pat, 0, i), 0), 1);
2651	      break;
2652	    case SET:
2653	      /* test if it is a store */
2654	      tmp_class = may_trap_exp (SET_DEST (XVECEXP (pat, 0, i)), 1);
2655	      if (tmp_class == TRAP_RISKY)
2656		break;
2657	      /* test if it is a load  */
2658	      tmp_class =
2659		WORST_CLASS (tmp_class,
2660			   may_trap_exp (SET_SRC (XVECEXP (pat, 0, i)), 0));
2661	      break;
2662	    case TRAP_IF:
2663	      tmp_class = TRAP_RISKY;
2664	      break;
2665	    default:;
2666	    }
2667	  insn_class = WORST_CLASS (insn_class, tmp_class);
2668	  if (insn_class == TRAP_RISKY || insn_class == IRISKY)
2669	    break;
2670	}
2671    }
2672  else
2673    {
2674      code = GET_CODE (pat);
2675      switch (code)
2676	{
2677	case CLOBBER:
2678	  /* test if it is a 'store' */
2679	  tmp_class = may_trap_exp (XEXP (pat, 0), 1);
2680	  break;
2681	case SET:
2682	  /* test if it is a store */
2683	  tmp_class = may_trap_exp (SET_DEST (pat), 1);
2684	  if (tmp_class == TRAP_RISKY)
2685	    break;
2686	  /* test if it is a load  */
2687	  tmp_class =
2688	    WORST_CLASS (tmp_class,
2689			 may_trap_exp (SET_SRC (pat), 0));
2690	  break;
2691	case TRAP_IF:
2692	  tmp_class = TRAP_RISKY;
2693	  break;
2694	default:;
2695	}
2696      insn_class = tmp_class;
2697    }
2698
2699  return insn_class;
2700
2701}				/* haifa_classify_insn */
2702
2703/* Return 1 if load_insn is prisky (i.e. if load_insn is fed by
2704   a load moved speculatively, or if load_insn is protected by
2705   a compare on load_insn's address).  */
2706
2707static int
2708is_prisky (load_insn, bb_src, bb_trg)
2709     rtx load_insn;
2710     int bb_src, bb_trg;
2711{
2712  if (FED_BY_SPEC_LOAD (load_insn))
2713    return 1;
2714
2715  if (LOG_LINKS (load_insn) == NULL)
2716    /* dependence may 'hide' out of the region.  */
2717    return 1;
2718
2719  if (is_conditionally_protected (load_insn, bb_src, bb_trg))
2720    return 1;
2721
2722  return 0;
2723}				/* is_prisky */
2724
2725/* Insn is a candidate to be moved speculatively from bb_src to bb_trg.
2726   Return 1 if insn is exception-free (and the motion is valid)
2727   and 0 otherwise.  */
2728
2729static int
2730is_exception_free (insn, bb_src, bb_trg)
2731     rtx insn;
2732     int bb_src, bb_trg;
2733{
2734  int insn_class = haifa_classify_insn (insn);
2735
2736  /* handle non-load insns */
2737  switch (insn_class)
2738    {
2739    case TRAP_FREE:
2740      return 1;
2741    case TRAP_RISKY:
2742      return 0;
2743    default:;
2744    }
2745
2746  /* handle loads */
2747  if (!flag_schedule_speculative_load)
2748    return 0;
2749  IS_LOAD_INSN (insn) = 1;
2750  switch (insn_class)
2751    {
2752    case IFREE:
2753      return (1);
2754    case IRISKY:
2755      return 0;
2756    case PFREE_CANDIDATE:
2757      if (is_pfree (insn, bb_src, bb_trg))
2758	return 1;
2759      /* don't 'break' here: PFREE-candidate is also PRISKY-candidate */
2760    case PRISKY_CANDIDATE:
2761      if (!flag_schedule_speculative_load_dangerous
2762	  || is_prisky (insn, bb_src, bb_trg))
2763	return 0;
2764      break;
2765    default:;
2766    }
2767
2768  return flag_schedule_speculative_load_dangerous;
2769}				/* is_exception_free */
2770
2771
2772/* Process an insn's memory dependencies.  There are four kinds of
2773   dependencies:
2774
2775   (0) read dependence: read follows read
2776   (1) true dependence: read follows write
2777   (2) anti dependence: write follows read
2778   (3) output dependence: write follows write
2779
2780   We are careful to build only dependencies which actually exist, and
2781   use transitivity to avoid building too many links.  */
2782
2783/* Return the INSN_LIST containing INSN in LIST, or NULL
2784   if LIST does not contain INSN.  */
2785
2786HAIFA_INLINE static rtx
2787find_insn_list (insn, list)
2788     rtx insn;
2789     rtx list;
2790{
2791  while (list)
2792    {
2793      if (XEXP (list, 0) == insn)
2794	return list;
2795      list = XEXP (list, 1);
2796    }
2797  return 0;
2798}
2799
2800
2801/* Return 1 if the pair (insn, x) is found in (LIST, LIST1), or 0 otherwise.  */
2802
2803HAIFA_INLINE static char
2804find_insn_mem_list (insn, x, list, list1)
2805     rtx insn, x;
2806     rtx list, list1;
2807{
2808  while (list)
2809    {
2810      if (XEXP (list, 0) == insn
2811	  && XEXP (list1, 0) == x)
2812	return 1;
2813      list = XEXP (list, 1);
2814      list1 = XEXP (list1, 1);
2815    }
2816  return 0;
2817}
2818
2819
2820/* Compute the function units used by INSN.  This caches the value
2821   returned by function_units_used.  A function unit is encoded as the
2822   unit number if the value is non-negative and the compliment of a
2823   mask if the value is negative.  A function unit index is the
2824   non-negative encoding.  */
2825
2826HAIFA_INLINE static int
2827insn_unit (insn)
2828     rtx insn;
2829{
2830  register int unit = INSN_UNIT (insn);
2831
2832  if (unit == 0)
2833    {
2834      recog_memoized (insn);
2835
2836      /* A USE insn, or something else we don't need to understand.
2837         We can't pass these directly to function_units_used because it will
2838         trigger a fatal error for unrecognizable insns.  */
2839      if (INSN_CODE (insn) < 0)
2840	unit = -1;
2841      else
2842	{
2843	  unit = function_units_used (insn);
2844	  /* Increment non-negative values so we can cache zero.  */
2845	  if (unit >= 0)
2846	    unit++;
2847	}
2848      /* We only cache 16 bits of the result, so if the value is out of
2849         range, don't cache it.  */
2850      if (FUNCTION_UNITS_SIZE < HOST_BITS_PER_SHORT
2851	  || unit >= 0
2852	  || (unit & ~((1 << (HOST_BITS_PER_SHORT - 1)) - 1)) == 0)
2853	INSN_UNIT (insn) = unit;
2854    }
2855  return (unit > 0 ? unit - 1 : unit);
2856}
2857
2858/* Compute the blockage range for executing INSN on UNIT.  This caches
2859   the value returned by the blockage_range_function for the unit.
2860   These values are encoded in an int where the upper half gives the
2861   minimum value and the lower half gives the maximum value.  */
2862
2863HAIFA_INLINE static unsigned int
2864blockage_range (unit, insn)
2865     int unit;
2866     rtx insn;
2867{
2868  unsigned int blockage = INSN_BLOCKAGE (insn);
2869  unsigned int range;
2870
2871  if ((int) UNIT_BLOCKED (blockage) != unit + 1)
2872    {
2873      range = function_units[unit].blockage_range_function (insn);
2874      /* We only cache the blockage range for one unit and then only if
2875         the values fit.  */
2876      if (HOST_BITS_PER_INT >= UNIT_BITS + 2 * BLOCKAGE_BITS)
2877	INSN_BLOCKAGE (insn) = ENCODE_BLOCKAGE (unit + 1, range);
2878    }
2879  else
2880    range = BLOCKAGE_RANGE (blockage);
2881
2882  return range;
2883}
2884
2885/* A vector indexed by function unit instance giving the last insn to use
2886   the unit.  The value of the function unit instance index for unit U
2887   instance I is (U + I * FUNCTION_UNITS_SIZE).  */
2888static rtx unit_last_insn[FUNCTION_UNITS_SIZE * MAX_MULTIPLICITY];
2889
2890/* A vector indexed by function unit instance giving the minimum time when
2891   the unit will unblock based on the maximum blockage cost.  */
2892static int unit_tick[FUNCTION_UNITS_SIZE * MAX_MULTIPLICITY];
2893
2894/* A vector indexed by function unit number giving the number of insns
2895   that remain to use the unit.  */
2896static int unit_n_insns[FUNCTION_UNITS_SIZE];
2897
2898/* Reset the function unit state to the null state.  */
2899
2900static void
2901clear_units ()
2902{
2903  bzero ((char *) unit_last_insn, sizeof (unit_last_insn));
2904  bzero ((char *) unit_tick, sizeof (unit_tick));
2905  bzero ((char *) unit_n_insns, sizeof (unit_n_insns));
2906}
2907
2908/* Return the issue-delay of an insn */
2909
2910HAIFA_INLINE static int
2911insn_issue_delay (insn)
2912     rtx insn;
2913{
2914  int i, delay = 0;
2915  int unit = insn_unit (insn);
2916
2917  /* efficiency note: in fact, we are working 'hard' to compute a
2918     value that was available in md file, and is not available in
2919     function_units[] structure.  It would be nice to have this
2920     value there, too.  */
2921  if (unit >= 0)
2922    {
2923      if (function_units[unit].blockage_range_function &&
2924	  function_units[unit].blockage_function)
2925	delay = function_units[unit].blockage_function (insn, insn);
2926    }
2927  else
2928    for (i = 0, unit = ~unit; unit; i++, unit >>= 1)
2929      if ((unit & 1) != 0 && function_units[i].blockage_range_function
2930	  && function_units[i].blockage_function)
2931	delay = MAX (delay, function_units[i].blockage_function (insn, insn));
2932
2933  return delay;
2934}
2935
2936/* Return the actual hazard cost of executing INSN on the unit UNIT,
2937   instance INSTANCE at time CLOCK if the previous actual hazard cost
2938   was COST.  */
2939
2940HAIFA_INLINE static int
2941actual_hazard_this_instance (unit, instance, insn, clock, cost)
2942     int unit, instance, clock, cost;
2943     rtx insn;
2944{
2945  int tick = unit_tick[instance];	/* issue time of the last issued insn */
2946
2947  if (tick - clock > cost)
2948    {
2949      /* The scheduler is operating forward, so unit's last insn is the
2950         executing insn and INSN is the candidate insn.  We want a
2951         more exact measure of the blockage if we execute INSN at CLOCK
2952         given when we committed the execution of the unit's last insn.
2953
2954         The blockage value is given by either the unit's max blockage
2955         constant, blockage range function, or blockage function.  Use
2956         the most exact form for the given unit.  */
2957
2958      if (function_units[unit].blockage_range_function)
2959	{
2960	  if (function_units[unit].blockage_function)
2961	    tick += (function_units[unit].blockage_function
2962		     (unit_last_insn[instance], insn)
2963		     - function_units[unit].max_blockage);
2964	  else
2965	    tick += ((int) MAX_BLOCKAGE_COST (blockage_range (unit, insn))
2966		     - function_units[unit].max_blockage);
2967	}
2968      if (tick - clock > cost)
2969	cost = tick - clock;
2970    }
2971  return cost;
2972}
2973
2974/* Record INSN as having begun execution on the units encoded by UNIT at
2975   time CLOCK.  */
2976
2977HAIFA_INLINE static void
2978schedule_unit (unit, insn, clock)
2979     int unit, clock;
2980     rtx insn;
2981{
2982  int i;
2983
2984  if (unit >= 0)
2985    {
2986      int instance = unit;
2987#if MAX_MULTIPLICITY > 1
2988      /* Find the first free instance of the function unit and use that
2989         one.  We assume that one is free.  */
2990      for (i = function_units[unit].multiplicity - 1; i > 0; i--)
2991	{
2992	  if (!actual_hazard_this_instance (unit, instance, insn, clock, 0))
2993	    break;
2994	  instance += FUNCTION_UNITS_SIZE;
2995	}
2996#endif
2997      unit_last_insn[instance] = insn;
2998      unit_tick[instance] = (clock + function_units[unit].max_blockage);
2999    }
3000  else
3001    for (i = 0, unit = ~unit; unit; i++, unit >>= 1)
3002      if ((unit & 1) != 0)
3003	schedule_unit (i, insn, clock);
3004}
3005
3006/* Return the actual hazard cost of executing INSN on the units encoded by
3007   UNIT at time CLOCK if the previous actual hazard cost was COST.  */
3008
3009HAIFA_INLINE static int
3010actual_hazard (unit, insn, clock, cost)
3011     int unit, clock, cost;
3012     rtx insn;
3013{
3014  int i;
3015
3016  if (unit >= 0)
3017    {
3018      /* Find the instance of the function unit with the minimum hazard.  */
3019      int instance = unit;
3020      int best_cost = actual_hazard_this_instance (unit, instance, insn,
3021						   clock, cost);
3022      int this_cost;
3023
3024#if MAX_MULTIPLICITY > 1
3025      if (best_cost > cost)
3026	{
3027	  for (i = function_units[unit].multiplicity - 1; i > 0; i--)
3028	    {
3029	      instance += FUNCTION_UNITS_SIZE;
3030	      this_cost = actual_hazard_this_instance (unit, instance, insn,
3031						       clock, cost);
3032	      if (this_cost < best_cost)
3033		{
3034		  best_cost = this_cost;
3035		  if (this_cost <= cost)
3036		    break;
3037		}
3038	    }
3039	}
3040#endif
3041      cost = MAX (cost, best_cost);
3042    }
3043  else
3044    for (i = 0, unit = ~unit; unit; i++, unit >>= 1)
3045      if ((unit & 1) != 0)
3046	cost = actual_hazard (i, insn, clock, cost);
3047
3048  return cost;
3049}
3050
3051/* Return the potential hazard cost of executing an instruction on the
3052   units encoded by UNIT if the previous potential hazard cost was COST.
3053   An insn with a large blockage time is chosen in preference to one
3054   with a smaller time; an insn that uses a unit that is more likely
3055   to be used is chosen in preference to one with a unit that is less
3056   used.  We are trying to minimize a subsequent actual hazard.  */
3057
3058HAIFA_INLINE static int
3059potential_hazard (unit, insn, cost)
3060     int unit, cost;
3061     rtx insn;
3062{
3063  int i, ncost;
3064  unsigned int minb, maxb;
3065
3066  if (unit >= 0)
3067    {
3068      minb = maxb = function_units[unit].max_blockage;
3069      if (maxb > 1)
3070	{
3071	  if (function_units[unit].blockage_range_function)
3072	    {
3073	      maxb = minb = blockage_range (unit, insn);
3074	      maxb = MAX_BLOCKAGE_COST (maxb);
3075	      minb = MIN_BLOCKAGE_COST (minb);
3076	    }
3077
3078	  if (maxb > 1)
3079	    {
3080	      /* Make the number of instructions left dominate.  Make the
3081	         minimum delay dominate the maximum delay.  If all these
3082	         are the same, use the unit number to add an arbitrary
3083	         ordering.  Other terms can be added.  */
3084	      ncost = minb * 0x40 + maxb;
3085	      ncost *= (unit_n_insns[unit] - 1) * 0x1000 + unit;
3086	      if (ncost > cost)
3087		cost = ncost;
3088	    }
3089	}
3090    }
3091  else
3092    for (i = 0, unit = ~unit; unit; i++, unit >>= 1)
3093      if ((unit & 1) != 0)
3094	cost = potential_hazard (i, insn, cost);
3095
3096  return cost;
3097}
3098
3099/* Compute cost of executing INSN given the dependence LINK on the insn USED.
3100   This is the number of cycles between instruction issue and
3101   instruction results.  */
3102
3103HAIFA_INLINE static int
3104insn_cost (insn, link, used)
3105     rtx insn, link, used;
3106{
3107  register int cost = INSN_COST (insn);
3108
3109  if (cost == 0)
3110    {
3111      recog_memoized (insn);
3112
3113      /* A USE insn, or something else we don't need to understand.
3114         We can't pass these directly to result_ready_cost because it will
3115         trigger a fatal error for unrecognizable insns.  */
3116      if (INSN_CODE (insn) < 0)
3117	{
3118	  INSN_COST (insn) = 1;
3119	  return 1;
3120	}
3121      else
3122	{
3123	  cost = result_ready_cost (insn);
3124
3125	  if (cost < 1)
3126	    cost = 1;
3127
3128	  INSN_COST (insn) = cost;
3129	}
3130    }
3131
3132  /* in this case estimate cost without caring how insn is used.  */
3133  if (link == 0 && used == 0)
3134    return cost;
3135
3136  /* A USE insn should never require the value used to be computed.  This
3137     allows the computation of a function's result and parameter values to
3138     overlap the return and call.  */
3139  recog_memoized (used);
3140  if (INSN_CODE (used) < 0)
3141    LINK_COST_FREE (link) = 1;
3142
3143  /* If some dependencies vary the cost, compute the adjustment.  Most
3144     commonly, the adjustment is complete: either the cost is ignored
3145     (in the case of an output- or anti-dependence), or the cost is
3146     unchanged.  These values are cached in the link as LINK_COST_FREE
3147     and LINK_COST_ZERO.  */
3148
3149  if (LINK_COST_FREE (link))
3150    cost = 1;
3151#ifdef ADJUST_COST
3152  else if (!LINK_COST_ZERO (link))
3153    {
3154      int ncost = cost;
3155
3156      ADJUST_COST (used, link, insn, ncost);
3157      if (ncost <= 1)
3158	LINK_COST_FREE (link) = ncost = 1;
3159      if (cost == ncost)
3160	LINK_COST_ZERO (link) = 1;
3161      cost = ncost;
3162    }
3163#endif
3164  return cost;
3165}
3166
3167/* Compute the priority number for INSN.  */
3168
3169static int
3170priority (insn)
3171     rtx insn;
3172{
3173  int this_priority;
3174  rtx link;
3175
3176  if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
3177    return 0;
3178
3179  if ((this_priority = INSN_PRIORITY (insn)) == 0)
3180    {
3181      if (INSN_DEPEND (insn) == 0)
3182	this_priority = insn_cost (insn, 0, 0);
3183      else
3184	for (link = INSN_DEPEND (insn); link; link = XEXP (link, 1))
3185	  {
3186	    rtx next;
3187	    int next_priority;
3188
3189	    if (RTX_INTEGRATED_P (link))
3190	      continue;
3191
3192	    next = XEXP (link, 0);
3193
3194	    /* critical path is meaningful in block boundaries only */
3195	    if (INSN_BLOCK (next) != INSN_BLOCK (insn))
3196	      continue;
3197
3198	    next_priority = insn_cost (insn, link, next) + priority (next);
3199	    if (next_priority > this_priority)
3200	      this_priority = next_priority;
3201	  }
3202      INSN_PRIORITY (insn) = this_priority;
3203    }
3204  return this_priority;
3205}
3206
3207
3208/* Remove all INSN_LISTs and EXPR_LISTs from the pending lists and add
3209   them to the unused_*_list variables, so that they can be reused.  */
3210
3211static void
3212free_pending_lists ()
3213{
3214  if (current_nr_blocks <= 1)
3215    {
3216      free_list (&pending_read_insns, &unused_insn_list);
3217      free_list (&pending_write_insns, &unused_insn_list);
3218      free_list (&pending_read_mems, &unused_expr_list);
3219      free_list (&pending_write_mems, &unused_expr_list);
3220    }
3221  else
3222    {
3223      /* interblock scheduling */
3224      int bb;
3225
3226      for (bb = 0; bb < current_nr_blocks; bb++)
3227	{
3228	  free_list (&bb_pending_read_insns[bb], &unused_insn_list);
3229	  free_list (&bb_pending_write_insns[bb], &unused_insn_list);
3230	  free_list (&bb_pending_read_mems[bb], &unused_expr_list);
3231	  free_list (&bb_pending_write_mems[bb], &unused_expr_list);
3232	}
3233    }
3234}
3235
3236/* Add an INSN and MEM reference pair to a pending INSN_LIST and MEM_LIST.
3237   The MEM is a memory reference contained within INSN, which we are saving
3238   so that we can do memory aliasing on it.  */
3239
3240static void
3241add_insn_mem_dependence (insn_list, mem_list, insn, mem)
3242     rtx *insn_list, *mem_list, insn, mem;
3243{
3244  register rtx link;
3245
3246  link = alloc_INSN_LIST (insn, *insn_list);
3247  *insn_list = link;
3248
3249  link = alloc_EXPR_LIST (VOIDmode, mem, *mem_list);
3250  *mem_list = link;
3251
3252  pending_lists_length++;
3253}
3254
3255
3256/* Make a dependency between every memory reference on the pending lists
3257   and INSN, thus flushing the pending lists.  If ONLY_WRITE, don't flush
3258   the read list.  */
3259
3260static void
3261flush_pending_lists (insn, only_write)
3262     rtx insn;
3263     int only_write;
3264{
3265  rtx u;
3266  rtx link;
3267
3268  while (pending_read_insns && ! only_write)
3269    {
3270      add_dependence (insn, XEXP (pending_read_insns, 0), REG_DEP_ANTI);
3271
3272      link = pending_read_insns;
3273      pending_read_insns = XEXP (pending_read_insns, 1);
3274      XEXP (link, 1) = unused_insn_list;
3275      unused_insn_list = link;
3276
3277      link = pending_read_mems;
3278      pending_read_mems = XEXP (pending_read_mems, 1);
3279      XEXP (link, 1) = unused_expr_list;
3280      unused_expr_list = link;
3281    }
3282  while (pending_write_insns)
3283    {
3284      add_dependence (insn, XEXP (pending_write_insns, 0), REG_DEP_ANTI);
3285
3286      link = pending_write_insns;
3287      pending_write_insns = XEXP (pending_write_insns, 1);
3288      XEXP (link, 1) = unused_insn_list;
3289      unused_insn_list = link;
3290
3291      link = pending_write_mems;
3292      pending_write_mems = XEXP (pending_write_mems, 1);
3293      XEXP (link, 1) = unused_expr_list;
3294      unused_expr_list = link;
3295    }
3296  pending_lists_length = 0;
3297
3298  /* last_pending_memory_flush is now a list of insns */
3299  for (u = last_pending_memory_flush; u; u = XEXP (u, 1))
3300    add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3301
3302  free_list (&last_pending_memory_flush, &unused_insn_list);
3303  last_pending_memory_flush = alloc_INSN_LIST (insn, NULL_RTX);
3304}
3305
3306/* Analyze a single SET or CLOBBER rtx, X, creating all dependencies generated
3307   by the write to the destination of X, and reads of everything mentioned.  */
3308
3309static void
3310sched_analyze_1 (x, insn)
3311     rtx x;
3312     rtx insn;
3313{
3314  register int regno;
3315  register rtx dest = SET_DEST (x);
3316  enum rtx_code code = GET_CODE (x);
3317
3318  if (dest == 0)
3319    return;
3320
3321  if (GET_CODE (dest) == PARALLEL
3322      && GET_MODE (dest) == BLKmode)
3323    {
3324      register int i;
3325      for (i = XVECLEN (dest, 0) - 1; i >= 0; i--)
3326	sched_analyze_1 (XVECEXP (dest, 0, i), insn);
3327      if (GET_CODE (x) == SET)
3328	sched_analyze_2 (SET_SRC (x), insn);
3329      return;
3330    }
3331
3332  while (GET_CODE (dest) == STRICT_LOW_PART || GET_CODE (dest) == SUBREG
3333      || GET_CODE (dest) == ZERO_EXTRACT || GET_CODE (dest) == SIGN_EXTRACT)
3334    {
3335      if (GET_CODE (dest) == ZERO_EXTRACT || GET_CODE (dest) == SIGN_EXTRACT)
3336	{
3337	  /* The second and third arguments are values read by this insn.  */
3338	  sched_analyze_2 (XEXP (dest, 1), insn);
3339	  sched_analyze_2 (XEXP (dest, 2), insn);
3340	}
3341      dest = SUBREG_REG (dest);
3342    }
3343
3344  if (GET_CODE (dest) == REG)
3345    {
3346      register int i;
3347
3348      regno = REGNO (dest);
3349
3350      /* A hard reg in a wide mode may really be multiple registers.
3351         If so, mark all of them just like the first.  */
3352      if (regno < FIRST_PSEUDO_REGISTER)
3353	{
3354	  i = HARD_REGNO_NREGS (regno, GET_MODE (dest));
3355	  while (--i >= 0)
3356	    {
3357	      rtx u;
3358
3359	      for (u = reg_last_uses[regno + i]; u; u = XEXP (u, 1))
3360		add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3361
3362	      for (u = reg_last_sets[regno + i]; u; u = XEXP (u, 1))
3363		add_dependence (insn, XEXP (u, 0), REG_DEP_OUTPUT);
3364
3365	      /* Clobbers need not be ordered with respect to one another,
3366		 but sets must be ordered with respect to a pending clobber. */
3367	      if (code == SET)
3368		{
3369	          reg_last_uses[regno + i] = 0;
3370	          for (u = reg_last_clobbers[regno + i]; u; u = XEXP (u, 1))
3371		    add_dependence (insn, XEXP (u, 0), REG_DEP_OUTPUT);
3372	          SET_REGNO_REG_SET (reg_pending_sets, regno + i);
3373		}
3374	      else
3375		SET_REGNO_REG_SET (reg_pending_clobbers, regno + i);
3376
3377	      /* Function calls clobber all call_used regs.  */
3378	      if (global_regs[regno + i]
3379		  || (code == SET && call_used_regs[regno + i]))
3380		for (u = last_function_call; u; u = XEXP (u, 1))
3381		  add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3382	    }
3383	}
3384      else
3385	{
3386	  rtx u;
3387
3388	  for (u = reg_last_uses[regno]; u; u = XEXP (u, 1))
3389	    add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3390
3391	  for (u = reg_last_sets[regno]; u; u = XEXP (u, 1))
3392	    add_dependence (insn, XEXP (u, 0), REG_DEP_OUTPUT);
3393
3394	  if (code == SET)
3395	    {
3396	      reg_last_uses[regno] = 0;
3397	      for (u = reg_last_clobbers[regno]; u; u = XEXP (u, 1))
3398		add_dependence (insn, XEXP (u, 0), REG_DEP_OUTPUT);
3399	      SET_REGNO_REG_SET (reg_pending_sets, regno);
3400	    }
3401	  else
3402	    SET_REGNO_REG_SET (reg_pending_clobbers, regno);
3403
3404	  /* Pseudos that are REG_EQUIV to something may be replaced
3405	     by that during reloading.  We need only add dependencies for
3406	     the address in the REG_EQUIV note.  */
3407	  if (!reload_completed
3408	      && reg_known_equiv_p[regno]
3409	      && GET_CODE (reg_known_value[regno]) == MEM)
3410	    sched_analyze_2 (XEXP (reg_known_value[regno], 0), insn);
3411
3412	  /* Don't let it cross a call after scheduling if it doesn't
3413	     already cross one.  */
3414
3415	  if (REG_N_CALLS_CROSSED (regno) == 0)
3416	    for (u = last_function_call; u; u = XEXP (u, 1))
3417	      add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3418	}
3419    }
3420  else if (GET_CODE (dest) == MEM)
3421    {
3422      /* Writing memory.  */
3423
3424      if (pending_lists_length > 32)
3425	{
3426	  /* Flush all pending reads and writes to prevent the pending lists
3427	     from getting any larger.  Insn scheduling runs too slowly when
3428	     these lists get long.  The number 32 was chosen because it
3429	     seems like a reasonable number.  When compiling GCC with itself,
3430	     this flush occurs 8 times for sparc, and 10 times for m88k using
3431	     the number 32.  */
3432	  flush_pending_lists (insn, 0);
3433	}
3434      else
3435	{
3436	  rtx u;
3437	  rtx pending, pending_mem;
3438
3439	  pending = pending_read_insns;
3440	  pending_mem = pending_read_mems;
3441	  while (pending)
3442	    {
3443	      /* If a dependency already exists, don't create a new one.  */
3444	      if (!find_insn_list (XEXP (pending, 0), LOG_LINKS (insn)))
3445		if (anti_dependence (XEXP (pending_mem, 0), dest))
3446		  add_dependence (insn, XEXP (pending, 0), REG_DEP_ANTI);
3447
3448	      pending = XEXP (pending, 1);
3449	      pending_mem = XEXP (pending_mem, 1);
3450	    }
3451
3452	  pending = pending_write_insns;
3453	  pending_mem = pending_write_mems;
3454	  while (pending)
3455	    {
3456	      /* If a dependency already exists, don't create a new one.  */
3457	      if (!find_insn_list (XEXP (pending, 0), LOG_LINKS (insn)))
3458		if (output_dependence (XEXP (pending_mem, 0), dest))
3459		  add_dependence (insn, XEXP (pending, 0), REG_DEP_OUTPUT);
3460
3461	      pending = XEXP (pending, 1);
3462	      pending_mem = XEXP (pending_mem, 1);
3463	    }
3464
3465	  for (u = last_pending_memory_flush; u; u = XEXP (u, 1))
3466	    add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3467
3468	  add_insn_mem_dependence (&pending_write_insns, &pending_write_mems,
3469				   insn, dest);
3470	}
3471      sched_analyze_2 (XEXP (dest, 0), insn);
3472    }
3473
3474  /* Analyze reads.  */
3475  if (GET_CODE (x) == SET)
3476    sched_analyze_2 (SET_SRC (x), insn);
3477}
3478
3479/* Analyze the uses of memory and registers in rtx X in INSN.  */
3480
3481static void
3482sched_analyze_2 (x, insn)
3483     rtx x;
3484     rtx insn;
3485{
3486  register int i;
3487  register int j;
3488  register enum rtx_code code;
3489  register char *fmt;
3490
3491  if (x == 0)
3492    return;
3493
3494  code = GET_CODE (x);
3495
3496  switch (code)
3497    {
3498    case CONST_INT:
3499    case CONST_DOUBLE:
3500    case SYMBOL_REF:
3501    case CONST:
3502    case LABEL_REF:
3503      /* Ignore constants.  Note that we must handle CONST_DOUBLE here
3504         because it may have a cc0_rtx in its CONST_DOUBLE_CHAIN field, but
3505         this does not mean that this insn is using cc0.  */
3506      return;
3507
3508#ifdef HAVE_cc0
3509    case CC0:
3510      {
3511	rtx link, prev;
3512
3513	/* User of CC0 depends on immediately preceding insn.  */
3514	SCHED_GROUP_P (insn) = 1;
3515
3516	/* There may be a note before this insn now, but all notes will
3517	   be removed before we actually try to schedule the insns, so
3518	   it won't cause a problem later.  We must avoid it here though.  */
3519	prev = prev_nonnote_insn (insn);
3520
3521	/* Make a copy of all dependencies on the immediately previous insn,
3522	   and add to this insn.  This is so that all the dependencies will
3523	   apply to the group.  Remove an explicit dependence on this insn
3524	   as SCHED_GROUP_P now represents it.  */
3525
3526	if (find_insn_list (prev, LOG_LINKS (insn)))
3527	  remove_dependence (insn, prev);
3528
3529	for (link = LOG_LINKS (prev); link; link = XEXP (link, 1))
3530	  add_dependence (insn, XEXP (link, 0), REG_NOTE_KIND (link));
3531
3532	return;
3533      }
3534#endif
3535
3536    case REG:
3537      {
3538	rtx u;
3539	int regno = REGNO (x);
3540	if (regno < FIRST_PSEUDO_REGISTER)
3541	  {
3542	    int i;
3543
3544	    i = HARD_REGNO_NREGS (regno, GET_MODE (x));
3545	    while (--i >= 0)
3546	      {
3547		reg_last_uses[regno + i]
3548		  = alloc_INSN_LIST (insn, reg_last_uses[regno + i]);
3549
3550		for (u = reg_last_sets[regno + i]; u; u = XEXP (u, 1))
3551		  add_dependence (insn, XEXP (u, 0), 0);
3552
3553		/* ??? This should never happen.  */
3554		for (u = reg_last_clobbers[regno + i]; u; u = XEXP (u, 1))
3555		  add_dependence (insn, XEXP (u, 0), 0);
3556
3557		if ((call_used_regs[regno + i] || global_regs[regno + i]))
3558		  /* Function calls clobber all call_used regs.  */
3559		  for (u = last_function_call; u; u = XEXP (u, 1))
3560		    add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3561	      }
3562	  }
3563	else
3564	  {
3565	    reg_last_uses[regno] = alloc_INSN_LIST (insn, reg_last_uses[regno]);
3566
3567	    for (u = reg_last_sets[regno]; u; u = XEXP (u, 1))
3568	      add_dependence (insn, XEXP (u, 0), 0);
3569
3570	    /* ??? This should never happen.  */
3571	    for (u = reg_last_clobbers[regno]; u; u = XEXP (u, 1))
3572	      add_dependence (insn, XEXP (u, 0), 0);
3573
3574	    /* Pseudos that are REG_EQUIV to something may be replaced
3575	       by that during reloading.  We need only add dependencies for
3576	       the address in the REG_EQUIV note.  */
3577	    if (!reload_completed
3578		&& reg_known_equiv_p[regno]
3579		&& GET_CODE (reg_known_value[regno]) == MEM)
3580	      sched_analyze_2 (XEXP (reg_known_value[regno], 0), insn);
3581
3582	    /* If the register does not already cross any calls, then add this
3583	       insn to the sched_before_next_call list so that it will still
3584	       not cross calls after scheduling.  */
3585	    if (REG_N_CALLS_CROSSED (regno) == 0)
3586	      add_dependence (sched_before_next_call, insn, REG_DEP_ANTI);
3587	  }
3588	return;
3589      }
3590
3591    case MEM:
3592      {
3593	/* Reading memory.  */
3594	rtx u;
3595	rtx pending, pending_mem;
3596
3597	pending = pending_read_insns;
3598	pending_mem = pending_read_mems;
3599	while (pending)
3600	  {
3601	    /* If a dependency already exists, don't create a new one.  */
3602	    if (!find_insn_list (XEXP (pending, 0), LOG_LINKS (insn)))
3603	      if (read_dependence (XEXP (pending_mem, 0), x))
3604		add_dependence (insn, XEXP (pending, 0), REG_DEP_ANTI);
3605
3606	    pending = XEXP (pending, 1);
3607	    pending_mem = XEXP (pending_mem, 1);
3608	  }
3609
3610	pending = pending_write_insns;
3611	pending_mem = pending_write_mems;
3612	while (pending)
3613	  {
3614	    /* If a dependency already exists, don't create a new one.  */
3615	    if (!find_insn_list (XEXP (pending, 0), LOG_LINKS (insn)))
3616	      if (true_dependence (XEXP (pending_mem, 0), VOIDmode,
3617		  x, rtx_varies_p))
3618		add_dependence (insn, XEXP (pending, 0), 0);
3619
3620	    pending = XEXP (pending, 1);
3621	    pending_mem = XEXP (pending_mem, 1);
3622	  }
3623
3624	for (u = last_pending_memory_flush; u; u = XEXP (u, 1))
3625	  add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3626
3627	/* Always add these dependencies to pending_reads, since
3628	   this insn may be followed by a write.  */
3629	add_insn_mem_dependence (&pending_read_insns, &pending_read_mems,
3630				 insn, x);
3631
3632	/* Take advantage of tail recursion here.  */
3633	sched_analyze_2 (XEXP (x, 0), insn);
3634	return;
3635      }
3636
3637    /* Force pending stores to memory in case a trap handler needs them.  */
3638    case TRAP_IF:
3639      flush_pending_lists (insn, 1);
3640      break;
3641
3642    case ASM_OPERANDS:
3643    case ASM_INPUT:
3644    case UNSPEC_VOLATILE:
3645      {
3646	rtx u;
3647
3648	/* Traditional and volatile asm instructions must be considered to use
3649	   and clobber all hard registers, all pseudo-registers and all of
3650	   memory.  So must TRAP_IF and UNSPEC_VOLATILE operations.
3651
3652	   Consider for instance a volatile asm that changes the fpu rounding
3653	   mode.  An insn should not be moved across this even if it only uses
3654	   pseudo-regs because it might give an incorrectly rounded result.  */
3655	if (code != ASM_OPERANDS || MEM_VOLATILE_P (x))
3656	  {
3657	    int max_reg = max_reg_num ();
3658	    for (i = 0; i < max_reg; i++)
3659	      {
3660		for (u = reg_last_uses[i]; u; u = XEXP (u, 1))
3661		  add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3662		reg_last_uses[i] = 0;
3663
3664		for (u = reg_last_sets[i]; u; u = XEXP (u, 1))
3665		  add_dependence (insn, XEXP (u, 0), 0);
3666
3667		for (u = reg_last_clobbers[i]; u; u = XEXP (u, 1))
3668		  add_dependence (insn, XEXP (u, 0), 0);
3669	      }
3670	    reg_pending_sets_all = 1;
3671
3672	    flush_pending_lists (insn, 0);
3673	  }
3674
3675	/* For all ASM_OPERANDS, we must traverse the vector of input operands.
3676	   We can not just fall through here since then we would be confused
3677	   by the ASM_INPUT rtx inside ASM_OPERANDS, which do not indicate
3678	   traditional asms unlike their normal usage.  */
3679
3680	if (code == ASM_OPERANDS)
3681	  {
3682	    for (j = 0; j < ASM_OPERANDS_INPUT_LENGTH (x); j++)
3683	      sched_analyze_2 (ASM_OPERANDS_INPUT (x, j), insn);
3684	    return;
3685	  }
3686	break;
3687      }
3688
3689    case PRE_DEC:
3690    case POST_DEC:
3691    case PRE_INC:
3692    case POST_INC:
3693      /* These both read and modify the result.  We must handle them as writes
3694         to get proper dependencies for following instructions.  We must handle
3695         them as reads to get proper dependencies from this to previous
3696         instructions.  Thus we need to pass them to both sched_analyze_1
3697         and sched_analyze_2.  We must call sched_analyze_2 first in order
3698         to get the proper antecedent for the read.  */
3699      sched_analyze_2 (XEXP (x, 0), insn);
3700      sched_analyze_1 (x, insn);
3701      return;
3702
3703    default:
3704      break;
3705    }
3706
3707  /* Other cases: walk the insn.  */
3708  fmt = GET_RTX_FORMAT (code);
3709  for (i = GET_RTX_LENGTH (code) - 1; i >= 0; i--)
3710    {
3711      if (fmt[i] == 'e')
3712	sched_analyze_2 (XEXP (x, i), insn);
3713      else if (fmt[i] == 'E')
3714	for (j = 0; j < XVECLEN (x, i); j++)
3715	  sched_analyze_2 (XVECEXP (x, i, j), insn);
3716    }
3717}
3718
3719/* Analyze an INSN with pattern X to find all dependencies.  */
3720
3721static void
3722sched_analyze_insn (x, insn, loop_notes)
3723     rtx x, insn;
3724     rtx loop_notes;
3725{
3726  register RTX_CODE code = GET_CODE (x);
3727  rtx link;
3728  int maxreg = max_reg_num ();
3729  int i;
3730
3731  if (code == SET || code == CLOBBER)
3732    sched_analyze_1 (x, insn);
3733  else if (code == PARALLEL)
3734    {
3735      register int i;
3736      for (i = XVECLEN (x, 0) - 1; i >= 0; i--)
3737	{
3738	  code = GET_CODE (XVECEXP (x, 0, i));
3739	  if (code == SET || code == CLOBBER)
3740	    sched_analyze_1 (XVECEXP (x, 0, i), insn);
3741	  else
3742	    sched_analyze_2 (XVECEXP (x, 0, i), insn);
3743	}
3744    }
3745  else
3746    sched_analyze_2 (x, insn);
3747
3748  /* Mark registers CLOBBERED or used by called function.  */
3749  if (GET_CODE (insn) == CALL_INSN)
3750    for (link = CALL_INSN_FUNCTION_USAGE (insn); link; link = XEXP (link, 1))
3751      {
3752	if (GET_CODE (XEXP (link, 0)) == CLOBBER)
3753	  sched_analyze_1 (XEXP (link, 0), insn);
3754	else
3755	  sched_analyze_2 (XEXP (link, 0), insn);
3756      }
3757
3758  /* If there is a {LOOP,EHREGION}_{BEG,END} note in the middle of a basic
3759     block, then we must be sure that no instructions are scheduled across it.
3760     Otherwise, the reg_n_refs info (which depends on loop_depth) would
3761     become incorrect.  */
3762
3763  if (loop_notes)
3764    {
3765      int max_reg = max_reg_num ();
3766      int schedule_barrier_found = 0;
3767      rtx link;
3768
3769      /* Update loop_notes with any notes from this insn.  Also determine
3770	 if any of the notes on the list correspond to instruction scheduling
3771	 barriers (loop, eh & setjmp notes, but not range notes.  */
3772      link = loop_notes;
3773      while (XEXP (link, 1))
3774	{
3775	  if (INTVAL (XEXP (link, 0)) == NOTE_INSN_LOOP_BEG
3776	      || INTVAL (XEXP (link, 0)) == NOTE_INSN_LOOP_END
3777	      || INTVAL (XEXP (link, 0)) == NOTE_INSN_EH_REGION_BEG
3778	      || INTVAL (XEXP (link, 0)) == NOTE_INSN_EH_REGION_END
3779	      || INTVAL (XEXP (link, 0)) == NOTE_INSN_SETJMP)
3780	    schedule_barrier_found = 1;
3781
3782	  link = XEXP (link, 1);
3783	}
3784      XEXP (link, 1) = REG_NOTES (insn);
3785      REG_NOTES (insn) = loop_notes;
3786
3787      /* Add dependencies if a scheduling barrier was found.  */
3788      if (schedule_barrier_found)
3789	{
3790	  for (i = 0; i < max_reg; i++)
3791	    {
3792	      rtx u;
3793	      for (u = reg_last_uses[i]; u; u = XEXP (u, 1))
3794		add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3795	      reg_last_uses[i] = 0;
3796
3797	      for (u = reg_last_sets[i]; u; u = XEXP (u, 1))
3798		add_dependence (insn, XEXP (u, 0), 0);
3799
3800	      for (u = reg_last_clobbers[i]; u; u = XEXP (u, 1))
3801		add_dependence (insn, XEXP (u, 0), 0);
3802	    }
3803	  reg_pending_sets_all = 1;
3804
3805	  flush_pending_lists (insn, 0);
3806	}
3807
3808    }
3809
3810  /* Accumulate clobbers until the next set so that it will be output dependant
3811     on all of them.  At the next set we can clear the clobber list, since
3812     subsequent sets will be output dependant on it.  */
3813  EXECUTE_IF_SET_IN_REG_SET (reg_pending_sets, 0, i,
3814			     {
3815			       free_list (&reg_last_sets[i], &unused_insn_list);
3816			       free_list (&reg_last_clobbers[i],
3817					  &unused_insn_list);
3818			       reg_last_sets[i]
3819				 = alloc_INSN_LIST (insn, NULL_RTX);
3820			     });
3821  EXECUTE_IF_SET_IN_REG_SET (reg_pending_clobbers, 0, i,
3822			     {
3823			       reg_last_clobbers[i]
3824				 = alloc_INSN_LIST (insn, reg_last_clobbers[i]);
3825			     });
3826  CLEAR_REG_SET (reg_pending_sets);
3827  CLEAR_REG_SET (reg_pending_clobbers);
3828
3829  if (reg_pending_sets_all)
3830    {
3831      for (i = 0; i < maxreg; i++)
3832	{
3833	  free_list (&reg_last_sets[i], &unused_insn_list);
3834	  reg_last_sets[i] = alloc_INSN_LIST (insn, NULL_RTX);
3835	}
3836
3837      reg_pending_sets_all = 0;
3838    }
3839
3840  /* Handle function calls and function returns created by the epilogue
3841     threading code.  */
3842  if (GET_CODE (insn) == CALL_INSN || GET_CODE (insn) == JUMP_INSN)
3843    {
3844      rtx dep_insn;
3845      rtx prev_dep_insn;
3846
3847      /* When scheduling instructions, we make sure calls don't lose their
3848         accompanying USE insns by depending them one on another in order.
3849
3850         Also, we must do the same thing for returns created by the epilogue
3851         threading code.  Note this code works only in this special case,
3852         because other passes make no guarantee that they will never emit
3853         an instruction between a USE and a RETURN.  There is such a guarantee
3854         for USE instructions immediately before a call.  */
3855
3856      prev_dep_insn = insn;
3857      dep_insn = PREV_INSN (insn);
3858      while (GET_CODE (dep_insn) == INSN
3859	     && GET_CODE (PATTERN (dep_insn)) == USE
3860	     && GET_CODE (XEXP (PATTERN (dep_insn), 0)) == REG)
3861	{
3862	  SCHED_GROUP_P (prev_dep_insn) = 1;
3863
3864	  /* Make a copy of all dependencies on dep_insn, and add to insn.
3865	     This is so that all of the dependencies will apply to the
3866	     group.  */
3867
3868	  for (link = LOG_LINKS (dep_insn); link; link = XEXP (link, 1))
3869	    add_dependence (insn, XEXP (link, 0), REG_NOTE_KIND (link));
3870
3871	  prev_dep_insn = dep_insn;
3872	  dep_insn = PREV_INSN (dep_insn);
3873	}
3874    }
3875}
3876
3877/* Analyze every insn between HEAD and TAIL inclusive, creating LOG_LINKS
3878   for every dependency.  */
3879
3880static void
3881sched_analyze (head, tail)
3882     rtx head, tail;
3883{
3884  register rtx insn;
3885  register rtx u;
3886  rtx loop_notes = 0;
3887
3888  for (insn = head;; insn = NEXT_INSN (insn))
3889    {
3890      if (GET_CODE (insn) == INSN || GET_CODE (insn) == JUMP_INSN)
3891	{
3892	  /* Make each JUMP_INSN a scheduling barrier for memory references.  */
3893	  if (GET_CODE (insn) == JUMP_INSN)
3894	    last_pending_memory_flush
3895	      = alloc_INSN_LIST (insn, last_pending_memory_flush);
3896	  sched_analyze_insn (PATTERN (insn), insn, loop_notes);
3897	  loop_notes = 0;
3898	}
3899      else if (GET_CODE (insn) == CALL_INSN)
3900	{
3901	  rtx x;
3902	  register int i;
3903
3904	  CANT_MOVE (insn) = 1;
3905
3906	  /* Any instruction using a hard register which may get clobbered
3907	     by a call needs to be marked as dependent on this call.
3908	     This prevents a use of a hard return reg from being moved
3909	     past a void call (i.e. it does not explicitly set the hard
3910	     return reg).  */
3911
3912	  /* If this call is followed by a NOTE_INSN_SETJMP, then assume that
3913	     all registers, not just hard registers, may be clobbered by this
3914	     call.  */
3915
3916	  /* Insn, being a CALL_INSN, magically depends on
3917	     `last_function_call' already.  */
3918
3919	  if (NEXT_INSN (insn) && GET_CODE (NEXT_INSN (insn)) == NOTE
3920	      && NOTE_LINE_NUMBER (NEXT_INSN (insn)) == NOTE_INSN_SETJMP)
3921	    {
3922	      int max_reg = max_reg_num ();
3923	      for (i = 0; i < max_reg; i++)
3924		{
3925		  for (u = reg_last_uses[i]; u; u = XEXP (u, 1))
3926		    add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3927
3928		  reg_last_uses[i] = 0;
3929
3930		  for (u = reg_last_sets[i]; u; u = XEXP (u, 1))
3931		    add_dependence (insn, XEXP (u, 0), 0);
3932
3933		  for (u = reg_last_clobbers[i]; u; u = XEXP (u, 1))
3934		    add_dependence (insn, XEXP (u, 0), 0);
3935		}
3936	      reg_pending_sets_all = 1;
3937
3938	      /* Add a pair of fake REG_NOTE which we will later
3939		 convert back into a NOTE_INSN_SETJMP note.  See
3940		 reemit_notes for why we use a pair of NOTEs.  */
3941	      REG_NOTES (insn) = alloc_EXPR_LIST (REG_DEAD,
3942						  GEN_INT (0),
3943						  REG_NOTES (insn));
3944	      REG_NOTES (insn) = alloc_EXPR_LIST (REG_DEAD,
3945						  GEN_INT (NOTE_INSN_SETJMP),
3946						  REG_NOTES (insn));
3947	    }
3948	  else
3949	    {
3950	      for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
3951		if (call_used_regs[i] || global_regs[i])
3952		  {
3953		    for (u = reg_last_uses[i]; u; u = XEXP (u, 1))
3954		      add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3955
3956		    for (u = reg_last_sets[i]; u; u = XEXP (u, 1))
3957		      add_dependence (insn, XEXP (u, 0), REG_DEP_ANTI);
3958
3959		    SET_REGNO_REG_SET (reg_pending_clobbers, i);
3960		  }
3961	    }
3962
3963	  /* For each insn which shouldn't cross a call, add a dependence
3964	     between that insn and this call insn.  */
3965	  x = LOG_LINKS (sched_before_next_call);
3966	  while (x)
3967	    {
3968	      add_dependence (insn, XEXP (x, 0), REG_DEP_ANTI);
3969	      x = XEXP (x, 1);
3970	    }
3971	  LOG_LINKS (sched_before_next_call) = 0;
3972
3973	  sched_analyze_insn (PATTERN (insn), insn, loop_notes);
3974	  loop_notes = 0;
3975
3976	  /* In the absence of interprocedural alias analysis, we must flush
3977	     all pending reads and writes, and start new dependencies starting
3978	     from here.  But only flush writes for constant calls (which may
3979	     be passed a pointer to something we haven't written yet).  */
3980	  flush_pending_lists (insn, CONST_CALL_P (insn));
3981
3982	  /* Depend this function call (actually, the user of this
3983	     function call) on all hard register clobberage.  */
3984
3985	  /* last_function_call is now a list of insns */
3986	  free_list(&last_function_call, &unused_insn_list);
3987	  last_function_call = alloc_INSN_LIST (insn, NULL_RTX);
3988	}
3989
3990      /* See comments on reemit_notes as to why we do this.  */
3991      /* ??? Actually, the reemit_notes just say what is done, not why.  */
3992
3993      else if (GET_CODE (insn) == NOTE
3994	       && (NOTE_LINE_NUMBER (insn) == NOTE_INSN_RANGE_START
3995		   || NOTE_LINE_NUMBER (insn) == NOTE_INSN_RANGE_END))
3996	{
3997	  loop_notes = alloc_EXPR_LIST (REG_DEAD, NOTE_RANGE_INFO (insn),
3998					loop_notes);
3999	  loop_notes = alloc_EXPR_LIST (REG_DEAD,
4000					GEN_INT (NOTE_LINE_NUMBER (insn)),
4001					loop_notes);
4002	}
4003      else if (GET_CODE (insn) == NOTE
4004	       && (NOTE_LINE_NUMBER (insn) == NOTE_INSN_LOOP_BEG
4005		   || NOTE_LINE_NUMBER (insn) == NOTE_INSN_LOOP_END
4006		   || NOTE_LINE_NUMBER (insn) == NOTE_INSN_EH_REGION_BEG
4007		   || NOTE_LINE_NUMBER (insn) == NOTE_INSN_EH_REGION_END
4008		   || (NOTE_LINE_NUMBER (insn) == NOTE_INSN_SETJMP
4009		       && GET_CODE (PREV_INSN (insn)) != CALL_INSN)))
4010	{
4011	  loop_notes = alloc_EXPR_LIST (REG_DEAD,
4012					GEN_INT (NOTE_BLOCK_NUMBER (insn)),
4013					loop_notes);
4014	  loop_notes = alloc_EXPR_LIST (REG_DEAD,
4015					GEN_INT (NOTE_LINE_NUMBER (insn)),
4016					loop_notes);
4017	  CONST_CALL_P (loop_notes) = CONST_CALL_P (insn);
4018	}
4019
4020      if (insn == tail)
4021	return;
4022    }
4023  abort ();
4024}
4025
4026/* Called when we see a set of a register.  If death is true, then we are
4027   scanning backwards.  Mark that register as unborn.  If nobody says
4028   otherwise, that is how things will remain.  If death is false, then we
4029   are scanning forwards.  Mark that register as being born.  */
4030
4031static void
4032sched_note_set (x, death)
4033     rtx x;
4034     int death;
4035{
4036  register int regno;
4037  register rtx reg = SET_DEST (x);
4038  int subreg_p = 0;
4039
4040  if (reg == 0)
4041    return;
4042
4043  if (GET_CODE (reg) == PARALLEL
4044      && GET_MODE (reg) == BLKmode)
4045    {
4046      register int i;
4047      for (i = XVECLEN (reg, 0) - 1; i >= 0; i--)
4048	sched_note_set (XVECEXP (reg, 0, i), death);
4049      return;
4050    }
4051
4052  while (GET_CODE (reg) == SUBREG || GET_CODE (reg) == STRICT_LOW_PART
4053	 || GET_CODE (reg) == SIGN_EXTRACT || GET_CODE (reg) == ZERO_EXTRACT)
4054    {
4055      /* Must treat modification of just one hardware register of a multi-reg
4056         value or just a byte field of a register exactly the same way that
4057         mark_set_1 in flow.c does, i.e. anything except a paradoxical subreg
4058         does not kill the entire register.  */
4059      if (GET_CODE (reg) != SUBREG
4060	  || REG_SIZE (SUBREG_REG (reg)) > REG_SIZE (reg))
4061	subreg_p = 1;
4062
4063      reg = SUBREG_REG (reg);
4064    }
4065
4066  if (GET_CODE (reg) != REG)
4067    return;
4068
4069  /* Global registers are always live, so the code below does not apply
4070     to them.  */
4071
4072  regno = REGNO (reg);
4073  if (regno >= FIRST_PSEUDO_REGISTER || !global_regs[regno])
4074    {
4075      if (death)
4076	{
4077	  /* If we only set part of the register, then this set does not
4078	     kill it.  */
4079	  if (subreg_p)
4080	    return;
4081
4082	  /* Try killing this register.  */
4083	  if (regno < FIRST_PSEUDO_REGISTER)
4084	    {
4085	      int j = HARD_REGNO_NREGS (regno, GET_MODE (reg));
4086	      while (--j >= 0)
4087		{
4088		  CLEAR_REGNO_REG_SET (bb_live_regs, regno + j);
4089		}
4090	    }
4091	  else
4092	    {
4093	      /* Recompute REG_BASIC_BLOCK as we update all the other
4094		 dataflow information.  */
4095	      if (sched_reg_basic_block[regno] == REG_BLOCK_UNKNOWN)
4096		sched_reg_basic_block[regno] = current_block_num;
4097	      else if (sched_reg_basic_block[regno] != current_block_num)
4098		sched_reg_basic_block[regno] = REG_BLOCK_GLOBAL;
4099
4100	      CLEAR_REGNO_REG_SET (bb_live_regs, regno);
4101	    }
4102	}
4103      else
4104	{
4105	  /* Make the register live again.  */
4106	  if (regno < FIRST_PSEUDO_REGISTER)
4107	    {
4108	      int j = HARD_REGNO_NREGS (regno, GET_MODE (reg));
4109	      while (--j >= 0)
4110		{
4111		  SET_REGNO_REG_SET (bb_live_regs, regno + j);
4112		}
4113	    }
4114	  else
4115	    {
4116	      SET_REGNO_REG_SET (bb_live_regs, regno);
4117	    }
4118	}
4119    }
4120}
4121
4122/* Macros and functions for keeping the priority queue sorted, and
4123   dealing with queueing and dequeueing of instructions.  */
4124
4125#define SCHED_SORT(READY, N_READY)                                   \
4126do { if ((N_READY) == 2)				             \
4127       swap_sort (READY, N_READY);			             \
4128     else if ((N_READY) > 2)                                         \
4129         qsort (READY, N_READY, sizeof (rtx), rank_for_schedule); }  \
4130while (0)
4131
4132/* Returns a positive value if x is preferred; returns a negative value if
4133   y is preferred.  Should never return 0, since that will make the sort
4134   unstable.  */
4135
4136static int
4137rank_for_schedule (x, y)
4138     const GENERIC_PTR x;
4139     const GENERIC_PTR y;
4140{
4141  rtx tmp = *(rtx *)y;
4142  rtx tmp2 = *(rtx *)x;
4143  rtx link;
4144  int tmp_class, tmp2_class, depend_count1, depend_count2;
4145  int val, priority_val, spec_val, prob_val, weight_val;
4146
4147
4148  /* prefer insn with higher priority */
4149  priority_val = INSN_PRIORITY (tmp2) - INSN_PRIORITY (tmp);
4150  if (priority_val)
4151    return priority_val;
4152
4153  /* prefer an insn with smaller contribution to registers-pressure */
4154  if (!reload_completed &&
4155      (weight_val = INSN_REG_WEIGHT (tmp) - INSN_REG_WEIGHT (tmp2)))
4156    return (weight_val);
4157
4158  /* some comparison make sense in interblock scheduling only */
4159  if (INSN_BB (tmp) != INSN_BB (tmp2))
4160    {
4161      /* prefer an inblock motion on an interblock motion */
4162      if ((INSN_BB (tmp2) == target_bb) && (INSN_BB (tmp) != target_bb))
4163	return 1;
4164      if ((INSN_BB (tmp) == target_bb) && (INSN_BB (tmp2) != target_bb))
4165	return -1;
4166
4167      /* prefer a useful motion on a speculative one */
4168      if ((spec_val = IS_SPECULATIVE_INSN (tmp) - IS_SPECULATIVE_INSN (tmp2)))
4169	return (spec_val);
4170
4171      /* prefer a more probable (speculative) insn */
4172      prob_val = INSN_PROBABILITY (tmp2) - INSN_PROBABILITY (tmp);
4173      if (prob_val)
4174	return (prob_val);
4175    }
4176
4177  /* compare insns based on their relation to the last-scheduled-insn */
4178  if (last_scheduled_insn)
4179    {
4180      /* Classify the instructions into three classes:
4181         1) Data dependent on last schedule insn.
4182         2) Anti/Output dependent on last scheduled insn.
4183         3) Independent of last scheduled insn, or has latency of one.
4184         Choose the insn from the highest numbered class if different.  */
4185      link = find_insn_list (tmp, INSN_DEPEND (last_scheduled_insn));
4186      if (link == 0 || insn_cost (last_scheduled_insn, link, tmp) == 1)
4187	tmp_class = 3;
4188      else if (REG_NOTE_KIND (link) == 0)	/* Data dependence.  */
4189	tmp_class = 1;
4190      else
4191	tmp_class = 2;
4192
4193      link = find_insn_list (tmp2, INSN_DEPEND (last_scheduled_insn));
4194      if (link == 0 || insn_cost (last_scheduled_insn, link, tmp2) == 1)
4195	tmp2_class = 3;
4196      else if (REG_NOTE_KIND (link) == 0)	/* Data dependence.  */
4197	tmp2_class = 1;
4198      else
4199	tmp2_class = 2;
4200
4201      if ((val = tmp2_class - tmp_class))
4202	return val;
4203    }
4204
4205  /* Prefer the insn which has more later insns that depend on it.
4206     This gives the scheduler more freedom when scheduling later
4207     instructions at the expense of added register pressure.  */
4208  depend_count1 = 0;
4209  for (link = INSN_DEPEND (tmp); link; link = XEXP (link, 1))
4210    depend_count1++;
4211
4212  depend_count2 = 0;
4213  for (link = INSN_DEPEND (tmp2); link; link = XEXP (link, 1))
4214    depend_count2++;
4215
4216  val = depend_count2 - depend_count1;
4217  if (val)
4218    return val;
4219
4220  /* If insns are equally good, sort by INSN_LUID (original insn order),
4221     so that we make the sort stable.  This minimizes instruction movement,
4222     thus minimizing sched's effect on debugging and cross-jumping.  */
4223  return INSN_LUID (tmp) - INSN_LUID (tmp2);
4224}
4225
4226/* Resort the array A in which only element at index N may be out of order.  */
4227
4228HAIFA_INLINE static void
4229swap_sort (a, n)
4230     rtx *a;
4231     int n;
4232{
4233  rtx insn = a[n - 1];
4234  int i = n - 2;
4235
4236  while (i >= 0 && rank_for_schedule (a + i, &insn) >= 0)
4237    {
4238      a[i + 1] = a[i];
4239      i -= 1;
4240    }
4241  a[i + 1] = insn;
4242}
4243
4244static int max_priority;
4245
4246/* Add INSN to the insn queue so that it can be executed at least
4247   N_CYCLES after the currently executing insn.  Preserve insns
4248   chain for debugging purposes.  */
4249
4250HAIFA_INLINE static void
4251queue_insn (insn, n_cycles)
4252     rtx insn;
4253     int n_cycles;
4254{
4255  int next_q = NEXT_Q_AFTER (q_ptr, n_cycles);
4256  rtx link = alloc_INSN_LIST (insn, insn_queue[next_q]);
4257  insn_queue[next_q] = link;
4258  q_size += 1;
4259
4260  if (sched_verbose >= 2)
4261    {
4262      fprintf (dump, ";;\t\tReady-->Q: insn %d: ", INSN_UID (insn));
4263
4264      if (INSN_BB (insn) != target_bb)
4265	fprintf (dump, "(b%d) ", INSN_BLOCK (insn));
4266
4267      fprintf (dump, "queued for %d cycles.\n", n_cycles);
4268    }
4269
4270}
4271
4272/* Return nonzero if PAT is the pattern of an insn which makes a
4273   register live.  */
4274
4275HAIFA_INLINE static int
4276birthing_insn_p (pat)
4277     rtx pat;
4278{
4279  int j;
4280
4281  if (reload_completed == 1)
4282    return 0;
4283
4284  if (GET_CODE (pat) == SET
4285      && (GET_CODE (SET_DEST (pat)) == REG
4286	  || (GET_CODE (SET_DEST (pat)) == PARALLEL
4287	      && GET_MODE (SET_DEST (pat)) == BLKmode)))
4288    {
4289      rtx dest = SET_DEST (pat);
4290      int i;
4291
4292      /* It would be more accurate to use refers_to_regno_p or
4293	 reg_mentioned_p to determine when the dest is not live before this
4294	 insn.  */
4295      if (GET_CODE (dest) == REG)
4296	{
4297	  i = REGNO (dest);
4298	  if (REGNO_REG_SET_P (bb_live_regs, i))
4299	    return (REG_N_SETS (i) == 1);
4300	}
4301      else
4302	{
4303	  for (i = XVECLEN (dest, 0) - 1; i >= 0; i--)
4304	    {
4305	      int regno = REGNO (SET_DEST (XVECEXP (dest, 0, i)));
4306	      if (REGNO_REG_SET_P (bb_live_regs, regno))
4307		return (REG_N_SETS (regno) == 1);
4308	    }
4309	}
4310      return 0;
4311    }
4312  if (GET_CODE (pat) == PARALLEL)
4313    {
4314      for (j = 0; j < XVECLEN (pat, 0); j++)
4315	if (birthing_insn_p (XVECEXP (pat, 0, j)))
4316	  return 1;
4317    }
4318  return 0;
4319}
4320
4321/* PREV is an insn that is ready to execute.  Adjust its priority if that
4322   will help shorten register lifetimes.  */
4323
4324HAIFA_INLINE static void
4325adjust_priority (prev)
4326     rtx prev;
4327{
4328  /* Trying to shorten register lives after reload has completed
4329     is useless and wrong.  It gives inaccurate schedules.  */
4330  if (reload_completed == 0)
4331    {
4332      rtx note;
4333      int n_deaths = 0;
4334
4335      /* ??? This code has no effect, because REG_DEAD notes are removed
4336	 before we ever get here.  */
4337      for (note = REG_NOTES (prev); note; note = XEXP (note, 1))
4338	if (REG_NOTE_KIND (note) == REG_DEAD)
4339	  n_deaths += 1;
4340
4341      /* Defer scheduling insns which kill registers, since that
4342	 shortens register lives.  Prefer scheduling insns which
4343	 make registers live for the same reason.  */
4344      switch (n_deaths)
4345	{
4346	default:
4347	  INSN_PRIORITY (prev) >>= 3;
4348	  break;
4349	case 3:
4350	  INSN_PRIORITY (prev) >>= 2;
4351	  break;
4352	case 2:
4353	case 1:
4354	  INSN_PRIORITY (prev) >>= 1;
4355	  break;
4356	case 0:
4357	  if (birthing_insn_p (PATTERN (prev)))
4358	    {
4359	      int max = max_priority;
4360
4361	      if (max > INSN_PRIORITY (prev))
4362		INSN_PRIORITY (prev) = max;
4363	    }
4364	  break;
4365	}
4366#ifdef ADJUST_PRIORITY
4367      ADJUST_PRIORITY (prev);
4368#endif
4369    }
4370}
4371
4372/* Clock at which the previous instruction was issued.  */
4373static int last_clock_var;
4374
4375/* INSN is the "currently executing insn".  Launch each insn which was
4376   waiting on INSN.  READY is a vector of insns which are ready to fire.
4377   N_READY is the number of elements in READY.  CLOCK is the current
4378   cycle.  */
4379
4380static int
4381schedule_insn (insn, ready, n_ready, clock)
4382     rtx insn;
4383     rtx *ready;
4384     int n_ready;
4385     int clock;
4386{
4387  rtx link;
4388  int unit;
4389
4390  unit = insn_unit (insn);
4391
4392  if (sched_verbose >= 2)
4393    {
4394      fprintf (dump, ";;\t\t--> scheduling insn <<<%d>>> on unit ", INSN_UID (insn));
4395      insn_print_units (insn);
4396      fprintf (dump, "\n");
4397    }
4398
4399  if (sched_verbose && unit == -1)
4400    visualize_no_unit (insn);
4401
4402  if (MAX_BLOCKAGE > 1 || issue_rate > 1 || sched_verbose)
4403    schedule_unit (unit, insn, clock);
4404
4405  if (INSN_DEPEND (insn) == 0)
4406    return n_ready;
4407
4408  /* This is used by the function adjust_priority above.  */
4409  if (n_ready > 0)
4410    max_priority = MAX (INSN_PRIORITY (ready[0]), INSN_PRIORITY (insn));
4411  else
4412    max_priority = INSN_PRIORITY (insn);
4413
4414  for (link = INSN_DEPEND (insn); link != 0; link = XEXP (link, 1))
4415    {
4416      rtx next = XEXP (link, 0);
4417      int cost = insn_cost (insn, link, next);
4418
4419      INSN_TICK (next) = MAX (INSN_TICK (next), clock + cost);
4420
4421      if ((INSN_DEP_COUNT (next) -= 1) == 0)
4422	{
4423	  int effective_cost = INSN_TICK (next) - clock;
4424
4425	  /* For speculative insns, before inserting to ready/queue,
4426	     check live, exception-free, and issue-delay */
4427	  if (INSN_BB (next) != target_bb
4428	      && (!IS_VALID (INSN_BB (next))
4429		  || CANT_MOVE (next)
4430		  || (IS_SPECULATIVE_INSN (next)
4431		      && (insn_issue_delay (next) > 3
4432			  || !check_live (next, INSN_BB (next))
4433		 || !is_exception_free (next, INSN_BB (next), target_bb)))))
4434	    continue;
4435
4436	  if (sched_verbose >= 2)
4437	    {
4438	      fprintf (dump, ";;\t\tdependences resolved: insn %d ", INSN_UID (next));
4439
4440	      if (current_nr_blocks > 1 && INSN_BB (next) != target_bb)
4441		fprintf (dump, "/b%d ", INSN_BLOCK (next));
4442
4443	      if (effective_cost <= 1)
4444		fprintf (dump, "into ready\n");
4445	      else
4446		fprintf (dump, "into queue with cost=%d\n", effective_cost);
4447	    }
4448
4449	  /* Adjust the priority of NEXT and either put it on the ready
4450	     list or queue it.  */
4451	  adjust_priority (next);
4452	  if (effective_cost <= 1)
4453	    ready[n_ready++] = next;
4454	  else
4455	    queue_insn (next, effective_cost);
4456	}
4457    }
4458
4459  /* Annotate the instruction with issue information -- TImode
4460     indicates that the instruction is expected not to be able
4461     to issue on the same cycle as the previous insn.  A machine
4462     may use this information to decide how the instruction should
4463     be aligned.  */
4464  if (reload_completed && issue_rate > 1)
4465    {
4466      PUT_MODE (insn, clock > last_clock_var ? TImode : VOIDmode);
4467      last_clock_var = clock;
4468    }
4469
4470  return n_ready;
4471}
4472
4473
4474/* Add a REG_DEAD note for REG to INSN, reusing a REG_DEAD note from the
4475   dead_notes list.  */
4476
4477static void
4478create_reg_dead_note (reg, insn)
4479     rtx reg, insn;
4480{
4481  rtx link;
4482
4483  /* The number of registers killed after scheduling must be the same as the
4484     number of registers killed before scheduling.  The number of REG_DEAD
4485     notes may not be conserved, i.e. two SImode hard register REG_DEAD notes
4486     might become one DImode hard register REG_DEAD note, but the number of
4487     registers killed will be conserved.
4488
4489     We carefully remove REG_DEAD notes from the dead_notes list, so that
4490     there will be none left at the end.  If we run out early, then there
4491     is a bug somewhere in flow, combine and/or sched.  */
4492
4493  if (dead_notes == 0)
4494    {
4495      if (current_nr_blocks <= 1)
4496	abort ();
4497      else
4498	link = alloc_EXPR_LIST (REG_DEAD, NULL_RTX, NULL_RTX);
4499    }
4500  else
4501    {
4502      /* Number of regs killed by REG.  */
4503      int regs_killed = (REGNO (reg) >= FIRST_PSEUDO_REGISTER ? 1
4504			 : HARD_REGNO_NREGS (REGNO (reg), GET_MODE (reg)));
4505      /* Number of regs killed by REG_DEAD notes taken off the list.  */
4506      int reg_note_regs;
4507
4508      link = dead_notes;
4509      reg_note_regs = (REGNO (XEXP (link, 0)) >= FIRST_PSEUDO_REGISTER ? 1
4510		       : HARD_REGNO_NREGS (REGNO (XEXP (link, 0)),
4511					   GET_MODE (XEXP (link, 0))));
4512      while (reg_note_regs < regs_killed)
4513	{
4514	  link = XEXP (link, 1);
4515
4516	  /* LINK might be zero if we killed more registers after scheduling
4517	     than before, and the last hard register we kill is actually
4518	     multiple hard regs.
4519
4520	     This is normal for interblock scheduling, so deal with it in
4521	     that case, else abort.  */
4522	  if (link == NULL_RTX && current_nr_blocks <= 1)
4523	    abort ();
4524	  else if (link == NULL_RTX)
4525	    link = alloc_EXPR_LIST (REG_DEAD, gen_rtx_REG (word_mode, 0),
4526				    NULL_RTX);
4527
4528	  reg_note_regs += (REGNO (XEXP (link, 0)) >= FIRST_PSEUDO_REGISTER ? 1
4529			    : HARD_REGNO_NREGS (REGNO (XEXP (link, 0)),
4530						GET_MODE (XEXP (link, 0))));
4531	}
4532      dead_notes = XEXP (link, 1);
4533
4534      /* If we took too many regs kills off, put the extra ones back.  */
4535      while (reg_note_regs > regs_killed)
4536	{
4537	  rtx temp_reg, temp_link;
4538
4539	  temp_reg = gen_rtx_REG (word_mode, 0);
4540	  temp_link = alloc_EXPR_LIST (REG_DEAD, temp_reg, dead_notes);
4541	  dead_notes = temp_link;
4542	  reg_note_regs--;
4543	}
4544    }
4545
4546  XEXP (link, 0) = reg;
4547  XEXP (link, 1) = REG_NOTES (insn);
4548  REG_NOTES (insn) = link;
4549}
4550
4551/* Subroutine on attach_deaths_insn--handles the recursive search
4552   through INSN.  If SET_P is true, then x is being modified by the insn.  */
4553
4554static void
4555attach_deaths (x, insn, set_p)
4556     rtx x;
4557     rtx insn;
4558     int set_p;
4559{
4560  register int i;
4561  register int j;
4562  register enum rtx_code code;
4563  register char *fmt;
4564
4565  if (x == 0)
4566    return;
4567
4568  code = GET_CODE (x);
4569
4570  switch (code)
4571    {
4572    case CONST_INT:
4573    case CONST_DOUBLE:
4574    case LABEL_REF:
4575    case SYMBOL_REF:
4576    case CONST:
4577    case CODE_LABEL:
4578    case PC:
4579    case CC0:
4580      /* Get rid of the easy cases first.  */
4581      return;
4582
4583    case REG:
4584      {
4585	/* If the register dies in this insn, queue that note, and mark
4586	   this register as needing to die.  */
4587	/* This code is very similar to mark_used_1 (if set_p is false)
4588	   and mark_set_1 (if set_p is true) in flow.c.  */
4589
4590	register int regno;
4591	int some_needed;
4592	int all_needed;
4593
4594	if (set_p)
4595	  return;
4596
4597	regno = REGNO (x);
4598	all_needed = some_needed = REGNO_REG_SET_P (old_live_regs, regno);
4599	if (regno < FIRST_PSEUDO_REGISTER)
4600	  {
4601	    int n;
4602
4603	    n = HARD_REGNO_NREGS (regno, GET_MODE (x));
4604	    while (--n > 0)
4605	      {
4606		int needed = (REGNO_REG_SET_P (old_live_regs, regno + n));
4607		some_needed |= needed;
4608		all_needed &= needed;
4609	      }
4610	  }
4611
4612	/* If it wasn't live before we started, then add a REG_DEAD note.
4613	   We must check the previous lifetime info not the current info,
4614	   because we may have to execute this code several times, e.g.
4615	   once for a clobber (which doesn't add a note) and later
4616	   for a use (which does add a note).
4617
4618	   Always make the register live.  We must do this even if it was
4619	   live before, because this may be an insn which sets and uses
4620	   the same register, in which case the register has already been
4621	   killed, so we must make it live again.
4622
4623	   Global registers are always live, and should never have a REG_DEAD
4624	   note added for them, so none of the code below applies to them.  */
4625
4626	if (regno >= FIRST_PSEUDO_REGISTER || ! global_regs[regno])
4627	  {
4628	    /* Never add REG_DEAD notes for STACK_POINTER_REGNUM
4629	       since it's always considered to be live.  Similarly
4630	       for FRAME_POINTER_REGNUM if a frame pointer is needed
4631	       and for ARG_POINTER_REGNUM if it is fixed.  */
4632	    if (! (regno == FRAME_POINTER_REGNUM
4633		   && (! reload_completed || frame_pointer_needed))
4634#if HARD_FRAME_POINTER_REGNUM != FRAME_POINTER_REGNUM
4635		&& ! (regno == HARD_FRAME_POINTER_REGNUM
4636		      && (! reload_completed || frame_pointer_needed))
4637#endif
4638#if ARG_POINTER_REGNUM != FRAME_POINTER_REGNUM
4639		&& ! (regno == ARG_POINTER_REGNUM && fixed_regs[regno])
4640#endif
4641		&& regno != STACK_POINTER_REGNUM)
4642	      {
4643		if (! all_needed && ! dead_or_set_p (insn, x))
4644		  {
4645		    /* Check for the case where the register dying partially
4646		       overlaps the register set by this insn.  */
4647		    if (regno < FIRST_PSEUDO_REGISTER
4648			&& HARD_REGNO_NREGS (regno, GET_MODE (x)) > 1)
4649		      {
4650			int n = HARD_REGNO_NREGS (regno, GET_MODE (x));
4651			while (--n >= 0)
4652			  some_needed |= dead_or_set_regno_p (insn, regno + n);
4653		      }
4654
4655		    /* If none of the words in X is needed, make a REG_DEAD
4656		       note.  Otherwise, we must make partial REG_DEAD
4657		       notes.  */
4658		    if (! some_needed)
4659		      create_reg_dead_note (x, insn);
4660		    else
4661		      {
4662			int i;
4663
4664			/* Don't make a REG_DEAD note for a part of a
4665			   register that is set in the insn.  */
4666			for (i = HARD_REGNO_NREGS (regno, GET_MODE (x)) - 1;
4667			     i >= 0; i--)
4668			  if (! REGNO_REG_SET_P (old_live_regs, regno+i)
4669			      && ! dead_or_set_regno_p (insn, regno + i))
4670			    create_reg_dead_note (gen_rtx_REG (reg_raw_mode[regno + i],
4671							       regno + i),
4672						  insn);
4673		      }
4674		  }
4675	      }
4676
4677	    if (regno < FIRST_PSEUDO_REGISTER)
4678	      {
4679		int j = HARD_REGNO_NREGS (regno, GET_MODE (x));
4680		while (--j >= 0)
4681		  {
4682		    SET_REGNO_REG_SET (bb_live_regs, regno + j);
4683		  }
4684	      }
4685	    else
4686	      {
4687		/* Recompute REG_BASIC_BLOCK as we update all the other
4688		   dataflow information.  */
4689		if (sched_reg_basic_block[regno] == REG_BLOCK_UNKNOWN)
4690		  sched_reg_basic_block[regno] = current_block_num;
4691		else if (sched_reg_basic_block[regno] != current_block_num)
4692		  sched_reg_basic_block[regno] = REG_BLOCK_GLOBAL;
4693
4694		SET_REGNO_REG_SET (bb_live_regs, regno);
4695	      }
4696	  }
4697	return;
4698      }
4699
4700    case MEM:
4701      /* Handle tail-recursive case.  */
4702      attach_deaths (XEXP (x, 0), insn, 0);
4703      return;
4704
4705    case SUBREG:
4706      attach_deaths (SUBREG_REG (x), insn,
4707		     set_p && ((GET_MODE_SIZE (GET_MODE (SUBREG_REG (x)))
4708				<= UNITS_PER_WORD)
4709			       || (GET_MODE_SIZE (GET_MODE (SUBREG_REG (x)))
4710				   == GET_MODE_SIZE (GET_MODE ((x))))));
4711      return;
4712
4713    case STRICT_LOW_PART:
4714      attach_deaths (XEXP (x, 0), insn, 0);
4715      return;
4716
4717    case ZERO_EXTRACT:
4718    case SIGN_EXTRACT:
4719      attach_deaths (XEXP (x, 0), insn, 0);
4720      attach_deaths (XEXP (x, 1), insn, 0);
4721      attach_deaths (XEXP (x, 2), insn, 0);
4722      return;
4723
4724    case PARALLEL:
4725      if (set_p
4726	  && GET_MODE (x) == BLKmode)
4727	{
4728	  for (i = XVECLEN (x, 0) - 1; i >= 0; i--)
4729	    attach_deaths (SET_DEST (XVECEXP (x, 0, i)), insn, 1);
4730	  return;
4731	}
4732
4733      /* fallthrough */
4734    default:
4735      /* Other cases: walk the insn.  */
4736      fmt = GET_RTX_FORMAT (code);
4737      for (i = GET_RTX_LENGTH (code) - 1; i >= 0; i--)
4738	{
4739	  if (fmt[i] == 'e')
4740	    attach_deaths (XEXP (x, i), insn, 0);
4741	  else if (fmt[i] == 'E')
4742	    for (j = 0; j < XVECLEN (x, i); j++)
4743	      attach_deaths (XVECEXP (x, i, j), insn, 0);
4744	}
4745    }
4746}
4747
4748/* After INSN has executed, add register death notes for each register
4749   that is dead after INSN.  */
4750
4751static void
4752attach_deaths_insn (insn)
4753     rtx insn;
4754{
4755  rtx x = PATTERN (insn);
4756  register RTX_CODE code = GET_CODE (x);
4757  rtx link;
4758
4759  if (code == SET)
4760    {
4761      attach_deaths (SET_SRC (x), insn, 0);
4762
4763      /* A register might die here even if it is the destination, e.g.
4764         it is the target of a volatile read and is otherwise unused.
4765         Hence we must always call attach_deaths for the SET_DEST.  */
4766      attach_deaths (SET_DEST (x), insn, 1);
4767    }
4768  else if (code == PARALLEL)
4769    {
4770      register int i;
4771      for (i = XVECLEN (x, 0) - 1; i >= 0; i--)
4772	{
4773	  code = GET_CODE (XVECEXP (x, 0, i));
4774	  if (code == SET)
4775	    {
4776	      attach_deaths (SET_SRC (XVECEXP (x, 0, i)), insn, 0);
4777
4778	      attach_deaths (SET_DEST (XVECEXP (x, 0, i)), insn, 1);
4779	    }
4780	  /* Flow does not add REG_DEAD notes to registers that die in
4781	     clobbers, so we can't either.  */
4782	  else if (code != CLOBBER)
4783	    attach_deaths (XVECEXP (x, 0, i), insn, 0);
4784	}
4785    }
4786  /* If this is a CLOBBER, only add REG_DEAD notes to registers inside a
4787     MEM being clobbered, just like flow.  */
4788  else if (code == CLOBBER && GET_CODE (XEXP (x, 0)) == MEM)
4789    attach_deaths (XEXP (XEXP (x, 0), 0), insn, 0);
4790  /* Otherwise don't add a death note to things being clobbered.  */
4791  else if (code != CLOBBER)
4792    attach_deaths (x, insn, 0);
4793
4794  /* Make death notes for things used in the called function.  */
4795  if (GET_CODE (insn) == CALL_INSN)
4796    for (link = CALL_INSN_FUNCTION_USAGE (insn); link; link = XEXP (link, 1))
4797      attach_deaths (XEXP (XEXP (link, 0), 0), insn,
4798		     GET_CODE (XEXP (link, 0)) == CLOBBER);
4799}
4800
4801/* functions for handlnig of notes */
4802
4803/* Delete notes beginning with INSN and put them in the chain
4804   of notes ended by NOTE_LIST.
4805   Returns the insn following the notes.  */
4806
4807static rtx
4808unlink_other_notes (insn, tail)
4809     rtx insn, tail;
4810{
4811  rtx prev = PREV_INSN (insn);
4812
4813  while (insn != tail && GET_CODE (insn) == NOTE)
4814    {
4815      rtx next = NEXT_INSN (insn);
4816      /* Delete the note from its current position.  */
4817      if (prev)
4818	NEXT_INSN (prev) = next;
4819      if (next)
4820	PREV_INSN (next) = prev;
4821
4822      /* Don't save away NOTE_INSN_SETJMPs, because they must remain
4823         immediately after the call they follow.  We use a fake
4824         (REG_DEAD (const_int -1)) note to remember them.
4825         Likewise with NOTE_INSN_{LOOP,EHREGION}_{BEG, END}.  */
4826      if (NOTE_LINE_NUMBER (insn) != NOTE_INSN_SETJMP
4827	  && NOTE_LINE_NUMBER (insn) != NOTE_INSN_LOOP_BEG
4828	  && NOTE_LINE_NUMBER (insn) != NOTE_INSN_LOOP_END
4829	  && NOTE_LINE_NUMBER (insn) != NOTE_INSN_RANGE_START
4830	  && NOTE_LINE_NUMBER (insn) != NOTE_INSN_RANGE_END
4831	  && NOTE_LINE_NUMBER (insn) != NOTE_INSN_EH_REGION_BEG
4832	  && NOTE_LINE_NUMBER (insn) != NOTE_INSN_EH_REGION_END)
4833	{
4834	  /* Insert the note at the end of the notes list.  */
4835	  PREV_INSN (insn) = note_list;
4836	  if (note_list)
4837	    NEXT_INSN (note_list) = insn;
4838	  note_list = insn;
4839	}
4840
4841      insn = next;
4842    }
4843  return insn;
4844}
4845
4846/* Delete line notes beginning with INSN. Record line-number notes so
4847   they can be reused.  Returns the insn following the notes.  */
4848
4849static rtx
4850unlink_line_notes (insn, tail)
4851     rtx insn, tail;
4852{
4853  rtx prev = PREV_INSN (insn);
4854
4855  while (insn != tail && GET_CODE (insn) == NOTE)
4856    {
4857      rtx next = NEXT_INSN (insn);
4858
4859      if (write_symbols != NO_DEBUG && NOTE_LINE_NUMBER (insn) > 0)
4860	{
4861	  /* Delete the note from its current position.  */
4862	  if (prev)
4863	    NEXT_INSN (prev) = next;
4864	  if (next)
4865	    PREV_INSN (next) = prev;
4866
4867	  /* Record line-number notes so they can be reused.  */
4868	  LINE_NOTE (insn) = insn;
4869	}
4870      else
4871	prev = insn;
4872
4873      insn = next;
4874    }
4875  return insn;
4876}
4877
4878/* Return the head and tail pointers of BB.  */
4879
4880HAIFA_INLINE static void
4881get_block_head_tail (bb, headp, tailp)
4882     int bb;
4883     rtx *headp;
4884     rtx *tailp;
4885{
4886
4887  rtx head;
4888  rtx tail;
4889  int b;
4890
4891  b = BB_TO_BLOCK (bb);
4892
4893  /* HEAD and TAIL delimit the basic block being scheduled.  */
4894  head = BLOCK_HEAD (b);
4895  tail = BLOCK_END (b);
4896
4897  /* Don't include any notes or labels at the beginning of the
4898     basic block, or notes at the ends of basic blocks.  */
4899  while (head != tail)
4900    {
4901      if (GET_CODE (head) == NOTE)
4902	head = NEXT_INSN (head);
4903      else if (GET_CODE (tail) == NOTE)
4904	tail = PREV_INSN (tail);
4905      else if (GET_CODE (head) == CODE_LABEL)
4906	head = NEXT_INSN (head);
4907      else
4908	break;
4909    }
4910
4911  *headp = head;
4912  *tailp = tail;
4913}
4914
4915/* Delete line notes from bb. Save them so they can be later restored
4916   (in restore_line_notes ()).  */
4917
4918static void
4919rm_line_notes (bb)
4920     int bb;
4921{
4922  rtx next_tail;
4923  rtx tail;
4924  rtx head;
4925  rtx insn;
4926
4927  get_block_head_tail (bb, &head, &tail);
4928
4929  if (head == tail
4930      && (GET_RTX_CLASS (GET_CODE (head)) != 'i'))
4931    return;
4932
4933  next_tail = NEXT_INSN (tail);
4934  for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
4935    {
4936      rtx prev;
4937
4938      /* Farm out notes, and maybe save them in NOTE_LIST.
4939         This is needed to keep the debugger from
4940         getting completely deranged.  */
4941      if (GET_CODE (insn) == NOTE)
4942	{
4943	  prev = insn;
4944	  insn = unlink_line_notes (insn, next_tail);
4945
4946	  if (prev == tail)
4947	    abort ();
4948	  if (prev == head)
4949	    abort ();
4950	  if (insn == next_tail)
4951	    abort ();
4952	}
4953    }
4954}
4955
4956/* Save line number notes for each insn in bb.  */
4957
4958static void
4959save_line_notes (bb)
4960     int bb;
4961{
4962  rtx head, tail;
4963  rtx next_tail;
4964
4965  /* We must use the true line number for the first insn in the block
4966     that was computed and saved at the start of this pass.  We can't
4967     use the current line number, because scheduling of the previous
4968     block may have changed the current line number.  */
4969
4970  rtx line = line_note_head[BB_TO_BLOCK (bb)];
4971  rtx insn;
4972
4973  get_block_head_tail (bb, &head, &tail);
4974  next_tail = NEXT_INSN (tail);
4975
4976  for (insn = BLOCK_HEAD (BB_TO_BLOCK (bb));
4977       insn != next_tail;
4978       insn = NEXT_INSN (insn))
4979    if (GET_CODE (insn) == NOTE && NOTE_LINE_NUMBER (insn) > 0)
4980      line = insn;
4981    else
4982      LINE_NOTE (insn) = line;
4983}
4984
4985
4986/* After bb was scheduled, insert line notes into the insns list.  */
4987
4988static void
4989restore_line_notes (bb)
4990     int bb;
4991{
4992  rtx line, note, prev, new;
4993  int added_notes = 0;
4994  int b;
4995  rtx head, next_tail, insn;
4996
4997  b = BB_TO_BLOCK (bb);
4998
4999  head = BLOCK_HEAD (b);
5000  next_tail = NEXT_INSN (BLOCK_END (b));
5001
5002  /* Determine the current line-number.  We want to know the current
5003     line number of the first insn of the block here, in case it is
5004     different from the true line number that was saved earlier.  If
5005     different, then we need a line number note before the first insn
5006     of this block.  If it happens to be the same, then we don't want to
5007     emit another line number note here.  */
5008  for (line = head; line; line = PREV_INSN (line))
5009    if (GET_CODE (line) == NOTE && NOTE_LINE_NUMBER (line) > 0)
5010      break;
5011
5012  /* Walk the insns keeping track of the current line-number and inserting
5013     the line-number notes as needed.  */
5014  for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
5015    if (GET_CODE (insn) == NOTE && NOTE_LINE_NUMBER (insn) > 0)
5016      line = insn;
5017  /* This used to emit line number notes before every non-deleted note.
5018     However, this confuses a debugger, because line notes not separated
5019     by real instructions all end up at the same address.  I can find no
5020     use for line number notes before other notes, so none are emitted.  */
5021    else if (GET_CODE (insn) != NOTE
5022	     && (note = LINE_NOTE (insn)) != 0
5023	     && note != line
5024	     && (line == 0
5025		 || NOTE_LINE_NUMBER (note) != NOTE_LINE_NUMBER (line)
5026		 || NOTE_SOURCE_FILE (note) != NOTE_SOURCE_FILE (line)))
5027      {
5028	line = note;
5029	prev = PREV_INSN (insn);
5030	if (LINE_NOTE (note))
5031	  {
5032	    /* Re-use the original line-number note.  */
5033	    LINE_NOTE (note) = 0;
5034	    PREV_INSN (note) = prev;
5035	    NEXT_INSN (prev) = note;
5036	    PREV_INSN (insn) = note;
5037	    NEXT_INSN (note) = insn;
5038	  }
5039	else
5040	  {
5041	    added_notes++;
5042	    new = emit_note_after (NOTE_LINE_NUMBER (note), prev);
5043	    NOTE_SOURCE_FILE (new) = NOTE_SOURCE_FILE (note);
5044	    RTX_INTEGRATED_P (new) = RTX_INTEGRATED_P (note);
5045	  }
5046      }
5047  if (sched_verbose && added_notes)
5048    fprintf (dump, ";; added %d line-number notes\n", added_notes);
5049}
5050
5051/* After scheduling the function, delete redundant line notes from the
5052   insns list.  */
5053
5054static void
5055rm_redundant_line_notes ()
5056{
5057  rtx line = 0;
5058  rtx insn = get_insns ();
5059  int active_insn = 0;
5060  int notes = 0;
5061
5062  /* Walk the insns deleting redundant line-number notes.  Many of these
5063     are already present.  The remainder tend to occur at basic
5064     block boundaries.  */
5065  for (insn = get_last_insn (); insn; insn = PREV_INSN (insn))
5066    if (GET_CODE (insn) == NOTE && NOTE_LINE_NUMBER (insn) > 0)
5067      {
5068	/* If there are no active insns following, INSN is redundant.  */
5069	if (active_insn == 0)
5070	  {
5071	    notes++;
5072	    NOTE_SOURCE_FILE (insn) = 0;
5073	    NOTE_LINE_NUMBER (insn) = NOTE_INSN_DELETED;
5074	  }
5075	/* If the line number is unchanged, LINE is redundant.  */
5076	else if (line
5077		 && NOTE_LINE_NUMBER (line) == NOTE_LINE_NUMBER (insn)
5078		 && NOTE_SOURCE_FILE (line) == NOTE_SOURCE_FILE (insn))
5079	  {
5080	    notes++;
5081	    NOTE_SOURCE_FILE (line) = 0;
5082	    NOTE_LINE_NUMBER (line) = NOTE_INSN_DELETED;
5083	    line = insn;
5084	  }
5085	else
5086	  line = insn;
5087	active_insn = 0;
5088      }
5089    else if (!((GET_CODE (insn) == NOTE
5090		&& NOTE_LINE_NUMBER (insn) == NOTE_INSN_DELETED)
5091	       || (GET_CODE (insn) == INSN
5092		   && (GET_CODE (PATTERN (insn)) == USE
5093		       || GET_CODE (PATTERN (insn)) == CLOBBER))))
5094      active_insn++;
5095
5096  if (sched_verbose && notes)
5097    fprintf (dump, ";; deleted %d line-number notes\n", notes);
5098}
5099
5100/* Delete notes between head and tail and put them in the chain
5101   of notes ended by NOTE_LIST.  */
5102
5103static void
5104rm_other_notes (head, tail)
5105     rtx head;
5106     rtx tail;
5107{
5108  rtx next_tail;
5109  rtx insn;
5110
5111  if (head == tail
5112      && (GET_RTX_CLASS (GET_CODE (head)) != 'i'))
5113    return;
5114
5115  next_tail = NEXT_INSN (tail);
5116  for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
5117    {
5118      rtx prev;
5119
5120      /* Farm out notes, and maybe save them in NOTE_LIST.
5121         This is needed to keep the debugger from
5122         getting completely deranged.  */
5123      if (GET_CODE (insn) == NOTE)
5124	{
5125	  prev = insn;
5126
5127	  insn = unlink_other_notes (insn, next_tail);
5128
5129	  if (prev == tail)
5130	    abort ();
5131	  if (prev == head)
5132	    abort ();
5133	  if (insn == next_tail)
5134	    abort ();
5135	}
5136    }
5137}
5138
5139/* Constructor for `sometimes' data structure.  */
5140
5141static int
5142new_sometimes_live (regs_sometimes_live, regno, sometimes_max)
5143     struct sometimes *regs_sometimes_live;
5144     int regno;
5145     int sometimes_max;
5146{
5147  register struct sometimes *p;
5148
5149  /* There should never be a register greater than max_regno here.  If there
5150     is, it means that a define_split has created a new pseudo reg.  This
5151     is not allowed, since there will not be flow info available for any
5152     new register, so catch the error here.  */
5153  if (regno >= max_regno)
5154    abort ();
5155
5156  p = &regs_sometimes_live[sometimes_max];
5157  p->regno = regno;
5158  p->live_length = 0;
5159  p->calls_crossed = 0;
5160  sometimes_max++;
5161  return sometimes_max;
5162}
5163
5164/* Count lengths of all regs we are currently tracking,
5165   and find new registers no longer live.  */
5166
5167static void
5168finish_sometimes_live (regs_sometimes_live, sometimes_max)
5169     struct sometimes *regs_sometimes_live;
5170     int sometimes_max;
5171{
5172  int i;
5173
5174  for (i = 0; i < sometimes_max; i++)
5175    {
5176      register struct sometimes *p = &regs_sometimes_live[i];
5177      int regno = p->regno;
5178
5179      sched_reg_live_length[regno] += p->live_length;
5180      sched_reg_n_calls_crossed[regno] += p->calls_crossed;
5181    }
5182}
5183
5184/* functions for computation of registers live/usage info */
5185
5186/* It is assumed that prior to scheduling BASIC_BLOCK (b)->global_live_at_start
5187   contains the registers that are alive at the entry to b.
5188
5189   Two passes follow: The first pass is performed before the scheduling
5190   of a region. It scans each block of the region forward, computing
5191   the set of registers alive at the end of the basic block and
5192   discard REG_DEAD notes (done by find_pre_sched_live ()).
5193
5194   The second path is invoked after scheduling all region blocks.
5195   It scans each block of the region backward, a block being traversed
5196   only after its succesors in the region. When the set of registers
5197   live at the end of a basic block may be changed by the scheduling
5198   (this may happen for multiple blocks region), it is computed as
5199   the union of the registers live at the start of its succesors.
5200   The last-use information is updated by inserting REG_DEAD notes.
5201   (done by find_post_sched_live ()) */
5202
5203/* Scan all the insns to be scheduled, removing register death notes.
5204   Register death notes end up in DEAD_NOTES.
5205   Recreate the register life information for the end of this basic
5206   block.  */
5207
5208static void
5209find_pre_sched_live (bb)
5210     int bb;
5211{
5212  rtx insn, next_tail, head, tail;
5213  int b = BB_TO_BLOCK (bb);
5214
5215  get_block_head_tail (bb, &head, &tail);
5216  COPY_REG_SET (bb_live_regs, BASIC_BLOCK (b)->global_live_at_start);
5217  next_tail = NEXT_INSN (tail);
5218
5219  for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
5220    {
5221      rtx prev, next, link;
5222      int reg_weight = 0;
5223
5224      /* Handle register life information.  */
5225      if (GET_RTX_CLASS (GET_CODE (insn)) == 'i')
5226	{
5227	  /* See if the register gets born here.  */
5228	  /* We must check for registers being born before we check for
5229	     registers dying.  It is possible for a register to be born and
5230	     die in the same insn, e.g. reading from a volatile memory
5231	     location into an otherwise unused register.  Such a register
5232	     must be marked as dead after this insn.  */
5233	  if (GET_CODE (PATTERN (insn)) == SET
5234	      || GET_CODE (PATTERN (insn)) == CLOBBER)
5235	    {
5236	      sched_note_set (PATTERN (insn), 0);
5237	      reg_weight++;
5238	    }
5239
5240	  else if (GET_CODE (PATTERN (insn)) == PARALLEL)
5241	    {
5242	      int j;
5243	      for (j = XVECLEN (PATTERN (insn), 0) - 1; j >= 0; j--)
5244		if (GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == SET
5245		    || GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == CLOBBER)
5246		  {
5247		    sched_note_set (XVECEXP (PATTERN (insn), 0, j), 0);
5248		    reg_weight++;
5249		  }
5250
5251	      /* ??? This code is obsolete and should be deleted.  It
5252	         is harmless though, so we will leave it in for now.  */
5253	      for (j = XVECLEN (PATTERN (insn), 0) - 1; j >= 0; j--)
5254		if (GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == USE)
5255		  sched_note_set (XVECEXP (PATTERN (insn), 0, j), 0);
5256	    }
5257
5258	  /* Each call cobbers (makes live) all call-clobbered regs
5259	     that are not global or fixed.  Note that the function-value
5260	     reg is a call_clobbered reg.  */
5261	  if (GET_CODE (insn) == CALL_INSN)
5262	    {
5263	      int j;
5264	      for (j = 0; j < FIRST_PSEUDO_REGISTER; j++)
5265		if (call_used_regs[j] && !global_regs[j]
5266		    && ! fixed_regs[j])
5267		  {
5268		    SET_REGNO_REG_SET (bb_live_regs, j);
5269		  }
5270	    }
5271
5272	  /* Need to know what registers this insn kills.  */
5273	  for (prev = 0, link = REG_NOTES (insn); link; link = next)
5274	    {
5275	      next = XEXP (link, 1);
5276	      if ((REG_NOTE_KIND (link) == REG_DEAD
5277		   || REG_NOTE_KIND (link) == REG_UNUSED)
5278	      /* Verify that the REG_NOTE has a valid value.  */
5279		  && GET_CODE (XEXP (link, 0)) == REG)
5280		{
5281		  register int regno = REGNO (XEXP (link, 0));
5282
5283		  reg_weight--;
5284
5285		  /* Only unlink REG_DEAD notes; leave REG_UNUSED notes
5286		     alone.  */
5287		  if (REG_NOTE_KIND (link) == REG_DEAD)
5288		    {
5289		      if (prev)
5290			XEXP (prev, 1) = next;
5291		      else
5292			REG_NOTES (insn) = next;
5293		      XEXP (link, 1) = dead_notes;
5294		      dead_notes = link;
5295		    }
5296		  else
5297		    prev = link;
5298
5299		  if (regno < FIRST_PSEUDO_REGISTER)
5300		    {
5301		      int j = HARD_REGNO_NREGS (regno,
5302						GET_MODE (XEXP (link, 0)));
5303		      while (--j >= 0)
5304			{
5305			  CLEAR_REGNO_REG_SET (bb_live_regs, regno+j);
5306			}
5307		    }
5308		  else
5309		    {
5310		      CLEAR_REGNO_REG_SET (bb_live_regs, regno);
5311		    }
5312		}
5313	      else
5314		prev = link;
5315	    }
5316	}
5317
5318      INSN_REG_WEIGHT (insn) = reg_weight;
5319    }
5320}
5321
5322/* Update register life and usage information for block bb
5323   after scheduling.  Put register dead notes back in the code.  */
5324
5325static void
5326find_post_sched_live (bb)
5327     int bb;
5328{
5329  int sometimes_max;
5330  int j, i;
5331  int b;
5332  rtx insn;
5333  rtx head, tail, prev_head, next_tail;
5334
5335  register struct sometimes *regs_sometimes_live;
5336
5337  b = BB_TO_BLOCK (bb);
5338
5339  /* compute live regs at the end of bb as a function of its successors.  */
5340  if (current_nr_blocks > 1)
5341    {
5342      int e;
5343      int first_edge;
5344
5345      first_edge = e = OUT_EDGES (b);
5346      CLEAR_REG_SET (bb_live_regs);
5347
5348      if (e)
5349	do
5350	  {
5351	    int b_succ;
5352
5353	    b_succ = TO_BLOCK (e);
5354	    IOR_REG_SET (bb_live_regs,
5355			 BASIC_BLOCK (b_succ)->global_live_at_start);
5356	    e = NEXT_OUT (e);
5357	  }
5358	while (e != first_edge);
5359    }
5360
5361  get_block_head_tail (bb, &head, &tail);
5362  next_tail = NEXT_INSN (tail);
5363  prev_head = PREV_INSN (head);
5364
5365  EXECUTE_IF_SET_IN_REG_SET (bb_live_regs, FIRST_PSEUDO_REGISTER, i,
5366			     {
5367			       sched_reg_basic_block[i] = REG_BLOCK_GLOBAL;
5368			     });
5369
5370  /* if the block is empty, same regs are alive at its end and its start.
5371     since this is not guaranteed after interblock scheduling, make sure they
5372     are truly identical.  */
5373  if (NEXT_INSN (prev_head) == tail
5374      && (GET_RTX_CLASS (GET_CODE (tail)) != 'i'))
5375    {
5376      if (current_nr_blocks > 1)
5377	COPY_REG_SET (BASIC_BLOCK (b)->global_live_at_start, bb_live_regs);
5378
5379      return;
5380    }
5381
5382  b = BB_TO_BLOCK (bb);
5383  current_block_num = b;
5384
5385  /* Keep track of register lives.  */
5386  old_live_regs = ALLOCA_REG_SET ();
5387  regs_sometimes_live
5388    = (struct sometimes *) alloca (max_regno * sizeof (struct sometimes));
5389  sometimes_max = 0;
5390
5391  /* initiate "sometimes" data, starting with registers live at end */
5392  sometimes_max = 0;
5393  COPY_REG_SET (old_live_regs, bb_live_regs);
5394  EXECUTE_IF_SET_IN_REG_SET (bb_live_regs, 0, j,
5395			     {
5396			       sometimes_max
5397				 = new_sometimes_live (regs_sometimes_live,
5398						       j, sometimes_max);
5399			     });
5400
5401  /* scan insns back, computing regs live info */
5402  for (insn = tail; insn != prev_head; insn = PREV_INSN (insn))
5403    {
5404      /* First we kill registers set by this insn, and then we
5405         make registers used by this insn live.  This is the opposite
5406         order used above because we are traversing the instructions
5407         backwards.  */
5408
5409      /* Strictly speaking, we should scan REG_UNUSED notes and make
5410         every register mentioned there live, however, we will just
5411         kill them again immediately below, so there doesn't seem to
5412         be any reason why we bother to do this.  */
5413
5414      /* See if this is the last notice we must take of a register.  */
5415      if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
5416	continue;
5417
5418      if (GET_CODE (PATTERN (insn)) == SET
5419	  || GET_CODE (PATTERN (insn)) == CLOBBER)
5420	sched_note_set (PATTERN (insn), 1);
5421      else if (GET_CODE (PATTERN (insn)) == PARALLEL)
5422	{
5423	  for (j = XVECLEN (PATTERN (insn), 0) - 1; j >= 0; j--)
5424	    if (GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == SET
5425		|| GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == CLOBBER)
5426	      sched_note_set (XVECEXP (PATTERN (insn), 0, j), 1);
5427	}
5428
5429      /* This code keeps life analysis information up to date.  */
5430      if (GET_CODE (insn) == CALL_INSN)
5431	{
5432	  register struct sometimes *p;
5433
5434	  /* A call kills all call used registers that are not
5435	     global or fixed, except for those mentioned in the call
5436	     pattern which will be made live again later.  */
5437	  for (i = 0; i < FIRST_PSEUDO_REGISTER; i++)
5438	    if (call_used_regs[i] && ! global_regs[i]
5439		&& ! fixed_regs[i])
5440	      {
5441		CLEAR_REGNO_REG_SET (bb_live_regs, i);
5442	      }
5443
5444	  /* Regs live at the time of a call instruction must not
5445	     go in a register clobbered by calls.  Record this for
5446	     all regs now live.  Note that insns which are born or
5447	     die in a call do not cross a call, so this must be done
5448	     after the killings (above) and before the births
5449	     (below).  */
5450	  p = regs_sometimes_live;
5451	  for (i = 0; i < sometimes_max; i++, p++)
5452	    if (REGNO_REG_SET_P (bb_live_regs, p->regno))
5453	      p->calls_crossed += 1;
5454	}
5455
5456      /* Make every register used live, and add REG_DEAD notes for
5457         registers which were not live before we started.  */
5458      attach_deaths_insn (insn);
5459
5460      /* Find registers now made live by that instruction.  */
5461      EXECUTE_IF_AND_COMPL_IN_REG_SET (bb_live_regs, old_live_regs, 0, j,
5462				 {
5463				   sometimes_max
5464				     = new_sometimes_live (regs_sometimes_live,
5465							   j, sometimes_max);
5466				 });
5467      IOR_REG_SET (old_live_regs, bb_live_regs);
5468
5469      /* Count lengths of all regs we are worrying about now,
5470         and handle registers no longer live.  */
5471
5472      for (i = 0; i < sometimes_max; i++)
5473	{
5474	  register struct sometimes *p = &regs_sometimes_live[i];
5475	  int regno = p->regno;
5476
5477	  p->live_length += 1;
5478
5479	  if (!REGNO_REG_SET_P (bb_live_regs, regno))
5480	    {
5481	      /* This is the end of one of this register's lifetime
5482	         segments.  Save the lifetime info collected so far,
5483	         and clear its bit in the old_live_regs entry.  */
5484	      sched_reg_live_length[regno] += p->live_length;
5485	      sched_reg_n_calls_crossed[regno] += p->calls_crossed;
5486	      CLEAR_REGNO_REG_SET (old_live_regs, p->regno);
5487
5488	      /* Delete the reg_sometimes_live entry for this reg by
5489	         copying the last entry over top of it.  */
5490	      *p = regs_sometimes_live[--sometimes_max];
5491	      /* ...and decrement i so that this newly copied entry
5492	         will be processed.  */
5493	      i--;
5494	    }
5495	}
5496    }
5497
5498  finish_sometimes_live (regs_sometimes_live, sometimes_max);
5499
5500  /* In interblock scheduling, global_live_at_start may have changed.  */
5501  if (current_nr_blocks > 1)
5502    COPY_REG_SET (BASIC_BLOCK (b)->global_live_at_start, bb_live_regs);
5503
5504
5505  FREE_REG_SET (old_live_regs);
5506}				/* find_post_sched_live */
5507
5508/* After scheduling the subroutine, restore information about uses of
5509   registers.  */
5510
5511static void
5512update_reg_usage ()
5513{
5514  int regno;
5515
5516  if (n_basic_blocks > 0)
5517    EXECUTE_IF_SET_IN_REG_SET (bb_live_regs, FIRST_PSEUDO_REGISTER, regno,
5518			       {
5519				 sched_reg_basic_block[regno]
5520				   = REG_BLOCK_GLOBAL;
5521			       });
5522
5523  for (regno = 0; regno < max_regno; regno++)
5524    if (sched_reg_live_length[regno])
5525      {
5526	if (sched_verbose)
5527	  {
5528	    if (REG_LIVE_LENGTH (regno) > sched_reg_live_length[regno])
5529	      fprintf (dump,
5530		       ";; register %d life shortened from %d to %d\n",
5531		       regno, REG_LIVE_LENGTH (regno),
5532		       sched_reg_live_length[regno]);
5533	    /* Negative values are special; don't overwrite the current
5534	       reg_live_length value if it is negative.  */
5535	    else if (REG_LIVE_LENGTH (regno) < sched_reg_live_length[regno]
5536		     && REG_LIVE_LENGTH (regno) >= 0)
5537	      fprintf (dump,
5538		       ";; register %d life extended from %d to %d\n",
5539		       regno, REG_LIVE_LENGTH (regno),
5540		       sched_reg_live_length[regno]);
5541
5542	    if (!REG_N_CALLS_CROSSED (regno)
5543		&& sched_reg_n_calls_crossed[regno])
5544	      fprintf (dump,
5545		       ";; register %d now crosses calls\n", regno);
5546	    else if (REG_N_CALLS_CROSSED (regno)
5547		     && !sched_reg_n_calls_crossed[regno]
5548		     && REG_BASIC_BLOCK (regno) != REG_BLOCK_GLOBAL)
5549	      fprintf (dump,
5550		       ";; register %d no longer crosses calls\n", regno);
5551
5552	    if (REG_BASIC_BLOCK (regno) != sched_reg_basic_block[regno]
5553		&& sched_reg_basic_block[regno] != REG_BLOCK_UNKNOWN
5554		&& REG_BASIC_BLOCK(regno) != REG_BLOCK_UNKNOWN)
5555	      fprintf (dump,
5556		       ";; register %d changed basic block from %d to %d\n",
5557			regno, REG_BASIC_BLOCK(regno),
5558			sched_reg_basic_block[regno]);
5559
5560	  }
5561	/* Negative values are special; don't overwrite the current
5562	   reg_live_length value if it is negative.  */
5563	if (REG_LIVE_LENGTH (regno) >= 0)
5564	  REG_LIVE_LENGTH (regno) = sched_reg_live_length[regno];
5565
5566	if (sched_reg_basic_block[regno] != REG_BLOCK_UNKNOWN
5567	    && REG_BASIC_BLOCK(regno) != REG_BLOCK_UNKNOWN)
5568	  REG_BASIC_BLOCK(regno) = sched_reg_basic_block[regno];
5569
5570	/* We can't change the value of reg_n_calls_crossed to zero for
5571	   pseudos which are live in more than one block.
5572
5573	   This is because combine might have made an optimization which
5574	   invalidated global_live_at_start and reg_n_calls_crossed,
5575	   but it does not update them.  If we update reg_n_calls_crossed
5576	   here, the two variables are now inconsistent, and this might
5577	   confuse the caller-save code into saving a register that doesn't
5578	   need to be saved.  This is only a problem when we zero calls
5579	   crossed for a pseudo live in multiple basic blocks.
5580
5581	   Alternatively, we could try to correctly update basic block live
5582	   at start here in sched, but that seems complicated.
5583
5584	   Note: it is possible that a global register became local, as result
5585	   of interblock motion, but will remain marked as a global register.  */
5586	if (sched_reg_n_calls_crossed[regno]
5587	    || REG_BASIC_BLOCK (regno) != REG_BLOCK_GLOBAL)
5588	  REG_N_CALLS_CROSSED (regno) = sched_reg_n_calls_crossed[regno];
5589
5590      }
5591}
5592
5593/* Scheduling clock, modified in schedule_block() and queue_to_ready () */
5594static int clock_var;
5595
5596/* Move insns that became ready to fire from queue to ready list.  */
5597
5598static int
5599queue_to_ready (ready, n_ready)
5600     rtx ready[];
5601     int n_ready;
5602{
5603  rtx insn;
5604  rtx link;
5605
5606  q_ptr = NEXT_Q (q_ptr);
5607
5608  /* Add all pending insns that can be scheduled without stalls to the
5609     ready list.  */
5610  for (link = insn_queue[q_ptr]; link; link = XEXP (link, 1))
5611    {
5612
5613      insn = XEXP (link, 0);
5614      q_size -= 1;
5615
5616      if (sched_verbose >= 2)
5617	fprintf (dump, ";;\t\tQ-->Ready: insn %d: ", INSN_UID (insn));
5618
5619      if (sched_verbose >= 2 && INSN_BB (insn) != target_bb)
5620	fprintf (dump, "(b%d) ", INSN_BLOCK (insn));
5621
5622      ready[n_ready++] = insn;
5623      if (sched_verbose >= 2)
5624	fprintf (dump, "moving to ready without stalls\n");
5625    }
5626  insn_queue[q_ptr] = 0;
5627
5628  /* If there are no ready insns, stall until one is ready and add all
5629     of the pending insns at that point to the ready list.  */
5630  if (n_ready == 0)
5631    {
5632      register int stalls;
5633
5634      for (stalls = 1; stalls < INSN_QUEUE_SIZE; stalls++)
5635	{
5636	  if ((link = insn_queue[NEXT_Q_AFTER (q_ptr, stalls)]))
5637	    {
5638	      for (; link; link = XEXP (link, 1))
5639		{
5640		  insn = XEXP (link, 0);
5641		  q_size -= 1;
5642
5643		  if (sched_verbose >= 2)
5644		    fprintf (dump, ";;\t\tQ-->Ready: insn %d: ", INSN_UID (insn));
5645
5646		  if (sched_verbose >= 2 && INSN_BB (insn) != target_bb)
5647		    fprintf (dump, "(b%d) ", INSN_BLOCK (insn));
5648
5649		  ready[n_ready++] = insn;
5650		  if (sched_verbose >= 2)
5651		    fprintf (dump, "moving to ready with %d stalls\n", stalls);
5652		}
5653	      insn_queue[NEXT_Q_AFTER (q_ptr, stalls)] = 0;
5654
5655	      if (n_ready)
5656		break;
5657	    }
5658	}
5659
5660      if (sched_verbose && stalls)
5661	visualize_stall_cycles (BB_TO_BLOCK (target_bb), stalls);
5662      q_ptr = NEXT_Q_AFTER (q_ptr, stalls);
5663      clock_var += stalls;
5664    }
5665  return n_ready;
5666}
5667
5668/* Print the ready list for debugging purposes. Callable from debugger.  */
5669
5670static void
5671debug_ready_list (ready, n_ready)
5672     rtx ready[];
5673     int n_ready;
5674{
5675  int i;
5676
5677  for (i = 0; i < n_ready; i++)
5678    {
5679      fprintf (dump, "  %d", INSN_UID (ready[i]));
5680      if (current_nr_blocks > 1 && INSN_BB (ready[i]) != target_bb)
5681	fprintf (dump, "/b%d", INSN_BLOCK (ready[i]));
5682    }
5683  fprintf (dump, "\n");
5684}
5685
5686/* Print names of units on which insn can/should execute, for debugging.  */
5687
5688static void
5689insn_print_units (insn)
5690     rtx insn;
5691{
5692  int i;
5693  int unit = insn_unit (insn);
5694
5695  if (unit == -1)
5696    fprintf (dump, "none");
5697  else if (unit >= 0)
5698    fprintf (dump, "%s", function_units[unit].name);
5699  else
5700    {
5701      fprintf (dump, "[");
5702      for (i = 0, unit = ~unit; unit; i++, unit >>= 1)
5703	if (unit & 1)
5704	  {
5705	    fprintf (dump, "%s", function_units[i].name);
5706	    if (unit != 1)
5707	      fprintf (dump, " ");
5708	  }
5709      fprintf (dump, "]");
5710    }
5711}
5712
5713/* MAX_VISUAL_LINES is the maximum number of lines in visualization table
5714   of a basic block.  If more lines are needed, table is splitted to two.
5715   n_visual_lines is the number of lines printed so far for a block.
5716   visual_tbl contains the block visualization info.
5717   vis_no_unit holds insns in a cycle that are not mapped to any unit.  */
5718#define MAX_VISUAL_LINES 100
5719#define INSN_LEN 30
5720int n_visual_lines;
5721char *visual_tbl;
5722int n_vis_no_unit;
5723rtx vis_no_unit[10];
5724
5725/* Finds units that are in use in this fuction. Required only
5726   for visualization.  */
5727
5728static void
5729init_target_units ()
5730{
5731  rtx insn;
5732  int unit;
5733
5734  for (insn = get_last_insn (); insn; insn = PREV_INSN (insn))
5735    {
5736      if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
5737	continue;
5738
5739      unit = insn_unit (insn);
5740
5741      if (unit < 0)
5742	target_units |= ~unit;
5743      else
5744	target_units |= (1 << unit);
5745    }
5746}
5747
5748/* Return the length of the visualization table */
5749
5750static int
5751get_visual_tbl_length ()
5752{
5753  int unit, i;
5754  int n, n1;
5755  char *s;
5756
5757  /* compute length of one field in line */
5758  s = (char *) alloca (INSN_LEN + 5);
5759  sprintf (s, "  %33s", "uname");
5760  n1 = strlen (s);
5761
5762  /* compute length of one line */
5763  n = strlen (";; ");
5764  n += n1;
5765  for (unit = 0; unit < FUNCTION_UNITS_SIZE; unit++)
5766    if (function_units[unit].bitmask & target_units)
5767      for (i = 0; i < function_units[unit].multiplicity; i++)
5768	n += n1;
5769  n += n1;
5770  n += strlen ("\n") + 2;
5771
5772  /* compute length of visualization string */
5773  return (MAX_VISUAL_LINES * n);
5774}
5775
5776/* Init block visualization debugging info */
5777
5778static void
5779init_block_visualization ()
5780{
5781  strcpy (visual_tbl, "");
5782  n_visual_lines = 0;
5783  n_vis_no_unit = 0;
5784}
5785
5786#define BUF_LEN 256
5787
5788static char *
5789safe_concat (buf, cur, str)
5790     char *buf;
5791     char *cur;
5792     char *str;
5793{
5794  char *end = buf + BUF_LEN - 2;	/* leave room for null */
5795  int c;
5796
5797  if (cur > end)
5798    {
5799      *end = '\0';
5800      return end;
5801    }
5802
5803  while (cur < end && (c = *str++) != '\0')
5804    *cur++ = c;
5805
5806  *cur = '\0';
5807  return cur;
5808}
5809
5810/* This recognizes rtx, I classified as expressions. These are always */
5811/* represent some action on values or results of other expression, */
5812/* that may be stored in objects representing values.  */
5813
5814static void
5815print_exp (buf, x, verbose)
5816     char *buf;
5817     rtx x;
5818     int verbose;
5819{
5820  char tmp[BUF_LEN];
5821  char *st[4];
5822  char *cur = buf;
5823  char *fun = (char *)0;
5824  char *sep;
5825  rtx op[4];
5826  int i;
5827
5828  for (i = 0; i < 4; i++)
5829    {
5830      st[i] = (char *)0;
5831      op[i] = NULL_RTX;
5832    }
5833
5834  switch (GET_CODE (x))
5835    {
5836    case PLUS:
5837      op[0] = XEXP (x, 0);
5838      if (GET_CODE (XEXP (x, 1)) == CONST_INT
5839	  && INTVAL (XEXP (x, 1)) < 0)
5840	{
5841	  st[1] = "-";
5842	  op[1] = GEN_INT (-INTVAL (XEXP (x, 1)));
5843	}
5844      else
5845	{
5846	  st[1] = "+";
5847	  op[1] = XEXP (x, 1);
5848	}
5849      break;
5850    case LO_SUM:
5851      op[0] = XEXP (x, 0);
5852      st[1] = "+low(";
5853      op[1] = XEXP (x, 1);
5854      st[2] = ")";
5855      break;
5856    case MINUS:
5857      op[0] = XEXP (x, 0);
5858      st[1] = "-";
5859      op[1] = XEXP (x, 1);
5860      break;
5861    case COMPARE:
5862      fun = "cmp";
5863      op[0] = XEXP (x, 0);
5864      op[1] = XEXP (x, 1);
5865      break;
5866    case NEG:
5867      st[0] = "-";
5868      op[0] = XEXP (x, 0);
5869      break;
5870    case MULT:
5871      op[0] = XEXP (x, 0);
5872      st[1] = "*";
5873      op[1] = XEXP (x, 1);
5874      break;
5875    case DIV:
5876      op[0] = XEXP (x, 0);
5877      st[1] = "/";
5878      op[1] = XEXP (x, 1);
5879      break;
5880    case UDIV:
5881      fun = "udiv";
5882      op[0] = XEXP (x, 0);
5883      op[1] = XEXP (x, 1);
5884      break;
5885    case MOD:
5886      op[0] = XEXP (x, 0);
5887      st[1] = "%";
5888      op[1] = XEXP (x, 1);
5889      break;
5890    case UMOD:
5891      fun = "umod";
5892      op[0] = XEXP (x, 0);
5893      op[1] = XEXP (x, 1);
5894      break;
5895    case SMIN:
5896      fun = "smin";
5897      op[0] = XEXP (x, 0);
5898      op[1] = XEXP (x, 1);
5899      break;
5900    case SMAX:
5901      fun = "smax";
5902      op[0] = XEXP (x, 0);
5903      op[1] = XEXP (x, 1);
5904      break;
5905    case UMIN:
5906      fun = "umin";
5907      op[0] = XEXP (x, 0);
5908      op[1] = XEXP (x, 1);
5909      break;
5910    case UMAX:
5911      fun = "umax";
5912      op[0] = XEXP (x, 0);
5913      op[1] = XEXP (x, 1);
5914      break;
5915    case NOT:
5916      st[0] = "!";
5917      op[0] = XEXP (x, 0);
5918      break;
5919    case AND:
5920      op[0] = XEXP (x, 0);
5921      st[1] = "&";
5922      op[1] = XEXP (x, 1);
5923      break;
5924    case IOR:
5925      op[0] = XEXP (x, 0);
5926      st[1] = "|";
5927      op[1] = XEXP (x, 1);
5928      break;
5929    case XOR:
5930      op[0] = XEXP (x, 0);
5931      st[1] = "^";
5932      op[1] = XEXP (x, 1);
5933      break;
5934    case ASHIFT:
5935      op[0] = XEXP (x, 0);
5936      st[1] = "<<";
5937      op[1] = XEXP (x, 1);
5938      break;
5939    case LSHIFTRT:
5940      op[0] = XEXP (x, 0);
5941      st[1] = " 0>>";
5942      op[1] = XEXP (x, 1);
5943      break;
5944    case ASHIFTRT:
5945      op[0] = XEXP (x, 0);
5946      st[1] = ">>";
5947      op[1] = XEXP (x, 1);
5948      break;
5949    case ROTATE:
5950      op[0] = XEXP (x, 0);
5951      st[1] = "<-<";
5952      op[1] = XEXP (x, 1);
5953      break;
5954    case ROTATERT:
5955      op[0] = XEXP (x, 0);
5956      st[1] = ">->";
5957      op[1] = XEXP (x, 1);
5958      break;
5959    case ABS:
5960      fun = "abs";
5961      op[0] = XEXP (x, 0);
5962      break;
5963    case SQRT:
5964      fun = "sqrt";
5965      op[0] = XEXP (x, 0);
5966      break;
5967    case FFS:
5968      fun = "ffs";
5969      op[0] = XEXP (x, 0);
5970      break;
5971    case EQ:
5972      op[0] = XEXP (x, 0);
5973      st[1] = "==";
5974      op[1] = XEXP (x, 1);
5975      break;
5976    case NE:
5977      op[0] = XEXP (x, 0);
5978      st[1] = "!=";
5979      op[1] = XEXP (x, 1);
5980      break;
5981    case GT:
5982      op[0] = XEXP (x, 0);
5983      st[1] = ">";
5984      op[1] = XEXP (x, 1);
5985      break;
5986    case GTU:
5987      fun = "gtu";
5988      op[0] = XEXP (x, 0);
5989      op[1] = XEXP (x, 1);
5990      break;
5991    case LT:
5992      op[0] = XEXP (x, 0);
5993      st[1] = "<";
5994      op[1] = XEXP (x, 1);
5995      break;
5996    case LTU:
5997      fun = "ltu";
5998      op[0] = XEXP (x, 0);
5999      op[1] = XEXP (x, 1);
6000      break;
6001    case GE:
6002      op[0] = XEXP (x, 0);
6003      st[1] = ">=";
6004      op[1] = XEXP (x, 1);
6005      break;
6006    case GEU:
6007      fun = "geu";
6008      op[0] = XEXP (x, 0);
6009      op[1] = XEXP (x, 1);
6010      break;
6011    case LE:
6012      op[0] = XEXP (x, 0);
6013      st[1] = "<=";
6014      op[1] = XEXP (x, 1);
6015      break;
6016    case LEU:
6017      fun = "leu";
6018      op[0] = XEXP (x, 0);
6019      op[1] = XEXP (x, 1);
6020      break;
6021    case SIGN_EXTRACT:
6022      fun = (verbose) ? "sign_extract" : "sxt";
6023      op[0] = XEXP (x, 0);
6024      op[1] = XEXP (x, 1);
6025      op[2] = XEXP (x, 2);
6026      break;
6027    case ZERO_EXTRACT:
6028      fun = (verbose) ? "zero_extract" : "zxt";
6029      op[0] = XEXP (x, 0);
6030      op[1] = XEXP (x, 1);
6031      op[2] = XEXP (x, 2);
6032      break;
6033    case SIGN_EXTEND:
6034      fun = (verbose) ? "sign_extend" : "sxn";
6035      op[0] = XEXP (x, 0);
6036      break;
6037    case ZERO_EXTEND:
6038      fun = (verbose) ? "zero_extend" : "zxn";
6039      op[0] = XEXP (x, 0);
6040      break;
6041    case FLOAT_EXTEND:
6042      fun = (verbose) ? "float_extend" : "fxn";
6043      op[0] = XEXP (x, 0);
6044      break;
6045    case TRUNCATE:
6046      fun = (verbose) ? "trunc" : "trn";
6047      op[0] = XEXP (x, 0);
6048      break;
6049    case FLOAT_TRUNCATE:
6050      fun = (verbose) ? "float_trunc" : "ftr";
6051      op[0] = XEXP (x, 0);
6052      break;
6053    case FLOAT:
6054      fun = (verbose) ? "float" : "flt";
6055      op[0] = XEXP (x, 0);
6056      break;
6057    case UNSIGNED_FLOAT:
6058      fun = (verbose) ? "uns_float" : "ufl";
6059      op[0] = XEXP (x, 0);
6060      break;
6061    case FIX:
6062      fun = "fix";
6063      op[0] = XEXP (x, 0);
6064      break;
6065    case UNSIGNED_FIX:
6066      fun = (verbose) ? "uns_fix" : "ufx";
6067      op[0] = XEXP (x, 0);
6068      break;
6069    case PRE_DEC:
6070      st[0] = "--";
6071      op[0] = XEXP (x, 0);
6072      break;
6073    case PRE_INC:
6074      st[0] = "++";
6075      op[0] = XEXP (x, 0);
6076      break;
6077    case POST_DEC:
6078      op[0] = XEXP (x, 0);
6079      st[1] = "--";
6080      break;
6081    case POST_INC:
6082      op[0] = XEXP (x, 0);
6083      st[1] = "++";
6084      break;
6085    case CALL:
6086      st[0] = "call ";
6087      op[0] = XEXP (x, 0);
6088      if (verbose)
6089	{
6090	  st[1] = " argc:";
6091	  op[1] = XEXP (x, 1);
6092	}
6093      break;
6094    case IF_THEN_ELSE:
6095      st[0] = "{(";
6096      op[0] = XEXP (x, 0);
6097      st[1] = ")?";
6098      op[1] = XEXP (x, 1);
6099      st[2] = ":";
6100      op[2] = XEXP (x, 2);
6101      st[3] = "}";
6102      break;
6103    case TRAP_IF:
6104      fun = "trap_if";
6105      op[0] = TRAP_CONDITION (x);
6106      break;
6107    case UNSPEC:
6108    case UNSPEC_VOLATILE:
6109      {
6110	cur = safe_concat (buf, cur, "unspec");
6111	if (GET_CODE (x) == UNSPEC_VOLATILE)
6112	  cur = safe_concat (buf, cur, "/v");
6113	cur = safe_concat (buf, cur, "[");
6114	sep = "";
6115	for (i = 0; i < XVECLEN (x, 0); i++)
6116	  {
6117	    print_pattern (tmp, XVECEXP (x, 0, i), verbose);
6118	    cur = safe_concat (buf, cur, sep);
6119	    cur = safe_concat (buf, cur, tmp);
6120	    sep = ",";
6121	  }
6122	cur = safe_concat (buf, cur, "] ");
6123	sprintf (tmp, "%d", XINT (x, 1));
6124	cur = safe_concat (buf, cur, tmp);
6125      }
6126      break;
6127    default:
6128      /* if (verbose) debug_rtx (x); */
6129      st[0] = GET_RTX_NAME (GET_CODE (x));
6130      break;
6131    }
6132
6133  /* Print this as a function? */
6134  if (fun)
6135    {
6136      cur = safe_concat (buf, cur, fun);
6137      cur = safe_concat (buf, cur, "(");
6138    }
6139
6140  for (i = 0; i < 4; i++)
6141    {
6142      if (st[i])
6143	cur = safe_concat (buf, cur, st[i]);
6144
6145      if (op[i])
6146	{
6147	  if (fun && i != 0)
6148	    cur = safe_concat (buf, cur, ",");
6149
6150	  print_value (tmp, op[i], verbose);
6151	  cur = safe_concat (buf, cur, tmp);
6152	}
6153    }
6154
6155  if (fun)
6156    cur = safe_concat (buf, cur, ")");
6157}		/* print_exp */
6158
6159/* Prints rtxes, i customly classified as values. They're constants, */
6160/* registers, labels, symbols and memory accesses.  */
6161
6162static void
6163print_value (buf, x, verbose)
6164     char *buf;
6165     rtx x;
6166     int verbose;
6167{
6168  char t[BUF_LEN];
6169  char *cur = buf;
6170
6171  switch (GET_CODE (x))
6172    {
6173    case CONST_INT:
6174      sprintf (t, HOST_WIDE_INT_PRINT_HEX, INTVAL (x));
6175      cur = safe_concat (buf, cur, t);
6176      break;
6177    case CONST_DOUBLE:
6178      sprintf (t, "<0x%lx,0x%lx>", (long)XWINT (x, 2), (long)XWINT (x, 3));
6179      cur = safe_concat (buf, cur, t);
6180      break;
6181    case CONST_STRING:
6182      cur = safe_concat (buf, cur, "\"");
6183      cur = safe_concat (buf, cur, XSTR (x, 0));
6184      cur = safe_concat (buf, cur, "\"");
6185      break;
6186    case SYMBOL_REF:
6187      cur = safe_concat (buf, cur, "`");
6188      cur = safe_concat (buf, cur, XSTR (x, 0));
6189      cur = safe_concat (buf, cur, "'");
6190      break;
6191    case LABEL_REF:
6192      sprintf (t, "L%d", INSN_UID (XEXP (x, 0)));
6193      cur = safe_concat (buf, cur, t);
6194      break;
6195    case CONST:
6196      print_value (t, XEXP (x, 0), verbose);
6197      cur = safe_concat (buf, cur, "const(");
6198      cur = safe_concat (buf, cur, t);
6199      cur = safe_concat (buf, cur, ")");
6200      break;
6201    case HIGH:
6202      print_value (t, XEXP (x, 0), verbose);
6203      cur = safe_concat (buf, cur, "high(");
6204      cur = safe_concat (buf, cur, t);
6205      cur = safe_concat (buf, cur, ")");
6206      break;
6207    case REG:
6208      if (REGNO (x) < FIRST_PSEUDO_REGISTER)
6209	{
6210	  int c = reg_names[ REGNO (x) ][0];
6211	  if (c >= '0' && c <= '9')
6212	    cur = safe_concat (buf, cur, "%");
6213
6214	  cur = safe_concat (buf, cur, reg_names[ REGNO (x) ]);
6215	}
6216      else
6217	{
6218	  sprintf (t, "r%d", REGNO (x));
6219	  cur = safe_concat (buf, cur, t);
6220	}
6221      break;
6222    case SUBREG:
6223      print_value (t, SUBREG_REG (x), verbose);
6224      cur = safe_concat (buf, cur, t);
6225      sprintf (t, "#%d", SUBREG_WORD (x));
6226      cur = safe_concat (buf, cur, t);
6227      break;
6228    case SCRATCH:
6229      cur = safe_concat (buf, cur, "scratch");
6230      break;
6231    case CC0:
6232      cur = safe_concat (buf, cur, "cc0");
6233      break;
6234    case PC:
6235      cur = safe_concat (buf, cur, "pc");
6236      break;
6237    case MEM:
6238      print_value (t, XEXP (x, 0), verbose);
6239      cur = safe_concat (buf, cur, "[");
6240      cur = safe_concat (buf, cur, t);
6241      cur = safe_concat (buf, cur, "]");
6242      break;
6243    default:
6244      print_exp (t, x, verbose);
6245      cur = safe_concat (buf, cur, t);
6246      break;
6247    }
6248}				/* print_value */
6249
6250/* The next step in insn detalization, its pattern recognition */
6251
6252static void
6253print_pattern (buf, x, verbose)
6254     char *buf;
6255     rtx x;
6256     int verbose;
6257{
6258  char t1[BUF_LEN], t2[BUF_LEN], t3[BUF_LEN];
6259
6260  switch (GET_CODE (x))
6261    {
6262    case SET:
6263      print_value (t1, SET_DEST (x), verbose);
6264      print_value (t2, SET_SRC (x), verbose);
6265      sprintf (buf, "%s=%s", t1, t2);
6266      break;
6267    case RETURN:
6268      sprintf (buf, "return");
6269      break;
6270    case CALL:
6271      print_exp (buf, x, verbose);
6272      break;
6273    case CLOBBER:
6274      print_value (t1, XEXP (x, 0), verbose);
6275      sprintf (buf, "clobber %s", t1);
6276      break;
6277    case USE:
6278      print_value (t1, XEXP (x, 0), verbose);
6279      sprintf (buf, "use %s", t1);
6280      break;
6281    case PARALLEL:
6282      {
6283	int i;
6284
6285	sprintf (t1, "{");
6286	for (i = 0; i < XVECLEN (x, 0); i++)
6287	  {
6288	    print_pattern (t2, XVECEXP (x, 0, i), verbose);
6289	    sprintf (t3, "%s%s;", t1, t2);
6290	    strcpy (t1, t3);
6291	  }
6292	sprintf (buf, "%s}", t1);
6293      }
6294      break;
6295    case SEQUENCE:
6296      {
6297	int i;
6298
6299	sprintf (t1, "%%{");
6300	for (i = 0; i < XVECLEN (x, 0); i++)
6301	  {
6302	    print_insn (t2, XVECEXP (x, 0, i), verbose);
6303	    sprintf (t3, "%s%s;", t1, t2);
6304	    strcpy (t1, t3);
6305	  }
6306	sprintf (buf, "%s%%}", t1);
6307      }
6308      break;
6309    case ASM_INPUT:
6310      sprintf (buf, "asm {%s}", XSTR (x, 0));
6311      break;
6312    case ADDR_VEC:
6313      break;
6314    case ADDR_DIFF_VEC:
6315      print_value (buf, XEXP (x, 0), verbose);
6316      break;
6317    case TRAP_IF:
6318      print_value (t1, TRAP_CONDITION (x), verbose);
6319      sprintf (buf, "trap_if %s", t1);
6320      break;
6321    case UNSPEC:
6322      {
6323	int i;
6324
6325	sprintf (t1, "unspec{");
6326	for (i = 0; i < XVECLEN (x, 0); i++)
6327	  {
6328	    print_pattern (t2, XVECEXP (x, 0, i), verbose);
6329	    sprintf (t3, "%s%s;", t1, t2);
6330	    strcpy (t1, t3);
6331	  }
6332	sprintf (buf, "%s}", t1);
6333      }
6334      break;
6335    case UNSPEC_VOLATILE:
6336      {
6337	int i;
6338
6339	sprintf (t1, "unspec/v{");
6340	for (i = 0; i < XVECLEN (x, 0); i++)
6341	  {
6342	    print_pattern (t2, XVECEXP (x, 0, i), verbose);
6343	    sprintf (t3, "%s%s;", t1, t2);
6344	    strcpy (t1, t3);
6345	  }
6346	sprintf (buf, "%s}", t1);
6347      }
6348      break;
6349    default:
6350      print_value (buf, x, verbose);
6351    }
6352}				/* print_pattern */
6353
6354/* This is the main function in rtl visualization mechanism. It
6355   accepts an rtx and tries to recognize it as an insn, then prints it
6356   properly in human readable form, resembling assembler mnemonics.  */
6357/* For every insn it prints its UID and BB the insn belongs */
6358/* too. (probably the last "option" should be extended somehow, since */
6359/* it depends now on sched.c inner variables ...) */
6360
6361static void
6362print_insn (buf, x, verbose)
6363     char *buf;
6364     rtx x;
6365     int verbose;
6366{
6367  char t[BUF_LEN];
6368  rtx insn = x;
6369
6370  switch (GET_CODE (x))
6371    {
6372    case INSN:
6373      print_pattern (t, PATTERN (x), verbose);
6374      if (verbose)
6375	sprintf (buf, "b%d: i% 4d: %s", INSN_BB (x),
6376		 INSN_UID (x), t);
6377      else
6378	sprintf (buf, "%-4d %s", INSN_UID (x), t);
6379      break;
6380    case JUMP_INSN:
6381      print_pattern (t, PATTERN (x), verbose);
6382      if (verbose)
6383	sprintf (buf, "b%d: i% 4d: jump %s", INSN_BB (x),
6384		 INSN_UID (x), t);
6385      else
6386	sprintf (buf, "%-4d %s", INSN_UID (x), t);
6387      break;
6388    case CALL_INSN:
6389      x = PATTERN (insn);
6390      if (GET_CODE (x) == PARALLEL)
6391	{
6392	  x = XVECEXP (x, 0, 0);
6393	  print_pattern (t, x, verbose);
6394	}
6395      else
6396	strcpy (t, "call <...>");
6397      if (verbose)
6398	sprintf (buf, "b%d: i% 4d: %s", INSN_BB (insn),
6399		 INSN_UID (insn), t);
6400      else
6401	sprintf (buf, "%-4d %s", INSN_UID (insn), t);
6402      break;
6403    case CODE_LABEL:
6404      sprintf (buf, "L%d:", INSN_UID (x));
6405      break;
6406    case BARRIER:
6407      sprintf (buf, "i% 4d: barrier", INSN_UID (x));
6408      break;
6409    case NOTE:
6410      if (NOTE_LINE_NUMBER (x) > 0)
6411	sprintf (buf, "%4d note \"%s\" %d", INSN_UID (x),
6412		 NOTE_SOURCE_FILE (x), NOTE_LINE_NUMBER (x));
6413      else
6414	sprintf (buf, "%4d %s", INSN_UID (x),
6415		 GET_NOTE_INSN_NAME (NOTE_LINE_NUMBER (x)));
6416      break;
6417    default:
6418      if (verbose)
6419	{
6420	  sprintf (buf, "Not an INSN at all\n");
6421	  debug_rtx (x);
6422	}
6423      else
6424	sprintf (buf, "i%-4d  <What?>", INSN_UID (x));
6425    }
6426}				/* print_insn */
6427
6428/* Print visualization debugging info */
6429
6430static void
6431print_block_visualization (b, s)
6432     int b;
6433     char *s;
6434{
6435  int unit, i;
6436
6437  /* print header */
6438  fprintf (dump, "\n;;   ==================== scheduling visualization for block %d %s \n", b, s);
6439
6440  /* Print names of units */
6441  fprintf (dump, ";;   %-8s", "clock");
6442  for (unit = 0; unit < FUNCTION_UNITS_SIZE; unit++)
6443    if (function_units[unit].bitmask & target_units)
6444      for (i = 0; i < function_units[unit].multiplicity; i++)
6445	fprintf (dump, "  %-33s", function_units[unit].name);
6446  fprintf (dump, "  %-8s\n", "no-unit");
6447
6448  fprintf (dump, ";;   %-8s", "=====");
6449  for (unit = 0; unit < FUNCTION_UNITS_SIZE; unit++)
6450    if (function_units[unit].bitmask & target_units)
6451      for (i = 0; i < function_units[unit].multiplicity; i++)
6452	fprintf (dump, "  %-33s", "==============================");
6453  fprintf (dump, "  %-8s\n", "=======");
6454
6455  /* Print insns in each cycle */
6456  fprintf (dump, "%s\n", visual_tbl);
6457}
6458
6459/* Print insns in the 'no_unit' column of visualization */
6460
6461static void
6462visualize_no_unit (insn)
6463     rtx insn;
6464{
6465  vis_no_unit[n_vis_no_unit] = insn;
6466  n_vis_no_unit++;
6467}
6468
6469/* Print insns scheduled in clock, for visualization.  */
6470
6471static void
6472visualize_scheduled_insns (b, clock)
6473     int b, clock;
6474{
6475  int i, unit;
6476
6477  /* if no more room, split table into two */
6478  if (n_visual_lines >= MAX_VISUAL_LINES)
6479    {
6480      print_block_visualization (b, "(incomplete)");
6481      init_block_visualization ();
6482    }
6483
6484  n_visual_lines++;
6485
6486  sprintf (visual_tbl + strlen (visual_tbl), ";;   %-8d", clock);
6487  for (unit = 0; unit < FUNCTION_UNITS_SIZE; unit++)
6488    if (function_units[unit].bitmask & target_units)
6489      for (i = 0; i < function_units[unit].multiplicity; i++)
6490	{
6491	  int instance = unit + i * FUNCTION_UNITS_SIZE;
6492	  rtx insn = unit_last_insn[instance];
6493
6494	  /* print insns that still keep the unit busy */
6495	  if (insn &&
6496	      actual_hazard_this_instance (unit, instance, insn, clock, 0))
6497	    {
6498	      char str[BUF_LEN];
6499	      print_insn (str, insn, 0);
6500	      str[INSN_LEN] = '\0';
6501	      sprintf (visual_tbl + strlen (visual_tbl), "  %-33s", str);
6502	    }
6503	  else
6504	    sprintf (visual_tbl + strlen (visual_tbl), "  %-33s", "------------------------------");
6505	}
6506
6507  /* print insns that are not assigned to any unit */
6508  for (i = 0; i < n_vis_no_unit; i++)
6509    sprintf (visual_tbl + strlen (visual_tbl), "  %-8d",
6510	     INSN_UID (vis_no_unit[i]));
6511  n_vis_no_unit = 0;
6512
6513  sprintf (visual_tbl + strlen (visual_tbl), "\n");
6514}
6515
6516/* Print stalled cycles */
6517
6518static void
6519visualize_stall_cycles (b, stalls)
6520     int b, stalls;
6521{
6522  int i;
6523
6524  /* if no more room, split table into two */
6525  if (n_visual_lines >= MAX_VISUAL_LINES)
6526    {
6527      print_block_visualization (b, "(incomplete)");
6528      init_block_visualization ();
6529    }
6530
6531  n_visual_lines++;
6532
6533  sprintf (visual_tbl + strlen (visual_tbl), ";;       ");
6534  for (i = 0; i < stalls; i++)
6535    sprintf (visual_tbl + strlen (visual_tbl), ".");
6536  sprintf (visual_tbl + strlen (visual_tbl), "\n");
6537}
6538
6539/* move_insn1: Remove INSN from insn chain, and link it after LAST insn */
6540
6541static rtx
6542move_insn1 (insn, last)
6543     rtx insn, last;
6544{
6545  NEXT_INSN (PREV_INSN (insn)) = NEXT_INSN (insn);
6546  PREV_INSN (NEXT_INSN (insn)) = PREV_INSN (insn);
6547
6548  NEXT_INSN (insn) = NEXT_INSN (last);
6549  PREV_INSN (NEXT_INSN (last)) = insn;
6550
6551  NEXT_INSN (last) = insn;
6552  PREV_INSN (insn) = last;
6553
6554  return insn;
6555}
6556
6557/* Search INSN for fake REG_DEAD note pairs for NOTE_INSN_SETJMP,
6558   NOTE_INSN_{LOOP,EHREGION}_{BEG,END}; and convert them back into
6559   NOTEs.  The REG_DEAD note following first one is contains the saved
6560   value for NOTE_BLOCK_NUMBER which is useful for
6561   NOTE_INSN_EH_REGION_{BEG,END} NOTEs.  LAST is the last instruction
6562   output by the instruction scheduler.  Return the new value of LAST.  */
6563
6564static rtx
6565reemit_notes (insn, last)
6566     rtx insn;
6567     rtx last;
6568{
6569  rtx note, retval;
6570
6571  retval = last;
6572  for (note = REG_NOTES (insn); note; note = XEXP (note, 1))
6573    {
6574      if (REG_NOTE_KIND (note) == REG_DEAD
6575	  && GET_CODE (XEXP (note, 0)) == CONST_INT)
6576	{
6577	  int note_type = INTVAL (XEXP (note, 0));
6578	  if (note_type == NOTE_INSN_SETJMP)
6579	    {
6580	      retval = emit_note_after (NOTE_INSN_SETJMP, insn);
6581	      CONST_CALL_P (retval) = CONST_CALL_P (note);
6582	      remove_note (insn, note);
6583	      note = XEXP (note, 1);
6584	    }
6585	  else if (note_type == NOTE_INSN_RANGE_START
6586                   || note_type == NOTE_INSN_RANGE_END)
6587	    {
6588	      last = emit_note_before (note_type, last);
6589	      remove_note (insn, note);
6590	      note = XEXP (note, 1);
6591	      NOTE_RANGE_INFO (last) = XEXP (note, 0);
6592	    }
6593	  else
6594	    {
6595	      last = emit_note_before (INTVAL (XEXP (note, 0)), last);
6596	      remove_note (insn, note);
6597	      note = XEXP (note, 1);
6598	      NOTE_BLOCK_NUMBER (last) = INTVAL (XEXP (note, 0));
6599	    }
6600	  remove_note (insn, note);
6601	}
6602    }
6603  return retval;
6604}
6605
6606/* Move INSN, and all insns which should be issued before it,
6607   due to SCHED_GROUP_P flag.  Reemit notes if needed.
6608
6609   Return the last insn emitted by the scheduler, which is the
6610   return value from the first call to reemit_notes.  */
6611
6612static rtx
6613move_insn (insn, last)
6614     rtx insn, last;
6615{
6616  rtx retval = NULL;
6617
6618  /* If INSN has SCHED_GROUP_P set, then issue it and any other
6619     insns with SCHED_GROUP_P set first.  */
6620  while (SCHED_GROUP_P (insn))
6621    {
6622      rtx prev = PREV_INSN (insn);
6623
6624      /* Move a SCHED_GROUP_P insn.  */
6625      move_insn1 (insn, last);
6626      /* If this is the first call to reemit_notes, then record
6627	 its return value.  */
6628      if (retval == NULL_RTX)
6629	retval = reemit_notes (insn, insn);
6630      else
6631	reemit_notes (insn, insn);
6632      insn = prev;
6633    }
6634
6635  /* Now move the first non SCHED_GROUP_P insn.  */
6636  move_insn1 (insn, last);
6637
6638  /* If this is the first call to reemit_notes, then record
6639     its return value.  */
6640  if (retval == NULL_RTX)
6641    retval = reemit_notes (insn, insn);
6642  else
6643    reemit_notes (insn, insn);
6644
6645  return retval;
6646}
6647
6648/* Return an insn which represents a SCHED_GROUP, which is
6649   the last insn in the group.  */
6650
6651static rtx
6652group_leader (insn)
6653     rtx insn;
6654{
6655  rtx prev;
6656
6657  do
6658    {
6659      prev = insn;
6660      insn = next_nonnote_insn (insn);
6661    }
6662  while (insn && SCHED_GROUP_P (insn) && (GET_CODE (insn) != CODE_LABEL));
6663
6664  return prev;
6665}
6666
6667/* Use forward list scheduling to rearrange insns of block BB in region RGN,
6668   possibly bringing insns from subsequent blocks in the same region.
6669   Return number of insns scheduled.  */
6670
6671static int
6672schedule_block (bb, rgn_n_insns)
6673     int bb;
6674     int rgn_n_insns;
6675{
6676  /* Local variables.  */
6677  rtx insn, last;
6678  rtx *ready;
6679  int i;
6680  int n_ready = 0;
6681  int can_issue_more;
6682
6683  /* flow block of this bb */
6684  int b = BB_TO_BLOCK (bb);
6685
6686  /* target_n_insns == number of insns in b before scheduling starts.
6687     sched_target_n_insns == how many of b's insns were scheduled.
6688     sched_n_insns == how many insns were scheduled in b */
6689  int target_n_insns = 0;
6690  int sched_target_n_insns = 0;
6691  int sched_n_insns = 0;
6692
6693#define NEED_NOTHING	0
6694#define NEED_HEAD	1
6695#define NEED_TAIL	2
6696  int new_needs;
6697
6698  /* head/tail info for this block */
6699  rtx prev_head;
6700  rtx next_tail;
6701  rtx head;
6702  rtx tail;
6703  int bb_src;
6704
6705  /* We used to have code to avoid getting parameters moved from hard
6706     argument registers into pseudos.
6707
6708     However, it was removed when it proved to be of marginal benefit
6709     and caused problems because schedule_block and compute_forward_dependences
6710     had different notions of what the "head" insn was.  */
6711  get_block_head_tail (bb, &head, &tail);
6712
6713  /* Interblock scheduling could have moved the original head insn from this
6714     block into a proceeding block.  This may also cause schedule_block and
6715     compute_forward_dependences to have different notions of what the
6716     "head" insn was.
6717
6718     If the interblock movement happened to make this block start with
6719     some notes (LOOP, EH or SETJMP) before the first real insn, then
6720     HEAD will have various special notes attached to it which must be
6721     removed so that we don't end up with extra copies of the notes.  */
6722  if (GET_RTX_CLASS (GET_CODE (head)) == 'i')
6723    {
6724      rtx note;
6725
6726      for (note = REG_NOTES (head); note; note = XEXP (note, 1))
6727	if (REG_NOTE_KIND (note) == REG_DEAD
6728	    && GET_CODE (XEXP (note, 0)) == CONST_INT)
6729	  remove_note (head, note);
6730    }
6731
6732  next_tail = NEXT_INSN (tail);
6733  prev_head = PREV_INSN (head);
6734
6735  /* If the only insn left is a NOTE or a CODE_LABEL, then there is no need
6736     to schedule this block.  */
6737  if (head == tail
6738      && (GET_RTX_CLASS (GET_CODE (head)) != 'i'))
6739    return (sched_n_insns);
6740
6741  /* debug info */
6742  if (sched_verbose)
6743    {
6744      fprintf (dump, ";;   ======================================================\n");
6745      fprintf (dump,
6746	       ";;   -- basic block %d from %d to %d -- %s reload\n",
6747	       b, INSN_UID (BLOCK_HEAD (b)), INSN_UID (BLOCK_END (b)),
6748	       (reload_completed ? "after" : "before"));
6749      fprintf (dump, ";;   ======================================================\n");
6750      fprintf (dump, "\n");
6751
6752      visual_tbl = (char *) alloca (get_visual_tbl_length ());
6753      init_block_visualization ();
6754    }
6755
6756  /* remove remaining note insns from the block, save them in
6757     note_list.  These notes are restored at the end of
6758     schedule_block ().  */
6759  note_list = 0;
6760  rm_other_notes (head, tail);
6761
6762  target_bb = bb;
6763
6764  /* prepare current target block info */
6765  if (current_nr_blocks > 1)
6766    {
6767      candidate_table = (candidate *) alloca (current_nr_blocks * sizeof (candidate));
6768
6769      bblst_last = 0;
6770      /* ??? It is not clear why bblst_size is computed this way.  The original
6771	 number was clearly too small as it resulted in compiler failures.
6772	 Multiplying by the original number by 2 (to account for update_bbs
6773	 members) seems to be a reasonable solution.  */
6774      /* ??? Or perhaps there is a bug somewhere else in this file?  */
6775      bblst_size = (current_nr_blocks - bb) * rgn_nr_edges * 2;
6776      bblst_table = (int *) alloca (bblst_size * sizeof (int));
6777
6778      bitlst_table_last = 0;
6779      bitlst_table_size = rgn_nr_edges;
6780      bitlst_table = (int *) alloca (rgn_nr_edges * sizeof (int));
6781
6782      compute_trg_info (bb);
6783    }
6784
6785  clear_units ();
6786
6787  /* Allocate the ready list */
6788  ready = (rtx *) alloca ((rgn_n_insns + 1) * sizeof (rtx));
6789
6790  /* Print debugging information.  */
6791  if (sched_verbose >= 5)
6792    debug_dependencies ();
6793
6794
6795  /* Initialize ready list with all 'ready' insns in target block.
6796     Count number of insns in the target block being scheduled.  */
6797  n_ready = 0;
6798  for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
6799    {
6800      rtx next;
6801
6802      if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
6803	continue;
6804      next = NEXT_INSN (insn);
6805
6806      if (INSN_DEP_COUNT (insn) == 0
6807	  && (SCHED_GROUP_P (next) == 0 || GET_RTX_CLASS (GET_CODE (next)) != 'i'))
6808	ready[n_ready++] = insn;
6809      if (!(SCHED_GROUP_P (insn)))
6810	target_n_insns++;
6811    }
6812
6813  /* Add to ready list all 'ready' insns in valid source blocks.
6814     For speculative insns, check-live, exception-free, and
6815     issue-delay.  */
6816  for (bb_src = bb + 1; bb_src < current_nr_blocks; bb_src++)
6817    if (IS_VALID (bb_src))
6818      {
6819	rtx src_head;
6820	rtx src_next_tail;
6821	rtx tail, head;
6822
6823	get_block_head_tail (bb_src, &head, &tail);
6824	src_next_tail = NEXT_INSN (tail);
6825	src_head = head;
6826
6827	if (head == tail
6828	    && (GET_RTX_CLASS (GET_CODE (head)) != 'i'))
6829	  continue;
6830
6831	for (insn = src_head; insn != src_next_tail; insn = NEXT_INSN (insn))
6832	  {
6833	    if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
6834	      continue;
6835
6836	    if (!CANT_MOVE (insn)
6837		&& (!IS_SPECULATIVE_INSN (insn)
6838		    || (insn_issue_delay (insn) <= 3
6839			&& check_live (insn, bb_src)
6840			&& is_exception_free (insn, bb_src, target_bb))))
6841
6842	      {
6843		rtx next;
6844
6845		next = NEXT_INSN (insn);
6846		if (INSN_DEP_COUNT (insn) == 0
6847		    && (SCHED_GROUP_P (next) == 0
6848			|| GET_RTX_CLASS (GET_CODE (next)) != 'i'))
6849		  ready[n_ready++] = insn;
6850	      }
6851	  }
6852      }
6853
6854#ifdef MD_SCHED_INIT
6855  MD_SCHED_INIT (dump, sched_verbose);
6856#endif
6857
6858  /* no insns scheduled in this block yet */
6859  last_scheduled_insn = 0;
6860
6861  /* Sort the ready list */
6862  SCHED_SORT (ready, n_ready);
6863#ifdef MD_SCHED_REORDER
6864  MD_SCHED_REORDER (dump, sched_verbose, ready, n_ready);
6865#endif
6866
6867  if (sched_verbose >= 2)
6868    {
6869      fprintf (dump, ";;\t\tReady list initially:             ");
6870      debug_ready_list (ready, n_ready);
6871    }
6872
6873  /* Q_SIZE is the total number of insns in the queue.  */
6874  q_ptr = 0;
6875  q_size = 0;
6876  clock_var = 0;
6877  last_clock_var = 0;
6878  bzero ((char *) insn_queue, sizeof (insn_queue));
6879
6880  /* We start inserting insns after PREV_HEAD.  */
6881  last = prev_head;
6882
6883  /* Initialize INSN_QUEUE, LIST and NEW_NEEDS.  */
6884  new_needs = (NEXT_INSN (prev_head) == BLOCK_HEAD (b)
6885	       ? NEED_HEAD : NEED_NOTHING);
6886  if (PREV_INSN (next_tail) == BLOCK_END (b))
6887    new_needs |= NEED_TAIL;
6888
6889  /* loop until all the insns in BB are scheduled.  */
6890  while (sched_target_n_insns < target_n_insns)
6891    {
6892      int b1;
6893
6894      clock_var++;
6895
6896      /* Add to the ready list all pending insns that can be issued now.
6897         If there are no ready insns, increment clock until one
6898         is ready and add all pending insns at that point to the ready
6899         list.  */
6900      n_ready = queue_to_ready (ready, n_ready);
6901
6902      if (n_ready == 0)
6903	abort ();
6904
6905      if (sched_verbose >= 2)
6906	{
6907	  fprintf (dump, ";;\t\tReady list after queue_to_ready:  ");
6908	  debug_ready_list (ready, n_ready);
6909	}
6910
6911      /* Sort the ready list.  */
6912      SCHED_SORT (ready, n_ready);
6913#ifdef MD_SCHED_REORDER
6914      MD_SCHED_REORDER (dump, sched_verbose, ready, n_ready);
6915#endif
6916
6917      if (sched_verbose)
6918	{
6919	  fprintf (dump, "\n;;\tReady list (t =%3d):  ", clock_var);
6920	  debug_ready_list (ready, n_ready);
6921	}
6922
6923      /* Issue insns from ready list.
6924         It is important to count down from n_ready, because n_ready may change
6925         as insns are issued.  */
6926      can_issue_more = issue_rate;
6927      for (i = n_ready - 1; i >= 0 && can_issue_more; i--)
6928	{
6929	  rtx insn = ready[i];
6930	  int cost = actual_hazard (insn_unit (insn), insn, clock_var, 0);
6931
6932	  if (cost > 1)
6933	    {
6934	      queue_insn (insn, cost);
6935	      ready[i] = ready[--n_ready];	/* remove insn from ready list */
6936	    }
6937	  else if (cost == 0)
6938	    {
6939	      /* an interblock motion? */
6940	      if (INSN_BB (insn) != target_bb)
6941		{
6942		  rtx temp;
6943
6944		  if (IS_SPECULATIVE_INSN (insn))
6945		    {
6946
6947		      if (!check_live (insn, INSN_BB (insn)))
6948			{
6949			  /* speculative motion, live check failed, remove
6950			     insn from ready list */
6951			  ready[i] = ready[--n_ready];
6952			  continue;
6953			}
6954		      update_live (insn, INSN_BB (insn));
6955
6956		      /* for speculative load, mark insns fed by it.  */
6957		      if (IS_LOAD_INSN (insn) || FED_BY_SPEC_LOAD (insn))
6958			set_spec_fed (insn);
6959
6960		      nr_spec++;
6961		    }
6962		  nr_inter++;
6963
6964		  temp = insn;
6965		  while (SCHED_GROUP_P (temp))
6966		    temp = PREV_INSN (temp);
6967
6968		  /* Update source block boundaries.   */
6969		  b1 = INSN_BLOCK (temp);
6970		  if (temp == BLOCK_HEAD (b1)
6971		      && insn == BLOCK_END (b1))
6972		    {
6973		      /* We moved all the insns in the basic block.
6974			 Emit a note after the last insn and update the
6975			 begin/end boundaries to point to the note.  */
6976		      emit_note_after (NOTE_INSN_DELETED, insn);
6977		      BLOCK_END (b1) = NEXT_INSN (insn);
6978		      BLOCK_HEAD (b1) = NEXT_INSN (insn);
6979		    }
6980		  else if (insn == BLOCK_END (b1))
6981		    {
6982		      /* We took insns from the end of the basic block,
6983			 so update the end of block boundary so that it
6984			 points to the first insn we did not move.  */
6985		      BLOCK_END (b1) = PREV_INSN (temp);
6986		    }
6987		  else if (temp == BLOCK_HEAD (b1))
6988		    {
6989		      /* We took insns from the start of the basic block,
6990			 so update the start of block boundary so that
6991			 it points to the first insn we did not move.  */
6992		      BLOCK_HEAD (b1) = NEXT_INSN (insn);
6993		    }
6994		}
6995	      else
6996		{
6997		  /* in block motion */
6998		  sched_target_n_insns++;
6999		}
7000
7001	      last_scheduled_insn = insn;
7002	      last = move_insn (insn, last);
7003	      sched_n_insns++;
7004
7005#ifdef MD_SCHED_VARIABLE_ISSUE
7006	      MD_SCHED_VARIABLE_ISSUE (dump, sched_verbose, insn, can_issue_more);
7007#else
7008	      can_issue_more--;
7009#endif
7010
7011	      n_ready = schedule_insn (insn, ready, n_ready, clock_var);
7012
7013	      /* remove insn from ready list */
7014	      ready[i] = ready[--n_ready];
7015
7016	      /* close this block after scheduling its jump */
7017	      if (GET_CODE (last_scheduled_insn) == JUMP_INSN)
7018		break;
7019	    }
7020	}
7021
7022      /* debug info */
7023      if (sched_verbose)
7024	{
7025	  visualize_scheduled_insns (b, clock_var);
7026	}
7027    }
7028
7029  /* debug info */
7030  if (sched_verbose)
7031    {
7032      fprintf (dump, ";;\tReady list (final):  ");
7033      debug_ready_list (ready, n_ready);
7034      print_block_visualization (b, "");
7035    }
7036
7037  /* Sanity check -- queue must be empty now.  Meaningless if region has
7038     multiple bbs.  */
7039  if (current_nr_blocks > 1)
7040    if (!flag_schedule_interblock && q_size != 0)
7041      abort ();
7042
7043  /* update head/tail boundaries.  */
7044  head = NEXT_INSN (prev_head);
7045  tail = last;
7046
7047  /* Restore-other-notes: NOTE_LIST is the end of a chain of notes
7048     previously found among the insns.  Insert them at the beginning
7049     of the insns.  */
7050  if (note_list != 0)
7051    {
7052      rtx note_head = note_list;
7053
7054      while (PREV_INSN (note_head))
7055	{
7056	  note_head = PREV_INSN (note_head);
7057	}
7058
7059      PREV_INSN (note_head) = PREV_INSN (head);
7060      NEXT_INSN (PREV_INSN (head)) = note_head;
7061      PREV_INSN (head) = note_list;
7062      NEXT_INSN (note_list) = head;
7063      head = note_head;
7064    }
7065
7066  /* update target block boundaries.  */
7067  if (new_needs & NEED_HEAD)
7068    BLOCK_HEAD (b) = head;
7069
7070  if (new_needs & NEED_TAIL)
7071    BLOCK_END (b) = tail;
7072
7073  /* debugging */
7074  if (sched_verbose)
7075    {
7076      fprintf (dump, ";;   total time = %d\n;;   new basic block head = %d\n",
7077	       clock_var, INSN_UID (BLOCK_HEAD (b)));
7078      fprintf (dump, ";;   new basic block end = %d\n\n",
7079	       INSN_UID (BLOCK_END (b)));
7080    }
7081
7082  return (sched_n_insns);
7083}				/* schedule_block () */
7084
7085
7086/* print the bit-set of registers, S.  callable from debugger */
7087
7088extern void
7089debug_reg_vector (s)
7090     regset s;
7091{
7092  int regno;
7093
7094  EXECUTE_IF_SET_IN_REG_SET (s, 0, regno,
7095			     {
7096			       fprintf (dump, " %d", regno);
7097			     });
7098
7099  fprintf (dump, "\n");
7100}
7101
7102/* Use the backward dependences from LOG_LINKS to build
7103   forward dependences in INSN_DEPEND.  */
7104
7105static void
7106compute_block_forward_dependences (bb)
7107     int bb;
7108{
7109  rtx insn, link;
7110  rtx tail, head;
7111  rtx next_tail;
7112  enum reg_note dep_type;
7113
7114  get_block_head_tail (bb, &head, &tail);
7115  next_tail = NEXT_INSN (tail);
7116  for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
7117    {
7118      if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
7119	continue;
7120
7121      insn = group_leader (insn);
7122
7123      for (link = LOG_LINKS (insn); link; link = XEXP (link, 1))
7124	{
7125	  rtx x = group_leader (XEXP (link, 0));
7126	  rtx new_link;
7127
7128	  if (x != XEXP (link, 0))
7129	    continue;
7130
7131	  /* Ignore dependences upon deleted insn */
7132	  if (GET_CODE (x) == NOTE || INSN_DELETED_P (x))
7133	    continue;
7134	  if (find_insn_list (insn, INSN_DEPEND (x)))
7135	    continue;
7136
7137	  new_link = alloc_INSN_LIST (insn, INSN_DEPEND (x));
7138
7139	  dep_type = REG_NOTE_KIND (link);
7140	  PUT_REG_NOTE_KIND (new_link, dep_type);
7141
7142	  INSN_DEPEND (x) = new_link;
7143	  INSN_DEP_COUNT (insn) += 1;
7144	}
7145    }
7146}
7147
7148/* Initialize variables for region data dependence analysis.
7149   n_bbs is the number of region blocks */
7150
7151__inline static void
7152init_rgn_data_dependences (n_bbs)
7153     int n_bbs;
7154{
7155  int bb;
7156
7157  /* variables for which one copy exists for each block */
7158  bzero ((char *) bb_pending_read_insns, n_bbs * sizeof (rtx));
7159  bzero ((char *) bb_pending_read_mems, n_bbs * sizeof (rtx));
7160  bzero ((char *) bb_pending_write_insns, n_bbs * sizeof (rtx));
7161  bzero ((char *) bb_pending_write_mems, n_bbs * sizeof (rtx));
7162  bzero ((char *) bb_pending_lists_length, n_bbs * sizeof (rtx));
7163  bzero ((char *) bb_last_pending_memory_flush, n_bbs * sizeof (rtx));
7164  bzero ((char *) bb_last_function_call, n_bbs * sizeof (rtx));
7165  bzero ((char *) bb_sched_before_next_call, n_bbs * sizeof (rtx));
7166
7167  /* Create an insn here so that we can hang dependencies off of it later.  */
7168  for (bb = 0; bb < n_bbs; bb++)
7169    {
7170      bb_sched_before_next_call[bb] =
7171	gen_rtx_INSN (VOIDmode, 0, NULL_RTX, NULL_RTX,
7172		      NULL_RTX, 0, NULL_RTX, NULL_RTX);
7173      LOG_LINKS (bb_sched_before_next_call[bb]) = 0;
7174    }
7175}
7176
7177/* Add dependences so that branches are scheduled to run last in their block */
7178
7179static void
7180add_branch_dependences (head, tail)
7181     rtx head, tail;
7182{
7183
7184  rtx insn, last;
7185
7186  /* For all branches, calls, uses, and cc0 setters, force them to remain
7187     in order at the end of the block by adding dependencies and giving
7188     the last a high priority.  There may be notes present, and prev_head
7189     may also be a note.
7190
7191     Branches must obviously remain at the end.  Calls should remain at the
7192     end since moving them results in worse register allocation.  Uses remain
7193     at the end to ensure proper register allocation.  cc0 setters remaim
7194     at the end because they can't be moved away from their cc0 user.  */
7195  insn = tail;
7196  last = 0;
7197  while (GET_CODE (insn) == CALL_INSN || GET_CODE (insn) == JUMP_INSN
7198	 || (GET_CODE (insn) == INSN
7199	     && (GET_CODE (PATTERN (insn)) == USE
7200#ifdef HAVE_cc0
7201		 || sets_cc0_p (PATTERN (insn))
7202#endif
7203	     ))
7204	 || GET_CODE (insn) == NOTE)
7205    {
7206      if (GET_CODE (insn) != NOTE)
7207	{
7208	  if (last != 0
7209	      && !find_insn_list (insn, LOG_LINKS (last)))
7210	    {
7211	      add_dependence (last, insn, REG_DEP_ANTI);
7212	      INSN_REF_COUNT (insn)++;
7213	    }
7214
7215	  CANT_MOVE (insn) = 1;
7216
7217	  last = insn;
7218	  /* Skip over insns that are part of a group.
7219	     Make each insn explicitly depend on the previous insn.
7220	     This ensures that only the group header will ever enter
7221	     the ready queue (and, when scheduled, will automatically
7222	     schedule the SCHED_GROUP_P block).  */
7223	  while (SCHED_GROUP_P (insn))
7224	    {
7225	      rtx temp = prev_nonnote_insn (insn);
7226	      add_dependence (insn, temp, REG_DEP_ANTI);
7227	      insn = temp;
7228	    }
7229	}
7230
7231      /* Don't overrun the bounds of the basic block.  */
7232      if (insn == head)
7233	break;
7234
7235      insn = PREV_INSN (insn);
7236    }
7237
7238  /* make sure these insns are scheduled last in their block */
7239  insn = last;
7240  if (insn != 0)
7241    while (insn != head)
7242      {
7243	insn = prev_nonnote_insn (insn);
7244
7245	if (INSN_REF_COUNT (insn) != 0)
7246	  continue;
7247
7248	if (!find_insn_list (last, LOG_LINKS (insn)))
7249	  add_dependence (last, insn, REG_DEP_ANTI);
7250	INSN_REF_COUNT (insn) = 1;
7251
7252	/* Skip over insns that are part of a group.  */
7253	while (SCHED_GROUP_P (insn))
7254	  insn = prev_nonnote_insn (insn);
7255      }
7256}
7257
7258/* Compute bacward dependences inside BB.  In a multiple blocks region:
7259   (1) a bb is analyzed after its predecessors, and (2) the lists in
7260   effect at the end of bb (after analyzing for bb) are inherited by
7261   bb's successrs.
7262
7263   Specifically for reg-reg data dependences, the block insns are
7264   scanned by sched_analyze () top-to-bottom.  Two lists are
7265   naintained by sched_analyze (): reg_last_defs[] for register DEFs,
7266   and reg_last_uses[] for register USEs.
7267
7268   When analysis is completed for bb, we update for its successors:
7269   ;  - DEFS[succ] = Union (DEFS [succ], DEFS [bb])
7270   ;  - USES[succ] = Union (USES [succ], DEFS [bb])
7271
7272   The mechanism for computing mem-mem data dependence is very
7273   similar, and the result is interblock dependences in the region.  */
7274
7275static void
7276compute_block_backward_dependences (bb)
7277     int bb;
7278{
7279  int b;
7280  rtx x;
7281  rtx head, tail;
7282  int max_reg = max_reg_num ();
7283
7284  b = BB_TO_BLOCK (bb);
7285
7286  if (current_nr_blocks == 1)
7287    {
7288      reg_last_uses = (rtx *) alloca (max_reg * sizeof (rtx));
7289      reg_last_sets = (rtx *) alloca (max_reg * sizeof (rtx));
7290      reg_last_clobbers = (rtx *) alloca (max_reg * sizeof (rtx));
7291
7292      bzero ((char *) reg_last_uses, max_reg * sizeof (rtx));
7293      bzero ((char *) reg_last_sets, max_reg * sizeof (rtx));
7294      bzero ((char *) reg_last_clobbers, max_reg * sizeof (rtx));
7295
7296      pending_read_insns = 0;
7297      pending_read_mems = 0;
7298      pending_write_insns = 0;
7299      pending_write_mems = 0;
7300      pending_lists_length = 0;
7301      last_function_call = 0;
7302      last_pending_memory_flush = 0;
7303      sched_before_next_call
7304	= gen_rtx_INSN (VOIDmode, 0, NULL_RTX, NULL_RTX,
7305			NULL_RTX, 0, NULL_RTX, NULL_RTX);
7306      LOG_LINKS (sched_before_next_call) = 0;
7307    }
7308  else
7309    {
7310      reg_last_uses = bb_reg_last_uses[bb];
7311      reg_last_sets = bb_reg_last_sets[bb];
7312      reg_last_clobbers = bb_reg_last_clobbers[bb];
7313
7314      pending_read_insns = bb_pending_read_insns[bb];
7315      pending_read_mems = bb_pending_read_mems[bb];
7316      pending_write_insns = bb_pending_write_insns[bb];
7317      pending_write_mems = bb_pending_write_mems[bb];
7318      pending_lists_length = bb_pending_lists_length[bb];
7319      last_function_call = bb_last_function_call[bb];
7320      last_pending_memory_flush = bb_last_pending_memory_flush[bb];
7321
7322      sched_before_next_call = bb_sched_before_next_call[bb];
7323    }
7324
7325  /* do the analysis for this block */
7326  get_block_head_tail (bb, &head, &tail);
7327  sched_analyze (head, tail);
7328  add_branch_dependences (head, tail);
7329
7330  if (current_nr_blocks > 1)
7331    {
7332      int e, first_edge;
7333      int b_succ, bb_succ;
7334      int reg;
7335      rtx link_insn, link_mem;
7336      rtx u;
7337
7338      /* these lists should point to the right place, for correct freeing later.  */
7339      bb_pending_read_insns[bb] = pending_read_insns;
7340      bb_pending_read_mems[bb] = pending_read_mems;
7341      bb_pending_write_insns[bb] = pending_write_insns;
7342      bb_pending_write_mems[bb] = pending_write_mems;
7343
7344      /* bb's structures are inherited by it's successors */
7345      first_edge = e = OUT_EDGES (b);
7346      if (e > 0)
7347	do
7348	  {
7349	    b_succ = TO_BLOCK (e);
7350	    bb_succ = BLOCK_TO_BB (b_succ);
7351
7352	    /* only bbs "below" bb, in the same region, are interesting */
7353	    if (CONTAINING_RGN (b) != CONTAINING_RGN (b_succ)
7354		|| bb_succ <= bb)
7355	      {
7356		e = NEXT_OUT (e);
7357		continue;
7358	      }
7359
7360	    for (reg = 0; reg < max_reg; reg++)
7361	      {
7362
7363		/* reg-last-uses lists are inherited by bb_succ */
7364		for (u = reg_last_uses[reg]; u; u = XEXP (u, 1))
7365		  {
7366		    if (find_insn_list (XEXP (u, 0), (bb_reg_last_uses[bb_succ])[reg]))
7367		      continue;
7368
7369		    (bb_reg_last_uses[bb_succ])[reg]
7370		      = alloc_INSN_LIST (XEXP (u, 0),
7371					 (bb_reg_last_uses[bb_succ])[reg]);
7372		  }
7373
7374		/* reg-last-defs lists are inherited by bb_succ */
7375		for (u = reg_last_sets[reg]; u; u = XEXP (u, 1))
7376		  {
7377		    if (find_insn_list (XEXP (u, 0), (bb_reg_last_sets[bb_succ])[reg]))
7378		      continue;
7379
7380		    (bb_reg_last_sets[bb_succ])[reg]
7381		      = alloc_INSN_LIST (XEXP (u, 0),
7382					 (bb_reg_last_sets[bb_succ])[reg]);
7383		  }
7384
7385		for (u = reg_last_clobbers[reg]; u; u = XEXP (u, 1))
7386		  {
7387		    if (find_insn_list (XEXP (u, 0), (bb_reg_last_clobbers[bb_succ])[reg]))
7388		      continue;
7389
7390		    (bb_reg_last_clobbers[bb_succ])[reg]
7391		      = alloc_INSN_LIST (XEXP (u, 0),
7392					 (bb_reg_last_clobbers[bb_succ])[reg]);
7393		  }
7394	      }
7395
7396	    /* mem read/write lists are inherited by bb_succ */
7397	    link_insn = pending_read_insns;
7398	    link_mem = pending_read_mems;
7399	    while (link_insn)
7400	      {
7401		if (!(find_insn_mem_list (XEXP (link_insn, 0), XEXP (link_mem, 0),
7402					  bb_pending_read_insns[bb_succ],
7403					  bb_pending_read_mems[bb_succ])))
7404		  add_insn_mem_dependence (&bb_pending_read_insns[bb_succ],
7405					   &bb_pending_read_mems[bb_succ],
7406				   XEXP (link_insn, 0), XEXP (link_mem, 0));
7407		link_insn = XEXP (link_insn, 1);
7408		link_mem = XEXP (link_mem, 1);
7409	      }
7410
7411	    link_insn = pending_write_insns;
7412	    link_mem = pending_write_mems;
7413	    while (link_insn)
7414	      {
7415		if (!(find_insn_mem_list (XEXP (link_insn, 0), XEXP (link_mem, 0),
7416					  bb_pending_write_insns[bb_succ],
7417					  bb_pending_write_mems[bb_succ])))
7418		  add_insn_mem_dependence (&bb_pending_write_insns[bb_succ],
7419					   &bb_pending_write_mems[bb_succ],
7420				   XEXP (link_insn, 0), XEXP (link_mem, 0));
7421
7422		link_insn = XEXP (link_insn, 1);
7423		link_mem = XEXP (link_mem, 1);
7424	      }
7425
7426	    /* last_function_call is inherited by bb_succ */
7427	    for (u = last_function_call; u; u = XEXP (u, 1))
7428	      {
7429		if (find_insn_list (XEXP (u, 0), bb_last_function_call[bb_succ]))
7430		  continue;
7431
7432		bb_last_function_call[bb_succ]
7433		  = alloc_INSN_LIST (XEXP (u, 0),
7434				     bb_last_function_call[bb_succ]);
7435	      }
7436
7437	    /* last_pending_memory_flush is inherited by bb_succ */
7438	    for (u = last_pending_memory_flush; u; u = XEXP (u, 1))
7439	      {
7440		if (find_insn_list (XEXP (u, 0), bb_last_pending_memory_flush[bb_succ]))
7441		  continue;
7442
7443		bb_last_pending_memory_flush[bb_succ]
7444		  = alloc_INSN_LIST (XEXP (u, 0),
7445				     bb_last_pending_memory_flush[bb_succ]);
7446	      }
7447
7448	    /* sched_before_next_call is inherited by bb_succ */
7449	    x = LOG_LINKS (sched_before_next_call);
7450	    for (; x; x = XEXP (x, 1))
7451	      add_dependence (bb_sched_before_next_call[bb_succ],
7452			      XEXP (x, 0), REG_DEP_ANTI);
7453
7454	    e = NEXT_OUT (e);
7455	  }
7456	while (e != first_edge);
7457    }
7458
7459  /* Free up the INSN_LISTs
7460
7461     Note this loop is executed max_reg * nr_regions times.  It's first
7462     implementation accounted for over 90% of the calls to free_list.
7463     The list was empty for the vast majority of those calls.  On the PA,
7464     not calling free_list in those cases improves -O2 compile times by
7465     3-5% on average.  */
7466  for (b = 0; b < max_reg; ++b)
7467    {
7468      if (reg_last_clobbers[b])
7469	free_list (&reg_last_clobbers[b], &unused_insn_list);
7470      if (reg_last_sets[b])
7471	free_list (&reg_last_sets[b], &unused_insn_list);
7472      if (reg_last_uses[b])
7473	free_list (&reg_last_uses[b], &unused_insn_list);
7474    }
7475
7476  /* Assert that we won't need bb_reg_last_* for this block anymore.  */
7477  if (current_nr_blocks > 1)
7478    {
7479      bb_reg_last_uses[bb] = (rtx *) NULL_RTX;
7480      bb_reg_last_sets[bb] = (rtx *) NULL_RTX;
7481      bb_reg_last_clobbers[bb] = (rtx *) NULL_RTX;
7482    }
7483}
7484
7485/* Print dependences for debugging, callable from debugger */
7486
7487void
7488debug_dependencies ()
7489{
7490  int bb;
7491
7492  fprintf (dump, ";;   --------------- forward dependences: ------------ \n");
7493  for (bb = 0; bb < current_nr_blocks; bb++)
7494    {
7495      if (1)
7496	{
7497	  rtx head, tail;
7498	  rtx next_tail;
7499	  rtx insn;
7500
7501	  get_block_head_tail (bb, &head, &tail);
7502	  next_tail = NEXT_INSN (tail);
7503	  fprintf (dump, "\n;;   --- Region Dependences --- b %d bb %d \n",
7504		   BB_TO_BLOCK (bb), bb);
7505
7506	  fprintf (dump, ";;   %7s%6s%6s%6s%6s%6s%11s%6s\n",
7507	  "insn", "code", "bb", "dep", "prio", "cost", "blockage", "units");
7508	  fprintf (dump, ";;   %7s%6s%6s%6s%6s%6s%11s%6s\n",
7509	  "----", "----", "--", "---", "----", "----", "--------", "-----");
7510	  for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
7511	    {
7512	      rtx link;
7513	      int unit, range;
7514
7515	      if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
7516		{
7517		  int n;
7518		  fprintf (dump, ";;   %6d ", INSN_UID (insn));
7519		  if (GET_CODE (insn) == NOTE)
7520		    {
7521		      n = NOTE_LINE_NUMBER (insn);
7522		      if (n < 0)
7523			fprintf (dump, "%s\n", GET_NOTE_INSN_NAME (n));
7524		      else
7525			fprintf (dump, "line %d, file %s\n", n,
7526				 NOTE_SOURCE_FILE (insn));
7527		    }
7528		  else
7529		    fprintf (dump, " {%s}\n", GET_RTX_NAME (GET_CODE (insn)));
7530		  continue;
7531		}
7532
7533	      unit = insn_unit (insn);
7534	      range = (unit < 0
7535		 || function_units[unit].blockage_range_function == 0) ? 0 :
7536		function_units[unit].blockage_range_function (insn);
7537	      fprintf (dump,
7538		       ";;   %s%5d%6d%6d%6d%6d%6d  %3d -%3d   ",
7539		       (SCHED_GROUP_P (insn) ? "+" : " "),
7540		       INSN_UID (insn),
7541		       INSN_CODE (insn),
7542		       INSN_BB (insn),
7543		       INSN_DEP_COUNT (insn),
7544		       INSN_PRIORITY (insn),
7545		       insn_cost (insn, 0, 0),
7546		       (int) MIN_BLOCKAGE_COST (range),
7547		       (int) MAX_BLOCKAGE_COST (range));
7548	      insn_print_units (insn);
7549	      fprintf (dump, "\t: ");
7550	      for (link = INSN_DEPEND (insn); link; link = XEXP (link, 1))
7551		fprintf (dump, "%d ", INSN_UID (XEXP (link, 0)));
7552	      fprintf (dump, "\n");
7553	    }
7554	}
7555    }
7556  fprintf (dump, "\n");
7557}
7558
7559/* Set_priorities: compute priority of each insn in the block */
7560
7561static int
7562set_priorities (bb)
7563     int bb;
7564{
7565  rtx insn;
7566  int n_insn;
7567
7568  rtx tail;
7569  rtx prev_head;
7570  rtx head;
7571
7572  get_block_head_tail (bb, &head, &tail);
7573  prev_head = PREV_INSN (head);
7574
7575  if (head == tail
7576      && (GET_RTX_CLASS (GET_CODE (head)) != 'i'))
7577    return 0;
7578
7579  n_insn = 0;
7580  for (insn = tail; insn != prev_head; insn = PREV_INSN (insn))
7581    {
7582
7583      if (GET_CODE (insn) == NOTE)
7584	continue;
7585
7586      if (!(SCHED_GROUP_P (insn)))
7587	n_insn++;
7588      (void) priority (insn);
7589    }
7590
7591  return n_insn;
7592}
7593
7594/* Make each element of VECTOR point at an rtx-vector,
7595   taking the space for all those rtx-vectors from SPACE.
7596   SPACE is of type (rtx *), but it is really as long as NELTS rtx-vectors.
7597   BYTES_PER_ELT is the number of bytes in one rtx-vector.
7598   (this is the same as init_regset_vector () in flow.c) */
7599
7600static void
7601init_rtx_vector (vector, space, nelts, bytes_per_elt)
7602     rtx **vector;
7603     rtx *space;
7604     int nelts;
7605     int bytes_per_elt;
7606{
7607  register int i;
7608  register rtx *p = space;
7609
7610  for (i = 0; i < nelts; i++)
7611    {
7612      vector[i] = p;
7613      p += bytes_per_elt / sizeof (*p);
7614    }
7615}
7616
7617/* Schedule a region.  A region is either an inner loop, a loop-free
7618   subroutine, or a single basic block.  Each bb in the region is
7619   scheduled after its flow predecessors.  */
7620
7621static void
7622schedule_region (rgn)
7623     int rgn;
7624{
7625  int bb;
7626  int rgn_n_insns = 0;
7627  int sched_rgn_n_insns = 0;
7628
7629  /* set variables for the current region */
7630  current_nr_blocks = RGN_NR_BLOCKS (rgn);
7631  current_blocks = RGN_BLOCKS (rgn);
7632
7633  reg_pending_sets = ALLOCA_REG_SET ();
7634  reg_pending_clobbers = ALLOCA_REG_SET ();
7635  reg_pending_sets_all = 0;
7636
7637  /* initializations for region data dependence analyisis */
7638  if (current_nr_blocks > 1)
7639    {
7640      rtx *space;
7641      int maxreg = max_reg_num ();
7642
7643      bb_reg_last_uses = (rtx **) alloca (current_nr_blocks * sizeof (rtx *));
7644      space = (rtx *) alloca (current_nr_blocks * maxreg * sizeof (rtx));
7645      bzero ((char *) space, current_nr_blocks * maxreg * sizeof (rtx));
7646      init_rtx_vector (bb_reg_last_uses, space, current_nr_blocks,
7647		       maxreg * sizeof (rtx *));
7648
7649      bb_reg_last_sets = (rtx **) alloca (current_nr_blocks * sizeof (rtx *));
7650      space = (rtx *) alloca (current_nr_blocks * maxreg * sizeof (rtx));
7651      bzero ((char *) space, current_nr_blocks * maxreg * sizeof (rtx));
7652      init_rtx_vector (bb_reg_last_sets, space, current_nr_blocks,
7653		       maxreg * sizeof (rtx *));
7654
7655      bb_reg_last_clobbers =
7656	(rtx **) alloca (current_nr_blocks * sizeof (rtx *));
7657      space = (rtx *) alloca (current_nr_blocks * maxreg * sizeof (rtx));
7658      bzero ((char *) space, current_nr_blocks * maxreg * sizeof (rtx));
7659      init_rtx_vector (bb_reg_last_clobbers, space, current_nr_blocks,
7660		       maxreg * sizeof (rtx *));
7661
7662      bb_pending_read_insns = (rtx *) alloca (current_nr_blocks * sizeof (rtx));
7663      bb_pending_read_mems = (rtx *) alloca (current_nr_blocks * sizeof (rtx));
7664      bb_pending_write_insns =
7665	(rtx *) alloca (current_nr_blocks * sizeof (rtx));
7666      bb_pending_write_mems = (rtx *) alloca (current_nr_blocks * sizeof (rtx));
7667      bb_pending_lists_length =
7668	(int *) alloca (current_nr_blocks * sizeof (int));
7669      bb_last_pending_memory_flush =
7670	(rtx *) alloca (current_nr_blocks * sizeof (rtx));
7671      bb_last_function_call = (rtx *) alloca (current_nr_blocks * sizeof (rtx));
7672      bb_sched_before_next_call =
7673	(rtx *) alloca (current_nr_blocks * sizeof (rtx));
7674
7675      init_rgn_data_dependences (current_nr_blocks);
7676    }
7677
7678  /* compute LOG_LINKS */
7679  for (bb = 0; bb < current_nr_blocks; bb++)
7680    compute_block_backward_dependences (bb);
7681
7682  /* compute INSN_DEPEND */
7683  for (bb = current_nr_blocks - 1; bb >= 0; bb--)
7684    compute_block_forward_dependences (bb);
7685
7686  /* Delete line notes, compute live-regs at block end, and set priorities.  */
7687  dead_notes = 0;
7688  for (bb = 0; bb < current_nr_blocks; bb++)
7689    {
7690      if (reload_completed == 0)
7691	find_pre_sched_live (bb);
7692
7693      if (write_symbols != NO_DEBUG)
7694	{
7695	  save_line_notes (bb);
7696	  rm_line_notes (bb);
7697	}
7698
7699      rgn_n_insns += set_priorities (bb);
7700    }
7701
7702  /* compute interblock info: probabilities, split-edges, dominators, etc.  */
7703  if (current_nr_blocks > 1)
7704    {
7705      int i;
7706
7707      prob = (float *) alloca ((current_nr_blocks) * sizeof (float));
7708
7709      bbset_size = current_nr_blocks / HOST_BITS_PER_WIDE_INT + 1;
7710      dom = (bbset *) alloca (current_nr_blocks * sizeof (bbset));
7711      for (i = 0; i < current_nr_blocks; i++)
7712	{
7713	  dom[i] = (bbset) alloca (bbset_size * sizeof (HOST_WIDE_INT));
7714	  bzero ((char *) dom[i], bbset_size * sizeof (HOST_WIDE_INT));
7715	}
7716
7717      /* edge to bit */
7718      rgn_nr_edges = 0;
7719      edge_to_bit = (int *) alloca (nr_edges * sizeof (int));
7720      for (i = 1; i < nr_edges; i++)
7721	if (CONTAINING_RGN (FROM_BLOCK (i)) == rgn)
7722	  EDGE_TO_BIT (i) = rgn_nr_edges++;
7723      rgn_edges = (int *) alloca (rgn_nr_edges * sizeof (int));
7724
7725      rgn_nr_edges = 0;
7726      for (i = 1; i < nr_edges; i++)
7727	if (CONTAINING_RGN (FROM_BLOCK (i)) == (rgn))
7728	  rgn_edges[rgn_nr_edges++] = i;
7729
7730      /* split edges */
7731      edgeset_size = rgn_nr_edges / HOST_BITS_PER_WIDE_INT + 1;
7732      pot_split = (edgeset *) alloca (current_nr_blocks * sizeof (edgeset));
7733      ancestor_edges = (edgeset *) alloca (current_nr_blocks * sizeof (edgeset));
7734      for (i = 0; i < current_nr_blocks; i++)
7735	{
7736	  pot_split[i] =
7737	    (edgeset) alloca (edgeset_size * sizeof (HOST_WIDE_INT));
7738	  bzero ((char *) pot_split[i],
7739		 edgeset_size * sizeof (HOST_WIDE_INT));
7740	  ancestor_edges[i] =
7741	    (edgeset) alloca (edgeset_size * sizeof (HOST_WIDE_INT));
7742	  bzero ((char *) ancestor_edges[i],
7743		 edgeset_size * sizeof (HOST_WIDE_INT));
7744	}
7745
7746      /* compute probabilities, dominators, split_edges */
7747      for (bb = 0; bb < current_nr_blocks; bb++)
7748	compute_dom_prob_ps (bb);
7749    }
7750
7751  /* now we can schedule all blocks */
7752  for (bb = 0; bb < current_nr_blocks; bb++)
7753    {
7754      sched_rgn_n_insns += schedule_block (bb, rgn_n_insns);
7755
7756#ifdef USE_C_ALLOCA
7757      alloca (0);
7758#endif
7759    }
7760
7761  /* sanity check: verify that all region insns were scheduled */
7762  if (sched_rgn_n_insns != rgn_n_insns)
7763    abort ();
7764
7765  /* update register life and usage information */
7766  if (reload_completed == 0)
7767    {
7768      for (bb = current_nr_blocks - 1; bb >= 0; bb--)
7769	find_post_sched_live (bb);
7770
7771      if (current_nr_blocks <= 1)
7772	/* Sanity check.  There should be no REG_DEAD notes leftover at the end.
7773	   In practice, this can occur as the result of bugs in flow, combine.c,
7774	   and/or sched.c.  The values of the REG_DEAD notes remaining are
7775	   meaningless, because dead_notes is just used as a free list.  */
7776	if (dead_notes != 0)
7777	  abort ();
7778    }
7779
7780  /* restore line notes.  */
7781  if (write_symbols != NO_DEBUG)
7782    {
7783      for (bb = 0; bb < current_nr_blocks; bb++)
7784	restore_line_notes (bb);
7785    }
7786
7787  /* Done with this region */
7788  free_pending_lists ();
7789
7790  FREE_REG_SET (reg_pending_sets);
7791  FREE_REG_SET (reg_pending_clobbers);
7792}
7793
7794/* Subroutine of update_flow_info.  Determines whether any new REG_NOTEs are
7795   needed for the hard register mentioned in the note.  This can happen
7796   if the reference to the hard register in the original insn was split into
7797   several smaller hard register references in the split insns.  */
7798
7799static void
7800split_hard_reg_notes (note, first, last)
7801     rtx note, first, last;
7802{
7803  rtx reg, temp, link;
7804  int n_regs, i, new_reg;
7805  rtx insn;
7806
7807  /* Assume that this is a REG_DEAD note.  */
7808  if (REG_NOTE_KIND (note) != REG_DEAD)
7809    abort ();
7810
7811  reg = XEXP (note, 0);
7812
7813  n_regs = HARD_REGNO_NREGS (REGNO (reg), GET_MODE (reg));
7814
7815  for (i = 0; i < n_regs; i++)
7816    {
7817      new_reg = REGNO (reg) + i;
7818
7819      /* Check for references to new_reg in the split insns.  */
7820      for (insn = last;; insn = PREV_INSN (insn))
7821	{
7822	  if (GET_RTX_CLASS (GET_CODE (insn)) == 'i'
7823	      && (temp = regno_use_in (new_reg, PATTERN (insn))))
7824	    {
7825	      /* Create a new reg dead note ere.  */
7826	      link = alloc_EXPR_LIST (REG_DEAD, temp, REG_NOTES (insn));
7827	      REG_NOTES (insn) = link;
7828
7829	      /* If killed multiple registers here, then add in the excess.  */
7830	      i += HARD_REGNO_NREGS (REGNO (temp), GET_MODE (temp)) - 1;
7831
7832	      break;
7833	    }
7834	  /* It isn't mentioned anywhere, so no new reg note is needed for
7835	     this register.  */
7836	  if (insn == first)
7837	    break;
7838	}
7839    }
7840}
7841
7842/* Subroutine of update_flow_info.  Determines whether a SET or CLOBBER in an
7843   insn created by splitting needs a REG_DEAD or REG_UNUSED note added.  */
7844
7845static void
7846new_insn_dead_notes (pat, insn, last, orig_insn)
7847     rtx pat, insn, last, orig_insn;
7848{
7849  rtx dest, tem, set;
7850
7851  /* PAT is either a CLOBBER or a SET here.  */
7852  dest = XEXP (pat, 0);
7853
7854  while (GET_CODE (dest) == ZERO_EXTRACT || GET_CODE (dest) == SUBREG
7855	 || GET_CODE (dest) == STRICT_LOW_PART
7856	 || GET_CODE (dest) == SIGN_EXTRACT)
7857    dest = XEXP (dest, 0);
7858
7859  if (GET_CODE (dest) == REG)
7860    {
7861      /* If the original insn already used this register, we may not add new
7862         notes for it.  One example for a split that needs this test is
7863	 when a multi-word memory access with register-indirect addressing
7864	 is split into multiple memory accesses with auto-increment and
7865	 one adjusting add instruction for the address register.  */
7866      if (reg_referenced_p (dest, PATTERN (orig_insn)))
7867	return;
7868      for (tem = last; tem != insn; tem = PREV_INSN (tem))
7869	{
7870	  if (GET_RTX_CLASS (GET_CODE (tem)) == 'i'
7871	      && reg_overlap_mentioned_p (dest, PATTERN (tem))
7872	      && (set = single_set (tem)))
7873	    {
7874	      rtx tem_dest = SET_DEST (set);
7875
7876	      while (GET_CODE (tem_dest) == ZERO_EXTRACT
7877		     || GET_CODE (tem_dest) == SUBREG
7878		     || GET_CODE (tem_dest) == STRICT_LOW_PART
7879		     || GET_CODE (tem_dest) == SIGN_EXTRACT)
7880		tem_dest = XEXP (tem_dest, 0);
7881
7882	      if (!rtx_equal_p (tem_dest, dest))
7883		{
7884		  /* Use the same scheme as combine.c, don't put both REG_DEAD
7885		     and REG_UNUSED notes on the same insn.  */
7886		  if (!find_regno_note (tem, REG_UNUSED, REGNO (dest))
7887		      && !find_regno_note (tem, REG_DEAD, REGNO (dest)))
7888		    {
7889		      rtx note = alloc_EXPR_LIST (REG_DEAD, dest,
7890						  REG_NOTES (tem));
7891		      REG_NOTES (tem) = note;
7892		    }
7893		  /* The reg only dies in one insn, the last one that uses
7894		     it.  */
7895		  break;
7896		}
7897	      else if (reg_overlap_mentioned_p (dest, SET_SRC (set)))
7898		/* We found an instruction that both uses the register,
7899		   and sets it, so no new REG_NOTE is needed for this set.  */
7900		break;
7901	    }
7902	}
7903      /* If this is a set, it must die somewhere, unless it is the dest of
7904         the original insn, and hence is live after the original insn.  Abort
7905         if it isn't supposed to be live after the original insn.
7906
7907         If this is a clobber, then just add a REG_UNUSED note.  */
7908      if (tem == insn)
7909	{
7910	  int live_after_orig_insn = 0;
7911	  rtx pattern = PATTERN (orig_insn);
7912	  int i;
7913
7914	  if (GET_CODE (pat) == CLOBBER)
7915	    {
7916	      rtx note = alloc_EXPR_LIST (REG_UNUSED, dest, REG_NOTES (insn));
7917	      REG_NOTES (insn) = note;
7918	      return;
7919	    }
7920
7921	  /* The original insn could have multiple sets, so search the
7922	     insn for all sets.  */
7923	  if (GET_CODE (pattern) == SET)
7924	    {
7925	      if (reg_overlap_mentioned_p (dest, SET_DEST (pattern)))
7926		live_after_orig_insn = 1;
7927	    }
7928	  else if (GET_CODE (pattern) == PARALLEL)
7929	    {
7930	      for (i = 0; i < XVECLEN (pattern, 0); i++)
7931		if (GET_CODE (XVECEXP (pattern, 0, i)) == SET
7932		    && reg_overlap_mentioned_p (dest,
7933						SET_DEST (XVECEXP (pattern,
7934								   0, i))))
7935		  live_after_orig_insn = 1;
7936	    }
7937
7938	  if (!live_after_orig_insn)
7939	    abort ();
7940	}
7941    }
7942}
7943
7944/* Subroutine of update_flow_info.  Update the value of reg_n_sets for all
7945   registers modified by X.  INC is -1 if the containing insn is being deleted,
7946   and is 1 if the containing insn is a newly generated insn.  */
7947
7948static void
7949update_n_sets (x, inc)
7950     rtx x;
7951     int inc;
7952{
7953  rtx dest = SET_DEST (x);
7954
7955  while (GET_CODE (dest) == STRICT_LOW_PART || GET_CODE (dest) == SUBREG
7956      || GET_CODE (dest) == ZERO_EXTRACT || GET_CODE (dest) == SIGN_EXTRACT)
7957    dest = SUBREG_REG (dest);
7958
7959  if (GET_CODE (dest) == REG)
7960    {
7961      int regno = REGNO (dest);
7962
7963      if (regno < FIRST_PSEUDO_REGISTER)
7964	{
7965	  register int i;
7966	  int endregno = regno + HARD_REGNO_NREGS (regno, GET_MODE (dest));
7967
7968	  for (i = regno; i < endregno; i++)
7969	    REG_N_SETS (i) += inc;
7970	}
7971      else
7972	REG_N_SETS (regno) += inc;
7973    }
7974}
7975
7976/* Updates all flow-analysis related quantities (including REG_NOTES) for
7977   the insns from FIRST to LAST inclusive that were created by splitting
7978   ORIG_INSN.  NOTES are the original REG_NOTES.  */
7979
7980void
7981update_flow_info (notes, first, last, orig_insn)
7982     rtx notes;
7983     rtx first, last;
7984     rtx orig_insn;
7985{
7986  rtx insn, note;
7987  rtx next;
7988  rtx orig_dest, temp;
7989  rtx set;
7990
7991  /* Get and save the destination set by the original insn.  */
7992
7993  orig_dest = single_set (orig_insn);
7994  if (orig_dest)
7995    orig_dest = SET_DEST (orig_dest);
7996
7997  /* Move REG_NOTES from the original insn to where they now belong.  */
7998
7999  for (note = notes; note; note = next)
8000    {
8001      next = XEXP (note, 1);
8002      switch (REG_NOTE_KIND (note))
8003	{
8004	case REG_DEAD:
8005	case REG_UNUSED:
8006	  /* Move these notes from the original insn to the last new insn where
8007	     the register is now set.  */
8008
8009	  for (insn = last;; insn = PREV_INSN (insn))
8010	    {
8011	      if (GET_RTX_CLASS (GET_CODE (insn)) == 'i'
8012		  && reg_mentioned_p (XEXP (note, 0), PATTERN (insn)))
8013		{
8014		  /* If this note refers to a multiple word hard register, it
8015		     may have been split into several smaller hard register
8016		     references, so handle it specially.  */
8017		  temp = XEXP (note, 0);
8018		  if (REG_NOTE_KIND (note) == REG_DEAD
8019		      && GET_CODE (temp) == REG
8020		      && REGNO (temp) < FIRST_PSEUDO_REGISTER
8021		      && HARD_REGNO_NREGS (REGNO (temp), GET_MODE (temp)) > 1)
8022		    split_hard_reg_notes (note, first, last);
8023		  else
8024		    {
8025		      XEXP (note, 1) = REG_NOTES (insn);
8026		      REG_NOTES (insn) = note;
8027		    }
8028
8029		  /* Sometimes need to convert REG_UNUSED notes to REG_DEAD
8030		     notes.  */
8031		  /* ??? This won't handle multiple word registers correctly,
8032		     but should be good enough for now.  */
8033		  if (REG_NOTE_KIND (note) == REG_UNUSED
8034		      && GET_CODE (XEXP (note, 0)) != SCRATCH
8035		      && !dead_or_set_p (insn, XEXP (note, 0)))
8036		    PUT_REG_NOTE_KIND (note, REG_DEAD);
8037
8038		  /* The reg only dies in one insn, the last one that uses
8039		     it.  */
8040		  break;
8041		}
8042	      /* It must die somewhere, fail it we couldn't find where it died.
8043
8044	         If this is a REG_UNUSED note, then it must be a temporary
8045	         register that was not needed by this instantiation of the
8046	         pattern, so we can safely ignore it.  */
8047	      if (insn == first)
8048		{
8049		  if (REG_NOTE_KIND (note) != REG_UNUSED)
8050		    abort ();
8051
8052		  break;
8053		}
8054	    }
8055	  break;
8056
8057	case REG_WAS_0:
8058	  /* If the insn that set the register to 0 was deleted, this
8059	     note cannot be relied on any longer.  The destination might
8060	     even have been moved to memory.
8061             This was observed for SH4 with execute/920501-6.c compilation,
8062	     -O2 -fomit-frame-pointer -finline-functions .  */
8063	  if (GET_CODE (XEXP (note, 0)) == NOTE
8064	      || INSN_DELETED_P (XEXP (note, 0)))
8065	    break;
8066	  /* This note applies to the dest of the original insn.  Find the
8067	     first new insn that now has the same dest, and move the note
8068	     there.  */
8069
8070	  if (!orig_dest)
8071	    abort ();
8072
8073	  for (insn = first;; insn = NEXT_INSN (insn))
8074	    {
8075	      if (GET_RTX_CLASS (GET_CODE (insn)) == 'i'
8076		  && (temp = single_set (insn))
8077		  && rtx_equal_p (SET_DEST (temp), orig_dest))
8078		{
8079		  XEXP (note, 1) = REG_NOTES (insn);
8080		  REG_NOTES (insn) = note;
8081		  /* The reg is only zero before one insn, the first that
8082		     uses it.  */
8083		  break;
8084		}
8085	      /* If this note refers to a multiple word hard
8086		 register, it may have been split into several smaller
8087		 hard register references.  We could split the notes,
8088		 but simply dropping them is good enough.  */
8089	      if (GET_CODE (orig_dest) == REG
8090		  && REGNO (orig_dest) < FIRST_PSEUDO_REGISTER
8091		  && HARD_REGNO_NREGS (REGNO (orig_dest),
8092				       GET_MODE (orig_dest)) > 1)
8093		    break;
8094	      /* It must be set somewhere, fail if we couldn't find where it
8095	         was set.  */
8096	      if (insn == last)
8097		abort ();
8098	    }
8099	  break;
8100
8101	case REG_EQUAL:
8102	case REG_EQUIV:
8103	  /* A REG_EQUIV or REG_EQUAL note on an insn with more than one
8104	     set is meaningless.  Just drop the note.  */
8105	  if (!orig_dest)
8106	    break;
8107
8108	case REG_NO_CONFLICT:
8109	  /* These notes apply to the dest of the original insn.  Find the last
8110	     new insn that now has the same dest, and move the note there.  */
8111
8112	  if (!orig_dest)
8113	    abort ();
8114
8115	  for (insn = last;; insn = PREV_INSN (insn))
8116	    {
8117	      if (GET_RTX_CLASS (GET_CODE (insn)) == 'i'
8118		  && (temp = single_set (insn))
8119		  && rtx_equal_p (SET_DEST (temp), orig_dest))
8120		{
8121		  XEXP (note, 1) = REG_NOTES (insn);
8122		  REG_NOTES (insn) = note;
8123		  /* Only put this note on one of the new insns.  */
8124		  break;
8125		}
8126
8127	      /* The original dest must still be set someplace.  Abort if we
8128	         couldn't find it.  */
8129	      if (insn == first)
8130		{
8131		  /* However, if this note refers to a multiple word hard
8132		     register, it may have been split into several smaller
8133		     hard register references.  We could split the notes,
8134		     but simply dropping them is good enough.  */
8135		  if (GET_CODE (orig_dest) == REG
8136		      && REGNO (orig_dest) < FIRST_PSEUDO_REGISTER
8137		      && HARD_REGNO_NREGS (REGNO (orig_dest),
8138					   GET_MODE (orig_dest)) > 1)
8139		    break;
8140		  /* Likewise for multi-word memory references.  */
8141		  if (GET_CODE (orig_dest) == MEM
8142		      && SIZE_FOR_MODE (orig_dest) > UNITS_PER_WORD)
8143		    break;
8144		  abort ();
8145		}
8146	    }
8147	  break;
8148
8149	case REG_LIBCALL:
8150	  /* Move a REG_LIBCALL note to the first insn created, and update
8151	     the corresponding REG_RETVAL note.  */
8152	  XEXP (note, 1) = REG_NOTES (first);
8153	  REG_NOTES (first) = note;
8154
8155	  insn = XEXP (note, 0);
8156	  note = find_reg_note (insn, REG_RETVAL, NULL_RTX);
8157	  if (note)
8158	    XEXP (note, 0) = first;
8159	  break;
8160
8161	case REG_EXEC_COUNT:
8162	  /* Move a REG_EXEC_COUNT note to the first insn created.  */
8163	  XEXP (note, 1) = REG_NOTES (first);
8164	  REG_NOTES (first) = note;
8165	  break;
8166
8167	case REG_RETVAL:
8168	  /* Move a REG_RETVAL note to the last insn created, and update
8169	     the corresponding REG_LIBCALL note.  */
8170	  XEXP (note, 1) = REG_NOTES (last);
8171	  REG_NOTES (last) = note;
8172
8173	  insn = XEXP (note, 0);
8174	  note = find_reg_note (insn, REG_LIBCALL, NULL_RTX);
8175	  if (note)
8176	    XEXP (note, 0) = last;
8177	  break;
8178
8179	case REG_NONNEG:
8180	case REG_BR_PROB:
8181	  /* This should be moved to whichever instruction is a JUMP_INSN.  */
8182
8183	  for (insn = last;; insn = PREV_INSN (insn))
8184	    {
8185	      if (GET_CODE (insn) == JUMP_INSN)
8186		{
8187		  XEXP (note, 1) = REG_NOTES (insn);
8188		  REG_NOTES (insn) = note;
8189		  /* Only put this note on one of the new insns.  */
8190		  break;
8191		}
8192	      /* Fail if we couldn't find a JUMP_INSN.  */
8193	      if (insn == first)
8194		abort ();
8195	    }
8196	  break;
8197
8198	case REG_INC:
8199	  /* reload sometimes leaves obsolete REG_INC notes around.  */
8200	  if (reload_completed)
8201	    break;
8202	  /* This should be moved to whichever instruction now has the
8203	     increment operation.  */
8204	  abort ();
8205
8206	case REG_LABEL:
8207	  /* Should be moved to the new insn(s) which use the label.  */
8208	  for (insn = first; insn != NEXT_INSN (last); insn = NEXT_INSN (insn))
8209	    if (GET_RTX_CLASS (GET_CODE (insn)) == 'i'
8210		&& reg_mentioned_p (XEXP (note, 0), PATTERN (insn)))
8211	      {
8212	        REG_NOTES (insn) = alloc_EXPR_LIST (REG_LABEL,
8213						    XEXP (note, 0),
8214						    REG_NOTES (insn));
8215	      }
8216	  break;
8217
8218	case REG_CC_SETTER:
8219	case REG_CC_USER:
8220	  /* These two notes will never appear until after reorg, so we don't
8221	     have to handle them here.  */
8222	default:
8223	  abort ();
8224	}
8225    }
8226
8227  /* Each new insn created, except the last, has a new set.  If the destination
8228     is a register, then this reg is now live across several insns, whereas
8229     previously the dest reg was born and died within the same insn.  To
8230     reflect this, we now need a REG_DEAD note on the insn where this
8231     dest reg dies.
8232
8233     Similarly, the new insns may have clobbers that need REG_UNUSED notes.  */
8234
8235  for (insn = first; insn != last; insn = NEXT_INSN (insn))
8236    {
8237      rtx pat;
8238      int i;
8239
8240      pat = PATTERN (insn);
8241      if (GET_CODE (pat) == SET || GET_CODE (pat) == CLOBBER)
8242	new_insn_dead_notes (pat, insn, last, orig_insn);
8243      else if (GET_CODE (pat) == PARALLEL)
8244	{
8245	  for (i = 0; i < XVECLEN (pat, 0); i++)
8246	    if (GET_CODE (XVECEXP (pat, 0, i)) == SET
8247		|| GET_CODE (XVECEXP (pat, 0, i)) == CLOBBER)
8248	      new_insn_dead_notes (XVECEXP (pat, 0, i), insn, last, orig_insn);
8249	}
8250    }
8251
8252  /* If any insn, except the last, uses the register set by the last insn,
8253     then we need a new REG_DEAD note on that insn.  In this case, there
8254     would not have been a REG_DEAD note for this register in the original
8255     insn because it was used and set within one insn.  */
8256
8257  set = single_set (last);
8258  if (set)
8259    {
8260      rtx dest = SET_DEST (set);
8261
8262      while (GET_CODE (dest) == ZERO_EXTRACT || GET_CODE (dest) == SUBREG
8263	     || GET_CODE (dest) == STRICT_LOW_PART
8264	     || GET_CODE (dest) == SIGN_EXTRACT)
8265	dest = XEXP (dest, 0);
8266
8267      if (GET_CODE (dest) == REG
8268	  /* Global registers are always live, so the code below does not
8269	     apply to them.  */
8270	  && (REGNO (dest) >= FIRST_PSEUDO_REGISTER
8271	      || ! global_regs[REGNO (dest)]))
8272	{
8273	  rtx stop_insn = PREV_INSN (first);
8274
8275	  /* If the last insn uses the register that it is setting, then
8276	     we don't want to put a REG_DEAD note there.  Search backwards
8277	     to find the first insn that sets but does not use DEST.  */
8278
8279	  insn = last;
8280	  if (reg_overlap_mentioned_p (dest, SET_SRC (set)))
8281	    {
8282	      for (insn = PREV_INSN (insn); insn != first;
8283		   insn = PREV_INSN (insn))
8284		{
8285		  if ((set = single_set (insn))
8286		      && reg_mentioned_p (dest, SET_DEST (set))
8287		      && ! reg_overlap_mentioned_p (dest, SET_SRC (set)))
8288		    break;
8289		}
8290	    }
8291
8292	  /* Now find the first insn that uses but does not set DEST.  */
8293
8294	  for (insn = PREV_INSN (insn); insn != stop_insn;
8295	       insn = PREV_INSN (insn))
8296	    {
8297	      if (GET_RTX_CLASS (GET_CODE (insn)) == 'i'
8298		  && reg_mentioned_p (dest, PATTERN (insn))
8299		  && (set = single_set (insn)))
8300		{
8301		  rtx insn_dest = SET_DEST (set);
8302
8303		  while (GET_CODE (insn_dest) == ZERO_EXTRACT
8304			 || GET_CODE (insn_dest) == SUBREG
8305			 || GET_CODE (insn_dest) == STRICT_LOW_PART
8306			 || GET_CODE (insn_dest) == SIGN_EXTRACT)
8307		    insn_dest = XEXP (insn_dest, 0);
8308
8309		  if (insn_dest != dest)
8310		    {
8311		      note = alloc_EXPR_LIST (REG_DEAD, dest, REG_NOTES (insn));
8312		      REG_NOTES (insn) = note;
8313		      /* The reg only dies in one insn, the last one
8314			 that uses it.  */
8315		      break;
8316		    }
8317		}
8318	    }
8319	}
8320    }
8321
8322  /* If the original dest is modifying a multiple register target, and the
8323     original instruction was split such that the original dest is now set
8324     by two or more SUBREG sets, then the split insns no longer kill the
8325     destination of the original insn.
8326
8327     In this case, if there exists an instruction in the same basic block,
8328     before the split insn, which uses the original dest, and this use is
8329     killed by the original insn, then we must remove the REG_DEAD note on
8330     this insn, because it is now superfluous.
8331
8332     This does not apply when a hard register gets split, because the code
8333     knows how to handle overlapping hard registers properly.  */
8334  if (orig_dest && GET_CODE (orig_dest) == REG)
8335    {
8336      int found_orig_dest = 0;
8337      int found_split_dest = 0;
8338
8339      for (insn = first;; insn = NEXT_INSN (insn))
8340	{
8341	  rtx pat;
8342	  int i;
8343
8344	  /* I'm not sure if this can happen, but let's be safe.  */
8345	  if (GET_RTX_CLASS (GET_CODE (insn)) != 'i')
8346	    continue;
8347
8348	  pat = PATTERN (insn);
8349	  i = GET_CODE (pat) == PARALLEL ? XVECLEN (pat, 0) : 0;
8350	  set = pat;
8351
8352	  for (;;)
8353	    {
8354	      if (GET_CODE (set) == SET)
8355		{
8356		  if (GET_CODE (SET_DEST (set)) == REG
8357		      && REGNO (SET_DEST (set)) == REGNO (orig_dest))
8358		    {
8359		      found_orig_dest = 1;
8360		      break;
8361		    }
8362		  else if (GET_CODE (SET_DEST (set)) == SUBREG
8363			   && SUBREG_REG (SET_DEST (set)) == orig_dest)
8364		    {
8365		      found_split_dest = 1;
8366		      break;
8367		    }
8368		}
8369	      if (--i < 0)
8370		break;
8371	      set = XVECEXP (pat, 0, i);
8372	    }
8373
8374	  if (insn == last)
8375	    break;
8376	}
8377
8378      if (found_split_dest)
8379	{
8380	  /* Search backwards from FIRST, looking for the first insn that uses
8381	     the original dest.  Stop if we pass a CODE_LABEL or a JUMP_INSN.
8382	     If we find an insn, and it has a REG_DEAD note, then delete the
8383	     note.  */
8384
8385	  for (insn = first; insn; insn = PREV_INSN (insn))
8386	    {
8387	      if (GET_CODE (insn) == CODE_LABEL
8388		  || GET_CODE (insn) == JUMP_INSN)
8389		break;
8390	      else if (GET_RTX_CLASS (GET_CODE (insn)) == 'i'
8391		       && reg_mentioned_p (orig_dest, insn))
8392		{
8393		  note = find_regno_note (insn, REG_DEAD, REGNO (orig_dest));
8394		  if (note)
8395		    remove_note (insn, note);
8396		}
8397	    }
8398	}
8399      else if (!found_orig_dest)
8400	{
8401	  int i, regno;
8402
8403	  /* Should never reach here for a pseudo reg.  */
8404	  if (REGNO (orig_dest) >= FIRST_PSEUDO_REGISTER)
8405	    abort ();
8406
8407	  /* This can happen for a hard register, if the splitter
8408	     does not bother to emit instructions which would be no-ops.
8409	     We try to verify that this is the case by checking to see if
8410	     the original instruction uses all of the registers that it
8411	     set.  This case is OK, because deleting a no-op can not affect
8412	     REG_DEAD notes on other insns.  If this is not the case, then
8413	     abort.  */
8414
8415	  regno = REGNO (orig_dest);
8416	  for (i = HARD_REGNO_NREGS (regno, GET_MODE (orig_dest)) - 1;
8417	       i >= 0; i--)
8418	    if (! refers_to_regno_p (regno + i, regno + i + 1, orig_insn,
8419				     NULL_PTR))
8420	      break;
8421	  if (i >= 0)
8422	    abort ();
8423	}
8424    }
8425
8426  /* Update reg_n_sets.  This is necessary to prevent local alloc from
8427     converting REG_EQUAL notes to REG_EQUIV when splitting has modified
8428     a reg from set once to set multiple times.  */
8429
8430  {
8431    rtx x = PATTERN (orig_insn);
8432    RTX_CODE code = GET_CODE (x);
8433
8434    if (code == SET || code == CLOBBER)
8435      update_n_sets (x, -1);
8436    else if (code == PARALLEL)
8437      {
8438	int i;
8439	for (i = XVECLEN (x, 0) - 1; i >= 0; i--)
8440	  {
8441	    code = GET_CODE (XVECEXP (x, 0, i));
8442	    if (code == SET || code == CLOBBER)
8443	      update_n_sets (XVECEXP (x, 0, i), -1);
8444	  }
8445      }
8446
8447    for (insn = first;; insn = NEXT_INSN (insn))
8448      {
8449	x = PATTERN (insn);
8450	code = GET_CODE (x);
8451
8452	if (code == SET || code == CLOBBER)
8453	  update_n_sets (x, 1);
8454	else if (code == PARALLEL)
8455	  {
8456	    int i;
8457	    for (i = XVECLEN (x, 0) - 1; i >= 0; i--)
8458	      {
8459		code = GET_CODE (XVECEXP (x, 0, i));
8460		if (code == SET || code == CLOBBER)
8461		  update_n_sets (XVECEXP (x, 0, i), 1);
8462	      }
8463	  }
8464
8465	if (insn == last)
8466	  break;
8467      }
8468  }
8469}
8470
8471/* The one entry point in this file.  DUMP_FILE is the dump file for
8472   this pass.  */
8473
8474void
8475schedule_insns (dump_file)
8476     FILE *dump_file;
8477{
8478
8479  int max_uid;
8480  int b;
8481  rtx insn;
8482  int rgn;
8483
8484  int luid;
8485
8486  /* disable speculative loads in their presence if cc0 defined */
8487#ifdef HAVE_cc0
8488  flag_schedule_speculative_load = 0;
8489#endif
8490
8491  /* Taking care of this degenerate case makes the rest of
8492     this code simpler.  */
8493  if (n_basic_blocks == 0)
8494    return;
8495
8496  /* set dump and sched_verbose for the desired debugging output.  If no
8497     dump-file was specified, but -fsched-verbose-N (any N), print to stderr.
8498     For -fsched-verbose-N, N>=10, print everything to stderr.  */
8499  sched_verbose = sched_verbose_param;
8500  if (sched_verbose_param == 0 && dump_file)
8501    sched_verbose = 1;
8502  dump = ((sched_verbose_param >= 10 || !dump_file) ? stderr : dump_file);
8503
8504  nr_inter = 0;
8505  nr_spec = 0;
8506
8507  /* Initialize the unused_*_lists.  We can't use the ones left over from
8508     the previous function, because gcc has freed that memory.  We can use
8509     the ones left over from the first sched pass in the second pass however,
8510     so only clear them on the first sched pass.  The first pass is before
8511     reload if flag_schedule_insns is set, otherwise it is afterwards.  */
8512
8513  if (reload_completed == 0 || !flag_schedule_insns)
8514    {
8515      unused_insn_list = 0;
8516      unused_expr_list = 0;
8517    }
8518
8519  /* initialize issue_rate */
8520  issue_rate = ISSUE_RATE;
8521
8522  /* do the splitting first for all blocks */
8523  for (b = 0; b < n_basic_blocks; b++)
8524    split_block_insns (b, 1);
8525
8526  max_uid = (get_max_uid () + 1);
8527
8528  cant_move = (char *) xmalloc (max_uid * sizeof (char));
8529  bzero ((char *) cant_move, max_uid * sizeof (char));
8530
8531  fed_by_spec_load = (char *) xmalloc (max_uid * sizeof (char));
8532  bzero ((char *) fed_by_spec_load, max_uid * sizeof (char));
8533
8534  is_load_insn = (char *) xmalloc (max_uid * sizeof (char));
8535  bzero ((char *) is_load_insn, max_uid * sizeof (char));
8536
8537  insn_orig_block = (int *) xmalloc (max_uid * sizeof (int));
8538  insn_luid = (int *) xmalloc (max_uid * sizeof (int));
8539
8540  luid = 0;
8541  for (b = 0; b < n_basic_blocks; b++)
8542    for (insn = BLOCK_HEAD (b);; insn = NEXT_INSN (insn))
8543      {
8544	INSN_BLOCK (insn) = b;
8545	INSN_LUID (insn) = luid++;
8546
8547	if (insn == BLOCK_END (b))
8548	  break;
8549      }
8550
8551  /* after reload, remove inter-blocks dependences computed before reload.  */
8552  if (reload_completed)
8553    {
8554      int b;
8555      rtx insn;
8556
8557      for (b = 0; b < n_basic_blocks; b++)
8558	for (insn = BLOCK_HEAD (b);; insn = NEXT_INSN (insn))
8559	  {
8560	    rtx link, prev;
8561
8562	    if (GET_RTX_CLASS (GET_CODE (insn)) == 'i')
8563	      {
8564		prev = NULL_RTX;
8565		link = LOG_LINKS (insn);
8566		while (link)
8567		  {
8568		    rtx x = XEXP (link, 0);
8569
8570		    if (INSN_BLOCK (x) != b)
8571		      {
8572		        remove_dependence (insn, x);
8573			link = prev ? XEXP (prev, 1) : LOG_LINKS (insn);
8574		      }
8575		    else
8576		      prev = link, link = XEXP (prev, 1);
8577		  }
8578	      }
8579
8580	    if (insn == BLOCK_END (b))
8581	      break;
8582	  }
8583    }
8584
8585  nr_regions = 0;
8586  rgn_table = (region *) alloca ((n_basic_blocks) * sizeof (region));
8587  rgn_bb_table = (int *) alloca ((n_basic_blocks) * sizeof (int));
8588  block_to_bb = (int *) alloca ((n_basic_blocks) * sizeof (int));
8589  containing_rgn = (int *) alloca ((n_basic_blocks) * sizeof (int));
8590
8591  /* compute regions for scheduling */
8592  if (reload_completed
8593      || n_basic_blocks == 1
8594      || !flag_schedule_interblock)
8595    {
8596      find_single_block_region ();
8597    }
8598  else
8599    {
8600      /* verify that a 'good' control flow graph can be built */
8601      if (is_cfg_nonregular ())
8602	{
8603	  find_single_block_region ();
8604	}
8605      else
8606	{
8607	  int_list_ptr *s_preds, *s_succs;
8608	  int *num_preds, *num_succs;
8609	  sbitmap *dom, *pdom;
8610
8611	  s_preds = (int_list_ptr *) alloca (n_basic_blocks
8612					     * sizeof (int_list_ptr));
8613	  s_succs = (int_list_ptr *) alloca (n_basic_blocks
8614					     * sizeof (int_list_ptr));
8615	  num_preds = (int *) alloca (n_basic_blocks * sizeof (int));
8616	  num_succs = (int *) alloca (n_basic_blocks * sizeof (int));
8617	  dom = sbitmap_vector_alloc (n_basic_blocks, n_basic_blocks);
8618	  pdom = sbitmap_vector_alloc (n_basic_blocks, n_basic_blocks);
8619
8620	  /* The scheduler runs after flow; therefore, we can't blindly call
8621	     back into find_basic_blocks since doing so could invalidate the
8622	     info in global_live_at_start.
8623
8624	     Consider a block consisting entirely of dead stores; after life
8625	     analysis it would be a block of NOTE_INSN_DELETED notes.  If
8626	     we call find_basic_blocks again, then the block would be removed
8627	     entirely and invalidate our the register live information.
8628
8629	     We could (should?) recompute register live information.  Doing
8630	     so may even be beneficial.  */
8631
8632	  compute_preds_succs (s_preds, s_succs, num_preds, num_succs);
8633
8634	  /* Compute the dominators and post dominators.  We don't currently use
8635	     post dominators, but we should for speculative motion analysis.  */
8636	  compute_dominators (dom, pdom, s_preds, s_succs);
8637
8638	  /* build_control_flow will return nonzero if it detects unreachable
8639	     blocks or any other irregularity with the cfg which prevents
8640	     cross block scheduling.  */
8641	  if (build_control_flow (s_preds, s_succs, num_preds, num_succs) != 0)
8642	    find_single_block_region ();
8643	  else
8644	    find_rgns (s_preds, s_succs, num_preds, num_succs, dom);
8645
8646	  if (sched_verbose >= 3)
8647	    debug_regions ();
8648
8649	  /* For now.  This will move as more and more of haifa is converted
8650	     to using the cfg code in flow.c  */
8651	  free_bb_mem ();
8652	  free (dom);
8653	  free (pdom);
8654	}
8655    }
8656
8657  /* Allocate data for this pass.  See comments, above,
8658     for what these vectors do.
8659
8660     We use xmalloc instead of alloca, because max_uid can be very large
8661     when there is a lot of function inlining.  If we used alloca, we could
8662     exceed stack limits on some hosts for some inputs.  */
8663  insn_priority = (int *) xmalloc (max_uid * sizeof (int));
8664  insn_reg_weight = (int *) xmalloc (max_uid * sizeof (int));
8665  insn_tick = (int *) xmalloc (max_uid * sizeof (int));
8666  insn_costs = (short *) xmalloc (max_uid * sizeof (short));
8667  insn_units = (short *) xmalloc (max_uid * sizeof (short));
8668  insn_blockage = (unsigned int *) xmalloc (max_uid * sizeof (unsigned int));
8669  insn_ref_count = (int *) xmalloc (max_uid * sizeof (int));
8670
8671  /* Allocate for forward dependencies */
8672  insn_dep_count = (int *) xmalloc (max_uid * sizeof (int));
8673  insn_depend = (rtx *) xmalloc (max_uid * sizeof (rtx));
8674
8675  if (reload_completed == 0)
8676    {
8677      int i;
8678
8679      sched_reg_n_calls_crossed = (int *) alloca (max_regno * sizeof (int));
8680      sched_reg_live_length = (int *) alloca (max_regno * sizeof (int));
8681      sched_reg_basic_block = (int *) alloca (max_regno * sizeof (int));
8682      bb_live_regs = ALLOCA_REG_SET ();
8683      bzero ((char *) sched_reg_n_calls_crossed, max_regno * sizeof (int));
8684      bzero ((char *) sched_reg_live_length, max_regno * sizeof (int));
8685
8686      for (i = 0; i < max_regno; i++)
8687	sched_reg_basic_block[i] = REG_BLOCK_UNKNOWN;
8688    }
8689  else
8690    {
8691      sched_reg_n_calls_crossed = 0;
8692      sched_reg_live_length = 0;
8693      bb_live_regs = 0;
8694    }
8695  init_alias_analysis ();
8696
8697  if (write_symbols != NO_DEBUG)
8698    {
8699      rtx line;
8700
8701      line_note = (rtx *) xmalloc (max_uid * sizeof (rtx));
8702      bzero ((char *) line_note, max_uid * sizeof (rtx));
8703      line_note_head = (rtx *) alloca (n_basic_blocks * sizeof (rtx));
8704      bzero ((char *) line_note_head, n_basic_blocks * sizeof (rtx));
8705
8706      /* Save-line-note-head:
8707         Determine the line-number at the start of each basic block.
8708         This must be computed and saved now, because after a basic block's
8709         predecessor has been scheduled, it is impossible to accurately
8710         determine the correct line number for the first insn of the block.  */
8711
8712      for (b = 0; b < n_basic_blocks; b++)
8713	for (line = BLOCK_HEAD (b); line; line = PREV_INSN (line))
8714	  if (GET_CODE (line) == NOTE && NOTE_LINE_NUMBER (line) > 0)
8715	    {
8716	      line_note_head[b] = line;
8717	      break;
8718	    }
8719    }
8720
8721  bzero ((char *) insn_priority, max_uid * sizeof (int));
8722  bzero ((char *) insn_reg_weight, max_uid * sizeof (int));
8723  bzero ((char *) insn_tick, max_uid * sizeof (int));
8724  bzero ((char *) insn_costs, max_uid * sizeof (short));
8725  bzero ((char *) insn_units, max_uid * sizeof (short));
8726  bzero ((char *) insn_blockage, max_uid * sizeof (unsigned int));
8727  bzero ((char *) insn_ref_count, max_uid * sizeof (int));
8728
8729  /* Initialize for forward dependencies */
8730  bzero ((char *) insn_depend, max_uid * sizeof (rtx));
8731  bzero ((char *) insn_dep_count, max_uid * sizeof (int));
8732
8733  /* Find units used in this fuction, for visualization */
8734  if (sched_verbose)
8735    init_target_units ();
8736
8737  /* ??? Add a NOTE after the last insn of the last basic block.  It is not
8738     known why this is done.  */
8739
8740  insn = BLOCK_END (n_basic_blocks - 1);
8741  if (NEXT_INSN (insn) == 0
8742      || (GET_CODE (insn) != NOTE
8743	  && GET_CODE (insn) != CODE_LABEL
8744	  /* Don't emit a NOTE if it would end up between an unconditional
8745	     jump and a BARRIER.  */
8746	  && !(GET_CODE (insn) == JUMP_INSN
8747	       && GET_CODE (NEXT_INSN (insn)) == BARRIER)))
8748    emit_note_after (NOTE_INSN_DELETED, BLOCK_END (n_basic_blocks - 1));
8749
8750  /* Schedule every region in the subroutine */
8751  for (rgn = 0; rgn < nr_regions; rgn++)
8752    {
8753      schedule_region (rgn);
8754
8755#ifdef USE_C_ALLOCA
8756      alloca (0);
8757#endif
8758    }
8759
8760  /* Reposition the prologue and epilogue notes in case we moved the
8761     prologue/epilogue insns.  */
8762  if (reload_completed)
8763    reposition_prologue_and_epilogue_notes (get_insns ());
8764
8765  /* delete redundant line notes.  */
8766  if (write_symbols != NO_DEBUG)
8767    rm_redundant_line_notes ();
8768
8769  /* Update information about uses of registers in the subroutine.  */
8770  if (reload_completed == 0)
8771    update_reg_usage ();
8772
8773  if (sched_verbose)
8774    {
8775      if (reload_completed == 0 && flag_schedule_interblock)
8776	{
8777	  fprintf (dump, "\n;; Procedure interblock/speculative motions == %d/%d \n",
8778		   nr_inter, nr_spec);
8779	}
8780      else
8781	{
8782	  if (nr_inter > 0)
8783	    abort ();
8784	}
8785      fprintf (dump, "\n\n");
8786    }
8787
8788  free (cant_move);
8789  free (fed_by_spec_load);
8790  free (is_load_insn);
8791  free (insn_orig_block);
8792  free (insn_luid);
8793
8794  free (insn_priority);
8795  free (insn_reg_weight);
8796  free (insn_tick);
8797  free (insn_costs);
8798  free (insn_units);
8799  free (insn_blockage);
8800  free (insn_ref_count);
8801
8802  free (insn_dep_count);
8803  free (insn_depend);
8804
8805  if (write_symbols != NO_DEBUG)
8806    free (line_note);
8807
8808  if (bb_live_regs)
8809    FREE_REG_SET (bb_live_regs);
8810
8811  if (edge_table)
8812    {
8813      free (edge_table);
8814      edge_table = NULL;
8815    }
8816
8817  if (in_edges)
8818    {
8819      free (in_edges);
8820      in_edges = NULL;
8821    }
8822  if (out_edges)
8823    {
8824      free (out_edges);
8825      out_edges = NULL;
8826    }
8827}
8828#endif /* INSN_SCHEDULING */
8829