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