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