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