BugFix:
[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 /**
870  * Check if the varlue_arg_base is used.
871  */
872 static void find_addr(ir_node *node, void *env) {
873   if (is_Proj(node) && get_irn_op(get_Proj_pred(node)) == op_Start) {
874     if (get_Proj_proj(node) == pn_Start_P_value_arg_base)
875       *(int *)env = 0;
876   }
877 }
878
879 /*
880  * currently, we cannot inline two cases:
881  * - call with compound arguments
882  * - graphs that take the address of a parameter
883  *
884  * check these conditions here
885  */
886 static int can_inline(ir_node *call, ir_graph *called_graph)
887 {
888   ir_type *call_type = get_Call_type(call);
889   int params, ress, i, res;
890   assert(is_Method_type(call_type));
891
892   params = get_method_n_params(call_type);
893   ress   = get_method_n_ress(call_type);
894
895   /* check params */
896   for (i = 0; i < params; ++i) {
897     ir_type *p_type = get_method_param_type(call_type, i);
898
899     if (is_compound_type(p_type))
900       return 0;
901   }
902
903   /* check res */
904   for (i = 0; i < ress; ++i) {
905     ir_type *r_type = get_method_res_type(call_type, i);
906
907     if (is_compound_type(r_type))
908       return 0;
909   }
910
911   res = 1;
912   irg_walk_graph(called_graph, find_addr, NULL, &res);
913
914   return res;
915 }
916
917 int inline_method(ir_node *call, ir_graph *called_graph) {
918   ir_node *pre_call;
919   ir_node *post_call, *post_bl;
920   ir_node *in[pn_Start_max];
921   ir_node *end, *end_bl;
922   ir_node **res_pred;
923   ir_node **cf_pred;
924   ir_node *ret, *phi;
925   int arity, n_ret, n_exc, n_res, i, j, rem_opt, irn_arity;
926   int exc_handling;
927   ir_type *called_frame;
928   irg_inline_property prop = get_irg_inline_property(called_graph);
929
930   if ( (prop < irg_inline_forced) &&
931        (!get_opt_optimize() || !get_opt_inline() || (prop == irg_inline_forbidden))) return 0;
932
933   /* Do not inline variadic functions. */
934   if (get_method_variadicity(get_entity_type(get_irg_entity(called_graph))) == variadicity_variadic)
935     return 0;
936
937   assert(get_method_n_params(get_entity_type(get_irg_entity(called_graph))) ==
938          get_method_n_params(get_Call_type(call)));
939
940   /*
941    * currently, we cannot inline two cases:
942    * - call with compound arguments
943    * - graphs that take the address of a parameter
944    */
945   if (! can_inline(call, called_graph))
946     return 0;
947
948   /* --  Turn off optimizations, this can cause problems when allocating new nodes. -- */
949   rem_opt = get_opt_optimize();
950   set_optimize(0);
951
952   /* Handle graph state */
953   assert(get_irg_phase_state(current_ir_graph) != phase_building);
954   assert(get_irg_pinned(current_ir_graph) == op_pin_state_pinned);
955   assert(get_irg_pinned(called_graph) == op_pin_state_pinned);
956   set_irg_outs_inconsistent(current_ir_graph);
957   set_irg_extblk_inconsistent(current_ir_graph);
958   set_irg_doms_inconsistent(current_ir_graph);
959   set_irg_loopinfo_inconsistent(current_ir_graph);
960   set_irg_callee_info_state(current_ir_graph, irg_callee_info_inconsistent);
961
962   /* -- Check preconditions -- */
963   assert(is_Call(call));
964   /* @@@ does not work for InterfaceIII.java after cgana
965      assert(get_Call_type(call) == get_entity_type(get_irg_entity(called_graph)));
966      assert(smaller_type(get_entity_type(get_irg_entity(called_graph)),
967      get_Call_type(call)));
968   */
969   if (called_graph == current_ir_graph) {
970     set_optimize(rem_opt);
971     return 0;
972   }
973
974   /* here we know we WILL inline, so inform the statistics */
975   hook_inline(call, called_graph);
976
977   /* -- Decide how to handle exception control flow: Is there a handler
978      for the Call node, or do we branch directly to End on an exception?
979      exc_handling:
980      0 There is a handler.
981      1 Branches to End.
982      2 Exception handling not represented in Firm. -- */
983   {
984     ir_node *proj, *Mproj = NULL, *Xproj = NULL;
985     for (proj = get_irn_link(call); proj; proj = get_irn_link(proj)) {
986       assert(is_Proj(proj));
987       if (get_Proj_proj(proj) == pn_Call_X_except) Xproj = proj;
988       if (get_Proj_proj(proj) == pn_Call_M_except) Mproj = proj;
989     }
990     if      (Mproj) { assert(Xproj); exc_handling = 0; } /*  Mproj           */
991     else if (Xproj) {                exc_handling = 1; } /* !Mproj &&  Xproj   */
992     else            {                exc_handling = 2; } /* !Mproj && !Xproj   */
993   }
994
995
996   /* --
997      the procedure and later replaces the Start node of the called graph.
998      Post_call is the old Call node and collects the results of the called
999      graph. Both will end up being a tuple.  -- */
1000   post_bl = get_nodes_block(call);
1001   set_irg_current_block(current_ir_graph, post_bl);
1002   /* XxMxPxPxPxT of Start + parameter of Call */
1003   in[pn_Start_X_initial_exec]   = new_Jmp();
1004   in[pn_Start_M]                = get_Call_mem(call);
1005   in[pn_Start_P_frame_base]     = get_irg_frame(current_ir_graph);
1006   in[pn_Start_P_globals]        = get_irg_globals(current_ir_graph);
1007   in[pn_Start_P_tls]            = get_irg_tls(current_ir_graph);
1008   in[pn_Start_T_args]           = new_Tuple(get_Call_n_params(call), get_Call_param_arr(call));
1009   /* in[pn_Start_P_value_arg_base] = ??? */
1010   assert(pn_Start_P_value_arg_base == pn_Start_max - 1 && "pn_Start_P_value_arg_base not supported, fix");
1011   pre_call = new_Tuple(pn_Start_max - 1, in);
1012   post_call = call;
1013
1014   /* --
1015      The new block gets the ins of the old block, pre_call and all its
1016      predecessors and all Phi nodes. -- */
1017   part_block(pre_call);
1018
1019   /* -- Prepare state for dead node elimination -- */
1020   /* Visited flags in calling irg must be >= flag in called irg.
1021      Else walker and arity computation will not work. */
1022   if (get_irg_visited(current_ir_graph) <= get_irg_visited(called_graph))
1023     set_irg_visited(current_ir_graph, get_irg_visited(called_graph)+1);
1024   if (get_irg_block_visited(current_ir_graph)< get_irg_block_visited(called_graph))
1025     set_irg_block_visited(current_ir_graph, get_irg_block_visited(called_graph));
1026   /* Set pre_call as new Start node in link field of the start node of
1027      calling graph and pre_calls block as new block for the start block
1028      of calling graph.
1029      Further mark these nodes so that they are not visited by the
1030      copying. */
1031   set_irn_link(get_irg_start(called_graph), pre_call);
1032   set_irn_visited(get_irg_start(called_graph), get_irg_visited(current_ir_graph));
1033   set_irn_link(get_irg_start_block(called_graph), get_nodes_block(pre_call));
1034   set_irn_visited(get_irg_start_block(called_graph), get_irg_visited(current_ir_graph));
1035   set_irn_link(get_irg_bad(called_graph), get_irg_bad(current_ir_graph));
1036   set_irn_visited(get_irg_bad(called_graph), get_irg_visited(current_ir_graph));
1037
1038   /* Initialize for compaction of in arrays */
1039   inc_irg_block_visited(current_ir_graph);
1040
1041   /* -- Replicate local entities of the called_graph -- */
1042   /* copy the entities. */
1043   called_frame = get_irg_frame_type(called_graph);
1044   for (i = 0; i < get_class_n_members(called_frame); i++) {
1045     entity *new_ent, *old_ent;
1046     old_ent = get_class_member(called_frame, i);
1047     new_ent = copy_entity_own(old_ent, get_cur_frame_type());
1048     set_entity_link(old_ent, new_ent);
1049   }
1050
1051   /* visited is > than that of called graph.  With this trick visited will
1052      remain unchanged so that an outer walker, e.g., searching the call nodes
1053      to inline, calling this inline will not visit the inlined nodes. */
1054   set_irg_visited(current_ir_graph, get_irg_visited(current_ir_graph)-1);
1055
1056   /* -- Performing dead node elimination inlines the graph -- */
1057   /* Copies the nodes to the obstack of current_ir_graph. Updates links to new
1058      entities. */
1059   /* @@@ endless loops are not copied!! -- they should be, I think... */
1060   irg_walk(get_irg_end(called_graph), copy_node_inline, copy_preds,
1061            get_irg_frame_type(called_graph));
1062
1063   /* Repair called_graph */
1064   set_irg_visited(called_graph, get_irg_visited(current_ir_graph));
1065   set_irg_block_visited(called_graph, get_irg_block_visited(current_ir_graph));
1066   set_Block_block_visited(get_irg_start_block(called_graph), 0);
1067
1068   /* -- Merge the end of the inlined procedure with the call site -- */
1069   /* We will turn the old Call node into a Tuple with the following
1070      predecessors:
1071      -1:  Block of Tuple.
1072      0: Phi of all Memories of Return statements.
1073      1: Jmp from new Block that merges the control flow from all exception
1074      predecessors of the old end block.
1075      2: Tuple of all arguments.
1076      3: Phi of Exception memories.
1077      In case the old Call directly branches to End on an exception we don't
1078      need the block merging all exceptions nor the Phi of the exception
1079      memories.
1080   */
1081
1082   /* -- Precompute some values -- */
1083   end_bl = get_new_node(get_irg_end_block(called_graph));
1084   end = get_new_node(get_irg_end(called_graph));
1085   arity = get_irn_arity(end_bl);    /* arity = n_exc + n_ret  */
1086   n_res = get_method_n_ress(get_Call_type(call));
1087
1088   res_pred = xmalloc (n_res * sizeof(*res_pred));
1089   cf_pred  = xmalloc (arity * sizeof(*res_pred));
1090
1091   set_irg_current_block(current_ir_graph, post_bl); /* just to make sure */
1092
1093   /* -- archive keepalives -- */
1094   irn_arity = get_irn_arity(end);
1095   for (i = 0; i < irn_arity; i++)
1096     add_End_keepalive(get_irg_end(current_ir_graph), get_irn_n(end, i));
1097
1098   /* The new end node will die.  We need not free as the in array is on the obstack:
1099      copy_node() only generated 'D' arrays. */
1100
1101   /* -- Replace Return nodes by Jump nodes. -- */
1102   n_ret = 0;
1103   for (i = 0; i < arity; i++) {
1104     ir_node *ret;
1105     ret = get_irn_n(end_bl, i);
1106     if (is_Return(ret)) {
1107       cf_pred[n_ret] = new_r_Jmp(current_ir_graph, get_nodes_block(ret));
1108       n_ret++;
1109     }
1110   }
1111   set_irn_in(post_bl, n_ret, cf_pred);
1112
1113   /* -- Build a Tuple for all results of the method.
1114      Add Phi node if there was more than one Return.  -- */
1115   turn_into_tuple(post_call, 4);
1116   /* First the Memory-Phi */
1117   n_ret = 0;
1118   for (i = 0; i < arity; i++) {
1119     ret = get_irn_n(end_bl, i);
1120     if (is_Return(ret)) {
1121       cf_pred[n_ret] = get_Return_mem(ret);
1122       n_ret++;
1123     }
1124   }
1125   phi = new_Phi(n_ret, cf_pred, mode_M);
1126   set_Tuple_pred(call, pn_Call_M_regular, phi);
1127   /* Conserve Phi-list for further inlinings -- but might be optimized */
1128   if (get_nodes_block(phi) == post_bl) {
1129     set_irn_link(phi, get_irn_link(post_bl));
1130     set_irn_link(post_bl, phi);
1131   }
1132   /* Now the real results */
1133   if (n_res > 0) {
1134     for (j = 0; j < n_res; j++) {
1135       n_ret = 0;
1136       for (i = 0; i < arity; i++) {
1137         ret = get_irn_n(end_bl, i);
1138         if (get_irn_op(ret) == op_Return) {
1139           cf_pred[n_ret] = get_Return_res(ret, j);
1140           n_ret++;
1141         }
1142       }
1143       if (n_ret > 0)
1144         phi = new_Phi(n_ret, cf_pred, get_irn_mode(cf_pred[0]));
1145       else
1146         phi = new_Bad();
1147       res_pred[j] = phi;
1148       /* Conserve Phi-list for further inlinings -- but might be optimized */
1149       if (get_nodes_block(phi) == post_bl) {
1150         set_irn_link(phi, get_irn_link(post_bl));
1151         set_irn_link(post_bl, phi);
1152       }
1153     }
1154     set_Tuple_pred(call, pn_Call_T_result, new_Tuple(n_res, res_pred));
1155   } else {
1156     set_Tuple_pred(call, pn_Call_T_result, new_Bad());
1157   }
1158   /* Finally the exception control flow.
1159      We have two (three) possible situations:
1160      First if the Call branches to an exception handler: We need to add a Phi node to
1161      collect the memory containing the exception objects.  Further we need
1162      to add another block to get a correct representation of this Phi.  To
1163      this block we add a Jmp that resolves into the X output of the Call
1164      when the Call is turned into a tuple.
1165      Second the Call branches to End, the exception is not handled.  Just
1166      add all inlined exception branches to the End node.
1167      Third: there is no Exception edge at all. Handle as case two. */
1168   if (exc_handling == 0) {
1169     n_exc = 0;
1170     for (i = 0; i < arity; i++) {
1171       ir_node *ret;
1172       ret = get_irn_n(end_bl, i);
1173       if (is_fragile_op(skip_Proj(ret)) || (get_irn_op(skip_Proj(ret)) == op_Raise)) {
1174         cf_pred[n_exc] = ret;
1175         n_exc++;
1176       }
1177     }
1178     if (n_exc > 0) {
1179       new_Block(n_exc, cf_pred);      /* watch it: current_block is changed! */
1180       set_Tuple_pred(call, pn_Call_X_except, new_Jmp());
1181       /* The Phi for the memories with the exception objects */
1182       n_exc = 0;
1183       for (i = 0; i < arity; i++) {
1184         ir_node *ret;
1185         ret = skip_Proj(get_irn_n(end_bl, i));
1186         if (is_Call(ret)) {
1187           cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 3);
1188           n_exc++;
1189         } else if (is_fragile_op(ret)) {
1190           /* We rely that all cfops have the memory output at the same position. */
1191           cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 0);
1192           n_exc++;
1193         } else if (get_irn_op(ret) == op_Raise) {
1194           cf_pred[n_exc] = new_r_Proj(current_ir_graph, get_nodes_block(ret), ret, mode_M, 1);
1195           n_exc++;
1196         }
1197       }
1198       set_Tuple_pred(call, pn_Call_M_except, new_Phi(n_exc, cf_pred, mode_M));
1199     } else {
1200       set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1201       set_Tuple_pred(call, pn_Call_M_except, new_Bad());
1202     }
1203   } else {
1204     ir_node *main_end_bl;
1205     int main_end_bl_arity;
1206     ir_node **end_preds;
1207
1208     /* assert(exc_handling == 1 || no exceptions. ) */
1209     n_exc = 0;
1210     for (i = 0; i < arity; i++) {
1211       ir_node *ret = get_irn_n(end_bl, i);
1212
1213       if (is_fragile_op(skip_Proj(ret)) || (get_irn_op(skip_Proj(ret)) == op_Raise)) {
1214         cf_pred[n_exc] = ret;
1215         n_exc++;
1216       }
1217     }
1218     main_end_bl = get_irg_end_block(current_ir_graph);
1219     main_end_bl_arity = get_irn_arity(main_end_bl);
1220     end_preds =  xmalloc ((n_exc + main_end_bl_arity) * sizeof(*end_preds));
1221
1222     for (i = 0; i < main_end_bl_arity; ++i)
1223       end_preds[i] = get_irn_n(main_end_bl, i);
1224     for (i = 0; i < n_exc; ++i)
1225       end_preds[main_end_bl_arity + i] = cf_pred[i];
1226     set_irn_in(main_end_bl, n_exc + main_end_bl_arity, end_preds);
1227     set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1228     set_Tuple_pred(call, pn_Call_M_except, new_Bad());
1229     free(end_preds);
1230   }
1231   free(res_pred);
1232   free(cf_pred);
1233
1234 #if 0  /* old. now better, correcter, faster implementation. */
1235   if (n_exc > 0) {
1236     /* -- If the exception control flow from the inlined Call directly
1237        branched to the end block we now have the following control
1238        flow predecessor pattern: ProjX -> Tuple -> Jmp.  We must
1239        remove the Jmp along with it's empty block and add Jmp's
1240        predecessors as predecessors of this end block.  No problem if
1241        there is no exception, because then branches Bad to End which
1242        is fine. --
1243        @@@ can't we know this beforehand: by getting the Proj(1) from
1244        the Call link list and checking whether it goes to Proj. */
1245     /* find the problematic predecessor of the end block. */
1246     end_bl = get_irg_end_block(current_ir_graph);
1247     for (i = 0; i < get_Block_n_cfgpreds(end_bl); i++) {
1248       cf_op = get_Block_cfgpred(end_bl, i);
1249       if (get_irn_op(cf_op) == op_Proj) {
1250         cf_op = get_Proj_pred(cf_op);
1251         if ((get_irn_op(cf_op) == op_Tuple) && (cf_op == call)) {
1252           /*  There are unoptimized tuples from inlineing before when no exc */
1253           assert(get_Proj_proj(get_Block_cfgpred(end_bl, i)) == pn_Call_X_except);
1254           cf_op = get_Tuple_pred(cf_op, pn_Call_X_except);
1255           assert(get_irn_op(cf_op) == op_Jmp);
1256           break;
1257         }
1258       }
1259     }
1260     /* repair */
1261     if (i < get_Block_n_cfgpreds(end_bl)) {
1262       bl = get_nodes_block(cf_op);
1263       arity = get_Block_n_cfgpreds(end_bl) + get_Block_n_cfgpreds(bl) - 1;
1264       cf_pred = xmalloc (arity * sizeof(*cf_pred));
1265       for (j = 0; j < i; j++)
1266         cf_pred[j] = get_Block_cfgpred(end_bl, j);
1267       for (j = j; j < i + get_Block_n_cfgpreds(bl); j++)
1268         cf_pred[j] = get_Block_cfgpred(bl, j-i);
1269       for (j = j; j < arity; j++)
1270         cf_pred[j] = get_Block_cfgpred(end_bl, j-get_Block_n_cfgpreds(bl) +1);
1271       set_irn_in(end_bl, arity, cf_pred);
1272       free(cf_pred);
1273       /*  Remove the exception pred from post-call Tuple. */
1274       set_Tuple_pred(call, pn_Call_X_except, new_Bad());
1275     }
1276   }
1277 #endif
1278
1279   /* --  Turn CSE back on. -- */
1280   set_optimize(rem_opt);
1281
1282   return 1;
1283 }
1284
1285 /********************************************************************/
1286 /* Apply inlineing to small methods.                                */
1287 /********************************************************************/
1288
1289 /* It makes no sense to inline too many calls in one procedure. Anyways,
1290    I didn't get a version with NEW_ARR_F to run. */
1291 #define MAX_INLINE 1024
1292
1293 /**
1294  * environment for inlining small irgs
1295  */
1296 typedef struct _inline_env_t {
1297   int pos;
1298   ir_node *calls[MAX_INLINE];
1299 } inline_env_t;
1300
1301 /**
1302  * Returns the irg called from a Call node. If the irg is not
1303  * known, NULL is returned.
1304  */
1305 static ir_graph *get_call_called_irg(ir_node *call) {
1306   ir_node *addr;
1307   ir_graph *called_irg = NULL;
1308
1309   assert(is_Call(call));
1310
1311   addr = get_Call_ptr(call);
1312   if ((get_irn_op(addr) == op_SymConst) && (get_SymConst_kind (addr) == symconst_addr_ent)) {
1313     called_irg = get_entity_irg(get_SymConst_entity(addr));
1314   }
1315
1316   return called_irg;
1317 }
1318
1319 static void collect_calls(ir_node *call, void *env) {
1320   ir_node *addr;
1321
1322   if (! is_Call(call)) return;
1323
1324   addr = get_Call_ptr(call);
1325
1326   if (get_irn_op(addr) == op_SymConst) {
1327     if (get_SymConst_kind(addr) == symconst_addr_ent) {
1328       ir_graph *called_irg = get_entity_irg(get_SymConst_entity(addr));
1329       inline_env_t *ienv = (inline_env_t *)env;
1330       if (called_irg && ienv->pos < MAX_INLINE) {
1331         /* The Call node calls a locally defined method.  Remember to inline. */
1332         ienv->calls[ienv->pos++] = call;
1333       }
1334     }
1335   }
1336 }
1337
1338 /**
1339  * Inlines all small methods at call sites where the called address comes
1340  * from a Const node that references the entity representing the called
1341  * method.
1342  * The size argument is a rough measure for the code size of the method:
1343  * Methods where the obstack containing the firm graph is smaller than
1344  * size are inlined.
1345  */
1346 void inline_small_irgs(ir_graph *irg, int size) {
1347   int i;
1348   ir_graph *rem = current_ir_graph;
1349   inline_env_t env /* = {0, NULL}*/;
1350
1351   if (!(get_opt_optimize() && get_opt_inline())) return;
1352
1353   current_ir_graph = irg;
1354   /* Handle graph state */
1355   assert(get_irg_phase_state(current_ir_graph) != phase_building);
1356   free_callee_info(current_ir_graph);
1357
1358   /* Find Call nodes to inline.
1359      (We can not inline during a walk of the graph, as inlineing the same
1360      method several times changes the visited flag of the walked graph:
1361      after the first inlineing visited of the callee equals visited of
1362      the caller.  With the next inlineing both are increased.) */
1363   env.pos = 0;
1364   irg_walk(get_irg_end(irg), NULL, collect_calls, &env);
1365
1366   if ((env.pos > 0) && (env.pos < MAX_INLINE)) {
1367     /* There are calls to inline */
1368     collect_phiprojs(irg);
1369     for (i = 0; i < env.pos; i++) {
1370       ir_graph *callee;
1371       callee = get_entity_irg(get_SymConst_entity(get_Call_ptr(env.calls[i])));
1372       if (((_obstack_memory_used(callee->obst) - (int)obstack_room(callee->obst)) < size) ||
1373         (get_irg_inline_property(callee) >= irg_inline_forced)) {
1374         inline_method(env.calls[i], callee);
1375       }
1376     }
1377   }
1378
1379   current_ir_graph = rem;
1380 }
1381
1382 /**
1383  * Environment for inlining irgs.
1384  */
1385 typedef struct {
1386   int n_nodes;       /**< Nodes in graph except Id, Tuple, Proj, Start, End */
1387   int n_nodes_orig;  /**< for statistics */
1388   eset *call_nodes;  /**< All call nodes in this graph */
1389   int n_call_nodes;
1390   int n_call_nodes_orig; /**< for statistics */
1391   int n_callers;   /**< Number of known graphs that call this graphs. */
1392   int n_callers_orig; /**< for statistics */
1393 } inline_irg_env;
1394
1395 /**
1396  * Allocate a new environment for inlining.
1397  */
1398 static inline_irg_env *new_inline_irg_env(void) {
1399   inline_irg_env *env    = xmalloc(sizeof(*env));
1400   env->n_nodes           = -2; /* do not count count Start, End */
1401   env->n_nodes_orig      = -2; /* do not count Start, End */
1402   env->call_nodes        = eset_create();
1403   env->n_call_nodes      = 0;
1404   env->n_call_nodes_orig = 0;
1405   env->n_callers         = 0;
1406   env->n_callers_orig    = 0;
1407   return env;
1408 }
1409
1410 /**
1411  * destroy an environment for inlining.
1412  */
1413 static void free_inline_irg_env(inline_irg_env *env) {
1414   eset_destroy(env->call_nodes);
1415   free(env);
1416 }
1417
1418 /**
1419  * post-walker: collect all calls in the inline-environment
1420  * of a graph and sum some statistics.
1421  */
1422 static void collect_calls2(ir_node *call, void *env) {
1423   inline_irg_env *x = (inline_irg_env *)env;
1424   ir_op *op = get_irn_op(call);
1425   ir_graph *callee;
1426
1427   /* count meaningful nodes in irg */
1428   if (op != op_Proj && op != op_Tuple && op != op_Sync) {
1429     x->n_nodes++;
1430     x->n_nodes_orig++;
1431   }
1432
1433   if (op != op_Call) return;
1434
1435   /* collect all call nodes */
1436   eset_insert(x->call_nodes, call);
1437   x->n_call_nodes++;
1438   x->n_call_nodes_orig++;
1439
1440   /* count all static callers */
1441   callee = get_call_called_irg(call);
1442   if (callee) {
1443     inline_irg_env *callee_env = get_irg_link(callee);
1444     callee_env->n_callers++;
1445     callee_env->n_callers_orig++;
1446   }
1447 }
1448
1449 /**
1450  * Returns TRUE if the number of callers in 0 in the irg's environment,
1451  * hence this irg is a leave.
1452  */
1453 INLINE static int is_leave(ir_graph *irg) {
1454   return (((inline_irg_env *)get_irg_link(irg))->n_call_nodes == 0);
1455 }
1456
1457 /**
1458  * Returns TRUE if the number of callers is smaller size in the irg's environment.
1459  */
1460 INLINE static int is_smaller(ir_graph *callee, int size) {
1461   return (((inline_irg_env *)get_irg_link(callee))->n_nodes < size);
1462 }
1463
1464
1465 /*
1466  * Inlines small leave methods at call sites where the called address comes
1467  * from a Const node that references the entity representing the called
1468  * method.
1469  * The size argument is a rough measure for the code size of the method:
1470  * Methods where the obstack containing the firm graph is smaller than
1471  * size are inlined.
1472  */
1473 void inline_leave_functions(int maxsize, int leavesize, int size) {
1474   inline_irg_env *env;
1475   int i, n_irgs = get_irp_n_irgs();
1476   ir_graph *rem = current_ir_graph;
1477   int did_inline = 1;
1478
1479   if (!(get_opt_optimize() && get_opt_inline())) return;
1480
1481   /* extend all irgs by a temporary data structure for inlining. */
1482   for (i = 0; i < n_irgs; ++i)
1483     set_irg_link(get_irp_irg(i), new_inline_irg_env());
1484
1485   /* Precompute information in temporary data structure. */
1486   for (i = 0; i < n_irgs; ++i) {
1487     current_ir_graph = get_irp_irg(i);
1488     assert(get_irg_phase_state(current_ir_graph) != phase_building);
1489     free_callee_info(current_ir_graph);
1490
1491     irg_walk(get_irg_end(current_ir_graph), NULL, collect_calls2,
1492              get_irg_link(current_ir_graph));
1493   }
1494
1495   /* -- and now inline. -- */
1496
1497   /* Inline leaves recursively -- we might construct new leaves. */
1498   while (did_inline) {
1499     did_inline = 0;
1500
1501     for (i = 0; i < n_irgs; ++i) {
1502       ir_node *call;
1503       int phiproj_computed = 0;
1504
1505       current_ir_graph = get_irp_irg(i);
1506       env = (inline_irg_env *)get_irg_link(current_ir_graph);
1507
1508       for (call = eset_first(env->call_nodes); call; call = eset_next(env->call_nodes)) {
1509         ir_graph *callee;
1510
1511         if (get_irn_op(call) == op_Tuple) continue;   /* We already have inlined this call. */
1512         callee = get_call_called_irg(call);
1513
1514         if (env->n_nodes > maxsize) continue; // break;
1515
1516         if (callee && (is_leave(callee) && is_smaller(callee, leavesize))) {
1517           if (!phiproj_computed) {
1518             phiproj_computed = 1;
1519             collect_phiprojs(current_ir_graph);
1520           }
1521           did_inline = inline_method(call, callee);
1522
1523           if (did_inline) {
1524             /* Do some statistics */
1525             inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1526             env->n_call_nodes --;
1527             env->n_nodes += callee_env->n_nodes;
1528             callee_env->n_callers--;
1529           }
1530         }
1531       }
1532     }
1533   }
1534
1535   /* inline other small functions. */
1536   for (i = 0; i < n_irgs; ++i) {
1537     ir_node *call;
1538     eset *walkset;
1539     int phiproj_computed = 0;
1540
1541     current_ir_graph = get_irp_irg(i);
1542     env = (inline_irg_env *)get_irg_link(current_ir_graph);
1543
1544     /* we can not walk and change a set, nor remove from it.
1545        So recompute.*/
1546     walkset = env->call_nodes;
1547     env->call_nodes = eset_create();
1548     for (call = eset_first(walkset); call; call = eset_next(walkset)) {
1549       ir_graph *callee;
1550
1551       if (get_irn_op(call) == op_Tuple) continue;   /* We already inlined. */
1552       callee = get_call_called_irg(call);
1553
1554       if (callee &&
1555           ((is_smaller(callee, size) && (env->n_nodes < maxsize)) ||    /* small function */
1556            (get_irg_inline_property(callee) >= irg_inline_forced))) {
1557         if (!phiproj_computed) {
1558             phiproj_computed = 1;
1559             collect_phiprojs(current_ir_graph);
1560         }
1561         if (inline_method(call, callee)) {
1562           inline_irg_env *callee_env = (inline_irg_env *)get_irg_link(callee);
1563           env->n_call_nodes--;
1564           eset_insert_all(env->call_nodes, callee_env->call_nodes);  /* @@@ ??? This are the wrong nodes !? Not the copied ones. */
1565           env->n_call_nodes += callee_env->n_call_nodes;
1566           env->n_nodes += callee_env->n_nodes;
1567           callee_env->n_callers--;
1568         }
1569       } else {
1570         eset_insert(env->call_nodes, call);
1571       }
1572     }
1573     eset_destroy(walkset);
1574   }
1575
1576   for (i = 0; i < n_irgs; ++i) {
1577     current_ir_graph = get_irp_irg(i);
1578 #if 0
1579     env = (inline_irg_env *)get_irg_link(current_ir_graph);
1580     if ((env->n_call_nodes_orig != env->n_call_nodes) ||
1581         (env->n_callers_orig != env->n_callers))
1582       printf("Nodes:%3d ->%3d, calls:%3d ->%3d, callers:%3d ->%3d, -- %s\n",
1583              env->n_nodes_orig, env->n_nodes, env->n_call_nodes_orig, env->n_call_nodes,
1584              env->n_callers_orig, env->n_callers,
1585              get_entity_name(get_irg_entity(current_ir_graph)));
1586 #endif
1587     free_inline_irg_env((inline_irg_env *)get_irg_link(current_ir_graph));
1588   }
1589
1590   current_ir_graph = rem;
1591 }
1592
1593 /*******************************************************************/
1594 /*  Code Placement.  Pins all floating nodes to a block where they */
1595 /*  will be executed only if needed.                               */
1596 /*******************************************************************/
1597
1598 /**
1599  * Returns non-zero, is a block is not reachable from Start.
1600  *
1601  * @param block  the block to test
1602  */
1603 static int
1604 is_Block_unreachable(ir_node *block) {
1605   return is_Block_dead(block) || get_Block_dom_depth(block) < 0;
1606 }
1607
1608 /**
1609  * Find the earliest correct block for N.  --- Place N into the
1610  * same Block as its dominance-deepest Input.
1611  *
1612  * We have to avoid calls to get_nodes_block() here
1613  * because the graph is floating.
1614  *
1615  * move_out_of_loops() expects that place_floats_early() have placed
1616  * all "living" nodes into a living block. That's why we must
1617  * move nodes in dead block with "live" successors into a valid
1618  * block.
1619  * We move them just into the same block as it's successor (or
1620  * in case of a Phi into the effective use block). For Phi successors,
1621  * this may still be a dead block, but then there is no real use, as
1622  * the control flow will be dead later.
1623  */
1624 static void
1625 place_floats_early(ir_node *n, pdeq *worklist)
1626 {
1627   int i, irn_arity;
1628
1629   /* we must not run into an infinite loop */
1630   assert(irn_not_visited(n));
1631   mark_irn_visited(n);
1632
1633   /* Place floating nodes. */
1634   if (get_irn_pinned(n) == op_pin_state_floats) {
1635     ir_node *curr_block = get_irn_n(n, -1);
1636     int in_dead_block   = is_Block_unreachable(curr_block);
1637     int depth           = 0;
1638     ir_node *b          = NULL;   /* The block to place this node in */
1639
1640     assert(get_irn_op(n) != op_Block);
1641
1642     if ((get_irn_op(n) == op_Const) ||
1643         (get_irn_op(n) == op_SymConst) ||
1644         (is_Bad(n)) ||
1645         (get_irn_op(n) == op_Unknown)) {
1646       /* These nodes will not be placed by the loop below. */
1647       b = get_irg_start_block(current_ir_graph);
1648       depth = 1;
1649     }
1650
1651     /* find the block for this node. */
1652     irn_arity = get_irn_arity(n);
1653     for (i = 0; i < irn_arity; i++) {
1654       ir_node *pred = get_irn_n(n, i);
1655       ir_node *pred_block;
1656
1657       if ((irn_not_visited(pred))
1658          && (get_irn_pinned(pred) == op_pin_state_floats)) {
1659
1660         /*
1661          * If the current node is NOT in a dead block, but one of its
1662          * predecessors is, we must move the predecessor to a live block.
1663          * Such thing can happen, if global CSE chose a node from a dead block.
1664          * We move it simple to our block.
1665          * Note that neither Phi nor End nodes are floating, so we don't
1666          * need to handle them here.
1667          */
1668         if (! in_dead_block) {
1669           if (get_irn_pinned(pred) == op_pin_state_floats &&
1670               is_Block_unreachable(get_irn_n(pred, -1)))
1671             set_nodes_block(pred, curr_block);
1672         }
1673         place_floats_early(pred, worklist);
1674       }
1675
1676       /*
1677        * A node in the Bad block must stay in the bad block,
1678        * so don't compute a new block for it.
1679        */
1680       if (in_dead_block)
1681         continue;
1682
1683       /* Because all loops contain at least one op_pin_state_pinned node, now all
1684          our inputs are either op_pin_state_pinned or place_early() has already
1685          been finished on them.  We do not have any unfinished inputs!  */
1686       pred_block = get_irn_n(pred, -1);
1687       if ((!is_Block_dead(pred_block)) &&
1688           (get_Block_dom_depth(pred_block) > depth)) {
1689         b = pred_block;
1690         depth = get_Block_dom_depth(pred_block);
1691       }
1692       /* Avoid that the node is placed in the Start block */
1693       if ((depth == 1) && (get_Block_dom_depth(get_irn_n(n, -1)) > 1)) {
1694         b = get_Block_cfg_out(get_irg_start_block(current_ir_graph), 0);
1695         assert(b != get_irg_start_block(current_ir_graph));
1696         depth = 2;
1697       }
1698     }
1699     if (b)
1700       set_nodes_block(n, b);
1701   }
1702
1703   /*
1704    * Add predecessors of non floating nodes and non-floating predecessors
1705    * of floating nodes to worklist and fix their blocks if the are in dead block.
1706    */
1707   irn_arity = get_irn_arity(n);
1708
1709   if (get_irn_op(n) == op_End) {
1710     /*
1711      * Simplest case: End node. Predecessors are keep-alives,
1712      * no need to move out of dead block.
1713      */
1714     for (i = -1; i < irn_arity; ++i) {
1715       ir_node *pred = get_irn_n(n, i);
1716       if (irn_not_visited(pred))
1717         pdeq_putr(worklist, pred);
1718     }
1719   }
1720   else if (is_Block(n)) {
1721     /*
1722      * Blocks: Predecessors are control flow, no need to move
1723      * them out of dead block.
1724      */
1725     for (i = irn_arity - 1; i >= 0; --i) {
1726       ir_node *pred = get_irn_n(n, i);
1727       if (irn_not_visited(pred))
1728         pdeq_putr(worklist, pred);
1729     }
1730   }
1731   else if (is_Phi(n)) {
1732     ir_node *pred;
1733     ir_node *curr_block = get_irn_n(n, -1);
1734     int in_dead_block   = is_Block_unreachable(curr_block);
1735
1736     /*
1737      * Phi nodes: move nodes from dead blocks into the effective use
1738      * of the Phi-input if the Phi is not in a bad block.
1739      */
1740     pred = get_irn_n(n, -1);
1741     if (irn_not_visited(pred))
1742       pdeq_putr(worklist, pred);
1743
1744     for (i = irn_arity - 1; i >= 0; --i) {
1745       ir_node *pred = get_irn_n(n, i);
1746
1747       if (irn_not_visited(pred)) {
1748         if (! in_dead_block &&
1749             get_irn_pinned(pred) == op_pin_state_floats &&
1750             is_Block_unreachable(get_irn_n(pred, -1))) {
1751           set_nodes_block(pred, get_Block_cfgpred_block(curr_block, i));
1752         }
1753         pdeq_putr(worklist, pred);
1754       }
1755     }
1756   }
1757   else {
1758     ir_node *pred;
1759     ir_node *curr_block = get_irn_n(n, -1);
1760     int in_dead_block   = is_Block_unreachable(curr_block);
1761
1762     /*
1763      * All other nodes: move nodes from dead blocks into the same block.
1764      */
1765     pred = get_irn_n(n, -1);
1766     if (irn_not_visited(pred))
1767       pdeq_putr(worklist, pred);
1768
1769     for (i = irn_arity - 1; i >= 0; --i) {
1770       ir_node *pred = get_irn_n(n, i);
1771
1772       if (irn_not_visited(pred)) {
1773         if (! in_dead_block &&
1774             get_irn_pinned(pred) == op_pin_state_floats &&
1775             is_Block_unreachable(get_irn_n(pred, -1))) {
1776           set_nodes_block(pred, curr_block);
1777         }
1778         pdeq_putr(worklist, pred);
1779       }
1780     }
1781   }
1782 }
1783
1784 /**
1785  * Floating nodes form subgraphs that begin at nodes as Const, Load,
1786  * Start, Call and that end at op_pin_state_pinned nodes as Store, Call.  Place_early
1787  * places all floating nodes reachable from its argument through floating
1788  * nodes and adds all beginnings at op_pin_state_pinned nodes to the worklist.
1789  */
1790 static INLINE void place_early(pdeq *worklist) {
1791   assert(worklist);
1792   inc_irg_visited(current_ir_graph);
1793
1794   /* this inits the worklist */
1795   place_floats_early(get_irg_end(current_ir_graph), worklist);
1796
1797   /* Work the content of the worklist. */
1798   while (!pdeq_empty(worklist)) {
1799     ir_node *n = pdeq_getl(worklist);
1800     if (irn_not_visited(n))
1801       place_floats_early(n, worklist);
1802   }
1803
1804   set_irg_outs_inconsistent(current_ir_graph);
1805   set_irg_pinned(current_ir_graph, op_pin_state_pinned);
1806 }
1807
1808 /**
1809  * Compute the deepest common ancestor of block and dca.
1810  */
1811 static ir_node *calc_dca(ir_node *dca, ir_node *block)
1812 {
1813   assert(block);
1814
1815   /* we do not want to place nodes in dead blocks */
1816   if (is_Block_dead(block))
1817     return dca;
1818
1819   /* We found a first legal placement. */
1820   if (!dca) return block;
1821
1822   /* Find a placement that is dominates both, dca and block. */
1823   while (get_Block_dom_depth(block) > get_Block_dom_depth(dca))
1824     block = get_Block_idom(block);
1825
1826   while (get_Block_dom_depth(dca) > get_Block_dom_depth(block)) {
1827     dca = get_Block_idom(dca);
1828   }
1829
1830   while (block != dca)
1831     { block = get_Block_idom(block); dca = get_Block_idom(dca); }
1832
1833   return dca;
1834 }
1835
1836 /** Deepest common dominance ancestor of DCA and CONSUMER of PRODUCER.
1837  * I.e., DCA is the block where we might place PRODUCER.
1838  * A data flow edge points from producer to consumer.
1839  */
1840 static ir_node *
1841 consumer_dom_dca(ir_node *dca, ir_node *consumer, ir_node *producer)
1842 {
1843   ir_node *block = NULL;
1844
1845   /* Compute the latest block into which we can place a node so that it is
1846      before consumer. */
1847   if (get_irn_op(consumer) == op_Phi) {
1848     /* our consumer is a Phi-node, the effective use is in all those
1849        blocks through which the Phi-node reaches producer */
1850     int i, irn_arity;
1851     ir_node *phi_block = get_nodes_block(consumer);
1852     irn_arity = get_irn_arity(consumer);
1853
1854     for (i = 0;  i < irn_arity; i++) {
1855       if (get_irn_n(consumer, i) == producer) {
1856         ir_node *new_block = get_nodes_block(get_Block_cfgpred(phi_block, i));
1857
1858         if (! is_Block_unreachable(new_block))
1859           block = calc_dca(block, new_block);
1860       }
1861     }
1862
1863     if (! block)
1864       block = get_irn_n(producer, -1);
1865   }
1866   else {
1867     assert(is_no_Block(consumer));
1868     block = get_nodes_block(consumer);
1869   }
1870
1871   /* Compute the deepest common ancestor of block and dca. */
1872   return calc_dca(dca, block);
1873 }
1874
1875 /* FIXME: the name clashes here with the function from ana/field_temperature.c
1876  * please rename. */
1877 static INLINE int get_irn_loop_depth(ir_node *n) {
1878   return get_loop_depth(get_irn_loop(n));
1879 }
1880
1881 /**
1882  * Move n to a block with less loop depth than it's current block. The
1883  * new block must be dominated by early.
1884  *
1885  * @param n      the node that should be moved
1886  * @param early  the earliest block we can n move to
1887  */
1888 static void
1889 move_out_of_loops (ir_node *n, ir_node *early)
1890 {
1891   ir_node *best, *dca;
1892   assert(n && early);
1893
1894
1895   /* Find the region deepest in the dominator tree dominating
1896      dca with the least loop nesting depth, but still dominated
1897      by our early placement. */
1898   dca = get_nodes_block(n);
1899
1900   best = dca;
1901   while (dca != early) {
1902     dca = get_Block_idom(dca);
1903     if (!dca || is_Bad(dca)) break; /* may be Bad if not reachable from Start */
1904     if (get_irn_loop_depth(dca) < get_irn_loop_depth(best)) {
1905       best = dca;
1906     }
1907   }
1908   if (best != get_nodes_block(n)) {
1909     /* debug output
1910     printf("Moving out of loop: "); DDMN(n);
1911     printf(" Outermost block: "); DDMN(early);
1912     printf(" Best block: "); DDMN(best);
1913     printf(" Innermost block: "); DDMN(get_nodes_block(n));
1914     */
1915     set_nodes_block(n, best);
1916   }
1917 }
1918
1919 /**
1920  * Find the latest legal block for N and place N into the
1921  * `optimal' Block between the latest and earliest legal block.
1922  * The `optimal' block is the dominance-deepest block of those
1923  * with the least loop-nesting-depth.  This places N out of as many
1924  * loops as possible and then makes it as control dependent as
1925  * possible.
1926  */
1927 static void
1928 place_floats_late(ir_node *n, pdeq *worklist)
1929 {
1930   int i;
1931   ir_node *early_blk;
1932
1933   assert(irn_not_visited(n)); /* no multiple placement */
1934
1935   mark_irn_visited(n);
1936
1937   /* no need to place block nodes, control nodes are already placed. */
1938   if ((get_irn_op(n) != op_Block) &&
1939       (!is_cfop(n)) &&
1940       (get_irn_mode(n) != mode_X)) {
1941     /* Remember the early_blk placement of this block to move it
1942        out of loop no further than the early_blk placement. */
1943     early_blk = get_irn_n(n, -1);
1944
1945     /*
1946      * BEWARE: Here we also get code, that is live, but
1947      * was in a dead block.  If the node is life, but because
1948      * of CSE in a dead block, we still might need it.
1949      */
1950
1951     /* Assure that our users are all placed, except the Phi-nodes.
1952        --- Each data flow cycle contains at least one Phi-node.  We
1953        have to break the `user has to be placed before the
1954        producer' dependence cycle and the Phi-nodes are the
1955        place to do so, because we need to base our placement on the
1956        final region of our users, which is OK with Phi-nodes, as they
1957        are op_pin_state_pinned, and they never have to be placed after a
1958        producer of one of their inputs in the same block anyway. */
1959     for (i = get_irn_n_outs(n) - 1; i >= 0; --i) {
1960       ir_node *succ = get_irn_out(n, i);
1961       if (irn_not_visited(succ) && (get_irn_op(succ) != op_Phi))
1962         place_floats_late(succ, worklist);
1963     }
1964
1965     if (! is_Block_dead(early_blk)) {
1966       /* do only move things that where not dead */
1967
1968       /* We have to determine the final block of this node... except for
1969          constants. */
1970       if ((get_irn_pinned(n) == op_pin_state_floats) &&
1971           (get_irn_op(n) != op_Const) &&
1972           (get_irn_op(n) != op_SymConst)) {
1973         ir_node *dca = NULL;  /* deepest common ancestor in the
1974                      dominator tree of all nodes'
1975                      blocks depending on us; our final
1976                      placement has to dominate DCA. */
1977         for (i = get_irn_n_outs(n) - 1; i >= 0; --i) {
1978           ir_node *succ = get_irn_out(n, i);
1979           ir_node *succ_blk;
1980
1981           if (get_irn_op(succ) == op_End) {
1982             /*
1983              * This consumer is the End node, a keep alive edge.
1984              * This is not a real consumer, so we ignore it
1985              */
1986             continue;
1987           }
1988
1989           /* ignore if succ is in dead code */
1990           succ_blk = get_irn_n(succ, -1);
1991           if (is_Block_unreachable(succ_blk))
1992             continue;
1993           dca = consumer_dom_dca(dca, succ, n);
1994         }
1995         if (dca) {
1996           set_nodes_block(n, dca);
1997           move_out_of_loops(n, early_blk);
1998         }
1999       }
2000     }
2001   }
2002
2003   /* Add predecessors of all non-floating nodes on list. (Those of floating
2004      nodes are placed already and therefore are marked.)  */
2005   for (i = 0; i < get_irn_n_outs(n); i++) {
2006     ir_node *succ = get_irn_out(n, i);
2007     if (irn_not_visited(get_irn_out(n, i))) {
2008       pdeq_putr(worklist, succ);
2009     }
2010   }
2011 }
2012
2013 static INLINE void place_late(pdeq *worklist) {
2014   assert(worklist);
2015   inc_irg_visited(current_ir_graph);
2016
2017   /* This fills the worklist initially. */
2018   place_floats_late(get_irg_start_block(current_ir_graph), worklist);
2019
2020   /* And now empty the worklist again... */
2021   while (!pdeq_empty(worklist)) {
2022     ir_node *n = pdeq_getl(worklist);
2023     if (irn_not_visited(n))
2024       place_floats_late(n, worklist);
2025   }
2026 }
2027
2028 void place_code(ir_graph *irg) {
2029   pdeq *worklist;
2030   ir_graph *rem = current_ir_graph;
2031
2032   current_ir_graph = irg;
2033
2034   if (!(get_opt_optimize() && get_opt_global_cse())) return;
2035
2036   /* Handle graph state */
2037   assert(get_irg_phase_state(irg) != phase_building);
2038   assure_doms(irg);
2039
2040   if (1 || get_irg_loopinfo_state(irg) != loopinfo_consistent) {
2041     free_loop_information(irg);
2042     construct_backedges(irg);
2043   }
2044
2045   /* Place all floating nodes as early as possible. This guarantees
2046      a legal code placement. */
2047   worklist = new_pdeq();
2048   place_early(worklist);
2049
2050   /* place_early() invalidates the outs, place_late needs them. */
2051   compute_irg_outs(irg);
2052
2053   /* Now move the nodes down in the dominator tree. This reduces the
2054      unnecessary executions of the node. */
2055   place_late(worklist);
2056
2057   set_irg_outs_inconsistent(current_ir_graph);
2058   set_irg_loopinfo_inconsistent(current_ir_graph);
2059   del_pdeq(worklist);
2060   current_ir_graph = rem;
2061 }
2062
2063 /**
2064  * Called by walker of remove_critical_cf_edges().
2065  *
2066  * Place an empty block to an edge between a blocks of multiple
2067  * predecessors and a block of multiple successors.
2068  *
2069  * @param n   IR node
2070  * @param env Environment of walker. The changed field.
2071  */
2072 static void walk_critical_cf_edges(ir_node *n, void *env) {
2073   int arity, i;
2074   ir_node *pre, *block, *jmp;
2075   int *changed = env;
2076   ir_graph *irg = get_irn_irg(n);
2077
2078   /* Block has multiple predecessors */
2079   arity = get_irn_arity(n);
2080   if (arity > 1) {
2081     if (n == get_irg_end_block(irg))
2082       return;  /*  No use to add a block here.      */
2083
2084     for (i = 0; i < arity; ++i) {
2085           const ir_op *cfop;
2086
2087       pre = get_irn_n(n, i);
2088       cfop = get_irn_op(skip_Proj(pre));
2089       /* Predecessor has multiple successors. Insert new control flow edge but
2090          ignore exception edges. */
2091       if (! is_op_fragile(cfop) && is_op_forking(cfop)) {
2092         /* set predecessor of new block */
2093         block = new_r_Block(irg, 1, &pre);
2094         /* insert new jmp node to new block */
2095         jmp = new_r_Jmp(irg, block);
2096         /* set successor of new block */
2097         set_irn_n(n, i, jmp);
2098         *changed = 1;
2099       } /* predecessor has multiple successors */
2100     } /* for all predecessors */
2101   } /* n is a multi-entry block */
2102 }
2103
2104 void remove_critical_cf_edges(ir_graph *irg) {
2105   int changed = 0;
2106
2107   irg_block_walk_graph(irg, NULL, walk_critical_cf_edges, &changed);
2108   if (changed) {
2109     /* control flow changed */
2110     set_irg_outs_inconsistent(irg);
2111     set_irg_extblk_inconsistent(irg);
2112     set_irg_doms_inconsistent(irg);
2113     set_irg_loopinfo_inconsistent(irg);
2114   }
2115 }