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