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