bring back Carry and Borrow (firm_decomp apparently uses it) and add a note that...
[libfirm] / include / libfirm / ircons.h
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
26  * @version $Id$
27  */
28
29 /**
30  *  @file
31  *
32  *  documentation no more supported since 2001
33  *
34  *  IR node construction.
35  *
36  *    This file documents all datatypes and constructors needed to
37  *    build a FIRM representation of a procedure.  The constructors are
38  *    also implemented in this file.
39  *
40  *    The documentation also gives a short manual how to use the library.
41  *
42  *    For extensive documentation of FIRM see UKA Techreport 1999-14.
43  *
44  *
45  *    Three kinds of nodes
46  *    --------------------
47  *
48  *      There are three kinds of nodes known to the IR:  entities,
49  *      types, and ir_nodes
50  *
51  *      + ir_nodes are the actual nodes of the FIRM intermediate representation.
52  *        They represent operations on the data of the program and control flow
53  *        operations.
54  *
55  *      + entity ==> implemented in entity.h
56  *        Refers to a single entity of the compiled program, e.g. a field of a
57  *        class or a method.  If a method or variable can not be assigned to
58  *        a method or class or the like, it is a global object.
59  *
60  *      + types ==> implemented in type.h
61  *        With types type information is represented.  There are several type
62  *       nodes.
63  *
64  *    Implementation of the FIRM operations: ir_node
65  *    ----------------------------------------------
66  *
67  *      Ir_nodes represent operations on the data of the program and control flow
68  *      operations.  Examples of ir_nodes:  Add, Jmp, Cmp
69  *
70  *      FIRM is a dataflow graph.  A dataflow graph is a directed graph,
71  *      so that every node has incoming and outgoing edges.  A node is
72  *      executable if every input at its incoming edges is available.
73  *      Execution of the dataflow graph is started at the Start node which
74  *      has no incoming edges and ends when the End node executes, even if
75  *      there are still executable or not executed nodes.  (Is this true,
76  *      or must all executable nodes be executed?)  (There are exceptions
77  *      to the dataflow paradigma that all inputs have to be available
78  *      before a node can execute: Phi, Block.  See UKA Techreport
79  *      1999-14.)
80  *
81  *      The implementation of FIRM differs from the view as a dataflow
82  *      graph.  To allow fast traversion of the graph edges are
83  *      implemented as C-pointers.  Inputs to nodes are not ambiguous, the
84  *      results can be used by several other nodes.  Each input can be
85  *      implemented as a single pointer to a predecessor node, outputs
86  *      need to be lists of pointers to successors.  Therefore a node
87  *      contains pointers to its predecessors so that the implementation is a
88  *      dataflow graph with reversed edges.  It has to be traversed bottom
89  *      up.
90  *
91  *      All nodes of the IR have the same basic structure.  They are
92  *      distinguished by a field containing the opcode.
93  *
94  *      The fields of an ir_node:
95  *
96  *      kind             A firm_kind tag containing k_ir_node.  This is useful for
97  *                       dynamically checking the type of a node.
98  *
99  *      *op              This ir_op gives the opcode as a tag and a string
100  *                       and the number of attributes of an ir_node.  There is
101  *                       one statically allocated struct ir_op for each opcode.
102  *
103  *      *mode            The ir_mode of the operation represented by this firm
104  *                       node.  The mode of the operation is the mode of its
105  *                       result.  A Firm mode is a datatype as known to the
106  *                       target, not a type of the source language.
107  *
108  *      visit            A flag for traversing the IR.
109  *
110  *      **in             An array with pointers to the node's predecessors.
111  *
112  *      *link            A pointer to an ir_node.  With this pointer all Phi nodes
113  *                       are attached to a Block, i.e. a Block points to its
114  *                       first Phi node, this node points to the second Phi node
115  *                       in the Block and so forth.  Used in mature_immBlock
116  *                       to find all Phi nodes to be matured.  It's also used to
117  *                       annotate a node with a better, optimized version of it.
118  *
119  *      attr             An attr struct containing the attributes of the nodes. The
120  *                       attributes depend on the opcode of the node.  The number
121  *                       of these attributes is given in op.
122  *
123  *    The struct ir_op
124  *    ----------------
125  *                       Not yet documented. See irop.h.
126  *
127  *    The struct ir_mode
128  *    ------------------
129  *                       Not yet documented. See irmode.h.
130  *
131  *    GLOBAL VARIABLES -- now also fields of ir_graph.
132  *    ================
133  *
134  *    current_ir_graph   Points to the current ir_graph.  All constructors for
135  *                       nodes add nodes to this graph.
136  *
137  *    ir_visited         An int used as flag to traverse the ir_graph.
138  *
139  *    block_visited      An int used as a flag to traverse block nodes in the
140  *                       graph.
141  *
142  *                       Others not yet documented.
143  *
144  *
145  *
146  *    CONSTRUCTOR FOR IR_GRAPH --> see irgraph.h
147  *    ========================
148  *
149  *
150  *    PROCEDURE TO CONSTRUCT AN IR GRAPH --> see also Firm tutorial
151  *    ==================================
152  *
153  *    This library supplies several interfaces to construct a FIRM graph for
154  *    a program:
155  *    - A "comfortable" interface generating SSA automatically.  Automatically
156  *      computed predecessors of nodes need not be specified in the constructors.
157  *      (new_<Node> constructurs and a set of additional routines.)
158  *    - A less comfortable interface where all predecessors except the block
159  *      an operation belongs to need to be specified.  SSA must be constructed
160  *      by hand.  (new_<Node> constructors and set_cur_block()).  This interface
161  *      is called "block oriented".  It automatically calles the local optimizations
162  *      for each new node.
163  *    - An even less comfortable interface where the block needs to be specified
164  *      explicitly.  This is called the "raw" interface. (new_r_<Node>
165  *      constructors).  These nodes are not optimized.
166  *
167  *    To use the functionality of the comfortable interface correctly the Front
168  *    End needs to follow certain protocols.  This is explained in the following.
169  *    To build a correct IR with the other interfaces study the semantics of
170  *    the firm node (See tech-reprot UKA 1999-14).  For the construction of
171  *    types and entities see the documentation in those modules.
172  *
173  *    First the Frontend needs to decide which variables and values used in
174  *    a procedure can be represented by dataflow edges.  These are variables
175  *    that need not be saved to memory as they cause no side effects visible
176  *    out of the procedure.  Often these are all compiler generated
177  *    variables and simple local variables of the procedure as integers,
178  *    reals and pointers.  The frontend has to count and number these variables.
179  *
180  *    First an ir_graph needs to be constructed with new_ir_graph.  The
181  *    constructor gets the number of local variables.  The graph is held in the
182  *    global variable irg.
183  *
184  *    Now the construction of the procedure can start.  Several basic blocks can
185  *    be constructed in parallel, but the code within each block needs to
186  *    be constructed (almost) in program order.
187  *
188  *    A global variable holds the current basic block.  All (non block) nodes
189  *    generated are added to this block.  The current block can be set with
190  *    set_cur_block(block).  If several blocks are constructed in parallel block
191  *    switches need to be performed constantly.
192  *
193  *    To generate a Block node (with the comfortable interface), its predecessor
194  *    control flow nodes need not be known.  In case of cyclic control flow these
195  *    can not be known when the block is constructed.  With add_immBlock_pred(block,
196  *    cfnode) predecessors can be added to the block.  If all predecessors are
197  *    added to the block mature_immBlock(b) needs to be called.  Calling mature_immBlock
198  *    early improves the efficiency of the Phi node construction algorithm.
199  *    But if several  blocks are constructed at once, mature_immBlock must only
200  *    be called after performing all set_values and set_stores in the block!
201  *    (See documentation of new_immBlock constructor.)
202  *
203  *    The constructors of arithmetic nodes require that their predecessors
204  *    are mentioned.  Sometimes these are available in the Frontend as the
205  *    predecessors have just been generated by the frontend.  If they are local
206  *    values, the predecessors can be obtained from the library with a call to
207  *    get_value(local_val_nr).  (local_val_nr needs to be administered by
208  *    the Frontend.)  A call to get_value triggers the generation of Phi nodes.
209  *    If an arithmetic operation produces a local value, this value needs to be
210  *    passed to the library by set_value(node, local_val_nr).
211  *    In straight line code these two operations just remember and return the
212  *    pointer to nodes producing the value.  If the value passes block boundaries
213  *    Phi nodes can be inserted.
214  *    Similar routines exist to manage the Memory operands: set_store and
215  *    get_store.
216  *
217  *    Several nodes produce more than one result.  An example is the Div node.
218  *    Such nodes return tuples of values.  From these individual values can be
219  *    extracted by proj nodes.
220  *
221  *    The following example illustrates the construction of a simple basic block
222  *    with two predecessors stored in variables cf_pred1 and cf_pred2, containing
223  *    the code
224  *      a = a div a;
225  *    and finally jumping to an other block.  The variable a got the local_val_nr
226  *    42 by the frontend.
227  *
228  *    ir_node *this_block, *cf_pred1, *cf_pred2, *a_val, *mem, *div, *res, *cf_op;
229  *
230  *    this_block = new_immBlock();
231  *    add_immBlock_pred(this_block, cf_pred1);
232  *    add_immBlock_pred(this_block, cf_pred2);
233  *    mature_immBlock(this_block);
234  *    a_val = get_value(42, mode_Iu);
235  *    mem = get_store();
236  *    div = new_Div(mem, a_val, a_val, mode_Iu);
237  *    mem = new_Proj(div, mode_M, pn_Div_M);   * for the numbers for Proj see docu *
238  *    res = new_Proj(div, mode_Iu, pn_Div_res);
239  *    set_store(mem);
240  *    set_value(res, 42);
241  *    cf_op = new_Jmp();
242  *
243  *    For further information look at the documentation of the nodes and
244  *    constructors and at the paragraph COPING WITH DATA OBJECTS at the
245  *    end of this documentation.
246  *
247  *    The comfortable interface contains the following routines further explained
248  *    below:
249  *
250  *    ir_node *new_immBlock (void);
251  *    ir_node *new_Start    (void);
252  *    ir_node *new_End      (void);
253  *    ir_node *new_Jmp      (void);
254  *    ir_node *new_IJmp     (ir_node *tgt);
255  *    ir_node *new_Cond     (ir_node *c);
256  *    ir_node *new_Return   (ir_node *store, int arity, ir_node **in);
257  *    ir_node *new_Const    (tarval *con);
258  *    ir_node *new_SymConst (ir_mode *mode, symconst_symbol value, symconst_kind kind);
259  *    ir_node *new_simpleSel (ir_node *store, ir_node *objptr, ir_entity *ent);
260  *    ir_node *new_Sel    (ir_node *store, ir_node *objptr, int arity,
261  *                         ir_node **in, ir_entity *ent);
262  *    ir_node *new_Call   (ir_node *store, ir_node *callee, int arity,
263  *                         ir_node **in, type_method *type);
264  *    ir_node *new_Builtin(ir_node *store, ir_builtin_kind kind, int arity,
265  *                         ir_node **in, type_method *type);
266  *    ir_node *new_Add    (ir_node *op1, ir_node *op2, ir_mode *mode);
267  *    ir_node *new_Sub    (ir_node *op1, ir_node *op2, ir_mode *mode);
268  *    ir_node *new_Minus  (ir_node *op,  ir_mode *mode);
269  *    ir_node *new_Mul    (ir_node *op1, ir_node *op2, ir_mode *mode);
270  *    ir_node *new_Mulh   (ir_node *op1, ir_node *op2, ir_mode *mode);
271  *    ir_node *new_Quot   (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state);
272  *    ir_node *new_DivMod (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state);
273  *    ir_node *new_Div    (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state);
274  *    ir_node *new_Mod    (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state;
275  *    ir_node *new_Abs    (ir_node *op,                ir_mode *mode);
276  *    ir_node *new_And    (ir_node *op1, ir_node *op2, ir_mode *mode);
277  *    ir_node *new_Or     (ir_node *op1, ir_node *op2, ir_mode *mode);
278  *    ir_node *new_Eor    (ir_node *op1, ir_node *op2, ir_mode *mode);
279  *    ir_node *new_Not    (ir_node *op,                ir_mode *mode);
280  *    ir_node *new_Shl    (ir_node *op,  ir_node *k,   ir_mode *mode);
281  *    ir_node *new_Shr    (ir_node *op,  ir_node *k,   ir_mode *mode);
282  *    ir_node *new_Shrs   (ir_node *op,  ir_node *k,   ir_mode *mode);
283  *    ir_node *new_Rotl   (ir_node *op,  ir_node *k,   ir_mode *mode);
284  *    ir_node *new_Cmp    (ir_node *op1, ir_node *op2);
285  *    ir_node *new_Conv   (ir_node *op, ir_mode *mode);
286  *    ir_node *new_Cast   (ir_node *op, ir_type *to_tp);
287  *    ir_node *new_Carry  (ir_node *op1, ir_node *op2, ir_mode *mode);
288  *    ir_node *new_Borrow (ir_node *op1, ir_node *op2, ir_mode *mode);
289  *    ir_node *new_Load   (ir_node *store, ir_node *addr, ir_mode *mode, ir_cons_flags flags);
290  *    ir_node *new_Store  (ir_node *store, ir_node *addr, ir_node *val, ir_cons_flags flags);
291  *    ir_node *new_Alloc  (ir_node *store, ir_node *count, ir_type *alloc_type,
292  *                         where_alloc where);
293  *    ir_node *new_Free   (ir_node *store, ir_node *ptr, ir_node *size,
294  *               ir_type *free_type, where_alloc where);
295  *    ir_node *new_Proj   (ir_node *arg, ir_mode *mode, long proj);
296  *    ir_node *new_NoMem  (void);
297  *    ir_node *new_Mux    (ir_node *sel, ir_node *ir_false, ir_node *ir_true, ir_mode *mode);
298  *    ir_node *new_CopyB  (ir_node *store, ir_node *dst, ir_node *src, ir_type *data_type);
299  *    ir_node *new_InstOf (ir_node *store, ir_node obj, ir_type *ent);
300  *    ir_node *new_Raise  (ir_node *store, ir_node *obj);
301  *    ir_node *new_Bound  (ir_node *store, ir_node *idx, ir_node *lower, ir_node *upper);
302  *    ir_node *new_Pin    (ir_node *node);
303  *
304  *    void add_immBlock_pred (ir_node *block, ir_node *jmp);
305  *    void mature_immBlock (ir_node *block);
306  *    void set_cur_block (ir_node *target);
307  *    ir_node *get_value (int pos, ir_mode *mode);
308  *    void set_value (int pos, ir_node *value);
309  *    ir_node *get_store (void);
310  *    void set_store (ir_node *store);
311  *    keep_alive (ir_node ka)
312  *
313  *    IR_NODES AND CONSTRUCTORS FOR IR_NODES
314  *    =======================================
315  *
316  *    All ir_nodes are defined by a common data structure.  They are distinguished
317  *    by their opcode and differ in the number of their attributes.
318  *
319  *    Const nodes are always added to the start block.
320  *    All other constructors add the created node to the current_block.
321  *    swich_block(block) allows to set the current block to block.
322  *
323  *    Watch for my inconsistent use of input and predecessor (dataflow view)
324  *    and `the node points to' (implementation view).
325  *
326  *    The following description of the nodes lists four properties them if these
327  *    are of interest:
328  *     - the parameters to the constructor
329  *     - the inputs of the Firm node
330  *     - the outputs of the Firm node
331  *     - attributes to the node
332  *
333  *    ------------
334  *
335  *    ir_node *new_immBlock (void)
336  *    ----------------------------
337  *
338  *    Creates a new block. When a new block is created it cannot be known how
339  *    many predecessors this block will have in the control flow graph.
340  *    Therefore the list of inputs can not be fixed at creation.  Predecessors
341  *    can be added with add_immBlock_pred (block, control flow operation).
342  *    With every added predecessor the number of inputs to Phi nodes also
343  *    changes.
344  *
345  *    The block can be completed by mature_immBlock(block) if all predecessors are
346  *    known.  If several blocks are built at once, mature_immBlock can only be called
347  *    after set_value has been called for all values that are life at the end
348  *    of the block.  This is necessary so that Phi nodes created mature_immBlock
349  *    get the right predecessors in case of cyclic dependencies.  If all set_values
350  *    of this block are called after maturing it and before calling get_value
351  *    in some block that is control flow dependent on this block, the construction
352  *    is correct.
353  *
354  *    Example for faulty IR construction:  (draw the graph on a paper and you'll
355  *                                          get it ;-)
356  *
357  *      block_before_loop = new_immBlock();
358  *      set_cur_block(block_before_loop);
359  *      set_value(x);
360  *      mature_immBlock(block_before_loop);
361  *      before2header = new_Jmp;
362  *
363  *      loop_header = new_immBlock ();
364  *      set_cur_block(loop_header);
365  *      header2body - new_Jmp();
366  *
367  *      loop_body = new_immBlock ();
368  *      set_cur_block(loop_body);
369  *      body2header = new_Jmp();
370  *
371  *      add_immBlock_pred(loop_header, before2header);
372  *      add_immBlock_pred(loop_header, body2header);
373  *      add_immBlock_pred(loop_body, header2body);
374  *
375  *      mature_immBlock(loop_header);
376  *      mature_immBlock(loop_body);
377  *
378  *      get_value(loop_body, x);   //  gets the Phi in loop_header
379  *      set_value(loop_header, x); //  sets the value the above get_value should
380  *                                 //  have returned!!!
381  *
382  *    Mature_immBlock also fixes the number of inputs to the Phi nodes.  Mature_immBlock
383  *    should be called as early as possible, as afterwards the generation of Phi
384  *   nodes is more efficient.
385  *
386  *    Inputs:
387  *      There is an input for each control flow predecessor of the block.
388  *      The input points to an instruction producing an output of type X.
389  *      Possible predecessors:  Start, Jmp, Cond, Raise or Return or any node
390  *      possibly causing an exception.  (Often the real predecessors are Projs.)
391  *    Output:
392  *      Mode BB (R), all nodes belonging to this block should consume this output.
393  *      As they are strict (except Block and Phi node) it is a necessary condition
394  *      that the block node executed before any other node in this block executes.
395  *    Attributes:
396  *      block.matured  Indicates whether the block is mature.
397  *      block.**graph_arr
398  *                      This attribute contains all local values valid in this
399  *                      block. This is needed to build the Phi nodes and removed
400  *                      if the graph is complete.  This field is used by the
401  *              internal construction algorithm and should not be accessed
402  *              from outside.
403  *
404  *
405  *    ir_node *new_Block (int arity, ir_node **in)
406  *    --------------------------------------------
407  *
408  *    Creates a new Block with the given list of predecessors.  This block
409  *    is mature.  As other constructors calls optimization and verify for the
410  *    block.  If one of the predecessors is Unknown (as it has to be filled in
411  *    later) optimizations are skipped.  This is necessary to
412  *    construct Blocks in loops.
413  *
414  *
415  *    CONTROL FLOW OPERATIONS
416  *    -----------------------
417  *
418  *    In each block there must be exactly one of the control flow
419  *    operations Start, End, Jmp, Cond, Return or Raise.  The output of a
420  *    control flow operation points to the block to be executed next.
421  *
422  *    ir_node *new_Start (void)
423  *    -------------------------
424  *
425  *    Creates a start node.  Not actually needed public.  There is only one such
426  *   node in each procedure which is automatically created by new_ir_graph.
427  *
428  *    Inputs:
429  *      No inputs except the block it belogns to.
430  *    Output:
431  *      A tuple of 4 (5, 6) distinct values. These are labeled by the following
432  *      projection numbers (pn_Start):
433  *      * pn_Start_X_initial_exec    mode X, points to the first block to be exe *                                   cuted.
434  *      * pn_Start_M                 mode M, the global store
435  *      * pn_Start_P_frame_base      mode P, a pointer to the base of the proce  *                                   dures stack frame.
436  *      * pn_Start_P_globals         mode P, a pointer to the part of the memory *                                   containing_all_ global things.
437  *      * pn_Start_T_args            mode T, a tuple containing all arguments of *                                   the procedure.
438  *
439  *
440  *    ir_node *new_End (void)
441  *    -----------------------
442  *
443  *    Creates an end node.  Not actually needed public.  There is only one such
444  *   node in each procedure which is automatically created by new_ir_graph.
445  *
446  *    Inputs:
447  *      No inputs except the block it belongs to.
448  *    Output:
449  *      No output.
450  *
451  *    ir_node *new_Jmp (void)
452  *    -----------------------
453  *
454  *    Creates a Jmp node.
455  *
456  *    Inputs:
457  *      The block the node belongs to
458  *    Output:
459  *      Control flow to the next block.
460  *
461  *    ir_node *new_IJmp (ir_node *tgt)
462  *    -----------------------
463  *
464  *    Creates an IJmp node.
465  *
466  *    Inputs:
467  *      The node that represents the target jump address
468  *    Output:
469  *      Control flow to an unknown target, must be pinned by
470  *      the End node.
471  *
472  *    ir_node *new_Cond (ir_node *c)
473  *    ------------------------------
474  *
475  *    Creates a Cond node.  There are two versions of this node.
476  *
477  *    The Boolean Cond:
478  *    Input:
479  *      A value of mode b.
480  *    Output:
481  *      A tuple of two control flows.  The first is taken if the input is
482  *      false, the second if it is true.
483  *
484  *    The Switch Cond:
485  *    Input:
486  *      A value of mode I_u. (i)
487  *    Output:
488  *      A tuple of n control flows.  If the Cond's input is i, control
489  *      flow will procede along output i. If the input is >= n control
490  *      flow proceeds along output n.
491  *
492  *    ir_node *new_Return (ir_node *store, int arity, ir_node **in)
493  *    -------------------------------------------------------------
494  *
495  *    The return node has as inputs the results of the procedure.  It
496  *    passes the control flow to the end_block.
497  *
498  *    Inputs:
499  *      The memory state.
500  *      All results.
501  *    Output
502  *      Control flow to the end block.
503  *
504  *    ---------
505  *
506  *    ir_node *new_Const (tarval *con)
507  *    -----------------------------------------------
508  *
509  *    Creates a constant in the constant table and adds a Const node
510  *    returning this value to the start block. The mode is derived
511  *    from the tarval.
512  *
513  *    Parameters:
514  *      *con             Points to an entry in the constant table.
515  *                       This pointer is added to the attributes of
516  *                       the node (self->attr.con)
517  *    Inputs:
518  *      No inputs except the block it belogns to.
519  *    Output:
520  *      The constant value.
521  *    Attribute:
522  *      attr.con   A tarval* pointer to the proper entry in the constant
523  *                 table.
524  *
525  *    ir_node *new_SymConst (ir_mode *mode, union symconst_symbol value, symconst_addr_ent kind)
526  *    -----------------------------------------------------------------------------------------
527  *
528  *    There are several symbolic constants:
529  *     symconst_type_tag   The symbolic constant represents a type tag.
530  *     symconst_type_size  The symbolic constant represents the size of a type.
531  *     symconst_type_align The symbolic constant represents the alignment of a type.
532  *     symconst_addr_ent   The symbolic constant represents the address of an entity.
533  *     symconst_ofs_ent    The symbolic constant represents the offset of an
534  *                         entity in its owner type.
535  *     symconst_enum_const The symbolic constant is a enumeration constant of an
536  *                         enumeration type.
537  *
538  *    Parameters
539  *      mode        P for SymConsts representing addresses, Iu otherwise.
540  *      value       The type, ident, entity or enum constant, depending on the
541  *                  kind
542  *      kind        The kind of the symbolic constant, see the list above.
543  *
544  *    Inputs:
545  *      No inputs except the block it belongs to.
546  *    Output:
547  *      A symbolic constant.
548  *
549  *    Attributes:
550  *      attr.i.num       The symconst_addr_ent, i.e. one of
551  *                        -symconst_type_tag
552  *                        -symconst_type_size
553  *                        -symconst_type_align
554  *                        -symconst_addr_ent
555  *
556  *    If the attr.i.num is symconst_type_tag, symconst_type_size or symconst_type_align,
557  *    the node contains an attribute:
558  *
559  *      attr.i.*type,    a pointer to a type_class.
560  *        if it is linkage_ptr_info it contains
561  *      attr.i.*ptrinfo,  an ident holding information for the linker.
562  *
563  *    ---------------
564  *
565  *    ir_node *new_simpleSel (ir_node *store, ir_node *frame, ir_entity *sel)
566  *    -----------------------------------------------------------------------
567  *
568  *
569  *    Selects an entity from a compound type. This entity can be a field or
570  *    a method.
571  *
572  *    Parameters:
573  *      *store     The memory in which the object the entity should be selected
574  *                 from is allocated.
575  *      *frame     The pointer to the object.
576  *      *sel       The entity to select.
577  *
578  *    Inputs:
579  *      The memory containing the object.
580  *      A pointer to the object.
581  *      An unsigned integer.
582  *    Output:
583  *      A pointer to the selected entity.
584  *    Attributes:
585  *      attr.sel   Pointer to the entity
586  *
587  *
588  *    ir_node *new_Sel (ir_node *store, ir_node *frame, int arity, ir_node **in,
589  *    --------------------------------------------------------------------------
590  *                      ir_entity *sel)
591  *                      ---------------
592  *
593  *    Selects a field from an array type.  The entity has as owner the array, as
594  *    type the arrays element type.  The indices to access an array element are
595  *    given also.
596  *
597  *    Parameters:
598  *      *store     The memory in which the object the entity should be selected from
599  *                 is allocated.
600  *      *frame     The pointer to the object.
601  *      *arity     number of array indices.
602  *      *in        array with index inputs to the node.
603  *      *sel       The entity to select.
604  *
605  *    Inputs:
606  *      The memory containing the object.
607  *      A pointer to the object.
608  *      As much unsigned integer as there are array expressions.
609  *    Output:
610  *      A pointer to the selected entity.
611  *    Attributes:
612  *      attr.sel   Pointer to the entity
613  *
614  *    The constructors new_Sel and new_simpleSel generate the same IR nodes.
615  *    simpleSel just sets the arity of the index inputs to zero.
616  *
617  *
618  *    ARITHMETIC OPERATIONS
619  *    ---------------------
620  *
621  *    ir_node *new_Call (ir_node *store, ir_node *callee, int arity, ir_node **in,
622  *    ----------------------------------------------------------------------------
623  *                       type_method *type)
624  *                       ------------------
625  *
626  *    Creates a procedure call.
627  *
628  *    Parameters
629  *      *store           The actual store.
630  *      *callee          A pointer to the called procedure.
631  *      arity            The number of procedure parameters.
632  *      **in             An array with the pointers to the parameters.
633  *                       The constructor copies this array.
634  *      *type            Type information of the procedure called.
635  *
636  *    Inputs:
637  *      The store, the callee and the parameters.
638  *    Output:
639  *      A tuple containing the eventually changed store and the procedure
640  *      results.
641  *    Attributes:
642  *      attr.call        Contains the attributes for the procedure.
643  *
644  *    ir_node *new_Builtin(ir_node *store, ir_builtin_kind kind, int arity, ir_node **in,
645  *    -----------------------------------------------------------------------------------
646  *                       type_method *type)
647  *                       ------------------
648  *
649  *    Creates a builtin call.
650  *
651  *    Parameters
652  *      *store           The actual store.
653  *      kind             Describes the called builtin.
654  *      arity            The number of procedure parameters.
655  *      **in             An array with the pointers to the parameters.
656  *                       The constructor copies this array.
657  *      *type            Type information of the procedure called.
658  *
659  *    Inputs:
660  *      The store, the kind and the parameters.
661  *    Output:
662  *      A tuple containing the eventually changed store and the procedure
663  *      results.
664  *    Attributes:
665  *      attr.builtin     Contains the attributes for the called builtin.
666  *
667  *    ir_node *new_Add (ir_node *op1, ir_node *op2, ir_mode *mode)
668  *    ------------------------------------------------------------
669  *
670  *    Trivial.
671  *
672  *    ir_node *new_Sub (ir_node *op1, ir_node *op2, ir_mode *mode)
673  *    ------------------------------------------------------------
674  *
675  *    Trivial.
676  *
677  *    ir_node *new_Minus (ir_node *op, ir_mode *mode)
678  *    -----------------------------------------------
679  *
680  *    Unary Minus operations on integer and floating point values.
681  *
682  *    ir_node *new_Mul (ir_node *op1, ir_node *op2, ir_mode *mode)
683  *    ------------------------------------------------------------
684  *
685  *    Trivial.
686  *
687  *    ir_node *new_Mulh (ir_node *op1, ir_node *op2, ir_mode *mode)
688  *    ------------------------------------------------------------
689  *
690  *    Returns the high order bits of a n*n=2n multiplication.
691  *
692  *    ir_node *new_Quot (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state)
693  *    -------------------------------------------------------------------------------------------------
694  *
695  *    Quot performs exact division of floating point numbers.  It's mode
696  *    is Tuple, the mode of the result must match the Proj mode
697  *    that extracts the result of the arithmetic operations.
698  *
699  *    Inputs:
700  *      The store needed to model exceptions and the two operands.
701  *    Output:
702  *      A tuple containing a memory and a execution for modeling exceptions
703  *      and the result of the arithmetic operation.
704  *
705  *    ir_node *new_DivMod (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state)
706  *    ---------------------------------------------------------------------------------------------------
707  *
708  *    Performs Div and Mod on integer values.
709  *
710  *    Output:
711  *      A tuple containing a memory and a execution for modeling exceptions
712  *      and the two result of the arithmetic operations.
713  *
714  *    ir_node *new_Div (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state)
715  *    ------------------------------------------------------------------------------------------------
716  *
717  *    Trivial.
718  *
719  *    ir_node *new_Mod (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state)
720  *    ------------------------------------------------------------------------------------------------
721  *
722  *    Trivial.
723  *
724  *    ir_node *new_Abs (ir_node *op, ir_mode *mode)
725  *    ---------------------------------------------
726  *
727  *    Trivial.
728  *
729  *    ir_node *new_And (ir_node *op1, ir_node *op2, ir_mode *mode)
730  *    ------------------------------------------------------------
731  *
732  *    Trivial.
733  *
734  *    ir_node *new_Or (ir_node *op1, ir_node *op2, ir_mode *mode)
735  *    -----------------------------------------------------------
736  *
737  *    Trivial.
738  *
739  *    ir_node *new_Eor (ir_node *op1, ir_node *op2, ir_mode *mode)
740  *    ------------------------------------------------------------
741  *
742  *    Trivial.
743  *
744  *    ir_node *new_Not (ir_node *op, ir_mode *mode)
745  *    ---------------------------------------------
746  *
747  *    This node constructs a constant where all bits are set to one
748  *    and a Eor of this constant and the operator.  This simulates a
749  *    Not operation.
750  *
751  *    ir_node *new_Shl (ir_node *op, ir_node *k, ir_mode *mode)
752  *    ---------------------------------------------------------
753  *
754  *    Trivial.
755  *
756  *    ir_node *new_Shr (ir_node *op, ir_node *k, ir_mode *mode)
757  *    ---------------------------------------------------------
758  *
759  *    Logic shift right, i.e., zero extended.
760  *
761  *
762  *    ir_node *new_Shrs (ir_node *op, ir_node *k, ir_mode *mode)
763  *    ----------------------------------------------------------
764  *
765  *    Arithmetic shift right, i.e., sign extended.
766  *
767  *    ir_node *new_Rotl (ir_node *op, ir_node *k, ir_mode *mode)
768  *    ---------------------------------------------------------
769  *
770  *    Rotates the operand to the left by k bits.
771  *
772  *    ir_node *new_Carry (ir_node *op1, ir_node *op2, ir_mode *mode)
773  *    ------------------------------------------------------------
774  *
775  *    Calculates the Carry value for integer addition. Used only
776  *    in lowering code.
777  *
778  *    ir_node *new_Borrow (ir_node *op1, ir_node *op2, ir_mode *mode)
779  *    ------------------------------------------------------------
780  *
781  *    Calculates the Borrow value for integer substraction. Used only
782  *    in lowering code.
783  *
784  *    ir_node *new_Conv (ir_node *op, ir_mode *mode)
785  *    ---------------------------------------------
786  *
787  *    Mode conversion.  For allowed conversions see UKA Tech Report
788  *    1999-14.
789  *
790  *    ir_node *new_Cmp (ir_node *op1, ir_node *op2)
791  *    ---------------------------------------------
792  *
793  *    Input:
794  *      The two values to be compared.
795  *    Output:
796  *      A 16-tuple containing the results of the 16 different comparisons.
797  *      The following is a list giving the comparisons and a projection
798  *      number (pn_Cmp) to use in Proj nodes to extract the proper result.
799  *        pn_Cmp_False false
800  *        pn_Cmp_Eq    equal
801  *        pn_Cmp_Lt    less
802  *        pn_Cmp_Le    less or equal
803  *        pn_Cmp_Gt    greater
804  *        pn_Cmp_Ge    greater of equal
805  *        pn_Cmp_Lg    less or greater
806  *        pn_Cmp_Leg   less, equal or greater = ordered
807  *        pn_Cmp_Uo    unordered
808  *        pn_Cmp_Ue    unordered or equal
809  *        pn_Cmp_Ul    unordered or less
810  *        pn_Cmp_Ule   unordered, less or equal
811  *        pn_Cmp_Ug    unordered or greater
812  *        pn_Cmp_Uge   unordered, greater or equal
813  *        pn_Cmp_Ne    unordered, less or greater = not equal
814  *        pn_Cmp_True  true
815  *
816  *
817  *
818  *    ------------
819  *
820  *    In general, Phi nodes are automaitcally inserted.  In some cases, if
821  *    all predecessors of a block are known, an explicit Phi node constructor
822  *    is needed.  E.g., to construct a FIRM graph for a statement as
823  *      a = (b==c) ? 2 : 5;
824  *
825  *    ir_node *new_Phi (int arity, ir_node **in, ir_mode *mode)
826  *    ---------------------------------------------------------
827  *
828  *    Creates a Phi node. The in's order has to correspond to the order
829  *    of in's of current_block.  This is not checked by the library!
830  *    If one of the predecessors is Unknown (as it has to be filled in
831  *    later) optimizations are skipped.  This is necessary to
832  *    construct Phi nodes in loops.
833  *
834  *    Parameter
835  *      arity            number of predecessors
836  *      **in             array with predecessors
837  *      *mode            The mode of it's inputs and output.
838  *    Inputs:
839  *      A Phi node has as many inputs as the block it belongs to.
840  *      Each input points to a definition of the same value on a
841  *      different path in the control flow.
842  *    Output
843  *      The definition valid in this block.
844  *
845  *    ir_node *new_Mux (ir_node *sel, ir_node *ir_false, ir_node *ir_true, ir_mode *mode)
846  *    -----------------------------------------------------------------------------------
847  *
848  *    Creates a Mux node. This node implements the following semantic:
849  *    If the sel node (which must be of mode_b) evaluates to true, its value is
850  *    ir_true, else ir_false;
851  *
852  *
853  *
854  *    OPERATIONS TO MANAGE MEMORY EXPLICITLY
855  *    --------------------------------------
856  *
857  *    ir_node *new_Load (ir_node *store, ir_node *addr, ir_mode *mode, ir_cons_flags flags)
858  *    -------------------------------------------------------------------------------------
859  *
860  *    The Load operation reads a value from memory.
861  *
862  *    Parameters:
863  *    *store        The current memory.
864  *    *addr         A pointer to the variable to be read in this memory.
865  *    *mode         The mode of the value to be loaded.
866  *     flags        Additional flags for alignment, volatility and pin state.
867  *
868  *    Inputs:
869  *      The memory and a pointer to a variable in this memory.
870  *    Output:
871  *      A tuple of the memory, a control flow to be taken in case of
872  *      an exception and the loaded value.
873  *
874  *    ir_node *new_Store (ir_node *store, ir_node *addr, ir_node *val, ir_cons_flags flags)
875  *    -------------------------------------------------------------------------------------
876  *
877  *    The Store operation writes a value to a variable in memory.
878  *
879  *    Inputs:
880  *      The memory, a pointer to a variable in this memory and the value
881  *      to write to this variable.
882  *    Output:
883  *      A tuple of the changed memory and a control flow to be taken in
884  *      case of an exception.
885  *
886  *    ir_node *new_Alloc (ir_node *store, ir_node *count, ir_type *alloc_type,
887  *    -----------------------------------------------------------------------
888  *                        where_alloc where)
889  *                        ------------------
890  *
891  *    The Alloc node allocates a new variable.  It can be specified whether the
892  *    variable should be allocated to the stack or to the heap.
893  *
894  *    Parameters:
895  *      *store       The memory which shall contain the new variable.
896  *      *count       This field is for allocating arrays, it specifies how
897  *                   many array elements are to be allocated.
898  *      *alloc_type  The type of the allocated variable. In case of allocating
899  *                   arrays this has to be the array type, not the type of the
900  *                   array elements.
901  *      where        Where to allocate the variable, either heap_alloc or stack_alloc.
902  *
903  *    Inputs:
904  *      A memory and an unsigned integer.
905  *    Output:
906  *      A tuple of the changed memory, a control flow to be taken in
907  *      case of an exception and the pointer to the new variable.
908  *    Attributes:
909  *      a.where          Indicates where the variable is allocated.
910  *      a.*type          A pointer to the class the allocated data object
911  *                       belongs to.
912  *
913  *    ir_node *new_Free (ir_node *store, ir_node *ptr, ir_node *size, ir_type *free_type,
914  *    -----------------------------------------------------------------------------------
915  *                        where_alloc where)
916  *                        ------------------
917  *
918  *    The Free node frees memory of the given variable.
919  *
920  *    Parameters:
921  *      *store       The memory which shall contain the new variable.
922  *      *ptr         The pointer to the object to free.
923  *      *size        The number of objects of type free_type to free in a sequence.
924  *      *free_type   The type of the freed variable.
925  *      where        Where the variable was allocated, either heap_alloc or stack_alloc.
926  *
927  *    Inputs:
928  *      A memory, a pointer and an unsigned integer.
929  *    Output:
930  *      The changed memory.
931  *    Attributes:
932  *      f.*type          A pointer to the type information of the freed data object.
933  *
934  *    Not Implemented!
935  *
936  *    ir_node *new_Sync (int arity, ir_node **in)
937  *    -------------------------------------------
938  *
939  *    The Sync operation unifies several partial memory blocks.  These blocks
940  *    have to be pairwise disjunct or the values in common locations have to
941  *    be identical.  This operation allows to specify all operations that eventually
942  *    need several partial memory blocks as input with a single entrance by
943  *    unifying the memories with a preceding Sync operation.
944  *
945  *    Parameters
946  *      arity    The number of memories to synchronize.
947  *      **in     An array of pointers to nodes that produce an output of
948  *               type memory.
949  *    Inputs
950  *      Several memories.
951  *    Output
952  *      The unified memory.
953  *
954  *
955  *    SPECIAL OPERATIONS
956  *    ------------------
957  *
958  *    ir_node *new_Bad (void)
959  *    -----------------------
960  *
961  *    Returns the unique Bad node current_ir_graph->bad.
962  *    This node is used to express results of dead code elimination.
963  *
964  *    ir_node *new_NoMem (void)
965  *    -----------------------------------------------------------------------------------
966  *
967  *    Returns the unique NoMem node current_ir_graph->no_mem.
968  *    This node is used as input for operations that need a Memory, but do not
969  *    change it like Div by const != 0, analyzed calls etc.
970  *
971  *    ir_node *new_Proj (ir_node *arg, ir_mode *mode, long proj)
972  *    ----------------------------------------------------------
973  *
974  *    Selects one entry of a tuple.  This is a hidden edge with attributes.
975  *
976  *    Parameters
977  *      *arg      A node producing a tuple.
978  *      *mode     The mode of the value to project.
979  *      proj      The position of the value in the tuple.
980  *    Input:
981  *      The tuple.
982  *    Output:
983  *      The value.
984  *
985  *    ir_node *new_Tuple (int arity, ir_node **in)
986  *    --------------------------------------------
987  *
988  *    Builds a Tuple from single values.  This is needed to implement
989  *    optimizations that remove a node that produced a tuple.  The node can be
990  *    replaced by the Tuple operation so that the following Proj nodes have not to
991  *    be changed.  (They are hard to find due to the implementation with pointers
992  *    in only one direction.)  The Tuple node is smaller than any other
993  *    node, so that a node can be changed into a Tuple by just changing it's
994  *    opcode and giving it a new in array.
995  *
996  *    Parameters
997  *      arity    The number of tuple elements.
998  *      **in     An array containing pointers to the nodes producing the
999  *               tuple elements.
1000  *
1001  *    ir_node *new_Id (ir_node *val, ir_mode *mode)
1002  *    ---------------------------------------------
1003  *
1004  *    The single output of the Id operation is it's input.  Also needed
1005  *    for optimizations.
1006  *
1007  *
1008  *    HIGH LEVEL OPERATIONS
1009  *    ---------------------
1010  *
1011  *    ir_node *new_CopyB (ir_node *store, ir_node *dst, ir_node *src, ir_type *data_type)
1012  *    -----------------------------------------------------------------------------------
1013  *
1014  *    Describes a high level block copy of a compound type from address src to
1015  *    address dst. Must be lowered to a Call to a runtime memory copy function.
1016  *
1017  *
1018  *    HIGH LEVEL OPERATIONS: Exception Support
1019  *    ----------------------------------------
1020  *    See TechReport 1999-14, chapter Exceptions.
1021  *
1022  *    ir_node *new_InstOf(ir_node *store, ir_node *ptr, ir_type *type);
1023  *    -----------------------------------------------------------------------------------
1024  *
1025  *    Describes a high level type check. Must be lowered to a Call to a runtime check
1026  *    function.
1027  *
1028  *    ir_node *new_Raise (ir_node *store, ir_node *obj)
1029  *    -------------------------------------------------
1030  *
1031  *    Raises an exception.  Unconditional change of control flow.  Writes
1032  *    an explicit Except variable to memory to pass it to the exception
1033  *    handler.  Must be lowered to a Call to a runtime check
1034  *    function.
1035  *
1036  *    Inputs:
1037  *      The memory state.
1038  *      A pointer to the Except variable.
1039  *    Output:
1040  *      A tuple of control flow and the changed memory state.  The control flow
1041  *      points to the exception handler if it is definied in this procedure,
1042  *      else it points to the end_block.
1043  *
1044  *    ir_node *new_Bound  (ir_node *store, ir_node *idx, ir_node *lower, ir_node *upper);
1045  *    -----------------------------------------------------------------------------------
1046  *
1047  *    Describes a high level bounds check. Must be lowered to a Call to a runtime check
1048  *    function.
1049  *
1050  *    ir_node *new_Pin  (ir_node *node);
1051  *    -----------------------------------------------------------------------------------
1052  *
1053  *    Pin the value of the node node in the current block  No users of the Pin node can
1054  *    float above the Block of the Pin. The node cannot float behind this block. Often
1055  *    used to Pin the NoMem node.
1056  *
1057  *
1058  *    COPING WITH DATA OBJECTS
1059  *    ========================
1060  *
1061  *    Two kinds of data objects have to be distinguished for generating
1062  *    FIRM.  First there are local variables other than arrays that are
1063  *    known to be alias free.  Second there are all other data objects.
1064  *    For the first a common SSA representation is built, the second
1065  *    are modeled by saving them to memory.  The memory is treated as
1066  *    a single local variable, the alias problem is hidden in the
1067  *    content of this variable.
1068  *
1069  *    All values known in a Block are listed in the block's attribute,
1070  *    block.**graph_arr which is used to automatically insert Phi nodes.
1071  *    The following two functions can be used to add a newly computed value
1072  *    to the array, or to get the producer of a value, i.e., the current
1073  *    live value.
1074  *
1075  *    inline void set_value (int pos, ir_node *value)
1076  *    -----------------------------------------------
1077  *
1078  *    Has to be called for every assignment to a local variable.  It
1079  *    adds the value to the array of used values at position pos.  Pos
1080  *    has to be a unique identifier for an entry in the procedure's
1081  *    definition table.  It can be used to access the value again.
1082  *    Requires current_block to be set correctly.
1083  *
1084  *    ir_node *get_value (int pos, ir_mode *mode)
1085  *    -------------------------------------------
1086  *
1087  *    Returns the node defining the value referred to by pos. If the
1088  *    value is not defined in this block a Phi node is generated and
1089  *    all definitions reaching this Phi node are collected.  It can
1090  *    happen that the algorithm allocates an unnecessary Phi node,
1091  *    e.g. if there is only one definition of this value, but this
1092  *    definition reaches the currend block on several different
1093  *    paths.  This Phi node will be eliminated if optimizations are
1094  *    turned on right after it's creation.
1095  *    Requires current_block to be set correctly.
1096  *
1097  *    There are two special routines for the global store:
1098  *
1099  *    void set_store (ir_node *store)
1100  *    -------------------------------
1101  *
1102  *    Adds the store to the array of known values at a reserved
1103  *    position.
1104  *    Requires current_block to be set correctly.
1105  *
1106  *    ir_node *get_store (void)
1107  *    -------------------------
1108  *
1109  *    Returns the node defining the actual store.
1110  *    Requires current_block to be set correctly.
1111  *
1112  *
1113  *    inline void keep_alive (ir_node *ka)
1114  *    ------------------------------------
1115  *
1116  *    Keep this node alive because it is (might be) not in the control
1117  *    flow from Start to End.  Adds the node to the list in the end
1118  *   node.
1119  *
1120  */
1121 #ifndef FIRM_IR_IRCONS_H
1122 #define FIRM_IR_IRCONS_H
1123
1124 #include "firm_types.h"
1125 #include "begin.h"
1126 #include "irnode.h"
1127
1128 /**
1129  * constrained flags for memory operations.
1130  */
1131 typedef enum ir_cons_flags {
1132         cons_none      = 0,        /**< No constrains. */
1133         cons_volatile  = 1U << 0,  /**< Memory operation is volatile. */
1134         cons_unaligned = 1U << 1,  /**< Memory operation is unaligned. */
1135         cons_floats    = 1U << 2   /**< Memory operation can float. */
1136 } ir_cons_flags;
1137
1138 /*-------------------------------------------------------------------------*/
1139 /* The raw interface                                                       */
1140 /*-------------------------------------------------------------------------*/
1141
1142 /** Constructor for a Block node.
1143  *
1144  * Constructs a mature block with the given predecessors.
1145  *
1146  * @param *db    A Pointer for  debug information.
1147  * @param irg    The IR graph the block belongs to.
1148  * @param arity  The number of control predecessors.
1149  * @param in[]   An array of control predecessors.  The length of
1150  *               the array must be 'arity'.  The constructor copies this array.
1151  */
1152 FIRM_API ir_node *new_rd_Block(dbg_info *db, ir_graph *irg, int arity, ir_node *in[]);
1153
1154 /** Constructor for a Start node.
1155  *
1156  * @param *db    A pointer for debug information.
1157  * @param *irg   The IR graph the node belongs to.
1158  * @param *block The IR block the node belongs to.
1159  */
1160 FIRM_API ir_node *new_rd_Start(dbg_info *db, ir_graph *irg, ir_node *block);
1161
1162 /** Constructor for a End node.
1163  *
1164  * @param *db    A pointer for  debug information.
1165  * @param *irg   The IR graph the node  belongs to.
1166  * @param *block The IR block the node belongs to.
1167  */
1168 FIRM_API ir_node *new_rd_End(dbg_info *db, ir_graph *irg, ir_node *block);
1169
1170 /** Constructor for a Jmp node.
1171  *
1172  * Jmp represents control flow to a single control successor.
1173  *
1174  * @param *db     A pointer for debug information.
1175  * @param *block  The IR block the node belongs to.
1176  */
1177 FIRM_API ir_node *new_rd_Jmp(dbg_info *db, ir_node *block);
1178
1179 /** Constructor for an IJmp node.
1180  *
1181  * IJmp represents control flow to a single control successor not
1182  * statically known i.e. an indirect Jmp.
1183  *
1184  * @param *db     A pointer for debug information.
1185  * @param *block  The IR block the node belongs to.
1186  * @param *tgt    The IR node representing the target address.
1187  */
1188 FIRM_API ir_node *new_rd_IJmp(dbg_info *db, ir_node *block, ir_node *tgt);
1189
1190 /** Constructor for a Cond node.
1191  *
1192  * If c is mode_b represents a conditional branch (if/else). If c is
1193  * mode_Is/mode_Iu (?) represents a switch.  (Allocates dense Cond
1194  * node, default Proj is 0.)
1195  *
1196  * This is not consistent:  Input to Cond is Is, Proj has as proj number
1197  * longs.
1198  *
1199  * @param *db    A pointer for debug information.
1200  * @param *block The IR block the node belongs to.
1201  * @param *c     The conditions parameter. Can be of mode b or I_u.
1202  */
1203 FIRM_API ir_node *new_rd_Cond(dbg_info *db, ir_node *block, ir_node *c);
1204
1205 /** Constructor for a Return node.
1206  *
1207  * Returns the memory and zero or more return values.  Only node that
1208  * can end regular control flow.
1209  *
1210  * @param *db    A pointer for debug information.
1211  * @param *block The IR block the node belongs to.
1212  * @param *store The state of memory.
1213  * @param arity  Number of return values.
1214  * @param *in    Array of length arity with return values.  The constructor copies this array.
1215  */
1216 FIRM_API ir_node *new_rd_Return(dbg_info *db, ir_node *block,
1217                                 ir_node *store, int arity, ir_node *in[]);
1218
1219 /** Constructor for a Const_type node.
1220  *
1221  * Adds the node to the start block.
1222  *
1223  * The constant represents a target value.  This constructor sets high
1224  * level type information for the constant value.
1225  * Derives mode from passed tarval.
1226  *
1227  * @param *db    A pointer for debug information.
1228  * @param *irg   The IR graph the node  belongs to.
1229  * @param *con   Points to an entry in the constant table.
1230  * @param *tp    The type of the constant.
1231  */
1232 FIRM_API ir_node *new_rd_Const_type(dbg_info *db, ir_graph *irg,
1233                                     tarval *con, ir_type *tp);
1234
1235 /** Constructor for a Const node.
1236  *
1237  * Adds the node to the start block.
1238  *
1239  * Constructor for a Const node. The constant represents a target
1240  * value.  Sets the type information to type_unknown.  (No more
1241  * supported: If tv is entity derives a somehow useful type.)
1242  * Derives mode from passed tarval.
1243  *
1244  * @param *db    A pointer for debug information.
1245  * @param *irg   The IR graph the node  belongs to.
1246  * @param *con   Points to an entry in the constant table.
1247  */
1248 FIRM_API ir_node *new_rd_Const(dbg_info *db, ir_graph *irg, tarval *con);
1249
1250 /**
1251  * Constructor for a Const node.
1252  *
1253  * Adds the node to the start block.
1254  *
1255  * Constructor for a Const node. The constant represents a target
1256  * value.  Sets the type information to type_unknown.  (No more
1257  * supported: If tv is entity derives a somehow useful type.)
1258  *
1259  * @param *db    A pointer for debug information.
1260  * @param *irg   The IR graph the node  belongs to.
1261  * @param *mode  The mode of the operands and results.
1262  * @param value  A value from which the tarval is made.
1263  */
1264 FIRM_API ir_node *new_rd_Const_long(dbg_info *db, ir_graph *irg,
1265                                     ir_mode *mode, long value);
1266
1267 /** Constructor for a SymConst_type node.
1268  *
1269  *  This is the constructor for a symbolic constant.
1270  *    There are several kinds of symbolic constants:
1271  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
1272  *                          type the tag stands for is given explicitly.
1273  *    - symconst_type_size  The symbolic constant represents the size of a type.
1274  *                          The type of which the constant represents the size
1275  *                          is given explicitly.
1276  *    - symconst_type_align The symbolic constant represents the alignment of a
1277  *                          type.  The type of which the constant represents the
1278  *                          size is given explicitly.
1279  *    - symconst_addr_ent   The symbolic constant represents the address of an
1280  *                          entity (variable or method).  The variable is given
1281  *                          explicitly by a firm entity.
1282  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
1283  *                          entity in its owner type.
1284  *    - symconst_enum_const The symbolic constant is a enumeration constant of
1285  *                          an enumeration type.
1286  *
1287  *    Inputs to the node:
1288  *      No inputs except the block it belongs to.
1289  *    Outputs of the node.
1290  *      An unsigned integer (I_u) or a pointer (P).
1291  *
1292  *    Mention union in declaration so that the firmjni generator recognizes that
1293  *    it can not cast the argument to an int.
1294  *
1295  * @param *db     A pointer for debug information.
1296  * @param *irg    The IR graph the node  belongs to.
1297  * @param mode    The mode for the SymConst.
1298  * @param val     A type, ident, entity or enum constant depending on the
1299  *                SymConst kind.
1300  * @param kind    The kind of the symbolic constant, see the list above
1301  * @param tp      The source type of the constant.
1302  */
1303 FIRM_API ir_node *new_rd_SymConst_type(dbg_info *db, ir_graph *irg,
1304                                        ir_mode *mode, union symconst_symbol val,
1305                                        symconst_kind kind, ir_type *tp);
1306
1307 /** Constructor for a SymConst node.
1308  *
1309  *  Same as new_rd_SymConst_type, except that it sets the type to type_unknown.
1310  */
1311 FIRM_API ir_node *new_rd_SymConst(dbg_info *db, ir_graph *irg, ir_mode *mode,
1312                                   union symconst_symbol value,
1313                                   symconst_kind kind);
1314
1315 /** Constructor for a SymConst addr_ent node.
1316  *
1317  * Same as new_rd_SymConst_type, except that the constructor is tailored for
1318  * symconst_addr_ent.
1319  * Adds the SymConst to the start block of irg. */
1320 FIRM_API ir_node *new_rd_SymConst_addr_ent(dbg_info *db, ir_graph *irg,
1321                                            ir_mode *mode, ir_entity *symbol,
1322                                            ir_type *tp);
1323
1324 /** Constructor for a SymConst ofs_ent node.
1325  *
1326  * Same as new_rd_SymConst_type, except that the constructor is tailored for
1327  * symconst_ofs_ent.
1328  * Adds the SymConst to the start block of irg.
1329  */
1330 FIRM_API ir_node *new_rd_SymConst_ofs_ent(dbg_info *db, ir_graph *irg,
1331                                           ir_mode *mode, ir_entity *symbol,
1332                                           ir_type *tp);
1333
1334 /** Constructor for a SymConst type_tag node.
1335  *
1336  * Same as new_rd_SymConst_type, except that the constructor is tailored for
1337  * symconst_type_tag.
1338  * Adds the SymConst to the start block of irg.
1339  */
1340 FIRM_API ir_node *new_rd_SymConst_type_tag(dbg_info *db, ir_graph *irg,
1341                                            ir_mode *mode, ir_type *symbol,
1342                                            ir_type *tp);
1343
1344 /** Constructor for a SymConst size node.
1345  *
1346  * Same as new_rd_SymConst_type, except that the constructor is tailored for
1347  * symconst_type_size.
1348  * Adds the SymConst to the start block of irg. */
1349 FIRM_API ir_node *new_rd_SymConst_size(dbg_info *db, ir_graph *irg,
1350                                        ir_mode *mode, ir_type *symbol,
1351                                        ir_type *tp);
1352
1353 /** Constructor for a SymConst size node.
1354  *
1355  * Same as new_rd_SymConst_type, except that the constructor is tailored for
1356  * symconst_type_align.
1357  * Adds the SymConst to the start block of irg.
1358  */
1359 FIRM_API ir_node *new_rd_SymConst_align(dbg_info *db, ir_graph *irg,
1360                                         ir_mode *mode, ir_type *symbol,
1361                                         ir_type *tp);
1362
1363 /** Constructor for a simpleSel node.
1364  *
1365  *  This is a shortcut for the new_rd_Sel() constructor.  To be used for
1366  *  Sel nodes that do not select from an array, i.e., have no index
1367  *  inputs.  It adds the two parameters 0, NULL.
1368  *
1369  * @param   *db        A pointer for debug information.
1370  * @param   *block     The IR block the node belongs to.
1371  * @param   *store     The memory in which the object the entity should be
1372  *                     selected from is allocated.
1373  * @param   *objptr    The object from that the Sel operation selects a
1374  *                     single attribute out.
1375  * @param   *ent       The entity to select.
1376  */
1377 FIRM_API ir_node *new_rd_simpleSel(dbg_info *db, ir_node *block, ir_node *store,
1378                                    ir_node *objptr, ir_entity *ent);
1379
1380 /** Constructor for a Sel node.
1381  *
1382  * The select node selects an entity (field or method) from an entity
1383  * with a compound type.  It explicitly specifies the entity selected.
1384  * Dynamically the node may select entities that overwrite the given
1385  * entity.  If the selected entity is an array element entity the Sel
1386  * node takes the required array indices as inputs.
1387  *
1388  * @param   *db        A pointer for debug information.
1389  * @param   *block     The IR block the node belongs to.
1390  * @param   *store     The memory in which the object the entity should be selected
1391  *                     from is allocated.
1392  * @param   *objptr    A pointer to a compound entity the Sel operation selects a
1393  *                     single attribute from.
1394  * @param   *n_index   The number of array indices needed to select an array element entity.
1395  * @param   *index[]   If the compound entity is an array the indices of the selected
1396  *                     element entity.  The constructor copies this array.
1397  * @param   *ent       The entity to select.
1398  */
1399 FIRM_API ir_node *new_rd_Sel(dbg_info *db, ir_node *block, ir_node *store,
1400                              ir_node *objptr, int n_index, ir_node *index[],
1401                              ir_entity *ent);
1402
1403 /** Constructor for a Call node.
1404  *
1405  * Represents all kinds of method and function calls.
1406  *
1407  * @param   *db     A pointer for debug information.
1408  * @param   *block  The IR block the node belongs to.
1409  * @param   *store  The current memory state.
1410  * @param   *callee A pointer to the called procedure.
1411  * @param   arity   The number of procedure parameters.
1412  * @param   *in[]   An array with the procedure parameters. The constructor copies this array.
1413  * @param   *tp     Type information of the procedure called.
1414  */
1415 FIRM_API ir_node *new_rd_Call(dbg_info *db, ir_node *block, ir_node *store,
1416                               ir_node *callee, int arity, ir_node *in[],
1417                               ir_type *tp);
1418
1419 /** Constructor for a Builtin node.
1420  *
1421  * Represents a call of a backend-specific builtin..
1422  *
1423  * @param   *db     A pointer for debug information.
1424  * @param   *block  The IR block the node belongs to.
1425  * @param   *store  The current memory state.
1426  * @param   arity   The number of procedure parameters.
1427  * @param   *in[]   An array with the procedure parameters. The constructor copies this array.
1428  * @param   kind    The kind of the called builtin.
1429  * @param   *tp     Type information of the procedure called.
1430  */
1431 FIRM_API ir_node *new_rd_Builtin(dbg_info *db, ir_node *block, ir_node *store,
1432                                  int arity, ir_node *in[], ir_builtin_kind kind,
1433                                  ir_type *tp);
1434
1435 /** Constructor for a Add node.
1436  *
1437  * @param   *db    A pointer for debug information.
1438  * @param   *block The IR block the node belongs to.
1439  * @param   *op1   The first operand.
1440  * @param   *op2   The second operand.
1441  * @param   *mode  The mode of the operands and the result.
1442  */
1443 FIRM_API ir_node *new_rd_Add(dbg_info *db, ir_node *block, ir_node *op1,
1444                              ir_node *op2, ir_mode *mode);
1445
1446 /** Constructor for a Sub node.
1447  *
1448  * @param   *db    A pointer for debug information.
1449  * @param   *block The IR block the node belongs to.
1450  * @param   *op1   The first operand.
1451  * @param   *op2   The second operand.
1452  * @param   *mode  The mode of the operands and the result.
1453  */
1454 FIRM_API ir_node *new_rd_Sub(dbg_info *db, ir_node *block,
1455                              ir_node *op1, ir_node *op2, ir_mode *mode);
1456
1457 /** Constructor for a Minus node.
1458  *
1459  * @param   *db    A pointer for debug information.
1460  * @param   *block The IR block the node belongs to.
1461  * @param   *op    The operand .
1462  * @param   *mode  The mode of the operand and the result.
1463  */
1464 FIRM_API ir_node *new_rd_Minus(dbg_info *db, ir_node *block,
1465                                ir_node *op, ir_mode *mode);
1466
1467 /** Constructor for a Mul node.
1468  *
1469  * @param   *db    A pointer for debug information.
1470  * @param   *block The IR block the node belongs to.
1471  * @param   *op1   The first operand.
1472  * @param   *op2   The second operand.
1473  * @param   *mode  The mode of the operands and the result.
1474  */
1475 FIRM_API ir_node *new_rd_Mul(dbg_info *db, ir_node *block,
1476                              ir_node *op1, ir_node *op2, ir_mode *mode);
1477
1478 /** Constructor for a Mulh node.
1479  *
1480  * @param   *db    A pointer for debug information.
1481  * @param   *block The IR block the node belongs to.
1482  * @param   *op1   The first operand.
1483  * @param   *op2   The second operand.
1484  * @param   *mode  The mode of the operands and the result.
1485  */
1486 FIRM_API ir_node *new_rd_Mulh(dbg_info *db, ir_node *block,
1487                               ir_node *op1, ir_node *op2, ir_mode *mode);
1488
1489 /** Constructor for a Quot node.
1490  *
1491  * @param   *db    A pointer for debug information.
1492  * @param   *block The IR block the node belongs to.
1493  * @param   *memop The store needed to model exceptions
1494  * @param   *op1   The first operand.
1495  * @param   *op2   The second operand.
1496  * @param   *mode  The mode of the result.
1497  * @param   state  The pinned state.
1498  */
1499 FIRM_API ir_node *new_rd_Quot(dbg_info *db, ir_node *block, ir_node *memop,
1500                               ir_node *op1, ir_node *op2, ir_mode *mode,
1501                               op_pin_state state);
1502
1503 /** Constructor for a DivMod node.
1504  *
1505  * @param   *db    A pointer for debug information.
1506  * @param   *block The IR block the node belongs to.
1507  * @param   *memop The store needed to model exceptions
1508  * @param   *op1   The first operand.
1509  * @param   *op2   The second operand.
1510  * @param   *mode  The mode of the results.
1511  * @param   state  The pinned state.
1512  */
1513 FIRM_API ir_node *new_rd_DivMod(dbg_info *db, ir_node *block, ir_node *memop,
1514                                 ir_node *op1, ir_node *op2, ir_mode *mode,
1515                                 op_pin_state state);
1516
1517 /** Constructor for a Div node.
1518  *
1519  * @param   *db    A pointer for debug information.
1520  * @param   *block The IR block the node belongs to.
1521  * @param   *memop The store needed to model exceptions
1522  * @param   *op1   The first operand.
1523  * @param   *op2   The second operand.
1524  * @param   *mode  The mode of the result.
1525  * @param   state  The pinned state.
1526  */
1527 FIRM_API ir_node *new_rd_Div(dbg_info *db, ir_node *block, ir_node *memop,
1528                              ir_node *op1, ir_node *op2, ir_mode *mode,
1529                              op_pin_state state);
1530
1531 /** Constructor for a remainderless Div node.
1532  *
1533  * @param   *db    A pointer for debug information.
1534  * @param   *block The IR block the node belongs to.
1535  * @param   *memop The store needed to model exceptions
1536  * @param   *op1   The first operand.
1537  * @param   *op2   The second operand.
1538  * @param   *mode  The mode of the result.
1539  * @param   state  The pinned state.
1540  */
1541 FIRM_API ir_node *new_rd_DivRL(dbg_info *db, ir_node *block, ir_node *memop,
1542                                ir_node *op1, ir_node *op2, ir_mode *mode,
1543                                op_pin_state state);
1544
1545 /** Constructor for a Mod node.
1546  *
1547  * @param   *db    A pointer for debug information.
1548  * @param   *block The IR block the node belongs to.
1549  * @param   *memop The store needed to model exceptions
1550  * @param   *op1   The first operand.
1551  * @param   *op2   The second operand.
1552  * @param   *mode  The mode of the result.
1553  * @param   state  The pinned state.
1554  */
1555 FIRM_API ir_node *new_rd_Mod(dbg_info *db, ir_node *block, ir_node *memop,
1556                              ir_node *op1, ir_node *op2, ir_mode *mode,
1557                              op_pin_state state);
1558
1559 /** Constructor for a Abs node.
1560  *
1561  * @param   *db    A pointer for debug information.
1562  * @param   *block The IR block the node belongs to.
1563  * @param   *op    The operand
1564  * @param   *mode  The mode of the operands and the result.
1565  */
1566 FIRM_API ir_node *new_rd_Abs(dbg_info *db, ir_node *block, ir_node *op,
1567                              ir_mode *mode);
1568
1569 /** Constructor for a And node.
1570  *
1571  * @param   *db    A pointer for debug information.
1572  * @param   *block The IR block the node belongs to.
1573  * @param   *op1   The first operand.
1574  * @param   *op2   The second operand.
1575  * @param   *mode  The mode of the operands and the result.
1576  */
1577 FIRM_API ir_node *new_rd_And(dbg_info *db, ir_node *block,
1578                              ir_node *op1, ir_node *op2, ir_mode *mode);
1579
1580 /** Constructor for a Or node.
1581  *
1582  * @param   *db    A pointer for debug information.
1583  * @param   *block The IR block the node belongs to.
1584  * @param   *op1   The first operand.
1585  * @param   *op2   The second operand.
1586  * @param   *mode  The mode of the operands and the result.
1587  */
1588 FIRM_API ir_node *new_rd_Or(dbg_info *db, ir_node *block,
1589                             ir_node *op1, ir_node *op2, ir_mode *mode);
1590
1591 /** Constructor for a Eor node.
1592  *
1593  * @param   *db    A pointer for debug information.
1594  * @param   *block The IR block the node belongs to.
1595  * @param   *op1   The first operand.
1596  * @param   *op2   The second operand.
1597  * @param   *mode  The mode of the operands and the results.
1598  */
1599 FIRM_API ir_node *new_rd_Eor(dbg_info *db, ir_node *block,
1600                              ir_node *op1, ir_node *op2, ir_mode *mode);
1601
1602 /** Constructor for a Not node.
1603  *
1604  * @param   *db    A pointer for debug information.
1605  * @param   *block The IR block the node belongs to.
1606  * @param   *op    The operand.
1607  * @param   *mode  The mode of the operand and the result.
1608  */
1609 FIRM_API ir_node *new_rd_Not(dbg_info *db, ir_node *block, ir_node *op,
1610                              ir_mode *mode);
1611
1612 /** Constructor for a Cmp node.
1613  *
1614  * @param   *db    A pointer for debug information.
1615  * @param   *block The IR block the node belongs to.
1616  * @param   *op1   The first operand.
1617  * @param   *op2   The second operand.
1618  */
1619 FIRM_API ir_node *new_rd_Cmp(dbg_info *db, ir_node *block,
1620                              ir_node *op1, ir_node *op2);
1621
1622 /** Constructor for a Shl node.
1623  *
1624  * @param   *db    A pointer for debug information.
1625  * @param   *block The IR block the node belongs to.
1626  * @param   *op    The operand.
1627  * @param   *k     The number of bits to  shift the operand .
1628  * @param   *mode  The mode of the operand and the result.
1629  */
1630 FIRM_API ir_node *new_rd_Shl(dbg_info *db, ir_node *block,
1631                              ir_node *op, ir_node *k, ir_mode *mode);
1632
1633 /** Constructor for a Shr node.
1634  *
1635  * @param   *db    A pointer for debug information.
1636  * @param   *block The IR block the node belongs to.
1637  * @param   *op    The operand.
1638  * @param   *k     The number of bits to shift the operand .
1639  * @param   *mode  The mode of the operand and the result.
1640  */
1641 FIRM_API ir_node *new_rd_Shr(dbg_info *db, ir_node *block,
1642                              ir_node *op, ir_node *k, ir_mode *mode);
1643
1644 /** Constructor for a Shrs node.
1645  *
1646  * @param   *db    A pointer for debug information.
1647  * @param   *block The IR block the node belongs to.
1648  * @param   *op    The operand.
1649  * @param   *k     The number of bits to shift the operand.
1650  * @param   *mode  The mode of the operand and the result.
1651  */
1652 FIRM_API ir_node *new_rd_Shrs(dbg_info *db, ir_node *block,
1653                               ir_node *op, ir_node *k, ir_mode *mode);
1654
1655 /** Constructor for a Rotl node.
1656  *
1657  * @param   *db    A pointer for debug information.
1658  * @param   *block The IR block the node belongs to.
1659  * @param   *op    The operand.
1660  * @param   *k     The number of bits to rotate the operand.
1661  * @param   *mode  The mode of the operand.
1662  */
1663 FIRM_API ir_node *new_rd_Rotl(dbg_info *db, ir_node *block,
1664                               ir_node *op, ir_node *k, ir_mode *mode);
1665
1666
1667 /** Constructor for a Conv node.
1668  *
1669  * @param   *db    A pointer for debug information.
1670  * @param   *block The IR block the node belongs to.
1671  * @param   *op    The operand.
1672  * @param   *mode  The mode of this the operand muss be converted .
1673  */
1674 FIRM_API ir_node *new_rd_Conv(dbg_info *db, ir_node *block, ir_node *op,
1675                               ir_mode *mode);
1676
1677 /** Constructor for a strictConv node.
1678  *
1679  * @param   *db    A pointer for debug information.
1680  * @param   *block The IR block the node belongs to.
1681  * @param   *op    The operand.
1682  * @param   *mode  The mode of this the operand muss be converted .
1683  */
1684 FIRM_API ir_node *new_rd_strictConv(dbg_info *db, ir_node *block,
1685                                     ir_node *op, ir_mode *mode);
1686
1687 /** Constructor for a Cast node.
1688  *
1689  * High level type cast.
1690  *
1691  * @param   *db    A pointer for debug information.
1692  * @param   *block The IR block the node belongs to.
1693  * @param   *op    The operand.
1694  * @param   *to_tp The type of this the operand muss be casted .
1695  */
1696 FIRM_API ir_node *new_rd_Cast(dbg_info *db, ir_node *block,
1697                               ir_node *op, ir_type *to_tp);
1698
1699 /** Constructor for a Carry node.
1700  * Note: This node is not supported by the backends! Only use for program
1701  * analysis tasks.
1702  *
1703  * @param   *db    A pointer for debug information.
1704  * @param   *block The IR block the node belongs to.
1705  * @param   *op1   The first operand.
1706  * @param   *op2   The second operand.
1707  * @param   *mode  The mode of the operands and the result.
1708  */
1709 FIRM_API ir_node *new_rd_Carry(dbg_info *db, ir_node *block,
1710                                ir_node *op1, ir_node *op2, ir_mode *mode);
1711
1712 /** Constructor for a Borrow node.
1713  * Note: This node is not supported by the backends! Only use for program
1714  * analysis tasks.
1715  *
1716  * @param   *db    A pointer for debug information.
1717  * @param   *block The IR block the node belongs to.
1718  * @param   *op1   The first operand.
1719  * @param   *op2   The second operand.
1720  * @param   *mode  The mode of the operands and the result.
1721  */
1722 FIRM_API ir_node *new_rd_Borrow(dbg_info *db, ir_node *block,
1723                                 ir_node *op1, ir_node *op2, ir_mode *mode);
1724
1725 /** Constructor for a Phi node.
1726  *
1727  * @param *db    A pointer for debug information.
1728  * @param *block The IR block the node belongs to.
1729  * @param arity  The number of predecessors
1730  * @param *in[]  Array with predecessors.  The constructor copies this array.
1731  * @param *mode  The mode of it's inputs and output.
1732  */
1733 FIRM_API ir_node *new_rd_Phi(dbg_info *db, ir_node *block, int arity,
1734                              ir_node *in[], ir_mode *mode);
1735
1736 /** Constructor for a Load node.
1737  *
1738  * @param *db    A pointer for debug information.
1739  * @param *block The IR block the node belongs to.
1740  * @param *store The current memory
1741  * @param *adr   A pointer to the variable to be read in this memory.
1742  * @param *mode  The mode of the value to be loaded.
1743  * @param  flags Additional flags for alignment, volatility and pin state.
1744  */
1745 FIRM_API ir_node *new_rd_Load(dbg_info *db, ir_node *block, ir_node *store,
1746                               ir_node *adr, ir_mode *mode, ir_cons_flags flags);
1747
1748 /** Constructor for a Store node.
1749  *
1750  * @param *db    A pointer for debug information.
1751  * @param *block The IR block the node belongs to.
1752  * @param *store The current memory
1753  * @param *adr   A pointer to the variable to be read in this memory.
1754  * @param *val   The value to write to this variable.
1755  * @param  flags Additional flags for alignment, volatility and pin state.
1756  */
1757 FIRM_API ir_node *new_rd_Store(dbg_info *db, ir_node *block, ir_node *store,
1758                                ir_node *adr, ir_node *val, ir_cons_flags flags);
1759
1760 /** Constructor for a Alloc node.
1761  *
1762  * The Alloc node extends the memory by space for an entity of type alloc_type.
1763  *
1764  * @param *db         A pointer for debug information.
1765  * @param *block      The IR block the node belongs to.
1766  * @param *store      The memory which shall contain the new variable.
1767  * @param *count      The number of objects to allocate.
1768  * @param *alloc_type The type of the allocated variable.
1769  * @param where       Where to allocate the variable, either heap_alloc or stack_alloc.
1770  */
1771 FIRM_API ir_node *new_rd_Alloc(dbg_info *db, ir_node *block, ir_node *store,
1772                                ir_node *count, ir_type *alloc_type,
1773                                ir_where_alloc where);
1774
1775 /** Constructor for a Free node.
1776  *
1777  * Frees the memory occupied by the entity pointed to by the pointer
1778  * arg.  Type indicates the type of the entity the argument points to.
1779  *
1780  * @param *db         A pointer for debug information.
1781  * @param *block      The IR block the node belongs to.
1782  * @param *store      The memory which shall contain the new variable.
1783  * @param *ptr        The pointer to the object to free.
1784  * @param *size       The number of objects of type free_type to free in a sequence.
1785  * @param *free_type  The type of the freed variable.
1786  * @param where       Where the variable was allocated, either heap_alloc or stack_alloc.
1787  */
1788 FIRM_API ir_node *new_rd_Free(dbg_info *db, ir_node *block, ir_node *store,
1789                               ir_node *ptr, ir_node *size, ir_type *free_type,
1790                               ir_where_alloc where);
1791
1792 /** Constructor for a Sync node.
1793  *
1794  * Merges several memory values.  The node assumes that a variable
1795  * either occurs only in one of the memories, or it contains the same
1796  * value in all memories where it occurs.
1797  *
1798  * @param *db       A pointer for debug information.
1799  * @param *block    The IR block the node belongs to.
1800  * @param  arity    The number of memories to synchronize.
1801  * @param  *in[]    An array of pointers to nodes that produce an output of type
1802  *                  memory.  The constructor copies this array.
1803  */
1804 FIRM_API ir_node *new_rd_Sync(dbg_info *db, ir_node *block, int arity,
1805                               ir_node *in[]);
1806
1807 /** Constructor for a Proj node.
1808  *
1809  * Projects a single value out of a tuple.  The parameter proj gives the
1810  * position of the value within the tuple.
1811  *
1812  * @param *db    A pointer for debug information.
1813  * @param arg    A node producing a tuple.  The node must have mode_T.
1814  * @param *mode  The mode of the value to project.
1815  * @param proj   The position of the value in the tuple.
1816  */
1817 FIRM_API ir_node *new_rd_Proj(dbg_info *db, ir_node *arg, ir_mode *mode,
1818                               long proj);
1819
1820 /** Constructor for a defaultProj node.
1821  *
1822  * Represents the default control flow of a Switch-Cond node.
1823  *
1824  * @param *db       A pointer for debug information.
1825  * @param arg       A node producing a tuple.
1826  * @param max_proj  The end position of the value in the tuple.
1827  */
1828 FIRM_API ir_node *new_rd_defaultProj(dbg_info *db, ir_node *arg, long max_proj);
1829
1830 /** Constructor for a Tuple node.
1831  *
1832  * This is an auxiliary node to replace a node that returns a tuple
1833  * without changing the corresponding Proj nodes.
1834  *
1835  * @param *db     A pointer for debug information.
1836  * @param *block  The IR block the node belongs to.
1837  * @param arity   The number of tuple elements.
1838  * @param *in[]   An array containing pointers to the nodes producing the tuple
1839  *                elements. The constructor copies this array.
1840  */
1841 FIRM_API ir_node *new_rd_Tuple(dbg_info *db, ir_node *block,
1842                                int arity, ir_node *in[]);
1843
1844 /** Constructor for a Id node.
1845  *
1846  * This is an auxiliary node to replace a node that returns a single
1847  * value.
1848  *
1849  * @param *db     A pointer for debug information.
1850  * @param *block  The IR block the node belongs to.
1851  * @param *val    The value
1852  * @param *mode   The mode of *val.
1853  */
1854 FIRM_API ir_node *new_rd_Id(dbg_info *db, ir_node *block,
1855                             ir_node *val, ir_mode *mode);
1856
1857 /** Constructor for a Confirm node.
1858  *
1859  * Specifies constraints for a value.  To support dataflow analyses.
1860  *
1861  * Example: If the value never exceeds '100' this is expressed by placing a
1862  * Confirm node val = new_d_Confirm(db, val, 100, '<=') on the dataflow edge.
1863  *
1864  * @param *db     A pointer for debug information.
1865  * @param *block  The IR block the node belong to.
1866  * @param *val    The value we express a constraint for
1867  * @param *bound  The value to compare against. Must be a firm node, typically a constant.
1868  * @param cmp     The compare operation.
1869  */
1870 FIRM_API ir_node *new_rd_Confirm(dbg_info *db, ir_node *block,
1871                                  ir_node *val, ir_node *bound, pn_Cmp cmp);
1872
1873 /** Constructor for an Unknown node.
1874  *
1875  * Represents an arbitrary value.  Places the node in the start block.
1876  *
1877  * @param *db     A pointer for debug information.
1878  * @param *irg    The IR graph the node  belongs to.
1879  * @param *m      The mode of the unknown value.
1880  */
1881 FIRM_API ir_node *new_rd_Unknown(dbg_info *db, ir_graph *irg, ir_mode *m);
1882
1883 /** Constructor for a Mux node.
1884  *
1885  * @param *db       A pointer for debug information.
1886  * @param *block    The block the node belong to.
1887  * @param *sel      The ir_node that calculates the boolean select.
1888  * @param *ir_true  The ir_node that calculates the true result.
1889  * @param *ir_false The ir_node that calculates the false result.
1890  * @param *mode     The mode of the node (and it_true and ir_false).
1891  */
1892 FIRM_API ir_node *new_rd_Mux(dbg_info *db, ir_node *block, ir_node *sel,
1893                              ir_node *ir_false, ir_node *ir_true,
1894                              ir_mode *mode);
1895
1896 /** Constructor for a CopyB node.
1897  *
1898  * @param *db         A pointer for debug information.
1899  * @param *block      The block the node belong to.
1900  * @param *store      The current memory
1901  * @param *dst        The ir_node that represents the destination address.
1902  * @param *src        The ir_node that represents the source address.
1903  * @param *data_type  The type of the copied data
1904  */
1905 FIRM_API ir_node *new_rd_CopyB(dbg_info *db, ir_node *block, ir_node *store,
1906                                ir_node *dst, ir_node *src, ir_type *data_type);
1907
1908 /** Constructor for a InstOf node.
1909  *
1910  * A High-Level Type check.
1911  *
1912  * @param   *db        A pointer for debug information.
1913  * @param   *block     The IR block the node belongs to.
1914  * @param   *store     The memory in which the object the entity should be selected
1915  *                     from is allocated.
1916  * @param   *objptr    A pointer to a object of a class type.
1917  * @param   *type      The type of which objptr must be.
1918  */
1919 FIRM_API ir_node *new_rd_InstOf(dbg_info *db, ir_node *block, ir_node *store,
1920                                 ir_node *objptr, ir_type *type);
1921
1922 /** Constructor for a Raise node.
1923  *
1924  * A High-Level Exception throw.
1925  *
1926  * @param *db    A pointer for debug information.
1927  * @param *block The IR block the node belongs to.
1928  * @param *store The current memory.
1929  * @param *obj   A pointer to the Except variable.
1930  */
1931 FIRM_API ir_node *new_rd_Raise(dbg_info *db, ir_node *block, ir_node *store,
1932                                ir_node *obj);
1933
1934 /** Constructor for a Bound node.
1935  *
1936  * A High-Level bounds check. Checks whether lower <= idx && idx < upper.
1937  *
1938  * @param *db         A pointer for debug information.
1939  * @param *block      The block the node belong to.
1940  * @param *store      The current memory.
1941  * @param *idx        The ir_node that represents an index.
1942  * @param *lower      The ir_node that represents the lower bound for the index.
1943  * @param *upper      The ir_node that represents the upper bound for the index.
1944  */
1945 FIRM_API ir_node *new_rd_Bound(dbg_info *db, ir_node *block,
1946                                ir_node *store, ir_node *idx, ir_node *lower,
1947                                ir_node *upper);
1948
1949 /** Constructor for a Pin node.
1950  *
1951  * @param *db         A pointer for debug information.
1952  * @param *block      The block the node belong to.
1953  * @param *node       The node which value should be pinned.
1954  */
1955 FIRM_API ir_node *new_rd_Pin(dbg_info *db, ir_node *block, ir_node *node);
1956
1957 /** Constructor for an ASM pseudo node.
1958  *
1959  * @param *db         A pointer for debug information.
1960  * @param *block      The block the node belong to.
1961  * @param arity       The number of data inputs to the node.
1962  * @param *in         The array of length arity of data inputs.
1963  * @param *inputs     The array of length arity of input constraints.
1964  * @param n_outs      The number of data outputs to the node.
1965  * @param *outputs    The array of length n_outs of output constraints.
1966  * @param n_clobber   The number of clobbered registers.
1967  * @param *clobber    The array of length n_clobber of clobbered registers.
1968  * @param *asm_text   The assembler text.
1969  */
1970 FIRM_API ir_node *new_rd_ASM(dbg_info *db, ir_node *block,
1971                             int arity, ir_node *in[], ir_asm_constraint *inputs,
1972                             int n_outs, ir_asm_constraint *outputs,
1973                             int n_clobber, ident *clobber[], ident *asm_text);
1974
1975 /*-------------------------------------------------------------------------*/
1976 /* The raw interface without debug support                                 */
1977 /*-------------------------------------------------------------------------*/
1978
1979 /** Constructor for a Block node.
1980  *
1981  * Constructs a mature block with the given predecessors.  Use Unknown
1982  * nodes as predecessors to construct a block if the number of
1983  * predecessors is known, but not the predecessors themselves.  This
1984  * constructor does not set current_block.  It not be used with
1985  * automatic Phi node construction.
1986  *
1987  *
1988  * @param irg    The IR graph the block belongs to.
1989  * @param arity  The number of control predecessors.
1990  * @param in[]   An array of control predecessors.  The length of
1991  *               the array must be 'arity'. The constructor copies this array.
1992  */
1993 FIRM_API ir_node *new_r_Block(ir_graph *irg, int arity, ir_node *in[]);
1994
1995 /** Constructor for a Start node.
1996  *
1997  * @param *irg   The IR graph the node belongs to.
1998  * @param *block The IR block the node belongs to.
1999  */
2000 FIRM_API ir_node *new_r_Start(ir_graph *irg, ir_node *block);
2001
2002 /** Constructor for a End node.
2003  *
2004  * @param *irg   The IR graph the node  belongs to.
2005  * @param *block The IR block the node belongs to.
2006  */
2007 FIRM_API ir_node *new_r_End(ir_graph *irg, ir_node *block);
2008
2009 /** Constructor for a Jmp node.
2010  *
2011  * Jmp represents control flow to a single control successor.
2012  *
2013  * @param *block  The IR block the node belongs to.
2014  */
2015 FIRM_API ir_node *new_r_Jmp(ir_node *block);
2016
2017 /** Constructor for an IJmp node.
2018  *
2019  * IJmp represents control flow to a single control successor not
2020  * statically known i.e. an indirect Jmp.
2021  *
2022  * @param *block  The IR block the node belongs to.
2023  * @param *tgt    The IR node representing the target address.
2024  */
2025 FIRM_API ir_node *new_r_IJmp(ir_node *block, ir_node *tgt);
2026
2027 /** Constructor for a Cond node.
2028  *
2029  * If c is mode_b represents a conditional branch (if/else). If c is
2030  * mode_Is/mode_Iu (?) represents a switch.  (Allocates dense Cond
2031  * node, default Proj is 0.)
2032  *
2033  * This is not consistent:  Input to Cond is Is, Proj has as proj number
2034  * longs.
2035  *
2036  * @param *block The IR block the node belongs to.
2037  * @param *c     The conditions parameter.Can be of mode b or I_u.
2038  */
2039 FIRM_API ir_node *new_r_Cond(ir_node *block, ir_node *c);
2040
2041 /** Constructor for a Return node.
2042  *
2043  * Returns the memory and zero or more return values.  Only node that
2044  * can end regular control flow.
2045  *
2046  * @param *block The IR block the node belongs to.
2047  * @param *store The state of memory.
2048  * @param arity  Number of array indices.
2049  * @param *in[]   Array with index inputs to the node. The constructor copies this array.
2050  */
2051 FIRM_API ir_node *new_r_Return(ir_node *block, ir_node *store,
2052                                int arity, ir_node *in[]);
2053
2054 /** Constructor for a Const node.
2055  *
2056  * Adds the node to the start block.
2057  *
2058  * Constructor for a Const node. The constant represents a target
2059  * value.  Sets the type information to type_unknown.  (No more
2060  * supported: If tv is entity derives a somehow useful type.)
2061  * Derives mode from passed tarval.
2062  *
2063  * @param *irg   The IR graph the node  belongs to.
2064  * @param *con   Points to an entry in the constant table.
2065  */
2066 FIRM_API ir_node *new_r_Const(ir_graph *irg, tarval *con);
2067
2068 /** Constructor for a Const node.
2069  *
2070  * Adds the node to the start block.
2071  *
2072  * Constructor for a Const node. The constant represents a target
2073  * value.  Sets the type information to type_unknown.  (No more
2074  * supported: If tv is entity derives a somehow useful type.)
2075  *
2076  * @param *irg   The IR graph the node  belongs to.
2077  * @param *mode  The mode of the operands and the results.
2078  * @param value  A value from which the tarval is made.
2079  */
2080 FIRM_API ir_node *new_r_Const_long(ir_graph *irg, ir_mode *mode, long value);
2081
2082 /** Constructor for a Const_type node.
2083  *
2084  * Adds the node to the start block.
2085  *
2086  * The constant represents a target value.  This constructor sets high
2087  * level type information for the constant value.
2088  * Derives mode from passed tarval.
2089  *
2090  * @param *irg   The IR graph the node  belongs to.
2091  * @param *con   Points to an entry in the constant table.
2092  * @param *tp    The type of the constant.
2093  */
2094 FIRM_API ir_node *new_r_Const_type(ir_graph *irg, tarval *con, ir_type *tp);
2095
2096 /** Constructor for a SymConst node.
2097  *
2098  *  This is the constructor for a symbolic constant.
2099  *    There are several kinds of symbolic constants:
2100  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
2101  *                          type the tag stands for is given explicitly.
2102  *    - symconst_type_size  The symbolic constant represents the size of a type.
2103  *                          The type of which the constant represents the size
2104  *                          is given explicitly.
2105  *    - symconst_type_align The symbolic constant represents the alignment of a
2106  *                          type.  The type of which the constant represents the
2107  *                          size is given explicitly.
2108  *    - symconst_addr_ent   The symbolic constant represents the address of an
2109  *                          entity (variable or method).  The variable is given
2110  *                          explicitly by a firm entity.
2111  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
2112  *                          entity in its owner type.
2113  *    - symconst_enum_const The symbolic constant is a enumeration constant of
2114  *                          an enumeration type.
2115  *
2116  *    Inputs to the node:
2117  *      No inputs except the block it belongs to.
2118  *    Outputs of the node.
2119  *      An unsigned integer (I_u) or a pointer (P).
2120  *
2121  *    Mention union in declaration so that the firmjni generator recognizes that
2122  *    it can not cast the argument to an int.
2123  *
2124  * @param *irg    The IR graph the node  belongs to.
2125  * @param mode    The mode for the SymConst.
2126  * @param value   A type, ident, entity or enum constant depending on the
2127  *                SymConst kind.
2128  * @param kind    The kind of the symbolic constant, see the list above
2129  */
2130 FIRM_API ir_node *new_r_SymConst(ir_graph *irg, ir_mode *mode,
2131                                  union symconst_symbol value,
2132                                  symconst_kind kind);
2133
2134 /** Constructor for a simpleSel node.
2135  *
2136  *  This is a shortcut for the new_d_Sel() constructor.  To be used for
2137  *  Sel nodes that do not select from an array, i.e., have no index
2138  *  inputs.  It adds the two parameters 0, NULL.
2139  *
2140  * @param *block     The IR block the node belongs to.
2141  * @param *store     The memory in which the object the entity should be selected
2142  *                   from is allocated.
2143  * @param *objptr    The object from that the Sel operation selects a
2144  *                   single attribute out.
2145  * @param *ent       The entity to select.
2146  */
2147 FIRM_API ir_node *new_r_simpleSel(ir_node *block, ir_node *store,
2148                                   ir_node *objptr, ir_entity *ent);
2149
2150 /** Constructor for a Sel node.
2151  *
2152  * The select node selects an entity (field or method) from an entity
2153  * with a compound type.  It explicitly specifies the entity selected.
2154  * Dynamically the node may select entities that overwrite the given
2155  * entity.  If the selected entity is an array element entity the Sel
2156  * node takes the required array indices as inputs.
2157  *
2158  * @param *block     The IR block the node belongs to.
2159  * @param *store     The memory in which the object the entity should be selected
2160  *                   from is allocated.
2161  * @param *objptr    A pointer to a compound entity the Sel operation selects a
2162  *                   single attribute from.
2163  * @param *n_index   The number of array indices needed to select an array element entity.
2164  * @param *index[]   If the compound entity is an array the indices of the selected
2165  *                   element entity.  The constructor copies this array.
2166  * @param *ent       The entity to select.
2167  */
2168 FIRM_API ir_node *new_r_Sel(ir_node *block, ir_node *store,
2169                             ir_node *objptr, int n_index, ir_node *index[],
2170                             ir_entity *ent);
2171
2172 /** Constructor for a Call node.
2173  *
2174  * Represents all kinds of method and function calls.
2175  *
2176  * @param *block  The IR block the node belongs to.
2177  * @param *store  The actual store.
2178  * @param *callee A pointer to the called procedure.
2179  * @param arity   The number of procedure parameters.
2180  * @param *in[]   An array with the pointers to the parameters. The constructor copies this array.
2181  * @param *tp     Type information of the procedure called.
2182  */
2183 FIRM_API ir_node *new_r_Call(ir_node *block, ir_node *store,
2184                              ir_node *callee, int arity, ir_node *in[],
2185                              ir_type *tp);
2186
2187 /** Constructor for a Builtin node.
2188  *
2189  * Represents a call of a backend-specific builtin..
2190  *
2191  * @param *block  The IR block the node belongs to.
2192  * @param *store  The actual store.
2193  * @param arity   The number of procedure parameters.
2194  * @param *in[]   An array with the pointers to the parameters. The constructor copies this array.
2195  * @param kind    The kind of the called builtin.
2196  * @param *tp     Type information of the procedure called.
2197  */
2198 FIRM_API ir_node *new_r_Builtin(ir_node *block, ir_node *store,
2199                                 int arity, ir_node *in[], ir_builtin_kind kind,
2200                                 ir_type *tp);
2201
2202 /** Constructor for a Add node.
2203  *
2204  * @param *block The IR block the node belongs to.
2205  * @param *op1   The first operand.
2206  * @param *op2   The second operand.
2207  * @param *mode  The mode of the operands and the result.
2208  */
2209 FIRM_API ir_node *new_r_Add(ir_node *block, ir_node *op1, ir_node *op2,
2210                             ir_mode *mode);
2211
2212 /**
2213  * Constructor for a Sub node.
2214  *
2215  * @param *block The IR block the node belongs to.
2216  * @param *op1   The first operand.
2217  * @param *op2   The second operand.
2218  * @param *mode  The mode of the operands and the results.
2219  */
2220 FIRM_API ir_node *new_r_Sub(ir_node *block, ir_node *op1, ir_node *op2,
2221                             ir_mode *mode);
2222
2223 /** Constructor for a Minus node.
2224  *
2225  * @param *block The IR block the node belongs to.
2226  * @param *op    The operand.
2227  * @param *mode  The mode of the operand and the result.
2228  */
2229 FIRM_API ir_node *new_r_Minus(ir_node *block, ir_node *op, ir_mode *mode);
2230
2231 /** Constructor for a Mul node.
2232  *
2233  * @param *block The IR block the node belongs to.
2234  * @param *op1   The first operand.
2235  * @param *op2   The second operand.
2236  * @param *mode  The mode of the operands and the result.
2237  */
2238 FIRM_API ir_node *new_r_Mul(ir_node *block, ir_node *op1, ir_node *op2,
2239                             ir_mode *mode);
2240
2241 /** Constructor for a Mulh node.
2242  *
2243  * @param *block The IR block the node belongs to.
2244  * @param *op1   The first operand.
2245  * @param *op2   The second operand.
2246  * @param *mode  The mode of the operands and the result.
2247  */
2248 FIRM_API ir_node *new_r_Mulh(ir_node *block, ir_node *op1, ir_node *op2,
2249                              ir_mode *mode);
2250
2251 /** Constructor for a Quot node.
2252  *
2253  * @param *block The IR block the node belongs to.
2254  * @param *memop The store needed to model exceptions
2255  * @param *op1   The first operand.
2256  * @param *op2   The second operand.
2257  * @param *mode  The mode of the result.
2258  * @param state  The pinned state.
2259  */
2260 FIRM_API ir_node *new_r_Quot(ir_node *block, ir_node *memop,
2261                              ir_node *op1, ir_node *op2, ir_mode *mode,
2262                              op_pin_state state);
2263
2264 /** Constructor for a DivMod node.
2265  *
2266  * @param *block The IR block the node belongs to.
2267  * @param *memop The store needed to model exceptions
2268  * @param *op1   The first operand.
2269  * @param *op2   The second operand.
2270  * @param *mode  The mode of the results.
2271  * @param state  The pinned state.
2272  */
2273 FIRM_API ir_node *new_r_DivMod(ir_node *block, ir_node *memop,
2274                                ir_node *op1, ir_node *op2, ir_mode *mode,
2275                                op_pin_state state);
2276
2277 /** Constructor for a Div node.
2278  *
2279  * @param *block The IR block the node belongs to.
2280  * @param *memop The store needed to model exceptions
2281  * @param *op1   The first operand.
2282  * @param *op2   The second operand.
2283  * @param *mode  The mode of the result.
2284  * @param state  The pinned state.
2285  */
2286 FIRM_API ir_node *new_r_Div(ir_node *block, ir_node *memop,
2287                             ir_node *op1, ir_node *op2, ir_mode *mode,
2288                             op_pin_state state);
2289
2290 /** Constructor for a remainderless Div node.
2291  *
2292  * @param *block The IR block the node belongs to.
2293  * @param *memop The store needed to model exceptions
2294  * @param *op1   The first operand.
2295  * @param *op2   The second operand.
2296  * @param *mode  The mode of the result.
2297  * @param state  The pinned state.
2298  */
2299 FIRM_API ir_node *new_r_DivRL(ir_node *block, ir_node *memop,
2300                               ir_node *op1, ir_node *op2, ir_mode *mode,
2301                               op_pin_state state);
2302
2303 /** Constructor for a Mod node.
2304  *
2305  * @param *block The IR block the node belongs to.
2306  * @param *memop The store needed to model exceptions
2307  * @param *op1   The first operand.
2308  * @param *op2   The second operand.
2309  * @param *mode  The mode of the result.
2310  * @param state  The pinned state.
2311  */
2312 FIRM_API ir_node *new_r_Mod(ir_node *block, ir_node *memop,
2313                             ir_node *op1, ir_node *op2, ir_mode *mode,
2314                             op_pin_state state);
2315
2316 /** Constructor for a Abs node.
2317  *
2318  * @param *block The IR block the node belongs to.
2319  * @param *op    The operand
2320  * @param *mode  The mode of the operands and the result.
2321  */
2322 FIRM_API ir_node *new_r_Abs(ir_node *block, ir_node *op, ir_mode *mode);
2323
2324 /** Constructor for a And node.
2325  *
2326  * @param *block The IR block the node belongs to.
2327  * @param *op1   The first operand.
2328  * @param *op2   The second operand.
2329  * @param *mode  The mode of the operands and the result.
2330  */
2331 FIRM_API ir_node *new_r_And(ir_node *block, ir_node *op1, ir_node *op2,
2332                             ir_mode *mode);
2333
2334 /** Constructor for a Or node.
2335  *
2336  * @param *block The IR block the node belongs to.
2337  * @param *op1   The first operand.
2338  * @param *op2   The second operand.
2339  * @param *mode  The mode of the operands and the result.
2340  */
2341 FIRM_API ir_node *new_r_Or(ir_node *block, ir_node *op1, ir_node *op2,
2342                            ir_mode *mode);
2343
2344 /** Constructor for a Eor node.
2345  *
2346  * @param *block The IR block the node belongs to.
2347  * @param *op1   The first operand.
2348  * @param *op2   The second operand.
2349  * @param *mode  The mode of the operands and the results.
2350  */
2351 FIRM_API ir_node *new_r_Eor(ir_node *block, ir_node *op1, ir_node *op2,
2352                             ir_mode *mode);
2353
2354 /** Constructor for a Not node.
2355  *
2356  * @param *block The IR block the node belongs to.
2357  * @param *op    The operand.
2358  * @param *mode  The mode of the operand and the result.
2359  */
2360 FIRM_API ir_node *new_r_Not(ir_node *block, ir_node *op, ir_mode *mode);
2361
2362 /** Constructor for a Cmp node.
2363  *
2364  * @param *block The IR block the node belongs to.
2365  * @param *op1   The first operand.
2366  * @param *op2   The second operand.
2367  */
2368 FIRM_API ir_node *new_r_Cmp(ir_node *block, ir_node *op1, ir_node *op2);
2369
2370 /** Constructor for a Shl node.
2371  *
2372  * @param   *block The IR block the node belongs to.
2373  * @param   *op    The operand.
2374  * @param   *k     The number of bits to  shift the operand .
2375  * @param   *mode  The mode of the operand and the result.
2376  */
2377 FIRM_API ir_node *new_r_Shl(ir_node *block, ir_node *op, ir_node *k,
2378                             ir_mode *mode);
2379
2380 /** Constructor for a Shr node.
2381  *
2382  * @param *block The IR block the node belongs to.
2383  * @param *op    The operand.
2384  * @param *k     The number of bits to shift the operand .
2385  * @param *mode  The mode of the operand and the result.
2386  */
2387 FIRM_API ir_node *new_r_Shr(ir_node *block, ir_node *op, ir_node *k,
2388                             ir_mode *mode);
2389
2390 /**
2391  * Constructor for a Shrs node.
2392  *
2393  * @param  *block The IR block the node belongs to.
2394  * @param  *op    The operand.
2395  * @param  *k     The number of bits to shift the operand.
2396  * @param  *mode  The mode of the operand and the result.
2397  */
2398 FIRM_API ir_node *new_r_Shrs(ir_node *block, ir_node *op, ir_node *k,
2399                              ir_mode *mode);
2400
2401 /** Constructor for a Rotl node.
2402  *
2403  * @param *block The IR block the node belongs to.
2404  * @param *op    The operand.
2405  * @param *k     The number of bits to rotate the operand.
2406  * @param *mode  The mode of the operand.
2407  */
2408 FIRM_API ir_node *new_r_Rotl(ir_node *block, ir_node *op, ir_node *k,
2409                              ir_mode *mode);
2410
2411 /** Constructor for a Conv node.
2412  *
2413  * @param *block The IR block the node belongs to.
2414  * @param *op    The operand.
2415  * @param *mode  The mode of this the operand muss be converted .
2416  */
2417 FIRM_API ir_node *new_r_Conv(ir_node *block, ir_node *op, ir_mode *mode);
2418
2419 /** Constructor for a strict Conv node.
2420  *
2421  * @param *block The IR block the node belongs to.
2422  * @param *op    The operand.
2423  * @param *mode  The mode of this the operand muss be converted .
2424  */
2425 FIRM_API ir_node *new_r_strictConv(ir_node *block, ir_node *op, ir_mode *mode);
2426
2427 /** Constructor for a Cast node.
2428  *
2429  * High level type cast
2430  *
2431  * @param *block The IR block the node belongs to.
2432  * @param *op    The operand.
2433  * @param *to_tp The type of this the operand muss be casted .
2434  */
2435 FIRM_API ir_node *new_r_Cast(ir_node *block, ir_node *op, ir_type *to_tp);
2436
2437 /** Constructor for a Carry node.
2438  *
2439  * @param *block The IR block the node belongs to.
2440  * @param *op1   The first operand.
2441  * @param *op2   The second operand.
2442  * @param *mode  The mode of the operands and the result.
2443  */
2444 FIRM_API ir_node *new_r_Carry(ir_node *block, ir_node *op1, ir_node *op2,
2445                               ir_mode *mode);
2446
2447 /**
2448  * Constructor for a Borrow node.
2449  *
2450  * @param *block The IR block the node belongs to.
2451  * @param *op1   The first operand.
2452  * @param *op2   The second operand.
2453  * @param *mode  The mode of the operands and the results.
2454  */
2455 FIRM_API ir_node *new_r_Borrow(ir_node *block, ir_node *op1, ir_node *op2,
2456                                ir_mode *mode);
2457
2458 /** Constructor for a Phi node.
2459  *
2460  * @param *block The IR block the node belongs to.
2461  * @param arity  The number of predecessors
2462  * @param *in[]  Array with predecessors. The constructor copies this array.
2463  * @param *mode  The mode of it's inputs and output.
2464  */
2465 FIRM_API ir_node *new_r_Phi(ir_node *block, int arity, ir_node *in[],
2466                             ir_mode *mode);
2467
2468 /** Constructor for a Load node.
2469  *
2470  * @param *block The IR block the node belongs to.
2471  * @param *store The current memory
2472  * @param *adr   A pointer to the variable to be read in this memory.
2473  * @param *mode  The mode of the value to be loaded.
2474  * @param  flags Additional flags for alignment, volatility and pin state.
2475  */
2476 FIRM_API ir_node *new_r_Load(ir_node *block, ir_node *store,
2477                              ir_node *adr, ir_mode *mode, ir_cons_flags flags);
2478
2479 /** Constructor for a Store node.
2480  *
2481  * @param *block The IR block the node belongs to.
2482  * @param *store The current memory
2483  * @param *adr   A pointer to the variable to be read in this memory.
2484  * @param *val   The value to write to this variable.
2485  * @param  flags Additional flags for alignment, volatility and pin state.
2486  */
2487 FIRM_API ir_node *new_r_Store(ir_node *block, ir_node *store,
2488                               ir_node *adr, ir_node *val, ir_cons_flags flags);
2489
2490 /** Constructor for a Alloc node.
2491  *
2492  * The Alloc node extends the memory by space for an entity of type alloc_type.
2493  *
2494  * @param *block      The IR block the node belongs to.
2495  * @param *store      The memory which shall contain the new variable.
2496  * @param *count      The number of objects to allocate.
2497  * @param *alloc_type The type of the allocated variable.
2498  * @param where       Where to allocate the variable, either heap_alloc or stack_alloc.
2499  */
2500 FIRM_API ir_node *new_r_Alloc(ir_node *block, ir_node *store,
2501                               ir_node *count, ir_type *alloc_type,
2502                               ir_where_alloc where);
2503
2504 /** Constructor for a Free node.
2505  *
2506  * Frees the memory occupied by the entity pointed to by the pointer
2507  * arg.  Type indicates the type of the entity the argument points to.
2508  *
2509  * @param *block      The IR block the node belongs to.
2510  * @param *store      The memory which shall contain the new variable.
2511  * @param *ptr        The pointer to the object to free.
2512  * @param *size       The number of objects of type free_type to free in a sequence.
2513  * @param *free_type  The type of the freed variable.
2514  * @param where       Where the variable was allocated, either heap_alloc or stack_alloc.
2515  */
2516 FIRM_API ir_node *new_r_Free(ir_node *block, ir_node *store, ir_node *ptr,
2517                              ir_node *size, ir_type *free_type,
2518                              ir_where_alloc where);
2519
2520 /** Constructor for a Sync node.
2521  *
2522  * Merges several memory values.  The node assumes that a variable
2523  * either occurs only in one of the memories, or it contains the same
2524  * value in all memories where it occurs.
2525  *
2526  * @param *block   The IR block the node belongs to.
2527  * @param arity    The number of memories to synchronize.
2528  * @param *in[]    An array of pointers to nodes that produce an output of  type memory.
2529  *                 The constructor copies this array.
2530  */
2531 FIRM_API ir_node *new_r_Sync(ir_node *block, int arity, ir_node *in[]);
2532
2533 /** Constructor for a Proj node.
2534  *
2535  * Projects a single value out of a tuple.  The parameter proj gives the
2536  * position of the value within the tuple.
2537  *
2538  * @param arg    A node producing a tuple.
2539  * @param mode   The mode of the value to project.
2540  * @param proj   The position of the value in the tuple.
2541  */
2542 FIRM_API ir_node *new_r_Proj(ir_node *arg, ir_mode *mode, long proj);
2543
2544 /** Constructor for a defaultProj node.
2545  *
2546  * Represents the default control flow of a Switch-Cond node.
2547  *
2548  * @param arg       A node producing a tuple.
2549  * @param max_proj  The end  position of the value in the tuple.
2550  */
2551 FIRM_API ir_node *new_r_defaultProj(ir_node *arg, long max_proj);
2552
2553
2554 /** Constructor for a Tuple node.
2555  *
2556  * This is an auxiliary node to replace a node that returns a tuple
2557  * without changing the corresponding Proj nodes.
2558  *
2559  * @param *block  The IR block the node belongs to.
2560  * @param arity   The number of tuple elements.
2561  * @param *in[]   An array containing pointers to the nodes producing the tuple elements.
2562  *                The constructor copies this array.
2563  */
2564 FIRM_API ir_node *new_r_Tuple(ir_node *block, int arity, ir_node *in[]);
2565
2566 /** Constructor for a Id node.
2567  *
2568  * This is an auxiliary node to replace a node that returns a single
2569  * value.
2570  *
2571  * @param *block  The IR block the node belongs to.
2572  * @param *val    The operand to Id.
2573  * @param *mode   The mode of *val.
2574  */
2575 FIRM_API ir_node *new_r_Id(ir_node *block, ir_node *val, ir_mode *mode);
2576
2577 /** Constructor for a Bad node.
2578  *
2579  * Returns the unique Bad node of the graph.  The same as
2580  * get_irg_bad().
2581  *
2582  * @param *irg    The IR graph the node  belongs to.
2583  */
2584 FIRM_API ir_node *new_r_Bad(ir_graph *irg);
2585
2586 /** Constructor for a Confirm node.
2587  *
2588  * Specifies constraints for a value.  To support dataflow analyses.
2589  *
2590  * Example: If the value never exceeds '100' this is expressed by placing a
2591  * Confirm node val = new_d_Confirm(db, val, 100, '<=') on the dataflow edge.
2592  *
2593  * @param *block  The IR block the node belong to.
2594  * @param *val    The value we express a constraint for
2595  * @param *bound  The value to compare against. Must be a firm node, typically a constant.
2596  * @param cmp     The compare operation.
2597  */
2598 FIRM_API ir_node *new_r_Confirm(ir_node *block, ir_node *val, ir_node *bound,
2599                                 pn_Cmp cmp);
2600
2601 /** Constructor for a Unknown node.
2602  *
2603  * Represents an arbitrary value.  Places the node in
2604  * the start block.
2605  *
2606  * @param *irg    The IR graph the node  belongs to.
2607  * @param *m      The mode of the unknown value.
2608  */
2609 FIRM_API ir_node *new_r_Unknown(ir_graph *irg, ir_mode *m);
2610
2611 /** Constructor for a NoMem node.
2612  *
2613  * Returns the unique NoMem node of the graph.  The same as
2614  * get_irg_no_mem().
2615  *
2616  * @param *irg    The IR graph the node belongs to.
2617  */
2618 FIRM_API ir_node *new_r_NoMem(ir_graph *irg);
2619
2620 /** Constructor for a Mux node.
2621  *
2622  * @param *block    The block the node belong to.
2623  * @param *sel      The ir_node that calculates the boolean select.
2624  * @param *ir_true  The ir_node that calculates the true result.
2625  * @param *ir_false The ir_node that calculates the false result.
2626  * @param *mode     The mode of the node (and it_true and ir_false).
2627  */
2628 FIRM_API ir_node *new_r_Mux(ir_node *block, ir_node *sel,
2629                             ir_node *ir_false, ir_node *ir_true, ir_mode *mode);
2630
2631 /** Constructor for a CopyB node.
2632  *
2633  * @param *block      The block the node belong to.
2634  * @param *store      The current memory
2635  * @param *dst        The ir_node that represents the destination address.
2636  * @param *src        The ir_node that represents the source address.
2637  * @param *data_type  The type of the copied data
2638  */
2639 FIRM_API ir_node *new_r_CopyB(ir_node *block, ir_node *store,
2640                               ir_node *dst, ir_node *src, ir_type *data_type);
2641
2642 /** Constructor for a InstOf node.
2643  *
2644  * A High-Level Type check.
2645  *
2646  * @param *block     The block the node belong to.
2647  * @param *store     The memory in which the object the entity should be selected
2648  *                   from is allocated.
2649  * @param *objptr    A pointer to a object of a class type.
2650  * @param *type      The type of which objptr must be.
2651  */
2652 FIRM_API ir_node *new_r_InstOf(ir_node *block, ir_node *store,
2653                                ir_node *objptr, ir_type *type);
2654
2655 /** Constructor for a Raise node.
2656  *
2657  * A High-Level Exception throw.
2658  *
2659  * @param *block The IR block the node belongs to.
2660  * @param *store The current memory.
2661  * @param *obj   A pointer to the Except variable.
2662  */
2663 FIRM_API ir_node *new_r_Raise(ir_node *block, ir_node *store, ir_node *obj);
2664
2665 /** Constructor for a Bound node.
2666  *
2667  * A High-Level bounds check. Checks whether lower <= idx && idx < upper.
2668  *
2669  * @param *block      The block the node belong to.
2670  * @param *store      The current memory.
2671  * @param *idx        The ir_node that represents an index.
2672  * @param *lower      The ir_node that represents the lower bound for the index.
2673  * @param *upper      The ir_node that represents the upper bound for the index.
2674  */
2675 FIRM_API ir_node *new_r_Bound(ir_node *block, ir_node *store,
2676                               ir_node *idx, ir_node *lower, ir_node *upper);
2677
2678 /** Constructor for a Pin node.
2679  *
2680  * @param *block      The block the node belong to.
2681  * @param *node       The node which value should be pinned.
2682  */
2683 FIRM_API ir_node *new_r_Pin(ir_node *block, ir_node *node);
2684
2685 /** Constructor for an ASM pseudo node.
2686  *
2687  * @param *block      The block the node belong to.
2688  * @param arity       The number of data inputs to the node.
2689  * @param *in         The array of length arity of data inputs.
2690  * @param *inputs     The array of length arity of input constraints.
2691  * @param n_outs      The number of data outputs to the node.
2692  * @param *outputs    The array of length n_outs of output constraints.
2693  * @param n_clobber   The number of clobbered registers.
2694  * @param *clobber    The array of length n_clobber of clobbered registers.
2695  * @param *asm_text   The assembler text.
2696  */
2697 FIRM_API ir_node *new_r_ASM(ir_node *block,
2698                             int arity, ir_node *in[], ir_asm_constraint *inputs,
2699                             int n_outs, ir_asm_constraint *outputs,
2700                             int n_clobber, ident *clobber[], ident *asm_text);
2701
2702 /*-----------------------------------------------------------------------*/
2703 /* The block oriented interface                                          */
2704 /*-----------------------------------------------------------------------*/
2705
2706 /** Sets the current block in which the following constructors place the
2707  *  nodes they construct.
2708  *
2709  *  @param target  The new current block.
2710  */
2711 FIRM_API void set_cur_block(ir_node *target);
2712
2713 /** Returns the current block of the current graph. */
2714 FIRM_API ir_node *get_cur_block(void);
2715
2716 /** Constructor for a Block node.
2717  *
2718  * Adds the block to the graph in current_ir_graph. Constructs a Block
2719  * with a fixed number of predecessors.
2720  *
2721  * @param *db    A Pointer for debug information.
2722  * @param arity  The number of control predecessors.
2723  * @param in[]   An array of control predecessors.  The length of
2724  *               the array must be 'arity'.
2725  */
2726 FIRM_API ir_node *new_d_Block(dbg_info *db, int arity, ir_node *in[]);
2727
2728 /** Constructor for a Start node.
2729  *
2730  * Adds the node to the block in current_ir_block.
2731  *
2732  * @param *db    A pointer for debug information.
2733  */
2734 FIRM_API ir_node *new_d_Start(dbg_info *db);
2735
2736 /** Constructor for a End node.
2737  *
2738  * Adds the node to the block in current_ir_block.
2739  *
2740  * @param *db     A pointer for debug information.
2741  */
2742 FIRM_API ir_node *new_d_End(dbg_info *db);
2743
2744 /** Constructor for a Jmp node.
2745  *
2746  * Adds the node to the block in current_ir_block.
2747  *
2748  * Jmp represents control flow to a single control successor.
2749  *
2750  * @param *db     A pointer for debug information.
2751  */
2752 FIRM_API ir_node *new_d_Jmp(dbg_info *db);
2753
2754 /** Constructor for an IJmp node.
2755  *
2756  * IJmp represents control flow to a single control successor not
2757  * statically known i.e. an indirect Jmp.
2758  *
2759  * @param *db     A pointer for debug information.
2760  * @param *tgt    The IR node representing the target address.
2761  */
2762 FIRM_API ir_node *new_d_IJmp(dbg_info *db, ir_node *tgt);
2763
2764 /** Constructor for a Cond node.
2765  *
2766  * Adds the node to the block in current_ir_block.
2767  *
2768  * If c is mode_b represents a conditional branch (if/else). If c is
2769  * mode_Is/mode_Iu (?) represents a switch.  (Allocates dense Cond
2770  * node, default Proj is 0.)
2771  *
2772  * This is not consistent:  Input to Cond is Is, Proj has as proj number
2773  * longs.
2774  *
2775  * @param *db    A pointer for debug information.
2776  * @param *c     The conditions parameter.Can be of mode b or I_u.
2777  */
2778 FIRM_API ir_node *new_d_Cond(dbg_info *db, ir_node *c);
2779
2780 /** Constructor for a Return node.
2781  *
2782  * Adds the node to the block in current_ir_block.
2783  *
2784  * Returns the memory and zero or more return values.  Only node that
2785  * can end regular control flow.
2786  *
2787  * @param *db    A pointer for debug information.
2788  * @param *store The state of memory.
2789  * @param arity  Number of array indices.
2790  * @param *in    Array with index inputs to the node.
2791  */
2792 FIRM_API ir_node *new_d_Return(dbg_info *db, ir_node *store,
2793                                int arity, ir_node *in[]);
2794
2795 /** Constructor for a Const_type node.
2796  *
2797  * Adds the node to the start block.
2798  *
2799  * The constant represents a target value.  This constructor sets high
2800  * level type information for the constant value.
2801  * Derives mode from passed tarval.
2802  *
2803  * @param *db    A pointer for debug information.
2804  * @param *con   Points to an entry in the constant table. This pointer is
2805                  added to the attributes of the node.
2806  * @param *tp    The type of the constant.
2807  */
2808 FIRM_API ir_node *new_d_Const_type(dbg_info *db, tarval *con, ir_type *tp);
2809
2810 /** Constructor for a Const node.
2811  *
2812  * Adds the node to the block in current_ir_block.
2813  *
2814  * Constructor for a Const node. The constant represents a target
2815  * value.  Sets the type information to type_unknown.  (No more
2816  * supported: If tv is entity derives a somehow useful type.)
2817  * Derives mode from passed tarval.
2818  *
2819  * @param *db    A pointer for debug information.
2820  * @param *con   Points to an entry in the constant table. This pointer is added
2821  *               to the attributes of the node.
2822  */
2823 FIRM_API ir_node *new_d_Const(dbg_info *db, tarval *con);
2824
2825 /**
2826  * @see new_rd_Const_long()
2827  *
2828  * @param *db    A pointer for debug information.
2829  * @param *mode  The mode of the operands and results.
2830  * @param value  A value from which the tarval is made.
2831  */
2832 FIRM_API ir_node *new_d_Const_long(dbg_info *db, ir_mode *mode, long value);
2833
2834 /** Constructor for a SymConst_type node.
2835  *
2836  *  This is the constructor for a symbolic constant.
2837  *    There are several kinds of symbolic constants:
2838  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
2839  *                          type the tag stands for is given explicitly.
2840  *    - symconst_type_size  The symbolic constant represents the size of a type.
2841  *                          The type of which the constant represents the size
2842  *                          is given explicitly.
2843  *    - symconst_type_align The symbolic constant represents the alignment of a
2844  *                          type.  The type of which the constant represents the
2845  *                          size is given explicitly.
2846  *    - symconst_addr_ent   The symbolic constant represents the address of an
2847  *                          entity (variable or method).  The variable is given
2848  *                          explicitly by a firm entity.
2849  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
2850  *                          entity in its owner type.
2851  *    - symconst_enum_const The symbolic constant is a enumeration constant of
2852  *                          an enumeration type.
2853  *
2854  *    Inputs to the node:
2855  *      No inputs except the block it belongs to.
2856  *    Outputs of the node.
2857  *      An unsigned integer (I_u) or a pointer (P).
2858  *
2859  *    Mention union in declaration so that the firmjni generator recognizes that
2860  *    it can not cast the argument to an int.
2861  *
2862  * @param *db     A pointer for debug information.
2863  * @param mode    The mode for the SymConst.
2864  * @param value   A type, ident, entity or enum constant depending on the
2865  *                SymConst kind.
2866  * @param kind    The kind of the symbolic constant, see the list above
2867  * @param tp      The source type of the constant.
2868  */
2869 FIRM_API ir_node *new_d_SymConst_type(dbg_info *db, ir_mode *mode,
2870                                       union symconst_symbol value,
2871                                       symconst_kind kind, ir_type *tp);
2872
2873 /** Constructor for a SymConst node.
2874  *
2875  *  Same as new_d_SymConst_type, except that it sets the type to type_unknown.
2876  */
2877 FIRM_API ir_node *new_d_SymConst(dbg_info *db, ir_mode *mode,
2878                                  union symconst_symbol value,
2879                                  symconst_kind kind);
2880
2881 /** Constructor for a simpleSel node.
2882  *
2883  *  This is a shortcut for the new_d_Sel() constructor.  To be used for
2884  *  Sel nodes that do not select from an array, i.e., have no index
2885  *  inputs.  It adds the two parameters 0, NULL.
2886  *
2887  * @param   *db        A pointer for debug information.
2888  * @param   *store     The memory in which the object the entity should be
2889  *                     selected from is allocated.
2890  * @param   *objptr    The object from that the Sel operation selects a
2891  *                     single attribute out.
2892  * @param   *ent       The entity to select.
2893  */
2894 FIRM_API ir_node *new_d_simpleSel(dbg_info *db, ir_node *store, ir_node *objptr,
2895                                   ir_entity *ent);
2896
2897 /** Constructor for a Sel node.
2898  *
2899  * The select node selects an entity (field or method) from an entity
2900  * with a compound type.  It explicitly specifies the entity selected.
2901  * Dynamically the node may select entities that overwrite the given
2902  * entity.  If the selected entity is an array element entity the Sel
2903  * node takes the required array indices as inputs.
2904  * Adds the node to the block in current_ir_block.
2905  *
2906  * @param   *db        A pointer for debug information.
2907  * @param   *store     The memory in which the object the entity should be selected
2908  *                     from is allocated.
2909  * @param   *objptr    A pointer to a compound entity the Sel operation selects a
2910  *                     single attribute from.
2911  * @param   arity      The number of array indices needed to select an array element entity.
2912  * @param   *in[]      If the compound entity is an array the indices of the selected
2913  *                     element entity.  The constructor copies this array.
2914  * @param   *ent       The entity to select.
2915  */
2916 FIRM_API ir_node *new_d_Sel(dbg_info *db, ir_node *store, ir_node *objptr,
2917                             int arity, ir_node *in[], ir_entity *ent);
2918
2919 /** Constructor for a Call node.
2920  *
2921  * Represents all kinds of method and function calls.
2922  * Adds the node to the block in current_ir_block.
2923  *
2924  * @param   *db     A pointer for debug information.
2925  * @param   *store  The actual store.
2926  * @param   *callee A pointer to the called procedure.
2927  * @param   arity   The number of procedure parameters.
2928  * @param   *in[]   An array with the pointers to the parameters. The constructor copies this array.
2929  * @param   *tp     Type information of the procedure called.
2930  */
2931 FIRM_API ir_node *new_d_Call(dbg_info *db, ir_node *store, ir_node *callee,
2932                              int arity, ir_node *in[], ir_type *tp);
2933
2934 /** Constructor for a Builtin node.
2935  *
2936  * Represents a call of a backend-specific builtin..
2937  * Adds the node to the block in current_ir_block.
2938  *
2939  * @param   *db     A pointer for debug information.
2940  * @param   *store  The actual store.
2941  * @param   arity   The number of procedure parameters.
2942  * @param   *in[]   An array with the pointers to the parameters. The constructor copies this array.
2943  * @param   kind    The kind of the called builtin.
2944  * @param   *tp     Type information of the procedure called.
2945  */
2946 FIRM_API ir_node *new_d_Builtin(dbg_info *db, ir_node *store,
2947                                 int arity, ir_node *in[],
2948                                 ir_builtin_kind kind, ir_type *tp);
2949
2950 /** Constructor for a Add node.
2951  *
2952  * Adds the node to the block in current_ir_block.
2953  *
2954  * @param   *db    A pointer for debug information.
2955  * @param   *op1   The first operand.
2956  * @param   *op2   The second operand.
2957  * @param   *mode  The mode of the operands and the result.
2958  */
2959 FIRM_API ir_node *new_d_Add(dbg_info *db, ir_node *op1, ir_node *op2,
2960                             ir_mode *mode);
2961
2962 /** Constructor for a Sub node.
2963  *
2964  * Adds the node to the block in current_ir_block.
2965  *
2966  * @param   *db    A pointer for debug information.
2967  * @param   *op1   The first operand.
2968  * @param   *op2   The second operand.
2969  * @param   *mode  The mode of the operands and the result.
2970  */
2971 FIRM_API ir_node *new_d_Sub(dbg_info *db, ir_node *op1, ir_node *op2,
2972                             ir_mode *mode);
2973
2974 /** Constructor for a Minus node.
2975  *
2976  * Adds the node to the block in current_ir_block.
2977  *
2978  * @param   *db    A pointer for debug information.
2979  * @param   *op    The operand .
2980  * @param   *mode  The mode of the operand and the result.
2981  */
2982 FIRM_API ir_node *new_d_Minus(dbg_info *db, ir_node *op,  ir_mode *mode);
2983
2984 /** Constructor for a Mul node.
2985  *
2986  * Adds the node to the block in current_ir_block.
2987  *
2988  * @param   *db    A pointer for debug information.
2989  * @param   *op1   The first operand.
2990  * @param   *op2   The second operand.
2991  * @param   *mode  The mode of the operands and the result.
2992  */
2993 FIRM_API ir_node *new_d_Mul(dbg_info *db, ir_node *op1, ir_node *op2,
2994                             ir_mode *mode);
2995
2996 /** Constructor for a Mulh node.
2997  *
2998  * Adds the node to the block in current_ir_block.
2999  *
3000  * @param   *db    A pointer for debug information.
3001  * @param   *op1   The first operand.
3002  * @param   *op2   The second operand.
3003  * @param   *mode  The mode of the operands and the result.
3004  */
3005 FIRM_API ir_node *new_d_Mulh(dbg_info *db, ir_node *op1, ir_node *op2,
3006                              ir_mode *mode);
3007
3008 /** Constructor for a Quot node.
3009  *
3010  * Adds the node to the block in current_ir_block.
3011  *
3012  * @param   *db    A pointer for debug information.
3013  * @param   *memop The store needed to model exceptions
3014  * @param   *op1   The first operand.
3015  * @param   *op2   The second operand.
3016  * @param   *mode  The mode of the result.
3017  * @param   state  The pinned state.
3018  */
3019 FIRM_API ir_node *new_d_Quot(dbg_info *db, ir_node *memop,
3020                              ir_node *op1, ir_node *op2, ir_mode *mode,
3021                              op_pin_state state);
3022
3023 /** Constructor for a DivMod node.
3024  *
3025  * Adds the node to the block in current_ir_block.
3026  *
3027  * @param   *db    A pointer for debug information.
3028  * @param   *memop The store needed to model exceptions
3029  * @param   *op1   The first operand.
3030  * @param   *op2   The second operand.
3031  * @param   *mode  The mode of the results.
3032  * @param   state  The pinned state.
3033  */
3034 FIRM_API ir_node *new_d_DivMod(dbg_info *db, ir_node *memop, ir_node *op1,
3035                                ir_node *op2, ir_mode *mode, op_pin_state state);
3036
3037 /** Constructor for a Div node.
3038  *
3039  * Adds the node to the block in current_ir_block.
3040  *
3041  * @param   *db    A pointer for debug information.
3042  * @param   *memop The store needed to model exceptions
3043  * @param   *op1   The first operand.
3044  * @param   *op2   The second operand.
3045  * @param   *mode  The mode of the result.
3046  * @param   state  The pinned state.
3047  */
3048 FIRM_API ir_node *new_d_Div(dbg_info *db, ir_node *memop, ir_node *op1,
3049                             ir_node *op2, ir_mode *mode, op_pin_state state);
3050
3051 /** Constructor for a remainderless Div node.
3052  *
3053  * Adds the node to the block in current_ir_block.
3054  *
3055  * @param   *db    A pointer for debug information.
3056  * @param   *memop The store needed to model exceptions
3057  * @param   *op1   The first operand.
3058  * @param   *op2   The second operand.
3059  * @param   *mode  The mode of the result.
3060  * @param   state  The pinned state.
3061  */
3062 FIRM_API ir_node *new_d_DivRL(dbg_info *db, ir_node *memop,
3063                               ir_node *op1, ir_node *op2, ir_mode *mode,
3064                               op_pin_state state);
3065
3066 /** Constructor for a Mod node.
3067  *
3068  * Adds the node to the block in current_ir_block.
3069  *
3070  * @param   *db    A pointer for debug information.
3071  * @param   *memop The store needed to model exceptions
3072  * @param   *op1   The first operand.
3073  * @param   *op2   The second operand.
3074  * @param   *mode  The mode of the result.
3075  * @param   state  The pinned state.
3076  */
3077 FIRM_API ir_node *new_d_Mod(dbg_info *db, ir_node *memop,
3078                             ir_node *op1, ir_node *op2, ir_mode *mode,
3079                             op_pin_state state);
3080
3081 /** Constructor for a Abs node.
3082  *
3083  * Adds the node to the block in current_ir_block.
3084  *
3085  * @param   *db    A pointer for debug information.
3086  * @param   *op    The operand
3087  * @param   *mode  The mode of the operands and the result.
3088  */
3089 FIRM_API ir_node *new_d_Abs(dbg_info *db, ir_node *op, ir_mode *mode);
3090
3091 /** Constructor for a And node.
3092  *
3093  * Adds the node to the block in current_ir_block.
3094  *
3095  * @param   *db    A pointer for debug information.
3096  * @param   *op1   The first operand.
3097  * @param   *op2   The second operand.
3098  * @param   *mode  The mode of the operands and the result.
3099  */
3100 FIRM_API ir_node *new_d_And(dbg_info *db, ir_node *op1, ir_node *op2,
3101                             ir_mode *mode);
3102
3103 /** Constructor for a Or node.
3104  *
3105  * Adds the node to the block in current_ir_block.
3106  *
3107  * @param   *db    A pointer for debug information.
3108  * @param   *op1   The first operand.
3109  * @param   *op2   The second operand.
3110  * @param   *mode  The mode of the operands and the result.
3111  */
3112 FIRM_API ir_node *new_d_Or(dbg_info *db, ir_node *op1, ir_node *op2,
3113                            ir_mode *mode);
3114
3115 /** Constructor for a Eor node.
3116  *
3117  * Adds the node to the block in current_ir_block.
3118  *
3119  * @param   *db    A pointer for debug information.
3120  * @param   *op1   The first operand.
3121  * @param   *op2   The second operand.
3122  * @param   *mode  The mode of the operands and the results.
3123  */
3124 FIRM_API ir_node *new_d_Eor(dbg_info *db, ir_node *op1, ir_node *op2,
3125                             ir_mode *mode);
3126
3127 /** Constructor for a Not node.
3128  *
3129  * Adds the node to the block in current_ir_block.
3130  *
3131  * @param   *db    A pointer for debug information.
3132  * @param   *op    The operand.
3133  * @param   *mode  The mode of the operand and the result.
3134  */
3135 FIRM_API ir_node *new_d_Not(dbg_info *db, ir_node *op, ir_mode *mode);
3136
3137 /** Constructor for a Shl node.
3138  *
3139  * Adds the node to the block in current_ir_block.
3140  *
3141  * @param   *db    A pointer for debug information.
3142  * @param   *op    The operand.
3143  * @param   *k     The number of bits to  shift the operand .
3144  * @param   *mode  The mode of the operand and the result.
3145  */
3146 FIRM_API ir_node *new_d_Shl(dbg_info *db, ir_node *op, ir_node *k,
3147                             ir_mode *mode);
3148
3149 /** Constructor for a Shr node.
3150  *
3151  * Adds the node to the block in current_ir_block.
3152  *
3153  * @param   *db    A pointer for debug information.
3154  * @param   *op    The operand.
3155  * @param   *k     The number of bits to  shift the operand .
3156  * @param   *mode  The mode of the operand and the result.
3157  */
3158 FIRM_API ir_node *new_d_Shr(dbg_info *db, ir_node *op, ir_node *k,
3159                             ir_mode *mode);
3160
3161 /** Constructor for a Shrs node.
3162  *
3163  * Adds the node to the block in current_ir_block.
3164  *
3165  * @param   *db    A pointer for debug information.
3166  * @param   *op    The operand.
3167  * @param   *k     The number of bits to  shift the operand .
3168  * @param   *mode  The mode of the operand and the result.
3169  */
3170 FIRM_API ir_node *new_d_Shrs(dbg_info *db, ir_node *op, ir_node *k,
3171                              ir_mode *mode);
3172
3173 /** Constructor for a Rotl node.
3174  *
3175  * Adds the node to the block in current_ir_block.
3176  *
3177  * @param   *db    A pointer for debug information.
3178  * @param   *op    The operand.
3179  * @param   *k     The number of bits to rotate the operand.
3180  * @param   *mode  The mode of the operand.
3181  */
3182 FIRM_API ir_node *new_d_Rotl(dbg_info *db, ir_node *op, ir_node *k,
3183                              ir_mode *mode);
3184
3185 /** Constructor for a Cmp node.
3186  *
3187  * Adds the node to the block in current_ir_block.
3188  *
3189  * @param   *db    A pointer for debug information.
3190  * @param   *op1   The first operand.
3191  * @param   *op2   The second operand.
3192  */
3193 FIRM_API ir_node *new_d_Cmp(dbg_info *db, ir_node *op1, ir_node *op2);
3194
3195 /** Constructor for a Conv node.
3196  *
3197  * Adds the node to the block in current_ir_block.
3198  *
3199  * @param   *db    A pointer for debug information.
3200  * @param   *op    The operand.
3201  * @param   *mode  The mode of this the operand muss be converted .
3202  */
3203 FIRM_API ir_node *new_d_Conv(dbg_info *db, ir_node *op, ir_mode *mode);
3204
3205 /** Constructor for a strict Conv node.
3206  *
3207  * Adds the node to the block in current_ir_block.
3208  *
3209  * @param   *db    A pointer for debug information.
3210  * @param   *op    The operand.
3211  * @param   *mode  The mode of this the operand muss be converted .
3212  */
3213 FIRM_API ir_node *new_d_strictConv(dbg_info *db, ir_node *op, ir_mode *mode);
3214
3215 /** Constructor for a Cast node.
3216  *
3217  * High level type cast
3218  * Adds the node to the block in current_ir_block.
3219  *
3220  * @param   *db    A pointer for debug information.
3221  * @param   *op    The operand.
3222  * @param   *to_tp The type of this the operand muss be casted .
3223  */
3224 FIRM_API ir_node *new_d_Cast(dbg_info *db, ir_node *op, ir_type *to_tp);
3225
3226 /** Constructor for a Carry node.
3227  *
3228  * Adds the node to the block in current_ir_block.
3229  *
3230  * @param   *db    A pointer for debug information.
3231  * @param   *op1   The first operand.
3232  * @param   *op2   The second operand.
3233  * @param   *mode  The mode of the operands and the result.
3234  */
3235 FIRM_API ir_node *new_d_Carry(dbg_info *db, ir_node *op1, ir_node *op2,
3236                               ir_mode *mode);
3237
3238 /** Constructor for a Borrow node.
3239  *
3240  * Adds the node to the block in current_ir_block.
3241  *
3242  * @param   *db    A pointer for debug information.
3243  * @param   *op1   The first operand.
3244  * @param   *op2   The second operand.
3245  * @param   *mode  The mode of the operands and the result.
3246  */
3247 FIRM_API ir_node *new_d_Borrow(dbg_info *db, ir_node *op1, ir_node *op2,
3248                                ir_mode *mode);
3249
3250 /** Constructor for a Phi node.
3251  *
3252  * Adds the node to the block in current_ir_block.
3253  *
3254  * @param *db    A pointer for debug information.
3255  * @param arity  The number of predecessors
3256  * @param *in    Array with predecessors
3257  * @param *mode  The mode of it's inputs and output.
3258  */
3259 FIRM_API ir_node *new_d_Phi(dbg_info *db, int arity, ir_node *in[],
3260                             ir_mode *mode);
3261
3262 /** Constructor for a Load node.
3263  *
3264  * Adds the node to the block in current_ir_block.
3265  *
3266  * @param *db    A pointer for debug information.
3267  * @param *store The current memory
3268  * @param *addr  A pointer to the variable to be read in this memory.
3269  * @param *mode  The mode of the value to be loaded.
3270  * @param  flags Additional flags for alignment, volatility and pin state.
3271  */
3272 FIRM_API ir_node *new_d_Load(dbg_info *db, ir_node *store, ir_node *addr,
3273                              ir_mode *mode, ir_cons_flags flags);
3274
3275 /** Constructor for a Store node.
3276  *
3277  * Adds the node to the block in current_ir_block.
3278  *
3279  * @param *db    A pointer for debug information.
3280  * @param *store The current memory
3281  * @param *addr  A pointer to the variable to be read in this memory.
3282  * @param *val   The value to write to this variable.
3283  * @param  flags Additional flags for alignment, volatility and pin state.
3284  */
3285 FIRM_API ir_node *new_d_Store(dbg_info *db, ir_node *store, ir_node *addr,
3286                               ir_node *val, ir_cons_flags flags);
3287
3288 /** Constructor for a Alloc node.
3289  *
3290  * The Alloc node extends the memory by space for an entity of type alloc_type.
3291  * Adds the node to the block in current_ir_block.
3292  *
3293  * @param *db         A pointer for debug information.
3294  * @param *store      The memory which shall contain the new variable.
3295  * @param *count      The number of objects to allocate.
3296  * @param *alloc_type The type of the allocated variable.
3297  * @param where       Where to allocate the variable, either heap_alloc or stack_alloc.
3298  */
3299 FIRM_API ir_node *new_d_Alloc(dbg_info *db, ir_node *store, ir_node *count,
3300                               ir_type *alloc_type, ir_where_alloc where);
3301
3302  /** Constructor for a Free node.
3303  *
3304  * Frees the memory occupied by the entity pointed to by the pointer
3305  * arg.  Type indicates the type of the entity the argument points to.
3306  * Adds the node to the block in current_ir_block.
3307  *
3308  * @param *db         A pointer for debug information.
3309  * @param *store      The memory which shall contain the new variable.
3310  * @param *ptr        The pointer to the object to free.
3311  * @param *size       The number of objects of type free_type to free in a sequence.
3312  * @param *free_type  The type of the freed variable.
3313  * @param where       Where the variable was allocated, either heap_alloc or stack_alloc.
3314  */
3315 FIRM_API ir_node *new_d_Free(dbg_info *db, ir_node *store, ir_node *ptr,
3316                              ir_node *size, ir_type *free_type,
3317                              ir_where_alloc where);
3318
3319 /** Constructor for a Sync node.
3320  *
3321  * Merges several memory values.  The node assumes that a variable
3322  * either occurs only in one of the memories, or it contains the same
3323  * value in all memories where it occurs.
3324  * Adds the node to the block in current_ir_block.
3325  *
3326  * @param *db       A pointer for debug information.
3327  * @param  arity    The number of memories to synchronize.
3328  * @param  **in     An array of pointers to nodes that produce an output of type
3329  *                  memory.  The constructor copies this array.
3330  */
3331 FIRM_API ir_node *new_d_Sync(dbg_info *db, int arity, ir_node *in[]);
3332
3333 /** Constructor for a Proj node.
3334  *
3335  * Projects a single value out of a tuple.  The parameter proj gives the
3336  * position of the value within the tuple.
3337  * Adds the node to the block in current_ir_block.
3338  *
3339  * @param *db    A pointer for deubug information.
3340  * @param arg    A node producing a tuple.
3341  * @param *mode  The mode of the value to project.
3342  * @param proj   The position of the value in the tuple.
3343  */
3344 FIRM_API ir_node *new_d_Proj(dbg_info *db, ir_node *arg, ir_mode *mode,
3345                              long proj);
3346
3347 /** Constructor for a defaultProj node.
3348  *
3349  * Represents the default control flow of a Switch-Cond node.
3350  * Adds the node to the block in current_ir_block.
3351  *
3352  * @param *db       A pointer for debug information.
3353  * @param arg       A node producing a tuple.
3354  * @param max_proj  The end  position of the value in the tuple.
3355  */
3356 FIRM_API ir_node *new_d_defaultProj(dbg_info *db, ir_node *arg, long max_proj);
3357
3358 /** Constructor for a Tuple node.
3359  *
3360  * This is an auxiliary node to replace a node that returns a tuple
3361  * without changing the corresponding Proj nodes.
3362  * Adds the node to the block in current_ir_block.
3363  *
3364  * @param *db     A pointer for debug information.
3365  * @param arity   The number of tuple elements.
3366  * @param **in    An array containing pointers to the nodes producing the tuple elements.
3367  */
3368 FIRM_API ir_node *new_d_Tuple(dbg_info *db, int arity, ir_node *in[]);
3369
3370 /** Constructor for a Id node.
3371  *
3372  * This is an auxiliary node to replace a node that returns a single
3373  * value. Adds the node to the block in current_ir_block.
3374  *
3375  * @param *db     A pointer for debug information.
3376  * @param *val    The operand to Id.
3377  * @param *mode   The mode of *val.
3378  */
3379 FIRM_API ir_node *new_d_Id(dbg_info *db, ir_node *val, ir_mode *mode);
3380
3381 /** Constructor for a Confirm node.
3382  *
3383  * Constructor for a Confirm node. Adds the node to the block in current_ir_block.
3384  * Specifies constraints for a value.  To support dataflow analyses.
3385  *
3386  * Example: If the value never exceeds '100' this is expressed by placing a
3387  * Confirm node val = new_d_Confirm(db, val, 100, '<=') on the dataflow edge.
3388  *
3389  * @param *db     A pointer for debug information.
3390  * @param *val    The value we express a constraint for
3391  * @param *bound  The value to compare against. Must be a firm node, typically a constant.
3392  * @param cmp     The compare operation.
3393  */
3394 FIRM_API ir_node *new_d_Confirm(dbg_info *db, ir_node *val, ir_node *bound,
3395                                 pn_Cmp cmp);
3396
3397 /** Constructor for an Unknown node.
3398  *
3399  * Represents an arbitrary value.  Places the node in
3400  * the start block.
3401  *
3402  * @param *db     A pointer for debug information.
3403  * @param *m      The mode of the unknown value.
3404  */
3405 FIRM_API ir_node *new_d_Unknown(dbg_info *db, ir_mode *m);
3406
3407 /** Constructor for a Mux node.
3408  *
3409  * @param *db       A pointer for debug information.
3410  * @param *sel      The ir_node that calculates the boolean select.
3411  * @param *ir_true  The ir_node that calculates the true result.
3412  * @param *ir_false The ir_node that calculates the false result.
3413  * @param *mode     The mode of the node (and it_true and ir_false).
3414  */
3415 FIRM_API ir_node *new_d_Mux(dbg_info *db, ir_node *sel,
3416                             ir_node *ir_false, ir_node *ir_true, ir_mode *mode);
3417
3418 /** Constructor for a CopyB node.
3419  *
3420  * @param *db         A pointer for debug information.
3421  * @param *store      The current memory
3422  * @param *dst        The ir_node that represents the destination address.
3423  * @param *src        The ir_node that represents the source address.
3424  * @param *data_type  The type of the copied data
3425  */
3426 FIRM_API ir_node *new_d_CopyB(dbg_info *db, ir_node *store, ir_node *dst,
3427                               ir_node *src, ir_type *data_type);
3428
3429 /** Constructor for a InstOf node.
3430  *
3431  * A High-Level Type check.
3432  *
3433  * @param   *db        A pointer for debug information.
3434  * @param   *store     The memory in which the object the entity should be selected
3435  *                     from is allocated.
3436  * @param   *objptr    A pointer to a object of a class type.
3437  * @param   *type      The type of which objptr must be.
3438  */
3439 FIRM_API ir_node *new_d_InstOf(dbg_info *db, ir_node *store, ir_node *objptr,
3440                                ir_type *type);
3441
3442 /** Constructor for a Raise node.
3443  *
3444  * A High-Level Exception throw.
3445  *
3446  * @param *db    A pointer for debug information.
3447  * @param *store The current memory.
3448  * @param *obj   A pointer to the Except variable.
3449  */
3450 FIRM_API ir_node *new_d_Raise(dbg_info *db, ir_node *store, ir_node *obj);
3451
3452 /** Constructor for a Bound node.
3453  *
3454  * A High-Level bounds check. Checks whether lower <= idx && idx < upper.
3455  *
3456  * @param *db         A pointer for debug information.
3457  * @param *store      The current memory
3458  * @param *idx        The ir_node that represents an index.
3459  * @param *lower      The ir_node that represents the lower bound for the index.
3460  * @param *upper      The ir_node that represents the upper bound for the index.
3461  */
3462 FIRM_API ir_node *new_d_Bound(dbg_info *db, ir_node *store, ir_node *idx,
3463                               ir_node *lower, ir_node *upper);
3464
3465 /** Constructor for a Pin node.
3466  *
3467  * @param *db         A pointer for debug information.
3468  * @param *node       The node which value should be pinned.
3469  */
3470 FIRM_API ir_node *new_d_Pin(dbg_info *db, ir_node *node);
3471
3472 /** Constructor for an ASM pseudo node.
3473  *
3474  * @param *db         A pointer for debug information.
3475  * @param arity       The number of data inputs to the node.
3476  * @param *in         The array of length arity of data inputs.
3477  * @param *inputs     The array of length arity of input constraints.
3478  * @param n_outs      The number of data outputs to the node.
3479  * @param *outputs    The array of length n_outs of output constraints.
3480  * @param n_clobber   The number of clobbered registers.
3481  * @param *clobber    The array of length n_clobber of clobbered registers.
3482  * @param *asm_text   The assembler text.
3483  */
3484 FIRM_API ir_node *new_d_ASM(dbg_info *db, int arity, ir_node *in[],
3485                             ir_asm_constraint *inputs,
3486                             int n_outs, ir_asm_constraint *outputs,
3487                             int n_clobber, ident *clobber[], ident *asm_text);
3488
3489 /*-----------------------------------------------------------------------*/
3490 /* The block oriented interface without debug support                    */
3491 /*-----------------------------------------------------------------------*/
3492
3493 /** Constructor for a Block node.
3494  *
3495  * Constructor for a Block node. Adds the block to the graph in
3496  * current_ir_graph. Constructs a Block with a fixed number of predecessors.
3497  *
3498  * @param arity  The number of control predecessors.
3499  * @param in     An array of control predecessors.  The length of
3500  *               the array must be 'arity'.
3501  */
3502 FIRM_API ir_node *new_Block(int arity, ir_node *in[]);
3503
3504 /** Constructor for a Start node.
3505  *
3506  * Adds the node to the block in current_ir_block.
3507  *
3508  */
3509 FIRM_API ir_node *new_Start(void);
3510
3511 /** Constructor for an End node.
3512  *
3513  * Adds the node to the block in current_ir_block.
3514  */
3515 FIRM_API ir_node *new_End(void);
3516
3517 /** Constructor for a Jump node.
3518  *
3519  * Adds the node to the block in current_ir_block.
3520  *
3521  * Jmp represents control flow to a single control successor.
3522  */
3523 FIRM_API ir_node *new_Jmp(void);
3524
3525 /** Constructor for an IJmp node.
3526  *
3527  * IJmp represents control flow to a single control successor not
3528  * statically known i.e. an indirect Jmp.
3529  *
3530  * @param *tgt    The IR node representing the target address.
3531  */
3532 FIRM_API ir_node *new_IJmp(ir_node *tgt);
3533
3534 /** Constructor for a Cond node.
3535  *
3536  * If c is mode_b represents a conditional branch (if/else). If c is
3537  * mode_Is/mode_Iu (?) represents a switch.  (Allocates dense Cond
3538  * node, default Proj is 0.). Adds the node to the block in current_ir_block.
3539  *
3540  * This is not consistent:  Input to Cond is Is, Proj has as proj number
3541  * longs.
3542  *
3543  *
3544  * @param *c     The conditions parameter.Can be of mode b or I_u.
3545  */
3546 FIRM_API ir_node *new_Cond(ir_node *c);
3547
3548 /** Constructor for a Return node.
3549  *
3550  * Returns the memory and zero or more return values.  Only node that
3551  * can end regular control flow. Adds the node to the block in current_ir_block.
3552  *
3553  * @param *store The state of memory.
3554  * @param arity  Number of array indices.
3555  * @param *in    Array with index inputs to the node.
3556  */
3557 FIRM_API ir_node *new_Return(ir_node *store, int arity, ir_node *in[]);
3558
3559 /** Constructor for a Const node.
3560  *
3561  * Constructor for a Const node. The constant represents a target
3562  * value.  Sets the type information to type_unknown.  (No more
3563  * supported: If tv is entity derives a somehow useful type.)
3564  * Adds the node to the block in current_ir_block.
3565  * Derives mode from passed tarval.
3566  *
3567  * @param *con   Points to an entry in the constant table. This pointer is
3568  *               added to the attributes of  the node.
3569  */
3570 FIRM_API ir_node *new_Const(tarval *con);
3571
3572 /**
3573  * Make a const from a long.
3574  * This is just convenience for the usual
3575  * <code>
3576  * new_Const(mode, tarval_from_long(mode, ...))
3577  * </code>
3578  * pain.
3579  * @param mode The mode for the const.
3580  * @param value The value of the constant.
3581  * @return A new const node.
3582  */
3583 FIRM_API ir_node *new_Const_long(ir_mode *mode, long value);
3584
3585 /** Constructor for a Const node.
3586  *
3587  * Derives mode from passed tarval. */
3588 FIRM_API ir_node *new_Const_type(tarval *con, ir_type *tp);
3589
3590 /** Constructor for a SymConst_type node.
3591  *
3592  *  This is the constructor for a symbolic constant.
3593  *    There are several kinds of symbolic constants:
3594  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
3595  *                          type the tag stands for is given explicitly.
3596  *    - symconst_type_size  The symbolic constant represents the size of a type.
3597  *                          The type of which the constant represents the size
3598  *                          is given explicitly.
3599  *    - symconst_type_align The symbolic constant represents the alignment of a
3600  *                          type.  The type of which the constant represents the
3601  *                          size is given explicitly.
3602  *    - symconst_addr_ent   The symbolic constant represents the address of an
3603  *                          entity (variable or method).  The variable is given
3604  *                          explicitly by a firm entity.
3605  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
3606  *                          entity in its owner type.
3607  *    - symconst_enum_const The symbolic constant is a enumeration constant of
3608  *                          an enumeration type.
3609  *
3610  *    Inputs to the node:
3611  *      No inputs except the block it belongs to.
3612  *    Outputs of the node.
3613  *      An unsigned integer (I_u) or a pointer (P).
3614  *
3615  *    Mention union in declaration so that the firmjni generator recognizes that
3616  *    it can not cast the argument to an int.
3617  *
3618  * @param mode    The mode for the SymConst.
3619  * @param value   A type, ident, entity or enum constant depending on the
3620  *                SymConst kind.
3621  * @param kind    The kind of the symbolic constant, see the list above
3622  * @param tp      The source type of the constant.
3623  */
3624 FIRM_API ir_node *new_SymConst_type(ir_mode *mode, union symconst_symbol value,
3625                                     symconst_kind kind, ir_type *tp);
3626
3627 /** Constructor for a SymConst node.
3628  *
3629  *  This is the constructor for a symbolic constant.
3630  *    There are several kinds of symbolic constants:
3631  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
3632  *                          type the tag stands for is given explicitly.
3633  *    - symconst_type_size  The symbolic constant represents the size of a type.
3634  *                          The type of which the constant represents the size
3635  *                          is given explicitly.
3636  *    - symconst_type_align The symbolic constant represents the alignment of a
3637  *                          type.  The type of which the constant represents the
3638  *                          size is given explicitly.
3639  *    - symconst_addr_ent   The symbolic constant represents the address of an
3640  *                          entity (variable or method).  The variable is given
3641  *                          explicitly by a firm entity.
3642  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
3643  *                          entity in its owner type.
3644  *    - symconst_enum_const The symbolic constant is a enumeration constant of
3645  *                          an enumeration type.
3646  *
3647  *    Inputs to the node:
3648  *      No inputs except the block it belongs to.
3649  *    Outputs of the node.
3650  *      An unsigned integer (I_u) or a pointer (P).
3651  *
3652  *    Mention union in declaration so that the firmjni generator recognizes that
3653  *    it can not cast the argument to an int.
3654  *
3655  * @param mode    The mode for the SymConst.
3656  * @param value   A type, ident, entity or enum constant depending on the
3657  *                SymConst kind.
3658  * @param kind    The kind of the symbolic constant, see the list above
3659  */
3660 FIRM_API ir_node *new_SymConst(ir_mode *mode, union symconst_symbol value,
3661                                symconst_kind kind);
3662
3663 /** Constructor for a simpelSel node.
3664  *
3665  *  This is a shortcut for the new_Sel() constructor.  To be used for
3666  *  Sel nodes that do not select from an array, i.e., have no index
3667  *  inputs.  It adds the two parameters 0, NULL.
3668  *
3669  * @param   *store     The memory in which the object the entity should be selected from is allocated.
3670  * @param   *objptr    The object from that the Sel operation selects a single attribute out.
3671  * @param   *ent       The entity to select.
3672  */
3673 FIRM_API ir_node *new_simpleSel(ir_node *store, ir_node *objptr,
3674                                 ir_entity *ent);
3675
3676 /** Constructor for a Sel node.
3677  *
3678  * The select node selects an entity (field or method) from an entity
3679  * with a compound type.  It explicitly specifies the entity selected.
3680  * Dynamically the node may select entities that overwrite the given
3681  * entity.  If the selected entity is an array element entity the Sel
3682  * node takes the required array indices as inputs.
3683  * Adds the node to the block in current_ir_block.
3684  *
3685  * @param   *store     The memory in which the object the entity should be selected
3686  *                     from is allocated.
3687  * @param   *objptr    A pointer to a compound entity the Sel operation selects a
3688  *                     single attribute from.
3689  * @param   arity      The number of array indices needed to select an array element entity.
3690  * @param   *in[]      If the compound entity is an array the indices of the selected
3691  *                     element entity.  The constructor copies this array.
3692  * @param   *ent       The entity to select.
3693  */
3694 FIRM_API ir_node *new_Sel(ir_node *store, ir_node *objptr,
3695                           int arity, ir_node *in[], ir_entity *ent);
3696
3697 /** Constructor for a Call node.
3698  *
3699  * Adds the node to the block in current_ir_block.
3700  * Represents all kinds of method and function calls.
3701  *
3702  * @param   *store  The actual store.
3703  * @param   *callee A pointer to the called procedure.
3704  * @param   arity   The number of procedure parameters.
3705  * @param   *in[]   An array with the pointers to the parameters. The constructor copies this array.
3706  * @param   *tp     Type information of the procedure called.
3707  */
3708 FIRM_API ir_node *new_Call(ir_node *store, ir_node *callee,
3709                            int arity, ir_node *in[], ir_type *tp);
3710
3711 /** Constructor for a Builtin node.
3712  *
3713  * Represents a call of a backend-specific builtin..
3714  * Represents all kinds of method and function calls.
3715  *
3716  * @param   *store  The actual store.
3717  * @param   kind    The kind of the called builtin.
3718  * @param   arity   The number of procedure parameters.
3719  * @param   *in[]   An array with the pointers to the parameters. The constructor copies this array.
3720  * @param   *tp     Type information of the procedure called.
3721  */
3722 FIRM_API ir_node *new_Builtin(ir_node *store, int arity, ir_node *in[],
3723                               ir_builtin_kind kind, ir_type *tp);
3724
3725 /** Constructor for a Add node.
3726  *
3727  * Adds the node to the block in current_ir_block.
3728  *
3729  * @param   *op1   The first operand.
3730  * @param   *op2   The second operand.
3731  * @param   *mode  The mode of the operands and the result.
3732  */
3733 FIRM_API ir_node *new_Add(ir_node *op1, ir_node *op2, ir_mode *mode);
3734
3735 /** Constructor for a Sub node.
3736  *
3737  * Adds the node to the block in current_ir_block.
3738  *
3739  * @param   *op1   The first operand.
3740  * @param   *op2   The second operand.
3741  * @param   *mode  The mode of the operands and the result.
3742  */
3743 FIRM_API ir_node *new_Sub(ir_node *op1, ir_node *op2, ir_mode *mode);
3744
3745 /** Constructor for a Minus node.
3746  *
3747  * Adds the node to the block in current_ir_block.
3748  *
3749  * @param   *op    The operand .
3750  * @param   *mode  The mode of the operand and the result.
3751  */
3752 FIRM_API ir_node *new_Minus(ir_node *op,  ir_mode *mode);
3753
3754 /**
3755  * Constructor for a Mul node. Adds the node to the block in current_ir_block.
3756  *
3757  * @param   *op1   The first operand.
3758  * @param   *op2   The second operand.
3759  * @param   *mode  The mode of the operands and the result.
3760  */
3761 FIRM_API ir_node *new_Mul(ir_node *op1, ir_node *op2, ir_mode *mode);
3762
3763 /**
3764  * Constructor for a Mulh node. Adds the node to the block in current_ir_block.
3765  *
3766  * @param   *op1   The first operand.
3767  * @param   *op2   The second operand.
3768  * @param   *mode  The mode of the operands and the result.
3769  */
3770 FIRM_API ir_node *new_Mulh(ir_node *op1, ir_node *op2, ir_mode *mode);
3771
3772 /** Constructor for a Quot node.
3773  *
3774  * Adds the node to the block in current_ir_block.
3775  *
3776  * @param   *memop The store needed to model exceptions
3777  * @param   *op1   The first operand.
3778  * @param   *op2   The second operand.
3779  * @param   *mode  The mode of the result.
3780  * @param   state  The pinned state.
3781  */
3782 FIRM_API ir_node *new_Quot(ir_node *memop, ir_node *op1, ir_node *op2,
3783                            ir_mode *mode, op_pin_state state);
3784
3785 /** Constructor for a DivMod node.
3786  *
3787  * Adds the node to the block in current_ir_block.
3788  *
3789  * @param   *memop The store needed to model exceptions
3790  * @param   *op1   The first operand.
3791  * @param   *op2   The second operand.
3792  * @param   *mode  The mode of the results.
3793  * @param   state  The pinned state.
3794  */
3795 FIRM_API ir_node *new_DivMod(ir_node *memop, ir_node *op1, ir_node *op2,
3796                              ir_mode *mode, op_pin_state state);
3797
3798 /** Constructor for a Div node.
3799  *
3800  * Adds the node to the block in current_ir_block.
3801  *
3802  * @param   *memop The store needed to model exceptions
3803  * @param   *op1   The first operand.
3804  * @param   *op2   The second operand.
3805  * @param   *mode  The mode of the result.
3806  * @param   state  The pinned state.
3807  */
3808 FIRM_API ir_node *new_Div(ir_node *memop, ir_node *op1, ir_node *op2,
3809                           ir_mode *mode, op_pin_state state);
3810
3811 /** Constructor for a remainderless Div node.
3812  *
3813  * Adds the node to the block in current_ir_block.
3814  *
3815  * @param   *memop The store needed to model exceptions
3816  * @param   *op1   The first operand.
3817  * @param   *op2   The second operand.
3818  * @param   *mode  The mode of the result.
3819  * @param   state  The pinned state.
3820  */
3821 FIRM_API ir_node *new_DivRL(ir_node *memop, ir_node *op1, ir_node *op2,
3822                             ir_mode *mode, op_pin_state state);
3823
3824 /** Constructor for a Mod node.
3825  *
3826  * Adds the node to the block in current_ir_block.
3827  *
3828  * @param   *memop The store needed to model exceptions
3829  * @param   *op1   The first operand.
3830  * @param   *op2   The second operand.
3831  * @param   *mode  The mode of the result.
3832  * @param   state  The pinned state.
3833  */
3834 FIRM_API ir_node *new_Mod(ir_node *memop, ir_node *op1, ir_node *op2,
3835                           ir_mode *mode, op_pin_state state);
3836
3837 /** Constructor for a Abs node.
3838  *
3839  * Adds the node to the block in current_ir_block.
3840  *
3841  * @param   *op    The operand
3842  * @param   *mode  The mode of the operands and the result.
3843  */
3844 FIRM_API ir_node *new_Abs(ir_node *op, ir_mode *mode);
3845
3846 /** Constructor for a And node.
3847  *
3848  * Adds the node to the block in current_ir_block.
3849  *
3850  * @param   *op1   The first operand.
3851  * @param   *op2   The second operand.
3852  * @param   *mode  The mode of the operands and the result.
3853  */
3854 FIRM_API ir_node *new_And(ir_node *op1, ir_node *op2, ir_mode *mode);
3855
3856 /**
3857  * Constructor for a Or node. Adds the node to the block in current_ir_block.
3858  *
3859  * @param   *op1   The first operand.
3860  * @param   *op2   The second operand.
3861  * @param   *mode  The mode of the operands and the result.
3862  */
3863 FIRM_API ir_node *new_Or(ir_node *op1, ir_node *op2, ir_mode *mode);
3864
3865 /**
3866  * Constructor for a Eor node. Adds the node to the block in current_ir_block.
3867  *
3868  * @param   *op1   The first operand.
3869  * @param   *op2   The second operand.
3870  * @param   *mode  The mode of the operands and the results.
3871  */
3872 FIRM_API ir_node *new_Eor(ir_node *op1, ir_node *op2, ir_mode *mode);
3873
3874 /** Constructor for a Not node.
3875  *
3876  * Adds the node to the block in current_ir_block.
3877  *
3878  * @param   *op    The operand.
3879  * @param   *mode  The mode of the operand and the result.
3880  */
3881 FIRM_API ir_node *new_Not(ir_node *op, ir_mode *mode);
3882
3883 /** Constructor for a Shl node.
3884  *
3885  * Adds the node to the block in current_ir_block.
3886  *
3887  * @param   *op    The operand.
3888  * @param   *k     The number of bits to  shift the operand .
3889  * @param   *mode  The mode of the operand and the result.
3890  */
3891 FIRM_API ir_node *new_Shl(ir_node *op, ir_node *k, ir_mode *mode);
3892
3893 /**
3894  * Constructor for a Shr node. Adds the node to the block in current_ir_block.
3895  *
3896  * @param   *op    The operand.
3897  * @param   *k     The number of bits to  shift the operand .
3898  * @param   *mode  The mode of the operand and the result.
3899  */
3900 FIRM_API ir_node *new_Shr(ir_node *op, ir_node *k, ir_mode *mode);
3901
3902 /** Constructor for a Shrs node.
3903  *
3904  * Adds the node to the block in current_ir_block.
3905  *
3906  * @param   *op    The operand.
3907  * @param   *k     The number of bits to  shift the operand .
3908  * @param   *mode  The mode of the operand and the result.
3909  */
3910 FIRM_API ir_node *new_Shrs(ir_node *op, ir_node *k, ir_mode *mode);
3911
3912 /** Constructor for a Rotl node.
3913  *
3914  * Adds the node to the block in current_ir_block.
3915  *
3916  * @param   *op    The operand.
3917  * @param   *k     The number of bits to rotate the operand.
3918  * @param   *mode  The mode of the operand.
3919  */
3920 FIRM_API ir_node *new_Rotl(ir_node *op, ir_node *k, ir_mode *mode);
3921
3922 /** Constructor for a Cmp node.
3923  *
3924  * Adds the node to the block in current_ir_block.
3925  *
3926  * @param   *op1   The first operand.
3927  * @param   *op2   The second operand.
3928  */
3929 FIRM_API ir_node *new_Cmp(ir_node *op1, ir_node *op2);
3930
3931 /** Constructor for a Conv node.
3932  *
3933  * Adds the node to the block in current_ir_block.
3934  *
3935  * @param   *op          The operand.
3936  * @param   *mode        The mode of this the operand muss be converted.
3937  */
3938 FIRM_API ir_node *new_Conv(ir_node *op, ir_mode *mode);
3939
3940 /** Constructor for a strict Conv node.
3941  *
3942  * Adds the node to the block in current_ir_block.
3943  *
3944  * @param   *op          The operand.
3945  * @param   *mode        The mode of this the operand muss be converted.
3946  */
3947 FIRM_API ir_node *new_strictConv(ir_node *op, ir_mode *mode);
3948
3949 /** Constructor for a Cast node.
3950  *
3951  * Adds the node to the block in current_ir_block.
3952  * High level type cast
3953  *
3954  * @param   *op    The operand.
3955  * @param   *to_tp The type of this the operand muss be casted .
3956  */
3957 FIRM_API ir_node *new_Cast(ir_node *op, ir_type *to_tp);
3958
3959 /** Constructor for a Carry node.
3960  *
3961  * Adds the node to the block in current_ir_block.
3962  *
3963  * @param   *op1   The first operand.
3964  * @param   *op2   The second operand.
3965  * @param   *mode  The mode of the operands and the result.
3966  */
3967 FIRM_API ir_node *new_Carry(ir_node *op1, ir_node *op2, ir_mode *mode);
3968
3969 /** Constructor for a Borrow node.
3970  *
3971  * Adds the node to the block in current_ir_block.
3972  *
3973  * @param   *op1   The first operand.
3974  * @param   *op2   The second operand.
3975  * @param   *mode  The mode of the operands and the result.
3976  */
3977 FIRM_API ir_node *new_Borrow(ir_node *op1, ir_node *op2, ir_mode *mode);
3978
3979 /** Constructor for a Phi node.
3980  *
3981  * Adds the node to the block in current_ir_block.
3982  *
3983  * @param arity  The number of predecessors.
3984  * @param *in    Array with predecessors.
3985  * @param *mode  The mode of it's inputs and output.
3986  */
3987 FIRM_API ir_node *new_Phi(int arity, ir_node *in[], ir_mode *mode);
3988
3989 /** Constructor for a Load node.
3990  *
3991  * @param *store  The current memory.
3992  * @param *addr   A pointer to the variable to be read in this memory.
3993  * @param *mode   The mode of the value to be loaded.
3994  * @param  flags  Additional flags for alignment, volatility and pin state.
3995  */
3996 FIRM_API ir_node *new_Load(ir_node *store, ir_node *addr, ir_mode *mode,
3997                            ir_cons_flags flags);
3998
3999 /** Constructor for a Store node.
4000  *
4001  * @param *store  The current memory.
4002  * @param *addr   A pointer to the variable to be read in this memory.
4003  * @param *val    The value to write to this variable.
4004  * @param  flags  Additional flags for alignment, volatility and pin state.
4005  */
4006 FIRM_API ir_node *new_Store(ir_node *store, ir_node *addr, ir_node *val,
4007                             ir_cons_flags flags);
4008
4009 /** Constructor for a Alloc node.
4010  *
4011  * The Alloc node extends the memory by space for an entity of type alloc_type.
4012  * Adds the node to the block in current_ir_block.
4013  *
4014  * @param *store      The memory which shall contain the new variable.
4015  * @param *count      The number of objects to allocate.
4016  * @param *alloc_type The type of the allocated variable.
4017  * @param where       Where to allocate the variable, either heap_alloc or stack_alloc.
4018  */
4019 FIRM_API ir_node *new_Alloc(ir_node *store, ir_node *count, ir_type *alloc_type,
4020                             ir_where_alloc where);
4021
4022 /** Constructor for a Free node.
4023  *
4024  * Frees the memory occupied by the entity pointed to by the pointer
4025  * arg.  Type indicates the type of the entity the argument points to.
4026  * Adds the node to the block in current_ir_block.
4027  *
4028  * @param *store      The memory which shall contain the new variable.
4029  * @param *ptr        The pointer to the object to free.
4030  * @param *size       The number of objects of type free_type to free in a sequence.
4031  * @param *free_type  The type of the freed variable.
4032  * @param where       Where the variable was allocated, either heap_alloc or stack_alloc.
4033  */
4034 FIRM_API ir_node *new_Free(ir_node *store, ir_node *ptr, ir_node *size,
4035                            ir_type *free_type, ir_where_alloc where);
4036
4037 /** Constructor for a Sync node.
4038  *
4039  * Merges several memory values.  The node assumes that a variable
4040  * either occurs only in one of the memories, or it contains the same
4041  * value in all memories where it occurs.
4042  * Adds the node to the block in current_ir_block.
4043  *
4044  * @param  arity    The number of memories to synchronize.
4045  * @param  **in     An array of pointers to nodes that produce an output of type
4046  *                  memory.  The constructor copies this array.
4047  */
4048 FIRM_API ir_node *new_Sync(int arity, ir_node *in[]);
4049
4050 /** Constructor for a Proj node.
4051  *
4052  * Projects a single value out of a tuple.  The parameter proj gives the
4053  * position of the value within the tuple.
4054  * Adds the node to the block in current_ir_block.
4055  *
4056  * @param arg    A node producing a tuple.
4057  * @param *mode  The mode of the value to project.
4058  * @param proj   The position of the value in the tuple.
4059  */
4060 FIRM_API ir_node *new_Proj(ir_node *arg, ir_mode *mode, long proj);
4061
4062 /** Constructor for a defaultProj node.
4063  *
4064  * Represents the default control flow of a Switch-Cond node.
4065  * Adds the node to the block in current_ir_block.
4066  *
4067  * @param arg       A node producing a tuple.
4068  * @param max_proj  The end  position of the value in the tuple.
4069  */
4070 FIRM_API ir_node *new_defaultProj(ir_node *arg, long max_proj);
4071
4072 /** Constructor for a Tuple node.
4073  *
4074  * This is an auxiliary node to replace a node that returns a tuple
4075  * without changing the corresponding Proj nodes.
4076  * Adds the node to the block in current_ir_block.
4077  *
4078  * @param arity   The number of tuple elements.
4079  * @param **in    An array containing pointers to the nodes producing the tuple elements.
4080  */
4081 FIRM_API ir_node *new_Tuple(int arity, ir_node *in[]);
4082
4083 /** Constructor for an Id node.
4084  *
4085  * This is an auxiliary node to replace a node that returns a single
4086  * value. Adds the node to the block in current_ir_block.
4087  *
4088  * @param *val    The operand to Id.
4089  * @param *mode   The mode of *val.
4090  */
4091 FIRM_API ir_node *new_Id(ir_node *val, ir_mode *mode);
4092
4093 /** Constructor for a Bad node.
4094  *
4095  * Returns the unique Bad node of the graph.  The same as
4096  * get_irg_bad().
4097  */
4098 FIRM_API ir_node *new_Bad(void);
4099
4100 /** Constructor for a Confirm node.
4101  *
4102  * Specifies constraints for a value.  To support dataflow analyses.
4103  * Adds the node to the block in current_ir_block.
4104  *
4105  * Example: If the value never exceeds '100' this is expressed by placing a
4106  * Confirm node val = new_d_Confirm(db, val, 100, '<=') on the dataflow edge.
4107  *
4108  * @param *val    The value we express a constraint for
4109  * @param *bound  The value to compare against. Must be a firm node, typically a constant.
4110  * @param cmp     The compare operation.
4111  */
4112 FIRM_API ir_node *new_Confirm(ir_node *val, ir_node *bound, pn_Cmp cmp);
4113
4114 /** Constructor for an Unknown node.
4115  *
4116  * Represents an arbitrary value.  Places the node in
4117  * the start block.
4118  *
4119  * @param *m      The mode of the unknown value.
4120  */
4121 FIRM_API ir_node *new_Unknown(ir_mode *m);
4122
4123 /** Constructor for a NoMem node.
4124  *
4125  * Returns the unique NoMem node of the graph.  The same as
4126  * get_irg_no_mem().
4127  */
4128 FIRM_API ir_node *new_NoMem(void);
4129
4130 /** Constructor for a Mux node.
4131  *
4132  * Adds the node to the block in current_ir_block.
4133  *
4134  * @param *sel      The ir_node that calculates the boolean select.
4135  * @param *ir_true  The ir_node that calculates the true result.
4136  * @param *ir_false The ir_node that calculates the false result.
4137  * @param *mode     The mode of the node (and it_true and ir_false).
4138  */
4139 FIRM_API ir_node *new_Mux(ir_node *sel, ir_node *ir_false, ir_node *ir_true,
4140                           ir_mode *mode);
4141
4142 /** Constructor for a CopyB node.
4143  *
4144  * Adds the node to the block in current_ir_block.
4145  *
4146  * @param *store      The current memory
4147  * @param *dst        The ir_node that represents the destination address.
4148  * @param *src        The ir_node that represents the source address.
4149  * @param *data_type  The type of the copied data
4150  */
4151 FIRM_API ir_node *new_CopyB(ir_node *store, ir_node *dst, ir_node *src,
4152                             ir_type *data_type);
4153
4154 /** Constructor for a InstOf node.
4155  *
4156  * A High-Level Type check.
4157  *
4158  * @param   *store     The memory in which the object the entity should be selected
4159  *                     from is allocated.
4160  * @param   *objptr    A pointer to a object of a class type.
4161  * @param   *type      The type of which objptr must be.
4162  */
4163 FIRM_API ir_node *new_InstOf(ir_node *store, ir_node *objptr, ir_type *type);
4164
4165 /**Constructor for a Raise node.
4166  *
4167  * A High-Level Exception throw.
4168  *
4169  * @param *store The current memory.
4170  * @param *obj   A pointer to the Except variable.
4171  */
4172 FIRM_API ir_node *new_Raise(ir_node *store, ir_node *obj);
4173
4174 /** Constructor for a Bound node.
4175  *
4176  * A High-Level bounds check. Checks whether lower <= idx && idx < upper.
4177  *
4178  * Adds the node to the block in current_ir_block.
4179  *
4180  * @param *store      The current memory
4181  * @param *idx        The ir_node that represents an index.
4182  * @param *lower      The ir_node that represents the lower bound for the index.
4183  * @param *upper      The ir_node that represents the upper bound for the index.
4184  */
4185 FIRM_API ir_node *new_Bound(ir_node *store, ir_node *idx, ir_node *lower,
4186                             ir_node *upper);
4187
4188 /** Constructor for a Pin node.
4189  *
4190  * @param *node       The node which value should be pinned.
4191  */
4192 FIRM_API ir_node *new_Pin(ir_node *node);
4193
4194 /** Constructor for an ASM pseudo node.
4195  *
4196  * @param arity       The number of data inputs to the node.
4197  * @param *in         The array of length arity of data inputs.
4198  * @param *inputs     The array of length arity of input constraints.
4199  * @param n_outs      The number of data outputs to the node.
4200  * @param *outputs    The array of length n_outs of output constraints.
4201  * @param n_clobber   The number of clobbered registers.
4202  * @param *clobber    The array of length n_clobber of clobbered registers.
4203  * @param *asm_text   The assembler text.
4204  */
4205 FIRM_API ir_node *new_ASM(int arity, ir_node *in[], ir_asm_constraint *inputs,
4206                           int n_outs, ir_asm_constraint *outputs,
4207                           int n_clobber, ident *clobber[], ident *asm_text);
4208
4209 /**
4210  * @brief Constructor for a Dummy node.
4211  *
4212  * @param *db       debug info for the node
4213  * @param *mode     The mode of the node.
4214  * @param *irg      the graph to put the node into
4215  * @returns         the newly created note
4216  */
4217 FIRM_API ir_node *new_rd_Dummy(dbg_info *db, ir_graph *irg, ir_mode *mode);
4218
4219 /**
4220  * @copybrief new_rd_Dummy()
4221  *
4222  * @param *mode     The mode of the node.
4223  * @param *irg      the graph to put the node into
4224  * @returns         the newly created note
4225  */
4226 FIRM_API ir_node *new_r_Dummy(ir_graph *irg, ir_mode *mode);
4227
4228 /**
4229  * @copybrief new_rd_Dummy()
4230  *
4231  * @param *db       debug info for the node
4232  * @param *mode     The mode of the node.
4233  * @returns         the newly created note
4234  */
4235 FIRM_API ir_node *new_d_Dummy(dbg_info *db, ir_mode *mode);
4236
4237 /**
4238  * @copybrief new_rd_Dummy()
4239  *
4240  * @param *mode     The mode of the node.
4241  * @returns         the newly created note
4242  */
4243 FIRM_API ir_node *new_Dummy(ir_mode *mode);
4244
4245 /*---------------------------------------------------------------------*/
4246 /* The comfortable interface.                                          */
4247 /* Supports automatic Phi node construction.                           */
4248 /* All routines of the block oriented interface except new_Block are   */
4249 /* needed also.                                                        */
4250 /*---------------------------------------------------------------------*/
4251
4252 /** Create an immature Block.
4253  *
4254  * An immature Block has an unknown number of predecessors.  Predecessors
4255  * can be added with add_immBlock_pred().  Once all predecessors are
4256  * added the block must be matured.
4257  *
4258  * Adds the block to the graph in current_ir_graph. Can be used with automatic
4259  * Phi node construction.
4260  * This constructor can only be used if the graph is in state_building.
4261  */
4262 FIRM_API ir_node *new_d_immBlock(dbg_info *db);
4263 FIRM_API ir_node *new_immBlock(void);
4264
4265 /** Create an immature PartBlock.
4266  *
4267  * An immature block has only one Block or PartBlock predecessor.
4268  * A PartBlock forms together with one BLock and possibly other
4269  * PartBlocks a MacroBlock.
4270  *
4271  * Adds the PartBlock to the graph in current_ir_graph. Does set
4272  * current_block.  Can be used with automatic Phi node construction.
4273  * This constructor can only be used if the graph is in
4274  * state_building.
4275  */
4276 FIRM_API ir_node *new_d_immPartBlock(dbg_info *db, ir_node *pred_jmp);
4277 FIRM_API ir_node *new_immPartBlock(ir_node *pred_jmp);
4278
4279 /** Add a control flow edge to an immature block. */
4280 FIRM_API void add_immBlock_pred(ir_node *immblock, ir_node *jmp);
4281
4282 /** Finalize a Block node, when all control flows are known. */
4283 FIRM_API void mature_immBlock(ir_node *block);
4284
4285 /** Get the current value of a local variable.
4286  *
4287  * Use this function to obtain the last definition of the local variable
4288  * associated with pos.  Pos may not exceed the value passed as n_loc
4289  * to new_ir_graph.  This call automatically inserts Phi nodes.
4290  *
4291  * @param *db    A pointer for debug information.
4292  * @param  pos   The position/id of the local variable.
4293  * @param *mode  The mode of the value to get.
4294  */
4295 FIRM_API ir_node *get_d_value(dbg_info *db, int pos, ir_mode *mode);
4296 FIRM_API ir_node *get_value(int pos, ir_mode *mode);
4297
4298 /**
4299  * Try to guess the mode of a local variable.
4300  * This is done by recursively going up the control flow graph until
4301  * we find a definition for the variable. The mode of the first found
4302  * definition is returned. NULL in case no definition is found.
4303  *
4304  * @param  pos   The position/id of the local variable.
4305  */
4306 FIRM_API ir_mode *ir_guess_mode(int pos);
4307
4308 /** Remark a new definition of a variable.
4309  *
4310  * Use this function to remember a new definition of the value
4311  * associated with pos. Pos may not exceed the value passed as n_loc
4312  * to new_ir_graph.  This call is needed to automatically inserts Phi
4313  * nodes.
4314  *
4315  * @param  pos   The position/id of the local variable.
4316  * @param *value The new value written to the local variable.
4317  */
4318 FIRM_API void set_value(int pos, ir_node *value);
4319
4320 /**
4321  * Find the value number for a node in the current block.
4322  *
4323  * @param value  the searched value
4324  *
4325  * @return the value number of the value or -1 if this value has
4326  * no value number in the current block.
4327  */
4328 FIRM_API int find_value(ir_node *value);
4329
4330 /** Get the current memory state.
4331  *
4332  * Use this function to obtain the last definition of the memory
4333  * state.  This call automatically inserts Phi nodes for the memory
4334  * state value.
4335  */
4336 FIRM_API ir_node *get_store(void);
4337
4338 /** Remark a new definition of the memory state.
4339  *
4340  * Use this function to remember a new definition of the memory state.
4341  * This call is needed to automatically inserts Phi nodes.
4342  *
4343  * @param *store The new memory state.
4344  */
4345 FIRM_API void set_store(ir_node *store);
4346
4347 /** keep this node alive even if End is not control-reachable from it
4348  *
4349  * @param ka The node to keep alive.
4350  */
4351 FIRM_API void keep_alive(ir_node *ka);
4352
4353 /** Returns the frame type of the current graph */
4354 FIRM_API ir_type *get_cur_frame_type(void);
4355
4356
4357 /* --- initialize and finalize IR construction --- */
4358
4359 /** Puts the graph into state "phase_high" */
4360 FIRM_API void irg_finalize_cons(ir_graph *irg);
4361
4362 /** Puts the program and all graphs into state phase_high.
4363  *
4364  * This also remarks, the construction of types is finished,
4365  * e.g., that no more subtypes will be added.  */
4366 FIRM_API void irp_finalize_cons(void);
4367
4368 FIRM_API void ir_set_uninitialized_local_variable_func(
4369                 uninitialized_local_variable_func_t *func);
4370
4371 #include "end.h"
4372
4373 #endif