bd227e691fcf91bce4cae264bf8b0ab425524c19
[libfirm] / ir / ir / irgopt.c
1 /*
2  * Project:     libFIRM
3  * File name:   ir/ir/irgopt.c
4  * Purpose:     Optimizations for a whole ir graph, i.e., a procedure.
5  * Author:      Christian Schaefer, Goetz Lindenmaier
6  * Modified by: Sebastian Felis
7  * Created:
8  * CVS-ID:      $Id$
9  * Copyright:   (c) 1998-2003 Universität Karlsruhe
10  * Licence:     This file protected by GPL -  GNU GENERAL PUBLIC LICENSE.
11  */
12
13
14 #ifdef HAVE_CONFIG_H
15 # include "config.h"
16 #endif
17
18 #include <assert.h>
19
20 #include "irnode_t.h"
21 #include "irgraph_t.h"
22 #include "irprog_t.h"
23
24 #include "ircons.h"
25 #include "iropt_t.h"
26 #include "irgopt.h"
27 #include "irgmod.h"
28 #include "irgwalk.h"
29
30 #include "array.h"
31 #include "pset.h"
32 #include "pmap.h"
33 #include "eset.h"
34 #include "pdeq.h"       /* Fuer code placement */
35 #include "xmalloc.h"
36
37 #include "irouts.h"
38 #include "irloop_t.h"
39 #include "irbackedge_t.h"
40 #include "cgana.h"
41 #include "trouts.h"
42
43
44 #include "irflag_t.h"
45 #include "irhooks.h"
46 #include "iredges_t.h"
47 #include "irtools.h"
48
49 /* Defined in iropt.c */
50 pset *new_identities (void);
51 void  del_identities (pset *value_table);
52 void  add_identities (pset *value_table, ir_node *node);
53
54 /*------------------------------------------------------------------*/
55 /* apply optimizations of iropt to all nodes.                       */
56 /*------------------------------------------------------------------*/
57
58 static void init_link (ir_node *n, void *env) {
59   set_irn_link(n, NULL);
60 }
61
62 #if 0   /* Old version. Avoids Ids.
63            This is not necessary:  we do a post walk, and get_irn_n
64            removes ids anyways.  So it's much cheaper to call the
65            optimization less often and use the exchange() algorithm. */
66 static void
67 optimize_in_place_wrapper (ir_node *n, void *env) {
68   int i, irn_arity;
69   ir_node *optimized, *old;
70
71   irn_arity = get_irn_arity(n);
72   for (i = 0; i < irn_arity; i++) {
73     /* get_irn_n skips Id nodes, so comparison old != optimized does not
74        show all optimizations. Therefore always set new predecessor. */
75     old = get_irn_intra_n(n, i);
76     optimized = optimize_in_place_2(old);
77     set_irn_n(n, i, optimized);
78   }
79
80   if (get_irn_op(n) == op_Block) {
81     optimized = optimize_in_place_2(n);
82     if (optimized != n) exchange (n, optimized);
83   }
84 }
85 #else
86 static void
87 optimize_in_place_wrapper (ir_node *n, void *env) {
88   ir_node *optimized = optimize_in_place_2(n);
89   if (optimized != n) exchange (n, optimized);
90 }
91 #endif
92
93
94 static INLINE void do_local_optimize(ir_node *n) {
95   /* Handle graph state */
96   assert(get_irg_phase_state(current_ir_graph) != phase_building);
97
98   if (get_opt_global_cse())
99     set_irg_pinned(current_ir_graph, op_pin_state_floats);
100   set_irg_outs_inconsistent(current_ir_graph);
101   set_irg_doms_inconsistent(current_ir_graph);
102   set_irg_loopinfo_inconsistent(current_ir_graph);
103
104   /* Clean the value_table in irg for the CSE. */
105   del_identities(current_ir_graph->value_table);
106   current_ir_graph->value_table = new_identities();
107
108   /* walk over the graph */
109   irg_walk(n, init_link, optimize_in_place_wrapper, NULL);
110 }
111
112 void local_optimize_node(ir_node *n) {
113   ir_graph *rem = current_ir_graph;
114   current_ir_graph = get_irn_irg(n);
115
116   do_local_optimize(n);
117
118   current_ir_graph = rem;
119 }
120
121 /**
122  * Block-Walker: uses dominance depth to mark dead blocks.
123  */
124 static void kill_dead_blocks(ir_node *block, void *env)
125 {
126   if (get_Block_dom_depth(block) < 0)
127     if (block != get_irg_end_block(current_ir_graph)) {
128       /* we don't want that the end block of graphs with
129          endless loops is marked bad (although it is of course */
130       set_Block_dead(block);
131     }
132 }
133
134 void
135 local_optimize_graph (ir_graph *irg) {
136   ir_graph *rem = current_ir_graph;
137   current_ir_graph = irg;
138
139   if (get_irg_dom_state(current_ir_graph) == dom_consistent)
140     irg_block_walk_graph(irg, NULL, kill_dead_blocks, NULL);
141
142   do_local_optimize(get_irg_end(irg));
143
144   current_ir_graph = rem;
145 }
146
147
148 /*------------------------------------------------------------------*/
149 /* Routines for dead node elimination / copying garbage collection  */
150 /* of the obstack.                                                  */
151 /*------------------------------------------------------------------*/
152
153 /**
154  * Remember the new node in the old node by using a field all nodes have.
155  */
156 #define set_new_node(oldn, newn)  set_irn_link(oldn, newn)
157
158 /**
159  * Get this new node, before the old node is forgotten.
160  */
161 #define get_new_node(oldn) get_irn_link(oldn)
162
163 /**
164  * Check if a new node was set.
165  */
166 #define has_new_node(n) (get_new_node(n) != NULL)
167
168 /**
169  * We use the block_visited flag to mark that we have computed the
170  * number of useful predecessors for this block.
171  * Further we encode the new arity in this flag in the old blocks.
172  * Remembering the arity is useful, as it saves a lot of pointer
173  * accesses.  This function is called for all Phi and Block nodes
174  * in a Block.
175  */
176 static INLINE int
177 compute_new_arity(ir_node *b) {
178   int i, res, irn_arity;
179   int irg_v, block_v;
180
181   irg_v = get_irg_block_visited(current_ir_graph);
182   block_v = get_Block_block_visited(b);
183   if (block_v >= irg_v) {
184     /* we computed the number of preds for this block and saved it in the
185        block_v flag */
186     return block_v - irg_v;
187   } else {
188     /* compute the number of good predecessors */
189     res = irn_arity = get_irn_arity(b);
190     for (i = 0; i < irn_arity; i++)
191       if (get_irn_opcode(get_irn_n(b, i)) == iro_Bad) res--;
192     /* save it in the flag. */
193     set_Block_block_visited(b, irg_v + res);
194     return res;
195   }
196 }
197
198 /**
199  * Copies the node to the new obstack. The Ins of the new node point to
200  * the predecessors on the old obstack.  For block/phi nodes not all
201  * predecessors might be copied.  n->link points to the new node.
202  * For Phi and Block nodes the function allocates in-arrays with an arity
203  * only for useful predecessors.  The arity is determined by counting
204  * the non-bad predecessors of the block.
205  *
206  * @param n    The node to be copied
207  * @param env  if non-NULL, the node number attribute will be copied to the new node
208  *
209  * Note: Also used for loop unrolling.
210  */
211 static void copy_node(ir_node *n, void *env) {
212   ir_node *nn, *block;
213   int new_arity;
214   ir_op *op = get_irn_op(n);
215   int copy_node_nr = env != NULL;
216
217   /* The end node looses it's flexible in array.  This doesn't matter,
218      as dead node elimination builds End by hand, inlineing doesn't use
219      the End node. */
220   /* assert(op == op_End ||  ((_ARR_DESCR(n->in))->cookie != ARR_F_MAGIC)); */
221
222   if (op == op_Bad) {
223     /* node copied already */
224     return;
225   } else if (op == op_Block) {
226     block = NULL;
227     new_arity = compute_new_arity(n);
228     n->attr.block.graph_arr = NULL;
229   } else {
230     block = get_nodes_block(n);
231     if (op == op_Phi) {
232       new_arity = compute_new_arity(block);
233     } else {
234       new_arity = get_irn_arity(n);
235     }
236   }
237   nn = new_ir_node(get_irn_dbg_info(n),
238            current_ir_graph,
239            block,
240            op,
241            get_irn_mode(n),
242            new_arity,
243            get_irn_in(n) + 1);
244   /* Copy the attributes.  These might point to additional data.  If this
245      was allocated on the old obstack the pointers now are dangling.  This
246      frees e.g. the memory of the graph_arr allocated in new_immBlock. */
247   copy_node_attr(n, nn);
248   new_backedge_info(nn);
249
250 #if DEBUG_libfirm
251   if (copy_node_nr) {
252     /* for easier debugging, we want to copy the node numbers too */
253     nn->node_nr = n->node_nr;
254   }
255 #endif
256
257   set_new_node(n, nn);
258   hook_dead_node_elim_subst(current_ir_graph, n, nn);
259 }
260
261 /**
262  * Copies new predecessors of old node to new node remembered in link.
263  * Spare the Bad predecessors of Phi and Block nodes.
264  */
265 void
266 copy_preds (ir_node *n, void *env) {
267   ir_node *nn, *block;
268   int i, j, irn_arity;
269
270   nn = get_new_node(n);
271
272   /* printf("\n old node: "); DDMSG2(n);
273      printf(" new node: "); DDMSG2(nn);
274      printf(" arities: old: %d, new: %d\n", get_irn_arity(n), get_irn_arity(nn)); */
275
276   if (is_Block(n)) {
277     /* Don't copy Bad nodes. */
278     j = 0;
279     irn_arity = get_irn_arity(n);
280     for (i = 0; i < irn_arity; i++)
281       if (! is_Bad(get_irn_n(n, i))) {
282         set_irn_n (nn, j, get_new_node(get_irn_n(n, i)));
283         /*if (is_backedge(n, i)) set_backedge(nn, j);*/
284         j++;
285       }
286     /* repair the block visited flag from above misuse. Repair it in both
287        graphs so that the old one can still be used. */
288     set_Block_block_visited(nn, 0);
289     set_Block_block_visited(n, 0);
290     /* Local optimization could not merge two subsequent blocks if
291        in array contained Bads.  Now it's possible.
292        We don't call optimize_in_place as it requires
293        that the fields in ir_graph are set properly. */
294     if ((get_opt_control_flow_straightening()) &&
295         (get_Block_n_cfgpreds(nn) == 1) &&
296         (get_irn_op(get_Block_cfgpred(nn, 0)) == op_Jmp)) {
297       ir_node *old = get_nodes_block(get_Block_cfgpred(nn, 0));
298       if (nn == old) {
299         /* Jmp jumps into the block it is in -- deal self cycle. */
300         assert(is_Bad(get_new_node(get_irg_bad(current_ir_graph))));
301         exchange(nn, get_new_node(get_irg_bad(current_ir_graph)));
302       } else {
303         exchange(nn, old);
304       }
305     }
306   } else if (get_irn_op(n) == op_Phi) {
307     /* Don't copy node if corresponding predecessor in block is Bad.
308        The Block itself should not be Bad. */
309     block = get_nodes_block(n);
310     set_irn_n (nn, -1, get_new_node(block));
311     j = 0;
312     irn_arity = get_irn_arity(n);
313     for (i = 0; i < irn_arity; i++)
314       if (! is_Bad(get_irn_n(block, i))) {
315         set_irn_n (nn, j, get_new_node(get_irn_n(n, i)));
316         /*if (is_backedge(n, i)) set_backedge(nn, j);*/
317         j++;
318       }
319     /* If the pre walker reached this Phi after the post walker visited the
320        block block_visited is > 0. */
321     set_Block_block_visited(get_nodes_block(n), 0);
322     /* Compacting the Phi's ins might generate Phis with only one
323        predecessor. */
324     if (get_irn_arity(nn) == 1)
325       exchange(nn, get_irn_n(nn, 0));
326   } else {
327     irn_arity = get_irn_arity(n);
328     for (i = -1; i < irn_arity; i++)
329       set_irn_n (nn, i, get_new_node(get_irn_n(n, i)));
330   }
331   /* Now the new node is complete.  We can add it to the hash table for CSE.
332      @@@ inlining aborts if we identify End. Why? */
333   if (get_irn_op(nn) != op_End)
334     add_identities (current_ir_graph->value_table, nn);
335 }
336
337 /**
338  * Copies the graph recursively, compacts the keep-alives of the end node.
339  *
340  * @param irg           the graph to be copied
341  * @param copy_node_nr  If non-zero, the node number will be copied
342  */
343 static void copy_graph(ir_graph *irg, int copy_node_nr) {
344   ir_node *oe, *ne, *ob, *nb, *om, *nm; /* old end, new end, old bad, new bad, old NoMem, new NoMem */
345   ir_node *ka;      /* keep alive */
346   int i, irn_arity;
347
348   oe = get_irg_end(irg);
349   /* copy the end node by hand, allocate dynamic in array! */
350   ne = new_ir_node(get_irn_dbg_info(oe),
351            irg,
352            NULL,
353            op_End,
354            mode_X,
355            -1,
356            NULL);
357   /* Copy the attributes.  Well, there might be some in the future... */
358   copy_node_attr(oe, ne);
359   set_new_node(oe, ne);
360
361   /* copy the Bad node */
362   ob = get_irg_bad(irg);
363   nb = new_ir_node(get_irn_dbg_info(ob),
364            irg,
365            NULL,
366            op_Bad,
367            mode_T,
368            0,
369            NULL);
370   set_new_node(ob, nb);
371
372   /* copy the NoMem node */
373   om = get_irg_no_mem(irg);
374   nm = new_ir_node(get_irn_dbg_info(om),
375            irg,
376            NULL,
377            op_NoMem,
378            mode_M,
379            0,
380            NULL);
381   set_new_node(om, nm);
382
383   /* copy the live nodes */
384   irg_walk(get_nodes_block(oe), copy_node, copy_preds, INT_TO_PTR(copy_node_nr));
385   /* copy_preds for the end node ... */
386   set_nodes_block(ne, get_new_node(get_nodes_block(oe)));
387
388   /*- ... and now the keep alives. -*/
389   /* First pick the not marked block nodes and walk them.  We must pick these
390      first as else we will oversee blocks reachable from Phis. */
391   irn_arity = get_irn_arity(oe);
392   for (i = 0; i < irn_arity; i++) {
393     ka = get_irn_intra_n(oe, i);
394     if (is_Block(ka) &&
395         (get_irn_visited(ka) < get_irg_visited(irg))) {
396       /* We must keep the block alive and copy everything reachable */
397       set_irg_visited(irg, get_irg_visited(irg)-1);
398       irg_walk(ka, copy_node, copy_preds, INT_TO_PTR(copy_node_nr));
399       add_End_keepalive(ne, get_new_node(ka));
400     }
401   }
402
403   /* Now pick other nodes.  Here we will keep all! */
404   irn_arity = get_irn_arity(oe);
405   for (i = 0; i < irn_arity; i++) {
406     ka = get_irn_intra_n(oe, i);
407     if (!is_Block(ka)) {
408       if (get_irn_visited(ka) < get_irg_visited(irg)) {
409         /* We didn't copy the node yet.  */
410         set_irg_visited(irg, get_irg_visited(irg)-1);
411         irg_walk(ka, copy_node, copy_preds, INT_TO_PTR(copy_node_nr));
412       }
413       add_End_keepalive(ne, get_new_node(ka));
414     }
415   }
416
417   /* start block sometimes only reached after keep alives */
418   set_nodes_block(nb, get_new_node(get_nodes_block(ob)));
419   set_nodes_block(nm, get_new_node(get_nodes_block(om)));
420 }
421
422 /**
423  * Copies the graph reachable from current_ir_graph->end to the obstack
424  * in current_ir_graph and fixes the environment.
425  * Then fixes the fields in current_ir_graph containing nodes of the
426  * graph.
427  *
428  * @param copy_node_nr  If non-zero, the node number will be copied
429  */
430 static void
431 copy_graph_env (int copy_node_nr) {
432   ir_graph *irg = current_ir_graph;
433   ir_node *old_end, *n;
434   int i;
435
436   /* Not all nodes remembered in irg might be reachable
437      from the end node.  Assure their link is set to NULL, so that
438      we can test whether new nodes have been computed. */
439   for (i = anchor_max - 1; i >= 0; --i)
440     if (irg->anchors[i])
441       set_new_node(irg->anchors[i], NULL);
442
443   /* we use the block walk flag for removing Bads from Blocks ins. */
444   inc_irg_block_visited(irg);
445
446   /* copy the graph */
447   copy_graph(irg, copy_node_nr);
448
449   /* fix the fields in irg */
450   old_end = get_irg_end(irg);
451   set_irg_end        (irg, get_new_node(old_end));
452   set_irg_end_except (irg, get_irg_end(irg));
453   set_irg_end_reg    (irg, get_irg_end(irg));
454   free_End(old_end);
455   set_irg_end_block  (irg, get_new_node(get_irg_end_block(irg)));
456
457   n = get_irg_frame(irg);
458   if (!has_new_node(n)) {
459     copy_node (n, INT_TO_PTR(copy_node_nr));
460     copy_preds(n, NULL);
461   }
462   n = get_irg_globals(irg);
463   if (!has_new_node(n)) {
464     copy_node (n, INT_TO_PTR(copy_node_nr));
465     copy_preds(n, NULL);
466   }
467   n = get_irg_initial_mem(irg);
468   if (!has_new_node(n)) {
469     copy_node (n, INT_TO_PTR(copy_node_nr));
470     copy_preds(n, NULL);
471   }
472   n = get_irg_args(irg);
473   if (!has_new_node(n)) {
474     copy_node (n, INT_TO_PTR(copy_node_nr));
475     copy_preds(n, NULL);
476   }
477   n = get_irg_bad(irg);
478   if (!has_new_node(n)) {
479     copy_node(n, INT_TO_PTR(copy_node_nr));
480     copy_preds(n, NULL);
481   }
482   n = get_irg_no_mem(irg);
483   if (!has_new_node(n)) {
484     copy_node(n, INT_TO_PTR(copy_node_nr));
485     copy_preds(n, NULL);
486   }
487   set_irg_start      (irg, get_new_node(get_irg_start(irg)));
488   set_irg_start_block(irg, get_new_node(get_irg_start_block(irg)));
489   set_irg_frame      (irg, get_new_node(get_irg_frame(irg)));
490   set_irg_globals    (irg, get_new_node(get_irg_globals(irg)));
491   set_irg_initial_mem(irg, get_new_node(get_irg_initial_mem(irg)));
492   set_irg_args       (irg, get_new_node(get_irg_args(irg)));
493   set_irg_bad        (irg, get_new_node(get_irg_bad(irg)));
494   set_irg_no_mem     (irg, get_new_node(get_irg_no_mem(irg)));
495 }
496
497 /**
498  * Copies all reachable nodes to a new obstack.  Removes bad inputs
499  * from block nodes and the corresponding inputs from Phi nodes.
500  * Merges single exit blocks with single entry blocks and removes
501  * 1-input Phis.
502  * Adds all new nodes to a new hash table for CSE.  Does not
503  * perform CSE, so the hash table might contain common subexpressions.
504  */
505 void
506 dead_node_elimination(ir_graph *irg) {
507   ir_graph *rem;
508   int rem_ipview = get_interprocedural_view();
509   struct obstack *graveyard_obst = NULL;
510   struct obstack *rebirth_obst   = NULL;
511
512   if (get_opt_optimize() && get_opt_dead_node_elimination()) {
513     assert(! edges_activated(irg) && "dead node elimination requires disabled edges");
514
515     /* inform statistics that we started a dead-node elimination run */
516     hook_dead_node_elim(irg, 1);
517
518     /* Remember external state of current_ir_graph. */
519     rem = current_ir_graph;
520     current_ir_graph = irg;
521     set_interprocedural_view(0);
522
523     assert(get_irg_phase_state(current_ir_graph) != phase_building);
524
525     /* Handle graph state */
526     free_callee_info(current_ir_graph);
527     free_irg_outs(current_ir_graph);
528     free_trouts();
529
530     /* @@@ so far we loose loops when copying */
531     free_loop_information(current_ir_graph);
532
533     set_irg_doms_inconsistent(irg);
534
535     /* A quiet place, where the old obstack can rest in peace,
536        until it will be cremated. */
537     graveyard_obst = irg->obst;
538
539     /* A new obstack, where the reachable nodes will be copied to. */
540     rebirth_obst = xmalloc (sizeof(*rebirth_obst));
541     current_ir_graph->obst = rebirth_obst;
542     obstack_init (current_ir_graph->obst);
543
544     /* We also need a new hash table for cse */
545     del_identities (irg->value_table);
546     irg->value_table = new_identities ();
547
548     /* Copy the graph from the old to the new obstack */
549     copy_graph_env(1);
550
551     /* Free memory from old unoptimized obstack */
552     obstack_free(graveyard_obst, 0);  /* First empty the obstack ... */
553     xfree (graveyard_obst);           /* ... then free it.           */
554
555     /* inform statistics that the run is over */
556     hook_dead_node_elim(irg, 0);
557
558     current_ir_graph = rem;
559     set_interprocedural_view(rem_ipview);
560   }
561 }
562
563 /**
564  * Relink bad predecessors of a block and store the old in array to the
565  * link field. This function is called by relink_bad_predecessors().
566  * The array of link field starts with the block operand at position 0.
567  * If block has bad predecessors, create a new in array without bad preds.
568  * Otherwise let in array untouched.
569  */
570 static void relink_bad_block_predecessors(ir_node *n, void *env) {
571   ir_node **new_in, *irn;
572   int i, new_irn_n, old_irn_arity, new_irn_arity = 0;
573
574   /* if link field of block is NULL, look for bad predecessors otherwise
575      this is already done */
576   if (get_irn_op(n) == op_Block &&
577       get_irn_link(n) == NULL) {
578
579     /* save old predecessors in link field (position 0 is the block operand)*/
580     set_irn_link(n, get_irn_in(n));
581
582     /* count predecessors without bad nodes */
583     old_irn_arity = get_irn_arity(n);
584     for (i = 0; i < old_irn_arity; i++)
585       if (!is_Bad(get_irn_n(n, i))) new_irn_arity++;
586
587     /* arity changing: set new predecessors without bad nodes */
588     if (new_irn_arity < old_irn_arity) {
589       /* Get new predecessor array. We do not resize the array, as we must
590          keep the old one to update Phis. */
591       new_in = NEW_ARR_D (ir_node *, current_ir_graph->obst, (new_irn_arity+1));
592
593       /* set new predecessors in array */
594       new_in[0] = NULL;
595       new_irn_n = 1;
596       for (i = 0; i < old_irn_arity; i++) {
597         irn = get_irn_n(n, i);
598         if (!is_Bad(irn)) {
599           new_in[new_irn_n] = irn;
600           is_backedge(n, i) ? set_backedge(n, new_irn_n-1) : set_not_backedge(n, new_irn_n-1);
601           ++new_irn_n;
602         }
603       }
604       //ARR_SETLEN(int, n->attr.block.backedge, new_irn_arity);
605       ARR_SHRINKLEN(n->attr.block.backedge, new_irn_arity);
606       n->in = new_in;
607
608     } /* ir node has bad predecessors */
609
610   } /* Block is not relinked */
611 }
612
613 /**
614  * Relinks Bad predecessors from Blocks and Phis called by walker
615  * remove_bad_predecesors(). If n is a Block, call
616  * relink_bad_block_redecessors(). If n is a Phi-node, call also the relinking
617  * function of Phi's Block. If this block has bad predecessors, relink preds
618  * of the Phi-node.
619  */
620 static void relink_bad_predecessors(ir_node *n, void *env) {
621   ir_node *block, **old_in;
622   int i, old_irn_arity, new_irn_arity;
623
624   /* relink bad predecessors of a block */
625   if (get_irn_op(n) == op_Block)
626     relink_bad_block_predecessors(n, env);
627
628   /* If Phi node relink its block and its predecessors */
629   if (get_irn_op(n) == op_Phi) {
630
631     /* Relink predecessors of phi's block */
632     block = get_nodes_block(n);
633     if (get_irn_link(block) == NULL)
634       relink_bad_block_predecessors(block, env);
635
636     old_in = (ir_node **)get_irn_link(block); /* Of Phi's Block */
637     old_irn_arity = ARR_LEN(old_in);
638
639     /* Relink Phi predecessors if count of predecessors changed */
640     if (old_irn_arity != ARR_LEN(get_irn_in(block))) {
641       /* set new predecessors in array
642          n->in[0] remains the same block */
643       new_irn_arity = 1;
644       for(i = 1; i < old_irn_arity; i++)
645         if (!is_Bad((ir_node *)old_in[i])) {
646           n->in[new_irn_arity] = n->in[i];
647           is_backedge(n, i) ? set_backedge(n, new_irn_arity) : set_not_backedge(n, new_irn_arity);
648           ++new_irn_arity;
649         }
650
651       ARR_SETLEN(ir_node *, n->in, new_irn_arity);
652       ARR_SETLEN(int, n->attr.phi_backedge, new_irn_arity);
653     }
654
655   } /* n is a Phi node */
656 }
657
658 /*
659  * Removes Bad Bad predecessors from Blocks and the corresponding
660  * inputs to Phi nodes as in dead_node_elimination but without
661  * copying the graph.
662  * On walking up set the link field to NULL, on walking down call
663  * relink_bad_predecessors() (This function stores the old in array
664  * to the link field and sets a new in array if arity of predecessors
665  * changes).
666  */
667 void remove_bad_predecessors(ir_graph *irg) {
668   irg_walk_graph(irg, init_link, relink_bad_predecessors, NULL);
669 }
670
671
672 /*
673    __                      _  __ __
674   (_     __    o     _    | \/  |_
675   __)|_| | \_/ | \_/(/_   |_/\__|__
676
677   The following stuff implements a facility that automatically patches
678   registered ir_node pointers to the new node when a dead node elimination occurs.
679 */
680
681 struct _survive_dce_t {
682   struct obstack obst;
683   pmap *places;
684   pmap *new_places;
685   hook_entry_t dead_node_elim;
686   hook_entry_t dead_node_elim_subst;
687 };
688
689 typedef struct _survive_dce_list_t {
690   struct _survive_dce_list_t *next;
691   ir_node **place;
692 } survive_dce_list_t;
693
694 static void dead_node_hook(void *context, ir_graph *irg, int start)
695 {
696   survive_dce_t *sd = context;
697
698   /* Create a new map before the dead node elimination is performed. */
699   if(start) {
700     sd->new_places = pmap_create_ex(pmap_count(sd->places));
701   }
702
703   /* Patch back all nodes if dead node elimination is over and something is to be done. */
704   else {
705     pmap_destroy(sd->places);
706     sd->places     = sd->new_places;
707     sd->new_places = NULL;
708   }
709 }
710
711 static void dead_node_subst_hook(void *context, ir_graph *irg, ir_node *old, ir_node *nw)
712 {
713   survive_dce_t *sd = context;
714   survive_dce_list_t *list = pmap_get(sd->places, old);
715
716   /* If the node is to be patched back, write the new address to all registered locations. */
717   if(list) {
718     survive_dce_list_t *p;
719
720     for(p = list; p; p = p->next)
721       *(p->place) = nw;
722
723     pmap_insert(sd->new_places, nw, list);
724   }
725 }
726
727 /**
728  * Make a new Survive DCE environment.
729  */
730 survive_dce_t *new_survive_dce(void)
731 {
732   survive_dce_t *res = xmalloc(sizeof(res[0]));
733   obstack_init(&res->obst);
734   res->places     = pmap_create();
735   res->new_places = NULL;
736
737   res->dead_node_elim.hook._hook_dead_node_elim = dead_node_hook;
738   res->dead_node_elim.context                   = res;
739   res->dead_node_elim.next                      = NULL;
740
741   res->dead_node_elim_subst.hook._hook_dead_node_elim_subst = dead_node_subst_hook;
742   res->dead_node_elim_subst.context = res;
743   res->dead_node_elim_subst.next    = NULL;
744
745   register_hook(hook_dead_node_elim, &res->dead_node_elim);
746   register_hook(hook_dead_node_elim_subst, &res->dead_node_elim_subst);
747   return res;
748 }
749
750 /**
751  * Free a Survive DCE environment.
752  */
753 void free_survive_dce(survive_dce_t *sd)
754 {
755   obstack_free(&sd->obst, NULL);
756   pmap_destroy(sd->places);
757   unregister_hook(hook_dead_node_elim, &sd->dead_node_elim);
758   unregister_hook(hook_dead_node_elim_subst, &sd->dead_node_elim_subst);
759   free(sd);
760 }
761
762 /**
763  * Register a node pointer to be patched upon DCE.
764  * When DCE occurs, the node pointer specified by @p place will be
765  * patched to the new address of the node it is pointing to.
766  *
767  * @param sd    The Survive DCE environment.
768  * @param place The address of the node pointer.
769  */
770 void survive_dce_register_irn(survive_dce_t *sd, ir_node **place)
771 {
772   if(*place != NULL) {
773     ir_node *irn      = *place;
774     survive_dce_list_t *curr = pmap_get(sd->places, irn);
775     survive_dce_list_t *nw   = obstack_alloc(&sd->obst, sizeof(nw));
776
777     nw->next  = curr;
778     nw->place = place;
779
780     pmap_insert(sd->places, irn, nw);
781   }
782 }
783
784 /*--------------------------------------------------------------------*/
785 /*  Functionality for inlining                                         */
786 /*--------------------------------------------------------------------*/
787
788 /**
789  * Copy node for inlineing.  Updates attributes that change when
790  * inlineing but not for dead node elimination.
791  *
792  * Copies the node by calling copy_node() and then updates the entity if
793  * it's a local one.  env must be a pointer of the frame type of the
794  * inlined procedure. The new entities must be in the link field of
795  * the entities.
796  */
797 static INLINE void
798 copy_node_inline (ir_node *n, void *env) {
799   ir_node *nn;
800   ir_type *frame_tp = (ir_type *)env;
801
802   copy_node(n, NULL);
803   if (get_irn_op(n) == op_Sel) {
804     nn = get_new_node (n);
805     assert(is_Sel(nn));
806     if (get_entity_owner(get_Sel_entity(n)) == frame_tp) {
807       set_Sel_entity(nn, get_entity_link(get_Sel_entity(n)));
808     }
809   } else if (get_irn_op(n) == op_Block) {
810     nn = get_new_node (n);
811     nn->attr.block.irg = current_ir_graph;
812   }
813 }
814
815 static void find_addr(ir_node *node, void *env)
816 {
817   if (get_irn_opcode(node) == iro_Proj) {
818     if (get_Proj_proj(node) == pn_Start_P_value_arg_base)
819       *(int *)env = 0;
820   }
821 }
822
823 /*
824  * currently, we cannot inline two cases:
825  * - call with compound arguments
826  * - graphs that take the address of a parameter
827  *
828  * check these conditions here
829  */
830 static int can_inline(ir_node *call, ir_graph *called_graph)
831 {
832   ir_type *call_type = get_Call_type(call);
833   int params, ress, i, res;
834   assert(is_Method_type(call_type));
835
836   params = get_method_n_params(call_type);
837   ress   = get_method_n_ress(call_type);
838
839   /* check params */
840   for (i = 0; i < params; ++i) {
841     ir_type *p_type = get_method_param_type(call_type, i);
842
843     if (is_compound_type(p_type))
844       return 0;
845   }
846
847   /* check res */
848   for (i = 0; i < ress; ++i) {
849     ir_type *r_type = get_method_res_type(call_type, i);
850
851     if (is_compound_type(r_type))
852       return 0;
853   }
854
855   res = 1;
856   irg_walk_graph(called_graph, find_addr, NULL, &res);
857
858   return res;
859 }
860
861 int inline_method(ir_node *call, ir_graph *called_graph) {
862   ir_node *pre_call;
863   ir_node *post_call, *post_bl;
864   ir_node *in[5];
865   ir_node *end, *end_bl;
866   ir_node **res_pred;
867   ir_node **cf_pred;
868   ir_node *ret, *phi;
869   int arity, n_ret, n_exc, n_res, i, j, rem_opt, irn_arity;
870   int exc_handling;
871   ir_type *called_frame;
872   irg_inline_property prop = get_irg_inline_property(called_graph);
873
874   if ( (prop != irg_inline_forced) &&
875        (!get_opt_optimize() || !get_opt_inline() || (prop == irg_inline_forbidden))) return 0;
876
877   /* Do not inline variadic functions. */
878   if (get_method_variadicity(get_entity_type(get_irg_entity(called_graph))) == variadicity_variadic)
879     return 0;
880
881   assert(get_method_n_params(get_entity_type(get_irg_entity(called_graph))) ==
882          get_method_n_params(get_Call_type(call)));
883
884   /*
885    * currently, we cannot inline two cases:
886    * - call with compound arguments
887    * - graphs that take the address of a parameter
888    */
889   if (! can_inline(call, called_graph))
890     return 0;
891
892   /* --  Turn off optimizations, this can cause problems when allocating new nodes. -- */
893   rem_opt = get_opt_optimize();
894   set_optimize(0);
895
896   /* Handle graph state */
897   assert(get_irg_phase_state(current_ir_graph) != phase_building);
898   assert(get_irg_pinned(current_ir_graph) == op_pin_state_pinned);
899   assert(get_irg_pinned(called_graph) == op_pin_state_pinned);
900   set_irg_outs_inconsistent(current_ir_graph);
901   set_irg_extblk_inconsistent(current_ir_graph);
902   set_irg_doms_inconsistent(current_ir_graph);
903   set_irg_loopinfo_inconsistent(current_ir_graph);
904   set_irg_callee_info_state(current_ir_graph, irg_callee_info_inconsistent);
905
906   /* -- Check preconditions -- */
907   assert(is_Call(call));
908   /* @@@ does not work for InterfaceIII.java after cgana
909      assert(get_Call_type(call) == get_entity_type(get_irg_entity(called_graph)));
910      assert(smaller_type(get_entity_type(get_irg_entity(called_graph)),
911      get_Call_type(call)));
912   */
913   assert(get_type_tpop(get_Call_type(call)) == type_method);
914   if (called_graph == current_ir_graph) {
915     set_optimize(rem_opt);
916     return 0;
917   }
918
919   /* here we know we WILL inline, so inform the statistics */
920   hook_inline(call, called_graph);
921
922   /* -- Decide how to handle exception control flow: Is there a handler
923      for the Call node, or do we branch directly to End on an exception?
924      exc_handling:
925      0 There is a handler.
926      1 Branches to End.
927      2 Exception handling not represented in Firm. -- */
928   {
929     ir_node *proj, *Mproj = NULL, *Xproj = NULL;
930     for (proj = (ir_node *)get_irn_link(call); proj; proj = (ir_node *)get_irn_link(proj)) {
931       assert(get_irn_op(proj) == op_Proj);
932       if (get_Proj_proj(proj) == pn_Call_X_except) Xproj = proj;
933       if (get_Proj_proj(proj) == pn_Call_M_except) Mproj = proj;
934     }
935     if      (Mproj) { assert(Xproj); exc_handling = 0; } /*  Mproj           */
936     else if (Xproj) {                exc_handling = 1; } /* !Mproj &&  Xproj   */
937     else            {                exc_handling = 2; } /* !Mproj && !Xproj   */
938   }
939
940
941   /* --
942      the procedure and later replaces the Start node of the called graph.
943      Post_call is the old Call node and collects the results of the called
944      graph. Both will end up being a tuple.  -- */
945   post_bl = get_nodes_block(call);
946   set_irg_current_block(current_ir_graph, post_bl);
947   /* XxMxPxP of Start + parameter of Call */
948   in[pn_Start_X_initial_exec] = new_Jmp();
949   in[pn_Start_M]              = get_Call_mem(call);
950   in[pn_Start_P_frame_base]   = get_irg_frame(current_ir_graph);
951   in[pn_Start_P_globals]      = get_irg_globals(current_ir_graph);
952   in[pn_Start_T_args]         = new_Tuple(get_Call_n_params(call), get_Call_param_arr(call));
953   /* in[pn_Start_P_value_arg_base] = ??? */
954   pre_call = new_Tuple(5, in);
955   post_call = call;
956
957   /* --
958      The new block gets the ins of the old block, pre_call and all its
959      predecessors and all Phi nodes. -- */
960   part_block(pre_call);
961
962   /* -- Prepare state for dead node elimination -- */
963   /* Visited flags in calling irg must be >= flag in called irg.
964      Else walker and arity computation will not work. */
965   if (get_irg_visited(current_ir_graph) <= get_irg_visited(called_graph))
966     set_irg_visited(current_ir_graph, get_irg_visited(called_graph)+1);
967   if (get_irg_block_visited(current_ir_graph)< get_irg_block_visited(called_graph))
968     set_irg_block_visited(current_ir_graph, get_irg_block_visited(called_graph));
969   /* Set pre_call as new Start node in link field of the start node of
970      calling graph and pre_calls block as new block for the start block
971      of calling graph.
972      Further mark these nodes so that they are not visited by the
973      copying. */
974   set_irn_link(get_irg_start(called_graph), pre_call);
975   set_irn_visited(get_irg_start(called_graph), get_irg_visited(current_ir_graph));
976   set_irn_link(get_irg_start_block(called_graph), get_nodes_block(pre_call));
977   set_irn_visited(get_irg_start_block(called_graph), get_irg_visited(current_ir_graph));
978   set_irn_link(get_irg_bad(called_graph), get_irg_bad(current_ir_graph));
979   set_irn_visited(get_irg_bad(called_graph), get_irg_visited(current_ir_graph));
980
981   /* Initialize for compaction of in arrays */
982   inc_irg_block_visited(current_ir_graph);
983
984   /* -- Replicate local entities of the called_graph -- */
985   /* copy the entities. */
986   called_frame = get_irg_frame_type(called_graph);
987   for (i = 0; i < get_class_n_members(called_frame); i++) {
988     entity *new_ent, *old_ent;
989     old_ent = get_class_member(called_frame, i);
990     new_ent = copy_entity_own(old_ent, get_cur_frame_type());
991     set_entity_link(old_ent, new_ent);
992   }
993
994   /* visited is > than that of called graph.  With this trick visited will
995      remain unchanged so that an outer walker, e.g., searching the call nodes
996      to inline, calling this inline will not visit the inlined nodes. */
997   set_irg_visited(current_ir_graph, get_irg_visited(current_ir_graph)-1);
998
999   /* -- Performing dead node elimination inlines the graph -- */
1000   /* Copies the nodes to the obstack of current_ir_graph. Updates links to new
1001      entities. */
1002   /* @@@ endless loops are not copied!! -- they should be, I think... */
1003   irg_walk(get_irg_end(called_graph), copy_node_inline, copy_preds,
1004            get_irg_frame_type(called_graph));
1005
1006   /* Repair called_graph */
1007   set_irg_visited(called_graph, get_irg_visited(current_ir_graph));
1008   set_irg_block_visited(called_graph, get_irg_block_visited(current_ir_graph));
1009   set_Block_block_visited(get_irg_start_block(called_graph), 0);
1010
1011   /* -- Merge the end of the inlined procedure with the call site -- */
1012   /* We will turn the old Call node into a Tuple with the following
1013      predecessors:
1014      -1:  Block of Tuple.
1015      0: Phi of all Memories of Return statements.
1016      1: Jmp from new Block that merges the control flow from all exception
1017      predecessors of the old end block.
1018      2: Tuple of all arguments.
1019      3: Phi of Exception memories.
1020      In case the old Call directly branches to End on an exception we don't
1021      need the block merging all exceptions nor the Phi of the exception
1022      memories.
1023   */
1024
1025   /* -- Precompute some values -- */
1026   end_bl = get_new_node(get_irg_end_block(called_graph));
1027   end = get_new_node(get_irg_end(called_graph));
1028   arity = get_irn_arity(end_bl);    /* arity = n_exc + n_ret  */
1029   n_res = get_method_n_ress(get_Call_type(call));
1030
1031   res_pred = xmalloc (n_res * sizeof(*res_pred));
1032   cf_pred  = xmalloc (arity * sizeof(*res_pred));
1033
1034   set_irg_current_block(current_ir_graph, post_bl); /* just to make sure */
1035
1036   /* -- archive keepalives -- */
1037   irn_arity = get_irn_arity(end);
1038   for (i = 0; i < irn_arity; i++)
1039     add_End_keepalive(get_irg_end(current_ir_graph), get_irn_n(end, i));
1040
1041   /* The new end node will die.  We need not free as the in array is on the obstack:
1042      copy_node() only generated 'D' arrays. */
1043
1044   /* -- Replace Return nodes by Jump nodes. -- */
1045   n_ret = 0;
1046   for (i = 0; i < arity; i++) {
1047     ir_node *ret;
1048     ret = get_irn_n(end_bl, i);
1049     if (is_Return(ret)) {
1050       cf_pred[n_ret] = new_r_Jmp(current_ir_graph, get_nodes_block(ret));
1051       n_ret++;
1052     }
1053   }
1054   set_irn_in(post_bl, n_ret, cf_pred);
1055
1056   /* -- Build a Tuple for all results of the method.
1057      Add Phi node if there was more than one Return.  -- */
1058   turn_into_tuple(post_call, 4);
1059   /* First the Memory-Phi */
1060   n_ret = 0;
1061   for (i = 0; i < arity; i++) {
1062     ret = get_irn_n(end_bl, i);
1063     if (is_Return(ret)) {
1064       cf_pred[n_ret] = get_Return_mem(ret);
1065       n_ret++;
1066     }
1067   }
1068   phi = new_Phi(n_ret, cf_pred, mode_M);
1069   set_Tuple_pred(call, pn_Call_M_regular, phi);
1070   /* Conserve Phi-list for further inlinings -- but might be optimized */
1071   if (get_nodes_block(phi) == post_bl) {
1072     set_irn_link(phi, get_irn_link(post_bl));
1073     set_irn_link(post_bl, phi);
1074   }
1075   /* Now the real results */
1076   if (n_res > 0) {
1077     for (j = 0; j < n_res; j++) {
1078       n_ret = 0;
1079       for (i = 0; i < arity; i++) {
1080         ret = get_irn_n(end_bl, i);
1081         if (get_irn_op(ret) == op_Return) {
1082           cf_pred[n_ret] = get_Return_res(ret, j);
1083           n_ret++;
1084         }
1085       }
1086       if (n_ret > 0)
1087         phi = new_Phi(n_ret, cf_pred, get_irn_mode(cf_pred[0]));
1088       else
1089         phi = new_Bad();
1090       res_pred[j] = phi;
1091       /* Conserve Phi-list for further inlinings -- but might be optimized */
1092       if (get_nodes_block(phi) == post_bl) {
1093         set_irn_link(phi, get_irn_link(post_bl));
1094         set_irn_link(post_bl, phi);
1095       }
1096     }
1097     set_Tuple_pred(call, pn_Call_T_result, new_Tuple(n_res, res_pred));
1098   } else {
1099     set_Tuple_pred(call, pn_Call_T_result, new_Bad());
1100   }
1101   /* Finally the exception control flow.
1102      We have two (three) possible situations:
1103      First if the Call branches to an exception handler: We need to add a Phi node to
1104      collect the memory containing the exception objects.  Further we need
1105      to add another block to get a correct representation of this Phi.  To
1106      this block we add a Jmp that resolves into the X output of the Call
1107      when the Call is turned into a tuple.
1108      Second the Call branches to End, the exception is not handled.  Just
1109      add all inlined exception branches to the End node.
1110      Third: there is no Exception edge at all. Handle as case two. */
1111   if (exc_handling == 0) {
1112     n_exc = 0;
1113     for (i = 0; i < arity; i++) {
1114       ir_node *ret;
1115       ret = get_irn_n(end_bl, i);
1116       if (is_fragile_op(skip_Proj(ret)) || (get_irn_op(skip_Proj(ret)) == op_Raise)) {
1117         cf_pred[n_exc] = ret;
1118         n_exc++;
1119       }
1120     }
1121     if (n_exc > 0) {
1122       new_Block(n_exc, cf_pred);      /* watch it: current_block is changed! */
1123       set_Tuple_pred(call, pn_Call_X_except, new_Jmp());
1124       /* The Phi for the memories with the exception objects */
1125       n_exc = 0;
1126       for (i = 0; i < arity; i++) {
1127         ir_node *ret;
1128         ret = skip_Proj(get_irn_n(end_bl, i));
1129         if (is_Call(ret)) {
1130           cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 3);
1131           n_exc++;
1132         } else if (is_fragile_op(ret)) {
1133           /* We rely that all cfops have the memory output at the same position. */
1134           cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 0);
1135           n_exc++;
1136         } else if (get_irn_op(ret) == op_Raise) {
1137           cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 1);
1138           n_exc++;
1139         }
1140       }
1141       set_Tuple_pred(call, pn_Call_M_except, new_Phi(n_exc, cf_pred, mode_M));
1142     } else {
1143       set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1144       set_Tuple_pred(call, pn_Call_M_except, new_Bad());
1145     }
1146   } else {
1147     ir_node *main_end_bl;
1148     int main_end_bl_arity;
1149     ir_node **end_preds;
1150
1151     /* assert(exc_handling == 1 || no exceptions. ) */
1152     n_exc = 0;
1153     for (i = 0; i < arity; i++) {
1154       ir_node *ret = get_irn_n(end_bl, i);
1155
1156       if (is_fragile_op(skip_Proj(ret)) || (get_irn_op(skip_Proj(ret)) == op_Raise)) {
1157         cf_pred[n_exc] = ret;
1158         n_exc++;
1159       }
1160     }
1161     main_end_bl = get_irg_end_block(current_ir_graph);
1162     main_end_bl_arity = get_irn_arity(main_end_bl);
1163     end_preds =  xmalloc ((n_exc + main_end_bl_arity) * sizeof(*end_preds));
1164
1165     for (i = 0; i < main_end_bl_arity; ++i)
1166       end_preds[i] = get_irn_n(main_end_bl, i);
1167     for (i = 0; i < n_exc; ++i)
1168       end_preds[main_end_bl_arity + i] = cf_pred[i];
1169     set_irn_in(main_end_bl, n_exc + main_end_bl_arity, end_preds);
1170     set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1171     set_Tuple_pred(call, pn_Call_M_except, new_Bad());
1172     free(end_preds);
1173   }
1174   free(res_pred);
1175   free(cf_pred);
1176
1177 #if 0  /* old. now better, correcter, faster implementation. */
1178   if (n_exc > 0) {
1179     /* -- If the exception control flow from the inlined Call directly
1180        branched to the end block we now have the following control
1181        flow predecessor pattern: ProjX -> Tuple -> Jmp.  We must
1182        remove the Jmp along with it's empty block and add Jmp's
1183        predecessors as predecessors of this end block.  No problem if
1184        there is no exception, because then branches Bad to End which
1185        is fine. --
1186        @@@ can't we know this beforehand: by getting the Proj(1) from
1187        the Call link list and checking whether it goes to Proj. */
1188     /* find the problematic predecessor of the end block. */
1189     end_bl = get_irg_end_block(current_ir_graph);
1190     for (i = 0; i < get_Block_n_cfgpreds(end_bl); i++) {
1191       cf_op = get_Block_cfgpred(end_bl, i);
1192       if (get_irn_op(cf_op) == op_Proj) {
1193         cf_op = get_Proj_pred(cf_op);
1194         if ((get_irn_op(cf_op) == op_Tuple) && (cf_op == call)) {
1195           /*  There are unoptimized tuples from inlineing before when no exc */
1196           assert(get_Proj_proj(get_Block_cfgpred(end_bl, i)) == pn_Call_X_except);
1197           cf_op = get_Tuple_pred(cf_op, pn_Call_X_except);
1198           assert(get_irn_op(cf_op) == op_Jmp);
1199           break;
1200         }
1201       }
1202     }
1203     /* repair */
1204     if (i < get_Block_n_cfgpreds(end_bl)) {
1205       bl = get_nodes_block(cf_op);
1206       arity = get_Block_n_cfgpreds(end_bl) + get_Block_n_cfgpreds(bl) - 1;
1207       cf_pred = xmalloc (arity * sizeof(*cf_pred));
1208       for (j = 0; j < i; j++)
1209         cf_pred[j] = get_Block_cfgpred(end_bl, j);
1210       for (j = j; j < i + get_Block_n_cfgpreds(bl); j++)
1211         cf_pred[j] = get_Block_cfgpred(bl, j-i);
1212       for (j = j; j < arity; j++)
1213         cf_pred[j] = get_Block_cfgpred(end_bl, j-get_Block_n_cfgpreds(bl) +1);
1214       set_irn_in(end_bl, arity, cf_pred);
1215       free(cf_pred);
1216       /*  Remove the exception pred from post-call Tuple. */
1217       set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1218     }
1219   }
1220 #endif
1221
1222   /* --  Turn CSE back on. -- */
1223   set_optimize(rem_opt);
1224
1225   return 1;
1226 }
1227
1228 /********************************************************************/
1229 /* Apply inlineing to small methods.                                */
1230 /********************************************************************/
1231
1232 /* It makes no sense to inline too many calls in one procedure. Anyways,
1233    I didn't get a version with NEW_ARR_F to run. */
1234 #define MAX_INLINE 1024
1235
1236 /**
1237  * environment for inlining small irgs
1238  */
1239 typedef struct _inline_env_t {
1240   int pos;
1241   ir_node *calls[MAX_INLINE];
1242 } inline_env_t;
1243
1244 /**
1245  * Returns the irg called from a Call node. If the irg is not
1246  * known, NULL is returned.
1247  */
1248 static ir_graph *get_call_called_irg(ir_node *call) {
1249   ir_node *addr;
1250   ir_graph *called_irg = NULL;
1251
1252   assert(is_Call(call));
1253
1254   addr = get_Call_ptr(call);
1255   if ((get_irn_op(addr) == op_SymConst) && (get_SymConst_kind (addr) == symconst_addr_ent)) {
1256     called_irg = get_entity_irg(get_SymConst_entity(addr));
1257   }
1258
1259   return called_irg;
1260 }
1261
1262 static void collect_calls(ir_node *call, void *env) {
1263   ir_node *addr;
1264
1265   if (! is_Call(call)) return;
1266
1267   addr = get_Call_ptr(call);
1268
1269   if (get_irn_op(addr) == op_SymConst) {
1270     if (get_SymConst_kind(addr) == symconst_addr_ent) {
1271       ir_graph *called_irg = get_entity_irg(get_SymConst_entity(addr));
1272       inline_env_t *ienv = (inline_env_t *)env;
1273       if (called_irg && ienv->pos < MAX_INLINE) {
1274         /* The Call node calls a locally defined method.  Remember to inline. */
1275         ienv->calls[ienv->pos++] = call;
1276       }
1277     }
1278   }
1279 }
1280
1281 /**
1282  * Inlines all small methods at call sites where the called address comes
1283  * from a Const node that references the entity representing the called
1284  * method.
1285  * The size argument is a rough measure for the code size of the method:
1286  * Methods where the obstack containing the firm graph is smaller than
1287  * size are inlined.
1288  */
1289 void inline_small_irgs(ir_graph *irg, int size) {
1290   int i;
1291   ir_graph *rem = current_ir_graph;
1292   inline_env_t env /* = {0, NULL}*/;
1293
1294   if (!(get_opt_optimize() && get_opt_inline())) return;
1295
1296   current_ir_graph = irg;
1297   /* Handle graph state */
1298   assert(get_irg_phase_state(current_ir_graph) != phase_building);
1299   free_callee_info(current_ir_graph);
1300
1301   /* Find Call nodes to inline.
1302      (We can not inline during a walk of the graph, as inlineing the same
1303      method several times changes the visited flag of the walked graph:
1304      after the first inlineing visited of the callee equals visited of
1305      the caller.  With the next inlineing both are increased.) */
1306   env.pos = 0;
1307   irg_walk(get_irg_end(irg), NULL, collect_calls, &env);
1308
1309   if ((env.pos > 0) && (env.pos < MAX_INLINE)) {
1310     /* There are calls to inline */
1311     collect_phiprojs(irg);
1312     for (i = 0; i < env.pos; i++) {
1313       ir_graph *callee;
1314       callee = get_entity_irg(get_SymConst_entity(get_Call_ptr(env.calls[i])));
1315       if (((_obstack_memory_used(callee->obst) - (int)obstack_room(callee->obst)) < size) ||
1316         (get_irg_inline_property(callee) == irg_inline_forced)) {
1317         inline_method(env.calls[i], callee);
1318       }
1319     }
1320   }
1321
1322   current_ir_graph = rem;
1323 }
1324
1325 /**
1326  * Environment for inlining irgs.
1327  */
1328 typedef struct {
1329   int n_nodes;       /**< Nodes in graph except Id, Tuple, Proj, Start, End */
1330   int n_nodes_orig;  /**< for statistics */
1331   eset *call_nodes;  /**< All call nodes in this graph */
1332   int n_call_nodes;
1333   int n_call_nodes_orig; /**< for statistics */
1334   int n_callers;   /**< Number of known graphs that call this graphs. */
1335   int n_callers_orig; /**< for statistics */
1336 } inline_irg_env;
1337
1338 /**
1339  * Allocate a new environment for inlining.
1340  */
1341 static inline_irg_env *new_inline_irg_env(void) {
1342   inline_irg_env *env    = xmalloc(sizeof(*env));
1343   env->n_nodes           = -2; /* do not count count Start, End */
1344   env->n_nodes_orig      = -2; /* do not count Start, End */
1345   env->call_nodes        = eset_create();
1346   env->n_call_nodes      = 0;
1347   env->n_call_nodes_orig = 0;
1348   env->n_callers         = 0;
1349   env->n_callers_orig    = 0;
1350   return env;
1351 }
1352
1353 /**
1354  * destroy an environment for inlining.
1355  */
1356 static void free_inline_irg_env(inline_irg_env *env) {
1357   eset_destroy(env->call_nodes);
1358   free(env);
1359 }
1360
1361 /**
1362  * post-walker: collect all calls in the inline-environment
1363  * of a graph and sum some statistics.
1364  */
1365 static void collect_calls2(ir_node *call, void *env) {
1366   inline_irg_env *x = (inline_irg_env *)env;
1367   ir_op *op = get_irn_op(call);
1368   ir_graph *callee;
1369
1370   /* count meaningful nodes in irg */
1371   if (op != op_Proj && op != op_Tuple && op != op_Sync) {
1372     x->n_nodes++;
1373     x->n_nodes_orig++;
1374   }
1375
1376   if (op != op_Call) return;
1377
1378   /* collect all call nodes */
1379   eset_insert(x->call_nodes, call);
1380   x->n_call_nodes++;
1381   x->n_call_nodes_orig++;
1382
1383   /* count all static callers */
1384   callee = get_call_called_irg(call);
1385   if (callee) {
1386     inline_irg_env *callee_env = get_irg_link(callee);
1387     callee_env->n_callers++;
1388     callee_env->n_callers_orig++;
1389   }
1390 }
1391
1392 /**
1393  * Returns TRUE if the number of callers in 0 in the irg's environment,
1394  * hence this irg is a leave.
1395  */
1396 INLINE static int is_leave(ir_graph *irg) {
1397   return (((inline_irg_env *)get_irg_link(irg))->n_call_nodes == 0);
1398 }
1399
1400 /**
1401  * Returns TRUE if the number of callers is smaller size in the irg's environment.
1402  */
1403 INLINE static int is_smaller(ir_graph *callee, int size) {
1404   return (((inline_irg_env *)get_irg_link(callee))->n_nodes < size);
1405 }
1406
1407
1408 /*
1409  * Inlines small leave methods at call sites where the called address comes
1410  * from a Const node that references the entity representing the called
1411  * method.
1412  * The size argument is a rough measure for the code size of the method:
1413  * Methods where the obstack containing the firm graph is smaller than
1414  * size are inlined.
1415  */
1416 void inline_leave_functions(int maxsize, int leavesize, int size) {
1417   inline_irg_env *env;
1418   int i, n_irgs = get_irp_n_irgs();
1419   ir_graph *rem = current_ir_graph;
1420   int did_inline = 1;
1421
1422   if (!(get_opt_optimize() && get_opt_inline())) return;
1423
1424   /* extend all irgs by a temporary data structure for inlining. */
1425   for (i = 0; i < n_irgs; ++i)
1426     set_irg_link(get_irp_irg(i), new_inline_irg_env());
1427
1428   /* Precompute information in temporary data structure. */
1429   for (i = 0; i < n_irgs; ++i) {
1430     current_ir_graph = get_irp_irg(i);
1431     assert(get_irg_phase_state(current_ir_graph) != phase_building);
1432     free_callee_info(current_ir_graph);
1433
1434     irg_walk(get_irg_end(current_ir_graph), NULL, collect_calls2,
1435              get_irg_link(current_ir_graph));
1436   }
1437
1438   /* -- and now inline. -- */
1439
1440   /* Inline leaves recursively -- we might construct new leaves. */
1441   while (did_inline) {
1442     did_inline = 0;
1443
1444     for (i = 0; i < n_irgs; ++i) {
1445       ir_node *call;
1446       int phiproj_computed = 0;
1447
1448       current_ir_graph = get_irp_irg(i);
1449       env = (inline_irg_env *)get_irg_link(current_ir_graph);
1450
1451       for (call = eset_first(env->call_nodes); call; call = eset_next(env->call_nodes)) {
1452         ir_graph *callee;
1453
1454         if (get_irn_op(call) == op_Tuple) continue;   /* We already have inlined this call. */
1455         callee = get_call_called_irg(call);
1456
1457         if (env->n_nodes > maxsize) continue; // break;
1458
1459         if (callee && (is_leave(callee) && is_smaller(callee, leavesize))) {
1460           if (!phiproj_computed) {
1461             phiproj_computed = 1;
1462             collect_phiprojs(current_ir_graph);
1463           }
1464           did_inline = inline_method(call, callee);
1465
1466           if (did_inline) {
1467             /* Do some statistics */
1468             inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1469             env->n_call_nodes --;
1470             env->n_nodes += callee_env->n_nodes;
1471             callee_env->n_callers--;
1472           }
1473         }
1474       }
1475     }
1476   }
1477
1478   /* inline other small functions. */
1479   for (i = 0; i < n_irgs; ++i) {
1480     ir_node *call;
1481     eset *walkset;
1482     int phiproj_computed = 0;
1483
1484     current_ir_graph = get_irp_irg(i);
1485     env = (inline_irg_env *)get_irg_link(current_ir_graph);
1486
1487     /* we can not walk and change a set, nor remove from it.
1488        So recompute.*/
1489     walkset = env->call_nodes;
1490     env->call_nodes = eset_create();
1491     for (call = eset_first(walkset); call; call = eset_next(walkset)) {
1492       ir_graph *callee;
1493
1494       if (get_irn_op(call) == op_Tuple) continue;   /* We already inlined. */
1495       callee = get_call_called_irg(call);
1496
1497       if (callee &&
1498           ((is_smaller(callee, size) && (env->n_nodes < maxsize)) ||    /* small function */
1499            (get_irg_inline_property(callee) == irg_inline_forced))) {
1500         if (!phiproj_computed) {
1501             phiproj_computed = 1;
1502             collect_phiprojs(current_ir_graph);
1503         }
1504         if (inline_method(call, callee)) {
1505           inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1506           env->n_call_nodes--;
1507           eset_insert_all(env->call_nodes, callee_env->call_nodes);  /* @@@ ??? This are the wrong nodes !? Not the copied ones. */
1508           env->n_call_nodes += callee_env->n_call_nodes;
1509           env->n_nodes += callee_env->n_nodes;
1510           callee_env->n_callers--;
1511         }
1512       } else {
1513         eset_insert(env->call_nodes, call);
1514       }
1515     }
1516     eset_destroy(walkset);
1517   }
1518
1519   for (i = 0; i < n_irgs; ++i) {
1520     current_ir_graph = get_irp_irg(i);
1521 #if 0
1522     env = (inline_irg_env *)get_irg_link(current_ir_graph);
1523     if ((env->n_call_nodes_orig != env->n_call_nodes) ||
1524         (env->n_callers_orig != env->n_callers))
1525       printf("Nodes:%3d ->%3d, calls:%3d ->%3d, callers:%3d ->%3d, -- %s\n",
1526              env->n_nodes_orig, env->n_nodes, env->n_call_nodes_orig, env->n_call_nodes,
1527              env->n_callers_orig, env->n_callers,
1528              get_entity_name(get_irg_entity(current_ir_graph)));
1529 #endif
1530     free_inline_irg_env((inline_irg_env *)get_irg_link(current_ir_graph));
1531   }
1532
1533   current_ir_graph = rem;
1534 }
1535
1536 /*******************************************************************/
1537 /*  Code Placement.  Pins all floating nodes to a block where they */
1538 /*  will be executed only if needed.                               */
1539 /*******************************************************************/
1540
1541 /**
1542  * Returns non-zero, is a block is not reachable from Start.
1543  *
1544  * @param block  the block to test
1545  */
1546 static int
1547 is_Block_unreachable(ir_node *block) {
1548   return is_Block_dead(block) || get_Block_dom_depth(block) < 0;
1549 }
1550
1551 /**
1552  * Find the earliest correct block for N.  --- Place N into the
1553  * same Block as its dominance-deepest Input.
1554  *
1555  * We have to avoid calls to get_nodes_block() here
1556  * because the graph is floating.
1557  *
1558  * move_out_of_loops() expects that place_floats_early() have placed
1559  * all "living" nodes into a living block. That's why we must
1560  * move nodes in dead block with "live" successors into a valid
1561  * block.
1562  * We move them just into the same block as it's successor (or
1563  * in case of a Phi into the effective use block). For Phi successors,
1564  * this may still be a dead block, but then there is no real use, as
1565  * the control flow will be dead later.
1566  */
1567 static void
1568 place_floats_early(ir_node *n, pdeq *worklist)
1569 {
1570   int i, irn_arity;
1571
1572   /* we must not run into an infinite loop */
1573   assert(irn_not_visited(n));
1574   mark_irn_visited(n);
1575
1576   /* Place floating nodes. */
1577   if (get_irn_pinned(n) == op_pin_state_floats) {
1578     ir_node *curr_block = get_irn_n(n, -1);
1579     int in_dead_block   = is_Block_unreachable(curr_block);
1580     int depth           = 0;
1581     ir_node *b          = NULL;   /* The block to place this node in */
1582
1583     assert(get_irn_op(n) != op_Block);
1584
1585     if ((get_irn_op(n) == op_Const) ||
1586         (get_irn_op(n) == op_SymConst) ||
1587         (is_Bad(n)) ||
1588         (get_irn_op(n) == op_Unknown)) {
1589       /* These nodes will not be placed by the loop below. */
1590       b = get_irg_start_block(current_ir_graph);
1591       depth = 1;
1592     }
1593
1594     /* find the block for this node. */
1595     irn_arity = get_irn_arity(n);
1596     for (i = 0; i < irn_arity; i++) {
1597       ir_node *pred = get_irn_n(n, i);
1598       ir_node *pred_block;
1599
1600       if ((irn_not_visited(pred))
1601          && (get_irn_pinned(pred) == op_pin_state_floats)) {
1602
1603         /*
1604          * If the current node is NOT in a dead block, but one of its
1605          * predecessors is, we must move the predecessor to a live block.
1606          * Such thing can happen, if global CSE chose a node from a dead block.
1607          * We move it simple to our block.
1608          * Note that neither Phi nor End nodes are floating, so we don't
1609          * need to handle them here.
1610          */
1611         if (! in_dead_block) {
1612           if (get_irn_pinned(pred) == op_pin_state_floats &&
1613               is_Block_unreachable(get_irn_n(pred, -1)))
1614             set_nodes_block(pred, curr_block);
1615         }
1616         place_floats_early(pred, worklist);
1617       }
1618
1619       /*
1620        * A node in the Bad block must stay in the bad block,
1621        * so don't compute a new block for it.
1622        */
1623       if (in_dead_block)
1624         continue;
1625
1626       /* Because all loops contain at least one op_pin_state_pinned node, now all
1627          our inputs are either op_pin_state_pinned or place_early() has already
1628          been finished on them.  We do not have any unfinished inputs!  */
1629       pred_block = get_irn_n(pred, -1);
1630       if ((!is_Block_dead(pred_block)) &&
1631           (get_Block_dom_depth(pred_block) > depth)) {
1632         b = pred_block;
1633         depth = get_Block_dom_depth(pred_block);
1634       }
1635       /* Avoid that the node is placed in the Start block */
1636       if ((depth == 1) && (get_Block_dom_depth(get_irn_n(n, -1)) > 1)) {
1637         b = get_Block_cfg_out(get_irg_start_block(current_ir_graph), 0);
1638         assert(b != get_irg_start_block(current_ir_graph));
1639         depth = 2;
1640       }
1641     }
1642     if (b)
1643       set_nodes_block(n, b);
1644   }
1645
1646   /*
1647    * Add predecessors of non floating nodes and non-floating predecessors
1648    * of floating nodes to worklist and fix their blocks if the are in dead block.
1649    */
1650   irn_arity = get_irn_arity(n);
1651
1652   if (get_irn_op(n) == op_End) {
1653     /*
1654      * Simplest case: End node. Predecessors are keep-alives,
1655      * no need to move out of dead block.
1656      */
1657     for (i = -1; i < irn_arity; ++i) {
1658       ir_node *pred = get_irn_n(n, i);
1659       if (irn_not_visited(pred))
1660         pdeq_putr(worklist, pred);
1661     }
1662   }
1663   else if (is_Block(n)) {
1664     /*
1665      * Blocks: Predecessors are control flow, no need to move
1666      * them out of dead block.
1667      */
1668     for (i = irn_arity - 1; i >= 0; --i) {
1669       ir_node *pred = get_irn_n(n, i);
1670       if (irn_not_visited(pred))
1671         pdeq_putr(worklist, pred);
1672     }
1673   }
1674   else if (is_Phi(n)) {
1675     ir_node *pred;
1676     ir_node *curr_block = get_irn_n(n, -1);
1677     int in_dead_block   = is_Block_unreachable(curr_block);
1678
1679     /*
1680      * Phi nodes: move nodes from dead blocks into the effective use
1681      * of the Phi-input if the Phi is not in a bad block.
1682      */
1683     pred = get_irn_n(n, -1);
1684     if (irn_not_visited(pred))
1685       pdeq_putr(worklist, pred);
1686
1687     for (i = irn_arity - 1; i >= 0; --i) {
1688       ir_node *pred = get_irn_n(n, i);
1689
1690       if (irn_not_visited(pred)) {
1691         if (! in_dead_block &&
1692             get_irn_pinned(pred) == op_pin_state_floats &&
1693             is_Block_unreachable(get_irn_n(pred, -1))) {
1694           set_nodes_block(pred, get_Block_cfgpred_block(curr_block, i));
1695         }
1696         pdeq_putr(worklist, pred);
1697       }
1698     }
1699   }
1700   else {
1701     ir_node *pred;
1702     ir_node *curr_block = get_irn_n(n, -1);
1703     int in_dead_block   = is_Block_unreachable(curr_block);
1704
1705     /*
1706      * All other nodes: move nodes from dead blocks into the same block.
1707      */
1708     pred = get_irn_n(n, -1);
1709     if (irn_not_visited(pred))
1710       pdeq_putr(worklist, pred);
1711
1712     for (i = irn_arity - 1; i >= 0; --i) {
1713       ir_node *pred = get_irn_n(n, i);
1714
1715       if (irn_not_visited(pred)) {
1716         if (! in_dead_block &&
1717             get_irn_pinned(pred) == op_pin_state_floats &&
1718             is_Block_unreachable(get_irn_n(pred, -1))) {
1719           set_nodes_block(pred, curr_block);
1720         }
1721         pdeq_putr(worklist, pred);
1722       }
1723     }
1724   }
1725 }
1726
1727 /**
1728  * Floating nodes form subgraphs that begin at nodes as Const, Load,
1729  * Start, Call and that end at op_pin_state_pinned nodes as Store, Call.  Place_early
1730  * places all floating nodes reachable from its argument through floating
1731  * nodes and adds all beginnings at op_pin_state_pinned nodes to the worklist.
1732  */
1733 static INLINE void place_early(pdeq *worklist) {
1734   assert(worklist);
1735   inc_irg_visited(current_ir_graph);
1736
1737   /* this inits the worklist */
1738   place_floats_early(get_irg_end(current_ir_graph), worklist);
1739
1740   /* Work the content of the worklist. */
1741   while (!pdeq_empty(worklist)) {
1742     ir_node *n = pdeq_getl(worklist);
1743     if (irn_not_visited(n))
1744       place_floats_early(n, worklist);
1745   }
1746
1747   set_irg_outs_inconsistent(current_ir_graph);
1748   set_irg_pinned(current_ir_graph, op_pin_state_pinned);
1749 }
1750
1751 /**
1752  * Compute the deepest common ancestor of block and dca.
1753  */
1754 static ir_node *calc_dca(ir_node *dca, ir_node *block)
1755 {
1756   assert(block);
1757
1758   /* we do not want to place nodes in dead blocks */
1759   if (is_Block_dead(block))
1760     return dca;
1761
1762   /* We found a first legal placement. */
1763   if (!dca) return block;
1764
1765   /* Find a placement that is dominates both, dca and block. */
1766   while (get_Block_dom_depth(block) > get_Block_dom_depth(dca))
1767     block = get_Block_idom(block);
1768
1769   while (get_Block_dom_depth(dca) > get_Block_dom_depth(block)) {
1770     dca = get_Block_idom(dca);
1771   }
1772
1773   while (block != dca)
1774     { block = get_Block_idom(block); dca = get_Block_idom(dca); }
1775
1776   return dca;
1777 }
1778
1779 /** Deepest common dominance ancestor of DCA and CONSUMER of PRODUCER.
1780  * I.e., DCA is the block where we might place PRODUCER.
1781  * A data flow edge points from producer to consumer.
1782  */
1783 static ir_node *
1784 consumer_dom_dca(ir_node *dca, ir_node *consumer, ir_node *producer)
1785 {
1786   ir_node *block = NULL;
1787
1788   /* Compute the latest block into which we can place a node so that it is
1789      before consumer. */
1790   if (get_irn_op(consumer) == op_Phi) {
1791     /* our consumer is a Phi-node, the effective use is in all those
1792        blocks through which the Phi-node reaches producer */
1793     int i, irn_arity;
1794     ir_node *phi_block = get_nodes_block(consumer);
1795     irn_arity = get_irn_arity(consumer);
1796
1797     for (i = 0;  i < irn_arity; i++) {
1798       if (get_irn_n(consumer, i) == producer) {
1799         ir_node *new_block = get_nodes_block(get_Block_cfgpred(phi_block, i));
1800
1801         if (! is_Block_unreachable(new_block))
1802           block = calc_dca(block, new_block);
1803       }
1804     }
1805
1806     if (! block)
1807       block = get_irn_n(producer, -1);
1808   }
1809   else {
1810     assert(is_no_Block(consumer));
1811     block = get_nodes_block(consumer);
1812   }
1813
1814   /* Compute the deepest common ancestor of block and dca. */
1815   return calc_dca(dca, block);
1816 }
1817
1818 /* FIXME: the name clashes here with the function from ana/field_temperature.c
1819  * please rename. */
1820 static INLINE int get_irn_loop_depth(ir_node *n) {
1821   return get_loop_depth(get_irn_loop(n));
1822 }
1823
1824 /**
1825  * Move n to a block with less loop depth than it's current block. The
1826  * new block must be dominated by early.
1827  *
1828  * @param n      the node that should be moved
1829  * @param early  the earliest block we can n move to
1830  */
1831 static void
1832 move_out_of_loops (ir_node *n, ir_node *early)
1833 {
1834   ir_node *best, *dca;
1835   assert(n && early);
1836
1837
1838   /* Find the region deepest in the dominator tree dominating
1839      dca with the least loop nesting depth, but still dominated
1840      by our early placement. */
1841   dca = get_nodes_block(n);
1842
1843   best = dca;
1844   while (dca != early) {
1845     dca = get_Block_idom(dca);
1846     if (!dca || is_Bad(dca)) break; /* may be Bad if not reachable from Start */
1847     if (get_irn_loop_depth(dca) < get_irn_loop_depth(best)) {
1848       best = dca;
1849     }
1850   }
1851   if (best != get_nodes_block(n)) {
1852     /* debug output
1853     printf("Moving out of loop: "); DDMN(n);
1854     printf(" Outermost block: "); DDMN(early);
1855     printf(" Best block: "); DDMN(best);
1856     printf(" Innermost block: "); DDMN(get_nodes_block(n));
1857     */
1858     set_nodes_block(n, best);
1859   }
1860 }
1861
1862 /**
1863  * Find the latest legal block for N and place N into the
1864  * `optimal' Block between the latest and earliest legal block.
1865  * The `optimal' block is the dominance-deepest block of those
1866  * with the least loop-nesting-depth.  This places N out of as many
1867  * loops as possible and then makes it as control dependent as
1868  * possible.
1869  */
1870 static void
1871 place_floats_late(ir_node *n, pdeq *worklist)
1872 {
1873   int i;
1874   ir_node *early_blk;
1875
1876   assert(irn_not_visited(n)); /* no multiple placement */
1877
1878   mark_irn_visited(n);
1879
1880   /* no need to place block nodes, control nodes are already placed. */
1881   if ((get_irn_op(n) != op_Block) &&
1882       (!is_cfop(n)) &&
1883       (get_irn_mode(n) != mode_X)) {
1884     /* Remember the early_blk placement of this block to move it
1885        out of loop no further than the early_blk placement. */
1886     early_blk = get_irn_n(n, -1);
1887
1888     /*
1889      * BEWARE: Here we also get code, that is live, but
1890      * was in a dead block.  If the node is life, but because
1891      * of CSE in a dead block, we still might need it.
1892      */
1893
1894     /* Assure that our users are all placed, except the Phi-nodes.
1895        --- Each data flow cycle contains at least one Phi-node.  We
1896        have to break the `user has to be placed before the
1897        producer' dependence cycle and the Phi-nodes are the
1898        place to do so, because we need to base our placement on the
1899        final region of our users, which is OK with Phi-nodes, as they
1900        are op_pin_state_pinned, and they never have to be placed after a
1901        producer of one of their inputs in the same block anyway. */
1902     for (i = get_irn_n_outs(n) - 1; i >= 0; --i) {
1903       ir_node *succ = get_irn_out(n, i);
1904       if (irn_not_visited(succ) && (get_irn_op(succ) != op_Phi))
1905         place_floats_late(succ, worklist);
1906     }
1907
1908     if (! is_Block_dead(early_blk)) {
1909       /* do only move things that where not dead */
1910
1911       /* We have to determine the final block of this node... except for
1912          constants. */
1913       if ((get_irn_pinned(n) == op_pin_state_floats) &&
1914           (get_irn_op(n) != op_Const) &&
1915           (get_irn_op(n) != op_SymConst)) {
1916         ir_node *dca = NULL;  /* deepest common ancestor in the
1917                      dominator tree of all nodes'
1918                      blocks depending on us; our final
1919                      placement has to dominate DCA. */
1920         for (i = get_irn_n_outs(n) - 1; i >= 0; --i) {
1921           ir_node *succ = get_irn_out(n, i);
1922           ir_node *succ_blk;
1923
1924           if (get_irn_op(succ) == op_End) {
1925             /*
1926              * This consumer is the End node, a keep alive edge.
1927              * This is not a real consumer, so we ignore it
1928              */
1929             continue;
1930           }
1931
1932           /* ignore if succ is in dead code */
1933           succ_blk = get_irn_n(succ, -1);
1934           if (is_Block_unreachable(succ_blk))
1935             continue;
1936           dca = consumer_dom_dca(dca, succ, n);
1937         }
1938         if (dca) {
1939           set_nodes_block(n, dca);
1940           move_out_of_loops(n, early_blk);
1941         }
1942       }
1943     }
1944   }
1945
1946   /* Add predecessors of all non-floating nodes on list. (Those of floating
1947      nodes are placed already and therefore are marked.)  */
1948   for (i = 0; i < get_irn_n_outs(n); i++) {
1949     ir_node *succ = get_irn_out(n, i);
1950     if (irn_not_visited(get_irn_out(n, i))) {
1951       pdeq_putr(worklist, succ);
1952     }
1953   }
1954 }
1955
1956 static INLINE void place_late(pdeq *worklist) {
1957   assert(worklist);
1958   inc_irg_visited(current_ir_graph);
1959
1960   /* This fills the worklist initially. */
1961   place_floats_late(get_irg_start_block(current_ir_graph), worklist);
1962
1963   /* And now empty the worklist again... */
1964   while (!pdeq_empty(worklist)) {
1965     ir_node *n = pdeq_getl(worklist);
1966     if (irn_not_visited(n))
1967       place_floats_late(n, worklist);
1968   }
1969 }
1970
1971 void place_code(ir_graph *irg) {
1972   pdeq *worklist;
1973   ir_graph *rem = current_ir_graph;
1974
1975   current_ir_graph = irg;
1976
1977   if (!(get_opt_optimize() && get_opt_global_cse())) return;
1978
1979   /* Handle graph state */
1980   assert(get_irg_phase_state(irg) != phase_building);
1981   if (get_irg_dom_state(irg) != dom_consistent)
1982     compute_doms(irg);
1983
1984   if (1 || get_irg_loopinfo_state(irg) != loopinfo_consistent) {
1985     free_loop_information(irg);
1986     construct_backedges(irg);
1987   }
1988
1989   /* Place all floating nodes as early as possible. This guarantees
1990      a legal code placement. */
1991   worklist = new_pdeq();
1992   place_early(worklist);
1993
1994   /* place_early() invalidates the outs, place_late needs them. */
1995   compute_irg_outs(irg);
1996
1997   /* Now move the nodes down in the dominator tree. This reduces the
1998      unnecessary executions of the node. */
1999   place_late(worklist);
2000
2001   set_irg_outs_inconsistent(current_ir_graph);
2002   set_irg_loopinfo_inconsistent(current_ir_graph);
2003   del_pdeq(worklist);
2004   current_ir_graph = rem;
2005 }
2006
2007 /**
2008  * Called by walker of remove_critical_cf_edges().
2009  *
2010  * Place an empty block to an edge between a blocks of multiple
2011  * predecessors and a block of multiple successors.
2012  *
2013  * @param n   IR node
2014  * @param env Environment of walker. The changed field.
2015  */
2016 static void walk_critical_cf_edges(ir_node *n, void *env) {
2017   int arity, i;
2018   ir_node *pre, *block, *jmp;
2019   int *changed = env;
2020
2021   /* Block has multiple predecessors */
2022   if (is_Block(n) && (get_irn_arity(n) > 1)) {
2023     if (n == get_irg_end_block(current_ir_graph))
2024       return;  /*  No use to add a block here.      */
2025
2026     arity = get_irn_arity(n);
2027     for (i=0; i<arity; i++) {
2028       pre = get_irn_n(n, i);
2029       /* Predecessor has multiple successors. Insert new control flow edge. */
2030       if (op_Raise != get_irn_op(skip_Proj(pre))) {
2031         /* set predecessor of new block */
2032         block = new_Block(1, &pre);
2033         /* insert new jmp node to new block */
2034         set_cur_block(block);
2035         jmp = new_Jmp();
2036         set_cur_block(n);
2037         /* set successor of new block */
2038         set_irn_n(n, i, jmp);
2039         *changed = 1;
2040       } /* predecessor has multiple successors */
2041     } /* for all predecessors */
2042   } /* n is a block */
2043 }
2044
2045 void remove_critical_cf_edges(ir_graph *irg) {
2046   int changed = 0;
2047   irg_walk_graph(irg, NULL, walk_critical_cf_edges, &changed);
2048
2049   if (changed) {
2050     /* control flow changed */
2051     set_irg_outs_inconsistent(irg);
2052     set_irg_extblk_inconsistent(irg);
2053     set_irg_doms_inconsistent(current_ir_graph);
2054     set_irg_loopinfo_inconsistent(current_ir_graph);
2055   }
2056
2057 }