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