remove $Id$, it doesn't work with git anyway
[libfirm] / ir / ir / ircons.c
1 /*
2  * Copyright (C) 1995-2011 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  */
27 #include "config.h"
28
29 #include "irprog_t.h"
30 #include "irgraph_t.h"
31 #include "irnode_t.h"
32 #include "irmode_t.h"
33 #include "ircons_t.h"
34 #include "irverify.h"
35 #include "irop_t.h"
36 #include "iropt_t.h"
37 #include "irgmod.h"
38 #include "irhooks.h"
39 #include "array_t.h"
40 #include "irbackedge_t.h"
41 #include "irflag_t.h"
42 #include "iredges_t.h"
43 #include "irflag_t.h"
44 #include "error.h"
45
46 #include "gen_ir_cons.c.inl"
47
48 /**
49  * Language dependent variable initialization callback.
50  */
51 static uninitialized_local_variable_func_t *default_initialize_local_variable = NULL;
52
53 ir_node *new_rd_Const_long(dbg_info *db, ir_graph *irg, ir_mode *mode,
54                            long value)
55 {
56         return new_rd_Const(db, irg, new_tarval_from_long(value, mode));
57 }
58
59 ir_node *new_rd_defaultProj(dbg_info *db, ir_node *arg, long max_proj)
60 {
61         ir_node *res;
62
63         assert(is_Cond(arg));
64         arg->attr.cond.default_proj = max_proj;
65         res = new_rd_Proj(db, arg, mode_X, max_proj);
66         return res;
67 }
68
69 ir_node *new_rd_ASM(dbg_info *db, ir_node *block, int arity, ir_node *in[],
70                     ir_asm_constraint *inputs, int n_outs,
71                         ir_asm_constraint *outputs, int n_clobber,
72                         ident *clobber[], ident *text)
73 {
74         ir_graph *irg = get_irn_irg(block);
75         ir_node  *res = new_ir_node(db, irg, block, op_ASM, mode_T, arity, in);
76
77         res->attr.assem.pin_state = op_pin_state_pinned;
78         res->attr.assem.input_constraints
79                 = NEW_ARR_D(ir_asm_constraint, irg->obst, arity);
80         res->attr.assem.output_constraints
81                 = NEW_ARR_D(ir_asm_constraint, irg->obst, n_outs);
82         res->attr.assem.clobbers = NEW_ARR_D(ident *, irg->obst, n_clobber);
83         res->attr.assem.text     = text;
84
85         memcpy(res->attr.assem.input_constraints,  inputs,  sizeof(inputs[0]) * arity);
86         memcpy(res->attr.assem.output_constraints, outputs, sizeof(outputs[0]) * n_outs);
87         memcpy(res->attr.assem.clobbers, clobber, sizeof(clobber[0]) * n_clobber);
88
89         irn_verify_irg(res, irg);
90         res = optimize_node(res);
91         return res;
92 }
93
94 ir_node *new_rd_simpleSel(dbg_info *db, ir_node *block, ir_node *store,
95                           ir_node *objptr, ir_entity *ent)
96 {
97         return new_rd_Sel(db, block, store, objptr, 0, NULL, ent);
98 }
99
100 ir_node *new_rd_SymConst(dbg_info *db, ir_graph *irg, ir_mode *mode,
101                          symconst_symbol value, symconst_kind symkind)
102 {
103         ir_node *block = get_irg_start_block(irg);
104         ir_node *res   = new_ir_node(db, irg, block, op_SymConst, mode, 0, NULL);
105         res->attr.symc.kind = symkind;
106         res->attr.symc.sym  = value;
107
108         irn_verify_irg(res, irg);
109         res = optimize_node(res);
110         return res;
111 }
112
113 ir_node *new_rd_SymConst_addr_ent(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_entity *symbol)
114 {
115         symconst_symbol sym;
116         sym.entity_p = symbol;
117         return new_rd_SymConst(db, irg, mode, sym, symconst_addr_ent);
118 }
119
120 ir_node *new_rd_SymConst_ofs_ent(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_entity *symbol)
121 {
122         symconst_symbol sym;
123         sym.entity_p = symbol;
124         return new_rd_SymConst(db, irg, mode, sym, symconst_ofs_ent);
125 }
126
127 ir_node *new_rd_SymConst_type_tag(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_type *symbol)
128 {
129         symconst_symbol sym;
130         sym.type_p = symbol;
131         return new_rd_SymConst(db, irg, mode, sym, symconst_type_tag);
132 }
133
134 ir_node *new_rd_SymConst_size(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_type *symbol)
135 {
136         symconst_symbol sym;
137         sym.type_p = symbol;
138         return new_rd_SymConst(db, irg, mode, sym, symconst_type_size);
139 }
140
141 ir_node *new_rd_SymConst_align(dbg_info *db, ir_graph *irg, ir_mode *mode, ir_type *symbol)
142 {
143         symconst_symbol sym;
144         sym.type_p = symbol;
145         return new_rd_SymConst(db, irg, mode, sym, symconst_type_align);
146 }
147
148 ir_node *new_r_Const_long(ir_graph *irg, ir_mode *mode, long value)
149 {
150         return new_rd_Const_long(NULL, irg, mode, value);
151 }
152 ir_node *new_r_SymConst(ir_graph *irg, ir_mode *mode, symconst_symbol value,
153                         symconst_kind symkind)
154 {
155         return new_rd_SymConst(NULL, irg, mode, value, symkind);
156 }
157 ir_node *new_r_simpleSel(ir_node *block, ir_node *store, ir_node *objptr,
158                          ir_entity *ent)
159 {
160         return new_rd_Sel(NULL, block, store, objptr, 0, NULL, ent);
161 }
162 ir_node *new_r_defaultProj(ir_node *arg, long max_proj)
163 {
164         return new_rd_defaultProj(NULL, arg, max_proj);
165 }
166 ir_node *new_r_ASM(ir_node *block,
167                    int arity, ir_node *in[], ir_asm_constraint *inputs,
168                    int n_outs, ir_asm_constraint *outputs,
169                    int n_clobber, ident *clobber[], ident *text)
170 {
171         return new_rd_ASM(NULL, block, arity, in, inputs, n_outs, outputs, n_clobber, clobber, text);
172 }
173
174 /** Creates a Phi node with 0 predecessors. */
175 static inline ir_node *new_rd_Phi0(dbg_info *dbgi, ir_node *block,
176                                    ir_mode *mode, int pos)
177 {
178         ir_graph *irg = get_irn_irg(block);
179         ir_node  *res = new_ir_node(dbgi, irg, block, op_Phi, mode, 0, NULL);
180         res->attr.phi.u.pos = pos;
181         irn_verify_irg(res, irg);
182         return res;
183 }
184
185 static ir_node *get_r_value_internal(ir_node *block, int pos, ir_mode *mode);
186
187 static void try_remove_unnecessary_phi(ir_node *phi)
188 {
189         ir_node *phi_value = NULL;
190         int      arity     = get_irn_arity(phi);
191         int      i;
192
193         /* see if all inputs are either pointing to a single value or
194          * are self references */
195         for (i = 0; i < arity; ++i) {
196                 ir_node *in = get_irn_n(phi, i);
197                 if (in == phi)
198                         continue;
199                 if (in == phi_value)
200                         continue;
201                 /** found a different value from the one we already found, can't remove
202                  * the phi (yet) */
203                 if (phi_value != NULL)
204                         return;
205                 phi_value = in;
206         }
207         if (phi_value == NULL)
208                 return;
209
210         /* if we're here then all phi inputs have been either phi_value
211          * or self-references, we can replace the phi by phi_value.
212          * We do this with an Id-node */
213         exchange(phi, phi_value);
214
215         /* recursively check phi_value, because it could be that we were the last
216          * phi-node in a loop-body. Then our arguments is an unnecessary phi in
217          * the loop header which can be eliminated now */
218         if (is_Phi(phi_value)) {
219                 try_remove_unnecessary_phi(phi_value);
220         }
221 }
222
223 /**
224  * Computes the predecessors for the real phi node, and then
225  * allocates and returns this node.  The routine called to allocate the
226  * node might optimize it away and return a real value.
227  * This function must be called with an in-array of proper size.
228  */
229 static ir_node *set_phi_arguments(ir_node *phi, int pos)
230 {
231         ir_node  *block        = get_nodes_block(phi);
232         ir_graph *irg          = get_irn_irg(block);
233         int       arity        = get_irn_arity(block);
234         ir_node **in           = ALLOCAN(ir_node*, arity);
235         ir_mode  *mode         = get_irn_mode(phi);
236         int       i;
237
238         /* This loop goes to all predecessor blocks of the block the Phi node
239            is in and there finds the operands of the Phi node by calling
240            get_r_value_internal.  */
241         for (i = 0; i < arity; ++i) {
242                 ir_node *cfgpred = get_Block_cfgpred_block(block, i);
243                 ir_node *value;
244                 if (is_Bad(cfgpred)) {
245                         value = new_r_Bad(irg, mode);
246                 } else {
247                         inc_irg_visited(irg);
248
249                         value = get_r_value_internal(cfgpred, pos, mode);
250                 }
251                 in[i] = value;
252         }
253
254         phi->attr.phi.u.backedge = new_backedge_arr(irg->obst, arity);
255         set_irn_in(phi, arity, in);
256         set_irn_op(phi, op_Phi);
257
258         irn_verify_irg(phi, irg);
259
260         /* Memory Phis in endless loops must be kept alive.
261            As we can't distinguish these easily we keep all of them alive. */
262         if (is_Phi(phi) && mode == mode_M)
263                 add_End_keepalive(get_irg_end(irg), phi);
264
265         try_remove_unnecessary_phi(phi);
266         return phi;
267 }
268
269 /**
270  * This function returns the last definition of a value.  In case
271  * this value was last defined in a previous block, Phi nodes are
272  * inserted.  If the part of the firm graph containing the definition
273  * is not yet constructed, a dummy Phi node is returned.
274  *
275  * @param block   the current block
276  * @param pos     the value number of the value searched
277  * @param mode    the mode of this value (needed for Phi construction)
278  */
279 static ir_node *get_r_value_internal(ir_node *block, int pos, ir_mode *mode)
280 {
281         ir_node  *res = block->attr.block.graph_arr[pos];
282         ir_graph *irg = get_irn_irg(block);
283         if (res != NULL)
284                 return res;
285
286         /* We ran into a cycle. This may happen in unreachable loops. */
287         if (irn_visited_else_mark(block)) {
288                 /* Since the loop is unreachable, return a Bad. */
289                 return new_r_Bad(irg, mode);
290         }
291
292         /* in a matured block we can immediately determine the phi arguments */
293         if (get_Block_matured(block)) {
294                 int arity = get_irn_arity(block);
295                 /* no predecessors: use unknown value */
296                 if (arity == 0 && block == get_irg_start_block(get_irn_irg(block))) {
297                         if (default_initialize_local_variable != NULL) {
298                                 ir_node *rem = get_r_cur_block(irg);
299                                 set_r_cur_block(irg, block);
300                                 res = default_initialize_local_variable(irg, mode, pos - 1);
301                                 set_r_cur_block(irg, rem);
302                         } else {
303                                 res = new_r_Unknown(irg, mode);
304                         }
305                 /* one predecessor just use its value */
306                 } else if (arity == 1) {
307                         ir_node *cfgpred = get_Block_cfgpred(block, 0);
308                         if (is_Bad(cfgpred)) {
309                                 res = new_r_Bad(irg, mode);
310                         } else {
311                                 ir_node *cfgpred_block = get_nodes_block(cfgpred);
312                                 res = get_r_value_internal(cfgpred_block, pos, mode);
313                         }
314                 /* multiple predecessors construct Phi */
315                 } else {
316                         res = new_rd_Phi0(NULL, block, mode, pos);
317                         /* enter phi0 into our variable value table to break cycles
318                          * arising from set_phi_arguments */
319                         block->attr.block.graph_arr[pos] = res;
320                         res = set_phi_arguments(res, pos);
321                 }
322         } else {
323                 /* in case of immature block we have to keep a Phi0 */
324                 res = new_rd_Phi0(NULL, block, mode, pos);
325                 /* enqueue phi so we can set arguments once the block matures */
326                 res->attr.phi.next     = block->attr.block.phis;
327                 block->attr.block.phis = res;
328         }
329         block->attr.block.graph_arr[pos] = res;
330         return res;
331 }
332
333 /* ************************************************************************** */
334
335 /*
336  * Finalize a Block node, when all control flows are known.
337  * Acceptable parameters are only Block nodes.
338  */
339 void mature_immBlock(ir_node *block)
340 {
341         size_t   n_preds;
342         ir_node  *next;
343         ir_node  *phi;
344         ir_graph *irg;
345
346         assert(is_Block(block));
347         if (get_Block_matured(block))
348                 return;
349
350         irg     = get_irn_irg(block);
351         n_preds = ARR_LEN(block->in) - 1;
352         /* Fix block parameters */
353         block->attr.block.backedge = new_backedge_arr(irg->obst, n_preds);
354
355         /* Traverse a chain of Phi nodes attached to this block and mature
356         these, too. */
357         for (phi = block->attr.block.phis; phi != NULL; phi = next) {
358                 ir_node *new_value;
359                 int      pos = phi->attr.phi.u.pos;
360
361                 next = phi->attr.phi.next;
362                 new_value = set_phi_arguments(phi, pos);
363                 if (block->attr.block.graph_arr[pos] == phi) {
364                         block->attr.block.graph_arr[pos] = new_value;
365                 }
366         }
367
368         set_Block_matured(block, 1);
369
370         /* Now, as the block is a finished Firm node, we can optimize it.
371            Since other nodes have been allocated since the block was created
372            we can not free the node on the obstack.  Therefore we have to call
373            optimize_in_place().
374            Unfortunately the optimization does not change a lot, as all allocated
375            nodes refer to the unoptimized node.
376            We can call optimize_in_place_2(), as global cse has no effect on blocks.
377          */
378         irn_verify_irg(block, irg);
379         block = optimize_in_place_2(block);
380 }
381
382 ir_node *new_d_Const_long(dbg_info *db, ir_mode *mode, long value)
383 {
384         assert(get_irg_phase_state(current_ir_graph) == phase_building);
385         return new_rd_Const_long(db, current_ir_graph, mode, value);
386 }
387
388 ir_node *new_d_defaultProj(dbg_info *db, ir_node *arg, long max_proj)
389 {
390         ir_node *res;
391         assert(is_Cond(arg) || is_Bad(arg));
392         assert(get_irg_phase_state(current_ir_graph) == phase_building);
393         if (is_Cond(arg))
394                 arg->attr.cond.default_proj = max_proj;
395         res = new_d_Proj(db, arg, mode_X, max_proj);
396         return res;
397 }
398
399 ir_node *new_d_simpleSel(dbg_info *db, ir_node *store, ir_node *objptr,
400                          ir_entity *ent)
401 {
402         assert(get_irg_phase_state(current_ir_graph) == phase_building);
403         return new_rd_Sel(db, current_ir_graph->current_block,
404                           store, objptr, 0, NULL, ent);
405 }
406
407 ir_node *new_d_SymConst(dbg_info *db, ir_mode *mode, symconst_symbol value,
408                         symconst_kind kind)
409 {
410         assert(get_irg_phase_state(current_ir_graph) == phase_building);
411         return new_rd_SymConst(db, current_ir_graph, mode, value, kind);
412 }
413
414 ir_node *new_d_ASM(dbg_info *db, int arity, ir_node *in[],
415                    ir_asm_constraint *inputs,
416                    int n_outs, ir_asm_constraint *outputs, int n_clobber,
417                    ident *clobber[], ident *text)
418 {
419         assert(get_irg_phase_state(current_ir_graph) == phase_building);
420         return new_rd_ASM(db, current_ir_graph->current_block, arity, in, inputs,
421                           n_outs, outputs, n_clobber, clobber, text);
422 }
423
424 ir_node *new_rd_strictConv(dbg_info *dbgi, ir_node *block, ir_node * irn_op, ir_mode * mode)
425 {
426         ir_node *res;
427         ir_graph *irg = get_Block_irg(block);
428
429         ir_node *in[1];
430         in[0] = irn_op;
431
432         res = new_ir_node(dbgi, irg, block, op_Conv, mode, 1, in);
433         res->attr.conv.strict = 1;
434         irn_verify_irg(res, irg);
435         res = optimize_node(res);
436         return res;
437 }
438
439 ir_node *new_r_strictConv(ir_node *block, ir_node * irn_op, ir_mode * mode)
440 {
441         return new_rd_strictConv(NULL, block, irn_op, mode);
442 }
443
444 ir_node *new_d_strictConv(dbg_info *dbgi, ir_node * irn_op, ir_mode * mode)
445 {
446         ir_node *res;
447         assert(get_irg_phase_state(current_ir_graph) == phase_building);
448         res = new_rd_strictConv(dbgi, current_ir_graph->current_block, irn_op, mode);
449         return res;
450 }
451
452 ir_node *new_strictConv(ir_node * irn_op, ir_mode * mode)
453 {
454         return new_d_strictConv(NULL, irn_op, mode);
455 }
456
457 ir_node *new_rd_DivRL(dbg_info *dbgi, ir_node *block, ir_node * irn_mem, ir_node * irn_left, ir_node * irn_right, ir_mode* resmode, op_pin_state pin_state)
458 {
459         ir_node *res;
460         ir_graph *irg = get_Block_irg(block);
461
462         ir_node *in[3];
463         in[0] = irn_mem;
464         in[1] = irn_left;
465         in[2] = irn_right;
466
467         res = new_ir_node(dbgi, irg, block, op_Div, mode_T, 3, in);
468         res->attr.div.resmode = resmode;
469         res->attr.div.no_remainder = 1;
470         res->attr.div.exc.pin_state = pin_state;
471         irn_verify_irg(res, irg);
472         res = optimize_node(res);
473         return res;
474 }
475
476 ir_node *new_r_DivRL(ir_node *block, ir_node * irn_mem, ir_node * irn_left, ir_node * irn_right, ir_mode* resmode, op_pin_state pin_state)
477 {
478         return new_rd_DivRL(NULL, block, irn_mem, irn_left, irn_right, resmode, pin_state);
479 }
480
481 ir_node *new_d_DivRL(dbg_info *dbgi, ir_node * irn_mem, ir_node * irn_left, ir_node * irn_right, ir_mode* resmode, op_pin_state pin_state)
482 {
483         ir_node *res;
484         assert(get_irg_phase_state(current_ir_graph) == phase_building);
485         res = new_rd_DivRL(dbgi, current_ir_graph->current_block, irn_mem, irn_left, irn_right, resmode, pin_state);
486         return res;
487 }
488
489 ir_node *new_DivRL(ir_node * irn_mem, ir_node * irn_left, ir_node * irn_right, ir_mode* resmode, op_pin_state pin_state)
490 {
491         return new_d_DivRL(NULL, irn_mem, irn_left, irn_right, resmode, pin_state);
492 }
493
494 ir_node *new_rd_immBlock(dbg_info *dbgi, ir_graph *irg)
495 {
496         ir_node *res;
497
498         assert(get_irg_phase_state(irg) == phase_building);
499         /* creates a new dynamic in-array as length of in is -1 */
500         res = new_ir_node(dbgi, irg, NULL, op_Block, mode_BB, -1, NULL);
501
502         set_Block_matured(res, 0);
503         res->attr.block.irg.irg     = irg;
504         res->attr.block.backedge    = NULL;
505         res->attr.block.in_cg       = NULL;
506         res->attr.block.cg_backedge = NULL;
507         res->attr.block.extblk      = NULL;
508         res->attr.block.entity      = NULL;
509
510         set_Block_block_visited(res, 0);
511
512         /* Create and initialize array for Phi-node construction. */
513         res->attr.block.graph_arr = NEW_ARR_D(ir_node *, irg->obst, irg->n_loc);
514         memset(res->attr.block.graph_arr, 0, sizeof(ir_node*) * irg->n_loc);
515
516         /* Immature block may not be optimized! */
517         irn_verify_irg(res, irg);
518
519         return res;
520 }
521
522 ir_node *new_r_immBlock(ir_graph *irg)
523 {
524         return new_rd_immBlock(NULL, irg);
525 }
526
527 ir_node *new_d_immBlock(dbg_info *dbgi)
528 {
529         return new_rd_immBlock(dbgi, current_ir_graph);
530 }
531
532 ir_node *new_immBlock(void)
533 {
534         return new_rd_immBlock(NULL, current_ir_graph);
535 }
536
537 void add_immBlock_pred(ir_node *block, ir_node *jmp)
538 {
539         int n = ARR_LEN(block->in) - 1;
540
541         assert(is_Block(block) && "Error: Must be a Block");
542         assert(!get_Block_matured(block) && "Error: Block already matured!\n");
543         assert(is_ir_node(jmp));
544
545         ARR_APP1(ir_node *, block->in, jmp);
546         /* Call the hook */
547         hook_set_irn_n(block, n, jmp, NULL);
548 }
549
550 void set_cur_block(ir_node *target)
551 {
552         set_r_cur_block(current_ir_graph, target);
553 }
554
555 void set_r_cur_block(ir_graph *irg, ir_node *target)
556 {
557         assert(target == NULL || get_irn_mode(target) == mode_BB);
558         assert(target == NULL || get_irn_irg(target)  == irg);
559         irg->current_block = target;
560 }
561
562 ir_node *get_r_cur_block(ir_graph *irg)
563 {
564         return irg->current_block;
565 }
566
567 ir_node *get_cur_block(void)
568 {
569         return get_r_cur_block(current_ir_graph);
570 }
571
572 ir_node *get_r_value(ir_graph *irg, int pos, ir_mode *mode)
573 {
574         assert(get_irg_phase_state(irg) == phase_building);
575         assert(pos >= 0);
576         inc_irg_visited(irg);
577
578         return get_r_value_internal(irg->current_block, pos + 1, mode);
579 }
580
581 ir_node *get_value(int pos, ir_mode *mode)
582 {
583         return get_r_value(current_ir_graph, pos, mode);
584 }
585
586 /**
587  * helper function for guess_mode: recursively look for a definition for
588  * local variable @p pos, returns its mode if found.
589  */
590 static ir_mode *guess_recursively(ir_node *block, int pos)
591 {
592         ir_node *value;
593         int      n_preds;
594         int      i;
595
596         if (irn_visited_else_mark(block))
597                 return NULL;
598
599         /* already have a defintion -> we can simply look at its mode */
600         value = block->attr.block.graph_arr[pos];
601         if (value != NULL)
602                 return get_irn_mode(value);
603
604         /* now we try to guess, by looking at the predecessor blocks */
605         n_preds = get_irn_arity(block);
606         for (i = 0; i < n_preds; ++i) {
607                 ir_node *pred_block = get_Block_cfgpred_block(block, i);
608                 ir_mode *mode       = guess_recursively(pred_block, pos);
609                 if (mode != NULL)
610                         return mode;
611         }
612
613         /* no way to guess */
614         return NULL;
615 }
616
617 ir_mode *ir_r_guess_mode(ir_graph *irg, int pos)
618 {
619         ir_node  *block = irg->current_block;
620         ir_node  *value = block->attr.block.graph_arr[pos+1];
621         ir_mode  *mode;
622
623         /* already have a defintion -> we can simply look at its mode */
624         if (value != NULL)
625                 return get_irn_mode(value);
626
627         ir_reserve_resources(irg, IR_RESOURCE_IRN_VISITED);
628         inc_irg_visited(irg);
629         mode = guess_recursively(block, pos+1);
630         ir_free_resources(irg, IR_RESOURCE_IRN_VISITED);
631
632         return mode;
633 }
634
635 ir_mode *ir_guess_mode(int pos)
636 {
637         return ir_r_guess_mode(current_ir_graph, pos);
638 }
639
640 void set_r_value(ir_graph *irg, int pos, ir_node *value)
641 {
642         assert(get_irg_phase_state(irg) == phase_building);
643         assert(pos >= 0);
644         assert(pos+1 < irg->n_loc);
645         assert(is_ir_node(value));
646         irg->current_block->attr.block.graph_arr[pos + 1] = value;
647 }
648
649 void set_value(int pos, ir_node *value)
650 {
651         set_r_value(current_ir_graph, pos, value);
652 }
653
654 int r_find_value(ir_graph *irg, ir_node *value)
655 {
656         size_t i;
657         ir_node *bl = irg->current_block;
658
659         for (i = ARR_LEN(bl->attr.block.graph_arr); i > 1;) {
660                 if (bl->attr.block.graph_arr[--i] == value)
661                         return i - 1;
662         }
663         return -1;
664 }
665
666 int find_value(ir_node *value)
667 {
668         return r_find_value(current_ir_graph, value);
669 }
670
671 ir_node *get_r_store(ir_graph *irg)
672 {
673         assert(get_irg_phase_state(irg) == phase_building);
674         inc_irg_visited(irg);
675         return get_r_value_internal(irg->current_block, 0, mode_M);
676 }
677
678 ir_node *get_store(void)
679 {
680         return get_r_store(current_ir_graph);
681 }
682
683 void set_r_store(ir_graph *irg, ir_node *store)
684 {
685         ir_node *load, *pload, *pred, *in[2];
686
687         assert(get_irg_phase_state(irg) == phase_building);
688         /* Beware: due to dead code elimination, a store might become a Bad node even in
689            the construction phase. */
690         assert((get_irn_mode(store) == mode_M || is_Bad(store)) && "storing non-memory node");
691
692         if (get_opt_auto_create_sync()) {
693                 /* handle non-volatile Load nodes by automatically creating Sync's */
694                 load = skip_Proj(store);
695                 if (is_Load(load) && get_Load_volatility(load) == volatility_non_volatile) {
696                         pred = get_Load_mem(load);
697
698                         if (is_Sync(pred)) {
699                                 /* a Load after a Sync: move it up */
700                                 ir_node *mem = skip_Proj(get_Sync_pred(pred, 0));
701
702                                 set_Load_mem(load, get_memop_mem(mem));
703                                 add_Sync_pred(pred, store);
704                                 store = pred;
705                         } else {
706                                 pload = skip_Proj(pred);
707                                 if (is_Load(pload) && get_Load_volatility(pload) == volatility_non_volatile) {
708                                         /* a Load after a Load: create a new Sync */
709                                         set_Load_mem(load, get_Load_mem(pload));
710
711                                         in[0] = pred;
712                                         in[1] = store;
713                                         store = new_r_Sync(irg->current_block, 2, in);
714                                 }
715                         }
716                 }
717         }
718         irg->current_block->attr.block.graph_arr[0] = store;
719 }
720
721 void set_store(ir_node *store)
722 {
723         set_r_store(current_ir_graph, store);
724 }
725
726 void keep_alive(ir_node *ka)
727 {
728         ir_graph *irg = get_irn_irg(ka);
729         add_End_keepalive(get_irg_end(irg), ka);
730 }
731
732 void ir_set_uninitialized_local_variable_func(
733                 uninitialized_local_variable_func_t *func)
734 {
735         default_initialize_local_variable = func;
736 }
737
738 void irg_finalize_cons(ir_graph *irg)
739 {
740         set_irg_phase_state(irg, phase_high);
741 }
742
743 void irp_finalize_cons(void)
744 {
745         size_t i, n;
746         for (i = 0, n = get_irp_n_irgs(); i < n; ++i) {
747                 irg_finalize_cons(get_irp_irg(i));
748         }
749         irp->phase_state = phase_high;
750 }
751
752 ir_node *new_Const_long(ir_mode *mode, long value)
753 {
754         return new_d_Const_long(NULL, mode, value);
755 }
756
757 ir_node *new_SymConst(ir_mode *mode, symconst_symbol value, symconst_kind kind)
758 {
759         return new_d_SymConst(NULL, mode, value, kind);
760 }
761 ir_node *new_simpleSel(ir_node *store, ir_node *objptr, ir_entity *ent)
762 {
763         return new_d_simpleSel(NULL, store, objptr, ent);
764 }
765 ir_node *new_defaultProj(ir_node *arg, long max_proj)
766 {
767         return new_d_defaultProj(NULL, arg, max_proj);
768 }
769 ir_node *new_ASM(int arity, ir_node *in[], ir_asm_constraint *inputs,
770                  int n_outs, ir_asm_constraint *outputs,
771                  int n_clobber, ident *clobber[], ident *text)
772 {
773         return new_d_ASM(NULL, arity, in, inputs, n_outs, outputs, n_clobber, clobber, text);
774 }
775
776 ir_node *new_r_Anchor(ir_graph *irg)
777 {
778         ir_node *in[anchor_last];
779         ir_node *res;
780         size_t   i;
781         memset(in, 0, sizeof(in));
782         res = new_ir_node(NULL, irg, NULL, op_Anchor, mode_ANY, anchor_last, in);
783         res->attr.anchor.irg.irg = irg;
784
785         /* hack to get get_irn_irg working: set block to ourself and allow
786          * get_Block_irg for anchor */
787         res->in[0] = res;
788
789         /* we can't have NULL inputs so reference ourselfes for now */
790         for (i = 0; i < (size_t)anchor_last; ++i) {
791                 set_irn_n(res, i, res);
792         }
793
794         return res;
795 }
796
797 ir_node *new_r_Block_noopt(ir_graph *irg, int arity, ir_node *in[])
798 {
799         ir_node *res = new_ir_node(NULL, irg, NULL, op_Block, mode_BB, arity, in);
800         res->attr.block.irg.irg = irg;
801         res->attr.block.backedge = new_backedge_arr(irg->obst, arity);
802         set_Block_matured(res, 1);
803         /* Create and initialize array for Phi-node construction. */
804         if (get_irg_phase_state(irg) == phase_building) {
805                 res->attr.block.graph_arr = NEW_ARR_D(ir_node *, irg->obst, irg->n_loc);
806                 memset(res->attr.block.graph_arr, 0, irg->n_loc * sizeof(ir_node*));
807         }
808         irn_verify_irg(res, irg);
809         return res;
810 }