xref: /openbsd-src/gnu/gcc/gcc/sched-rgn.c (revision 404b540a9034ac75a6199ad1a32d1bbc7a0d4210)
1*404b540aSrobert /* Instruction scheduling pass.
2*404b540aSrobert    Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998,
3*404b540aSrobert    1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
4*404b540aSrobert    Contributed by Michael Tiemann (tiemann@cygnus.com) Enhanced by,
5*404b540aSrobert    and currently maintained by, Jim Wilson (wilson@cygnus.com)
6*404b540aSrobert 
7*404b540aSrobert This file is part of GCC.
8*404b540aSrobert 
9*404b540aSrobert GCC is free software; you can redistribute it and/or modify it under
10*404b540aSrobert the terms of the GNU General Public License as published by the Free
11*404b540aSrobert Software Foundation; either version 2, or (at your option) any later
12*404b540aSrobert version.
13*404b540aSrobert 
14*404b540aSrobert GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15*404b540aSrobert WARRANTY; without even the implied warranty of MERCHANTABILITY or
16*404b540aSrobert FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17*404b540aSrobert for more details.
18*404b540aSrobert 
19*404b540aSrobert You should have received a copy of the GNU General Public License
20*404b540aSrobert along with GCC; see the file COPYING.  If not, write to the Free
21*404b540aSrobert Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
22*404b540aSrobert 02110-1301, USA.  */
23*404b540aSrobert 
24*404b540aSrobert /* This pass implements list scheduling within basic blocks.  It is
25*404b540aSrobert    run twice: (1) after flow analysis, but before register allocation,
26*404b540aSrobert    and (2) after register allocation.
27*404b540aSrobert 
28*404b540aSrobert    The first run performs interblock scheduling, moving insns between
29*404b540aSrobert    different blocks in the same "region", and the second runs only
30*404b540aSrobert    basic block scheduling.
31*404b540aSrobert 
32*404b540aSrobert    Interblock motions performed are useful motions and speculative
33*404b540aSrobert    motions, including speculative loads.  Motions requiring code
34*404b540aSrobert    duplication are not supported.  The identification of motion type
35*404b540aSrobert    and the check for validity of speculative motions requires
36*404b540aSrobert    construction and analysis of the function's control flow graph.
37*404b540aSrobert 
38*404b540aSrobert    The main entry point for this pass is schedule_insns(), called for
39*404b540aSrobert    each function.  The work of the scheduler is organized in three
40*404b540aSrobert    levels: (1) function level: insns are subject to splitting,
41*404b540aSrobert    control-flow-graph is constructed, regions are computed (after
42*404b540aSrobert    reload, each region is of one block), (2) region level: control
43*404b540aSrobert    flow graph attributes required for interblock scheduling are
44*404b540aSrobert    computed (dominators, reachability, etc.), data dependences and
45*404b540aSrobert    priorities are computed, and (3) block level: insns in the block
46*404b540aSrobert    are actually scheduled.  */
47*404b540aSrobert 
48*404b540aSrobert #include "config.h"
49*404b540aSrobert #include "system.h"
50*404b540aSrobert #include "coretypes.h"
51*404b540aSrobert #include "tm.h"
52*404b540aSrobert #include "toplev.h"
53*404b540aSrobert #include "rtl.h"
54*404b540aSrobert #include "tm_p.h"
55*404b540aSrobert #include "hard-reg-set.h"
56*404b540aSrobert #include "regs.h"
57*404b540aSrobert #include "function.h"
58*404b540aSrobert #include "flags.h"
59*404b540aSrobert #include "insn-config.h"
60*404b540aSrobert #include "insn-attr.h"
61*404b540aSrobert #include "except.h"
62*404b540aSrobert #include "toplev.h"
63*404b540aSrobert #include "recog.h"
64*404b540aSrobert #include "cfglayout.h"
65*404b540aSrobert #include "params.h"
66*404b540aSrobert #include "sched-int.h"
67*404b540aSrobert #include "target.h"
68*404b540aSrobert #include "timevar.h"
69*404b540aSrobert #include "tree-pass.h"
70*404b540aSrobert 
71*404b540aSrobert /* Define when we want to do count REG_DEAD notes before and after scheduling
72*404b540aSrobert    for sanity checking.  We can't do that when conditional execution is used,
73*404b540aSrobert    as REG_DEAD exist only for unconditional deaths.  */
74*404b540aSrobert 
75*404b540aSrobert #if !defined (HAVE_conditional_execution) && defined (ENABLE_CHECKING)
76*404b540aSrobert #define CHECK_DEAD_NOTES 1
77*404b540aSrobert #else
78*404b540aSrobert #define CHECK_DEAD_NOTES 0
79*404b540aSrobert #endif
80*404b540aSrobert 
81*404b540aSrobert 
82*404b540aSrobert #ifdef INSN_SCHEDULING
83*404b540aSrobert /* Some accessor macros for h_i_d members only used within this file.  */
84*404b540aSrobert #define INSN_REF_COUNT(INSN)	(h_i_d[INSN_UID (INSN)].ref_count)
85*404b540aSrobert #define FED_BY_SPEC_LOAD(insn)	(h_i_d[INSN_UID (insn)].fed_by_spec_load)
86*404b540aSrobert #define IS_LOAD_INSN(insn)	(h_i_d[INSN_UID (insn)].is_load_insn)
87*404b540aSrobert 
88*404b540aSrobert /* nr_inter/spec counts interblock/speculative motion for the function.  */
89*404b540aSrobert static int nr_inter, nr_spec;
90*404b540aSrobert 
91*404b540aSrobert static int is_cfg_nonregular (void);
92*404b540aSrobert static bool sched_is_disabled_for_current_region_p (void);
93*404b540aSrobert 
94*404b540aSrobert /* A region is the main entity for interblock scheduling: insns
95*404b540aSrobert    are allowed to move between blocks in the same region, along
96*404b540aSrobert    control flow graph edges, in the 'up' direction.  */
97*404b540aSrobert typedef struct
98*404b540aSrobert {
99*404b540aSrobert   /* Number of extended basic blocks in region.  */
100*404b540aSrobert   int rgn_nr_blocks;
101*404b540aSrobert   /* cblocks in the region (actually index in rgn_bb_table).  */
102*404b540aSrobert   int rgn_blocks;
103*404b540aSrobert   /* Dependencies for this region are already computed.  Basically, indicates,
104*404b540aSrobert      that this is a recovery block.  */
105*404b540aSrobert   unsigned int dont_calc_deps : 1;
106*404b540aSrobert   /* This region has at least one non-trivial ebb.  */
107*404b540aSrobert   unsigned int has_real_ebb : 1;
108*404b540aSrobert }
109*404b540aSrobert region;
110*404b540aSrobert 
111*404b540aSrobert /* Number of regions in the procedure.  */
112*404b540aSrobert static int nr_regions;
113*404b540aSrobert 
114*404b540aSrobert /* Table of region descriptions.  */
115*404b540aSrobert static region *rgn_table;
116*404b540aSrobert 
117*404b540aSrobert /* Array of lists of regions' blocks.  */
118*404b540aSrobert static int *rgn_bb_table;
119*404b540aSrobert 
120*404b540aSrobert /* Topological order of blocks in the region (if b2 is reachable from
121*404b540aSrobert    b1, block_to_bb[b2] > block_to_bb[b1]).  Note: A basic block is
122*404b540aSrobert    always referred to by either block or b, while its topological
123*404b540aSrobert    order name (in the region) is referred to by bb.  */
124*404b540aSrobert static int *block_to_bb;
125*404b540aSrobert 
126*404b540aSrobert /* The number of the region containing a block.  */
127*404b540aSrobert static int *containing_rgn;
128*404b540aSrobert 
129*404b540aSrobert /* The minimum probability of reaching a source block so that it will be
130*404b540aSrobert    considered for speculative scheduling.  */
131*404b540aSrobert static int min_spec_prob;
132*404b540aSrobert 
133*404b540aSrobert #define RGN_NR_BLOCKS(rgn) (rgn_table[rgn].rgn_nr_blocks)
134*404b540aSrobert #define RGN_BLOCKS(rgn) (rgn_table[rgn].rgn_blocks)
135*404b540aSrobert #define RGN_DONT_CALC_DEPS(rgn) (rgn_table[rgn].dont_calc_deps)
136*404b540aSrobert #define RGN_HAS_REAL_EBB(rgn) (rgn_table[rgn].has_real_ebb)
137*404b540aSrobert #define BLOCK_TO_BB(block) (block_to_bb[block])
138*404b540aSrobert #define CONTAINING_RGN(block) (containing_rgn[block])
139*404b540aSrobert 
140*404b540aSrobert void debug_regions (void);
141*404b540aSrobert static void find_single_block_region (void);
142*404b540aSrobert static void find_rgns (void);
143*404b540aSrobert static void extend_rgns (int *, int *, sbitmap, int *);
144*404b540aSrobert static bool too_large (int, int *, int *);
145*404b540aSrobert 
146*404b540aSrobert extern void debug_live (int, int);
147*404b540aSrobert 
148*404b540aSrobert /* Blocks of the current region being scheduled.  */
149*404b540aSrobert static int current_nr_blocks;
150*404b540aSrobert static int current_blocks;
151*404b540aSrobert 
152*404b540aSrobert static int rgn_n_insns;
153*404b540aSrobert 
154*404b540aSrobert /* The mapping from ebb to block.  */
155*404b540aSrobert /* ebb_head [i] - is index in rgn_bb_table, while
156*404b540aSrobert    EBB_HEAD (i) - is basic block index.
157*404b540aSrobert    BASIC_BLOCK (EBB_HEAD (i)) - head of ebb.  */
158*404b540aSrobert #define BB_TO_BLOCK(ebb) (rgn_bb_table[ebb_head[ebb]])
159*404b540aSrobert #define EBB_FIRST_BB(ebb) BASIC_BLOCK (BB_TO_BLOCK (ebb))
160*404b540aSrobert #define EBB_LAST_BB(ebb) BASIC_BLOCK (rgn_bb_table[ebb_head[ebb + 1] - 1])
161*404b540aSrobert 
162*404b540aSrobert /* Target info declarations.
163*404b540aSrobert 
164*404b540aSrobert    The block currently being scheduled is referred to as the "target" block,
165*404b540aSrobert    while other blocks in the region from which insns can be moved to the
166*404b540aSrobert    target are called "source" blocks.  The candidate structure holds info
167*404b540aSrobert    about such sources: are they valid?  Speculative?  Etc.  */
168*404b540aSrobert typedef struct
169*404b540aSrobert {
170*404b540aSrobert   basic_block *first_member;
171*404b540aSrobert   int nr_members;
172*404b540aSrobert }
173*404b540aSrobert bblst;
174*404b540aSrobert 
175*404b540aSrobert typedef struct
176*404b540aSrobert {
177*404b540aSrobert   char is_valid;
178*404b540aSrobert   char is_speculative;
179*404b540aSrobert   int src_prob;
180*404b540aSrobert   bblst split_bbs;
181*404b540aSrobert   bblst update_bbs;
182*404b540aSrobert }
183*404b540aSrobert candidate;
184*404b540aSrobert 
185*404b540aSrobert static candidate *candidate_table;
186*404b540aSrobert 
187*404b540aSrobert /* A speculative motion requires checking live information on the path
188*404b540aSrobert    from 'source' to 'target'.  The split blocks are those to be checked.
189*404b540aSrobert    After a speculative motion, live information should be modified in
190*404b540aSrobert    the 'update' blocks.
191*404b540aSrobert 
192*404b540aSrobert    Lists of split and update blocks for each candidate of the current
193*404b540aSrobert    target are in array bblst_table.  */
194*404b540aSrobert static basic_block *bblst_table;
195*404b540aSrobert static int bblst_size, bblst_last;
196*404b540aSrobert 
197*404b540aSrobert #define IS_VALID(src) ( candidate_table[src].is_valid )
198*404b540aSrobert #define IS_SPECULATIVE(src) ( candidate_table[src].is_speculative )
199*404b540aSrobert #define SRC_PROB(src) ( candidate_table[src].src_prob )
200*404b540aSrobert 
201*404b540aSrobert /* The bb being currently scheduled.  */
202*404b540aSrobert static int target_bb;
203*404b540aSrobert 
204*404b540aSrobert /* List of edges.  */
205*404b540aSrobert typedef struct
206*404b540aSrobert {
207*404b540aSrobert   edge *first_member;
208*404b540aSrobert   int nr_members;
209*404b540aSrobert }
210*404b540aSrobert edgelst;
211*404b540aSrobert 
212*404b540aSrobert static edge *edgelst_table;
213*404b540aSrobert static int edgelst_last;
214*404b540aSrobert 
215*404b540aSrobert static void extract_edgelst (sbitmap, edgelst *);
216*404b540aSrobert 
217*404b540aSrobert 
218*404b540aSrobert /* Target info functions.  */
219*404b540aSrobert static void split_edges (int, int, edgelst *);
220*404b540aSrobert static void compute_trg_info (int);
221*404b540aSrobert void debug_candidate (int);
222*404b540aSrobert void debug_candidates (int);
223*404b540aSrobert 
224*404b540aSrobert /* Dominators array: dom[i] contains the sbitmap of dominators of
225*404b540aSrobert    bb i in the region.  */
226*404b540aSrobert static sbitmap *dom;
227*404b540aSrobert 
228*404b540aSrobert /* bb 0 is the only region entry.  */
229*404b540aSrobert #define IS_RGN_ENTRY(bb) (!bb)
230*404b540aSrobert 
231*404b540aSrobert /* Is bb_src dominated by bb_trg.  */
232*404b540aSrobert #define IS_DOMINATED(bb_src, bb_trg)                                 \
233*404b540aSrobert ( TEST_BIT (dom[bb_src], bb_trg) )
234*404b540aSrobert 
235*404b540aSrobert /* Probability: Prob[i] is an int in [0, REG_BR_PROB_BASE] which is
236*404b540aSrobert    the probability of bb i relative to the region entry.  */
237*404b540aSrobert static int *prob;
238*404b540aSrobert 
239*404b540aSrobert /* Bit-set of edges, where bit i stands for edge i.  */
240*404b540aSrobert typedef sbitmap edgeset;
241*404b540aSrobert 
242*404b540aSrobert /* Number of edges in the region.  */
243*404b540aSrobert static int rgn_nr_edges;
244*404b540aSrobert 
245*404b540aSrobert /* Array of size rgn_nr_edges.  */
246*404b540aSrobert static edge *rgn_edges;
247*404b540aSrobert 
248*404b540aSrobert /* Mapping from each edge in the graph to its number in the rgn.  */
249*404b540aSrobert #define EDGE_TO_BIT(edge) ((int)(size_t)(edge)->aux)
250*404b540aSrobert #define SET_EDGE_TO_BIT(edge,nr) ((edge)->aux = (void *)(size_t)(nr))
251*404b540aSrobert 
252*404b540aSrobert /* The split edges of a source bb is different for each target
253*404b540aSrobert    bb.  In order to compute this efficiently, the 'potential-split edges'
254*404b540aSrobert    are computed for each bb prior to scheduling a region.  This is actually
255*404b540aSrobert    the split edges of each bb relative to the region entry.
256*404b540aSrobert 
257*404b540aSrobert    pot_split[bb] is the set of potential split edges of bb.  */
258*404b540aSrobert static edgeset *pot_split;
259*404b540aSrobert 
260*404b540aSrobert /* For every bb, a set of its ancestor edges.  */
261*404b540aSrobert static edgeset *ancestor_edges;
262*404b540aSrobert 
263*404b540aSrobert /* Array of EBBs sizes.  Currently we can get a ebb only through
264*404b540aSrobert    splitting of currently scheduling block, therefore, we don't need
265*404b540aSrobert    ebb_head array for every region, its sufficient to hold it only
266*404b540aSrobert    for current one.  */
267*404b540aSrobert static int *ebb_head;
268*404b540aSrobert 
269*404b540aSrobert static void compute_dom_prob_ps (int);
270*404b540aSrobert 
271*404b540aSrobert #define INSN_PROBABILITY(INSN) (SRC_PROB (BLOCK_TO_BB (BLOCK_NUM (INSN))))
272*404b540aSrobert #define IS_SPECULATIVE_INSN(INSN) (IS_SPECULATIVE (BLOCK_TO_BB (BLOCK_NUM (INSN))))
273*404b540aSrobert #define INSN_BB(INSN) (BLOCK_TO_BB (BLOCK_NUM (INSN)))
274*404b540aSrobert 
275*404b540aSrobert /* Speculative scheduling functions.  */
276*404b540aSrobert static int check_live_1 (int, rtx);
277*404b540aSrobert static void update_live_1 (int, rtx);
278*404b540aSrobert static int check_live (rtx, int);
279*404b540aSrobert static void update_live (rtx, int);
280*404b540aSrobert static void set_spec_fed (rtx);
281*404b540aSrobert static int is_pfree (rtx, int, int);
282*404b540aSrobert static int find_conditional_protection (rtx, int);
283*404b540aSrobert static int is_conditionally_protected (rtx, int, int);
284*404b540aSrobert static int is_prisky (rtx, int, int);
285*404b540aSrobert static int is_exception_free (rtx, int, int);
286*404b540aSrobert 
287*404b540aSrobert static bool sets_likely_spilled (rtx);
288*404b540aSrobert static void sets_likely_spilled_1 (rtx, rtx, void *);
289*404b540aSrobert static void add_branch_dependences (rtx, rtx);
290*404b540aSrobert static void compute_block_backward_dependences (int);
291*404b540aSrobert void debug_dependencies (void);
292*404b540aSrobert 
293*404b540aSrobert static void init_regions (void);
294*404b540aSrobert static void schedule_region (int);
295*404b540aSrobert static rtx concat_INSN_LIST (rtx, rtx);
296*404b540aSrobert static void concat_insn_mem_list (rtx, rtx, rtx *, rtx *);
297*404b540aSrobert static void propagate_deps (int, struct deps *);
298*404b540aSrobert static void free_pending_lists (void);
299*404b540aSrobert 
300*404b540aSrobert /* Functions for construction of the control flow graph.  */
301*404b540aSrobert 
302*404b540aSrobert /* Return 1 if control flow graph should not be constructed, 0 otherwise.
303*404b540aSrobert 
304*404b540aSrobert    We decide not to build the control flow graph if there is possibly more
305*404b540aSrobert    than one entry to the function, if computed branches exist, if we
306*404b540aSrobert    have nonlocal gotos, or if we have an unreachable loop.  */
307*404b540aSrobert 
308*404b540aSrobert static int
is_cfg_nonregular(void)309*404b540aSrobert is_cfg_nonregular (void)
310*404b540aSrobert {
311*404b540aSrobert   basic_block b;
312*404b540aSrobert   rtx insn;
313*404b540aSrobert 
314*404b540aSrobert   /* If we have a label that could be the target of a nonlocal goto, then
315*404b540aSrobert      the cfg is not well structured.  */
316*404b540aSrobert   if (nonlocal_goto_handler_labels)
317*404b540aSrobert     return 1;
318*404b540aSrobert 
319*404b540aSrobert   /* If we have any forced labels, then the cfg is not well structured.  */
320*404b540aSrobert   if (forced_labels)
321*404b540aSrobert     return 1;
322*404b540aSrobert 
323*404b540aSrobert   /* If we have exception handlers, then we consider the cfg not well
324*404b540aSrobert      structured.  ?!?  We should be able to handle this now that flow.c
325*404b540aSrobert      computes an accurate cfg for EH.  */
326*404b540aSrobert   if (current_function_has_exception_handlers ())
327*404b540aSrobert     return 1;
328*404b540aSrobert 
329*404b540aSrobert   /* If we have non-jumping insns which refer to labels, then we consider
330*404b540aSrobert      the cfg not well structured.  */
331*404b540aSrobert   FOR_EACH_BB (b)
332*404b540aSrobert     FOR_BB_INSNS (b, insn)
333*404b540aSrobert       {
334*404b540aSrobert 	/* Check for labels referred by non-jump insns.  */
335*404b540aSrobert 	if (NONJUMP_INSN_P (insn) || CALL_P (insn))
336*404b540aSrobert 	  {
337*404b540aSrobert 	    rtx note = find_reg_note (insn, REG_LABEL, NULL_RTX);
338*404b540aSrobert 	    if (note
339*404b540aSrobert 		&& ! (JUMP_P (NEXT_INSN (insn))
340*404b540aSrobert 		      && find_reg_note (NEXT_INSN (insn), REG_LABEL,
341*404b540aSrobert 					XEXP (note, 0))))
342*404b540aSrobert 	      return 1;
343*404b540aSrobert 	  }
344*404b540aSrobert 	/* If this function has a computed jump, then we consider the cfg
345*404b540aSrobert 	   not well structured.  */
346*404b540aSrobert 	else if (JUMP_P (insn) && computed_jump_p (insn))
347*404b540aSrobert 	  return 1;
348*404b540aSrobert       }
349*404b540aSrobert 
350*404b540aSrobert   /* Unreachable loops with more than one basic block are detected
351*404b540aSrobert      during the DFS traversal in find_rgns.
352*404b540aSrobert 
353*404b540aSrobert      Unreachable loops with a single block are detected here.  This
354*404b540aSrobert      test is redundant with the one in find_rgns, but it's much
355*404b540aSrobert      cheaper to go ahead and catch the trivial case here.  */
356*404b540aSrobert   FOR_EACH_BB (b)
357*404b540aSrobert     {
358*404b540aSrobert       if (EDGE_COUNT (b->preds) == 0
359*404b540aSrobert 	  || (single_pred_p (b)
360*404b540aSrobert 	      && single_pred (b) == b))
361*404b540aSrobert 	return 1;
362*404b540aSrobert     }
363*404b540aSrobert 
364*404b540aSrobert   /* All the tests passed.  Consider the cfg well structured.  */
365*404b540aSrobert   return 0;
366*404b540aSrobert }
367*404b540aSrobert 
368*404b540aSrobert /* Extract list of edges from a bitmap containing EDGE_TO_BIT bits.  */
369*404b540aSrobert 
370*404b540aSrobert static void
extract_edgelst(sbitmap set,edgelst * el)371*404b540aSrobert extract_edgelst (sbitmap set, edgelst *el)
372*404b540aSrobert {
373*404b540aSrobert   unsigned int i = 0;
374*404b540aSrobert   sbitmap_iterator sbi;
375*404b540aSrobert 
376*404b540aSrobert   /* edgelst table space is reused in each call to extract_edgelst.  */
377*404b540aSrobert   edgelst_last = 0;
378*404b540aSrobert 
379*404b540aSrobert   el->first_member = &edgelst_table[edgelst_last];
380*404b540aSrobert   el->nr_members = 0;
381*404b540aSrobert 
382*404b540aSrobert   /* Iterate over each word in the bitset.  */
383*404b540aSrobert   EXECUTE_IF_SET_IN_SBITMAP (set, 0, i, sbi)
384*404b540aSrobert     {
385*404b540aSrobert       edgelst_table[edgelst_last++] = rgn_edges[i];
386*404b540aSrobert       el->nr_members++;
387*404b540aSrobert     }
388*404b540aSrobert }
389*404b540aSrobert 
390*404b540aSrobert /* Functions for the construction of regions.  */
391*404b540aSrobert 
392*404b540aSrobert /* Print the regions, for debugging purposes.  Callable from debugger.  */
393*404b540aSrobert 
394*404b540aSrobert void
debug_regions(void)395*404b540aSrobert debug_regions (void)
396*404b540aSrobert {
397*404b540aSrobert   int rgn, bb;
398*404b540aSrobert 
399*404b540aSrobert   fprintf (sched_dump, "\n;;   ------------ REGIONS ----------\n\n");
400*404b540aSrobert   for (rgn = 0; rgn < nr_regions; rgn++)
401*404b540aSrobert     {
402*404b540aSrobert       fprintf (sched_dump, ";;\trgn %d nr_blocks %d:\n", rgn,
403*404b540aSrobert 	       rgn_table[rgn].rgn_nr_blocks);
404*404b540aSrobert       fprintf (sched_dump, ";;\tbb/block: ");
405*404b540aSrobert 
406*404b540aSrobert       /* We don't have ebb_head initialized yet, so we can't use
407*404b540aSrobert 	 BB_TO_BLOCK ().  */
408*404b540aSrobert       current_blocks = RGN_BLOCKS (rgn);
409*404b540aSrobert 
410*404b540aSrobert       for (bb = 0; bb < rgn_table[rgn].rgn_nr_blocks; bb++)
411*404b540aSrobert 	fprintf (sched_dump, " %d/%d ", bb, rgn_bb_table[current_blocks + bb]);
412*404b540aSrobert 
413*404b540aSrobert       fprintf (sched_dump, "\n\n");
414*404b540aSrobert     }
415*404b540aSrobert }
416*404b540aSrobert 
417*404b540aSrobert /* Build a single block region for each basic block in the function.
418*404b540aSrobert    This allows for using the same code for interblock and basic block
419*404b540aSrobert    scheduling.  */
420*404b540aSrobert 
421*404b540aSrobert static void
find_single_block_region(void)422*404b540aSrobert find_single_block_region (void)
423*404b540aSrobert {
424*404b540aSrobert   basic_block bb;
425*404b540aSrobert 
426*404b540aSrobert   nr_regions = 0;
427*404b540aSrobert 
428*404b540aSrobert   FOR_EACH_BB (bb)
429*404b540aSrobert     {
430*404b540aSrobert       rgn_bb_table[nr_regions] = bb->index;
431*404b540aSrobert       RGN_NR_BLOCKS (nr_regions) = 1;
432*404b540aSrobert       RGN_BLOCKS (nr_regions) = nr_regions;
433*404b540aSrobert       RGN_DONT_CALC_DEPS (nr_regions) = 0;
434*404b540aSrobert       RGN_HAS_REAL_EBB (nr_regions) = 0;
435*404b540aSrobert       CONTAINING_RGN (bb->index) = nr_regions;
436*404b540aSrobert       BLOCK_TO_BB (bb->index) = 0;
437*404b540aSrobert       nr_regions++;
438*404b540aSrobert     }
439*404b540aSrobert }
440*404b540aSrobert 
441*404b540aSrobert /* Update number of blocks and the estimate for number of insns
442*404b540aSrobert    in the region.  Return true if the region is "too large" for interblock
443*404b540aSrobert    scheduling (compile time considerations).  */
444*404b540aSrobert 
445*404b540aSrobert static bool
too_large(int block,int * num_bbs,int * num_insns)446*404b540aSrobert too_large (int block, int *num_bbs, int *num_insns)
447*404b540aSrobert {
448*404b540aSrobert   (*num_bbs)++;
449*404b540aSrobert   (*num_insns) += (INSN_LUID (BB_END (BASIC_BLOCK (block)))
450*404b540aSrobert 		   - INSN_LUID (BB_HEAD (BASIC_BLOCK (block))));
451*404b540aSrobert 
452*404b540aSrobert   return ((*num_bbs > PARAM_VALUE (PARAM_MAX_SCHED_REGION_BLOCKS))
453*404b540aSrobert 	  || (*num_insns > PARAM_VALUE (PARAM_MAX_SCHED_REGION_INSNS)));
454*404b540aSrobert }
455*404b540aSrobert 
456*404b540aSrobert /* Update_loop_relations(blk, hdr): Check if the loop headed by max_hdr[blk]
457*404b540aSrobert    is still an inner loop.  Put in max_hdr[blk] the header of the most inner
458*404b540aSrobert    loop containing blk.  */
459*404b540aSrobert #define UPDATE_LOOP_RELATIONS(blk, hdr)		\
460*404b540aSrobert {						\
461*404b540aSrobert   if (max_hdr[blk] == -1)			\
462*404b540aSrobert     max_hdr[blk] = hdr;				\
463*404b540aSrobert   else if (dfs_nr[max_hdr[blk]] > dfs_nr[hdr])	\
464*404b540aSrobert     RESET_BIT (inner, hdr);			\
465*404b540aSrobert   else if (dfs_nr[max_hdr[blk]] < dfs_nr[hdr])	\
466*404b540aSrobert     {						\
467*404b540aSrobert       RESET_BIT (inner,max_hdr[blk]);		\
468*404b540aSrobert       max_hdr[blk] = hdr;			\
469*404b540aSrobert     }						\
470*404b540aSrobert }
471*404b540aSrobert 
472*404b540aSrobert /* Find regions for interblock scheduling.
473*404b540aSrobert 
474*404b540aSrobert    A region for scheduling can be:
475*404b540aSrobert 
476*404b540aSrobert      * A loop-free procedure, or
477*404b540aSrobert 
478*404b540aSrobert      * A reducible inner loop, or
479*404b540aSrobert 
480*404b540aSrobert      * A basic block not contained in any other region.
481*404b540aSrobert 
482*404b540aSrobert    ?!? In theory we could build other regions based on extended basic
483*404b540aSrobert    blocks or reverse extended basic blocks.  Is it worth the trouble?
484*404b540aSrobert 
485*404b540aSrobert    Loop blocks that form a region are put into the region's block list
486*404b540aSrobert    in topological order.
487*404b540aSrobert 
488*404b540aSrobert    This procedure stores its results into the following global (ick) variables
489*404b540aSrobert 
490*404b540aSrobert      * rgn_nr
491*404b540aSrobert      * rgn_table
492*404b540aSrobert      * rgn_bb_table
493*404b540aSrobert      * block_to_bb
494*404b540aSrobert      * containing region
495*404b540aSrobert 
496*404b540aSrobert    We use dominator relationships to avoid making regions out of non-reducible
497*404b540aSrobert    loops.
498*404b540aSrobert 
499*404b540aSrobert    This procedure needs to be converted to work on pred/succ lists instead
500*404b540aSrobert    of edge tables.  That would simplify it somewhat.  */
501*404b540aSrobert 
502*404b540aSrobert static void
find_rgns(void)503*404b540aSrobert find_rgns (void)
504*404b540aSrobert {
505*404b540aSrobert   int *max_hdr, *dfs_nr, *degree;
506*404b540aSrobert   char no_loops = 1;
507*404b540aSrobert   int node, child, loop_head, i, head, tail;
508*404b540aSrobert   int count = 0, sp, idx = 0;
509*404b540aSrobert   edge_iterator current_edge;
510*404b540aSrobert   edge_iterator *stack;
511*404b540aSrobert   int num_bbs, num_insns, unreachable;
512*404b540aSrobert   int too_large_failure;
513*404b540aSrobert   basic_block bb;
514*404b540aSrobert 
515*404b540aSrobert   /* Note if a block is a natural loop header.  */
516*404b540aSrobert   sbitmap header;
517*404b540aSrobert 
518*404b540aSrobert   /* Note if a block is a natural inner loop header.  */
519*404b540aSrobert   sbitmap inner;
520*404b540aSrobert 
521*404b540aSrobert   /* Note if a block is in the block queue.  */
522*404b540aSrobert   sbitmap in_queue;
523*404b540aSrobert 
524*404b540aSrobert   /* Note if a block is in the block queue.  */
525*404b540aSrobert   sbitmap in_stack;
526*404b540aSrobert 
527*404b540aSrobert   /* Perform a DFS traversal of the cfg.  Identify loop headers, inner loops
528*404b540aSrobert      and a mapping from block to its loop header (if the block is contained
529*404b540aSrobert      in a loop, else -1).
530*404b540aSrobert 
531*404b540aSrobert      Store results in HEADER, INNER, and MAX_HDR respectively, these will
532*404b540aSrobert      be used as inputs to the second traversal.
533*404b540aSrobert 
534*404b540aSrobert      STACK, SP and DFS_NR are only used during the first traversal.  */
535*404b540aSrobert 
536*404b540aSrobert   /* Allocate and initialize variables for the first traversal.  */
537*404b540aSrobert   max_hdr = XNEWVEC (int, last_basic_block);
538*404b540aSrobert   dfs_nr = XCNEWVEC (int, last_basic_block);
539*404b540aSrobert   stack = XNEWVEC (edge_iterator, n_edges);
540*404b540aSrobert 
541*404b540aSrobert   inner = sbitmap_alloc (last_basic_block);
542*404b540aSrobert   sbitmap_ones (inner);
543*404b540aSrobert 
544*404b540aSrobert   header = sbitmap_alloc (last_basic_block);
545*404b540aSrobert   sbitmap_zero (header);
546*404b540aSrobert 
547*404b540aSrobert   in_queue = sbitmap_alloc (last_basic_block);
548*404b540aSrobert   sbitmap_zero (in_queue);
549*404b540aSrobert 
550*404b540aSrobert   in_stack = sbitmap_alloc (last_basic_block);
551*404b540aSrobert   sbitmap_zero (in_stack);
552*404b540aSrobert 
553*404b540aSrobert   for (i = 0; i < last_basic_block; i++)
554*404b540aSrobert     max_hdr[i] = -1;
555*404b540aSrobert 
556*404b540aSrobert   #define EDGE_PASSED(E) (ei_end_p ((E)) || ei_edge ((E))->aux)
557*404b540aSrobert   #define SET_EDGE_PASSED(E) (ei_edge ((E))->aux = ei_edge ((E)))
558*404b540aSrobert 
559*404b540aSrobert   /* DFS traversal to find inner loops in the cfg.  */
560*404b540aSrobert 
561*404b540aSrobert   current_edge = ei_start (single_succ (ENTRY_BLOCK_PTR)->succs);
562*404b540aSrobert   sp = -1;
563*404b540aSrobert 
564*404b540aSrobert   while (1)
565*404b540aSrobert     {
566*404b540aSrobert       if (EDGE_PASSED (current_edge))
567*404b540aSrobert 	{
568*404b540aSrobert 	  /* We have reached a leaf node or a node that was already
569*404b540aSrobert 	     processed.  Pop edges off the stack until we find
570*404b540aSrobert 	     an edge that has not yet been processed.  */
571*404b540aSrobert 	  while (sp >= 0 && EDGE_PASSED (current_edge))
572*404b540aSrobert 	    {
573*404b540aSrobert 	      /* Pop entry off the stack.  */
574*404b540aSrobert 	      current_edge = stack[sp--];
575*404b540aSrobert 	      node = ei_edge (current_edge)->src->index;
576*404b540aSrobert 	      gcc_assert (node != ENTRY_BLOCK);
577*404b540aSrobert 	      child = ei_edge (current_edge)->dest->index;
578*404b540aSrobert 	      gcc_assert (child != EXIT_BLOCK);
579*404b540aSrobert 	      RESET_BIT (in_stack, child);
580*404b540aSrobert 	      if (max_hdr[child] >= 0 && TEST_BIT (in_stack, max_hdr[child]))
581*404b540aSrobert 		UPDATE_LOOP_RELATIONS (node, max_hdr[child]);
582*404b540aSrobert 	      ei_next (&current_edge);
583*404b540aSrobert 	    }
584*404b540aSrobert 
585*404b540aSrobert 	  /* See if have finished the DFS tree traversal.  */
586*404b540aSrobert 	  if (sp < 0 && EDGE_PASSED (current_edge))
587*404b540aSrobert 	    break;
588*404b540aSrobert 
589*404b540aSrobert 	  /* Nope, continue the traversal with the popped node.  */
590*404b540aSrobert 	  continue;
591*404b540aSrobert 	}
592*404b540aSrobert 
593*404b540aSrobert       /* Process a node.  */
594*404b540aSrobert       node = ei_edge (current_edge)->src->index;
595*404b540aSrobert       gcc_assert (node != ENTRY_BLOCK);
596*404b540aSrobert       SET_BIT (in_stack, node);
597*404b540aSrobert       dfs_nr[node] = ++count;
598*404b540aSrobert 
599*404b540aSrobert       /* We don't traverse to the exit block.  */
600*404b540aSrobert       child = ei_edge (current_edge)->dest->index;
601*404b540aSrobert       if (child == EXIT_BLOCK)
602*404b540aSrobert 	{
603*404b540aSrobert 	  SET_EDGE_PASSED (current_edge);
604*404b540aSrobert 	  ei_next (&current_edge);
605*404b540aSrobert 	  continue;
606*404b540aSrobert 	}
607*404b540aSrobert 
608*404b540aSrobert       /* If the successor is in the stack, then we've found a loop.
609*404b540aSrobert 	 Mark the loop, if it is not a natural loop, then it will
610*404b540aSrobert 	 be rejected during the second traversal.  */
611*404b540aSrobert       if (TEST_BIT (in_stack, child))
612*404b540aSrobert 	{
613*404b540aSrobert 	  no_loops = 0;
614*404b540aSrobert 	  SET_BIT (header, child);
615*404b540aSrobert 	  UPDATE_LOOP_RELATIONS (node, child);
616*404b540aSrobert 	  SET_EDGE_PASSED (current_edge);
617*404b540aSrobert 	  ei_next (&current_edge);
618*404b540aSrobert 	  continue;
619*404b540aSrobert 	}
620*404b540aSrobert 
621*404b540aSrobert       /* If the child was already visited, then there is no need to visit
622*404b540aSrobert 	 it again.  Just update the loop relationships and restart
623*404b540aSrobert 	 with a new edge.  */
624*404b540aSrobert       if (dfs_nr[child])
625*404b540aSrobert 	{
626*404b540aSrobert 	  if (max_hdr[child] >= 0 && TEST_BIT (in_stack, max_hdr[child]))
627*404b540aSrobert 	    UPDATE_LOOP_RELATIONS (node, max_hdr[child]);
628*404b540aSrobert 	  SET_EDGE_PASSED (current_edge);
629*404b540aSrobert 	  ei_next (&current_edge);
630*404b540aSrobert 	  continue;
631*404b540aSrobert 	}
632*404b540aSrobert 
633*404b540aSrobert       /* Push an entry on the stack and continue DFS traversal.  */
634*404b540aSrobert       stack[++sp] = current_edge;
635*404b540aSrobert       SET_EDGE_PASSED (current_edge);
636*404b540aSrobert       current_edge = ei_start (ei_edge (current_edge)->dest->succs);
637*404b540aSrobert     }
638*404b540aSrobert 
639*404b540aSrobert   /* Reset ->aux field used by EDGE_PASSED.  */
640*404b540aSrobert   FOR_ALL_BB (bb)
641*404b540aSrobert     {
642*404b540aSrobert       edge_iterator ei;
643*404b540aSrobert       edge e;
644*404b540aSrobert       FOR_EACH_EDGE (e, ei, bb->succs)
645*404b540aSrobert 	e->aux = NULL;
646*404b540aSrobert     }
647*404b540aSrobert 
648*404b540aSrobert 
649*404b540aSrobert   /* Another check for unreachable blocks.  The earlier test in
650*404b540aSrobert      is_cfg_nonregular only finds unreachable blocks that do not
651*404b540aSrobert      form a loop.
652*404b540aSrobert 
653*404b540aSrobert      The DFS traversal will mark every block that is reachable from
654*404b540aSrobert      the entry node by placing a nonzero value in dfs_nr.  Thus if
655*404b540aSrobert      dfs_nr is zero for any block, then it must be unreachable.  */
656*404b540aSrobert   unreachable = 0;
657*404b540aSrobert   FOR_EACH_BB (bb)
658*404b540aSrobert     if (dfs_nr[bb->index] == 0)
659*404b540aSrobert       {
660*404b540aSrobert 	unreachable = 1;
661*404b540aSrobert 	break;
662*404b540aSrobert       }
663*404b540aSrobert 
664*404b540aSrobert   /* Gross.  To avoid wasting memory, the second pass uses the dfs_nr array
665*404b540aSrobert      to hold degree counts.  */
666*404b540aSrobert   degree = dfs_nr;
667*404b540aSrobert 
668*404b540aSrobert   FOR_EACH_BB (bb)
669*404b540aSrobert     degree[bb->index] = EDGE_COUNT (bb->preds);
670*404b540aSrobert 
671*404b540aSrobert   /* Do not perform region scheduling if there are any unreachable
672*404b540aSrobert      blocks.  */
673*404b540aSrobert   if (!unreachable)
674*404b540aSrobert     {
675*404b540aSrobert       int *queue, *degree1 = NULL;
676*404b540aSrobert       /* We use EXTENDED_RGN_HEADER as an addition to HEADER and put
677*404b540aSrobert 	 there basic blocks, which are forced to be region heads.
678*404b540aSrobert 	 This is done to try to assemble few smaller regions
679*404b540aSrobert 	 from a too_large region.  */
680*404b540aSrobert       sbitmap extended_rgn_header = NULL;
681*404b540aSrobert       bool extend_regions_p;
682*404b540aSrobert 
683*404b540aSrobert       if (no_loops)
684*404b540aSrobert 	SET_BIT (header, 0);
685*404b540aSrobert 
686*404b540aSrobert       /* Second traversal:find reducible inner loops and topologically sort
687*404b540aSrobert 	 block of each region.  */
688*404b540aSrobert 
689*404b540aSrobert       queue = XNEWVEC (int, n_basic_blocks);
690*404b540aSrobert 
691*404b540aSrobert       extend_regions_p = PARAM_VALUE (PARAM_MAX_SCHED_EXTEND_REGIONS_ITERS) > 0;
692*404b540aSrobert       if (extend_regions_p)
693*404b540aSrobert         {
694*404b540aSrobert           degree1 = xmalloc (last_basic_block * sizeof (int));
695*404b540aSrobert           extended_rgn_header = sbitmap_alloc (last_basic_block);
696*404b540aSrobert           sbitmap_zero (extended_rgn_header);
697*404b540aSrobert 	}
698*404b540aSrobert 
699*404b540aSrobert       /* Find blocks which are inner loop headers.  We still have non-reducible
700*404b540aSrobert 	 loops to consider at this point.  */
701*404b540aSrobert       FOR_EACH_BB (bb)
702*404b540aSrobert 	{
703*404b540aSrobert 	  if (TEST_BIT (header, bb->index) && TEST_BIT (inner, bb->index))
704*404b540aSrobert 	    {
705*404b540aSrobert 	      edge e;
706*404b540aSrobert 	      edge_iterator ei;
707*404b540aSrobert 	      basic_block jbb;
708*404b540aSrobert 
709*404b540aSrobert 	      /* Now check that the loop is reducible.  We do this separate
710*404b540aSrobert 		 from finding inner loops so that we do not find a reducible
711*404b540aSrobert 		 loop which contains an inner non-reducible loop.
712*404b540aSrobert 
713*404b540aSrobert 		 A simple way to find reducible/natural loops is to verify
714*404b540aSrobert 		 that each block in the loop is dominated by the loop
715*404b540aSrobert 		 header.
716*404b540aSrobert 
717*404b540aSrobert 		 If there exists a block that is not dominated by the loop
718*404b540aSrobert 		 header, then the block is reachable from outside the loop
719*404b540aSrobert 		 and thus the loop is not a natural loop.  */
720*404b540aSrobert 	      FOR_EACH_BB (jbb)
721*404b540aSrobert 		{
722*404b540aSrobert 		  /* First identify blocks in the loop, except for the loop
723*404b540aSrobert 		     entry block.  */
724*404b540aSrobert 		  if (bb->index == max_hdr[jbb->index] && bb != jbb)
725*404b540aSrobert 		    {
726*404b540aSrobert 		      /* Now verify that the block is dominated by the loop
727*404b540aSrobert 			 header.  */
728*404b540aSrobert 		      if (!dominated_by_p (CDI_DOMINATORS, jbb, bb))
729*404b540aSrobert 			break;
730*404b540aSrobert 		    }
731*404b540aSrobert 		}
732*404b540aSrobert 
733*404b540aSrobert 	      /* If we exited the loop early, then I is the header of
734*404b540aSrobert 		 a non-reducible loop and we should quit processing it
735*404b540aSrobert 		 now.  */
736*404b540aSrobert 	      if (jbb != EXIT_BLOCK_PTR)
737*404b540aSrobert 		continue;
738*404b540aSrobert 
739*404b540aSrobert 	      /* I is a header of an inner loop, or block 0 in a subroutine
740*404b540aSrobert 		 with no loops at all.  */
741*404b540aSrobert 	      head = tail = -1;
742*404b540aSrobert 	      too_large_failure = 0;
743*404b540aSrobert 	      loop_head = max_hdr[bb->index];
744*404b540aSrobert 
745*404b540aSrobert               if (extend_regions_p)
746*404b540aSrobert                 /* We save degree in case when we meet a too_large region
747*404b540aSrobert 		   and cancel it.  We need a correct degree later when
748*404b540aSrobert                    calling extend_rgns.  */
749*404b540aSrobert                 memcpy (degree1, degree, last_basic_block * sizeof (int));
750*404b540aSrobert 
751*404b540aSrobert 	      /* Decrease degree of all I's successors for topological
752*404b540aSrobert 		 ordering.  */
753*404b540aSrobert 	      FOR_EACH_EDGE (e, ei, bb->succs)
754*404b540aSrobert 		if (e->dest != EXIT_BLOCK_PTR)
755*404b540aSrobert 		  --degree[e->dest->index];
756*404b540aSrobert 
757*404b540aSrobert 	      /* Estimate # insns, and count # blocks in the region.  */
758*404b540aSrobert 	      num_bbs = 1;
759*404b540aSrobert 	      num_insns = (INSN_LUID (BB_END (bb))
760*404b540aSrobert 			   - INSN_LUID (BB_HEAD (bb)));
761*404b540aSrobert 
762*404b540aSrobert 	      /* Find all loop latches (blocks with back edges to the loop
763*404b540aSrobert 		 header) or all the leaf blocks in the cfg has no loops.
764*404b540aSrobert 
765*404b540aSrobert 		 Place those blocks into the queue.  */
766*404b540aSrobert 	      if (no_loops)
767*404b540aSrobert 		{
768*404b540aSrobert 		  FOR_EACH_BB (jbb)
769*404b540aSrobert 		    /* Leaf nodes have only a single successor which must
770*404b540aSrobert 		       be EXIT_BLOCK.  */
771*404b540aSrobert 		    if (single_succ_p (jbb)
772*404b540aSrobert 			&& single_succ (jbb) == EXIT_BLOCK_PTR)
773*404b540aSrobert 		      {
774*404b540aSrobert 			queue[++tail] = jbb->index;
775*404b540aSrobert 			SET_BIT (in_queue, jbb->index);
776*404b540aSrobert 
777*404b540aSrobert 			if (too_large (jbb->index, &num_bbs, &num_insns))
778*404b540aSrobert 			  {
779*404b540aSrobert 			    too_large_failure = 1;
780*404b540aSrobert 			    break;
781*404b540aSrobert 			  }
782*404b540aSrobert 		      }
783*404b540aSrobert 		}
784*404b540aSrobert 	      else
785*404b540aSrobert 		{
786*404b540aSrobert 		  edge e;
787*404b540aSrobert 
788*404b540aSrobert 		  FOR_EACH_EDGE (e, ei, bb->preds)
789*404b540aSrobert 		    {
790*404b540aSrobert 		      if (e->src == ENTRY_BLOCK_PTR)
791*404b540aSrobert 			continue;
792*404b540aSrobert 
793*404b540aSrobert 		      node = e->src->index;
794*404b540aSrobert 
795*404b540aSrobert 		      if (max_hdr[node] == loop_head && node != bb->index)
796*404b540aSrobert 			{
797*404b540aSrobert 			  /* This is a loop latch.  */
798*404b540aSrobert 			  queue[++tail] = node;
799*404b540aSrobert 			  SET_BIT (in_queue, node);
800*404b540aSrobert 
801*404b540aSrobert 			  if (too_large (node, &num_bbs, &num_insns))
802*404b540aSrobert 			    {
803*404b540aSrobert 			      too_large_failure = 1;
804*404b540aSrobert 			      break;
805*404b540aSrobert 			    }
806*404b540aSrobert 			}
807*404b540aSrobert 		    }
808*404b540aSrobert 		}
809*404b540aSrobert 
810*404b540aSrobert 	      /* Now add all the blocks in the loop to the queue.
811*404b540aSrobert 
812*404b540aSrobert 	     We know the loop is a natural loop; however the algorithm
813*404b540aSrobert 	     above will not always mark certain blocks as being in the
814*404b540aSrobert 	     loop.  Consider:
815*404b540aSrobert 		node   children
816*404b540aSrobert 		 a	  b,c
817*404b540aSrobert 		 b	  c
818*404b540aSrobert 		 c	  a,d
819*404b540aSrobert 		 d	  b
820*404b540aSrobert 
821*404b540aSrobert 	     The algorithm in the DFS traversal may not mark B & D as part
822*404b540aSrobert 	     of the loop (i.e. they will not have max_hdr set to A).
823*404b540aSrobert 
824*404b540aSrobert 	     We know they can not be loop latches (else they would have
825*404b540aSrobert 	     had max_hdr set since they'd have a backedge to a dominator
826*404b540aSrobert 	     block).  So we don't need them on the initial queue.
827*404b540aSrobert 
828*404b540aSrobert 	     We know they are part of the loop because they are dominated
829*404b540aSrobert 	     by the loop header and can be reached by a backwards walk of
830*404b540aSrobert 	     the edges starting with nodes on the initial queue.
831*404b540aSrobert 
832*404b540aSrobert 	     It is safe and desirable to include those nodes in the
833*404b540aSrobert 	     loop/scheduling region.  To do so we would need to decrease
834*404b540aSrobert 	     the degree of a node if it is the target of a backedge
835*404b540aSrobert 	     within the loop itself as the node is placed in the queue.
836*404b540aSrobert 
837*404b540aSrobert 	     We do not do this because I'm not sure that the actual
838*404b540aSrobert 	     scheduling code will properly handle this case. ?!? */
839*404b540aSrobert 
840*404b540aSrobert 	      while (head < tail && !too_large_failure)
841*404b540aSrobert 		{
842*404b540aSrobert 		  edge e;
843*404b540aSrobert 		  child = queue[++head];
844*404b540aSrobert 
845*404b540aSrobert 		  FOR_EACH_EDGE (e, ei, BASIC_BLOCK (child)->preds)
846*404b540aSrobert 		    {
847*404b540aSrobert 		      node = e->src->index;
848*404b540aSrobert 
849*404b540aSrobert 		      /* See discussion above about nodes not marked as in
850*404b540aSrobert 			 this loop during the initial DFS traversal.  */
851*404b540aSrobert 		      if (e->src == ENTRY_BLOCK_PTR
852*404b540aSrobert 			  || max_hdr[node] != loop_head)
853*404b540aSrobert 			{
854*404b540aSrobert 			  tail = -1;
855*404b540aSrobert 			  break;
856*404b540aSrobert 			}
857*404b540aSrobert 		      else if (!TEST_BIT (in_queue, node) && node != bb->index)
858*404b540aSrobert 			{
859*404b540aSrobert 			  queue[++tail] = node;
860*404b540aSrobert 			  SET_BIT (in_queue, node);
861*404b540aSrobert 
862*404b540aSrobert 			  if (too_large (node, &num_bbs, &num_insns))
863*404b540aSrobert 			    {
864*404b540aSrobert 			      too_large_failure = 1;
865*404b540aSrobert 			      break;
866*404b540aSrobert 			    }
867*404b540aSrobert 			}
868*404b540aSrobert 		    }
869*404b540aSrobert 		}
870*404b540aSrobert 
871*404b540aSrobert 	      if (tail >= 0 && !too_large_failure)
872*404b540aSrobert 		{
873*404b540aSrobert 		  /* Place the loop header into list of region blocks.  */
874*404b540aSrobert 		  degree[bb->index] = -1;
875*404b540aSrobert 		  rgn_bb_table[idx] = bb->index;
876*404b540aSrobert 		  RGN_NR_BLOCKS (nr_regions) = num_bbs;
877*404b540aSrobert 		  RGN_BLOCKS (nr_regions) = idx++;
878*404b540aSrobert                   RGN_DONT_CALC_DEPS (nr_regions) = 0;
879*404b540aSrobert 		  RGN_HAS_REAL_EBB (nr_regions) = 0;
880*404b540aSrobert 		  CONTAINING_RGN (bb->index) = nr_regions;
881*404b540aSrobert 		  BLOCK_TO_BB (bb->index) = count = 0;
882*404b540aSrobert 
883*404b540aSrobert 		  /* Remove blocks from queue[] when their in degree
884*404b540aSrobert 		     becomes zero.  Repeat until no blocks are left on the
885*404b540aSrobert 		     list.  This produces a topological list of blocks in
886*404b540aSrobert 		     the region.  */
887*404b540aSrobert 		  while (tail >= 0)
888*404b540aSrobert 		    {
889*404b540aSrobert 		      if (head < 0)
890*404b540aSrobert 			head = tail;
891*404b540aSrobert 		      child = queue[head];
892*404b540aSrobert 		      if (degree[child] == 0)
893*404b540aSrobert 			{
894*404b540aSrobert 			  edge e;
895*404b540aSrobert 
896*404b540aSrobert 			  degree[child] = -1;
897*404b540aSrobert 			  rgn_bb_table[idx++] = child;
898*404b540aSrobert 			  BLOCK_TO_BB (child) = ++count;
899*404b540aSrobert 			  CONTAINING_RGN (child) = nr_regions;
900*404b540aSrobert 			  queue[head] = queue[tail--];
901*404b540aSrobert 
902*404b540aSrobert 			  FOR_EACH_EDGE (e, ei, BASIC_BLOCK (child)->succs)
903*404b540aSrobert 			    if (e->dest != EXIT_BLOCK_PTR)
904*404b540aSrobert 			      --degree[e->dest->index];
905*404b540aSrobert 			}
906*404b540aSrobert 		      else
907*404b540aSrobert 			--head;
908*404b540aSrobert 		    }
909*404b540aSrobert 		  ++nr_regions;
910*404b540aSrobert 		}
911*404b540aSrobert               else if (extend_regions_p)
912*404b540aSrobert                 {
913*404b540aSrobert                   /* Restore DEGREE.  */
914*404b540aSrobert                   int *t = degree;
915*404b540aSrobert 
916*404b540aSrobert                   degree = degree1;
917*404b540aSrobert                   degree1 = t;
918*404b540aSrobert 
919*404b540aSrobert                   /* And force successors of BB to be region heads.
920*404b540aSrobert 		     This may provide several smaller regions instead
921*404b540aSrobert 		     of one too_large region.  */
922*404b540aSrobert                   FOR_EACH_EDGE (e, ei, bb->succs)
923*404b540aSrobert                     if (e->dest != EXIT_BLOCK_PTR)
924*404b540aSrobert                       SET_BIT (extended_rgn_header, e->dest->index);
925*404b540aSrobert                 }
926*404b540aSrobert 	    }
927*404b540aSrobert 	}
928*404b540aSrobert       free (queue);
929*404b540aSrobert 
930*404b540aSrobert       if (extend_regions_p)
931*404b540aSrobert         {
932*404b540aSrobert           free (degree1);
933*404b540aSrobert 
934*404b540aSrobert           sbitmap_a_or_b (header, header, extended_rgn_header);
935*404b540aSrobert           sbitmap_free (extended_rgn_header);
936*404b540aSrobert 
937*404b540aSrobert           extend_rgns (degree, &idx, header, max_hdr);
938*404b540aSrobert         }
939*404b540aSrobert     }
940*404b540aSrobert 
941*404b540aSrobert   /* Any block that did not end up in a region is placed into a region
942*404b540aSrobert      by itself.  */
943*404b540aSrobert   FOR_EACH_BB (bb)
944*404b540aSrobert     if (degree[bb->index] >= 0)
945*404b540aSrobert       {
946*404b540aSrobert 	rgn_bb_table[idx] = bb->index;
947*404b540aSrobert 	RGN_NR_BLOCKS (nr_regions) = 1;
948*404b540aSrobert 	RGN_BLOCKS (nr_regions) = idx++;
949*404b540aSrobert         RGN_DONT_CALC_DEPS (nr_regions) = 0;
950*404b540aSrobert 	RGN_HAS_REAL_EBB (nr_regions) = 0;
951*404b540aSrobert 	CONTAINING_RGN (bb->index) = nr_regions++;
952*404b540aSrobert 	BLOCK_TO_BB (bb->index) = 0;
953*404b540aSrobert       }
954*404b540aSrobert 
955*404b540aSrobert   free (max_hdr);
956*404b540aSrobert   free (degree);
957*404b540aSrobert   free (stack);
958*404b540aSrobert   sbitmap_free (header);
959*404b540aSrobert   sbitmap_free (inner);
960*404b540aSrobert   sbitmap_free (in_queue);
961*404b540aSrobert   sbitmap_free (in_stack);
962*404b540aSrobert }
963*404b540aSrobert 
964*404b540aSrobert static int gather_region_statistics (int **);
965*404b540aSrobert static void print_region_statistics (int *, int, int *, int);
966*404b540aSrobert 
967*404b540aSrobert /* Calculate the histogram that shows the number of regions having the
968*404b540aSrobert    given number of basic blocks, and store it in the RSP array.  Return
969*404b540aSrobert    the size of this array.  */
970*404b540aSrobert static int
gather_region_statistics(int ** rsp)971*404b540aSrobert gather_region_statistics (int **rsp)
972*404b540aSrobert {
973*404b540aSrobert   int i, *a = 0, a_sz = 0;
974*404b540aSrobert 
975*404b540aSrobert   /* a[i] is the number of regions that have (i + 1) basic blocks.  */
976*404b540aSrobert   for (i = 0; i < nr_regions; i++)
977*404b540aSrobert     {
978*404b540aSrobert       int nr_blocks = RGN_NR_BLOCKS (i);
979*404b540aSrobert 
980*404b540aSrobert       gcc_assert (nr_blocks >= 1);
981*404b540aSrobert 
982*404b540aSrobert       if (nr_blocks > a_sz)
983*404b540aSrobert 	{
984*404b540aSrobert 	  a = xrealloc (a, nr_blocks * sizeof (*a));
985*404b540aSrobert 	  do
986*404b540aSrobert 	    a[a_sz++] = 0;
987*404b540aSrobert 	  while (a_sz != nr_blocks);
988*404b540aSrobert 	}
989*404b540aSrobert 
990*404b540aSrobert       a[nr_blocks - 1]++;
991*404b540aSrobert     }
992*404b540aSrobert 
993*404b540aSrobert   *rsp = a;
994*404b540aSrobert   return a_sz;
995*404b540aSrobert }
996*404b540aSrobert 
997*404b540aSrobert /* Print regions statistics.  S1 and S2 denote the data before and after
998*404b540aSrobert    calling extend_rgns, respectively.  */
999*404b540aSrobert static void
print_region_statistics(int * s1,int s1_sz,int * s2,int s2_sz)1000*404b540aSrobert print_region_statistics (int *s1, int s1_sz, int *s2, int s2_sz)
1001*404b540aSrobert {
1002*404b540aSrobert   int i;
1003*404b540aSrobert 
1004*404b540aSrobert   /* We iterate until s2_sz because extend_rgns does not decrease
1005*404b540aSrobert      the maximal region size.  */
1006*404b540aSrobert   for (i = 1; i < s2_sz; i++)
1007*404b540aSrobert     {
1008*404b540aSrobert       int n1, n2;
1009*404b540aSrobert 
1010*404b540aSrobert       n2 = s2[i];
1011*404b540aSrobert 
1012*404b540aSrobert       if (n2 == 0)
1013*404b540aSrobert 	continue;
1014*404b540aSrobert 
1015*404b540aSrobert       if (i >= s1_sz)
1016*404b540aSrobert 	n1 = 0;
1017*404b540aSrobert       else
1018*404b540aSrobert 	n1 = s1[i];
1019*404b540aSrobert 
1020*404b540aSrobert       fprintf (sched_dump, ";; Region extension statistics: size %d: " \
1021*404b540aSrobert 	       "was %d + %d more\n", i + 1, n1, n2 - n1);
1022*404b540aSrobert     }
1023*404b540aSrobert }
1024*404b540aSrobert 
1025*404b540aSrobert /* Extend regions.
1026*404b540aSrobert    DEGREE - Array of incoming edge count, considering only
1027*404b540aSrobert    the edges, that don't have their sources in formed regions yet.
1028*404b540aSrobert    IDXP - pointer to the next available index in rgn_bb_table.
1029*404b540aSrobert    HEADER - set of all region heads.
1030*404b540aSrobert    LOOP_HDR - mapping from block to the containing loop
1031*404b540aSrobert    (two blocks can reside within one region if they have
1032*404b540aSrobert    the same loop header).  */
1033*404b540aSrobert static void
extend_rgns(int * degree,int * idxp,sbitmap header,int * loop_hdr)1034*404b540aSrobert extend_rgns (int *degree, int *idxp, sbitmap header, int *loop_hdr)
1035*404b540aSrobert {
1036*404b540aSrobert   int *order, i, rescan = 0, idx = *idxp, iter = 0, max_iter, *max_hdr;
1037*404b540aSrobert   int nblocks = n_basic_blocks - NUM_FIXED_BLOCKS;
1038*404b540aSrobert 
1039*404b540aSrobert   max_iter = PARAM_VALUE (PARAM_MAX_SCHED_EXTEND_REGIONS_ITERS);
1040*404b540aSrobert 
1041*404b540aSrobert   max_hdr = xmalloc (last_basic_block * sizeof (*max_hdr));
1042*404b540aSrobert 
1043*404b540aSrobert   order = xmalloc (last_basic_block * sizeof (*order));
1044*404b540aSrobert   post_order_compute (order, false);
1045*404b540aSrobert 
1046*404b540aSrobert   for (i = nblocks - 1; i >= 0; i--)
1047*404b540aSrobert     {
1048*404b540aSrobert       int bbn = order[i];
1049*404b540aSrobert       if (degree[bbn] >= 0)
1050*404b540aSrobert 	{
1051*404b540aSrobert 	  max_hdr[bbn] = bbn;
1052*404b540aSrobert 	  rescan = 1;
1053*404b540aSrobert 	}
1054*404b540aSrobert       else
1055*404b540aSrobert         /* This block already was processed in find_rgns.  */
1056*404b540aSrobert         max_hdr[bbn] = -1;
1057*404b540aSrobert     }
1058*404b540aSrobert 
1059*404b540aSrobert   /* The idea is to topologically walk through CFG in top-down order.
1060*404b540aSrobert      During the traversal, if all the predecessors of a node are
1061*404b540aSrobert      marked to be in the same region (they all have the same max_hdr),
1062*404b540aSrobert      then current node is also marked to be a part of that region.
1063*404b540aSrobert      Otherwise the node starts its own region.
1064*404b540aSrobert      CFG should be traversed until no further changes are made.  On each
1065*404b540aSrobert      iteration the set of the region heads is extended (the set of those
1066*404b540aSrobert      blocks that have max_hdr[bbi] == bbi).  This set is upper bounded by the
1067*404b540aSrobert      set of all basic blocks, thus the algorithm is guaranteed to terminate.  */
1068*404b540aSrobert 
1069*404b540aSrobert   while (rescan && iter < max_iter)
1070*404b540aSrobert     {
1071*404b540aSrobert       rescan = 0;
1072*404b540aSrobert 
1073*404b540aSrobert       for (i = nblocks - 1; i >= 0; i--)
1074*404b540aSrobert 	{
1075*404b540aSrobert 	  edge e;
1076*404b540aSrobert 	  edge_iterator ei;
1077*404b540aSrobert 	  int bbn = order[i];
1078*404b540aSrobert 
1079*404b540aSrobert 	  if (max_hdr[bbn] != -1 && !TEST_BIT (header, bbn))
1080*404b540aSrobert 	    {
1081*404b540aSrobert 	      int hdr = -1;
1082*404b540aSrobert 
1083*404b540aSrobert 	      FOR_EACH_EDGE (e, ei, BASIC_BLOCK (bbn)->preds)
1084*404b540aSrobert 		{
1085*404b540aSrobert 		  int predn = e->src->index;
1086*404b540aSrobert 
1087*404b540aSrobert 		  if (predn != ENTRY_BLOCK
1088*404b540aSrobert 		      /* If pred wasn't processed in find_rgns.  */
1089*404b540aSrobert 		      && max_hdr[predn] != -1
1090*404b540aSrobert 		      /* And pred and bb reside in the same loop.
1091*404b540aSrobert 			 (Or out of any loop).  */
1092*404b540aSrobert 		      && loop_hdr[bbn] == loop_hdr[predn])
1093*404b540aSrobert 		    {
1094*404b540aSrobert 		      if (hdr == -1)
1095*404b540aSrobert 			/* Then bb extends the containing region of pred.  */
1096*404b540aSrobert 			hdr = max_hdr[predn];
1097*404b540aSrobert 		      else if (hdr != max_hdr[predn])
1098*404b540aSrobert 			/* Too bad, there are at least two predecessors
1099*404b540aSrobert 			   that reside in different regions.  Thus, BB should
1100*404b540aSrobert 			   begin its own region.  */
1101*404b540aSrobert 			{
1102*404b540aSrobert 			  hdr = bbn;
1103*404b540aSrobert 			  break;
1104*404b540aSrobert 			}
1105*404b540aSrobert 		    }
1106*404b540aSrobert 		  else
1107*404b540aSrobert 		    /* BB starts its own region.  */
1108*404b540aSrobert 		    {
1109*404b540aSrobert 		      hdr = bbn;
1110*404b540aSrobert 		      break;
1111*404b540aSrobert 		    }
1112*404b540aSrobert 		}
1113*404b540aSrobert 
1114*404b540aSrobert 	      if (hdr == bbn)
1115*404b540aSrobert 		{
1116*404b540aSrobert 		  /* If BB start its own region,
1117*404b540aSrobert 		     update set of headers with BB.  */
1118*404b540aSrobert 		  SET_BIT (header, bbn);
1119*404b540aSrobert 		  rescan = 1;
1120*404b540aSrobert 		}
1121*404b540aSrobert 	      else
1122*404b540aSrobert 		gcc_assert (hdr != -1);
1123*404b540aSrobert 
1124*404b540aSrobert 	      max_hdr[bbn] = hdr;
1125*404b540aSrobert 	    }
1126*404b540aSrobert 	}
1127*404b540aSrobert 
1128*404b540aSrobert       iter++;
1129*404b540aSrobert     }
1130*404b540aSrobert 
1131*404b540aSrobert   /* Statistics were gathered on the SPEC2000 package of tests with
1132*404b540aSrobert      mainline weekly snapshot gcc-4.1-20051015 on ia64.
1133*404b540aSrobert 
1134*404b540aSrobert      Statistics for SPECint:
1135*404b540aSrobert      1 iteration : 1751 cases (38.7%)
1136*404b540aSrobert      2 iterations: 2770 cases (61.3%)
1137*404b540aSrobert      Blocks wrapped in regions by find_rgns without extension: 18295 blocks
1138*404b540aSrobert      Blocks wrapped in regions by 2 iterations in extend_rgns: 23821 blocks
1139*404b540aSrobert      (We don't count single block regions here).
1140*404b540aSrobert 
1141*404b540aSrobert      Statistics for SPECfp:
1142*404b540aSrobert      1 iteration : 621 cases (35.9%)
1143*404b540aSrobert      2 iterations: 1110 cases (64.1%)
1144*404b540aSrobert      Blocks wrapped in regions by find_rgns without extension: 6476 blocks
1145*404b540aSrobert      Blocks wrapped in regions by 2 iterations in extend_rgns: 11155 blocks
1146*404b540aSrobert      (We don't count single block regions here).
1147*404b540aSrobert 
1148*404b540aSrobert      By default we do at most 2 iterations.
1149*404b540aSrobert      This can be overridden with max-sched-extend-regions-iters parameter:
1150*404b540aSrobert      0 - disable region extension,
1151*404b540aSrobert      N > 0 - do at most N iterations.  */
1152*404b540aSrobert 
1153*404b540aSrobert   if (sched_verbose && iter != 0)
1154*404b540aSrobert     fprintf (sched_dump, ";; Region extension iterations: %d%s\n", iter,
1155*404b540aSrobert 	     rescan ? "... failed" : "");
1156*404b540aSrobert 
1157*404b540aSrobert   if (!rescan && iter != 0)
1158*404b540aSrobert     {
1159*404b540aSrobert       int *s1 = NULL, s1_sz = 0;
1160*404b540aSrobert 
1161*404b540aSrobert       /* Save the old statistics for later printout.  */
1162*404b540aSrobert       if (sched_verbose >= 6)
1163*404b540aSrobert 	s1_sz = gather_region_statistics (&s1);
1164*404b540aSrobert 
1165*404b540aSrobert       /* We have succeeded.  Now assemble the regions.  */
1166*404b540aSrobert       for (i = nblocks - 1; i >= 0; i--)
1167*404b540aSrobert 	{
1168*404b540aSrobert 	  int bbn = order[i];
1169*404b540aSrobert 
1170*404b540aSrobert 	  if (max_hdr[bbn] == bbn)
1171*404b540aSrobert 	    /* BBN is a region head.  */
1172*404b540aSrobert 	    {
1173*404b540aSrobert 	      edge e;
1174*404b540aSrobert 	      edge_iterator ei;
1175*404b540aSrobert 	      int num_bbs = 0, j, num_insns = 0, large;
1176*404b540aSrobert 
1177*404b540aSrobert 	      large = too_large (bbn, &num_bbs, &num_insns);
1178*404b540aSrobert 
1179*404b540aSrobert 	      degree[bbn] = -1;
1180*404b540aSrobert 	      rgn_bb_table[idx] = bbn;
1181*404b540aSrobert 	      RGN_BLOCKS (nr_regions) = idx++;
1182*404b540aSrobert 	      RGN_DONT_CALC_DEPS (nr_regions) = 0;
1183*404b540aSrobert 	      RGN_HAS_REAL_EBB (nr_regions) = 0;
1184*404b540aSrobert 	      CONTAINING_RGN (bbn) = nr_regions;
1185*404b540aSrobert 	      BLOCK_TO_BB (bbn) = 0;
1186*404b540aSrobert 
1187*404b540aSrobert 	      FOR_EACH_EDGE (e, ei, BASIC_BLOCK (bbn)->succs)
1188*404b540aSrobert 		if (e->dest != EXIT_BLOCK_PTR)
1189*404b540aSrobert 		  degree[e->dest->index]--;
1190*404b540aSrobert 
1191*404b540aSrobert 	      if (!large)
1192*404b540aSrobert 		/* Here we check whether the region is too_large.  */
1193*404b540aSrobert 		for (j = i - 1; j >= 0; j--)
1194*404b540aSrobert 		  {
1195*404b540aSrobert 		    int succn = order[j];
1196*404b540aSrobert 		    if (max_hdr[succn] == bbn)
1197*404b540aSrobert 		      {
1198*404b540aSrobert 			if ((large = too_large (succn, &num_bbs, &num_insns)))
1199*404b540aSrobert 			  break;
1200*404b540aSrobert 		      }
1201*404b540aSrobert 		  }
1202*404b540aSrobert 
1203*404b540aSrobert 	      if (large)
1204*404b540aSrobert 		/* If the region is too_large, then wrap every block of
1205*404b540aSrobert 		   the region into single block region.
1206*404b540aSrobert 		   Here we wrap region head only.  Other blocks are
1207*404b540aSrobert 		   processed in the below cycle.  */
1208*404b540aSrobert 		{
1209*404b540aSrobert 		  RGN_NR_BLOCKS (nr_regions) = 1;
1210*404b540aSrobert 		  nr_regions++;
1211*404b540aSrobert 		}
1212*404b540aSrobert 
1213*404b540aSrobert 	      num_bbs = 1;
1214*404b540aSrobert 
1215*404b540aSrobert 	      for (j = i - 1; j >= 0; j--)
1216*404b540aSrobert 		{
1217*404b540aSrobert 		  int succn = order[j];
1218*404b540aSrobert 
1219*404b540aSrobert 		  if (max_hdr[succn] == bbn)
1220*404b540aSrobert 		    /* This cycle iterates over all basic blocks, that
1221*404b540aSrobert 		       are supposed to be in the region with head BBN,
1222*404b540aSrobert 		       and wraps them into that region (or in single
1223*404b540aSrobert 		       block region).  */
1224*404b540aSrobert 		    {
1225*404b540aSrobert 		      gcc_assert (degree[succn] == 0);
1226*404b540aSrobert 
1227*404b540aSrobert 		      degree[succn] = -1;
1228*404b540aSrobert 		      rgn_bb_table[idx] = succn;
1229*404b540aSrobert 		      BLOCK_TO_BB (succn) = large ? 0 : num_bbs++;
1230*404b540aSrobert 		      CONTAINING_RGN (succn) = nr_regions;
1231*404b540aSrobert 
1232*404b540aSrobert 		      if (large)
1233*404b540aSrobert 			/* Wrap SUCCN into single block region.  */
1234*404b540aSrobert 			{
1235*404b540aSrobert 			  RGN_BLOCKS (nr_regions) = idx;
1236*404b540aSrobert 			  RGN_NR_BLOCKS (nr_regions) = 1;
1237*404b540aSrobert 			  RGN_DONT_CALC_DEPS (nr_regions) = 0;
1238*404b540aSrobert 			  RGN_HAS_REAL_EBB (nr_regions) = 0;
1239*404b540aSrobert 			  nr_regions++;
1240*404b540aSrobert 			}
1241*404b540aSrobert 
1242*404b540aSrobert 		      idx++;
1243*404b540aSrobert 
1244*404b540aSrobert 		      FOR_EACH_EDGE (e, ei, BASIC_BLOCK (succn)->succs)
1245*404b540aSrobert 			if (e->dest != EXIT_BLOCK_PTR)
1246*404b540aSrobert 			  degree[e->dest->index]--;
1247*404b540aSrobert 		    }
1248*404b540aSrobert 		}
1249*404b540aSrobert 
1250*404b540aSrobert 	      if (!large)
1251*404b540aSrobert 		{
1252*404b540aSrobert 		  RGN_NR_BLOCKS (nr_regions) = num_bbs;
1253*404b540aSrobert 		  nr_regions++;
1254*404b540aSrobert 		}
1255*404b540aSrobert 	    }
1256*404b540aSrobert 	}
1257*404b540aSrobert 
1258*404b540aSrobert       if (sched_verbose >= 6)
1259*404b540aSrobert 	{
1260*404b540aSrobert 	  int *s2, s2_sz;
1261*404b540aSrobert 
1262*404b540aSrobert           /* Get the new statistics and print the comparison with the
1263*404b540aSrobert              one before calling this function.  */
1264*404b540aSrobert 	  s2_sz = gather_region_statistics (&s2);
1265*404b540aSrobert 	  print_region_statistics (s1, s1_sz, s2, s2_sz);
1266*404b540aSrobert 	  free (s1);
1267*404b540aSrobert 	  free (s2);
1268*404b540aSrobert 	}
1269*404b540aSrobert     }
1270*404b540aSrobert 
1271*404b540aSrobert   free (order);
1272*404b540aSrobert   free (max_hdr);
1273*404b540aSrobert 
1274*404b540aSrobert   *idxp = idx;
1275*404b540aSrobert }
1276*404b540aSrobert 
1277*404b540aSrobert /* Functions for regions scheduling information.  */
1278*404b540aSrobert 
1279*404b540aSrobert /* Compute dominators, probability, and potential-split-edges of bb.
1280*404b540aSrobert    Assume that these values were already computed for bb's predecessors.  */
1281*404b540aSrobert 
1282*404b540aSrobert static void
compute_dom_prob_ps(int bb)1283*404b540aSrobert compute_dom_prob_ps (int bb)
1284*404b540aSrobert {
1285*404b540aSrobert   edge_iterator in_ei;
1286*404b540aSrobert   edge in_edge;
1287*404b540aSrobert 
1288*404b540aSrobert   /* We shouldn't have any real ebbs yet.  */
1289*404b540aSrobert   gcc_assert (ebb_head [bb] == bb + current_blocks);
1290*404b540aSrobert 
1291*404b540aSrobert   if (IS_RGN_ENTRY (bb))
1292*404b540aSrobert     {
1293*404b540aSrobert       SET_BIT (dom[bb], 0);
1294*404b540aSrobert       prob[bb] = REG_BR_PROB_BASE;
1295*404b540aSrobert       return;
1296*404b540aSrobert     }
1297*404b540aSrobert 
1298*404b540aSrobert   prob[bb] = 0;
1299*404b540aSrobert 
1300*404b540aSrobert   /* Initialize dom[bb] to '111..1'.  */
1301*404b540aSrobert   sbitmap_ones (dom[bb]);
1302*404b540aSrobert 
1303*404b540aSrobert   FOR_EACH_EDGE (in_edge, in_ei, BASIC_BLOCK (BB_TO_BLOCK (bb))->preds)
1304*404b540aSrobert     {
1305*404b540aSrobert       int pred_bb;
1306*404b540aSrobert       edge out_edge;
1307*404b540aSrobert       edge_iterator out_ei;
1308*404b540aSrobert 
1309*404b540aSrobert       if (in_edge->src == ENTRY_BLOCK_PTR)
1310*404b540aSrobert 	continue;
1311*404b540aSrobert 
1312*404b540aSrobert       pred_bb = BLOCK_TO_BB (in_edge->src->index);
1313*404b540aSrobert       sbitmap_a_and_b (dom[bb], dom[bb], dom[pred_bb]);
1314*404b540aSrobert       sbitmap_a_or_b (ancestor_edges[bb],
1315*404b540aSrobert 		      ancestor_edges[bb], ancestor_edges[pred_bb]);
1316*404b540aSrobert 
1317*404b540aSrobert       SET_BIT (ancestor_edges[bb], EDGE_TO_BIT (in_edge));
1318*404b540aSrobert 
1319*404b540aSrobert       sbitmap_a_or_b (pot_split[bb], pot_split[bb], pot_split[pred_bb]);
1320*404b540aSrobert 
1321*404b540aSrobert       FOR_EACH_EDGE (out_edge, out_ei, in_edge->src->succs)
1322*404b540aSrobert 	SET_BIT (pot_split[bb], EDGE_TO_BIT (out_edge));
1323*404b540aSrobert 
1324*404b540aSrobert       prob[bb] += ((prob[pred_bb] * in_edge->probability) / REG_BR_PROB_BASE);
1325*404b540aSrobert     }
1326*404b540aSrobert 
1327*404b540aSrobert   SET_BIT (dom[bb], bb);
1328*404b540aSrobert   sbitmap_difference (pot_split[bb], pot_split[bb], ancestor_edges[bb]);
1329*404b540aSrobert 
1330*404b540aSrobert   if (sched_verbose >= 2)
1331*404b540aSrobert     fprintf (sched_dump, ";;  bb_prob(%d, %d) = %3d\n", bb, BB_TO_BLOCK (bb),
1332*404b540aSrobert 	     (100 * prob[bb]) / REG_BR_PROB_BASE);
1333*404b540aSrobert }
1334*404b540aSrobert 
1335*404b540aSrobert /* Functions for target info.  */
1336*404b540aSrobert 
1337*404b540aSrobert /* Compute in BL the list of split-edges of bb_src relatively to bb_trg.
1338*404b540aSrobert    Note that bb_trg dominates bb_src.  */
1339*404b540aSrobert 
1340*404b540aSrobert static void
split_edges(int bb_src,int bb_trg,edgelst * bl)1341*404b540aSrobert split_edges (int bb_src, int bb_trg, edgelst *bl)
1342*404b540aSrobert {
1343*404b540aSrobert   sbitmap src = sbitmap_alloc (pot_split[bb_src]->n_bits);
1344*404b540aSrobert   sbitmap_copy (src, pot_split[bb_src]);
1345*404b540aSrobert 
1346*404b540aSrobert   sbitmap_difference (src, src, pot_split[bb_trg]);
1347*404b540aSrobert   extract_edgelst (src, bl);
1348*404b540aSrobert   sbitmap_free (src);
1349*404b540aSrobert }
1350*404b540aSrobert 
1351*404b540aSrobert /* Find the valid candidate-source-blocks for the target block TRG, compute
1352*404b540aSrobert    their probability, and check if they are speculative or not.
1353*404b540aSrobert    For speculative sources, compute their update-blocks and split-blocks.  */
1354*404b540aSrobert 
1355*404b540aSrobert static void
compute_trg_info(int trg)1356*404b540aSrobert compute_trg_info (int trg)
1357*404b540aSrobert {
1358*404b540aSrobert   candidate *sp;
1359*404b540aSrobert   edgelst el;
1360*404b540aSrobert   int i, j, k, update_idx;
1361*404b540aSrobert   basic_block block;
1362*404b540aSrobert   sbitmap visited;
1363*404b540aSrobert   edge_iterator ei;
1364*404b540aSrobert   edge e;
1365*404b540aSrobert 
1366*404b540aSrobert   /* Define some of the fields for the target bb as well.  */
1367*404b540aSrobert   sp = candidate_table + trg;
1368*404b540aSrobert   sp->is_valid = 1;
1369*404b540aSrobert   sp->is_speculative = 0;
1370*404b540aSrobert   sp->src_prob = REG_BR_PROB_BASE;
1371*404b540aSrobert 
1372*404b540aSrobert   visited = sbitmap_alloc (last_basic_block);
1373*404b540aSrobert 
1374*404b540aSrobert   for (i = trg + 1; i < current_nr_blocks; i++)
1375*404b540aSrobert     {
1376*404b540aSrobert       sp = candidate_table + i;
1377*404b540aSrobert 
1378*404b540aSrobert       sp->is_valid = IS_DOMINATED (i, trg);
1379*404b540aSrobert       if (sp->is_valid)
1380*404b540aSrobert 	{
1381*404b540aSrobert 	  int tf = prob[trg], cf = prob[i];
1382*404b540aSrobert 
1383*404b540aSrobert 	  /* In CFGs with low probability edges TF can possibly be zero.  */
1384*404b540aSrobert 	  sp->src_prob = (tf ? ((cf * REG_BR_PROB_BASE) / tf) : 0);
1385*404b540aSrobert 	  sp->is_valid = (sp->src_prob >= min_spec_prob);
1386*404b540aSrobert 	}
1387*404b540aSrobert 
1388*404b540aSrobert       if (sp->is_valid)
1389*404b540aSrobert 	{
1390*404b540aSrobert 	  split_edges (i, trg, &el);
1391*404b540aSrobert 	  sp->is_speculative = (el.nr_members) ? 1 : 0;
1392*404b540aSrobert 	  if (sp->is_speculative && !flag_schedule_speculative)
1393*404b540aSrobert 	    sp->is_valid = 0;
1394*404b540aSrobert 	}
1395*404b540aSrobert 
1396*404b540aSrobert       if (sp->is_valid)
1397*404b540aSrobert 	{
1398*404b540aSrobert 	  /* Compute split blocks and store them in bblst_table.
1399*404b540aSrobert 	     The TO block of every split edge is a split block.  */
1400*404b540aSrobert 	  sp->split_bbs.first_member = &bblst_table[bblst_last];
1401*404b540aSrobert 	  sp->split_bbs.nr_members = el.nr_members;
1402*404b540aSrobert 	  for (j = 0; j < el.nr_members; bblst_last++, j++)
1403*404b540aSrobert 	    bblst_table[bblst_last] = el.first_member[j]->dest;
1404*404b540aSrobert 	  sp->update_bbs.first_member = &bblst_table[bblst_last];
1405*404b540aSrobert 
1406*404b540aSrobert 	  /* Compute update blocks and store them in bblst_table.
1407*404b540aSrobert 	     For every split edge, look at the FROM block, and check
1408*404b540aSrobert 	     all out edges.  For each out edge that is not a split edge,
1409*404b540aSrobert 	     add the TO block to the update block list.  This list can end
1410*404b540aSrobert 	     up with a lot of duplicates.  We need to weed them out to avoid
1411*404b540aSrobert 	     overrunning the end of the bblst_table.  */
1412*404b540aSrobert 
1413*404b540aSrobert 	  update_idx = 0;
1414*404b540aSrobert 	  sbitmap_zero (visited);
1415*404b540aSrobert 	  for (j = 0; j < el.nr_members; j++)
1416*404b540aSrobert 	    {
1417*404b540aSrobert 	      block = el.first_member[j]->src;
1418*404b540aSrobert 	      FOR_EACH_EDGE (e, ei, block->succs)
1419*404b540aSrobert 		{
1420*404b540aSrobert 		  if (!TEST_BIT (visited, e->dest->index))
1421*404b540aSrobert 		    {
1422*404b540aSrobert 		      for (k = 0; k < el.nr_members; k++)
1423*404b540aSrobert 			if (e == el.first_member[k])
1424*404b540aSrobert 			  break;
1425*404b540aSrobert 
1426*404b540aSrobert 		      if (k >= el.nr_members)
1427*404b540aSrobert 			{
1428*404b540aSrobert 			  bblst_table[bblst_last++] = e->dest;
1429*404b540aSrobert 			  SET_BIT (visited, e->dest->index);
1430*404b540aSrobert 			  update_idx++;
1431*404b540aSrobert 			}
1432*404b540aSrobert 		    }
1433*404b540aSrobert 		}
1434*404b540aSrobert 	    }
1435*404b540aSrobert 	  sp->update_bbs.nr_members = update_idx;
1436*404b540aSrobert 
1437*404b540aSrobert 	  /* Make sure we didn't overrun the end of bblst_table.  */
1438*404b540aSrobert 	  gcc_assert (bblst_last <= bblst_size);
1439*404b540aSrobert 	}
1440*404b540aSrobert       else
1441*404b540aSrobert 	{
1442*404b540aSrobert 	  sp->split_bbs.nr_members = sp->update_bbs.nr_members = 0;
1443*404b540aSrobert 
1444*404b540aSrobert 	  sp->is_speculative = 0;
1445*404b540aSrobert 	  sp->src_prob = 0;
1446*404b540aSrobert 	}
1447*404b540aSrobert     }
1448*404b540aSrobert 
1449*404b540aSrobert   sbitmap_free (visited);
1450*404b540aSrobert }
1451*404b540aSrobert 
1452*404b540aSrobert /* Print candidates info, for debugging purposes.  Callable from debugger.  */
1453*404b540aSrobert 
1454*404b540aSrobert void
debug_candidate(int i)1455*404b540aSrobert debug_candidate (int i)
1456*404b540aSrobert {
1457*404b540aSrobert   if (!candidate_table[i].is_valid)
1458*404b540aSrobert     return;
1459*404b540aSrobert 
1460*404b540aSrobert   if (candidate_table[i].is_speculative)
1461*404b540aSrobert     {
1462*404b540aSrobert       int j;
1463*404b540aSrobert       fprintf (sched_dump, "src b %d bb %d speculative \n", BB_TO_BLOCK (i), i);
1464*404b540aSrobert 
1465*404b540aSrobert       fprintf (sched_dump, "split path: ");
1466*404b540aSrobert       for (j = 0; j < candidate_table[i].split_bbs.nr_members; j++)
1467*404b540aSrobert 	{
1468*404b540aSrobert 	  int b = candidate_table[i].split_bbs.first_member[j]->index;
1469*404b540aSrobert 
1470*404b540aSrobert 	  fprintf (sched_dump, " %d ", b);
1471*404b540aSrobert 	}
1472*404b540aSrobert       fprintf (sched_dump, "\n");
1473*404b540aSrobert 
1474*404b540aSrobert       fprintf (sched_dump, "update path: ");
1475*404b540aSrobert       for (j = 0; j < candidate_table[i].update_bbs.nr_members; j++)
1476*404b540aSrobert 	{
1477*404b540aSrobert 	  int b = candidate_table[i].update_bbs.first_member[j]->index;
1478*404b540aSrobert 
1479*404b540aSrobert 	  fprintf (sched_dump, " %d ", b);
1480*404b540aSrobert 	}
1481*404b540aSrobert       fprintf (sched_dump, "\n");
1482*404b540aSrobert     }
1483*404b540aSrobert   else
1484*404b540aSrobert     {
1485*404b540aSrobert       fprintf (sched_dump, " src %d equivalent\n", BB_TO_BLOCK (i));
1486*404b540aSrobert     }
1487*404b540aSrobert }
1488*404b540aSrobert 
1489*404b540aSrobert /* Print candidates info, for debugging purposes.  Callable from debugger.  */
1490*404b540aSrobert 
1491*404b540aSrobert void
debug_candidates(int trg)1492*404b540aSrobert debug_candidates (int trg)
1493*404b540aSrobert {
1494*404b540aSrobert   int i;
1495*404b540aSrobert 
1496*404b540aSrobert   fprintf (sched_dump, "----------- candidate table: target: b=%d bb=%d ---\n",
1497*404b540aSrobert 	   BB_TO_BLOCK (trg), trg);
1498*404b540aSrobert   for (i = trg + 1; i < current_nr_blocks; i++)
1499*404b540aSrobert     debug_candidate (i);
1500*404b540aSrobert }
1501*404b540aSrobert 
1502*404b540aSrobert /* Functions for speculative scheduling.  */
1503*404b540aSrobert 
1504*404b540aSrobert /* Return 0 if x is a set of a register alive in the beginning of one
1505*404b540aSrobert    of the split-blocks of src, otherwise return 1.  */
1506*404b540aSrobert 
1507*404b540aSrobert static int
check_live_1(int src,rtx x)1508*404b540aSrobert check_live_1 (int src, rtx x)
1509*404b540aSrobert {
1510*404b540aSrobert   int i;
1511*404b540aSrobert   int regno;
1512*404b540aSrobert   rtx reg = SET_DEST (x);
1513*404b540aSrobert 
1514*404b540aSrobert   if (reg == 0)
1515*404b540aSrobert     return 1;
1516*404b540aSrobert 
1517*404b540aSrobert   while (GET_CODE (reg) == SUBREG
1518*404b540aSrobert 	 || GET_CODE (reg) == ZERO_EXTRACT
1519*404b540aSrobert 	 || GET_CODE (reg) == STRICT_LOW_PART)
1520*404b540aSrobert     reg = XEXP (reg, 0);
1521*404b540aSrobert 
1522*404b540aSrobert   if (GET_CODE (reg) == PARALLEL)
1523*404b540aSrobert     {
1524*404b540aSrobert       int i;
1525*404b540aSrobert 
1526*404b540aSrobert       for (i = XVECLEN (reg, 0) - 1; i >= 0; i--)
1527*404b540aSrobert 	if (XEXP (XVECEXP (reg, 0, i), 0) != 0)
1528*404b540aSrobert 	  if (check_live_1 (src, XEXP (XVECEXP (reg, 0, i), 0)))
1529*404b540aSrobert 	    return 1;
1530*404b540aSrobert 
1531*404b540aSrobert       return 0;
1532*404b540aSrobert     }
1533*404b540aSrobert 
1534*404b540aSrobert   if (!REG_P (reg))
1535*404b540aSrobert     return 1;
1536*404b540aSrobert 
1537*404b540aSrobert   regno = REGNO (reg);
1538*404b540aSrobert 
1539*404b540aSrobert   if (regno < FIRST_PSEUDO_REGISTER && global_regs[regno])
1540*404b540aSrobert     {
1541*404b540aSrobert       /* Global registers are assumed live.  */
1542*404b540aSrobert       return 0;
1543*404b540aSrobert     }
1544*404b540aSrobert   else
1545*404b540aSrobert     {
1546*404b540aSrobert       if (regno < FIRST_PSEUDO_REGISTER)
1547*404b540aSrobert 	{
1548*404b540aSrobert 	  /* Check for hard registers.  */
1549*404b540aSrobert 	  int j = hard_regno_nregs[regno][GET_MODE (reg)];
1550*404b540aSrobert 	  while (--j >= 0)
1551*404b540aSrobert 	    {
1552*404b540aSrobert 	      for (i = 0; i < candidate_table[src].split_bbs.nr_members; i++)
1553*404b540aSrobert 		{
1554*404b540aSrobert 		  basic_block b = candidate_table[src].split_bbs.first_member[i];
1555*404b540aSrobert 
1556*404b540aSrobert 		  /* We can have split blocks, that were recently generated.
1557*404b540aSrobert 		     such blocks are always outside current region.  */
1558*404b540aSrobert 		  gcc_assert (glat_start[b->index]
1559*404b540aSrobert 			      || CONTAINING_RGN (b->index)
1560*404b540aSrobert 			      != CONTAINING_RGN (BB_TO_BLOCK (src)));
1561*404b540aSrobert 		  if (!glat_start[b->index]
1562*404b540aSrobert 		      || REGNO_REG_SET_P (glat_start[b->index],
1563*404b540aSrobert 					  regno + j))
1564*404b540aSrobert 		    {
1565*404b540aSrobert 		      return 0;
1566*404b540aSrobert 		    }
1567*404b540aSrobert 		}
1568*404b540aSrobert 	    }
1569*404b540aSrobert 	}
1570*404b540aSrobert       else
1571*404b540aSrobert 	{
1572*404b540aSrobert 	  /* Check for pseudo registers.  */
1573*404b540aSrobert 	  for (i = 0; i < candidate_table[src].split_bbs.nr_members; i++)
1574*404b540aSrobert 	    {
1575*404b540aSrobert 	      basic_block b = candidate_table[src].split_bbs.first_member[i];
1576*404b540aSrobert 
1577*404b540aSrobert 	      gcc_assert (glat_start[b->index]
1578*404b540aSrobert 			  || CONTAINING_RGN (b->index)
1579*404b540aSrobert 			  != CONTAINING_RGN (BB_TO_BLOCK (src)));
1580*404b540aSrobert 	      if (!glat_start[b->index]
1581*404b540aSrobert 		  || REGNO_REG_SET_P (glat_start[b->index], regno))
1582*404b540aSrobert 		{
1583*404b540aSrobert 		  return 0;
1584*404b540aSrobert 		}
1585*404b540aSrobert 	    }
1586*404b540aSrobert 	}
1587*404b540aSrobert     }
1588*404b540aSrobert 
1589*404b540aSrobert   return 1;
1590*404b540aSrobert }
1591*404b540aSrobert 
1592*404b540aSrobert /* If x is a set of a register R, mark that R is alive in the beginning
1593*404b540aSrobert    of every update-block of src.  */
1594*404b540aSrobert 
1595*404b540aSrobert static void
update_live_1(int src,rtx x)1596*404b540aSrobert update_live_1 (int src, rtx x)
1597*404b540aSrobert {
1598*404b540aSrobert   int i;
1599*404b540aSrobert   int regno;
1600*404b540aSrobert   rtx reg = SET_DEST (x);
1601*404b540aSrobert 
1602*404b540aSrobert   if (reg == 0)
1603*404b540aSrobert     return;
1604*404b540aSrobert 
1605*404b540aSrobert   while (GET_CODE (reg) == SUBREG
1606*404b540aSrobert 	 || GET_CODE (reg) == ZERO_EXTRACT
1607*404b540aSrobert 	 || GET_CODE (reg) == STRICT_LOW_PART)
1608*404b540aSrobert     reg = XEXP (reg, 0);
1609*404b540aSrobert 
1610*404b540aSrobert   if (GET_CODE (reg) == PARALLEL)
1611*404b540aSrobert     {
1612*404b540aSrobert       int i;
1613*404b540aSrobert 
1614*404b540aSrobert       for (i = XVECLEN (reg, 0) - 1; i >= 0; i--)
1615*404b540aSrobert 	if (XEXP (XVECEXP (reg, 0, i), 0) != 0)
1616*404b540aSrobert 	  update_live_1 (src, XEXP (XVECEXP (reg, 0, i), 0));
1617*404b540aSrobert 
1618*404b540aSrobert       return;
1619*404b540aSrobert     }
1620*404b540aSrobert 
1621*404b540aSrobert   if (!REG_P (reg))
1622*404b540aSrobert     return;
1623*404b540aSrobert 
1624*404b540aSrobert   /* Global registers are always live, so the code below does not apply
1625*404b540aSrobert      to them.  */
1626*404b540aSrobert 
1627*404b540aSrobert   regno = REGNO (reg);
1628*404b540aSrobert 
1629*404b540aSrobert   if (regno >= FIRST_PSEUDO_REGISTER || !global_regs[regno])
1630*404b540aSrobert     {
1631*404b540aSrobert       if (regno < FIRST_PSEUDO_REGISTER)
1632*404b540aSrobert 	{
1633*404b540aSrobert 	  int j = hard_regno_nregs[regno][GET_MODE (reg)];
1634*404b540aSrobert 	  while (--j >= 0)
1635*404b540aSrobert 	    {
1636*404b540aSrobert 	      for (i = 0; i < candidate_table[src].update_bbs.nr_members; i++)
1637*404b540aSrobert 		{
1638*404b540aSrobert 		  basic_block b = candidate_table[src].update_bbs.first_member[i];
1639*404b540aSrobert 
1640*404b540aSrobert 		  SET_REGNO_REG_SET (glat_start[b->index], regno + j);
1641*404b540aSrobert 		}
1642*404b540aSrobert 	    }
1643*404b540aSrobert 	}
1644*404b540aSrobert       else
1645*404b540aSrobert 	{
1646*404b540aSrobert 	  for (i = 0; i < candidate_table[src].update_bbs.nr_members; i++)
1647*404b540aSrobert 	    {
1648*404b540aSrobert 	      basic_block b = candidate_table[src].update_bbs.first_member[i];
1649*404b540aSrobert 
1650*404b540aSrobert 	      SET_REGNO_REG_SET (glat_start[b->index], regno);
1651*404b540aSrobert 	    }
1652*404b540aSrobert 	}
1653*404b540aSrobert     }
1654*404b540aSrobert }
1655*404b540aSrobert 
1656*404b540aSrobert /* Return 1 if insn can be speculatively moved from block src to trg,
1657*404b540aSrobert    otherwise return 0.  Called before first insertion of insn to
1658*404b540aSrobert    ready-list or before the scheduling.  */
1659*404b540aSrobert 
1660*404b540aSrobert static int
check_live(rtx insn,int src)1661*404b540aSrobert check_live (rtx insn, int src)
1662*404b540aSrobert {
1663*404b540aSrobert   /* Find the registers set by instruction.  */
1664*404b540aSrobert   if (GET_CODE (PATTERN (insn)) == SET
1665*404b540aSrobert       || GET_CODE (PATTERN (insn)) == CLOBBER)
1666*404b540aSrobert     return check_live_1 (src, PATTERN (insn));
1667*404b540aSrobert   else if (GET_CODE (PATTERN (insn)) == PARALLEL)
1668*404b540aSrobert     {
1669*404b540aSrobert       int j;
1670*404b540aSrobert       for (j = XVECLEN (PATTERN (insn), 0) - 1; j >= 0; j--)
1671*404b540aSrobert 	if ((GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == SET
1672*404b540aSrobert 	     || GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == CLOBBER)
1673*404b540aSrobert 	    && !check_live_1 (src, XVECEXP (PATTERN (insn), 0, j)))
1674*404b540aSrobert 	  return 0;
1675*404b540aSrobert 
1676*404b540aSrobert       return 1;
1677*404b540aSrobert     }
1678*404b540aSrobert 
1679*404b540aSrobert   return 1;
1680*404b540aSrobert }
1681*404b540aSrobert 
1682*404b540aSrobert /* Update the live registers info after insn was moved speculatively from
1683*404b540aSrobert    block src to trg.  */
1684*404b540aSrobert 
1685*404b540aSrobert static void
update_live(rtx insn,int src)1686*404b540aSrobert update_live (rtx insn, int src)
1687*404b540aSrobert {
1688*404b540aSrobert   /* Find the registers set by instruction.  */
1689*404b540aSrobert   if (GET_CODE (PATTERN (insn)) == SET
1690*404b540aSrobert       || GET_CODE (PATTERN (insn)) == CLOBBER)
1691*404b540aSrobert     update_live_1 (src, PATTERN (insn));
1692*404b540aSrobert   else if (GET_CODE (PATTERN (insn)) == PARALLEL)
1693*404b540aSrobert     {
1694*404b540aSrobert       int j;
1695*404b540aSrobert       for (j = XVECLEN (PATTERN (insn), 0) - 1; j >= 0; j--)
1696*404b540aSrobert 	if (GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == SET
1697*404b540aSrobert 	    || GET_CODE (XVECEXP (PATTERN (insn), 0, j)) == CLOBBER)
1698*404b540aSrobert 	  update_live_1 (src, XVECEXP (PATTERN (insn), 0, j));
1699*404b540aSrobert     }
1700*404b540aSrobert }
1701*404b540aSrobert 
1702*404b540aSrobert /* Nonzero if block bb_to is equal to, or reachable from block bb_from.  */
1703*404b540aSrobert #define IS_REACHABLE(bb_from, bb_to)					\
1704*404b540aSrobert   (bb_from == bb_to							\
1705*404b540aSrobert    || IS_RGN_ENTRY (bb_from)						\
1706*404b540aSrobert    || (TEST_BIT (ancestor_edges[bb_to],					\
1707*404b540aSrobert 	 EDGE_TO_BIT (single_pred_edge (BASIC_BLOCK (BB_TO_BLOCK (bb_from)))))))
1708*404b540aSrobert 
1709*404b540aSrobert /* Turns on the fed_by_spec_load flag for insns fed by load_insn.  */
1710*404b540aSrobert 
1711*404b540aSrobert static void
set_spec_fed(rtx load_insn)1712*404b540aSrobert set_spec_fed (rtx load_insn)
1713*404b540aSrobert {
1714*404b540aSrobert   rtx link;
1715*404b540aSrobert 
1716*404b540aSrobert   for (link = INSN_DEPEND (load_insn); link; link = XEXP (link, 1))
1717*404b540aSrobert     if (GET_MODE (link) == VOIDmode)
1718*404b540aSrobert       FED_BY_SPEC_LOAD (XEXP (link, 0)) = 1;
1719*404b540aSrobert }				/* set_spec_fed */
1720*404b540aSrobert 
1721*404b540aSrobert /* On the path from the insn to load_insn_bb, find a conditional
1722*404b540aSrobert branch depending on insn, that guards the speculative load.  */
1723*404b540aSrobert 
1724*404b540aSrobert static int
find_conditional_protection(rtx insn,int load_insn_bb)1725*404b540aSrobert find_conditional_protection (rtx insn, int load_insn_bb)
1726*404b540aSrobert {
1727*404b540aSrobert   rtx link;
1728*404b540aSrobert 
1729*404b540aSrobert   /* Iterate through DEF-USE forward dependences.  */
1730*404b540aSrobert   for (link = INSN_DEPEND (insn); link; link = XEXP (link, 1))
1731*404b540aSrobert     {
1732*404b540aSrobert       rtx next = XEXP (link, 0);
1733*404b540aSrobert       if ((CONTAINING_RGN (BLOCK_NUM (next)) ==
1734*404b540aSrobert 	   CONTAINING_RGN (BB_TO_BLOCK (load_insn_bb)))
1735*404b540aSrobert 	  && IS_REACHABLE (INSN_BB (next), load_insn_bb)
1736*404b540aSrobert 	  && load_insn_bb != INSN_BB (next)
1737*404b540aSrobert 	  && GET_MODE (link) == VOIDmode
1738*404b540aSrobert 	  && (JUMP_P (next)
1739*404b540aSrobert 	      || find_conditional_protection (next, load_insn_bb)))
1740*404b540aSrobert 	return 1;
1741*404b540aSrobert     }
1742*404b540aSrobert   return 0;
1743*404b540aSrobert }				/* find_conditional_protection */
1744*404b540aSrobert 
1745*404b540aSrobert /* Returns 1 if the same insn1 that participates in the computation
1746*404b540aSrobert    of load_insn's address is feeding a conditional branch that is
1747*404b540aSrobert    guarding on load_insn. This is true if we find a the two DEF-USE
1748*404b540aSrobert    chains:
1749*404b540aSrobert    insn1 -> ... -> conditional-branch
1750*404b540aSrobert    insn1 -> ... -> load_insn,
1751*404b540aSrobert    and if a flow path exist:
1752*404b540aSrobert    insn1 -> ... -> conditional-branch -> ... -> load_insn,
1753*404b540aSrobert    and if insn1 is on the path
1754*404b540aSrobert    region-entry -> ... -> bb_trg -> ... load_insn.
1755*404b540aSrobert 
1756*404b540aSrobert    Locate insn1 by climbing on LOG_LINKS from load_insn.
1757*404b540aSrobert    Locate the branch by following INSN_DEPEND from insn1.  */
1758*404b540aSrobert 
1759*404b540aSrobert static int
is_conditionally_protected(rtx load_insn,int bb_src,int bb_trg)1760*404b540aSrobert is_conditionally_protected (rtx load_insn, int bb_src, int bb_trg)
1761*404b540aSrobert {
1762*404b540aSrobert   rtx link;
1763*404b540aSrobert 
1764*404b540aSrobert   for (link = LOG_LINKS (load_insn); link; link = XEXP (link, 1))
1765*404b540aSrobert     {
1766*404b540aSrobert       rtx insn1 = XEXP (link, 0);
1767*404b540aSrobert 
1768*404b540aSrobert       /* Must be a DEF-USE dependence upon non-branch.  */
1769*404b540aSrobert       if (GET_MODE (link) != VOIDmode
1770*404b540aSrobert 	  || JUMP_P (insn1))
1771*404b540aSrobert 	continue;
1772*404b540aSrobert 
1773*404b540aSrobert       /* Must exist a path: region-entry -> ... -> bb_trg -> ... load_insn.  */
1774*404b540aSrobert       if (INSN_BB (insn1) == bb_src
1775*404b540aSrobert 	  || (CONTAINING_RGN (BLOCK_NUM (insn1))
1776*404b540aSrobert 	      != CONTAINING_RGN (BB_TO_BLOCK (bb_src)))
1777*404b540aSrobert 	  || (!IS_REACHABLE (bb_trg, INSN_BB (insn1))
1778*404b540aSrobert 	      && !IS_REACHABLE (INSN_BB (insn1), bb_trg)))
1779*404b540aSrobert 	continue;
1780*404b540aSrobert 
1781*404b540aSrobert       /* Now search for the conditional-branch.  */
1782*404b540aSrobert       if (find_conditional_protection (insn1, bb_src))
1783*404b540aSrobert 	return 1;
1784*404b540aSrobert 
1785*404b540aSrobert       /* Recursive step: search another insn1, "above" current insn1.  */
1786*404b540aSrobert       return is_conditionally_protected (insn1, bb_src, bb_trg);
1787*404b540aSrobert     }
1788*404b540aSrobert 
1789*404b540aSrobert   /* The chain does not exist.  */
1790*404b540aSrobert   return 0;
1791*404b540aSrobert }				/* is_conditionally_protected */
1792*404b540aSrobert 
1793*404b540aSrobert /* Returns 1 if a clue for "similar load" 'insn2' is found, and hence
1794*404b540aSrobert    load_insn can move speculatively from bb_src to bb_trg.  All the
1795*404b540aSrobert    following must hold:
1796*404b540aSrobert 
1797*404b540aSrobert    (1) both loads have 1 base register (PFREE_CANDIDATEs).
1798*404b540aSrobert    (2) load_insn and load1 have a def-use dependence upon
1799*404b540aSrobert    the same insn 'insn1'.
1800*404b540aSrobert    (3) either load2 is in bb_trg, or:
1801*404b540aSrobert    - there's only one split-block, and
1802*404b540aSrobert    - load1 is on the escape path, and
1803*404b540aSrobert 
1804*404b540aSrobert    From all these we can conclude that the two loads access memory
1805*404b540aSrobert    addresses that differ at most by a constant, and hence if moving
1806*404b540aSrobert    load_insn would cause an exception, it would have been caused by
1807*404b540aSrobert    load2 anyhow.  */
1808*404b540aSrobert 
1809*404b540aSrobert static int
is_pfree(rtx load_insn,int bb_src,int bb_trg)1810*404b540aSrobert is_pfree (rtx load_insn, int bb_src, int bb_trg)
1811*404b540aSrobert {
1812*404b540aSrobert   rtx back_link;
1813*404b540aSrobert   candidate *candp = candidate_table + bb_src;
1814*404b540aSrobert 
1815*404b540aSrobert   if (candp->split_bbs.nr_members != 1)
1816*404b540aSrobert     /* Must have exactly one escape block.  */
1817*404b540aSrobert     return 0;
1818*404b540aSrobert 
1819*404b540aSrobert   for (back_link = LOG_LINKS (load_insn);
1820*404b540aSrobert        back_link; back_link = XEXP (back_link, 1))
1821*404b540aSrobert     {
1822*404b540aSrobert       rtx insn1 = XEXP (back_link, 0);
1823*404b540aSrobert 
1824*404b540aSrobert       if (GET_MODE (back_link) == VOIDmode)
1825*404b540aSrobert 	{
1826*404b540aSrobert 	  /* Found a DEF-USE dependence (insn1, load_insn).  */
1827*404b540aSrobert 	  rtx fore_link;
1828*404b540aSrobert 
1829*404b540aSrobert 	  for (fore_link = INSN_DEPEND (insn1);
1830*404b540aSrobert 	       fore_link; fore_link = XEXP (fore_link, 1))
1831*404b540aSrobert 	    {
1832*404b540aSrobert 	      rtx insn2 = XEXP (fore_link, 0);
1833*404b540aSrobert 	      if (GET_MODE (fore_link) == VOIDmode)
1834*404b540aSrobert 		{
1835*404b540aSrobert 		  /* Found a DEF-USE dependence (insn1, insn2).  */
1836*404b540aSrobert 		  if (haifa_classify_insn (insn2) != PFREE_CANDIDATE)
1837*404b540aSrobert 		    /* insn2 not guaranteed to be a 1 base reg load.  */
1838*404b540aSrobert 		    continue;
1839*404b540aSrobert 
1840*404b540aSrobert 		  if (INSN_BB (insn2) == bb_trg)
1841*404b540aSrobert 		    /* insn2 is the similar load, in the target block.  */
1842*404b540aSrobert 		    return 1;
1843*404b540aSrobert 
1844*404b540aSrobert 		  if (*(candp->split_bbs.first_member) == BLOCK_FOR_INSN (insn2))
1845*404b540aSrobert 		    /* insn2 is a similar load, in a split-block.  */
1846*404b540aSrobert 		    return 1;
1847*404b540aSrobert 		}
1848*404b540aSrobert 	    }
1849*404b540aSrobert 	}
1850*404b540aSrobert     }
1851*404b540aSrobert 
1852*404b540aSrobert   /* Couldn't find a similar load.  */
1853*404b540aSrobert   return 0;
1854*404b540aSrobert }				/* is_pfree */
1855*404b540aSrobert 
1856*404b540aSrobert /* Return 1 if load_insn is prisky (i.e. if load_insn is fed by
1857*404b540aSrobert    a load moved speculatively, or if load_insn is protected by
1858*404b540aSrobert    a compare on load_insn's address).  */
1859*404b540aSrobert 
1860*404b540aSrobert static int
is_prisky(rtx load_insn,int bb_src,int bb_trg)1861*404b540aSrobert is_prisky (rtx load_insn, int bb_src, int bb_trg)
1862*404b540aSrobert {
1863*404b540aSrobert   if (FED_BY_SPEC_LOAD (load_insn))
1864*404b540aSrobert     return 1;
1865*404b540aSrobert 
1866*404b540aSrobert   if (LOG_LINKS (load_insn) == NULL)
1867*404b540aSrobert     /* Dependence may 'hide' out of the region.  */
1868*404b540aSrobert     return 1;
1869*404b540aSrobert 
1870*404b540aSrobert   if (is_conditionally_protected (load_insn, bb_src, bb_trg))
1871*404b540aSrobert     return 1;
1872*404b540aSrobert 
1873*404b540aSrobert   return 0;
1874*404b540aSrobert }
1875*404b540aSrobert 
1876*404b540aSrobert /* Insn is a candidate to be moved speculatively from bb_src to bb_trg.
1877*404b540aSrobert    Return 1 if insn is exception-free (and the motion is valid)
1878*404b540aSrobert    and 0 otherwise.  */
1879*404b540aSrobert 
1880*404b540aSrobert static int
is_exception_free(rtx insn,int bb_src,int bb_trg)1881*404b540aSrobert is_exception_free (rtx insn, int bb_src, int bb_trg)
1882*404b540aSrobert {
1883*404b540aSrobert   int insn_class = haifa_classify_insn (insn);
1884*404b540aSrobert 
1885*404b540aSrobert   /* Handle non-load insns.  */
1886*404b540aSrobert   switch (insn_class)
1887*404b540aSrobert     {
1888*404b540aSrobert     case TRAP_FREE:
1889*404b540aSrobert       return 1;
1890*404b540aSrobert     case TRAP_RISKY:
1891*404b540aSrobert       return 0;
1892*404b540aSrobert     default:;
1893*404b540aSrobert     }
1894*404b540aSrobert 
1895*404b540aSrobert   /* Handle loads.  */
1896*404b540aSrobert   if (!flag_schedule_speculative_load)
1897*404b540aSrobert     return 0;
1898*404b540aSrobert   IS_LOAD_INSN (insn) = 1;
1899*404b540aSrobert   switch (insn_class)
1900*404b540aSrobert     {
1901*404b540aSrobert     case IFREE:
1902*404b540aSrobert       return (1);
1903*404b540aSrobert     case IRISKY:
1904*404b540aSrobert       return 0;
1905*404b540aSrobert     case PFREE_CANDIDATE:
1906*404b540aSrobert       if (is_pfree (insn, bb_src, bb_trg))
1907*404b540aSrobert 	return 1;
1908*404b540aSrobert       /* Don't 'break' here: PFREE-candidate is also PRISKY-candidate.  */
1909*404b540aSrobert     case PRISKY_CANDIDATE:
1910*404b540aSrobert       if (!flag_schedule_speculative_load_dangerous
1911*404b540aSrobert 	  || is_prisky (insn, bb_src, bb_trg))
1912*404b540aSrobert 	return 0;
1913*404b540aSrobert       break;
1914*404b540aSrobert     default:;
1915*404b540aSrobert     }
1916*404b540aSrobert 
1917*404b540aSrobert   return flag_schedule_speculative_load_dangerous;
1918*404b540aSrobert }
1919*404b540aSrobert 
1920*404b540aSrobert /* The number of insns from the current block scheduled so far.  */
1921*404b540aSrobert static int sched_target_n_insns;
1922*404b540aSrobert /* The number of insns from the current block to be scheduled in total.  */
1923*404b540aSrobert static int target_n_insns;
1924*404b540aSrobert /* The number of insns from the entire region scheduled so far.  */
1925*404b540aSrobert static int sched_n_insns;
1926*404b540aSrobert 
1927*404b540aSrobert /* Implementations of the sched_info functions for region scheduling.  */
1928*404b540aSrobert static void init_ready_list (void);
1929*404b540aSrobert static int can_schedule_ready_p (rtx);
1930*404b540aSrobert static void begin_schedule_ready (rtx, rtx);
1931*404b540aSrobert static ds_t new_ready (rtx, ds_t);
1932*404b540aSrobert static int schedule_more_p (void);
1933*404b540aSrobert static const char *rgn_print_insn (rtx, int);
1934*404b540aSrobert static int rgn_rank (rtx, rtx);
1935*404b540aSrobert static int contributes_to_priority (rtx, rtx);
1936*404b540aSrobert static void compute_jump_reg_dependencies (rtx, regset, regset, regset);
1937*404b540aSrobert 
1938*404b540aSrobert /* Functions for speculative scheduling.  */
1939*404b540aSrobert static void add_remove_insn (rtx, int);
1940*404b540aSrobert static void extend_regions (void);
1941*404b540aSrobert static void add_block1 (basic_block, basic_block);
1942*404b540aSrobert static void fix_recovery_cfg (int, int, int);
1943*404b540aSrobert static basic_block advance_target_bb (basic_block, rtx);
1944*404b540aSrobert static void check_dead_notes1 (int, sbitmap);
1945*404b540aSrobert #ifdef ENABLE_CHECKING
1946*404b540aSrobert static int region_head_or_leaf_p (basic_block, int);
1947*404b540aSrobert #endif
1948*404b540aSrobert 
1949*404b540aSrobert /* Return nonzero if there are more insns that should be scheduled.  */
1950*404b540aSrobert 
1951*404b540aSrobert static int
schedule_more_p(void)1952*404b540aSrobert schedule_more_p (void)
1953*404b540aSrobert {
1954*404b540aSrobert   return sched_target_n_insns < target_n_insns;
1955*404b540aSrobert }
1956*404b540aSrobert 
1957*404b540aSrobert /* Add all insns that are initially ready to the ready list READY.  Called
1958*404b540aSrobert    once before scheduling a set of insns.  */
1959*404b540aSrobert 
1960*404b540aSrobert static void
init_ready_list(void)1961*404b540aSrobert init_ready_list (void)
1962*404b540aSrobert {
1963*404b540aSrobert   rtx prev_head = current_sched_info->prev_head;
1964*404b540aSrobert   rtx next_tail = current_sched_info->next_tail;
1965*404b540aSrobert   int bb_src;
1966*404b540aSrobert   rtx insn;
1967*404b540aSrobert 
1968*404b540aSrobert   target_n_insns = 0;
1969*404b540aSrobert   sched_target_n_insns = 0;
1970*404b540aSrobert   sched_n_insns = 0;
1971*404b540aSrobert 
1972*404b540aSrobert   /* Print debugging information.  */
1973*404b540aSrobert   if (sched_verbose >= 5)
1974*404b540aSrobert     debug_dependencies ();
1975*404b540aSrobert 
1976*404b540aSrobert   /* Prepare current target block info.  */
1977*404b540aSrobert   if (current_nr_blocks > 1)
1978*404b540aSrobert     {
1979*404b540aSrobert       candidate_table = XNEWVEC (candidate, current_nr_blocks);
1980*404b540aSrobert 
1981*404b540aSrobert       bblst_last = 0;
1982*404b540aSrobert       /* bblst_table holds split blocks and update blocks for each block after
1983*404b540aSrobert 	 the current one in the region.  split blocks and update blocks are
1984*404b540aSrobert 	 the TO blocks of region edges, so there can be at most rgn_nr_edges
1985*404b540aSrobert 	 of them.  */
1986*404b540aSrobert       bblst_size = (current_nr_blocks - target_bb) * rgn_nr_edges;
1987*404b540aSrobert       bblst_table = XNEWVEC (basic_block, bblst_size);
1988*404b540aSrobert 
1989*404b540aSrobert       edgelst_last = 0;
1990*404b540aSrobert       edgelst_table = XNEWVEC (edge, rgn_nr_edges);
1991*404b540aSrobert 
1992*404b540aSrobert       compute_trg_info (target_bb);
1993*404b540aSrobert     }
1994*404b540aSrobert 
1995*404b540aSrobert   /* Initialize ready list with all 'ready' insns in target block.
1996*404b540aSrobert      Count number of insns in the target block being scheduled.  */
1997*404b540aSrobert   for (insn = NEXT_INSN (prev_head); insn != next_tail; insn = NEXT_INSN (insn))
1998*404b540aSrobert     {
1999*404b540aSrobert       try_ready (insn);
2000*404b540aSrobert       target_n_insns++;
2001*404b540aSrobert 
2002*404b540aSrobert       gcc_assert (!(TODO_SPEC (insn) & BEGIN_CONTROL));
2003*404b540aSrobert     }
2004*404b540aSrobert 
2005*404b540aSrobert   /* Add to ready list all 'ready' insns in valid source blocks.
2006*404b540aSrobert      For speculative insns, check-live, exception-free, and
2007*404b540aSrobert      issue-delay.  */
2008*404b540aSrobert   for (bb_src = target_bb + 1; bb_src < current_nr_blocks; bb_src++)
2009*404b540aSrobert     if (IS_VALID (bb_src))
2010*404b540aSrobert       {
2011*404b540aSrobert 	rtx src_head;
2012*404b540aSrobert 	rtx src_next_tail;
2013*404b540aSrobert 	rtx tail, head;
2014*404b540aSrobert 
2015*404b540aSrobert 	get_ebb_head_tail (EBB_FIRST_BB (bb_src), EBB_LAST_BB (bb_src),
2016*404b540aSrobert 			   &head, &tail);
2017*404b540aSrobert 	src_next_tail = NEXT_INSN (tail);
2018*404b540aSrobert 	src_head = head;
2019*404b540aSrobert 
2020*404b540aSrobert 	for (insn = src_head; insn != src_next_tail; insn = NEXT_INSN (insn))
2021*404b540aSrobert 	  if (INSN_P (insn))
2022*404b540aSrobert 	    try_ready (insn);
2023*404b540aSrobert       }
2024*404b540aSrobert }
2025*404b540aSrobert 
2026*404b540aSrobert /* Called after taking INSN from the ready list.  Returns nonzero if this
2027*404b540aSrobert    insn can be scheduled, nonzero if we should silently discard it.  */
2028*404b540aSrobert 
2029*404b540aSrobert static int
can_schedule_ready_p(rtx insn)2030*404b540aSrobert can_schedule_ready_p (rtx insn)
2031*404b540aSrobert {
2032*404b540aSrobert   /* An interblock motion?  */
2033*404b540aSrobert   if (INSN_BB (insn) != target_bb
2034*404b540aSrobert       && IS_SPECULATIVE_INSN (insn)
2035*404b540aSrobert       && !check_live (insn, INSN_BB (insn)))
2036*404b540aSrobert     return 0;
2037*404b540aSrobert   else
2038*404b540aSrobert     return 1;
2039*404b540aSrobert }
2040*404b540aSrobert 
2041*404b540aSrobert /* Updates counter and other information.  Split from can_schedule_ready_p ()
2042*404b540aSrobert    because when we schedule insn speculatively then insn passed to
2043*404b540aSrobert    can_schedule_ready_p () differs from the one passed to
2044*404b540aSrobert    begin_schedule_ready ().  */
2045*404b540aSrobert static void
begin_schedule_ready(rtx insn,rtx last ATTRIBUTE_UNUSED)2046*404b540aSrobert begin_schedule_ready (rtx insn, rtx last ATTRIBUTE_UNUSED)
2047*404b540aSrobert {
2048*404b540aSrobert   /* An interblock motion?  */
2049*404b540aSrobert   if (INSN_BB (insn) != target_bb)
2050*404b540aSrobert     {
2051*404b540aSrobert       if (IS_SPECULATIVE_INSN (insn))
2052*404b540aSrobert 	{
2053*404b540aSrobert 	  gcc_assert (check_live (insn, INSN_BB (insn)));
2054*404b540aSrobert 
2055*404b540aSrobert 	  update_live (insn, INSN_BB (insn));
2056*404b540aSrobert 
2057*404b540aSrobert 	  /* For speculative load, mark insns fed by it.  */
2058*404b540aSrobert 	  if (IS_LOAD_INSN (insn) || FED_BY_SPEC_LOAD (insn))
2059*404b540aSrobert 	    set_spec_fed (insn);
2060*404b540aSrobert 
2061*404b540aSrobert 	  nr_spec++;
2062*404b540aSrobert 	}
2063*404b540aSrobert       nr_inter++;
2064*404b540aSrobert     }
2065*404b540aSrobert   else
2066*404b540aSrobert     {
2067*404b540aSrobert       /* In block motion.  */
2068*404b540aSrobert       sched_target_n_insns++;
2069*404b540aSrobert     }
2070*404b540aSrobert   sched_n_insns++;
2071*404b540aSrobert }
2072*404b540aSrobert 
2073*404b540aSrobert /* Called after INSN has all its hard dependencies resolved and the speculation
2074*404b540aSrobert    of type TS is enough to overcome them all.
2075*404b540aSrobert    Return nonzero if it should be moved to the ready list or the queue, or zero
2076*404b540aSrobert    if we should silently discard it.  */
2077*404b540aSrobert static ds_t
new_ready(rtx next,ds_t ts)2078*404b540aSrobert new_ready (rtx next, ds_t ts)
2079*404b540aSrobert {
2080*404b540aSrobert   if (INSN_BB (next) != target_bb)
2081*404b540aSrobert     {
2082*404b540aSrobert       int not_ex_free = 0;
2083*404b540aSrobert 
2084*404b540aSrobert       /* For speculative insns, before inserting to ready/queue,
2085*404b540aSrobert 	 check live, exception-free, and issue-delay.  */
2086*404b540aSrobert       if (!IS_VALID (INSN_BB (next))
2087*404b540aSrobert 	  || CANT_MOVE (next)
2088*404b540aSrobert 	  || (IS_SPECULATIVE_INSN (next)
2089*404b540aSrobert 	      && ((recog_memoized (next) >= 0
2090*404b540aSrobert 		   && min_insn_conflict_delay (curr_state, next, next)
2091*404b540aSrobert                    > PARAM_VALUE (PARAM_MAX_SCHED_INSN_CONFLICT_DELAY))
2092*404b540aSrobert                   || IS_SPECULATION_CHECK_P (next)
2093*404b540aSrobert 		  || !check_live (next, INSN_BB (next))
2094*404b540aSrobert 		  || (not_ex_free = !is_exception_free (next, INSN_BB (next),
2095*404b540aSrobert 							target_bb)))))
2096*404b540aSrobert 	{
2097*404b540aSrobert 	  if (not_ex_free
2098*404b540aSrobert 	      /* We are here because is_exception_free () == false.
2099*404b540aSrobert 		 But we possibly can handle that with control speculation.  */
2100*404b540aSrobert 	      && current_sched_info->flags & DO_SPECULATION)
2101*404b540aSrobert             /* Here we got new control-speculative instruction.  */
2102*404b540aSrobert             ts = set_dep_weak (ts, BEGIN_CONTROL, MAX_DEP_WEAK);
2103*404b540aSrobert 	  else
2104*404b540aSrobert             ts = (ts & ~SPECULATIVE) | HARD_DEP;
2105*404b540aSrobert 	}
2106*404b540aSrobert     }
2107*404b540aSrobert 
2108*404b540aSrobert   return ts;
2109*404b540aSrobert }
2110*404b540aSrobert 
2111*404b540aSrobert /* Return a string that contains the insn uid and optionally anything else
2112*404b540aSrobert    necessary to identify this insn in an output.  It's valid to use a
2113*404b540aSrobert    static buffer for this.  The ALIGNED parameter should cause the string
2114*404b540aSrobert    to be formatted so that multiple output lines will line up nicely.  */
2115*404b540aSrobert 
2116*404b540aSrobert static const char *
rgn_print_insn(rtx insn,int aligned)2117*404b540aSrobert rgn_print_insn (rtx insn, int aligned)
2118*404b540aSrobert {
2119*404b540aSrobert   static char tmp[80];
2120*404b540aSrobert 
2121*404b540aSrobert   if (aligned)
2122*404b540aSrobert     sprintf (tmp, "b%3d: i%4d", INSN_BB (insn), INSN_UID (insn));
2123*404b540aSrobert   else
2124*404b540aSrobert     {
2125*404b540aSrobert       if (current_nr_blocks > 1 && INSN_BB (insn) != target_bb)
2126*404b540aSrobert 	sprintf (tmp, "%d/b%d", INSN_UID (insn), INSN_BB (insn));
2127*404b540aSrobert       else
2128*404b540aSrobert 	sprintf (tmp, "%d", INSN_UID (insn));
2129*404b540aSrobert     }
2130*404b540aSrobert   return tmp;
2131*404b540aSrobert }
2132*404b540aSrobert 
2133*404b540aSrobert /* Compare priority of two insns.  Return a positive number if the second
2134*404b540aSrobert    insn is to be preferred for scheduling, and a negative one if the first
2135*404b540aSrobert    is to be preferred.  Zero if they are equally good.  */
2136*404b540aSrobert 
2137*404b540aSrobert static int
rgn_rank(rtx insn1,rtx insn2)2138*404b540aSrobert rgn_rank (rtx insn1, rtx insn2)
2139*404b540aSrobert {
2140*404b540aSrobert   /* Some comparison make sense in interblock scheduling only.  */
2141*404b540aSrobert   if (INSN_BB (insn1) != INSN_BB (insn2))
2142*404b540aSrobert     {
2143*404b540aSrobert       int spec_val, prob_val;
2144*404b540aSrobert 
2145*404b540aSrobert       /* Prefer an inblock motion on an interblock motion.  */
2146*404b540aSrobert       if ((INSN_BB (insn2) == target_bb) && (INSN_BB (insn1) != target_bb))
2147*404b540aSrobert 	return 1;
2148*404b540aSrobert       if ((INSN_BB (insn1) == target_bb) && (INSN_BB (insn2) != target_bb))
2149*404b540aSrobert 	return -1;
2150*404b540aSrobert 
2151*404b540aSrobert       /* Prefer a useful motion on a speculative one.  */
2152*404b540aSrobert       spec_val = IS_SPECULATIVE_INSN (insn1) - IS_SPECULATIVE_INSN (insn2);
2153*404b540aSrobert       if (spec_val)
2154*404b540aSrobert 	return spec_val;
2155*404b540aSrobert 
2156*404b540aSrobert       /* Prefer a more probable (speculative) insn.  */
2157*404b540aSrobert       prob_val = INSN_PROBABILITY (insn2) - INSN_PROBABILITY (insn1);
2158*404b540aSrobert       if (prob_val)
2159*404b540aSrobert 	return prob_val;
2160*404b540aSrobert     }
2161*404b540aSrobert   return 0;
2162*404b540aSrobert }
2163*404b540aSrobert 
2164*404b540aSrobert /* NEXT is an instruction that depends on INSN (a backward dependence);
2165*404b540aSrobert    return nonzero if we should include this dependence in priority
2166*404b540aSrobert    calculations.  */
2167*404b540aSrobert 
2168*404b540aSrobert static int
contributes_to_priority(rtx next,rtx insn)2169*404b540aSrobert contributes_to_priority (rtx next, rtx insn)
2170*404b540aSrobert {
2171*404b540aSrobert   /* NEXT and INSN reside in one ebb.  */
2172*404b540aSrobert   return BLOCK_TO_BB (BLOCK_NUM (next)) == BLOCK_TO_BB (BLOCK_NUM (insn));
2173*404b540aSrobert }
2174*404b540aSrobert 
2175*404b540aSrobert /* INSN is a JUMP_INSN, COND_SET is the set of registers that are
2176*404b540aSrobert    conditionally set before INSN.  Store the set of registers that
2177*404b540aSrobert    must be considered as used by this jump in USED and that of
2178*404b540aSrobert    registers that must be considered as set in SET.  */
2179*404b540aSrobert 
2180*404b540aSrobert static void
compute_jump_reg_dependencies(rtx insn ATTRIBUTE_UNUSED,regset cond_exec ATTRIBUTE_UNUSED,regset used ATTRIBUTE_UNUSED,regset set ATTRIBUTE_UNUSED)2181*404b540aSrobert compute_jump_reg_dependencies (rtx insn ATTRIBUTE_UNUSED,
2182*404b540aSrobert 			       regset cond_exec ATTRIBUTE_UNUSED,
2183*404b540aSrobert 			       regset used ATTRIBUTE_UNUSED,
2184*404b540aSrobert 			       regset set ATTRIBUTE_UNUSED)
2185*404b540aSrobert {
2186*404b540aSrobert   /* Nothing to do here, since we postprocess jumps in
2187*404b540aSrobert      add_branch_dependences.  */
2188*404b540aSrobert }
2189*404b540aSrobert 
2190*404b540aSrobert /* Used in schedule_insns to initialize current_sched_info for scheduling
2191*404b540aSrobert    regions (or single basic blocks).  */
2192*404b540aSrobert 
2193*404b540aSrobert static struct sched_info region_sched_info =
2194*404b540aSrobert {
2195*404b540aSrobert   init_ready_list,
2196*404b540aSrobert   can_schedule_ready_p,
2197*404b540aSrobert   schedule_more_p,
2198*404b540aSrobert   new_ready,
2199*404b540aSrobert   rgn_rank,
2200*404b540aSrobert   rgn_print_insn,
2201*404b540aSrobert   contributes_to_priority,
2202*404b540aSrobert   compute_jump_reg_dependencies,
2203*404b540aSrobert 
2204*404b540aSrobert   NULL, NULL,
2205*404b540aSrobert   NULL, NULL,
2206*404b540aSrobert   0, 0, 0,
2207*404b540aSrobert 
2208*404b540aSrobert   add_remove_insn,
2209*404b540aSrobert   begin_schedule_ready,
2210*404b540aSrobert   add_block1,
2211*404b540aSrobert   advance_target_bb,
2212*404b540aSrobert   fix_recovery_cfg,
2213*404b540aSrobert #ifdef ENABLE_CHECKING
2214*404b540aSrobert   region_head_or_leaf_p,
2215*404b540aSrobert #endif
2216*404b540aSrobert   SCHED_RGN | USE_GLAT
2217*404b540aSrobert #ifdef ENABLE_CHECKING
2218*404b540aSrobert   | DETACH_LIFE_INFO
2219*404b540aSrobert #endif
2220*404b540aSrobert };
2221*404b540aSrobert 
2222*404b540aSrobert /* Determine if PAT sets a CLASS_LIKELY_SPILLED_P register.  */
2223*404b540aSrobert 
2224*404b540aSrobert static bool
sets_likely_spilled(rtx pat)2225*404b540aSrobert sets_likely_spilled (rtx pat)
2226*404b540aSrobert {
2227*404b540aSrobert   bool ret = false;
2228*404b540aSrobert   note_stores (pat, sets_likely_spilled_1, &ret);
2229*404b540aSrobert   return ret;
2230*404b540aSrobert }
2231*404b540aSrobert 
2232*404b540aSrobert static void
sets_likely_spilled_1(rtx x,rtx pat,void * data)2233*404b540aSrobert sets_likely_spilled_1 (rtx x, rtx pat, void *data)
2234*404b540aSrobert {
2235*404b540aSrobert   bool *ret = (bool *) data;
2236*404b540aSrobert 
2237*404b540aSrobert   if (GET_CODE (pat) == SET
2238*404b540aSrobert       && REG_P (x)
2239*404b540aSrobert       && REGNO (x) < FIRST_PSEUDO_REGISTER
2240*404b540aSrobert       && CLASS_LIKELY_SPILLED_P (REGNO_REG_CLASS (REGNO (x))))
2241*404b540aSrobert     *ret = true;
2242*404b540aSrobert }
2243*404b540aSrobert 
2244*404b540aSrobert /* Add dependences so that branches are scheduled to run last in their
2245*404b540aSrobert    block.  */
2246*404b540aSrobert 
2247*404b540aSrobert static void
add_branch_dependences(rtx head,rtx tail)2248*404b540aSrobert add_branch_dependences (rtx head, rtx tail)
2249*404b540aSrobert {
2250*404b540aSrobert   rtx insn, last;
2251*404b540aSrobert 
2252*404b540aSrobert   /* For all branches, calls, uses, clobbers, cc0 setters, and instructions
2253*404b540aSrobert      that can throw exceptions, force them to remain in order at the end of
2254*404b540aSrobert      the block by adding dependencies and giving the last a high priority.
2255*404b540aSrobert      There may be notes present, and prev_head may also be a note.
2256*404b540aSrobert 
2257*404b540aSrobert      Branches must obviously remain at the end.  Calls should remain at the
2258*404b540aSrobert      end since moving them results in worse register allocation.  Uses remain
2259*404b540aSrobert      at the end to ensure proper register allocation.
2260*404b540aSrobert 
2261*404b540aSrobert      cc0 setters remain at the end because they can't be moved away from
2262*404b540aSrobert      their cc0 user.
2263*404b540aSrobert 
2264*404b540aSrobert      COND_EXEC insns cannot be moved past a branch (see e.g. PR17808).
2265*404b540aSrobert 
2266*404b540aSrobert      Insns setting CLASS_LIKELY_SPILLED_P registers (usually return values)
2267*404b540aSrobert      are not moved before reload because we can wind up with register
2268*404b540aSrobert      allocation failures.  */
2269*404b540aSrobert 
2270*404b540aSrobert   insn = tail;
2271*404b540aSrobert   last = 0;
2272*404b540aSrobert   while (CALL_P (insn)
2273*404b540aSrobert 	 || JUMP_P (insn)
2274*404b540aSrobert 	 || (NONJUMP_INSN_P (insn)
2275*404b540aSrobert 	     && (GET_CODE (PATTERN (insn)) == USE
2276*404b540aSrobert 		 || GET_CODE (PATTERN (insn)) == CLOBBER
2277*404b540aSrobert 		 || can_throw_internal (insn)
2278*404b540aSrobert #ifdef HAVE_cc0
2279*404b540aSrobert 		 || sets_cc0_p (PATTERN (insn))
2280*404b540aSrobert #endif
2281*404b540aSrobert 		 || (!reload_completed
2282*404b540aSrobert 		     && sets_likely_spilled (PATTERN (insn)))))
2283*404b540aSrobert 	 || NOTE_P (insn))
2284*404b540aSrobert     {
2285*404b540aSrobert       if (!NOTE_P (insn))
2286*404b540aSrobert 	{
2287*404b540aSrobert 	  if (last != 0 && !find_insn_list (insn, LOG_LINKS (last)))
2288*404b540aSrobert 	    {
2289*404b540aSrobert 	      if (! sched_insns_conditions_mutex_p (last, insn))
2290*404b540aSrobert 		add_dependence (last, insn, REG_DEP_ANTI);
2291*404b540aSrobert 	      INSN_REF_COUNT (insn)++;
2292*404b540aSrobert 	    }
2293*404b540aSrobert 
2294*404b540aSrobert 	  CANT_MOVE (insn) = 1;
2295*404b540aSrobert 
2296*404b540aSrobert 	  last = insn;
2297*404b540aSrobert 	}
2298*404b540aSrobert 
2299*404b540aSrobert       /* Don't overrun the bounds of the basic block.  */
2300*404b540aSrobert       if (insn == head)
2301*404b540aSrobert 	break;
2302*404b540aSrobert 
2303*404b540aSrobert       insn = PREV_INSN (insn);
2304*404b540aSrobert     }
2305*404b540aSrobert 
2306*404b540aSrobert   /* Make sure these insns are scheduled last in their block.  */
2307*404b540aSrobert   insn = last;
2308*404b540aSrobert   if (insn != 0)
2309*404b540aSrobert     while (insn != head)
2310*404b540aSrobert       {
2311*404b540aSrobert 	insn = prev_nonnote_insn (insn);
2312*404b540aSrobert 
2313*404b540aSrobert 	if (INSN_REF_COUNT (insn) != 0)
2314*404b540aSrobert 	  continue;
2315*404b540aSrobert 
2316*404b540aSrobert 	if (! sched_insns_conditions_mutex_p (last, insn))
2317*404b540aSrobert 	  add_dependence (last, insn, REG_DEP_ANTI);
2318*404b540aSrobert 	INSN_REF_COUNT (insn) = 1;
2319*404b540aSrobert       }
2320*404b540aSrobert 
2321*404b540aSrobert #ifdef HAVE_conditional_execution
2322*404b540aSrobert   /* Finally, if the block ends in a jump, and we are doing intra-block
2323*404b540aSrobert      scheduling, make sure that the branch depends on any COND_EXEC insns
2324*404b540aSrobert      inside the block to avoid moving the COND_EXECs past the branch insn.
2325*404b540aSrobert 
2326*404b540aSrobert      We only have to do this after reload, because (1) before reload there
2327*404b540aSrobert      are no COND_EXEC insns, and (2) the region scheduler is an intra-block
2328*404b540aSrobert      scheduler after reload.
2329*404b540aSrobert 
2330*404b540aSrobert      FIXME: We could in some cases move COND_EXEC insns past the branch if
2331*404b540aSrobert      this scheduler would be a little smarter.  Consider this code:
2332*404b540aSrobert 
2333*404b540aSrobert 		T = [addr]
2334*404b540aSrobert 	C  ?	addr += 4
2335*404b540aSrobert 	!C ?	X += 12
2336*404b540aSrobert 	C  ?	T += 1
2337*404b540aSrobert 	C  ?	jump foo
2338*404b540aSrobert 
2339*404b540aSrobert      On a target with a one cycle stall on a memory access the optimal
2340*404b540aSrobert      sequence would be:
2341*404b540aSrobert 
2342*404b540aSrobert 		T = [addr]
2343*404b540aSrobert 	C  ?	addr += 4
2344*404b540aSrobert 	C  ?	T += 1
2345*404b540aSrobert 	C  ?	jump foo
2346*404b540aSrobert 	!C ?	X += 12
2347*404b540aSrobert 
2348*404b540aSrobert      We don't want to put the 'X += 12' before the branch because it just
2349*404b540aSrobert      wastes a cycle of execution time when the branch is taken.
2350*404b540aSrobert 
2351*404b540aSrobert      Note that in the example "!C" will always be true.  That is another
2352*404b540aSrobert      possible improvement for handling COND_EXECs in this scheduler: it
2353*404b540aSrobert      could remove always-true predicates.  */
2354*404b540aSrobert 
2355*404b540aSrobert   if (!reload_completed || ! JUMP_P (tail))
2356*404b540aSrobert     return;
2357*404b540aSrobert 
2358*404b540aSrobert   insn = tail;
2359*404b540aSrobert   while (insn != head)
2360*404b540aSrobert     {
2361*404b540aSrobert       insn = PREV_INSN (insn);
2362*404b540aSrobert 
2363*404b540aSrobert       /* Note that we want to add this dependency even when
2364*404b540aSrobert 	 sched_insns_conditions_mutex_p returns true.  The whole point
2365*404b540aSrobert 	 is that we _want_ this dependency, even if these insns really
2366*404b540aSrobert 	 are independent.  */
2367*404b540aSrobert       if (INSN_P (insn) && GET_CODE (PATTERN (insn)) == COND_EXEC)
2368*404b540aSrobert 	add_dependence (tail, insn, REG_DEP_ANTI);
2369*404b540aSrobert     }
2370*404b540aSrobert #endif
2371*404b540aSrobert }
2372*404b540aSrobert 
2373*404b540aSrobert /* Data structures for the computation of data dependences in a regions.  We
2374*404b540aSrobert    keep one `deps' structure for every basic block.  Before analyzing the
2375*404b540aSrobert    data dependences for a bb, its variables are initialized as a function of
2376*404b540aSrobert    the variables of its predecessors.  When the analysis for a bb completes,
2377*404b540aSrobert    we save the contents to the corresponding bb_deps[bb] variable.  */
2378*404b540aSrobert 
2379*404b540aSrobert static struct deps *bb_deps;
2380*404b540aSrobert 
2381*404b540aSrobert /* Duplicate the INSN_LIST elements of COPY and prepend them to OLD.  */
2382*404b540aSrobert 
2383*404b540aSrobert static rtx
concat_INSN_LIST(rtx copy,rtx old)2384*404b540aSrobert concat_INSN_LIST (rtx copy, rtx old)
2385*404b540aSrobert {
2386*404b540aSrobert   rtx new = old;
2387*404b540aSrobert   for (; copy ; copy = XEXP (copy, 1))
2388*404b540aSrobert     new = alloc_INSN_LIST (XEXP (copy, 0), new);
2389*404b540aSrobert   return new;
2390*404b540aSrobert }
2391*404b540aSrobert 
2392*404b540aSrobert static void
concat_insn_mem_list(rtx copy_insns,rtx copy_mems,rtx * old_insns_p,rtx * old_mems_p)2393*404b540aSrobert concat_insn_mem_list (rtx copy_insns, rtx copy_mems, rtx *old_insns_p,
2394*404b540aSrobert 		      rtx *old_mems_p)
2395*404b540aSrobert {
2396*404b540aSrobert   rtx new_insns = *old_insns_p;
2397*404b540aSrobert   rtx new_mems = *old_mems_p;
2398*404b540aSrobert 
2399*404b540aSrobert   while (copy_insns)
2400*404b540aSrobert     {
2401*404b540aSrobert       new_insns = alloc_INSN_LIST (XEXP (copy_insns, 0), new_insns);
2402*404b540aSrobert       new_mems = alloc_EXPR_LIST (VOIDmode, XEXP (copy_mems, 0), new_mems);
2403*404b540aSrobert       copy_insns = XEXP (copy_insns, 1);
2404*404b540aSrobert       copy_mems = XEXP (copy_mems, 1);
2405*404b540aSrobert     }
2406*404b540aSrobert 
2407*404b540aSrobert   *old_insns_p = new_insns;
2408*404b540aSrobert   *old_mems_p = new_mems;
2409*404b540aSrobert }
2410*404b540aSrobert 
2411*404b540aSrobert /* After computing the dependencies for block BB, propagate the dependencies
2412*404b540aSrobert    found in TMP_DEPS to the successors of the block.  */
2413*404b540aSrobert static void
propagate_deps(int bb,struct deps * pred_deps)2414*404b540aSrobert propagate_deps (int bb, struct deps *pred_deps)
2415*404b540aSrobert {
2416*404b540aSrobert   basic_block block = BASIC_BLOCK (BB_TO_BLOCK (bb));
2417*404b540aSrobert   edge_iterator ei;
2418*404b540aSrobert   edge e;
2419*404b540aSrobert 
2420*404b540aSrobert   /* bb's structures are inherited by its successors.  */
2421*404b540aSrobert   FOR_EACH_EDGE (e, ei, block->succs)
2422*404b540aSrobert     {
2423*404b540aSrobert       struct deps *succ_deps;
2424*404b540aSrobert       unsigned reg;
2425*404b540aSrobert       reg_set_iterator rsi;
2426*404b540aSrobert 
2427*404b540aSrobert       /* Only bbs "below" bb, in the same region, are interesting.  */
2428*404b540aSrobert       if (e->dest == EXIT_BLOCK_PTR
2429*404b540aSrobert 	  || CONTAINING_RGN (block->index) != CONTAINING_RGN (e->dest->index)
2430*404b540aSrobert 	  || BLOCK_TO_BB (e->dest->index) <= bb)
2431*404b540aSrobert 	continue;
2432*404b540aSrobert 
2433*404b540aSrobert       succ_deps = bb_deps + BLOCK_TO_BB (e->dest->index);
2434*404b540aSrobert 
2435*404b540aSrobert       /* The reg_last lists are inherited by successor.  */
2436*404b540aSrobert       EXECUTE_IF_SET_IN_REG_SET (&pred_deps->reg_last_in_use, 0, reg, rsi)
2437*404b540aSrobert 	{
2438*404b540aSrobert 	  struct deps_reg *pred_rl = &pred_deps->reg_last[reg];
2439*404b540aSrobert 	  struct deps_reg *succ_rl = &succ_deps->reg_last[reg];
2440*404b540aSrobert 
2441*404b540aSrobert 	  succ_rl->uses = concat_INSN_LIST (pred_rl->uses, succ_rl->uses);
2442*404b540aSrobert 	  succ_rl->sets = concat_INSN_LIST (pred_rl->sets, succ_rl->sets);
2443*404b540aSrobert 	  succ_rl->clobbers = concat_INSN_LIST (pred_rl->clobbers,
2444*404b540aSrobert 						succ_rl->clobbers);
2445*404b540aSrobert 	  succ_rl->uses_length += pred_rl->uses_length;
2446*404b540aSrobert 	  succ_rl->clobbers_length += pred_rl->clobbers_length;
2447*404b540aSrobert 	}
2448*404b540aSrobert       IOR_REG_SET (&succ_deps->reg_last_in_use, &pred_deps->reg_last_in_use);
2449*404b540aSrobert 
2450*404b540aSrobert       /* Mem read/write lists are inherited by successor.  */
2451*404b540aSrobert       concat_insn_mem_list (pred_deps->pending_read_insns,
2452*404b540aSrobert 			    pred_deps->pending_read_mems,
2453*404b540aSrobert 			    &succ_deps->pending_read_insns,
2454*404b540aSrobert 			    &succ_deps->pending_read_mems);
2455*404b540aSrobert       concat_insn_mem_list (pred_deps->pending_write_insns,
2456*404b540aSrobert 			    pred_deps->pending_write_mems,
2457*404b540aSrobert 			    &succ_deps->pending_write_insns,
2458*404b540aSrobert 			    &succ_deps->pending_write_mems);
2459*404b540aSrobert 
2460*404b540aSrobert       succ_deps->last_pending_memory_flush
2461*404b540aSrobert 	= concat_INSN_LIST (pred_deps->last_pending_memory_flush,
2462*404b540aSrobert 			    succ_deps->last_pending_memory_flush);
2463*404b540aSrobert 
2464*404b540aSrobert       succ_deps->pending_lists_length += pred_deps->pending_lists_length;
2465*404b540aSrobert       succ_deps->pending_flush_length += pred_deps->pending_flush_length;
2466*404b540aSrobert 
2467*404b540aSrobert       /* last_function_call is inherited by successor.  */
2468*404b540aSrobert       succ_deps->last_function_call
2469*404b540aSrobert 	= concat_INSN_LIST (pred_deps->last_function_call,
2470*404b540aSrobert 			      succ_deps->last_function_call);
2471*404b540aSrobert 
2472*404b540aSrobert       /* sched_before_next_call is inherited by successor.  */
2473*404b540aSrobert       succ_deps->sched_before_next_call
2474*404b540aSrobert 	= concat_INSN_LIST (pred_deps->sched_before_next_call,
2475*404b540aSrobert 			    succ_deps->sched_before_next_call);
2476*404b540aSrobert     }
2477*404b540aSrobert 
2478*404b540aSrobert   /* These lists should point to the right place, for correct
2479*404b540aSrobert      freeing later.  */
2480*404b540aSrobert   bb_deps[bb].pending_read_insns = pred_deps->pending_read_insns;
2481*404b540aSrobert   bb_deps[bb].pending_read_mems = pred_deps->pending_read_mems;
2482*404b540aSrobert   bb_deps[bb].pending_write_insns = pred_deps->pending_write_insns;
2483*404b540aSrobert   bb_deps[bb].pending_write_mems = pred_deps->pending_write_mems;
2484*404b540aSrobert 
2485*404b540aSrobert   /* Can't allow these to be freed twice.  */
2486*404b540aSrobert   pred_deps->pending_read_insns = 0;
2487*404b540aSrobert   pred_deps->pending_read_mems = 0;
2488*404b540aSrobert   pred_deps->pending_write_insns = 0;
2489*404b540aSrobert   pred_deps->pending_write_mems = 0;
2490*404b540aSrobert }
2491*404b540aSrobert 
2492*404b540aSrobert /* Compute backward dependences inside bb.  In a multiple blocks region:
2493*404b540aSrobert    (1) a bb is analyzed after its predecessors, and (2) the lists in
2494*404b540aSrobert    effect at the end of bb (after analyzing for bb) are inherited by
2495*404b540aSrobert    bb's successors.
2496*404b540aSrobert 
2497*404b540aSrobert    Specifically for reg-reg data dependences, the block insns are
2498*404b540aSrobert    scanned by sched_analyze () top-to-bottom.  Two lists are
2499*404b540aSrobert    maintained by sched_analyze (): reg_last[].sets for register DEFs,
2500*404b540aSrobert    and reg_last[].uses for register USEs.
2501*404b540aSrobert 
2502*404b540aSrobert    When analysis is completed for bb, we update for its successors:
2503*404b540aSrobert    ;  - DEFS[succ] = Union (DEFS [succ], DEFS [bb])
2504*404b540aSrobert    ;  - USES[succ] = Union (USES [succ], DEFS [bb])
2505*404b540aSrobert 
2506*404b540aSrobert    The mechanism for computing mem-mem data dependence is very
2507*404b540aSrobert    similar, and the result is interblock dependences in the region.  */
2508*404b540aSrobert 
2509*404b540aSrobert static void
compute_block_backward_dependences(int bb)2510*404b540aSrobert compute_block_backward_dependences (int bb)
2511*404b540aSrobert {
2512*404b540aSrobert   rtx head, tail;
2513*404b540aSrobert   struct deps tmp_deps;
2514*404b540aSrobert 
2515*404b540aSrobert   tmp_deps = bb_deps[bb];
2516*404b540aSrobert 
2517*404b540aSrobert   /* Do the analysis for this block.  */
2518*404b540aSrobert   gcc_assert (EBB_FIRST_BB (bb) == EBB_LAST_BB (bb));
2519*404b540aSrobert   get_ebb_head_tail (EBB_FIRST_BB (bb), EBB_LAST_BB (bb), &head, &tail);
2520*404b540aSrobert   sched_analyze (&tmp_deps, head, tail);
2521*404b540aSrobert   add_branch_dependences (head, tail);
2522*404b540aSrobert 
2523*404b540aSrobert   if (current_nr_blocks > 1)
2524*404b540aSrobert     propagate_deps (bb, &tmp_deps);
2525*404b540aSrobert 
2526*404b540aSrobert   /* Free up the INSN_LISTs.  */
2527*404b540aSrobert   free_deps (&tmp_deps);
2528*404b540aSrobert }
2529*404b540aSrobert 
2530*404b540aSrobert /* Remove all INSN_LISTs and EXPR_LISTs from the pending lists and add
2531*404b540aSrobert    them to the unused_*_list variables, so that they can be reused.  */
2532*404b540aSrobert 
2533*404b540aSrobert static void
free_pending_lists(void)2534*404b540aSrobert free_pending_lists (void)
2535*404b540aSrobert {
2536*404b540aSrobert   int bb;
2537*404b540aSrobert 
2538*404b540aSrobert   for (bb = 0; bb < current_nr_blocks; bb++)
2539*404b540aSrobert     {
2540*404b540aSrobert       free_INSN_LIST_list (&bb_deps[bb].pending_read_insns);
2541*404b540aSrobert       free_INSN_LIST_list (&bb_deps[bb].pending_write_insns);
2542*404b540aSrobert       free_EXPR_LIST_list (&bb_deps[bb].pending_read_mems);
2543*404b540aSrobert       free_EXPR_LIST_list (&bb_deps[bb].pending_write_mems);
2544*404b540aSrobert     }
2545*404b540aSrobert }
2546*404b540aSrobert 
2547*404b540aSrobert /* Print dependences for debugging, callable from debugger.  */
2548*404b540aSrobert 
2549*404b540aSrobert void
debug_dependencies(void)2550*404b540aSrobert debug_dependencies (void)
2551*404b540aSrobert {
2552*404b540aSrobert   int bb;
2553*404b540aSrobert 
2554*404b540aSrobert   fprintf (sched_dump, ";;   --------------- forward dependences: ------------ \n");
2555*404b540aSrobert   for (bb = 0; bb < current_nr_blocks; bb++)
2556*404b540aSrobert     {
2557*404b540aSrobert       rtx head, tail;
2558*404b540aSrobert       rtx next_tail;
2559*404b540aSrobert       rtx insn;
2560*404b540aSrobert 
2561*404b540aSrobert       gcc_assert (EBB_FIRST_BB (bb) == EBB_LAST_BB (bb));
2562*404b540aSrobert       get_ebb_head_tail (EBB_FIRST_BB (bb), EBB_LAST_BB (bb), &head, &tail);
2563*404b540aSrobert       next_tail = NEXT_INSN (tail);
2564*404b540aSrobert       fprintf (sched_dump, "\n;;   --- Region Dependences --- b %d bb %d \n",
2565*404b540aSrobert 	       BB_TO_BLOCK (bb), bb);
2566*404b540aSrobert 
2567*404b540aSrobert       fprintf (sched_dump, ";;   %7s%6s%6s%6s%6s%6s%14s\n",
2568*404b540aSrobert 	       "insn", "code", "bb", "dep", "prio", "cost",
2569*404b540aSrobert 	       "reservation");
2570*404b540aSrobert       fprintf (sched_dump, ";;   %7s%6s%6s%6s%6s%6s%14s\n",
2571*404b540aSrobert 	       "----", "----", "--", "---", "----", "----",
2572*404b540aSrobert 	       "-----------");
2573*404b540aSrobert 
2574*404b540aSrobert       for (insn = head; insn != next_tail; insn = NEXT_INSN (insn))
2575*404b540aSrobert 	{
2576*404b540aSrobert 	  rtx link;
2577*404b540aSrobert 
2578*404b540aSrobert 	  if (! INSN_P (insn))
2579*404b540aSrobert 	    {
2580*404b540aSrobert 	      int n;
2581*404b540aSrobert 	      fprintf (sched_dump, ";;   %6d ", INSN_UID (insn));
2582*404b540aSrobert 	      if (NOTE_P (insn))
2583*404b540aSrobert 		{
2584*404b540aSrobert 		  n = NOTE_LINE_NUMBER (insn);
2585*404b540aSrobert 		  if (n < 0)
2586*404b540aSrobert 		    fprintf (sched_dump, "%s\n", GET_NOTE_INSN_NAME (n));
2587*404b540aSrobert 		  else
2588*404b540aSrobert 		    {
2589*404b540aSrobert 		      expanded_location xloc;
2590*404b540aSrobert 		      NOTE_EXPANDED_LOCATION (xloc, insn);
2591*404b540aSrobert 		      fprintf (sched_dump, "line %d, file %s\n",
2592*404b540aSrobert 			       xloc.line, xloc.file);
2593*404b540aSrobert 		    }
2594*404b540aSrobert 		}
2595*404b540aSrobert 	      else
2596*404b540aSrobert 		fprintf (sched_dump, " {%s}\n", GET_RTX_NAME (GET_CODE (insn)));
2597*404b540aSrobert 	      continue;
2598*404b540aSrobert 	    }
2599*404b540aSrobert 
2600*404b540aSrobert 	  fprintf (sched_dump,
2601*404b540aSrobert 		   ";;   %s%5d%6d%6d%6d%6d%6d   ",
2602*404b540aSrobert 		   (SCHED_GROUP_P (insn) ? "+" : " "),
2603*404b540aSrobert 		   INSN_UID (insn),
2604*404b540aSrobert 		   INSN_CODE (insn),
2605*404b540aSrobert 		   INSN_BB (insn),
2606*404b540aSrobert 		   INSN_DEP_COUNT (insn),
2607*404b540aSrobert 		   INSN_PRIORITY (insn),
2608*404b540aSrobert 		   insn_cost (insn, 0, 0));
2609*404b540aSrobert 
2610*404b540aSrobert 	  if (recog_memoized (insn) < 0)
2611*404b540aSrobert 	    fprintf (sched_dump, "nothing");
2612*404b540aSrobert 	  else
2613*404b540aSrobert 	    print_reservation (sched_dump, insn);
2614*404b540aSrobert 
2615*404b540aSrobert 	  fprintf (sched_dump, "\t: ");
2616*404b540aSrobert 	  for (link = INSN_DEPEND (insn); link; link = XEXP (link, 1))
2617*404b540aSrobert 	    fprintf (sched_dump, "%d ", INSN_UID (XEXP (link, 0)));
2618*404b540aSrobert 	  fprintf (sched_dump, "\n");
2619*404b540aSrobert 	}
2620*404b540aSrobert     }
2621*404b540aSrobert   fprintf (sched_dump, "\n");
2622*404b540aSrobert }
2623*404b540aSrobert 
2624*404b540aSrobert /* Returns true if all the basic blocks of the current region have
2625*404b540aSrobert    NOTE_DISABLE_SCHED_OF_BLOCK which means not to schedule that region.  */
2626*404b540aSrobert static bool
sched_is_disabled_for_current_region_p(void)2627*404b540aSrobert sched_is_disabled_for_current_region_p (void)
2628*404b540aSrobert {
2629*404b540aSrobert   int bb;
2630*404b540aSrobert 
2631*404b540aSrobert   for (bb = 0; bb < current_nr_blocks; bb++)
2632*404b540aSrobert     if (!(BASIC_BLOCK (BB_TO_BLOCK (bb))->flags & BB_DISABLE_SCHEDULE))
2633*404b540aSrobert       return false;
2634*404b540aSrobert 
2635*404b540aSrobert   return true;
2636*404b540aSrobert }
2637*404b540aSrobert 
2638*404b540aSrobert /* Schedule a region.  A region is either an inner loop, a loop-free
2639*404b540aSrobert    subroutine, or a single basic block.  Each bb in the region is
2640*404b540aSrobert    scheduled after its flow predecessors.  */
2641*404b540aSrobert 
2642*404b540aSrobert static void
schedule_region(int rgn)2643*404b540aSrobert schedule_region (int rgn)
2644*404b540aSrobert {
2645*404b540aSrobert   basic_block block;
2646*404b540aSrobert   edge_iterator ei;
2647*404b540aSrobert   edge e;
2648*404b540aSrobert   int bb;
2649*404b540aSrobert   int sched_rgn_n_insns = 0;
2650*404b540aSrobert 
2651*404b540aSrobert   rgn_n_insns = 0;
2652*404b540aSrobert   /* Set variables for the current region.  */
2653*404b540aSrobert   current_nr_blocks = RGN_NR_BLOCKS (rgn);
2654*404b540aSrobert   current_blocks = RGN_BLOCKS (rgn);
2655*404b540aSrobert 
2656*404b540aSrobert   /* See comments in add_block1, for what reasons we allocate +1 element.  */
2657*404b540aSrobert   ebb_head = xrealloc (ebb_head, (current_nr_blocks + 1) * sizeof (*ebb_head));
2658*404b540aSrobert   for (bb = 0; bb <= current_nr_blocks; bb++)
2659*404b540aSrobert     ebb_head[bb] = current_blocks + bb;
2660*404b540aSrobert 
2661*404b540aSrobert   /* Don't schedule region that is marked by
2662*404b540aSrobert      NOTE_DISABLE_SCHED_OF_BLOCK.  */
2663*404b540aSrobert   if (sched_is_disabled_for_current_region_p ())
2664*404b540aSrobert     return;
2665*404b540aSrobert 
2666*404b540aSrobert   if (!RGN_DONT_CALC_DEPS (rgn))
2667*404b540aSrobert     {
2668*404b540aSrobert       init_deps_global ();
2669*404b540aSrobert 
2670*404b540aSrobert       /* Initializations for region data dependence analysis.  */
2671*404b540aSrobert       bb_deps = XNEWVEC (struct deps, current_nr_blocks);
2672*404b540aSrobert       for (bb = 0; bb < current_nr_blocks; bb++)
2673*404b540aSrobert 	init_deps (bb_deps + bb);
2674*404b540aSrobert 
2675*404b540aSrobert       /* Compute LOG_LINKS.  */
2676*404b540aSrobert       for (bb = 0; bb < current_nr_blocks; bb++)
2677*404b540aSrobert         compute_block_backward_dependences (bb);
2678*404b540aSrobert 
2679*404b540aSrobert       /* Compute INSN_DEPEND.  */
2680*404b540aSrobert       for (bb = current_nr_blocks - 1; bb >= 0; bb--)
2681*404b540aSrobert         {
2682*404b540aSrobert           rtx head, tail;
2683*404b540aSrobert 
2684*404b540aSrobert 	  gcc_assert (EBB_FIRST_BB (bb) == EBB_LAST_BB (bb));
2685*404b540aSrobert           get_ebb_head_tail (EBB_FIRST_BB (bb), EBB_LAST_BB (bb), &head, &tail);
2686*404b540aSrobert 
2687*404b540aSrobert           compute_forward_dependences (head, tail);
2688*404b540aSrobert 
2689*404b540aSrobert           if (targetm.sched.dependencies_evaluation_hook)
2690*404b540aSrobert             targetm.sched.dependencies_evaluation_hook (head, tail);
2691*404b540aSrobert         }
2692*404b540aSrobert 
2693*404b540aSrobert       free_pending_lists ();
2694*404b540aSrobert 
2695*404b540aSrobert       finish_deps_global ();
2696*404b540aSrobert 
2697*404b540aSrobert       free (bb_deps);
2698*404b540aSrobert     }
2699*404b540aSrobert   else
2700*404b540aSrobert     /* This is a recovery block.  It is always a single block region.  */
2701*404b540aSrobert     gcc_assert (current_nr_blocks == 1);
2702*404b540aSrobert 
2703*404b540aSrobert   /* Set priorities.  */
2704*404b540aSrobert   current_sched_info->sched_max_insns_priority = 0;
2705*404b540aSrobert   for (bb = 0; bb < current_nr_blocks; bb++)
2706*404b540aSrobert     {
2707*404b540aSrobert       rtx head, tail;
2708*404b540aSrobert 
2709*404b540aSrobert       gcc_assert (EBB_FIRST_BB (bb) == EBB_LAST_BB (bb));
2710*404b540aSrobert       get_ebb_head_tail (EBB_FIRST_BB (bb), EBB_LAST_BB (bb), &head, &tail);
2711*404b540aSrobert 
2712*404b540aSrobert       rgn_n_insns += set_priorities (head, tail);
2713*404b540aSrobert     }
2714*404b540aSrobert   current_sched_info->sched_max_insns_priority++;
2715*404b540aSrobert 
2716*404b540aSrobert   /* Compute interblock info: probabilities, split-edges, dominators, etc.  */
2717*404b540aSrobert   if (current_nr_blocks > 1)
2718*404b540aSrobert     {
2719*404b540aSrobert       prob = XNEWVEC (int, current_nr_blocks);
2720*404b540aSrobert 
2721*404b540aSrobert       dom = sbitmap_vector_alloc (current_nr_blocks, current_nr_blocks);
2722*404b540aSrobert       sbitmap_vector_zero (dom, current_nr_blocks);
2723*404b540aSrobert 
2724*404b540aSrobert       /* Use ->aux to implement EDGE_TO_BIT mapping.  */
2725*404b540aSrobert       rgn_nr_edges = 0;
2726*404b540aSrobert       FOR_EACH_BB (block)
2727*404b540aSrobert 	{
2728*404b540aSrobert 	  if (CONTAINING_RGN (block->index) != rgn)
2729*404b540aSrobert 	    continue;
2730*404b540aSrobert 	  FOR_EACH_EDGE (e, ei, block->succs)
2731*404b540aSrobert 	    SET_EDGE_TO_BIT (e, rgn_nr_edges++);
2732*404b540aSrobert 	}
2733*404b540aSrobert 
2734*404b540aSrobert       rgn_edges = XNEWVEC (edge, rgn_nr_edges);
2735*404b540aSrobert       rgn_nr_edges = 0;
2736*404b540aSrobert       FOR_EACH_BB (block)
2737*404b540aSrobert 	{
2738*404b540aSrobert 	  if (CONTAINING_RGN (block->index) != rgn)
2739*404b540aSrobert 	    continue;
2740*404b540aSrobert 	  FOR_EACH_EDGE (e, ei, block->succs)
2741*404b540aSrobert 	    rgn_edges[rgn_nr_edges++] = e;
2742*404b540aSrobert 	}
2743*404b540aSrobert 
2744*404b540aSrobert       /* Split edges.  */
2745*404b540aSrobert       pot_split = sbitmap_vector_alloc (current_nr_blocks, rgn_nr_edges);
2746*404b540aSrobert       sbitmap_vector_zero (pot_split, current_nr_blocks);
2747*404b540aSrobert       ancestor_edges = sbitmap_vector_alloc (current_nr_blocks, rgn_nr_edges);
2748*404b540aSrobert       sbitmap_vector_zero (ancestor_edges, current_nr_blocks);
2749*404b540aSrobert 
2750*404b540aSrobert       /* Compute probabilities, dominators, split_edges.  */
2751*404b540aSrobert       for (bb = 0; bb < current_nr_blocks; bb++)
2752*404b540aSrobert 	compute_dom_prob_ps (bb);
2753*404b540aSrobert 
2754*404b540aSrobert       /* Cleanup ->aux used for EDGE_TO_BIT mapping.  */
2755*404b540aSrobert       /* We don't need them anymore.  But we want to avoid duplication of
2756*404b540aSrobert 	 aux fields in the newly created edges.  */
2757*404b540aSrobert       FOR_EACH_BB (block)
2758*404b540aSrobert 	{
2759*404b540aSrobert 	  if (CONTAINING_RGN (block->index) != rgn)
2760*404b540aSrobert 	    continue;
2761*404b540aSrobert 	  FOR_EACH_EDGE (e, ei, block->succs)
2762*404b540aSrobert 	    e->aux = NULL;
2763*404b540aSrobert         }
2764*404b540aSrobert     }
2765*404b540aSrobert 
2766*404b540aSrobert   /* Now we can schedule all blocks.  */
2767*404b540aSrobert   for (bb = 0; bb < current_nr_blocks; bb++)
2768*404b540aSrobert     {
2769*404b540aSrobert       basic_block first_bb, last_bb, curr_bb;
2770*404b540aSrobert       rtx head, tail;
2771*404b540aSrobert       int b = BB_TO_BLOCK (bb);
2772*404b540aSrobert 
2773*404b540aSrobert       first_bb = EBB_FIRST_BB (bb);
2774*404b540aSrobert       last_bb = EBB_LAST_BB (bb);
2775*404b540aSrobert 
2776*404b540aSrobert       get_ebb_head_tail (first_bb, last_bb, &head, &tail);
2777*404b540aSrobert 
2778*404b540aSrobert       if (no_real_insns_p (head, tail))
2779*404b540aSrobert 	{
2780*404b540aSrobert 	  gcc_assert (first_bb == last_bb);
2781*404b540aSrobert 	  continue;
2782*404b540aSrobert 	}
2783*404b540aSrobert 
2784*404b540aSrobert       current_sched_info->prev_head = PREV_INSN (head);
2785*404b540aSrobert       current_sched_info->next_tail = NEXT_INSN (tail);
2786*404b540aSrobert 
2787*404b540aSrobert       if (write_symbols != NO_DEBUG)
2788*404b540aSrobert 	{
2789*404b540aSrobert 	  save_line_notes (b, head, tail);
2790*404b540aSrobert 	  rm_line_notes (head, tail);
2791*404b540aSrobert 	}
2792*404b540aSrobert 
2793*404b540aSrobert       /* rm_other_notes only removes notes which are _inside_ the
2794*404b540aSrobert 	 block---that is, it won't remove notes before the first real insn
2795*404b540aSrobert 	 or after the last real insn of the block.  So if the first insn
2796*404b540aSrobert 	 has a REG_SAVE_NOTE which would otherwise be emitted before the
2797*404b540aSrobert 	 insn, it is redundant with the note before the start of the
2798*404b540aSrobert 	 block, and so we have to take it out.  */
2799*404b540aSrobert       if (INSN_P (head))
2800*404b540aSrobert 	{
2801*404b540aSrobert 	  rtx note;
2802*404b540aSrobert 
2803*404b540aSrobert 	  for (note = REG_NOTES (head); note; note = XEXP (note, 1))
2804*404b540aSrobert 	    if (REG_NOTE_KIND (note) == REG_SAVE_NOTE)
2805*404b540aSrobert 	      remove_note (head, note);
2806*404b540aSrobert 	}
2807*404b540aSrobert       else
2808*404b540aSrobert 	/* This means that first block in ebb is empty.
2809*404b540aSrobert 	   It looks to me as an impossible thing.  There at least should be
2810*404b540aSrobert 	   a recovery check, that caused the splitting.  */
2811*404b540aSrobert 	gcc_unreachable ();
2812*404b540aSrobert 
2813*404b540aSrobert       /* Remove remaining note insns from the block, save them in
2814*404b540aSrobert 	 note_list.  These notes are restored at the end of
2815*404b540aSrobert 	 schedule_block ().  */
2816*404b540aSrobert       rm_other_notes (head, tail);
2817*404b540aSrobert 
2818*404b540aSrobert       unlink_bb_notes (first_bb, last_bb);
2819*404b540aSrobert 
2820*404b540aSrobert       target_bb = bb;
2821*404b540aSrobert 
2822*404b540aSrobert       gcc_assert (flag_schedule_interblock || current_nr_blocks == 1);
2823*404b540aSrobert       current_sched_info->queue_must_finish_empty = current_nr_blocks == 1;
2824*404b540aSrobert 
2825*404b540aSrobert       curr_bb = first_bb;
2826*404b540aSrobert       schedule_block (&curr_bb, rgn_n_insns);
2827*404b540aSrobert       gcc_assert (EBB_FIRST_BB (bb) == first_bb);
2828*404b540aSrobert       sched_rgn_n_insns += sched_n_insns;
2829*404b540aSrobert 
2830*404b540aSrobert       /* Clean up.  */
2831*404b540aSrobert       if (current_nr_blocks > 1)
2832*404b540aSrobert 	{
2833*404b540aSrobert 	  free (candidate_table);
2834*404b540aSrobert 	  free (bblst_table);
2835*404b540aSrobert 	  free (edgelst_table);
2836*404b540aSrobert 	}
2837*404b540aSrobert     }
2838*404b540aSrobert 
2839*404b540aSrobert   /* Sanity check: verify that all region insns were scheduled.  */
2840*404b540aSrobert   gcc_assert (sched_rgn_n_insns == rgn_n_insns);
2841*404b540aSrobert 
2842*404b540aSrobert   /* Restore line notes.  */
2843*404b540aSrobert   if (write_symbols != NO_DEBUG)
2844*404b540aSrobert     {
2845*404b540aSrobert       for (bb = 0; bb < current_nr_blocks; bb++)
2846*404b540aSrobert 	{
2847*404b540aSrobert 	  rtx head, tail;
2848*404b540aSrobert 
2849*404b540aSrobert 	  get_ebb_head_tail (EBB_FIRST_BB (bb), EBB_LAST_BB (bb), &head, &tail);
2850*404b540aSrobert 	  restore_line_notes (head, tail);
2851*404b540aSrobert 	}
2852*404b540aSrobert     }
2853*404b540aSrobert 
2854*404b540aSrobert   /* Done with this region.  */
2855*404b540aSrobert 
2856*404b540aSrobert   if (current_nr_blocks > 1)
2857*404b540aSrobert     {
2858*404b540aSrobert       free (prob);
2859*404b540aSrobert       sbitmap_vector_free (dom);
2860*404b540aSrobert       sbitmap_vector_free (pot_split);
2861*404b540aSrobert       sbitmap_vector_free (ancestor_edges);
2862*404b540aSrobert       free (rgn_edges);
2863*404b540aSrobert     }
2864*404b540aSrobert }
2865*404b540aSrobert 
2866*404b540aSrobert /* Indexed by region, holds the number of death notes found in that region.
2867*404b540aSrobert    Used for consistency checks.  */
2868*404b540aSrobert static int *deaths_in_region;
2869*404b540aSrobert 
2870*404b540aSrobert /* Initialize data structures for region scheduling.  */
2871*404b540aSrobert 
2872*404b540aSrobert static void
init_regions(void)2873*404b540aSrobert init_regions (void)
2874*404b540aSrobert {
2875*404b540aSrobert   sbitmap blocks;
2876*404b540aSrobert   int rgn;
2877*404b540aSrobert 
2878*404b540aSrobert   nr_regions = 0;
2879*404b540aSrobert   rgn_table = 0;
2880*404b540aSrobert   rgn_bb_table = 0;
2881*404b540aSrobert   block_to_bb = 0;
2882*404b540aSrobert   containing_rgn = 0;
2883*404b540aSrobert   extend_regions ();
2884*404b540aSrobert 
2885*404b540aSrobert   /* Compute regions for scheduling.  */
2886*404b540aSrobert   if (reload_completed
2887*404b540aSrobert       || n_basic_blocks == NUM_FIXED_BLOCKS + 1
2888*404b540aSrobert       || !flag_schedule_interblock
2889*404b540aSrobert       || is_cfg_nonregular ())
2890*404b540aSrobert     {
2891*404b540aSrobert       find_single_block_region ();
2892*404b540aSrobert     }
2893*404b540aSrobert   else
2894*404b540aSrobert     {
2895*404b540aSrobert       /* Compute the dominators and post dominators.  */
2896*404b540aSrobert       calculate_dominance_info (CDI_DOMINATORS);
2897*404b540aSrobert 
2898*404b540aSrobert       /* Find regions.  */
2899*404b540aSrobert       find_rgns ();
2900*404b540aSrobert 
2901*404b540aSrobert       if (sched_verbose >= 3)
2902*404b540aSrobert 	debug_regions ();
2903*404b540aSrobert 
2904*404b540aSrobert       /* For now.  This will move as more and more of haifa is converted
2905*404b540aSrobert 	 to using the cfg code in flow.c.  */
2906*404b540aSrobert       free_dominance_info (CDI_DOMINATORS);
2907*404b540aSrobert     }
2908*404b540aSrobert   RGN_BLOCKS (nr_regions) = RGN_BLOCKS (nr_regions - 1) +
2909*404b540aSrobert     RGN_NR_BLOCKS (nr_regions - 1);
2910*404b540aSrobert 
2911*404b540aSrobert 
2912*404b540aSrobert   if (CHECK_DEAD_NOTES)
2913*404b540aSrobert     {
2914*404b540aSrobert       blocks = sbitmap_alloc (last_basic_block);
2915*404b540aSrobert       deaths_in_region = XNEWVEC (int, nr_regions);
2916*404b540aSrobert       /* Remove all death notes from the subroutine.  */
2917*404b540aSrobert       for (rgn = 0; rgn < nr_regions; rgn++)
2918*404b540aSrobert         check_dead_notes1 (rgn, blocks);
2919*404b540aSrobert 
2920*404b540aSrobert       sbitmap_free (blocks);
2921*404b540aSrobert     }
2922*404b540aSrobert   else
2923*404b540aSrobert     count_or_remove_death_notes (NULL, 1);
2924*404b540aSrobert }
2925*404b540aSrobert 
2926*404b540aSrobert /* The one entry point in this file.  */
2927*404b540aSrobert 
2928*404b540aSrobert void
schedule_insns(void)2929*404b540aSrobert schedule_insns (void)
2930*404b540aSrobert {
2931*404b540aSrobert   sbitmap large_region_blocks, blocks;
2932*404b540aSrobert   int rgn;
2933*404b540aSrobert   int any_large_regions;
2934*404b540aSrobert   basic_block bb;
2935*404b540aSrobert 
2936*404b540aSrobert   /* Taking care of this degenerate case makes the rest of
2937*404b540aSrobert      this code simpler.  */
2938*404b540aSrobert   if (n_basic_blocks == NUM_FIXED_BLOCKS)
2939*404b540aSrobert     return;
2940*404b540aSrobert 
2941*404b540aSrobert   nr_inter = 0;
2942*404b540aSrobert   nr_spec = 0;
2943*404b540aSrobert 
2944*404b540aSrobert   /* We need current_sched_info in init_dependency_caches, which is
2945*404b540aSrobert      invoked via sched_init.  */
2946*404b540aSrobert   current_sched_info = &region_sched_info;
2947*404b540aSrobert 
2948*404b540aSrobert   sched_init ();
2949*404b540aSrobert 
2950*404b540aSrobert   min_spec_prob = ((PARAM_VALUE (PARAM_MIN_SPEC_PROB) * REG_BR_PROB_BASE)
2951*404b540aSrobert 		    / 100);
2952*404b540aSrobert 
2953*404b540aSrobert   init_regions ();
2954*404b540aSrobert 
2955*404b540aSrobert   /* EBB_HEAD is a region-scope structure.  But we realloc it for
2956*404b540aSrobert      each region to save time/memory/something else.  */
2957*404b540aSrobert   ebb_head = 0;
2958*404b540aSrobert 
2959*404b540aSrobert   /* Schedule every region in the subroutine.  */
2960*404b540aSrobert   for (rgn = 0; rgn < nr_regions; rgn++)
2961*404b540aSrobert     schedule_region (rgn);
2962*404b540aSrobert 
2963*404b540aSrobert   free(ebb_head);
2964*404b540aSrobert 
2965*404b540aSrobert   /* Update life analysis for the subroutine.  Do single block regions
2966*404b540aSrobert      first so that we can verify that live_at_start didn't change.  Then
2967*404b540aSrobert      do all other blocks.  */
2968*404b540aSrobert   /* ??? There is an outside possibility that update_life_info, or more
2969*404b540aSrobert      to the point propagate_block, could get called with nonzero flags
2970*404b540aSrobert      more than once for one basic block.  This would be kinda bad if it
2971*404b540aSrobert      were to happen, since REG_INFO would be accumulated twice for the
2972*404b540aSrobert      block, and we'd have twice the REG_DEAD notes.
2973*404b540aSrobert 
2974*404b540aSrobert      I'm fairly certain that this _shouldn't_ happen, since I don't think
2975*404b540aSrobert      that live_at_start should change at region heads.  Not sure what the
2976*404b540aSrobert      best way to test for this kind of thing...  */
2977*404b540aSrobert 
2978*404b540aSrobert   if (current_sched_info->flags & DETACH_LIFE_INFO)
2979*404b540aSrobert     /* this flag can be set either by the target or by ENABLE_CHECKING.  */
2980*404b540aSrobert     attach_life_info ();
2981*404b540aSrobert 
2982*404b540aSrobert   allocate_reg_life_data ();
2983*404b540aSrobert 
2984*404b540aSrobert   any_large_regions = 0;
2985*404b540aSrobert   large_region_blocks = sbitmap_alloc (last_basic_block);
2986*404b540aSrobert   sbitmap_zero (large_region_blocks);
2987*404b540aSrobert   FOR_EACH_BB (bb)
2988*404b540aSrobert     SET_BIT (large_region_blocks, bb->index);
2989*404b540aSrobert 
2990*404b540aSrobert   blocks = sbitmap_alloc (last_basic_block);
2991*404b540aSrobert   sbitmap_zero (blocks);
2992*404b540aSrobert 
2993*404b540aSrobert   /* Update life information.  For regions consisting of multiple blocks
2994*404b540aSrobert      we've possibly done interblock scheduling that affects global liveness.
2995*404b540aSrobert      For regions consisting of single blocks we need to do only local
2996*404b540aSrobert      liveness.  */
2997*404b540aSrobert   for (rgn = 0; rgn < nr_regions; rgn++)
2998*404b540aSrobert     if (RGN_NR_BLOCKS (rgn) > 1
2999*404b540aSrobert 	/* Or the only block of this region has been split.  */
3000*404b540aSrobert 	|| RGN_HAS_REAL_EBB (rgn)
3001*404b540aSrobert 	/* New blocks (e.g. recovery blocks) should be processed
3002*404b540aSrobert 	   as parts of large regions.  */
3003*404b540aSrobert 	|| !glat_start[rgn_bb_table[RGN_BLOCKS (rgn)]])
3004*404b540aSrobert       any_large_regions = 1;
3005*404b540aSrobert     else
3006*404b540aSrobert       {
3007*404b540aSrobert 	SET_BIT (blocks, rgn_bb_table[RGN_BLOCKS (rgn)]);
3008*404b540aSrobert 	RESET_BIT (large_region_blocks, rgn_bb_table[RGN_BLOCKS (rgn)]);
3009*404b540aSrobert       }
3010*404b540aSrobert 
3011*404b540aSrobert   /* Don't update reg info after reload, since that affects
3012*404b540aSrobert      regs_ever_live, which should not change after reload.  */
3013*404b540aSrobert   update_life_info (blocks, UPDATE_LIFE_LOCAL,
3014*404b540aSrobert 		    (reload_completed ? PROP_DEATH_NOTES
3015*404b540aSrobert 		     : (PROP_DEATH_NOTES | PROP_REG_INFO)));
3016*404b540aSrobert   if (any_large_regions)
3017*404b540aSrobert     {
3018*404b540aSrobert       update_life_info (large_region_blocks, UPDATE_LIFE_GLOBAL,
3019*404b540aSrobert 			(reload_completed ? PROP_DEATH_NOTES
3020*404b540aSrobert 			 : (PROP_DEATH_NOTES | PROP_REG_INFO)));
3021*404b540aSrobert 
3022*404b540aSrobert #ifdef ENABLE_CHECKING
3023*404b540aSrobert       check_reg_live (true);
3024*404b540aSrobert #endif
3025*404b540aSrobert     }
3026*404b540aSrobert 
3027*404b540aSrobert   if (CHECK_DEAD_NOTES)
3028*404b540aSrobert     {
3029*404b540aSrobert       /* Verify the counts of basic block notes in single basic block
3030*404b540aSrobert          regions.  */
3031*404b540aSrobert       for (rgn = 0; rgn < nr_regions; rgn++)
3032*404b540aSrobert 	if (RGN_NR_BLOCKS (rgn) == 1)
3033*404b540aSrobert 	  {
3034*404b540aSrobert 	    sbitmap_zero (blocks);
3035*404b540aSrobert 	    SET_BIT (blocks, rgn_bb_table[RGN_BLOCKS (rgn)]);
3036*404b540aSrobert 
3037*404b540aSrobert 	    gcc_assert (deaths_in_region[rgn]
3038*404b540aSrobert 			== count_or_remove_death_notes (blocks, 0));
3039*404b540aSrobert 	  }
3040*404b540aSrobert       free (deaths_in_region);
3041*404b540aSrobert     }
3042*404b540aSrobert 
3043*404b540aSrobert   /* Reposition the prologue and epilogue notes in case we moved the
3044*404b540aSrobert      prologue/epilogue insns.  */
3045*404b540aSrobert   if (reload_completed)
3046*404b540aSrobert     reposition_prologue_and_epilogue_notes (get_insns ());
3047*404b540aSrobert 
3048*404b540aSrobert   /* Delete redundant line notes.  */
3049*404b540aSrobert   if (write_symbols != NO_DEBUG)
3050*404b540aSrobert     rm_redundant_line_notes ();
3051*404b540aSrobert 
3052*404b540aSrobert   if (sched_verbose)
3053*404b540aSrobert     {
3054*404b540aSrobert       if (reload_completed == 0 && flag_schedule_interblock)
3055*404b540aSrobert 	{
3056*404b540aSrobert 	  fprintf (sched_dump,
3057*404b540aSrobert 		   "\n;; Procedure interblock/speculative motions == %d/%d \n",
3058*404b540aSrobert 		   nr_inter, nr_spec);
3059*404b540aSrobert 	}
3060*404b540aSrobert       else
3061*404b540aSrobert 	gcc_assert (nr_inter <= 0);
3062*404b540aSrobert       fprintf (sched_dump, "\n\n");
3063*404b540aSrobert     }
3064*404b540aSrobert 
3065*404b540aSrobert   /* Clean up.  */
3066*404b540aSrobert   free (rgn_table);
3067*404b540aSrobert   free (rgn_bb_table);
3068*404b540aSrobert   free (block_to_bb);
3069*404b540aSrobert   free (containing_rgn);
3070*404b540aSrobert 
3071*404b540aSrobert   sched_finish ();
3072*404b540aSrobert 
3073*404b540aSrobert   sbitmap_free (blocks);
3074*404b540aSrobert   sbitmap_free (large_region_blocks);
3075*404b540aSrobert }
3076*404b540aSrobert 
3077*404b540aSrobert /* INSN has been added to/removed from current region.  */
3078*404b540aSrobert static void
add_remove_insn(rtx insn,int remove_p)3079*404b540aSrobert add_remove_insn (rtx insn, int remove_p)
3080*404b540aSrobert {
3081*404b540aSrobert   if (!remove_p)
3082*404b540aSrobert     rgn_n_insns++;
3083*404b540aSrobert   else
3084*404b540aSrobert     rgn_n_insns--;
3085*404b540aSrobert 
3086*404b540aSrobert   if (INSN_BB (insn) == target_bb)
3087*404b540aSrobert     {
3088*404b540aSrobert       if (!remove_p)
3089*404b540aSrobert 	target_n_insns++;
3090*404b540aSrobert       else
3091*404b540aSrobert 	target_n_insns--;
3092*404b540aSrobert     }
3093*404b540aSrobert }
3094*404b540aSrobert 
3095*404b540aSrobert /* Extend internal data structures.  */
3096*404b540aSrobert static void
extend_regions(void)3097*404b540aSrobert extend_regions (void)
3098*404b540aSrobert {
3099*404b540aSrobert   rgn_table = XRESIZEVEC (region, rgn_table, n_basic_blocks);
3100*404b540aSrobert   rgn_bb_table = XRESIZEVEC (int, rgn_bb_table, n_basic_blocks);
3101*404b540aSrobert   block_to_bb = XRESIZEVEC (int, block_to_bb, last_basic_block);
3102*404b540aSrobert   containing_rgn = XRESIZEVEC (int, containing_rgn, last_basic_block);
3103*404b540aSrobert }
3104*404b540aSrobert 
3105*404b540aSrobert /* BB was added to ebb after AFTER.  */
3106*404b540aSrobert static void
add_block1(basic_block bb,basic_block after)3107*404b540aSrobert add_block1 (basic_block bb, basic_block after)
3108*404b540aSrobert {
3109*404b540aSrobert   extend_regions ();
3110*404b540aSrobert 
3111*404b540aSrobert   if (after == 0 || after == EXIT_BLOCK_PTR)
3112*404b540aSrobert     {
3113*404b540aSrobert       int i;
3114*404b540aSrobert 
3115*404b540aSrobert       i = RGN_BLOCKS (nr_regions);
3116*404b540aSrobert       /* I - first free position in rgn_bb_table.  */
3117*404b540aSrobert 
3118*404b540aSrobert       rgn_bb_table[i] = bb->index;
3119*404b540aSrobert       RGN_NR_BLOCKS (nr_regions) = 1;
3120*404b540aSrobert       RGN_DONT_CALC_DEPS (nr_regions) = after == EXIT_BLOCK_PTR;
3121*404b540aSrobert       RGN_HAS_REAL_EBB (nr_regions) = 0;
3122*404b540aSrobert       CONTAINING_RGN (bb->index) = nr_regions;
3123*404b540aSrobert       BLOCK_TO_BB (bb->index) = 0;
3124*404b540aSrobert 
3125*404b540aSrobert       nr_regions++;
3126*404b540aSrobert 
3127*404b540aSrobert       RGN_BLOCKS (nr_regions) = i + 1;
3128*404b540aSrobert 
3129*404b540aSrobert       if (CHECK_DEAD_NOTES)
3130*404b540aSrobert         {
3131*404b540aSrobert           sbitmap blocks = sbitmap_alloc (last_basic_block);
3132*404b540aSrobert           deaths_in_region = xrealloc (deaths_in_region, nr_regions *
3133*404b540aSrobert 				       sizeof (*deaths_in_region));
3134*404b540aSrobert 
3135*404b540aSrobert           check_dead_notes1 (nr_regions - 1, blocks);
3136*404b540aSrobert 
3137*404b540aSrobert           sbitmap_free (blocks);
3138*404b540aSrobert         }
3139*404b540aSrobert     }
3140*404b540aSrobert   else
3141*404b540aSrobert     {
3142*404b540aSrobert       int i, pos;
3143*404b540aSrobert 
3144*404b540aSrobert       /* We need to fix rgn_table, block_to_bb, containing_rgn
3145*404b540aSrobert 	 and ebb_head.  */
3146*404b540aSrobert 
3147*404b540aSrobert       BLOCK_TO_BB (bb->index) = BLOCK_TO_BB (after->index);
3148*404b540aSrobert 
3149*404b540aSrobert       /* We extend ebb_head to one more position to
3150*404b540aSrobert 	 easily find the last position of the last ebb in
3151*404b540aSrobert 	 the current region.  Thus, ebb_head[BLOCK_TO_BB (after) + 1]
3152*404b540aSrobert 	 is _always_ valid for access.  */
3153*404b540aSrobert 
3154*404b540aSrobert       i = BLOCK_TO_BB (after->index) + 1;
3155*404b540aSrobert       pos = ebb_head[i] - 1;
3156*404b540aSrobert       /* Now POS is the index of the last block in the region.  */
3157*404b540aSrobert 
3158*404b540aSrobert       /* Find index of basic block AFTER.  */
3159*404b540aSrobert       for (; rgn_bb_table[pos] != after->index; pos--);
3160*404b540aSrobert 
3161*404b540aSrobert       pos++;
3162*404b540aSrobert       gcc_assert (pos > ebb_head[i - 1]);
3163*404b540aSrobert 
3164*404b540aSrobert       /* i - ebb right after "AFTER".  */
3165*404b540aSrobert       /* ebb_head[i] - VALID.  */
3166*404b540aSrobert 
3167*404b540aSrobert       /* Source position: ebb_head[i]
3168*404b540aSrobert 	 Destination position: ebb_head[i] + 1
3169*404b540aSrobert 	 Last position:
3170*404b540aSrobert 	   RGN_BLOCKS (nr_regions) - 1
3171*404b540aSrobert 	 Number of elements to copy: (last_position) - (source_position) + 1
3172*404b540aSrobert        */
3173*404b540aSrobert 
3174*404b540aSrobert       memmove (rgn_bb_table + pos + 1,
3175*404b540aSrobert 	       rgn_bb_table + pos,
3176*404b540aSrobert 	       ((RGN_BLOCKS (nr_regions) - 1) - (pos) + 1)
3177*404b540aSrobert 	       * sizeof (*rgn_bb_table));
3178*404b540aSrobert 
3179*404b540aSrobert       rgn_bb_table[pos] = bb->index;
3180*404b540aSrobert 
3181*404b540aSrobert       for (; i <= current_nr_blocks; i++)
3182*404b540aSrobert 	ebb_head [i]++;
3183*404b540aSrobert 
3184*404b540aSrobert       i = CONTAINING_RGN (after->index);
3185*404b540aSrobert       CONTAINING_RGN (bb->index) = i;
3186*404b540aSrobert 
3187*404b540aSrobert       RGN_HAS_REAL_EBB (i) = 1;
3188*404b540aSrobert 
3189*404b540aSrobert       for (++i; i <= nr_regions; i++)
3190*404b540aSrobert 	RGN_BLOCKS (i)++;
3191*404b540aSrobert 
3192*404b540aSrobert       /* We don't need to call check_dead_notes1 () because this new block
3193*404b540aSrobert 	 is just a split of the old.  We don't want to count anything twice.  */
3194*404b540aSrobert     }
3195*404b540aSrobert }
3196*404b540aSrobert 
3197*404b540aSrobert /* Fix internal data after interblock movement of jump instruction.
3198*404b540aSrobert    For parameter meaning please refer to
3199*404b540aSrobert    sched-int.h: struct sched_info: fix_recovery_cfg.  */
3200*404b540aSrobert static void
fix_recovery_cfg(int bbi,int check_bbi,int check_bb_nexti)3201*404b540aSrobert fix_recovery_cfg (int bbi, int check_bbi, int check_bb_nexti)
3202*404b540aSrobert {
3203*404b540aSrobert   int old_pos, new_pos, i;
3204*404b540aSrobert 
3205*404b540aSrobert   BLOCK_TO_BB (check_bb_nexti) = BLOCK_TO_BB (bbi);
3206*404b540aSrobert 
3207*404b540aSrobert   for (old_pos = ebb_head[BLOCK_TO_BB (check_bbi) + 1] - 1;
3208*404b540aSrobert        rgn_bb_table[old_pos] != check_bb_nexti;
3209*404b540aSrobert        old_pos--);
3210*404b540aSrobert   gcc_assert (old_pos > ebb_head[BLOCK_TO_BB (check_bbi)]);
3211*404b540aSrobert 
3212*404b540aSrobert   for (new_pos = ebb_head[BLOCK_TO_BB (bbi) + 1] - 1;
3213*404b540aSrobert        rgn_bb_table[new_pos] != bbi;
3214*404b540aSrobert        new_pos--);
3215*404b540aSrobert   new_pos++;
3216*404b540aSrobert   gcc_assert (new_pos > ebb_head[BLOCK_TO_BB (bbi)]);
3217*404b540aSrobert 
3218*404b540aSrobert   gcc_assert (new_pos < old_pos);
3219*404b540aSrobert 
3220*404b540aSrobert   memmove (rgn_bb_table + new_pos + 1,
3221*404b540aSrobert 	   rgn_bb_table + new_pos,
3222*404b540aSrobert 	   (old_pos - new_pos) * sizeof (*rgn_bb_table));
3223*404b540aSrobert 
3224*404b540aSrobert   rgn_bb_table[new_pos] = check_bb_nexti;
3225*404b540aSrobert 
3226*404b540aSrobert   for (i = BLOCK_TO_BB (bbi) + 1; i <= BLOCK_TO_BB (check_bbi); i++)
3227*404b540aSrobert     ebb_head[i]++;
3228*404b540aSrobert }
3229*404b540aSrobert 
3230*404b540aSrobert /* Return next block in ebb chain.  For parameter meaning please refer to
3231*404b540aSrobert    sched-int.h: struct sched_info: advance_target_bb.  */
3232*404b540aSrobert static basic_block
advance_target_bb(basic_block bb,rtx insn)3233*404b540aSrobert advance_target_bb (basic_block bb, rtx insn)
3234*404b540aSrobert {
3235*404b540aSrobert   if (insn)
3236*404b540aSrobert     return 0;
3237*404b540aSrobert 
3238*404b540aSrobert   gcc_assert (BLOCK_TO_BB (bb->index) == target_bb
3239*404b540aSrobert 	      && BLOCK_TO_BB (bb->next_bb->index) == target_bb);
3240*404b540aSrobert   return bb->next_bb;
3241*404b540aSrobert }
3242*404b540aSrobert 
3243*404b540aSrobert /* Count and remove death notes in region RGN, which consists of blocks
3244*404b540aSrobert    with indecies in BLOCKS.  */
3245*404b540aSrobert static void
check_dead_notes1(int rgn,sbitmap blocks)3246*404b540aSrobert check_dead_notes1 (int rgn, sbitmap blocks)
3247*404b540aSrobert {
3248*404b540aSrobert   int b;
3249*404b540aSrobert 
3250*404b540aSrobert   sbitmap_zero (blocks);
3251*404b540aSrobert   for (b = RGN_NR_BLOCKS (rgn) - 1; b >= 0; --b)
3252*404b540aSrobert     SET_BIT (blocks, rgn_bb_table[RGN_BLOCKS (rgn) + b]);
3253*404b540aSrobert 
3254*404b540aSrobert   deaths_in_region[rgn] = count_or_remove_death_notes (blocks, 1);
3255*404b540aSrobert }
3256*404b540aSrobert 
3257*404b540aSrobert #ifdef ENABLE_CHECKING
3258*404b540aSrobert /* Return non zero, if BB is head or leaf (depending of LEAF_P) block in
3259*404b540aSrobert    current region.  For more information please refer to
3260*404b540aSrobert    sched-int.h: struct sched_info: region_head_or_leaf_p.  */
3261*404b540aSrobert static int
region_head_or_leaf_p(basic_block bb,int leaf_p)3262*404b540aSrobert region_head_or_leaf_p (basic_block bb, int leaf_p)
3263*404b540aSrobert {
3264*404b540aSrobert   if (!leaf_p)
3265*404b540aSrobert     return bb->index == rgn_bb_table[RGN_BLOCKS (CONTAINING_RGN (bb->index))];
3266*404b540aSrobert   else
3267*404b540aSrobert     {
3268*404b540aSrobert       int i;
3269*404b540aSrobert       edge e;
3270*404b540aSrobert       edge_iterator ei;
3271*404b540aSrobert 
3272*404b540aSrobert       i = CONTAINING_RGN (bb->index);
3273*404b540aSrobert 
3274*404b540aSrobert       FOR_EACH_EDGE (e, ei, bb->succs)
3275*404b540aSrobert 	if (e->dest != EXIT_BLOCK_PTR
3276*404b540aSrobert             && CONTAINING_RGN (e->dest->index) == i
3277*404b540aSrobert 	    /* except self-loop.  */
3278*404b540aSrobert 	    && e->dest != bb)
3279*404b540aSrobert 	  return 0;
3280*404b540aSrobert 
3281*404b540aSrobert       return 1;
3282*404b540aSrobert     }
3283*404b540aSrobert }
3284*404b540aSrobert #endif /* ENABLE_CHECKING  */
3285*404b540aSrobert 
3286*404b540aSrobert #endif
3287*404b540aSrobert 
3288*404b540aSrobert static bool
gate_handle_sched(void)3289*404b540aSrobert gate_handle_sched (void)
3290*404b540aSrobert {
3291*404b540aSrobert #ifdef INSN_SCHEDULING
3292*404b540aSrobert   return flag_schedule_insns;
3293*404b540aSrobert #else
3294*404b540aSrobert   return 0;
3295*404b540aSrobert #endif
3296*404b540aSrobert }
3297*404b540aSrobert 
3298*404b540aSrobert /* Run instruction scheduler.  */
3299*404b540aSrobert static unsigned int
rest_of_handle_sched(void)3300*404b540aSrobert rest_of_handle_sched (void)
3301*404b540aSrobert {
3302*404b540aSrobert #ifdef INSN_SCHEDULING
3303*404b540aSrobert   /* Do control and data sched analysis,
3304*404b540aSrobert      and write some of the results to dump file.  */
3305*404b540aSrobert 
3306*404b540aSrobert   schedule_insns ();
3307*404b540aSrobert #endif
3308*404b540aSrobert   return 0;
3309*404b540aSrobert }
3310*404b540aSrobert 
3311*404b540aSrobert static bool
gate_handle_sched2(void)3312*404b540aSrobert gate_handle_sched2 (void)
3313*404b540aSrobert {
3314*404b540aSrobert #ifdef INSN_SCHEDULING
3315*404b540aSrobert   return optimize > 0 && flag_schedule_insns_after_reload;
3316*404b540aSrobert #else
3317*404b540aSrobert   return 0;
3318*404b540aSrobert #endif
3319*404b540aSrobert }
3320*404b540aSrobert 
3321*404b540aSrobert /* Run second scheduling pass after reload.  */
3322*404b540aSrobert static unsigned int
rest_of_handle_sched2(void)3323*404b540aSrobert rest_of_handle_sched2 (void)
3324*404b540aSrobert {
3325*404b540aSrobert #ifdef INSN_SCHEDULING
3326*404b540aSrobert   /* Do control and data sched analysis again,
3327*404b540aSrobert      and write some more of the results to dump file.  */
3328*404b540aSrobert 
3329*404b540aSrobert   split_all_insns (1);
3330*404b540aSrobert 
3331*404b540aSrobert   if (flag_sched2_use_superblocks || flag_sched2_use_traces)
3332*404b540aSrobert     {
3333*404b540aSrobert       schedule_ebbs ();
3334*404b540aSrobert       /* No liveness updating code yet, but it should be easy to do.
3335*404b540aSrobert          reg-stack recomputes the liveness when needed for now.  */
3336*404b540aSrobert       count_or_remove_death_notes (NULL, 1);
3337*404b540aSrobert       cleanup_cfg (CLEANUP_EXPENSIVE);
3338*404b540aSrobert     }
3339*404b540aSrobert   else
3340*404b540aSrobert     schedule_insns ();
3341*404b540aSrobert #endif
3342*404b540aSrobert   return 0;
3343*404b540aSrobert }
3344*404b540aSrobert 
3345*404b540aSrobert struct tree_opt_pass pass_sched =
3346*404b540aSrobert {
3347*404b540aSrobert   "sched1",                             /* name */
3348*404b540aSrobert   gate_handle_sched,                    /* gate */
3349*404b540aSrobert   rest_of_handle_sched,                 /* execute */
3350*404b540aSrobert   NULL,                                 /* sub */
3351*404b540aSrobert   NULL,                                 /* next */
3352*404b540aSrobert   0,                                    /* static_pass_number */
3353*404b540aSrobert   TV_SCHED,                             /* tv_id */
3354*404b540aSrobert   0,                                    /* properties_required */
3355*404b540aSrobert   0,                                    /* properties_provided */
3356*404b540aSrobert   0,                                    /* properties_destroyed */
3357*404b540aSrobert   0,                                    /* todo_flags_start */
3358*404b540aSrobert   TODO_dump_func |
3359*404b540aSrobert   TODO_ggc_collect,                     /* todo_flags_finish */
3360*404b540aSrobert   'S'                                   /* letter */
3361*404b540aSrobert };
3362*404b540aSrobert 
3363*404b540aSrobert struct tree_opt_pass pass_sched2 =
3364*404b540aSrobert {
3365*404b540aSrobert   "sched2",                             /* name */
3366*404b540aSrobert   gate_handle_sched2,                   /* gate */
3367*404b540aSrobert   rest_of_handle_sched2,                /* execute */
3368*404b540aSrobert   NULL,                                 /* sub */
3369*404b540aSrobert   NULL,                                 /* next */
3370*404b540aSrobert   0,                                    /* static_pass_number */
3371*404b540aSrobert   TV_SCHED2,                            /* tv_id */
3372*404b540aSrobert   0,                                    /* properties_required */
3373*404b540aSrobert   0,                                    /* properties_provided */
3374*404b540aSrobert   0,                                    /* properties_destroyed */
3375*404b540aSrobert   0,                                    /* todo_flags_start */
3376*404b540aSrobert   TODO_dump_func |
3377*404b540aSrobert   TODO_ggc_collect,                     /* todo_flags_finish */
3378*404b540aSrobert   'R'                                   /* letter */
3379*404b540aSrobert };
3380*404b540aSrobert 
3381