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