xref: /openbsd-src/gnu/gcc/gcc/mode-switching.c (revision 404b540a9034ac75a6199ad1a32d1bbc7a0d4210)
1*404b540aSrobert /* CPU mode switching
2*404b540aSrobert    Copyright (C) 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005
3*404b540aSrobert    Free Software Foundation, Inc.
4*404b540aSrobert 
5*404b540aSrobert This file is part of GCC.
6*404b540aSrobert 
7*404b540aSrobert GCC is free software; you can redistribute it and/or modify it under
8*404b540aSrobert the terms of the GNU General Public License as published by the Free
9*404b540aSrobert Software Foundation; either version 2, or (at your option) any later
10*404b540aSrobert version.
11*404b540aSrobert 
12*404b540aSrobert GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13*404b540aSrobert WARRANTY; without even the implied warranty of MERCHANTABILITY or
14*404b540aSrobert FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15*404b540aSrobert for more details.
16*404b540aSrobert 
17*404b540aSrobert You should have received a copy of the GNU General Public License
18*404b540aSrobert along with GCC; see the file COPYING.  If not, write to the Free
19*404b540aSrobert Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
20*404b540aSrobert 02110-1301, USA.  */
21*404b540aSrobert 
22*404b540aSrobert #include "config.h"
23*404b540aSrobert #include "system.h"
24*404b540aSrobert #include "coretypes.h"
25*404b540aSrobert #include "tm.h"
26*404b540aSrobert #include "rtl.h"
27*404b540aSrobert #include "regs.h"
28*404b540aSrobert #include "hard-reg-set.h"
29*404b540aSrobert #include "flags.h"
30*404b540aSrobert #include "real.h"
31*404b540aSrobert #include "insn-config.h"
32*404b540aSrobert #include "recog.h"
33*404b540aSrobert #include "basic-block.h"
34*404b540aSrobert #include "output.h"
35*404b540aSrobert #include "tm_p.h"
36*404b540aSrobert #include "function.h"
37*404b540aSrobert #include "tree-pass.h"
38*404b540aSrobert #include "timevar.h"
39*404b540aSrobert 
40*404b540aSrobert /* We want target macros for the mode switching code to be able to refer
41*404b540aSrobert    to instruction attribute values.  */
42*404b540aSrobert #include "insn-attr.h"
43*404b540aSrobert 
44*404b540aSrobert #ifdef OPTIMIZE_MODE_SWITCHING
45*404b540aSrobert 
46*404b540aSrobert /* The algorithm for setting the modes consists of scanning the insn list
47*404b540aSrobert    and finding all the insns which require a specific mode.  Each insn gets
48*404b540aSrobert    a unique struct seginfo element.  These structures are inserted into a list
49*404b540aSrobert    for each basic block.  For each entity, there is an array of bb_info over
50*404b540aSrobert    the flow graph basic blocks (local var 'bb_info'), and contains a list
51*404b540aSrobert    of all insns within that basic block, in the order they are encountered.
52*404b540aSrobert 
53*404b540aSrobert    For each entity, any basic block WITHOUT any insns requiring a specific
54*404b540aSrobert    mode are given a single entry, without a mode.  (Each basic block
55*404b540aSrobert    in the flow graph must have at least one entry in the segment table.)
56*404b540aSrobert 
57*404b540aSrobert    The LCM algorithm is then run over the flow graph to determine where to
58*404b540aSrobert    place the sets to the highest-priority value in respect of first the first
59*404b540aSrobert    insn in any one block.  Any adjustments required to the transparency
60*404b540aSrobert    vectors are made, then the next iteration starts for the next-lower
61*404b540aSrobert    priority mode, till for each entity all modes are exhausted.
62*404b540aSrobert 
63*404b540aSrobert    More details are located in the code for optimize_mode_switching().  */
64*404b540aSrobert 
65*404b540aSrobert /* This structure contains the information for each insn which requires
66*404b540aSrobert    either single or double mode to be set.
67*404b540aSrobert    MODE is the mode this insn must be executed in.
68*404b540aSrobert    INSN_PTR is the insn to be executed (may be the note that marks the
69*404b540aSrobert    beginning of a basic block).
70*404b540aSrobert    BBNUM is the flow graph basic block this insn occurs in.
71*404b540aSrobert    NEXT is the next insn in the same basic block.  */
72*404b540aSrobert struct seginfo
73*404b540aSrobert {
74*404b540aSrobert   int mode;
75*404b540aSrobert   rtx insn_ptr;
76*404b540aSrobert   int bbnum;
77*404b540aSrobert   struct seginfo *next;
78*404b540aSrobert   HARD_REG_SET regs_live;
79*404b540aSrobert };
80*404b540aSrobert 
81*404b540aSrobert struct bb_info
82*404b540aSrobert {
83*404b540aSrobert   struct seginfo *seginfo;
84*404b540aSrobert   int computing;
85*404b540aSrobert };
86*404b540aSrobert 
87*404b540aSrobert /* These bitmaps are used for the LCM algorithm.  */
88*404b540aSrobert 
89*404b540aSrobert static sbitmap *antic;
90*404b540aSrobert static sbitmap *transp;
91*404b540aSrobert static sbitmap *comp;
92*404b540aSrobert 
93*404b540aSrobert static struct seginfo * new_seginfo (int, rtx, int, HARD_REG_SET);
94*404b540aSrobert static void add_seginfo (struct bb_info *, struct seginfo *);
95*404b540aSrobert static void reg_dies (rtx, HARD_REG_SET);
96*404b540aSrobert static void reg_becomes_live (rtx, rtx, void *);
97*404b540aSrobert static void make_preds_opaque (basic_block, int);
98*404b540aSrobert 
99*404b540aSrobert 
100*404b540aSrobert /* This function will allocate a new BBINFO structure, initialized
101*404b540aSrobert    with the MODE, INSN, and basic block BB parameters.  */
102*404b540aSrobert 
103*404b540aSrobert static struct seginfo *
new_seginfo(int mode,rtx insn,int bb,HARD_REG_SET regs_live)104*404b540aSrobert new_seginfo (int mode, rtx insn, int bb, HARD_REG_SET regs_live)
105*404b540aSrobert {
106*404b540aSrobert   struct seginfo *ptr;
107*404b540aSrobert   ptr = XNEW (struct seginfo);
108*404b540aSrobert   ptr->mode = mode;
109*404b540aSrobert   ptr->insn_ptr = insn;
110*404b540aSrobert   ptr->bbnum = bb;
111*404b540aSrobert   ptr->next = NULL;
112*404b540aSrobert   COPY_HARD_REG_SET (ptr->regs_live, regs_live);
113*404b540aSrobert   return ptr;
114*404b540aSrobert }
115*404b540aSrobert 
116*404b540aSrobert /* Add a seginfo element to the end of a list.
117*404b540aSrobert    HEAD is a pointer to the list beginning.
118*404b540aSrobert    INFO is the structure to be linked in.  */
119*404b540aSrobert 
120*404b540aSrobert static void
add_seginfo(struct bb_info * head,struct seginfo * info)121*404b540aSrobert add_seginfo (struct bb_info *head, struct seginfo *info)
122*404b540aSrobert {
123*404b540aSrobert   struct seginfo *ptr;
124*404b540aSrobert 
125*404b540aSrobert   if (head->seginfo == NULL)
126*404b540aSrobert     head->seginfo = info;
127*404b540aSrobert   else
128*404b540aSrobert     {
129*404b540aSrobert       ptr = head->seginfo;
130*404b540aSrobert       while (ptr->next != NULL)
131*404b540aSrobert 	ptr = ptr->next;
132*404b540aSrobert       ptr->next = info;
133*404b540aSrobert     }
134*404b540aSrobert }
135*404b540aSrobert 
136*404b540aSrobert /* Make all predecessors of basic block B opaque, recursively, till we hit
137*404b540aSrobert    some that are already non-transparent, or an edge where aux is set; that
138*404b540aSrobert    denotes that a mode set is to be done on that edge.
139*404b540aSrobert    J is the bit number in the bitmaps that corresponds to the entity that
140*404b540aSrobert    we are currently handling mode-switching for.  */
141*404b540aSrobert 
142*404b540aSrobert static void
make_preds_opaque(basic_block b,int j)143*404b540aSrobert make_preds_opaque (basic_block b, int j)
144*404b540aSrobert {
145*404b540aSrobert   edge e;
146*404b540aSrobert   edge_iterator ei;
147*404b540aSrobert 
148*404b540aSrobert   FOR_EACH_EDGE (e, ei, b->preds)
149*404b540aSrobert     {
150*404b540aSrobert       basic_block pb = e->src;
151*404b540aSrobert 
152*404b540aSrobert       if (e->aux || ! TEST_BIT (transp[pb->index], j))
153*404b540aSrobert 	continue;
154*404b540aSrobert 
155*404b540aSrobert       RESET_BIT (transp[pb->index], j);
156*404b540aSrobert       make_preds_opaque (pb, j);
157*404b540aSrobert     }
158*404b540aSrobert }
159*404b540aSrobert 
160*404b540aSrobert /* Record in LIVE that register REG died.  */
161*404b540aSrobert 
162*404b540aSrobert static void
reg_dies(rtx reg,HARD_REG_SET live)163*404b540aSrobert reg_dies (rtx reg, HARD_REG_SET live)
164*404b540aSrobert {
165*404b540aSrobert   int regno, nregs;
166*404b540aSrobert 
167*404b540aSrobert   if (!REG_P (reg))
168*404b540aSrobert     return;
169*404b540aSrobert 
170*404b540aSrobert   regno = REGNO (reg);
171*404b540aSrobert   if (regno < FIRST_PSEUDO_REGISTER)
172*404b540aSrobert     for (nregs = hard_regno_nregs[regno][GET_MODE (reg)] - 1; nregs >= 0;
173*404b540aSrobert 	 nregs--)
174*404b540aSrobert       CLEAR_HARD_REG_BIT (live, regno + nregs);
175*404b540aSrobert }
176*404b540aSrobert 
177*404b540aSrobert /* Record in LIVE that register REG became live.
178*404b540aSrobert    This is called via note_stores.  */
179*404b540aSrobert 
180*404b540aSrobert static void
reg_becomes_live(rtx reg,rtx setter ATTRIBUTE_UNUSED,void * live)181*404b540aSrobert reg_becomes_live (rtx reg, rtx setter ATTRIBUTE_UNUSED, void *live)
182*404b540aSrobert {
183*404b540aSrobert   int regno, nregs;
184*404b540aSrobert 
185*404b540aSrobert   if (GET_CODE (reg) == SUBREG)
186*404b540aSrobert     reg = SUBREG_REG (reg);
187*404b540aSrobert 
188*404b540aSrobert   if (!REG_P (reg))
189*404b540aSrobert     return;
190*404b540aSrobert 
191*404b540aSrobert   regno = REGNO (reg);
192*404b540aSrobert   if (regno < FIRST_PSEUDO_REGISTER)
193*404b540aSrobert     for (nregs = hard_regno_nregs[regno][GET_MODE (reg)] - 1; nregs >= 0;
194*404b540aSrobert 	 nregs--)
195*404b540aSrobert       SET_HARD_REG_BIT (* (HARD_REG_SET *) live, regno + nregs);
196*404b540aSrobert }
197*404b540aSrobert 
198*404b540aSrobert /* Make sure if MODE_ENTRY is defined the MODE_EXIT is defined
199*404b540aSrobert    and vice versa.  */
200*404b540aSrobert #if defined (MODE_ENTRY) != defined (MODE_EXIT)
201*404b540aSrobert  #error "Both MODE_ENTRY and MODE_EXIT must be defined"
202*404b540aSrobert #endif
203*404b540aSrobert 
204*404b540aSrobert #if defined (MODE_ENTRY) && defined (MODE_EXIT)
205*404b540aSrobert /* Split the fallthrough edge to the exit block, so that we can note
206*404b540aSrobert    that there NORMAL_MODE is required.  Return the new block if it's
207*404b540aSrobert    inserted before the exit block.  Otherwise return null.  */
208*404b540aSrobert 
209*404b540aSrobert static basic_block
create_pre_exit(int n_entities,int * entity_map,const int * num_modes)210*404b540aSrobert create_pre_exit (int n_entities, int *entity_map, const int *num_modes)
211*404b540aSrobert {
212*404b540aSrobert   edge eg;
213*404b540aSrobert   edge_iterator ei;
214*404b540aSrobert   basic_block pre_exit;
215*404b540aSrobert 
216*404b540aSrobert   /* The only non-call predecessor at this stage is a block with a
217*404b540aSrobert      fallthrough edge; there can be at most one, but there could be
218*404b540aSrobert      none at all, e.g. when exit is called.  */
219*404b540aSrobert   pre_exit = 0;
220*404b540aSrobert   FOR_EACH_EDGE (eg, ei, EXIT_BLOCK_PTR->preds)
221*404b540aSrobert     if (eg->flags & EDGE_FALLTHRU)
222*404b540aSrobert       {
223*404b540aSrobert 	basic_block src_bb = eg->src;
224*404b540aSrobert 	regset live_at_end = src_bb->il.rtl->global_live_at_end;
225*404b540aSrobert 	rtx last_insn, ret_reg;
226*404b540aSrobert 
227*404b540aSrobert 	gcc_assert (!pre_exit);
228*404b540aSrobert 	/* If this function returns a value at the end, we have to
229*404b540aSrobert 	   insert the final mode switch before the return value copy
230*404b540aSrobert 	   to its hard register.  */
231*404b540aSrobert 	if (EDGE_COUNT (EXIT_BLOCK_PTR->preds) == 1
232*404b540aSrobert 	    && NONJUMP_INSN_P ((last_insn = BB_END (src_bb)))
233*404b540aSrobert 	    && GET_CODE (PATTERN (last_insn)) == USE
234*404b540aSrobert 	    && GET_CODE ((ret_reg = XEXP (PATTERN (last_insn), 0))) == REG)
235*404b540aSrobert 	  {
236*404b540aSrobert 	    int ret_start = REGNO (ret_reg);
237*404b540aSrobert 	    int nregs = hard_regno_nregs[ret_start][GET_MODE (ret_reg)];
238*404b540aSrobert 	    int ret_end = ret_start + nregs;
239*404b540aSrobert 	    int short_block = 0;
240*404b540aSrobert 	    int maybe_builtin_apply = 0;
241*404b540aSrobert 	    int forced_late_switch = 0;
242*404b540aSrobert 	    rtx before_return_copy;
243*404b540aSrobert 
244*404b540aSrobert 	    do
245*404b540aSrobert 	      {
246*404b540aSrobert 		rtx return_copy = PREV_INSN (last_insn);
247*404b540aSrobert 		rtx return_copy_pat, copy_reg;
248*404b540aSrobert 		int copy_start, copy_num;
249*404b540aSrobert 		int j;
250*404b540aSrobert 
251*404b540aSrobert 		if (INSN_P (return_copy))
252*404b540aSrobert 		  {
253*404b540aSrobert 		    if (GET_CODE (PATTERN (return_copy)) == USE
254*404b540aSrobert 			&& GET_CODE (XEXP (PATTERN (return_copy), 0)) == REG
255*404b540aSrobert 			&& (FUNCTION_VALUE_REGNO_P
256*404b540aSrobert 			    (REGNO (XEXP (PATTERN (return_copy), 0)))))
257*404b540aSrobert 		      {
258*404b540aSrobert 			maybe_builtin_apply = 1;
259*404b540aSrobert 			last_insn = return_copy;
260*404b540aSrobert 			continue;
261*404b540aSrobert 		      }
262*404b540aSrobert 		    /* If the return register is not (in its entirety)
263*404b540aSrobert 		       likely spilled, the return copy might be
264*404b540aSrobert 		       partially or completely optimized away.  */
265*404b540aSrobert 		    return_copy_pat = single_set (return_copy);
266*404b540aSrobert 		    if (!return_copy_pat)
267*404b540aSrobert 		      {
268*404b540aSrobert 			return_copy_pat = PATTERN (return_copy);
269*404b540aSrobert 			if (GET_CODE (return_copy_pat) != CLOBBER)
270*404b540aSrobert 			  break;
271*404b540aSrobert 		      }
272*404b540aSrobert 		    copy_reg = SET_DEST (return_copy_pat);
273*404b540aSrobert 		    if (GET_CODE (copy_reg) == REG)
274*404b540aSrobert 		      copy_start = REGNO (copy_reg);
275*404b540aSrobert 		    else if (GET_CODE (copy_reg) == SUBREG
276*404b540aSrobert 			     && GET_CODE (SUBREG_REG (copy_reg)) == REG)
277*404b540aSrobert 		      copy_start = REGNO (SUBREG_REG (copy_reg));
278*404b540aSrobert 		    else
279*404b540aSrobert 		      break;
280*404b540aSrobert 		    if (copy_start >= FIRST_PSEUDO_REGISTER)
281*404b540aSrobert 		      break;
282*404b540aSrobert 		    copy_num
283*404b540aSrobert 		      = hard_regno_nregs[copy_start][GET_MODE (copy_reg)];
284*404b540aSrobert 
285*404b540aSrobert 		    /* If the return register is not likely spilled, - as is
286*404b540aSrobert 		       the case for floating point on SH4 - then it might
287*404b540aSrobert 		       be set by an arithmetic operation that needs a
288*404b540aSrobert 		       different mode than the exit block.  */
289*404b540aSrobert 		    for (j = n_entities - 1; j >= 0; j--)
290*404b540aSrobert 		      {
291*404b540aSrobert 			int e = entity_map[j];
292*404b540aSrobert 			int mode = MODE_NEEDED (e, return_copy);
293*404b540aSrobert 
294*404b540aSrobert 			if (mode != num_modes[e] && mode != MODE_EXIT (e))
295*404b540aSrobert 			  break;
296*404b540aSrobert 		      }
297*404b540aSrobert 		    if (j >= 0)
298*404b540aSrobert 		      {
299*404b540aSrobert 			/* For the SH4, floating point loads depend on fpscr,
300*404b540aSrobert 			   thus we might need to put the final mode switch
301*404b540aSrobert 			   after the return value copy.  That is still OK,
302*404b540aSrobert 			   because a floating point return value does not
303*404b540aSrobert 			   conflict with address reloads.  */
304*404b540aSrobert 			if (copy_start >= ret_start
305*404b540aSrobert 			    && copy_start + copy_num <= ret_end
306*404b540aSrobert 			    && OBJECT_P (SET_SRC (return_copy_pat)))
307*404b540aSrobert 			  forced_late_switch = 1;
308*404b540aSrobert 			break;
309*404b540aSrobert 		      }
310*404b540aSrobert 
311*404b540aSrobert 		    if (copy_start >= ret_start
312*404b540aSrobert 			&& copy_start + copy_num <= ret_end)
313*404b540aSrobert 		      nregs -= copy_num;
314*404b540aSrobert 		    else if (!maybe_builtin_apply
315*404b540aSrobert 			     || !FUNCTION_VALUE_REGNO_P (copy_start))
316*404b540aSrobert 		      break;
317*404b540aSrobert 		    last_insn = return_copy;
318*404b540aSrobert 		  }
319*404b540aSrobert 		/* ??? Exception handling can lead to the return value
320*404b540aSrobert 		   copy being already separated from the return value use,
321*404b540aSrobert 		   as in  unwind-dw2.c .
322*404b540aSrobert 		   Similarly, conditionally returning without a value,
323*404b540aSrobert 		   and conditionally using builtin_return can lead to an
324*404b540aSrobert 		   isolated use.  */
325*404b540aSrobert 		if (return_copy == BB_HEAD (src_bb))
326*404b540aSrobert 		  {
327*404b540aSrobert 		    short_block = 1;
328*404b540aSrobert 		    break;
329*404b540aSrobert 		  }
330*404b540aSrobert 		last_insn = return_copy;
331*404b540aSrobert 	      }
332*404b540aSrobert 	    while (nregs);
333*404b540aSrobert 
334*404b540aSrobert 	    /* If we didn't see a full return value copy, verify that there
335*404b540aSrobert 	       is a plausible reason for this.  If some, but not all of the
336*404b540aSrobert 	       return register is likely spilled, we can expect that there
337*404b540aSrobert 	       is a copy for the likely spilled part.  */
338*404b540aSrobert 	    gcc_assert (!nregs
339*404b540aSrobert 			|| forced_late_switch
340*404b540aSrobert 			|| short_block
341*404b540aSrobert 			|| !(CLASS_LIKELY_SPILLED_P
342*404b540aSrobert 			     (REGNO_REG_CLASS (ret_start)))
343*404b540aSrobert 			|| (nregs
344*404b540aSrobert 			    != hard_regno_nregs[ret_start][GET_MODE (ret_reg)])
345*404b540aSrobert 			/* For multi-hard-register floating point
346*404b540aSrobert 		   	   values, sometimes the likely-spilled part
347*404b540aSrobert 		   	   is ordinarily copied first, then the other
348*404b540aSrobert 		   	   part is set with an arithmetic operation.
349*404b540aSrobert 		   	   This doesn't actually cause reload
350*404b540aSrobert 		   	   failures, so let it pass.  */
351*404b540aSrobert 			|| (GET_MODE_CLASS (GET_MODE (ret_reg)) != MODE_INT
352*404b540aSrobert 			    && nregs != 1));
353*404b540aSrobert 
354*404b540aSrobert 	    if (INSN_P (last_insn))
355*404b540aSrobert 	      {
356*404b540aSrobert 		before_return_copy
357*404b540aSrobert 		  = emit_note_before (NOTE_INSN_DELETED, last_insn);
358*404b540aSrobert 		/* Instructions preceding LAST_INSN in the same block might
359*404b540aSrobert 		   require a different mode than MODE_EXIT, so if we might
360*404b540aSrobert 		   have such instructions, keep them in a separate block
361*404b540aSrobert 		   from pre_exit.  */
362*404b540aSrobert 		if (last_insn != BB_HEAD (src_bb))
363*404b540aSrobert 		  src_bb = split_block (src_bb,
364*404b540aSrobert 					PREV_INSN (before_return_copy))->dest;
365*404b540aSrobert 	      }
366*404b540aSrobert 	    else
367*404b540aSrobert 	      before_return_copy = last_insn;
368*404b540aSrobert 	    pre_exit = split_block (src_bb, before_return_copy)->src;
369*404b540aSrobert 	  }
370*404b540aSrobert 	else
371*404b540aSrobert 	  {
372*404b540aSrobert 	    pre_exit = split_edge (eg);
373*404b540aSrobert 	    COPY_REG_SET (pre_exit->il.rtl->global_live_at_start, live_at_end);
374*404b540aSrobert 	    COPY_REG_SET (pre_exit->il.rtl->global_live_at_end, live_at_end);
375*404b540aSrobert 	  }
376*404b540aSrobert       }
377*404b540aSrobert 
378*404b540aSrobert   return pre_exit;
379*404b540aSrobert }
380*404b540aSrobert #endif
381*404b540aSrobert 
382*404b540aSrobert /* Find all insns that need a particular mode setting, and insert the
383*404b540aSrobert    necessary mode switches.  Return true if we did work.  */
384*404b540aSrobert 
385*404b540aSrobert static int
optimize_mode_switching(void)386*404b540aSrobert optimize_mode_switching (void)
387*404b540aSrobert {
388*404b540aSrobert   rtx insn;
389*404b540aSrobert   int e;
390*404b540aSrobert   basic_block bb;
391*404b540aSrobert   int need_commit = 0;
392*404b540aSrobert   sbitmap *kill;
393*404b540aSrobert   struct edge_list *edge_list;
394*404b540aSrobert   static const int num_modes[] = NUM_MODES_FOR_MODE_SWITCHING;
395*404b540aSrobert #define N_ENTITIES ARRAY_SIZE (num_modes)
396*404b540aSrobert   int entity_map[N_ENTITIES];
397*404b540aSrobert   struct bb_info *bb_info[N_ENTITIES];
398*404b540aSrobert   int i, j;
399*404b540aSrobert   int n_entities;
400*404b540aSrobert   int max_num_modes = 0;
401*404b540aSrobert   bool emited = false;
402*404b540aSrobert   basic_block post_entry ATTRIBUTE_UNUSED, pre_exit ATTRIBUTE_UNUSED;
403*404b540aSrobert 
404*404b540aSrobert   clear_bb_flags ();
405*404b540aSrobert 
406*404b540aSrobert   for (e = N_ENTITIES - 1, n_entities = 0; e >= 0; e--)
407*404b540aSrobert     if (OPTIMIZE_MODE_SWITCHING (e))
408*404b540aSrobert       {
409*404b540aSrobert 	int entry_exit_extra = 0;
410*404b540aSrobert 
411*404b540aSrobert 	/* Create the list of segments within each basic block.
412*404b540aSrobert 	   If NORMAL_MODE is defined, allow for two extra
413*404b540aSrobert 	   blocks split from the entry and exit block.  */
414*404b540aSrobert #if defined (MODE_ENTRY) && defined (MODE_EXIT)
415*404b540aSrobert 	entry_exit_extra = 3;
416*404b540aSrobert #endif
417*404b540aSrobert 	bb_info[n_entities]
418*404b540aSrobert 	  = XCNEWVEC (struct bb_info, last_basic_block + entry_exit_extra);
419*404b540aSrobert 	entity_map[n_entities++] = e;
420*404b540aSrobert 	if (num_modes[e] > max_num_modes)
421*404b540aSrobert 	  max_num_modes = num_modes[e];
422*404b540aSrobert       }
423*404b540aSrobert 
424*404b540aSrobert   if (! n_entities)
425*404b540aSrobert     return 0;
426*404b540aSrobert 
427*404b540aSrobert #if defined (MODE_ENTRY) && defined (MODE_EXIT)
428*404b540aSrobert   /* Split the edge from the entry block, so that we can note that
429*404b540aSrobert      there NORMAL_MODE is supplied.  */
430*404b540aSrobert   post_entry = split_edge (single_succ_edge (ENTRY_BLOCK_PTR));
431*404b540aSrobert   pre_exit = create_pre_exit (n_entities, entity_map, num_modes);
432*404b540aSrobert #endif
433*404b540aSrobert 
434*404b540aSrobert   /* Create the bitmap vectors.  */
435*404b540aSrobert 
436*404b540aSrobert   antic = sbitmap_vector_alloc (last_basic_block, n_entities);
437*404b540aSrobert   transp = sbitmap_vector_alloc (last_basic_block, n_entities);
438*404b540aSrobert   comp = sbitmap_vector_alloc (last_basic_block, n_entities);
439*404b540aSrobert 
440*404b540aSrobert   sbitmap_vector_ones (transp, last_basic_block);
441*404b540aSrobert 
442*404b540aSrobert   for (j = n_entities - 1; j >= 0; j--)
443*404b540aSrobert     {
444*404b540aSrobert       int e = entity_map[j];
445*404b540aSrobert       int no_mode = num_modes[e];
446*404b540aSrobert       struct bb_info *info = bb_info[j];
447*404b540aSrobert 
448*404b540aSrobert       /* Determine what the first use (if any) need for a mode of entity E is.
449*404b540aSrobert 	 This will be the mode that is anticipatable for this block.
450*404b540aSrobert 	 Also compute the initial transparency settings.  */
451*404b540aSrobert       FOR_EACH_BB (bb)
452*404b540aSrobert 	{
453*404b540aSrobert 	  struct seginfo *ptr;
454*404b540aSrobert 	  int last_mode = no_mode;
455*404b540aSrobert 	  HARD_REG_SET live_now;
456*404b540aSrobert 
457*404b540aSrobert 	  REG_SET_TO_HARD_REG_SET (live_now,
458*404b540aSrobert 				   bb->il.rtl->global_live_at_start);
459*404b540aSrobert 
460*404b540aSrobert 	  /* Pretend the mode is clobbered across abnormal edges.  */
461*404b540aSrobert 	  {
462*404b540aSrobert 	    edge_iterator ei;
463*404b540aSrobert 	    edge e;
464*404b540aSrobert 	    FOR_EACH_EDGE (e, ei, bb->preds)
465*404b540aSrobert 	      if (e->flags & EDGE_COMPLEX)
466*404b540aSrobert 		break;
467*404b540aSrobert 	    if (e)
468*404b540aSrobert 	      {
469*404b540aSrobert 		ptr = new_seginfo (no_mode, BB_HEAD (bb), bb->index, live_now);
470*404b540aSrobert 		add_seginfo (info + bb->index, ptr);
471*404b540aSrobert 		RESET_BIT (transp[bb->index], j);
472*404b540aSrobert 	      }
473*404b540aSrobert 	  }
474*404b540aSrobert 
475*404b540aSrobert 	  for (insn = BB_HEAD (bb);
476*404b540aSrobert 	       insn != NULL && insn != NEXT_INSN (BB_END (bb));
477*404b540aSrobert 	       insn = NEXT_INSN (insn))
478*404b540aSrobert 	    {
479*404b540aSrobert 	      if (INSN_P (insn))
480*404b540aSrobert 		{
481*404b540aSrobert 		  int mode = MODE_NEEDED (e, insn);
482*404b540aSrobert 		  rtx link;
483*404b540aSrobert 
484*404b540aSrobert 		  if (mode != no_mode && mode != last_mode)
485*404b540aSrobert 		    {
486*404b540aSrobert 		      last_mode = mode;
487*404b540aSrobert 		      ptr = new_seginfo (mode, insn, bb->index, live_now);
488*404b540aSrobert 		      add_seginfo (info + bb->index, ptr);
489*404b540aSrobert 		      RESET_BIT (transp[bb->index], j);
490*404b540aSrobert 		    }
491*404b540aSrobert #ifdef MODE_AFTER
492*404b540aSrobert 		  last_mode = MODE_AFTER (last_mode, insn);
493*404b540aSrobert #endif
494*404b540aSrobert 		  /* Update LIVE_NOW.  */
495*404b540aSrobert 		  for (link = REG_NOTES (insn); link; link = XEXP (link, 1))
496*404b540aSrobert 		    if (REG_NOTE_KIND (link) == REG_DEAD)
497*404b540aSrobert 		      reg_dies (XEXP (link, 0), live_now);
498*404b540aSrobert 
499*404b540aSrobert 		  note_stores (PATTERN (insn), reg_becomes_live, &live_now);
500*404b540aSrobert 		  for (link = REG_NOTES (insn); link; link = XEXP (link, 1))
501*404b540aSrobert 		    if (REG_NOTE_KIND (link) == REG_UNUSED)
502*404b540aSrobert 		      reg_dies (XEXP (link, 0), live_now);
503*404b540aSrobert 		}
504*404b540aSrobert 	    }
505*404b540aSrobert 
506*404b540aSrobert 	  info[bb->index].computing = last_mode;
507*404b540aSrobert 	  /* Check for blocks without ANY mode requirements.  */
508*404b540aSrobert 	  if (last_mode == no_mode)
509*404b540aSrobert 	    {
510*404b540aSrobert 	      ptr = new_seginfo (no_mode, BB_END (bb), bb->index, live_now);
511*404b540aSrobert 	      add_seginfo (info + bb->index, ptr);
512*404b540aSrobert 	    }
513*404b540aSrobert 	}
514*404b540aSrobert #if defined (MODE_ENTRY) && defined (MODE_EXIT)
515*404b540aSrobert       {
516*404b540aSrobert 	int mode = MODE_ENTRY (e);
517*404b540aSrobert 
518*404b540aSrobert 	if (mode != no_mode)
519*404b540aSrobert 	  {
520*404b540aSrobert 	    bb = post_entry;
521*404b540aSrobert 
522*404b540aSrobert 	    /* By always making this nontransparent, we save
523*404b540aSrobert 	       an extra check in make_preds_opaque.  We also
524*404b540aSrobert 	       need this to avoid confusing pre_edge_lcm when
525*404b540aSrobert 	       antic is cleared but transp and comp are set.  */
526*404b540aSrobert 	    RESET_BIT (transp[bb->index], j);
527*404b540aSrobert 
528*404b540aSrobert 	    /* Insert a fake computing definition of MODE into entry
529*404b540aSrobert 	       blocks which compute no mode. This represents the mode on
530*404b540aSrobert 	       entry.  */
531*404b540aSrobert 	    info[bb->index].computing = mode;
532*404b540aSrobert 
533*404b540aSrobert 	    if (pre_exit)
534*404b540aSrobert 	      info[pre_exit->index].seginfo->mode = MODE_EXIT (e);
535*404b540aSrobert 	  }
536*404b540aSrobert       }
537*404b540aSrobert #endif /* NORMAL_MODE */
538*404b540aSrobert     }
539*404b540aSrobert 
540*404b540aSrobert   kill = sbitmap_vector_alloc (last_basic_block, n_entities);
541*404b540aSrobert   for (i = 0; i < max_num_modes; i++)
542*404b540aSrobert     {
543*404b540aSrobert       int current_mode[N_ENTITIES];
544*404b540aSrobert       sbitmap *delete;
545*404b540aSrobert       sbitmap *insert;
546*404b540aSrobert 
547*404b540aSrobert       /* Set the anticipatable and computing arrays.  */
548*404b540aSrobert       sbitmap_vector_zero (antic, last_basic_block);
549*404b540aSrobert       sbitmap_vector_zero (comp, last_basic_block);
550*404b540aSrobert       for (j = n_entities - 1; j >= 0; j--)
551*404b540aSrobert 	{
552*404b540aSrobert 	  int m = current_mode[j] = MODE_PRIORITY_TO_MODE (entity_map[j], i);
553*404b540aSrobert 	  struct bb_info *info = bb_info[j];
554*404b540aSrobert 
555*404b540aSrobert 	  FOR_EACH_BB (bb)
556*404b540aSrobert 	    {
557*404b540aSrobert 	      if (info[bb->index].seginfo->mode == m)
558*404b540aSrobert 		SET_BIT (antic[bb->index], j);
559*404b540aSrobert 
560*404b540aSrobert 	      if (info[bb->index].computing == m)
561*404b540aSrobert 		SET_BIT (comp[bb->index], j);
562*404b540aSrobert 	    }
563*404b540aSrobert 	}
564*404b540aSrobert 
565*404b540aSrobert       /* Calculate the optimal locations for the
566*404b540aSrobert 	 placement mode switches to modes with priority I.  */
567*404b540aSrobert 
568*404b540aSrobert       FOR_EACH_BB (bb)
569*404b540aSrobert 	sbitmap_not (kill[bb->index], transp[bb->index]);
570*404b540aSrobert       edge_list = pre_edge_lcm (n_entities, transp, comp, antic,
571*404b540aSrobert 				kill, &insert, &delete);
572*404b540aSrobert 
573*404b540aSrobert       for (j = n_entities - 1; j >= 0; j--)
574*404b540aSrobert 	{
575*404b540aSrobert 	  /* Insert all mode sets that have been inserted by lcm.  */
576*404b540aSrobert 	  int no_mode = num_modes[entity_map[j]];
577*404b540aSrobert 
578*404b540aSrobert 	  /* Wherever we have moved a mode setting upwards in the flow graph,
579*404b540aSrobert 	     the blocks between the new setting site and the now redundant
580*404b540aSrobert 	     computation ceases to be transparent for any lower-priority
581*404b540aSrobert 	     mode of the same entity.  First set the aux field of each
582*404b540aSrobert 	     insertion site edge non-transparent, then propagate the new
583*404b540aSrobert 	     non-transparency from the redundant computation upwards till
584*404b540aSrobert 	     we hit an insertion site or an already non-transparent block.  */
585*404b540aSrobert 	  for (e = NUM_EDGES (edge_list) - 1; e >= 0; e--)
586*404b540aSrobert 	    {
587*404b540aSrobert 	      edge eg = INDEX_EDGE (edge_list, e);
588*404b540aSrobert 	      int mode;
589*404b540aSrobert 	      basic_block src_bb;
590*404b540aSrobert 	      HARD_REG_SET live_at_edge;
591*404b540aSrobert 	      rtx mode_set;
592*404b540aSrobert 
593*404b540aSrobert 	      eg->aux = 0;
594*404b540aSrobert 
595*404b540aSrobert 	      if (! TEST_BIT (insert[e], j))
596*404b540aSrobert 		continue;
597*404b540aSrobert 
598*404b540aSrobert 	      eg->aux = (void *)1;
599*404b540aSrobert 
600*404b540aSrobert 	      mode = current_mode[j];
601*404b540aSrobert 	      src_bb = eg->src;
602*404b540aSrobert 
603*404b540aSrobert 	      REG_SET_TO_HARD_REG_SET (live_at_edge,
604*404b540aSrobert 				       src_bb->il.rtl->global_live_at_end);
605*404b540aSrobert 
606*404b540aSrobert 	      start_sequence ();
607*404b540aSrobert 	      EMIT_MODE_SET (entity_map[j], mode, live_at_edge);
608*404b540aSrobert 	      mode_set = get_insns ();
609*404b540aSrobert 	      end_sequence ();
610*404b540aSrobert 
611*404b540aSrobert 	      /* Do not bother to insert empty sequence.  */
612*404b540aSrobert 	      if (mode_set == NULL_RTX)
613*404b540aSrobert 		continue;
614*404b540aSrobert 
615*404b540aSrobert 	      /* We should not get an abnormal edge here.  */
616*404b540aSrobert 	      gcc_assert (! (eg->flags & EDGE_ABNORMAL));
617*404b540aSrobert 
618*404b540aSrobert 	      need_commit = 1;
619*404b540aSrobert 	      insert_insn_on_edge (mode_set, eg);
620*404b540aSrobert 	    }
621*404b540aSrobert 
622*404b540aSrobert 	  FOR_EACH_BB_REVERSE (bb)
623*404b540aSrobert 	    if (TEST_BIT (delete[bb->index], j))
624*404b540aSrobert 	      {
625*404b540aSrobert 		make_preds_opaque (bb, j);
626*404b540aSrobert 		/* Cancel the 'deleted' mode set.  */
627*404b540aSrobert 		bb_info[j][bb->index].seginfo->mode = no_mode;
628*404b540aSrobert 	      }
629*404b540aSrobert 	}
630*404b540aSrobert 
631*404b540aSrobert       sbitmap_vector_free (delete);
632*404b540aSrobert       sbitmap_vector_free (insert);
633*404b540aSrobert       clear_aux_for_edges ();
634*404b540aSrobert       free_edge_list (edge_list);
635*404b540aSrobert     }
636*404b540aSrobert 
637*404b540aSrobert   /* Now output the remaining mode sets in all the segments.  */
638*404b540aSrobert   for (j = n_entities - 1; j >= 0; j--)
639*404b540aSrobert     {
640*404b540aSrobert       int no_mode = num_modes[entity_map[j]];
641*404b540aSrobert 
642*404b540aSrobert       FOR_EACH_BB_REVERSE (bb)
643*404b540aSrobert 	{
644*404b540aSrobert 	  struct seginfo *ptr, *next;
645*404b540aSrobert 	  for (ptr = bb_info[j][bb->index].seginfo; ptr; ptr = next)
646*404b540aSrobert 	    {
647*404b540aSrobert 	      next = ptr->next;
648*404b540aSrobert 	      if (ptr->mode != no_mode)
649*404b540aSrobert 		{
650*404b540aSrobert 		  rtx mode_set;
651*404b540aSrobert 
652*404b540aSrobert 		  start_sequence ();
653*404b540aSrobert 		  EMIT_MODE_SET (entity_map[j], ptr->mode, ptr->regs_live);
654*404b540aSrobert 		  mode_set = get_insns ();
655*404b540aSrobert 		  end_sequence ();
656*404b540aSrobert 
657*404b540aSrobert 		  /* Insert MODE_SET only if it is nonempty.  */
658*404b540aSrobert 		  if (mode_set != NULL_RTX)
659*404b540aSrobert 		    {
660*404b540aSrobert 		      emited = true;
661*404b540aSrobert 		      if (NOTE_P (ptr->insn_ptr)
662*404b540aSrobert 			  && (NOTE_LINE_NUMBER (ptr->insn_ptr)
663*404b540aSrobert 			      == NOTE_INSN_BASIC_BLOCK))
664*404b540aSrobert 			emit_insn_after (mode_set, ptr->insn_ptr);
665*404b540aSrobert 		      else
666*404b540aSrobert 			emit_insn_before (mode_set, ptr->insn_ptr);
667*404b540aSrobert 		    }
668*404b540aSrobert 		}
669*404b540aSrobert 
670*404b540aSrobert 	      free (ptr);
671*404b540aSrobert 	    }
672*404b540aSrobert 	}
673*404b540aSrobert 
674*404b540aSrobert       free (bb_info[j]);
675*404b540aSrobert     }
676*404b540aSrobert 
677*404b540aSrobert   /* Finished. Free up all the things we've allocated.  */
678*404b540aSrobert 
679*404b540aSrobert   sbitmap_vector_free (kill);
680*404b540aSrobert   sbitmap_vector_free (antic);
681*404b540aSrobert   sbitmap_vector_free (transp);
682*404b540aSrobert   sbitmap_vector_free (comp);
683*404b540aSrobert 
684*404b540aSrobert   if (need_commit)
685*404b540aSrobert     commit_edge_insertions ();
686*404b540aSrobert 
687*404b540aSrobert #if defined (MODE_ENTRY) && defined (MODE_EXIT)
688*404b540aSrobert   cleanup_cfg (CLEANUP_NO_INSN_DEL);
689*404b540aSrobert #else
690*404b540aSrobert   if (!need_commit && !emited)
691*404b540aSrobert     return 0;
692*404b540aSrobert #endif
693*404b540aSrobert 
694*404b540aSrobert   max_regno = max_reg_num ();
695*404b540aSrobert   allocate_reg_info (max_regno, FALSE, FALSE);
696*404b540aSrobert   update_life_info_in_dirty_blocks (UPDATE_LIFE_GLOBAL_RM_NOTES,
697*404b540aSrobert 				    (PROP_DEATH_NOTES | PROP_KILL_DEAD_CODE
698*404b540aSrobert 				     | PROP_SCAN_DEAD_CODE));
699*404b540aSrobert 
700*404b540aSrobert   return 1;
701*404b540aSrobert }
702*404b540aSrobert 
703*404b540aSrobert #endif /* OPTIMIZE_MODE_SWITCHING */
704*404b540aSrobert 
705*404b540aSrobert static bool
gate_mode_switching(void)706*404b540aSrobert gate_mode_switching (void)
707*404b540aSrobert {
708*404b540aSrobert #ifdef OPTIMIZE_MODE_SWITCHING
709*404b540aSrobert   return true;
710*404b540aSrobert #else
711*404b540aSrobert   return false;
712*404b540aSrobert #endif
713*404b540aSrobert }
714*404b540aSrobert 
715*404b540aSrobert static unsigned int
rest_of_handle_mode_switching(void)716*404b540aSrobert rest_of_handle_mode_switching (void)
717*404b540aSrobert {
718*404b540aSrobert #ifdef OPTIMIZE_MODE_SWITCHING
719*404b540aSrobert   no_new_pseudos = 0;
720*404b540aSrobert   optimize_mode_switching ();
721*404b540aSrobert   no_new_pseudos = 1;
722*404b540aSrobert #endif /* OPTIMIZE_MODE_SWITCHING */
723*404b540aSrobert   return 0;
724*404b540aSrobert }
725*404b540aSrobert 
726*404b540aSrobert 
727*404b540aSrobert struct tree_opt_pass pass_mode_switching =
728*404b540aSrobert {
729*404b540aSrobert   "mode-sw",                            /* name */
730*404b540aSrobert   gate_mode_switching,                  /* gate */
731*404b540aSrobert   rest_of_handle_mode_switching,        /* execute */
732*404b540aSrobert   NULL,                                 /* sub */
733*404b540aSrobert   NULL,                                 /* next */
734*404b540aSrobert   0,                                    /* static_pass_number */
735*404b540aSrobert   TV_MODE_SWITCH,                       /* tv_id */
736*404b540aSrobert   0,                                    /* properties_required */
737*404b540aSrobert   0,                                    /* properties_provided */
738*404b540aSrobert   0,                                    /* properties_destroyed */
739*404b540aSrobert   0,                                    /* todo_flags_start */
740*404b540aSrobert   TODO_dump_func,                       /* todo_flags_finish */
741*404b540aSrobert   0                                     /* letter */
742*404b540aSrobert };
743