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