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