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