316dc05fc6f4d3b12748019abeefad8d35df74be
[libfirm] / ir / ir / ircons.c
1 /*
2  * Copyright (C) 1995-2008 University of Karlsruhe.  All right reserved.
3  *
4  * This file is part of libFirm.
5  *
6  * This file may be distributed and/or modified under the terms of the
7  * GNU General Public License version 2 as published by the Free Software
8  * Foundation and appearing in the file LICENSE.GPL included in the
9  * packaging of this file.
10  *
11  * Licensees holding valid libFirm Professional Edition licenses may use
12  * this file in accordance with the libFirm Commercial License.
13  * Agreement provided with the Software.
14  *
15  * This file is provided AS IS with NO WARRANTY OF ANY KIND, INCLUDING THE
16  * WARRANTY OF DESIGN, MERCHANTABILITY AND FITNESS FOR A PARTICULAR
17  * PURPOSE.
18  */
19
20 /**
21  * @file
22  * @brief   Various irnode constructors. Automatic construction of SSA
23  *          representation.
24  * @author  Martin Trapp, Christian Schaefer, Goetz Lindenmaier, Boris Boesler
25  *          Michael Beck, Matthias Braun
26  * @version $Id$
27  */
28 #include "config.h"
29
30 #include "irprog_t.h"
31 #include "irgraph_t.h"
32 #include "irnode_t.h"
33 #include "irmode_t.h"
34 #include "ircons_t.h"
35 #include "irverify.h"
36 #include "irop_t.h"
37 #include "iropt_t.h"
38 #include "irgmod.h"
39 #include "irhooks.h"
40 #include "array_t.h"
41 #include "irbackedge_t.h"
42 #include "irflag_t.h"
43 #include "iredges_t.h"
44 #include "irflag_t.h"
45 #include "error.h"
46
47 #include "gen_ir_cons.c.inl"
48
49 /**
50  * Language dependent variable initialization callback.
51  */
52 static uninitialized_local_variable_func_t *default_initialize_local_variable = NULL;
53
54 /**
55  * Creates a Phi node with all predecessors.  Calling this constructor
56  * is only allowed if the corresponding block is mature.
57  */
58 ir_node *new_rd_Phi(dbg_info *db, ir_node *block, int arity, ir_node **in,
59                     ir_mode *mode)
60 {
61         ir_graph *irg = get_irn_irg(block);
62         ir_node  *res = new_ir_node(db, irg, block, op_Phi, mode, arity, in);
63         res->attr.phi.u.backedge = new_backedge_arr(irg->obst, arity);
64
65         res = optimize_node(res);
66         irn_verify_irg(res, irg);
67
68         /* Memory Phis in endless loops must be kept alive.
69            As we can't distinguish these easily we keep all of them alive. */
70         if (is_Phi(res) && mode == mode_M)
71                 add_End_keepalive(get_irg_end(irg), res);
72         return res;
73 }
74
75 ir_node *new_rd_Const(dbg_info *db, ir_graph *irg, ir_tarval *con)
76 {
77         ir_node  *block = get_irg_start_block(irg);
78         ir_mode  *mode  = get_tarval_mode(con);
79         ir_node  *res   = new_ir_node(db, irg, block, op_Const, mode, 0, NULL);
80         res->attr.con.tarval = con;
81
82         res = optimize_node (res);
83         irn_verify_irg(res, irg);
84
85         return res;
86 }
87
88 ir_node *new_rd_Const_long(dbg_info *db, ir_graph *irg, ir_mode *mode,
89                            long value)
90 {
91         return new_rd_Const(db, irg, new_tarval_from_long(value, mode));
92 }
93
94 ir_node *new_rd_defaultProj(dbg_info *db, ir_node *arg, long max_proj)
95 {
96         ir_node *res;
97
98         assert(is_Cond(arg));
99         arg->attr.cond.default_proj = max_proj;
100         res = new_rd_Proj(db, arg, mode_X, max_proj);
101         return res;
102 }
103
104 ir_node *new_rd_ASM(dbg_info *db, ir_node *block, int arity, ir_node *in[],
105                     ir_asm_constraint *inputs, int n_outs,
106                         ir_asm_constraint *outputs, int n_clobber,
107                         ident *clobber[], ident *text)
108 {
109         ir_graph *irg = get_irn_irg(block);
110         ir_node  *res = new_ir_node(db, irg, block, op_ASM, mode_T, arity, in);
111
112         res->attr.assem.pin_state = op_pin_state_pinned;
113         res->attr.assem.input_constraints
114                 = NEW_ARR_D(ir_asm_constraint, irg->obst, arity);
115         res->attr.assem.output_constraints
116                 = NEW_ARR_D(ir_asm_constraint, irg->obst, n_outs);
117         res->attr.assem.clobbers = NEW_ARR_D(ident *, irg->obst, n_clobber);
118         res->attr.assem.text     = text;
119
120         memcpy(res->attr.assem.input_constraints,  inputs,  sizeof(inputs[0]) * arity);
121         memcpy(res->attr.assem.output_constraints, outputs, sizeof(outputs[0]) * n_outs);
122         memcpy(res->attr.assem.clobbers, clobber, sizeof(clobber[0]) * n_clobber);
123
124         res = optimize_node(res);
125         irn_verify_irg(res, irg);
126         return res;
127 }
128
129 ir_node *new_rd_simpleSel(dbg_info *db, ir_node *block, ir_node *store,
130                           ir_node *objptr, ir_entity *ent)
131 {
132         return new_rd_Sel(db, block, store, objptr, 0, NULL, ent);
133 }
134
135 ir_node *new_rd_SymConst(dbg_info *db, ir_graph *irg, ir_mode *mode,
136                          symconst_symbol value, symconst_kind symkind)
137 {
138         ir_node *block = get_irg_start_block(irg);
139         ir_node *res   = new_ir_node(db, irg, block, op_SymConst, mode, 0, NULL);
140         res->attr.symc.kind = symkind;
141         res->attr.symc.sym  = value;
142
143         res = optimize_node(res);
144         irn_verify_irg(res, irg);
145         return res;
146 }
147
148 ir_node *new_rd_SymConst_addr_ent(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_entity *symbol)
149 {
150         symconst_symbol sym;
151         sym.entity_p = symbol;
152         return new_rd_SymConst(db, irg, mode, sym, symconst_addr_ent);
153 }
154
155 ir_node *new_rd_SymConst_ofs_ent(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_entity *symbol)
156 {
157         symconst_symbol sym;
158         sym.entity_p = symbol;
159         return new_rd_SymConst(db, irg, mode, sym, symconst_ofs_ent);
160 }
161
162 ir_node *new_rd_SymConst_type_tag(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_type *symbol)
163 {
164         symconst_symbol sym;
165         sym.type_p = symbol;
166         return new_rd_SymConst(db, irg, mode, sym, symconst_type_tag);
167 }
168
169 ir_node *new_rd_SymConst_size(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_type *symbol)
170 {
171         symconst_symbol sym;
172         sym.type_p = symbol;
173         return new_rd_SymConst(db, irg, mode, sym, symconst_type_size);
174 }
175
176 ir_node *new_rd_SymConst_align(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_type *symbol)
177 {
178         symconst_symbol sym;
179         sym.type_p = symbol;
180         return new_rd_SymConst(db, irg, mode, sym, symconst_type_align);
181 }
182
183 ir_node *new_r_Const(ir_graph *irg, ir_tarval *con)
184 {
185         return new_rd_Const(NULL, irg, con);
186 }
187 ir_node *new_r_Const_long(ir_graph *irg, ir_mode *mode, long value)
188 {
189         return new_rd_Const_long(NULL, irg, mode, value);
190 }
191 ir_node *new_r_SymConst(ir_graph *irg, ir_mode *mode, symconst_symbol value,
192                         symconst_kind symkind)
193 {
194         return new_rd_SymConst(NULL, irg, mode, value, symkind);
195 }
196 ir_node *new_r_simpleSel(ir_node *block, ir_node *store, ir_node *objptr,
197                          ir_entity *ent)
198 {
199         return new_rd_Sel(NULL, block, store, objptr, 0, NULL, ent);
200 }
201 ir_node *new_r_Phi(ir_node *block, int arity, ir_node **in, ir_mode *mode)
202 {
203         return new_rd_Phi(NULL, block, arity, in, mode);
204 }
205 ir_node *new_r_defaultProj(ir_node *arg, long max_proj)
206 {
207         return new_rd_defaultProj(NULL, arg, max_proj);
208 }
209 ir_node *new_r_ASM(ir_node *block,
210                    int arity, ir_node *in[], ir_asm_constraint *inputs,
211                    int n_outs, ir_asm_constraint *outputs,
212                    int n_clobber, ident *clobber[], ident *text)
213 {
214         return new_rd_ASM(NULL, block, arity, in, inputs, n_outs, outputs, n_clobber, clobber, text);
215 }
216
217 /* ***********************************************************************/
218 /* Methods necessary for automatic Phi node creation                     */
219 /*
220   ir_node *phi_merge            (ir_node *block, int pos, ir_mode *mode, ir_node **nin, int ins)
221   ir_node *get_r_value_internal (ir_node *block, int pos, ir_mode *mode);
222   ir_node *new_rd_Phi0          (ir_graph *irg, ir_node *block, ir_mode *mode)
223   ir_node *new_rd_Phi_in        (ir_graph *irg, ir_node *block, ir_mode *mode, ir_node **in, int ins)
224
225   Call Graph:   ( A ---> B == A "calls" B)
226
227        get_value         mature_immBlock
228           |                   |
229           |                   |
230           |                   |
231           |          ---> phi_merge
232           |         /       /   \
233           |        /       /     \
234          \|/      /      |/_      \
235        get_r_value_internal        |
236                 |                  |
237                 |                  |
238                \|/                \|/
239            new_rd_Phi0          new_rd_Phi_in
240
241 * *************************************************************************** */
242
243 /** Creates a Phi node with 0 predecessors. */
244 static inline ir_node *new_rd_Phi0(ir_node *block, ir_mode *mode)
245 {
246         ir_graph *irg = get_irn_irg(block);
247         ir_node  *res = new_ir_node(NULL, irg, block, op_Phi, mode, 0, NULL);
248         irn_verify_irg(res, irg);
249         return res;
250 }
251
252 /**
253  * Internal constructor of a Phi node by a phi_merge operation.
254  *
255  * @param block  the block in which the Phi will be constructed
256  * @param mode   the mod eof the Phi node
257  * @param in     the input array of the phi node
258  * @param n_in   number of elements in the input array
259  * @param phi0   in non-NULL: the Phi0 node in the same block that represents
260  *               the value for which the new Phi is constructed
261  */
262 static ir_node *new_rd_Phi_in(ir_node *block, ir_mode *mode,
263                               int n_in, ir_node **in, ir_node *phi0)
264 {
265         int i;
266         ir_node *res, *known;
267         ir_graph *irg = get_irn_irg(block);
268
269         /* Allocate a new node on the obstack.  The allocation copies the in
270            array. */
271         res = new_ir_node(NULL, irg, block, op_Phi, mode, n_in, in);
272         res->attr.phi.u.backedge = new_backedge_arr(irg->obst, n_in);
273
274         /* This loop checks whether the Phi has more than one predecessor.
275            If so, it is a real Phi node and we break the loop.  Else the
276            Phi node merges the same definition on several paths and therefore
277            is not needed.
278            Note: We MUST consider Bad nodes, else we might get data flow cycles in dead loops! */
279         known = res;
280         for (i = n_in - 1; i >= 0; --i) {
281                 assert(in[i]);
282
283                 in[i] = skip_Id(in[i]);  /* increases the number of freed Phis. */
284
285                 /* Optimize self referencing Phis:  We can't detect them yet properly, as
286                 they still refer to the Phi0 they will replace.  So replace right now. */
287                 if (phi0 && in[i] == phi0)
288                         in[i] = res;
289
290                 if (in[i] == res || in[i] == known)
291                         continue;
292
293                 if (known == res)
294                         known = in[i];
295                 else
296                         break;
297         }
298
299         /* i < 0: there is at most one predecessor, we don't need a phi node. */
300         if (i < 0) {
301                 if (res != known) {
302                         edges_node_deleted(res, current_ir_graph);
303                         obstack_free(current_ir_graph->obst, res);
304                         if (is_Phi(known)) {
305                                 /* If pred is a phi node we want to optimize it: If loops are matured in a bad
306                                    order, an enclosing Phi know may get superfluous. */
307                                 res = optimize_in_place_2(known);
308                                 if (res != known)
309                                         exchange(known, res);
310                         }
311                         else
312                                 res = known;
313                 } else {
314                         /* A undefined value, e.g., in unreachable code. */
315                         res = new_r_Bad(irg);
316                 }
317         } else {
318                 res = optimize_node(res);  /* This is necessary to add the node to the hash table for cse. */
319                 irn_verify_irg(res, irg);
320                 /* Memory Phis in endless loops must be kept alive.
321                    As we can't distinguish these easily we keep all of them alive. */
322                 if (is_Phi(res) && mode == mode_M)
323                         add_End_keepalive(get_irg_end(irg), res);
324         }
325
326         return res;
327 }
328
329 static ir_node *get_r_value_internal(ir_node *block, int pos, ir_mode *mode);
330
331 /**
332  * Computes the predecessors for the real phi node, and then
333  * allocates and returns this node.  The routine called to allocate the
334  * node might optimize it away and return a real value.
335  * This function must be called with an in-array of proper size.
336  */
337 static ir_node *phi_merge(ir_node *block, int pos, ir_mode *mode,
338                           int n_ins, ir_node **ins)
339 {
340         ir_graph *irg = get_irn_irg(block);
341         ir_node *prevBlock, *res, *phi0, *phi0_all;
342         int i;
343
344         /* If this block has no value at pos create a Phi0 and remember it
345            in graph_arr to break recursions.
346            Else we may not set graph_arr as there a later value is remembered. */
347         phi0 = NULL;
348         if (block->attr.block.graph_arr[pos] == NULL) {
349
350                 if (block == get_irg_start_block(irg)) {
351                         /* Collapsing to Bad tarvals is no good idea.
352                            So we call a user-supplied routine here that deals with this
353                            case as appropriate for the given language. Sorrily the only
354                            help we can give here is the position.
355
356                            Even if all variables are defined before use, it can happen that
357                            we get to the start block, if a Cond has been replaced by a tuple
358                            (bad, jmp).  In this case we call the function needlessly,
359                            eventually generating an non existent error.
360                            However, this SHOULD NOT HAPPEN, as bad control flow nodes are
361                            intercepted before recurring.
362                          */
363                         if (default_initialize_local_variable != NULL) {
364                                 ir_node *rem = get_r_cur_block(irg);
365
366                                 set_r_cur_block(irg, block);
367                                 block->attr.block.graph_arr[pos] = default_initialize_local_variable(irg, mode, pos - 1);
368                                 set_r_cur_block(irg, rem);
369                         } else {
370                                 block->attr.block.graph_arr[pos] = new_r_Unknown(irg, mode);
371                         }
372                         return block->attr.block.graph_arr[pos];
373                 } else {
374                         phi0 = new_rd_Phi0(block, mode);
375                         block->attr.block.graph_arr[pos] = phi0;
376                 }
377         }
378
379         /* This loop goes to all predecessor blocks of the block the Phi node
380            is in and there finds the operands of the Phi node by calling
381            get_r_value_internal.  */
382         for (i = 1; i <= n_ins; ++i) {
383                 ir_node *cf_pred = block->in[i];
384                 ir_node *prevCfOp = skip_Proj(cf_pred);
385                 assert(prevCfOp);
386                 if (is_Bad(prevCfOp)) {
387                         /* In case a Cond has been optimized we would get right to the start block
388                         with an invalid definition. */
389                         ins[i-1] = new_r_Bad(irg);
390                         continue;
391                 }
392                 prevBlock = prevCfOp->in[0]; /* go past control flow op to prev block */
393                 assert(prevBlock);
394                 if (!is_Bad(prevBlock)) {
395                         ins[i-1] = get_r_value_internal(prevBlock, pos, mode);
396                 } else {
397                         ins[i-1] = new_r_Bad(irg);
398                 }
399         }
400
401         /* We want to pass the Phi0 node to the constructor: this finds additional
402            optimization possibilities.
403            The Phi0 node either is allocated in this function, or it comes from
404            a former call to get_r_value_internal(). In this case we may not yet
405            exchange phi0, as this is done in mature_immBlock(). */
406         if (phi0 == NULL) {
407                 phi0_all = block->attr.block.graph_arr[pos];
408                 if (! is_Phi0(phi0_all)            ||
409                     get_irn_arity(phi0_all) != 0   ||
410                     get_nodes_block(phi0_all) != block)
411                         phi0_all = NULL;
412         } else {
413                 phi0_all = phi0;
414         }
415
416         /* After collecting all predecessors into the array ins a new Phi node
417            with these predecessors is created.  This constructor contains an
418            optimization: If all predecessors of the Phi node are identical it
419            returns the only operand instead of a new Phi node.  */
420         res = new_rd_Phi_in(block, mode, n_ins, ins, phi0_all);
421
422         /* In case we allocated a Phi0 node at the beginning of this procedure,
423            we need to exchange this Phi0 with the real Phi. */
424         if (phi0 != NULL) {
425                 exchange(phi0, res);
426                 block->attr.block.graph_arr[pos] = res;
427         }
428
429         return res;
430 }
431
432 /**
433  * This function returns the last definition of a value.  In case
434  * this value was last defined in a previous block, Phi nodes are
435  * inserted.  If the part of the firm graph containing the definition
436  * is not yet constructed, a dummy Phi node is returned.
437  *
438  * @param block   the current block
439  * @param pos     the value number of the value searched
440  * @param mode    the mode of this value (needed for Phi construction)
441  */
442 static ir_node *get_r_value_internal(ir_node *block, int pos, ir_mode *mode)
443 {
444         ir_node *res;
445         /* There are 4 cases to treat.
446
447            1. The block is not mature and we visit it the first time.  We can not
448               create a proper Phi node, therefore a Phi0, i.e., a Phi without
449               predecessors is returned.  This node is added to the linked list (block
450               attribute "phis") of the containing block to be completed when this block is
451               matured. (Completion will add a new Phi and turn the Phi0 into an Id
452               node.)
453
454            2. The value is already known in this block, graph_arr[pos] is set and we
455               visit the block the first time.  We can return the value without
456               creating any new nodes.
457
458            3. The block is mature and we visit it the first time.  A Phi node needs
459               to be created (phi_merge).  If the Phi is not needed, as all it's
460               operands are the same value reaching the block through different
461               paths, it's optimized away and the value itself is returned.
462
463            4. The block is mature, and we visit it the second time.  Now two
464               subcases are possible:
465               * The value was computed completely the last time we were here. This
466                 is the case if there is no loop.  We can return the proper value.
467               * The recursion that visited this node and set the flag did not
468                 return yet.  We are computing a value in a loop and need to
469                 break the recursion.  This case only happens if we visited
470             the same block with phi_merge before, which inserted a Phi0.
471             So we return the Phi0.
472         */
473
474         /* case 4 -- already visited. */
475         if (irn_visited(block)) {
476                 /* As phi_merge allocates a Phi0 this value is always defined. Here
477                 is the critical difference of the two algorithms. */
478                 assert(block->attr.block.graph_arr[pos]);
479                 return block->attr.block.graph_arr[pos];
480         }
481
482         /* visited the first time */
483         mark_irn_visited(block);
484
485         /* Get the local valid value */
486         res = block->attr.block.graph_arr[pos];
487
488         /* case 2 -- If the value is actually computed, return it. */
489         if (res != NULL)
490                 return res;
491
492         if (block->attr.block.is_matured) { /* case 3 */
493
494                 /* The Phi has the same amount of ins as the corresponding block. */
495                 int n_in = get_irn_arity(block);
496                 ir_node **in;
497                 NEW_ARR_A(ir_node *, in, n_in);
498
499                 /* Phi merge collects the predecessors and then creates a node. */
500                 res = phi_merge(block, pos, mode, n_in, in);
501         } else {  /* case 1 */
502                 /* The block is not mature, we don't know how many in's are needed.  A Phi
503                    with zero predecessors is created.  Such a Phi node is called Phi0
504                    node.  The Phi0 is then added to the list of Phi0 nodes in this block
505                    to be matured by mature_immBlock later.
506                    The Phi0 has to remember the pos of it's internal value.  If the real
507                    Phi is computed, pos is used to update the array with the local
508                    values. */
509                 res = new_rd_Phi0(block, mode);
510                 res->attr.phi.u.pos    = pos;
511                 res->attr.phi.next     = block->attr.block.phis;
512                 block->attr.block.phis = res;
513         }
514
515         assert(is_ir_node(res) && "phi_merge() failed to construct a definition");
516
517         /* The local valid value is available now. */
518         block->attr.block.graph_arr[pos] = res;
519
520         return res;
521 }
522
523 /* ************************************************************************** */
524
525 /*
526  * Finalize a Block node, when all control flows are known.
527  * Acceptable parameters are only Block nodes.
528  */
529 void mature_immBlock(ir_node *block)
530 {
531         int ins;
532         ir_node *n, **nin;
533         ir_node *next;
534
535         assert(is_Block(block));
536         if (!get_Block_matured(block)) {
537                 ir_graph *irg = current_ir_graph;
538
539                 ins = ARR_LEN(block->in) - 1;
540                 /* Fix block parameters */
541                 block->attr.block.backedge = new_backedge_arr(irg->obst, ins);
542
543                 /* An array for building the Phi nodes. */
544                 NEW_ARR_A(ir_node *, nin, ins);
545
546                 /* Traverse a chain of Phi nodes attached to this block and mature
547                 these, too. **/
548                 for (n = block->attr.block.phis; n; n = next) {
549                         inc_irg_visited(irg);
550                         next = n->attr.phi.next;
551                         exchange(n, phi_merge(block, n->attr.phi.u.pos, n->mode, ins, nin));
552                 }
553
554                 block->attr.block.is_matured = 1;
555
556                 /* Now, as the block is a finished Firm node, we can optimize it.
557                    Since other nodes have been allocated since the block was created
558                    we can not free the node on the obstack.  Therefore we have to call
559                    optimize_in_place().
560                    Unfortunately the optimization does not change a lot, as all allocated
561                    nodes refer to the unoptimized node.
562                    We can call optimize_in_place_2(), as global cse has no effect on blocks. */
563                 block = optimize_in_place_2(block);
564                 irn_verify_irg(block, irg);
565         }
566 }
567
568 ir_node *new_d_Phi(dbg_info *db, int arity, ir_node **in, ir_mode *mode)
569 {
570         assert(get_irg_phase_state(current_ir_graph) == phase_building);
571         return new_rd_Phi(db, current_ir_graph->current_block, arity, in, mode);
572 }
573
574 ir_node *new_d_Const(dbg_info *db, ir_tarval *con)
575 {
576         assert(get_irg_phase_state(current_ir_graph) == phase_building);
577         return new_rd_Const(db, current_ir_graph, con);
578 }
579
580 ir_node *new_d_Const_long(dbg_info *db, ir_mode *mode, long value)
581 {
582         assert(get_irg_phase_state(current_ir_graph) == phase_building);
583         return new_rd_Const_long(db, current_ir_graph, mode, value);
584 }
585
586 ir_node *new_d_defaultProj(dbg_info *db, ir_node *arg, long max_proj)
587 {
588         ir_node *res;
589         assert(is_Cond(arg));
590         assert(get_irg_phase_state(current_ir_graph) == phase_building);
591         arg->attr.cond.default_proj = max_proj;
592         res = new_d_Proj(db, arg, mode_X, max_proj);
593         return res;
594 }
595
596 ir_node *new_d_simpleSel(dbg_info *db, ir_node *store, ir_node *objptr,
597                          ir_entity *ent)
598 {
599         assert(get_irg_phase_state(current_ir_graph) == phase_building);
600         return new_rd_Sel(db, current_ir_graph->current_block,
601                           store, objptr, 0, NULL, ent);
602 }
603
604 ir_node *new_d_SymConst(dbg_info *db, ir_mode *mode, symconst_symbol value,
605                         symconst_kind kind)
606 {
607         assert(get_irg_phase_state(current_ir_graph) == phase_building);
608         return new_rd_SymConst(db, current_ir_graph, mode, value, kind);
609 }
610
611 ir_node *new_d_ASM(dbg_info *db, int arity, ir_node *in[],
612                    ir_asm_constraint *inputs,
613                    int n_outs, ir_asm_constraint *outputs, int n_clobber,
614                    ident *clobber[], ident *text)
615 {
616         assert(get_irg_phase_state(current_ir_graph) == phase_building);
617         return new_rd_ASM(db, current_ir_graph->current_block, arity, in, inputs,
618                           n_outs, outputs, n_clobber, clobber, text);
619 }
620
621 ir_node *new_rd_immBlock(dbg_info *dbgi, ir_graph *irg)
622 {
623         ir_node *res;
624
625         assert(get_irg_phase_state(irg) == phase_building);
626         /* creates a new dynamic in-array as length of in is -1 */
627         res = new_ir_node(dbgi, irg, NULL, op_Block, mode_BB, -1, NULL);
628
629         res->attr.block.is_matured  = 0;
630         res->attr.block.is_dead     = 0;
631         res->attr.block.irg.irg     = irg;
632         res->attr.block.backedge    = NULL;
633         res->attr.block.in_cg       = NULL;
634         res->attr.block.cg_backedge = NULL;
635         res->attr.block.extblk      = NULL;
636         res->attr.block.region      = NULL;
637         res->attr.block.entity      = NULL;
638
639         set_Block_block_visited(res, 0);
640
641         /* Create and initialize array for Phi-node construction. */
642         res->attr.block.graph_arr = NEW_ARR_D(ir_node *, irg->obst, irg->n_loc);
643         memset(res->attr.block.graph_arr, 0, sizeof(ir_node*) * irg->n_loc);
644
645         /* Immature block may not be optimized! */
646         irn_verify_irg(res, irg);
647
648         return res;
649 }
650
651 ir_node *new_r_immBlock(ir_graph *irg)
652 {
653         return new_rd_immBlock(NULL, irg);
654 }
655
656 ir_node *new_d_immBlock(dbg_info *dbgi)
657 {
658         return new_rd_immBlock(dbgi, current_ir_graph);
659 }
660
661 ir_node *new_immBlock(void)
662 {
663         return new_rd_immBlock(NULL, current_ir_graph);
664 }
665
666 void add_immBlock_pred(ir_node *block, ir_node *jmp)
667 {
668         int n = ARR_LEN(block->in) - 1;
669
670         assert(is_Block(block) && "Error: Must be a Block");
671         assert(!block->attr.block.is_matured && "Error: Block already matured!\n");
672         assert(is_ir_node(jmp));
673
674         ARR_APP1(ir_node *, block->in, jmp);
675         /* Call the hook */
676         hook_set_irn_n(block, n, jmp, NULL);
677 }
678
679 void set_cur_block(ir_node *target)
680 {
681         current_ir_graph->current_block = target;
682 }
683
684 void set_r_cur_block(ir_graph *irg, ir_node *target)
685 {
686         irg->current_block = target;
687 }
688
689 ir_node *get_r_cur_block(ir_graph *irg)
690 {
691         return irg->current_block;
692 }
693
694 ir_node *get_cur_block(void)
695 {
696         return get_r_cur_block(current_ir_graph);
697 }
698
699 ir_node *get_r_value(ir_graph *irg, int pos, ir_mode *mode)
700 {
701         assert(get_irg_phase_state(irg) == phase_building);
702         inc_irg_visited(irg);
703
704         assert(pos >= 0);
705
706         return get_r_value_internal(irg->current_block, pos + 1, mode);
707 }
708
709 ir_node *get_value(int pos, ir_mode *mode)
710 {
711         return get_r_value(current_ir_graph, pos, mode);
712 }
713
714 /**
715  * helper function for guess_mode: recursively look for a definition for
716  * local variable @p pos, returns its mode if found.
717  */
718 static ir_mode *guess_recursively(ir_node *block, int pos)
719 {
720         ir_node *value;
721         int      n_preds;
722         int      i;
723
724         if (irn_visited(block))
725                 return NULL;
726         mark_irn_visited(block);
727
728         /* already have a defintion -> we can simply look at its mode */
729         value = block->attr.block.graph_arr[pos];
730         if (value != NULL)
731                 return get_irn_mode(value);
732
733         /* now we try to guess, by looking at the predecessor blocks */
734         n_preds = get_irn_arity(block);
735         for (i = 0; i < n_preds; ++i) {
736                 ir_node *pred_block = get_Block_cfgpred_block(block, i);
737                 ir_mode *mode       = guess_recursively(pred_block, pos);
738                 if (mode != NULL)
739                         return mode;
740         }
741
742         /* no way to guess */
743         return NULL;
744 }
745
746 ir_mode *ir_guess_mode(int pos)
747 {
748         ir_graph *irg   = current_ir_graph;
749         ir_node  *block = irg->current_block;
750         ir_node  *value = block->attr.block.graph_arr[pos+1];
751         ir_mode  *mode;
752
753         /* already have a defintion -> we can simply look at its mode */
754         if (value != NULL)
755                 return get_irn_mode(value);
756
757         ir_reserve_resources(current_ir_graph, IR_RESOURCE_IRN_VISITED);
758         inc_irg_visited(current_ir_graph);
759         mode = guess_recursively(block, pos+1);
760         ir_free_resources(current_ir_graph, IR_RESOURCE_IRN_VISITED);
761
762         return mode;
763 }
764
765 void set_r_value(ir_graph *irg, int pos, ir_node *value)
766 {
767         assert(get_irg_phase_state(irg) == phase_building);
768         assert(pos >= 0);
769         assert(pos+1 < irg->n_loc);
770         assert(is_ir_node(value));
771         irg->current_block->attr.block.graph_arr[pos + 1] = value;
772 }
773
774 void set_value(int pos, ir_node *value)
775 {
776         set_r_value(current_ir_graph, pos, value);
777 }
778
779 int find_value(ir_node *value)
780 {
781         int i;
782         ir_node *bl = current_ir_graph->current_block;
783
784         for (i = ARR_LEN(bl->attr.block.graph_arr) - 1; i >= 1; --i)
785                 if (bl->attr.block.graph_arr[i] == value)
786                         return i - 1;
787         return -1;
788 }
789
790 ir_node *get_r_store(ir_graph *irg)
791 {
792         assert(get_irg_phase_state(irg) == phase_building);
793         inc_irg_visited(irg);
794         return get_r_value_internal(irg->current_block, 0, mode_M);
795 }
796
797 ir_node *get_store(void)
798 {
799         return get_r_store(current_ir_graph);
800 }
801
802 void set_r_store(ir_graph *irg, ir_node *store)
803 {
804         ir_node *load, *pload, *pred, *in[2];
805
806         assert(get_irg_phase_state(irg) == phase_building);
807         /* Beware: due to dead code elimination, a store might become a Bad node even in
808            the construction phase. */
809         assert((get_irn_mode(store) == mode_M || is_Bad(store)) && "storing non-memory node");
810
811         if (get_opt_auto_create_sync()) {
812                 /* handle non-volatile Load nodes by automatically creating Sync's */
813                 load = skip_Proj(store);
814                 if (is_Load(load) && get_Load_volatility(load) == volatility_non_volatile) {
815                         pred = get_Load_mem(load);
816
817                         if (is_Sync(pred)) {
818                                 /* a Load after a Sync: move it up */
819                                 ir_node *mem = skip_Proj(get_Sync_pred(pred, 0));
820
821                                 set_Load_mem(load, get_memop_mem(mem));
822                                 add_Sync_pred(pred, store);
823                                 store = pred;
824                         } else {
825                                 pload = skip_Proj(pred);
826                                 if (is_Load(pload) && get_Load_volatility(pload) == volatility_non_volatile) {
827                                         /* a Load after a Load: create a new Sync */
828                                         set_Load_mem(load, get_Load_mem(pload));
829
830                                         in[0] = pred;
831                                         in[1] = store;
832                                         store = new_r_Sync(irg->current_block, 2, in);
833                                 }
834                         }
835                 }
836         }
837         irg->current_block->attr.block.graph_arr[0] = store;
838 }
839
840 void set_store(ir_node *store)
841 {
842         set_r_store(current_ir_graph, store);
843 }
844
845 void keep_alive(ir_node *ka)
846 {
847         add_End_keepalive(get_irg_end(current_ir_graph), ka);
848 }
849
850 void ir_set_uninitialized_local_variable_func(
851                 uninitialized_local_variable_func_t *func)
852 {
853         default_initialize_local_variable = func;
854 }
855
856 void irg_finalize_cons(ir_graph *irg)
857 {
858         set_irg_phase_state(irg, phase_high);
859 }
860
861 void irp_finalize_cons(void)
862 {
863         int i;
864         for (i = get_irp_n_irgs() - 1; i >= 0; --i) {
865                 irg_finalize_cons(get_irp_irg(i));
866         }
867         irp->phase_state = phase_high;
868 }
869
870 ir_node *new_Const(ir_tarval *con)
871 {
872         return new_d_Const(NULL, con);
873 }
874
875 ir_node *new_Const_long(ir_mode *mode, long value)
876 {
877         return new_d_Const_long(NULL, mode, value);
878 }
879
880 ir_node *new_SymConst(ir_mode *mode, symconst_symbol value, symconst_kind kind)
881 {
882         return new_d_SymConst(NULL, mode, value, kind);
883 }
884 ir_node *new_simpleSel(ir_node *store, ir_node *objptr, ir_entity *ent)
885 {
886         return new_d_simpleSel(NULL, store, objptr, ent);
887 }
888 ir_node *new_Phi(int arity, ir_node **in, ir_mode *mode)
889 {
890         return new_d_Phi(NULL, arity, in, mode);
891 }
892 ir_node *new_defaultProj(ir_node *arg, long max_proj)
893 {
894         return new_d_defaultProj(NULL, arg, max_proj);
895 }
896 ir_node *new_ASM(int arity, ir_node *in[], ir_asm_constraint *inputs,
897                  int n_outs, ir_asm_constraint *outputs,
898                  int n_clobber, ident *clobber[], ident *text)
899 {
900         return new_d_ASM(NULL, arity, in, inputs, n_outs, outputs, n_clobber, clobber, text);
901 }
902
903 ir_node *new_r_Anchor(ir_graph *irg)
904 {
905         ir_node *in[anchor_last];
906         ir_node *res;
907         memset(in, 0, sizeof(in));
908         res = new_ir_node(NULL, irg, NULL, op_Anchor, mode_ANY, anchor_last, in);
909         res->attr.anchor.irg.irg = irg;
910
911         /* hack to get get_irn_irg working: set block to ourself and allow
912          * get_Block_irg for anchor */
913         res->in[0] = res;
914
915         return res;
916 }
917
918 ir_node *new_r_Block_noopt(ir_graph *irg, int arity, ir_node *in[])
919 {
920         ir_node *res = new_ir_node(NULL, irg, NULL, op_Block, mode_BB, arity, in);
921         res->attr.block.irg.irg = irg;
922         res->attr.block.backedge = new_backedge_arr(irg->obst, arity);
923         set_Block_matured(res, 1);
924         /* Create and initialize array for Phi-node construction. */
925         if (get_irg_phase_state(irg) == phase_building) {
926                 res->attr.block.graph_arr = NEW_ARR_D(ir_node *, irg->obst, irg->n_loc);
927                 memset(res->attr.block.graph_arr, 0, irg->n_loc * sizeof(ir_node*));
928         }
929         irn_verify_irg(res, irg);
930         return res;
931 }