remove r_keep_alive and let keep_alive decide irg based on the node
[libfirm] / include / libfirm / ircons.h
1 /*
2  * Copyright (C) 1995-2010 University of Karlsruhe.  All right reserved.
3  *
4  * This file is part of libFirm.
5  *
6  * This file may be distributed and/or modified under the terms of the
7  * GNU General Public License version 2 as published by the Free Software
8  * Foundation and appearing in the file LICENSE.GPL included in the
9  * packaging of this file.
10  *
11  * Licensees holding valid libFirm Professional Edition licenses may use
12  * this file in accordance with the libFirm Commercial License.
13  * Agreement provided with the Software.
14  *
15  * This file is provided AS IS with NO WARRANTY OF ANY KIND, INCLUDING THE
16  * WARRANTY OF DESIGN, MERCHANTABILITY AND FITNESS FOR A PARTICULAR
17  * PURPOSE.
18  */
19
20 /**
21  * @file
22  * @brief   Various irnode constructors. Automatic construction of SSA
23  *          representation.
24  * @author  Martin Trapp, Christian Schaefer, Goetz Lindenmaier, Boris Boesler,
25  *          Michael Beck
26  * @version $Id$
27  */
28
29 /**
30  *  @file
31  *
32  *  documentation no more supported since 2001
33  *
34  *  IR node construction.
35  *
36  *    This file documents all datatypes and constructors needed to
37  *    build a FIRM representation of a procedure.  The constructors are
38  *    also implemented in this file.
39  *
40  *    The documentation also gives a short manual how to use the library.
41  *
42  *    For extensive documentation of FIRM see UKA Techreport 1999-14.
43  *
44  *
45  *    Three kinds of nodes
46  *    --------------------
47  *
48  *      There are three kinds of nodes known to the IR:  entities,
49  *      types, and ir_nodes
50  *
51  *      + ir_nodes are the actual nodes of the FIRM intermediate representation.
52  *        They represent operations on the data of the program and control flow
53  *        operations.
54  *
55  *      + entity ==> implemented in entity.h
56  *        Refers to a single entity of the compiled program, e.g. a field of a
57  *        class or a method.  If a method or variable can not be assigned to
58  *        a method or class or the like, it is a global object.
59  *
60  *      + types ==> implemented in type.h
61  *        With types type information is represented.  There are several type
62  *       nodes.
63  *
64  *    Implementation of the FIRM operations: ir_node
65  *    ----------------------------------------------
66  *
67  *      Ir_nodes represent operations on the data of the program and control flow
68  *      operations.  Examples of ir_nodes:  Add, Jmp, Cmp
69  *
70  *      FIRM is a dataflow graph.  A dataflow graph is a directed graph,
71  *      so that every node has incoming and outgoing edges.  A node is
72  *      executable if every input at its incoming edges is available.
73  *      Execution of the dataflow graph is started at the Start node which
74  *      has no incoming edges and ends when the End node executes, even if
75  *      there are still executable or not executed nodes.  (Is this true,
76  *      or must all executable nodes be executed?)  (There are exceptions
77  *      to the dataflow paradigma that all inputs have to be available
78  *      before a node can execute: Phi, Block.  See UKA Techreport
79  *      1999-14.)
80  *
81  *      The implementation of FIRM differs from the view as a dataflow
82  *      graph.  To allow fast traversion of the graph edges are
83  *      implemented as C-pointers.  Inputs to nodes are not ambiguous, the
84  *      results can be used by several other nodes.  Each input can be
85  *      implemented as a single pointer to a predecessor node, outputs
86  *      need to be lists of pointers to successors.  Therefore a node
87  *      contains pointers to its predecessors so that the implementation is a
88  *      dataflow graph with reversed edges.  It has to be traversed bottom
89  *      up.
90  *
91  *      All nodes of the IR have the same basic structure.  They are
92  *      distinguished by a field containing the opcode.
93  *
94  *      The fields of an ir_node:
95  *
96  *      kind             A firm_kind tag containing k_ir_node.  This is useful for
97  *                       dynamically checking the type of a node.
98  *
99  *      *op              This ir_op gives the opcode as a tag and a string
100  *                       and the number of attributes of an ir_node.  There is
101  *                       one statically allocated struct ir_op for each opcode.
102  *
103  *      *mode            The ir_mode of the operation represented by this firm
104  *                       node.  The mode of the operation is the mode of its
105  *                       result.  A Firm mode is a datatype as known to the
106  *                       target, not a type of the source language.
107  *
108  *      visit            A flag for traversing the IR.
109  *
110  *      **in             An array with pointers to the node's predecessors.
111  *
112  *      *link            A pointer to an ir_node.  With this pointer all Phi nodes
113  *                       are attached to a Block, i.e. a Block points to its
114  *                       first Phi node, this node points to the second Phi node
115  *                       in the Block and so forth.  Used in mature_immBlock
116  *                       to find all Phi nodes to be matured.  It's also used to
117  *                       annotate a node with a better, optimized version of it.
118  *
119  *      attr             An attr struct containing the attributes of the nodes. The
120  *                       attributes depend on the opcode of the node.  The number
121  *                       of these attributes is given in op.
122  *
123  *    The struct ir_op
124  *    ----------------
125  *                       Not yet documented. See irop.h.
126  *
127  *    The struct ir_mode
128  *    ------------------
129  *                       Not yet documented. See irmode.h.
130  *
131  *    GLOBAL VARIABLES -- now also fields of ir_graph.
132  *    ================
133  *
134  *    current_ir_graph   Points to the current ir_graph.  All constructors for
135  *                       nodes add nodes to this graph.
136  *
137  *    ir_visited         An int used as flag to traverse the ir_graph.
138  *
139  *    block_visited      An int used as a flag to traverse block nodes in the
140  *                       graph.
141  *
142  *                       Others not yet documented.
143  *
144  *
145  *
146  *    CONSTRUCTOR FOR IR_GRAPH --> see irgraph.h
147  *    ========================
148  *
149  *
150  *    PROCEDURE TO CONSTRUCT AN IR GRAPH --> see also Firm tutorial
151  *    ==================================
152  *
153  *    This library supplies several interfaces to construct a FIRM graph for
154  *    a program:
155  *    - A "comfortable" interface generating SSA automatically.  Automatically
156  *      computed predecessors of nodes need not be specified in the constructors.
157  *      (new_<Node> constructurs and a set of additional routines.)
158  *    - A less comfortable interface where all predecessors except the block
159  *      an operation belongs to need to be specified.  SSA must be constructed
160  *      by hand.  (new_<Node> constructors and set_cur_block()).  This interface
161  *      is called "block oriented".  It automatically calles the local optimizations
162  *      for each new node.
163  *    - An even less comfortable interface where the block needs to be specified
164  *      explicitly.  This is called the "raw" interface. (new_r_<Node>
165  *      constructors).  These nodes are not optimized.
166  *
167  *    To use the functionality of the comfortable interface correctly the Front
168  *    End needs to follow certain protocols.  This is explained in the following.
169  *    To build a correct IR with the other interfaces study the semantics of
170  *    the firm node (See tech-reprot UKA 1999-14).  For the construction of
171  *    types and entities see the documentation in those modules.
172  *
173  *    First the Frontend needs to decide which variables and values used in
174  *    a procedure can be represented by dataflow edges.  These are variables
175  *    that need not be saved to memory as they cause no side effects visible
176  *    out of the procedure.  Often these are all compiler generated
177  *    variables and simple local variables of the procedure as integers,
178  *    reals and pointers.  The frontend has to count and number these variables.
179  *
180  *    First an ir_graph needs to be constructed with new_ir_graph.  The
181  *    constructor gets the number of local variables.  The graph is held in the
182  *    global variable irg.
183  *
184  *    Now the construction of the procedure can start.  Several basic blocks can
185  *    be constructed in parallel, but the code within each block needs to
186  *    be constructed (almost) in program order.
187  *
188  *    A global variable holds the current basic block.  All (non block) nodes
189  *    generated are added to this block.  The current block can be set with
190  *    set_cur_block(block).  If several blocks are constructed in parallel block
191  *    switches need to be performed constantly.
192  *
193  *    To generate a Block node (with the comfortable interface), its predecessor
194  *    control flow nodes need not be known.  In case of cyclic control flow these
195  *    can not be known when the block is constructed.  With add_immBlock_pred(block,
196  *    cfnode) predecessors can be added to the block.  If all predecessors are
197  *    added to the block mature_immBlock(b) needs to be called.  Calling mature_immBlock
198  *    early improves the efficiency of the Phi node construction algorithm.
199  *    But if several  blocks are constructed at once, mature_immBlock must only
200  *    be called after performing all set_values and set_stores in the block!
201  *    (See documentation of new_immBlock constructor.)
202  *
203  *    The constructors of arithmetic nodes require that their predecessors
204  *    are mentioned.  Sometimes these are available in the Frontend as the
205  *    predecessors have just been generated by the frontend.  If they are local
206  *    values, the predecessors can be obtained from the library with a call to
207  *    get_value(local_val_nr).  (local_val_nr needs to be administered by
208  *    the Frontend.)  A call to get_value triggers the generation of Phi nodes.
209  *    If an arithmetic operation produces a local value, this value needs to be
210  *    passed to the library by set_value(node, local_val_nr).
211  *    In straight line code these two operations just remember and return the
212  *    pointer to nodes producing the value.  If the value passes block boundaries
213  *    Phi nodes can be inserted.
214  *    Similar routines exist to manage the Memory operands: set_store and
215  *    get_store.
216  *
217  *    Several nodes produce more than one result.  An example is the Div node.
218  *    Such nodes return tuples of values.  From these individual values can be
219  *    extracted by proj nodes.
220  *
221  *    The following example illustrates the construction of a simple basic block
222  *    with two predecessors stored in variables cf_pred1 and cf_pred2, containing
223  *    the code
224  *      a = a div a;
225  *    and finally jumping to an other block.  The variable a got the local_val_nr
226  *    42 by the frontend.
227  *
228  *    ir_node *this_block, *cf_pred1, *cf_pred2, *a_val, *mem, *div, *res, *cf_op;
229  *
230  *    this_block = new_immBlock();
231  *    add_immBlock_pred(this_block, cf_pred1);
232  *    add_immBlock_pred(this_block, cf_pred2);
233  *    mature_immBlock(this_block);
234  *    a_val = get_value(42, mode_Iu);
235  *    mem = get_store();
236  *    div = new_Div(mem, a_val, a_val, mode_Iu);
237  *    mem = new_Proj(div, mode_M, pn_Div_M);   * for the numbers for Proj see docu *
238  *    res = new_Proj(div, mode_Iu, pn_Div_res);
239  *    set_store(mem);
240  *    set_value(res, 42);
241  *    cf_op = new_Jmp();
242  *
243  *    For further information look at the documentation of the nodes and
244  *    constructors and at the paragraph COPING WITH DATA OBJECTS at the
245  *    end of this documentation.
246  *
247  *    The comfortable interface contains the following routines further explained
248  *    below:
249  *
250  *    ir_node *new_immBlock (void);
251  *    ir_node *new_Start    (void);
252  *    ir_node *new_End      (void);
253  *    ir_node *new_Jmp      (void);
254  *    ir_node *new_IJmp     (ir_node *tgt);
255  *    ir_node *new_Cond     (ir_node *c);
256  *    ir_node *new_Return   (ir_node *store, int arity, ir_node **in);
257  *    ir_node *new_Const    (ir_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_Div    (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state);
272  *    ir_node *new_Mod    (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state;
273  *    ir_node *new_And    (ir_node *op1, ir_node *op2, ir_mode *mode);
274  *    ir_node *new_Or     (ir_node *op1, ir_node *op2, ir_mode *mode);
275  *    ir_node *new_Eor    (ir_node *op1, ir_node *op2, ir_mode *mode);
276  *    ir_node *new_Not    (ir_node *op,                ir_mode *mode);
277  *    ir_node *new_Shl    (ir_node *op,  ir_node *k,   ir_mode *mode);
278  *    ir_node *new_Shr    (ir_node *op,  ir_node *k,   ir_mode *mode);
279  *    ir_node *new_Shrs   (ir_node *op,  ir_node *k,   ir_mode *mode);
280  *    ir_node *new_Rotl   (ir_node *op,  ir_node *k,   ir_mode *mode);
281  *    ir_node *new_Cmp    (ir_node *op1, ir_node *op2);
282  *    ir_node *new_Conv   (ir_node *op, ir_mode *mode);
283  *    ir_node *new_Cast   (ir_node *op, ir_type *to_tp);
284  *    ir_node *new_Carry  (ir_node *op1, ir_node *op2, ir_mode *mode);
285  *    ir_node *new_Borrow (ir_node *op1, ir_node *op2, ir_mode *mode);
286  *    ir_node *new_Load   (ir_node *store, ir_node *addr, ir_mode *mode, ir_cons_flags flags);
287  *    ir_node *new_Store  (ir_node *store, ir_node *addr, ir_node *val, ir_cons_flags flags);
288  *    ir_node *new_Alloc  (ir_node *store, ir_node *count, ir_type *alloc_type,
289  *                         where_alloc where);
290  *    ir_node *new_Free   (ir_node *store, ir_node *ptr, ir_node *size,
291  *               ir_type *free_type, where_alloc where);
292  *    ir_node *new_Proj   (ir_node *arg, ir_mode *mode, long proj);
293  *    ir_node *new_NoMem  (void);
294  *    ir_node *new_Mux    (ir_node *sel, ir_node *ir_false, ir_node *ir_true, ir_mode *mode);
295  *    ir_node *new_CopyB  (ir_node *store, ir_node *dst, ir_node *src, ir_type *data_type);
296  *    ir_node *new_InstOf (ir_node *store, ir_node obj, ir_type *ent);
297  *    ir_node *new_Raise  (ir_node *store, ir_node *obj);
298  *    ir_node *new_Bound  (ir_node *store, ir_node *idx, ir_node *lower, ir_node *upper);
299  *    ir_node *new_Pin    (ir_node *node);
300  *
301  *    void add_immBlock_pred (ir_node *block, ir_node *jmp);
302  *    void mature_immBlock (ir_node *block);
303  *    void set_cur_block (ir_node *target);
304  *    ir_node *get_value (int pos, ir_mode *mode);
305  *    void set_value (int pos, ir_node *value);
306  *    ir_node *get_store (void);
307  *    void set_store (ir_node *store);
308  *    keep_alive (ir_node ka)
309  *
310  *    IR_NODES AND CONSTRUCTORS FOR IR_NODES
311  *    =======================================
312  *
313  *    All ir_nodes are defined by a common data structure.  They are distinguished
314  *    by their opcode and differ in the number of their attributes.
315  *
316  *    Const nodes are always added to the start block.
317  *    All other constructors add the created node to the current_block.
318  *    swich_block(block) allows to set the current block to block.
319  *
320  *    Watch for my inconsistent use of input and predecessor (dataflow view)
321  *    and `the node points to' (implementation view).
322  *
323  *    The following description of the nodes lists four properties them if these
324  *    are of interest:
325  *     - the parameters to the constructor
326  *     - the inputs of the Firm node
327  *     - the outputs of the Firm node
328  *     - attributes to the node
329  *
330  *    ------------
331  *
332  *    ir_node *new_immBlock (void)
333  *    ----------------------------
334  *
335  *    Creates a new block. When a new block is created it cannot be known how
336  *    many predecessors this block will have in the control flow graph.
337  *    Therefore the list of inputs can not be fixed at creation.  Predecessors
338  *    can be added with add_immBlock_pred (block, control flow operation).
339  *    With every added predecessor the number of inputs to Phi nodes also
340  *    changes.
341  *
342  *    The block can be completed by mature_immBlock(block) if all predecessors are
343  *    known.  If several blocks are built at once, mature_immBlock can only be called
344  *    after set_value has been called for all values that are life at the end
345  *    of the block.  This is necessary so that Phi nodes created mature_immBlock
346  *    get the right predecessors in case of cyclic dependencies.  If all set_values
347  *    of this block are called after maturing it and before calling get_value
348  *    in some block that is control flow dependent on this block, the construction
349  *    is correct.
350  *
351  *    Example for faulty IR construction:  (draw the graph on a paper and you'll
352  *                                          get it ;-)
353  *
354  *      block_before_loop = new_immBlock();
355  *      set_cur_block(block_before_loop);
356  *      set_value(x);
357  *      mature_immBlock(block_before_loop);
358  *      before2header = new_Jmp;
359  *
360  *      loop_header = new_immBlock ();
361  *      set_cur_block(loop_header);
362  *      header2body - new_Jmp();
363  *
364  *      loop_body = new_immBlock ();
365  *      set_cur_block(loop_body);
366  *      body2header = new_Jmp();
367  *
368  *      add_immBlock_pred(loop_header, before2header);
369  *      add_immBlock_pred(loop_header, body2header);
370  *      add_immBlock_pred(loop_body, header2body);
371  *
372  *      mature_immBlock(loop_header);
373  *      mature_immBlock(loop_body);
374  *
375  *      get_value(loop_body, x);   //  gets the Phi in loop_header
376  *      set_value(loop_header, x); //  sets the value the above get_value should
377  *                                 //  have returned!!!
378  *
379  *    Mature_immBlock also fixes the number of inputs to the Phi nodes.  Mature_immBlock
380  *    should be called as early as possible, as afterwards the generation of Phi
381  *    nodes is more efficient.
382  *
383  *    Inputs:
384  *      There is an input for each control flow predecessor of the block.
385  *      The input points to an instruction producing an output of type X.
386  *      Possible predecessors:  Start, Jmp, Cond, Raise or Return or any node
387  *      possibly causing an exception.  (Often the real predecessors are Projs.)
388  *    Output:
389  *      Mode BB (R), all nodes belonging to this block should consume this output.
390  *      As they are strict (except Block and Phi node) it is a necessary condition
391  *      that the block node executed before any other node in this block executes.
392  *    Attributes:
393  *      block.matured  Indicates whether the block is mature.
394  *      block.**graph_arr
395  *                      This attribute contains all local values valid in this
396  *                      block. This is needed to build the Phi nodes and removed
397  *                      if the graph is complete.  This field is used by the
398  *              internal construction algorithm and should not be accessed
399  *              from outside.
400  *
401  *
402  *    ir_node *new_Block (int arity, ir_node **in)
403  *    --------------------------------------------
404  *
405  *    Creates a new Block with the given list of predecessors.  This block
406  *    is mature.  As other constructors calls optimization and verify for the
407  *    block.  If one of the predecessors is Unknown (as it has to be filled in
408  *    later) optimizations are skipped.  This is necessary to
409  *    construct Blocks in loops.
410  *
411  *
412  *    CONTROL FLOW OPERATIONS
413  *    -----------------------
414  *
415  *    In each block there must be exactly one of the control flow
416  *    operations Start, End, Jmp, Cond, Return or Raise.  The output of a
417  *    control flow operation points to the block to be executed next.
418  *
419  *    ir_node *new_Start (void)
420  *    -------------------------
421  *
422  *    Creates a start node.  Not actually needed public.  There is only one such
423  *   node in each procedure which is automatically created by new_ir_graph.
424  *
425  *    Inputs:
426  *      No inputs except the block it belongs to.
427  *    Output:
428  *      A tuple of 4 (5, 6) distinct values. These are labeled by the following
429  *      projection numbers (pn_Start):
430  *      * pn_Start_X_initial_exec    mode X, points to the first block to be exe *                                   cuted.
431  *      * pn_Start_M                 mode M, the global store
432  *      * pn_Start_P_frame_base      mode P, a pointer to the base of the proce  *                                   dures stack frame.
433  *      * pn_Start_P_globals         mode P, a pointer to the part of the memory *                                   containing_all_ global things.
434  *      * pn_Start_T_args            mode T, a tuple containing all arguments of *                                   the procedure.
435  *
436  *
437  *    ir_node *new_End (void)
438  *    -----------------------
439  *
440  *    Creates an end node.  Not actually needed public.  There is only one such
441  *   node in each procedure which is automatically created by new_ir_graph.
442  *
443  *    Inputs:
444  *      No inputs except the block it belongs to.
445  *    Output:
446  *      No output.
447  *
448  *    ir_node *new_Jmp (void)
449  *    -----------------------
450  *
451  *    Creates a Jmp node.
452  *
453  *    Inputs:
454  *      The block the node belongs to
455  *    Output:
456  *      Control flow to the next block.
457  *
458  *    ir_node *new_IJmp (ir_node *tgt)
459  *    -----------------------
460  *
461  *    Creates an IJmp node.
462  *
463  *    Inputs:
464  *      The node that represents the target jump address
465  *    Output:
466  *      Control flow to an unknown target, must be pinned by
467  *      the End node.
468  *
469  *    ir_node *new_Cond (ir_node *c)
470  *    ------------------------------
471  *
472  *    Creates a Cond node.  There are two versions of this node.
473  *
474  *    The Boolean Cond:
475  *    Input:
476  *      A value of mode b.
477  *    Output:
478  *      A tuple of two control flows.  The first is taken if the input is
479  *      false, the second if it is true.
480  *
481  *    The Switch Cond:
482  *    Input:
483  *      A value of mode I_u. (i)
484  *    Output:
485  *      A tuple of n control flows.  If the Cond's input is i, control
486  *      flow will proceed along output i. If the input is >= n control
487  *      flow proceeds along output n.
488  *
489  *    ir_node *new_Return (ir_node *store, int arity, ir_node **in)
490  *    -------------------------------------------------------------
491  *
492  *    The Return node has as inputs the results of the procedure.  It
493  *    passes the control flow to the end_block.
494  *
495  *    Inputs:
496  *      The memory state.
497  *      All results.
498  *    Output
499  *      Control flow to the end block.
500  *
501  *
502  *    ir_node *new_Const (ir_tarval *con)
503  *    -----------------------------------------------
504  *
505  *    Creates a constant in the constant table and adds a Const node
506  *    returning this value to the start block. The mode is derived
507  *    from the tarval.
508  *
509  *    Parameters:
510  *      *con             Points to an entry in the constant table.
511  *                       This pointer is added to the attributes of
512  *                       the node (self->attr.con)
513  *    Inputs:
514  *      No inputs except the block it belogns to.
515  *    Output:
516  *      The constant value.
517  *    Attribute:
518  *      attr.con   A tarval* pointer to the proper entry in the constant
519  *                 table.
520  *
521  *    ir_node *new_SymConst (ir_mode *mode, union symconst_symbol value, symconst_addr_ent kind)
522  *    -----------------------------------------------------------------------------------------
523  *
524  *    There are several symbolic constants:
525  *     symconst_type_tag   The symbolic constant represents a type tag.
526  *     symconst_type_size  The symbolic constant represents the size of a type.
527  *     symconst_type_align The symbolic constant represents the alignment of a type.
528  *     symconst_addr_ent   The symbolic constant represents the address of an entity.
529  *     symconst_ofs_ent    The symbolic constant represents the offset of an
530  *                         entity in its owner type.
531  *     symconst_enum_const The symbolic constant is a enumeration constant of an
532  *                         enumeration type.
533  *
534  *    Parameters
535  *      mode        P for SymConsts representing addresses, Iu otherwise.
536  *      value       The type, ident, entity or enum constant, depending on the
537  *                  kind
538  *      kind        The kind of the symbolic constant, see the list above.
539  *
540  *    Inputs:
541  *      No inputs except the block it belongs to.
542  *    Output:
543  *      A symbolic constant.
544  *
545  *    Attributes:
546  *      attr.i.num       The symconst_addr_ent, i.e. one of
547  *                        -symconst_type_tag
548  *                        -symconst_type_size
549  *                        -symconst_type_align
550  *                        -symconst_addr_ent
551  *
552  *    If the attr.i.num is symconst_type_tag, symconst_type_size or symconst_type_align,
553  *    the node contains an attribute:
554  *
555  *      attr.i.*type,    a pointer to a type_class.
556  *        if it is linkage_ptr_info it contains
557  *      attr.i.*ptrinfo,  an ident holding information for the linker.
558  *
559  *    ---------------
560  *
561  *    ir_node *new_simpleSel (ir_node *store, ir_node *frame, ir_entity *sel)
562  *    -----------------------------------------------------------------------
563  *
564  *
565  *    Selects an entity from a compound type. This entity can be a field or
566  *    a method.
567  *
568  *    Parameters:
569  *      *store     The memory in which the object the entity should be selected
570  *                 from is allocated.
571  *      *frame     The pointer to the object.
572  *      *sel       The entity to select.
573  *
574  *    Inputs:
575  *      The memory containing the object.
576  *      A pointer to the object.
577  *      An unsigned integer.
578  *    Output:
579  *      A pointer to the selected entity.
580  *    Attributes:
581  *      attr.sel   Pointer to the entity
582  *
583  *
584  *    ir_node *new_Sel (ir_node *store, ir_node *frame, int arity, ir_node **in,
585  *    --------------------------------------------------------------------------
586  *                      ir_entity *sel)
587  *                      ---------------
588  *
589  *    Selects a field from an array type.  The entity has as owner the array, as
590  *    type the arrays element type.  The indices to access an array element are
591  *    given also.
592  *
593  *    Parameters:
594  *      *store     The memory in which the object the entity should be selected from
595  *                 is allocated.
596  *      *frame     The pointer to the object.
597  *      *arity     number of array indices.
598  *      *in        array with index inputs to the node.
599  *      *sel       The entity to select.
600  *
601  *    Inputs:
602  *      The memory containing the object.
603  *      A pointer to the object.
604  *      As much unsigned integer as there are array expressions.
605  *    Output:
606  *      A pointer to the selected entity.
607  *    Attributes:
608  *      attr.sel   Pointer to the entity
609  *
610  *    The constructors new_Sel and new_simpleSel generate the same IR nodes.
611  *    simpleSel just sets the arity of the index inputs to zero.
612  *
613  *
614  *    ARITHMETIC OPERATIONS
615  *    ---------------------
616  *
617  *    ir_node *new_Call (ir_node *store, ir_node *callee, int arity, ir_node **in,
618  *    ----------------------------------------------------------------------------
619  *                       type_method *type)
620  *                       ------------------
621  *
622  *    Creates a procedure call.
623  *
624  *    Parameters
625  *      *store           The actual store.
626  *      *callee          A pointer to the called procedure.
627  *      arity            The number of procedure parameters.
628  *      **in             An array with the pointers to the parameters.
629  *                       The constructor copies this array.
630  *      *type            Type information of the procedure called.
631  *
632  *    Inputs:
633  *      The store, the callee and the parameters.
634  *    Output:
635  *      A tuple containing the eventually changed store and the procedure
636  *      results.
637  *    Attributes:
638  *      attr.call        Contains the attributes for the procedure.
639  *
640  *    ir_node *new_Builtin(ir_node *store, ir_builtin_kind kind, int arity, ir_node **in,
641  *    -----------------------------------------------------------------------------------
642  *                       type_method *type)
643  *                       ------------------
644  *
645  *    Creates a builtin call.
646  *
647  *    Parameters
648  *      *store           The actual store.
649  *      kind             Describes the called builtin.
650  *      arity            The number of procedure parameters.
651  *      **in             An array with the pointers to the parameters.
652  *                       The constructor copies this array.
653  *      *type            Type information of the procedure called.
654  *
655  *    Inputs:
656  *      The store, the kind and the parameters.
657  *    Output:
658  *      A tuple containing the eventually changed store and the procedure
659  *      results.
660  *    Attributes:
661  *      attr.builtin     Contains the attributes for the called builtin.
662  *
663  *    ir_node *new_Add (ir_node *op1, ir_node *op2, ir_mode *mode)
664  *    ------------------------------------------------------------
665  *
666  *    Trivial.
667  *
668  *    ir_node *new_Sub (ir_node *op1, ir_node *op2, ir_mode *mode)
669  *    ------------------------------------------------------------
670  *
671  *    Trivial.
672  *
673  *    ir_node *new_Minus (ir_node *op, ir_mode *mode)
674  *    -----------------------------------------------
675  *
676  *    Unary Minus operations on integer and floating point values.
677  *
678  *    ir_node *new_Mul (ir_node *op1, ir_node *op2, ir_mode *mode)
679  *    ------------------------------------------------------------
680  *
681  *    Trivial.
682  *
683  *    ir_node *new_Mulh (ir_node *op1, ir_node *op2, ir_mode *mode)
684  *    ------------------------------------------------------------
685  *
686  *    Returns the high order bits of a n*n=2n multiplication.
687  *
688  *    ir_node *new_Div (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state)
689  *    ------------------------------------------------------------------------------------------------
690  *
691  *    Trivial.
692  *
693  *    ir_node *new_Mod (ir_node *memop, ir_node *op1, ir_node *op2, ir_mode *mode, op_pin_state state)
694  *    ------------------------------------------------------------------------------------------------
695  *
696  *    Trivial.
697  *
698  *    ir_node *new_And (ir_node *op1, ir_node *op2, ir_mode *mode)
699  *    ------------------------------------------------------------
700  *
701  *    Trivial.
702  *
703  *    ir_node *new_Or (ir_node *op1, ir_node *op2, ir_mode *mode)
704  *    -----------------------------------------------------------
705  *
706  *    Trivial.
707  *
708  *    ir_node *new_Eor (ir_node *op1, ir_node *op2, ir_mode *mode)
709  *    ------------------------------------------------------------
710  *
711  *    Trivial.
712  *
713  *    ir_node *new_Not (ir_node *op, ir_mode *mode)
714  *    ---------------------------------------------
715  *
716  *    This node constructs a constant where all bits are set to one
717  *    and a Eor of this constant and the operator.  This simulates a
718  *    Not operation.
719  *
720  *    ir_node *new_Shl (ir_node *op, ir_node *k, ir_mode *mode)
721  *    ---------------------------------------------------------
722  *
723  *    Trivial.
724  *
725  *    ir_node *new_Shr (ir_node *op, ir_node *k, ir_mode *mode)
726  *    ---------------------------------------------------------
727  *
728  *    Logic shift right, i.e., zero extended.
729  *
730  *
731  *    ir_node *new_Shrs (ir_node *op, ir_node *k, ir_mode *mode)
732  *    ----------------------------------------------------------
733  *
734  *    Arithmetic shift right, i.e., sign extended.
735  *
736  *    ir_node *new_Rotl (ir_node *op, ir_node *k, ir_mode *mode)
737  *    ---------------------------------------------------------
738  *
739  *    Rotates the operand to the left by k bits.
740  *
741  *    ir_node *new_Carry (ir_node *op1, ir_node *op2, ir_mode *mode)
742  *    ------------------------------------------------------------
743  *
744  *    Calculates the Carry value for integer addition. Used only
745  *    in lowering code.
746  *
747  *    ir_node *new_Borrow (ir_node *op1, ir_node *op2, ir_mode *mode)
748  *    ------------------------------------------------------------
749  *
750  *    Calculates the Borrow value for integer substraction. Used only
751  *    in lowering code.
752  *
753  *    ir_node *new_Conv (ir_node *op, ir_mode *mode)
754  *    ---------------------------------------------
755  *
756  *    Mode conversion.  For allowed conversions see UKA Tech Report
757  *    1999-14.
758  *
759  *    ir_node *new_Cmp (ir_node *op1, ir_node *op2)
760  *    ---------------------------------------------
761  *
762  *    Input:
763  *      The two values to be compared.
764  *    Output:
765  *      A 16-tuple containing the results of the 16 different comparisons.
766  *      The following is a list giving the comparisons and a projection
767  *      number (pn_Cmp) to use in Proj nodes to extract the proper result.
768  *        pn_Cmp_False false
769  *        pn_Cmp_Eq    equal
770  *        pn_Cmp_Lt    less
771  *        pn_Cmp_Le    less or equal
772  *        pn_Cmp_Gt    greater
773  *        pn_Cmp_Ge    greater of equal
774  *        pn_Cmp_Lg    less or greater
775  *        pn_Cmp_Leg   less, equal or greater = ordered
776  *        pn_Cmp_Uo    unordered
777  *        pn_Cmp_Ue    unordered or equal
778  *        pn_Cmp_Ul    unordered or less
779  *        pn_Cmp_Ule   unordered, less or equal
780  *        pn_Cmp_Ug    unordered or greater
781  *        pn_Cmp_Uge   unordered, greater or equal
782  *        pn_Cmp_Ne    unordered, less or greater = not equal
783  *        pn_Cmp_True  true
784  *
785  *
786  *
787  *    ------------
788  *
789  *    In general, Phi nodes are automaitcally inserted.  In some cases, if
790  *    all predecessors of a block are known, an explicit Phi node constructor
791  *    is needed.  E.g., to construct a FIRM graph for a statement as
792  *      a = (b==c) ? 2 : 5;
793  *
794  *    ir_node *new_Phi (int arity, ir_node **in, ir_mode *mode)
795  *    ---------------------------------------------------------
796  *
797  *    Creates a Phi node. The in's order has to correspond to the order
798  *    of in's of current_block.  This is not checked by the library!
799  *    If one of the predecessors is Unknown (as it has to be filled in
800  *    later) optimizations are skipped.  This is necessary to
801  *    construct Phi nodes in loops.
802  *
803  *    Parameter
804  *      arity            number of predecessors
805  *      **in             array with predecessors
806  *      *mode            The mode of its inputs and output.
807  *    Inputs:
808  *      A Phi node has as many inputs as the block it belongs to.
809  *      Each input points to a definition of the same value on a
810  *      different path in the control flow.
811  *    Output
812  *      The definition valid in this block.
813  *
814  *    ir_node *new_Mux (ir_node *sel, ir_node *ir_false, ir_node *ir_true, ir_mode *mode)
815  *    -----------------------------------------------------------------------------------
816  *
817  *    Creates a Mux node. This node implements the following semantic:
818  *    If the sel node (which must be of mode_b) evaluates to true, its value is
819  *    ir_true, else ir_false;
820  *
821  *
822  *
823  *    OPERATIONS TO MANAGE MEMORY EXPLICITLY
824  *    --------------------------------------
825  *
826  *    ir_node *new_Load (ir_node *store, ir_node *addr, ir_mode *mode, ir_cons_flags flags)
827  *    -------------------------------------------------------------------------------------
828  *
829  *    The Load operation reads a value from memory.
830  *
831  *    Parameters:
832  *    *store        The current memory.
833  *    *addr         A pointer to the variable to be read in this memory.
834  *    *mode         The mode of the value to be loaded.
835  *     flags        Additional flags for alignment, volatility and pin state.
836  *
837  *    Inputs:
838  *      The memory and a pointer to a variable in this memory.
839  *    Output:
840  *      A tuple of the memory, a control flow to be taken in case of
841  *      an exception and the loaded value.
842  *
843  *    ir_node *new_Store (ir_node *store, ir_node *addr, ir_node *val, ir_cons_flags flags)
844  *    -------------------------------------------------------------------------------------
845  *
846  *    The Store operation writes a value to a variable in memory.
847  *
848  *    Inputs:
849  *      The memory, a pointer to a variable in this memory and the value
850  *      to write to this variable.
851  *    Output:
852  *      A tuple of the changed memory and a control flow to be taken in
853  *      case of an exception.
854  *
855  *    ir_node *new_Alloc (ir_node *store, ir_node *count, ir_type *alloc_type,
856  *    -----------------------------------------------------------------------
857  *                        where_alloc where)
858  *                        ------------------
859  *
860  *    The Alloc node allocates a new variable.  It can be specified whether the
861  *    variable should be allocated to the stack or to the heap.
862  *
863  *    Parameters:
864  *      *store       The memory which shall contain the new variable.
865  *      *count       This field is for allocating arrays, it specifies how
866  *                   many array elements are to be allocated.
867  *      *alloc_type  The type of the allocated variable. In case of allocating
868  *                   arrays this has to be the array type, not the type of the
869  *                   array elements.
870  *      where        Where to allocate the variable, either heap_alloc or stack_alloc.
871  *
872  *    Inputs:
873  *      A memory and an unsigned integer.
874  *    Output:
875  *      A tuple of the changed memory, a control flow to be taken in
876  *      case of an exception and the pointer to the new variable.
877  *    Attributes:
878  *      a.where          Indicates where the variable is allocated.
879  *      a.*type          A pointer to the class the allocated data object
880  *                       belongs to.
881  *
882  *    ir_node *new_Free (ir_node *store, ir_node *ptr, ir_node *size, ir_type *free_type,
883  *    -----------------------------------------------------------------------------------
884  *                        where_alloc where)
885  *                        ------------------
886  *
887  *    The Free node frees memory of the given variable.
888  *
889  *    Parameters:
890  *      *store       The memory which shall contain the new variable.
891  *      *ptr         The pointer to the object to free.
892  *      *size        The number of objects of type free_type to free in a sequence.
893  *      *free_type   The type of the freed variable.
894  *      where        Where the variable was allocated, either heap_alloc or stack_alloc.
895  *
896  *    Inputs:
897  *      A memory, a pointer and an unsigned integer.
898  *    Output:
899  *      The changed memory.
900  *    Attributes:
901  *      f.*type          A pointer to the type information of the freed data object.
902  *
903  *    Not Implemented!
904  *
905  *    ir_node *new_Sync (int arity, ir_node **in)
906  *    -------------------------------------------
907  *
908  *    The Sync operation unifies several partial memory blocks.  These blocks
909  *    have to be pairwise disjunct or the values in common locations have to
910  *    be identical.  This operation allows to specify all operations that eventually
911  *    need several partial memory blocks as input with a single entrance by
912  *    unifying the memories with a preceding Sync operation.
913  *
914  *    Parameters
915  *      arity    The number of memories to synchronize.
916  *      **in     An array of pointers to nodes that produce an output of
917  *               type memory.
918  *    Inputs
919  *      Several memories.
920  *    Output
921  *      The unified memory.
922  *
923  *
924  *    SPECIAL OPERATIONS
925  *    ------------------
926  *
927  *    ir_node *new_Bad (void)
928  *    -----------------------
929  *
930  *    Returns the unique Bad node current_ir_graph->bad.
931  *    This node is used to express results of dead code elimination.
932  *
933  *    ir_node *new_NoMem (void)
934  *    -----------------------------------------------------------------------------------
935  *
936  *    Returns the unique NoMem node current_ir_graph->no_mem.
937  *    This node is used as input for operations that need a Memory, but do not
938  *    change it like Div by const != 0, analyzed calls etc.
939  *
940  *    ir_node *new_Proj (ir_node *arg, ir_mode *mode, long proj)
941  *    ----------------------------------------------------------
942  *
943  *    Selects one entry of a tuple.  This is a hidden edge with attributes.
944  *
945  *    Parameters
946  *      *arg      A node producing a tuple.
947  *      *mode     The mode of the value to project.
948  *      proj      The position of the value in the tuple.
949  *    Input:
950  *      The tuple.
951  *    Output:
952  *      The value.
953  *
954  *    ir_node *new_Tuple (int arity, ir_node **in)
955  *    --------------------------------------------
956  *
957  *    Builds a Tuple from single values.  This is needed to implement
958  *    optimizations that remove a node that produced a tuple.  The node can be
959  *    replaced by the Tuple operation so that the following Proj nodes have not to
960  *    be changed.  (They are hard to find due to the implementation with pointers
961  *    in only one direction.)  The Tuple node is smaller than any other
962  *    node, so that a node can be changed into a Tuple by just changing its
963  *    opcode and giving it a new in array.
964  *
965  *    Parameters
966  *      arity    The number of tuple elements.
967  *      **in     An array containing pointers to the nodes producing the
968  *               tuple elements.
969  *
970  *    ir_node *new_Id (ir_node *val, ir_mode *mode)
971  *    ---------------------------------------------
972  *
973  *    The single output of the Id operation is its input.  Also needed
974  *    for optimizations.
975  *
976  *
977  *    HIGH LEVEL OPERATIONS
978  *    ---------------------
979  *
980  *    ir_node *new_CopyB (ir_node *store, ir_node *dst, ir_node *src, ir_type *data_type)
981  *    -----------------------------------------------------------------------------------
982  *
983  *    Describes a high level block copy of a compound type from address src to
984  *    address dst. Must be lowered to a Call to a runtime memory copy function.
985  *
986  *
987  *    HIGH LEVEL OPERATIONS: Exception Support
988  *    ----------------------------------------
989  *    See TechReport 1999-14, chapter Exceptions.
990  *
991  *    ir_node *new_InstOf(ir_node *store, ir_node *ptr, ir_type *type);
992  *    -----------------------------------------------------------------------------------
993  *
994  *    Describes a high level type check. Must be lowered to a Call to a runtime check
995  *    function.
996  *
997  *    ir_node *new_Raise (ir_node *store, ir_node *obj)
998  *    -------------------------------------------------
999  *
1000  *    Raises an exception.  Unconditional change of control flow.  Writes
1001  *    an explicit Except variable to memory to pass it to the exception
1002  *    handler.  Must be lowered to a Call to a runtime check
1003  *    function.
1004  *
1005  *    Inputs:
1006  *      The memory state.
1007  *      A pointer to the Except variable.
1008  *    Output:
1009  *      A tuple of control flow and the changed memory state.  The control flow
1010  *      points to the exception handler if it is definied in this procedure,
1011  *      else it points to the end_block.
1012  *
1013  *    ir_node *new_Bound  (ir_node *store, ir_node *idx, ir_node *lower, ir_node *upper);
1014  *    -----------------------------------------------------------------------------------
1015  *
1016  *    Describes a high level bounds check. Must be lowered to a Call to a runtime check
1017  *    function.
1018  *
1019  *    ir_node *new_Pin  (ir_node *node);
1020  *    -----------------------------------------------------------------------------------
1021  *
1022  *    Pin the value of the node node in the current block  No users of the Pin node can
1023  *    float above the Block of the Pin. The node cannot float behind this block. Often
1024  *    used to Pin the NoMem node.
1025  *
1026  *
1027  *    COPING WITH DATA OBJECTS
1028  *    ========================
1029  *
1030  *    Two kinds of data objects have to be distinguished for generating
1031  *    FIRM.  First there are local variables other than arrays that are
1032  *    known to be alias free.  Second there are all other data objects.
1033  *    For the first a common SSA representation is built, the second
1034  *    are modeled by saving them to memory.  The memory is treated as
1035  *    a single local variable, the alias problem is hidden in the
1036  *    content of this variable.
1037  *
1038  *    All values known in a Block are listed in the block's attribute,
1039  *    block.**graph_arr which is used to automatically insert Phi nodes.
1040  *    The following two functions can be used to add a newly computed value
1041  *    to the array, or to get the producer of a value, i.e., the current
1042  *    live value.
1043  *
1044  *    inline void set_value (int pos, ir_node *value)
1045  *    -----------------------------------------------
1046  *
1047  *    Has to be called for every assignment to a local variable.  It
1048  *    adds the value to the array of used values at position pos.  Pos
1049  *    has to be a unique identifier for an entry in the procedure's
1050  *    definition table.  It can be used to access the value again.
1051  *    Requires current_block to be set correctly.
1052  *
1053  *    ir_node *get_value (int pos, ir_mode *mode)
1054  *    -------------------------------------------
1055  *
1056  *    Returns the node defining the value referred to by pos. If the
1057  *    value is not defined in this block a Phi node is generated and
1058  *    all definitions reaching this Phi node are collected.  It can
1059  *    happen that the algorithm allocates an unnecessary Phi node,
1060  *    e.g. if there is only one definition of this value, but this
1061  *    definition reaches the currend block on several different
1062  *    paths.  This Phi node will be eliminated if optimizations are
1063  *    turned on right after its creation.
1064  *    Requires current_block to be set correctly.
1065  *
1066  *    There are two special routines for the global store:
1067  *
1068  *    void set_store (ir_node *store)
1069  *    -------------------------------
1070  *
1071  *    Adds the store to the array of known values at a reserved
1072  *    position.
1073  *    Requires current_block to be set correctly.
1074  *
1075  *    ir_node *get_store (void)
1076  *    -------------------------
1077  *
1078  *    Returns the node defining the actual store.
1079  *    Requires current_block to be set correctly.
1080  *
1081  *
1082  *    inline void keep_alive (ir_node *ka)
1083  *    ------------------------------------
1084  *
1085  *    Keep this node alive because it is (might be) not in the control
1086  *    flow from Start to End.  Adds the node to the list in the end
1087  *   node.
1088  *
1089  */
1090 #ifndef FIRM_IR_IRCONS_H
1091 #define FIRM_IR_IRCONS_H
1092
1093 #include "firm_types.h"
1094 #include "begin.h"
1095 #include "irnode.h"
1096
1097 /*-------------------------------------------------------------------------*/
1098 /* The raw interface                                                       */
1099 /*-------------------------------------------------------------------------*/
1100
1101 /**
1102  * Constructor for a Const node.
1103  *
1104  * Adds the node to the start block.
1105  *
1106  * Constructor for a Const node. The constant represents a target
1107  * value.  Sets the type information to type_unknown.  (No more
1108  * supported: If tv is entity derives a somehow useful type.)
1109  *
1110  * @param *db    A pointer for debug information.
1111  * @param *irg   The IR graph the node  belongs to.
1112  * @param *mode  The mode of the operands and results.
1113  * @param value  A value from which the tarval is made.
1114  */
1115 FIRM_API ir_node *new_rd_Const_long(dbg_info *db, ir_graph *irg,
1116                                     ir_mode *mode, long value);
1117
1118 /** Constructor for a SymConst node.
1119  *
1120  *  This is the constructor for a symbolic constant.
1121  *    There are several kinds of symbolic constants:
1122  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
1123  *                          type the tag stands for is given explicitly.
1124  *    - symconst_type_size  The symbolic constant represents the size of a type.
1125  *                          The type of which the constant represents the size
1126  *                          is given explicitly.
1127  *    - symconst_type_align The symbolic constant represents the alignment of a
1128  *                          type.  The type of which the constant represents the
1129  *                          size is given explicitly.
1130  *    - symconst_addr_ent   The symbolic constant represents the address of an
1131  *                          entity (variable or method).  The variable is given
1132  *                          explicitly by a firm entity.
1133  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
1134  *                          entity in its owner type.
1135  *    - symconst_enum_const The symbolic constant is a enumeration constant of
1136  *                          an enumeration type.
1137  *
1138  *    Inputs to the node:
1139  *      No inputs except the block it belongs to.
1140  *    Outputs of the node.
1141  *      An unsigned integer (I_u) or a pointer (P).
1142  *
1143  *    Mention union in declaration so that the firmjni generator recognizes that
1144  *    it can not cast the argument to an int.
1145  *
1146  * @param *db     A pointer for debug information.
1147  * @param *irg    The IR graph the node  belongs to.
1148  * @param mode    The mode for the SymConst.
1149  * @param value   A type, ident, entity or enum constant depending on the
1150  *                SymConst kind.
1151  * @param kind    The kind of the symbolic constant, see the list above
1152  */
1153 FIRM_API ir_node *new_rd_SymConst(dbg_info *db, ir_graph *irg, ir_mode *mode,
1154                                   union symconst_symbol value,
1155                                   symconst_kind kind);
1156
1157 /** Constructor for a SymConst addr_ent node.
1158  *
1159  * Same as new_rd_SymConst, except that the constructor is tailored for
1160  * symconst_addr_ent.
1161  * Adds the SymConst to the start block of irg. */
1162 FIRM_API ir_node *new_rd_SymConst_addr_ent(dbg_info *db, ir_graph *irg,
1163                                            ir_mode *mode, ir_entity *symbol);
1164
1165 /** Constructor for a SymConst ofs_ent node.
1166  *
1167  * Same as new_rd_SymConst, except that the constructor is tailored for
1168  * symconst_ofs_ent.
1169  * Adds the SymConst to the start block of irg.
1170  */
1171 FIRM_API ir_node *new_rd_SymConst_ofs_ent(dbg_info *db, ir_graph *irg,
1172                                           ir_mode *mode, ir_entity *symbol);
1173
1174 /** Constructor for a SymConst type_tag node.
1175  *
1176  * Same as new_rd_SymConst, except that the constructor is tailored for
1177  * symconst_type_tag.
1178  * Adds the SymConst to the start block of irg.
1179  */
1180 FIRM_API ir_node *new_rd_SymConst_type_tag(dbg_info *db, ir_graph *irg,
1181                                            ir_mode *mode, ir_type *symbol);
1182
1183 /** Constructor for a SymConst size node.
1184  *
1185  * Same as new_rd_SymConst, except that the constructor is tailored for
1186  * symconst_type_size.
1187  * Adds the SymConst to the start block of irg. */
1188 FIRM_API ir_node *new_rd_SymConst_size(dbg_info *db, ir_graph *irg,
1189                                        ir_mode *mode, ir_type *symbol);
1190
1191 /** Constructor for a SymConst size node.
1192  *
1193  * Same as new_rd_SymConst, except that the constructor is tailored for
1194  * symconst_type_align.
1195  * Adds the SymConst to the start block of irg.
1196  */
1197 FIRM_API ir_node *new_rd_SymConst_align(dbg_info *db, ir_graph *irg,
1198                                         ir_mode *mode, ir_type *symbol);
1199
1200 /** Constructor for a simpleSel node.
1201  *
1202  *  This is a shortcut for the new_rd_Sel() constructor.  To be used for
1203  *  Sel nodes that do not select from an array, i.e., have no index
1204  *  inputs.  It adds the two parameters 0, NULL.
1205  *
1206  * @param   *db        A pointer for debug information.
1207  * @param   *block     The IR block the node belongs to.
1208  * @param   *store     The memory in which the object the entity should be
1209  *                     selected from is allocated.
1210  * @param   *objptr    The object from that the Sel operation selects a
1211  *                     single attribute out.
1212  * @param   *ent       The entity to select.
1213  */
1214 FIRM_API ir_node *new_rd_simpleSel(dbg_info *db, ir_node *block, ir_node *store,
1215                                    ir_node *objptr, ir_entity *ent);
1216
1217 /** Constructor for a remainderless Div node.
1218  *
1219  * @param   *db    A pointer for debug information.
1220  * @param   *block The IR block the node belongs to.
1221  * @param   *memop The store needed to model exceptions
1222  * @param   *op1   The first operand.
1223  * @param   *op2   The second operand.
1224  * @param   *mode  The mode of the result.
1225  * @param   state  The pinned state.
1226  */
1227 FIRM_API ir_node *new_rd_DivRL(dbg_info *db, ir_node *block, ir_node *memop,
1228                                ir_node *op1, ir_node *op2, ir_mode *mode,
1229                                op_pin_state state);
1230
1231 /** Constructor for a strictConv node.
1232  *
1233  * @param   *db    A pointer for debug information.
1234  * @param   *block The IR block the node belongs to.
1235  * @param   *op    The operand.
1236  * @param   *mode  The mode of this the operand muss be converted .
1237  */
1238 FIRM_API ir_node *new_rd_strictConv(dbg_info *db, ir_node *block,
1239                                     ir_node *op, ir_mode *mode);
1240
1241 /** Constructor for a defaultProj node.
1242  *
1243  * Represents the default control flow of a Switch-Cond node.
1244  *
1245  * @param *db       A pointer for debug information.
1246  * @param arg       A node producing a tuple.
1247  * @param max_proj  The end position of the value in the tuple.
1248  */
1249 FIRM_API ir_node *new_rd_defaultProj(dbg_info *db, ir_node *arg, long max_proj);
1250
1251 /** Constructor for an ASM pseudo node.
1252  *
1253  * @param *db         A pointer for debug information.
1254  * @param *block      The block the node belong to.
1255  * @param arity       The number of data inputs to the node.
1256  * @param *in         The array of length arity of data inputs.
1257  * @param *inputs     The array of length arity of input constraints.
1258  * @param n_outs      The number of data outputs to the node.
1259  * @param *outputs    The array of length n_outs of output constraints.
1260  * @param n_clobber   The number of clobbered registers.
1261  * @param *clobber    The array of length n_clobber of clobbered registers.
1262  * @param *asm_text   The assembler text.
1263  */
1264 FIRM_API ir_node *new_rd_ASM(dbg_info *db, ir_node *block,
1265                             int arity, ir_node *in[], ir_asm_constraint *inputs,
1266                             int n_outs, ir_asm_constraint *outputs,
1267                             int n_clobber, ident *clobber[], ident *asm_text);
1268
1269 /*-------------------------------------------------------------------------*/
1270 /* The raw interface without debug support                                 */
1271 /*-------------------------------------------------------------------------*/
1272
1273 /** Constructor for a Const node.
1274  *
1275  * Adds the node to the start block.
1276  *
1277  * Constructor for a Const node. The constant represents a target
1278  * value.  Sets the type information to type_unknown.  (No more
1279  * supported: If tv is entity derives a somehow useful type.)
1280  *
1281  * @param *irg   The IR graph the node  belongs to.
1282  * @param *mode  The mode of the operands and the results.
1283  * @param value  A value from which the tarval is made.
1284  */
1285 FIRM_API ir_node *new_r_Const_long(ir_graph *irg, ir_mode *mode, long value);
1286
1287 /** Constructor for a SymConst node.
1288  *
1289  *  This is the constructor for a symbolic constant.
1290  *    There are several kinds of symbolic constants:
1291  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
1292  *                          type the tag stands for is given explicitly.
1293  *    - symconst_type_size  The symbolic constant represents the size of a type.
1294  *                          The type of which the constant represents the size
1295  *                          is given explicitly.
1296  *    - symconst_type_align The symbolic constant represents the alignment of a
1297  *                          type.  The type of which the constant represents the
1298  *                          size is given explicitly.
1299  *    - symconst_addr_ent   The symbolic constant represents the address of an
1300  *                          entity (variable or method).  The variable is given
1301  *                          explicitly by a firm entity.
1302  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
1303  *                          entity in its owner type.
1304  *    - symconst_enum_const The symbolic constant is a enumeration constant of
1305  *                          an enumeration type.
1306  *
1307  *    Inputs to the node:
1308  *      No inputs except the block it belongs to.
1309  *    Outputs of the node.
1310  *      An unsigned integer (I_u) or a pointer (P).
1311  *
1312  *    Mention union in declaration so that the firmjni generator recognizes that
1313  *    it can not cast the argument to an int.
1314  *
1315  * @param *irg    The IR graph the node  belongs to.
1316  * @param mode    The mode for the SymConst.
1317  * @param value   A type, ident, entity or enum constant depending on the
1318  *                SymConst kind.
1319  * @param kind    The kind of the symbolic constant, see the list above
1320  */
1321 FIRM_API ir_node *new_r_SymConst(ir_graph *irg, ir_mode *mode,
1322                                  union symconst_symbol value,
1323                                  symconst_kind kind);
1324
1325 /** Constructor for a simpleSel node.
1326  *
1327  *  This is a shortcut for the new_d_Sel() constructor.  To be used for
1328  *  Sel nodes that do not select from an array, i.e., have no index
1329  *  inputs.  It adds the two parameters 0, NULL.
1330  *
1331  * @param *block     The IR block the node belongs to.
1332  * @param *store     The memory in which the object the entity should be selected
1333  *                   from is allocated.
1334  * @param *objptr    The object from that the Sel operation selects a
1335  *                   single attribute out.
1336  * @param *ent       The entity to select.
1337  */
1338 FIRM_API ir_node *new_r_simpleSel(ir_node *block, ir_node *store,
1339                                   ir_node *objptr, ir_entity *ent);
1340
1341 /** Constructor for a remainderless Div node.
1342  *
1343  * @param *block The IR block the node belongs to.
1344  * @param *memop The store needed to model exceptions
1345  * @param *op1   The first operand.
1346  * @param *op2   The second operand.
1347  * @param *mode  The mode of the result.
1348  * @param state  The pinned state.
1349  */
1350 FIRM_API ir_node *new_r_DivRL(ir_node *block, ir_node *memop,
1351                               ir_node *op1, ir_node *op2, ir_mode *mode,
1352                               op_pin_state state);
1353 /** Constructor for a strict Conv node.
1354  *
1355  * @param *block The IR block the node belongs to.
1356  * @param *op    The operand.
1357  * @param *mode  The mode of this the operand muss be converted .
1358  */
1359 FIRM_API ir_node *new_r_strictConv(ir_node *block, ir_node *op, ir_mode *mode);
1360
1361 /** Constructor for a defaultProj node.
1362  *
1363  * Represents the default control flow of a Switch-Cond node.
1364  *
1365  * @param arg       A node producing a tuple.
1366  * @param max_proj  The end  position of the value in the tuple.
1367  */
1368 FIRM_API ir_node *new_r_defaultProj(ir_node *arg, long max_proj);
1369
1370 /** Constructor for an ASM pseudo node.
1371  *
1372  * @param *block      The block the node belong to.
1373  * @param arity       The number of data inputs to the node.
1374  * @param *in         The array of length arity of data inputs.
1375  * @param *inputs     The array of length arity of input constraints.
1376  * @param n_outs      The number of data outputs to the node.
1377  * @param *outputs    The array of length n_outs of output constraints.
1378  * @param n_clobber   The number of clobbered registers.
1379  * @param *clobber    The array of length n_clobber of clobbered registers.
1380  * @param *asm_text   The assembler text.
1381  */
1382 FIRM_API ir_node *new_r_ASM(ir_node *block,
1383                             int arity, ir_node *in[], ir_asm_constraint *inputs,
1384                             int n_outs, ir_asm_constraint *outputs,
1385                             int n_clobber, ident *clobber[], ident *asm_text);
1386
1387 /*-----------------------------------------------------------------------*/
1388 /* The block oriented interface                                          */
1389 /*-----------------------------------------------------------------------*/
1390
1391 /** Sets the current block in which the following constructors place the
1392  *  nodes they construct.
1393  *
1394  *  @param target  The new current block.
1395  */
1396 FIRM_API void set_cur_block(ir_node *target);
1397 FIRM_API void set_r_cur_block(ir_graph *irg, ir_node *target);
1398
1399 /** Returns the current block of the current graph. */
1400 FIRM_API ir_node *get_cur_block(void);
1401 FIRM_API ir_node *get_r_cur_block(ir_graph *irg);
1402
1403 /**
1404  * @see new_rd_Const_long()
1405  *
1406  * @param *db    A pointer for debug information.
1407  * @param *mode  The mode of the operands and results.
1408  * @param value  A value from which the tarval is made.
1409  */
1410 FIRM_API ir_node *new_d_Const_long(dbg_info *db, ir_mode *mode, long value);
1411
1412 /** Constructor for a SymConst node.
1413  *
1414  *  This is the constructor for a symbolic constant.
1415  *    There are several kinds of symbolic constants:
1416  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
1417  *                          type the tag stands for is given explicitly.
1418  *    - symconst_type_size  The symbolic constant represents the size of a type.
1419  *                          The type of which the constant represents the size
1420  *                          is given explicitly.
1421  *    - symconst_type_align The symbolic constant represents the alignment of a
1422  *                          type.  The type of which the constant represents the
1423  *                          size is given explicitly.
1424  *    - symconst_addr_ent   The symbolic constant represents the address of an
1425  *                          entity (variable or method).  The variable is given
1426  *                          explicitly by a firm entity.
1427  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
1428  *                          entity in its owner type.
1429  *    - symconst_enum_const The symbolic constant is a enumeration constant of
1430  *                          an enumeration type.
1431  *
1432  *    Inputs to the node:
1433  *      No inputs except the block it belongs to.
1434  *    Outputs of the node.
1435  *      An unsigned integer (I_u) or a pointer (P).
1436  *
1437  *    Mention union in declaration so that the firmjni generator recognizes that
1438  *    it can not cast the argument to an int.
1439  *
1440  * @param *db     A pointer for debug information.
1441  * @param mode    The mode for the SymConst.
1442  * @param value   A type, ident, entity or enum constant depending on the
1443  *                SymConst kind.
1444  * @param kind    The kind of the symbolic constant, see the list above
1445  */
1446 FIRM_API ir_node *new_d_SymConst(dbg_info *db, ir_mode *mode,
1447                                  union symconst_symbol value,
1448                                  symconst_kind kind);
1449
1450 /** Constructor for a simpleSel node.
1451  *
1452  *  This is a shortcut for the new_d_Sel() constructor.  To be used for
1453  *  Sel nodes that do not select from an array, i.e., have no index
1454  *  inputs.  It adds the two parameters 0, NULL.
1455  *
1456  * @param   *db        A pointer for debug information.
1457  * @param   *store     The memory in which the object the entity should be
1458  *                     selected from is allocated.
1459  * @param   *objptr    The object from that the Sel operation selects a
1460  *                     single attribute out.
1461  * @param   *ent       The entity to select.
1462  */
1463 FIRM_API ir_node *new_d_simpleSel(dbg_info *db, ir_node *store, ir_node *objptr,
1464                                   ir_entity *ent);
1465 /** Constructor for a remainderless Div node.
1466  *
1467  * Adds the node to the block in current_ir_block.
1468  *
1469  * @param   *db    A pointer for debug information.
1470  * @param   *memop The store needed to model exceptions
1471  * @param   *op1   The first operand.
1472  * @param   *op2   The second operand.
1473  * @param   *mode  The mode of the result.
1474  * @param   state  The pinned state.
1475  */
1476 FIRM_API ir_node *new_d_DivRL(dbg_info *db, ir_node *memop,
1477                               ir_node *op1, ir_node *op2, ir_mode *mode,
1478                               op_pin_state state);
1479 /** Constructor for a strict Conv node.
1480  *
1481  * Adds the node to the block in current_ir_block.
1482  *
1483  * @param   *db    A pointer for debug information.
1484  * @param   *op    The operand.
1485  * @param   *mode  The mode of this the operand muss be converted .
1486  */
1487 FIRM_API ir_node *new_d_strictConv(dbg_info *db, ir_node *op, ir_mode *mode);
1488
1489 /** Constructor for a defaultProj node.
1490  *
1491  * Represents the default control flow of a Switch-Cond node.
1492  * Adds the node to the block in current_ir_block.
1493  *
1494  * @param *db       A pointer for debug information.
1495  * @param arg       A node producing a tuple.
1496  * @param max_proj  The end  position of the value in the tuple.
1497  */
1498 FIRM_API ir_node *new_d_defaultProj(dbg_info *db, ir_node *arg, long max_proj);
1499
1500 /** Constructor for an ASM pseudo node.
1501  *
1502  * @param *db         A pointer for debug information.
1503  * @param arity       The number of data inputs to the node.
1504  * @param *in         The array of length arity of data inputs.
1505  * @param *inputs     The array of length arity of input constraints.
1506  * @param n_outs      The number of data outputs to the node.
1507  * @param *outputs    The array of length n_outs of output constraints.
1508  * @param n_clobber   The number of clobbered registers.
1509  * @param *clobber    The array of length n_clobber of clobbered registers.
1510  * @param *asm_text   The assembler text.
1511  */
1512 FIRM_API ir_node *new_d_ASM(dbg_info *db, int arity, ir_node *in[],
1513                             ir_asm_constraint *inputs,
1514                             int n_outs, ir_asm_constraint *outputs,
1515                             int n_clobber, ident *clobber[], ident *asm_text);
1516
1517 /*-----------------------------------------------------------------------*/
1518 /* The block oriented interface without debug support                    */
1519 /*-----------------------------------------------------------------------*/
1520
1521 /**
1522  * Make a const from a long.
1523  * This is just convenience for the usual
1524  * <code>
1525  * new_Const(mode, tarval_from_long(mode, ...))
1526  * </code>
1527  * pain.
1528  * @param mode The mode for the const.
1529  * @param value The value of the constant.
1530  * @return A new const node.
1531  */
1532 FIRM_API ir_node *new_Const_long(ir_mode *mode, long value);
1533
1534 /** Constructor for a SymConst node.
1535  *
1536  *  This is the constructor for a symbolic constant.
1537  *    There are several kinds of symbolic constants:
1538  *    - symconst_type_tag   The symbolic constant represents a type tag.  The
1539  *                          type the tag stands for is given explicitly.
1540  *    - symconst_type_size  The symbolic constant represents the size of a type.
1541  *                          The type of which the constant represents the size
1542  *                          is given explicitly.
1543  *    - symconst_type_align The symbolic constant represents the alignment of a
1544  *                          type.  The type of which the constant represents the
1545  *                          size is given explicitly.
1546  *    - symconst_addr_ent   The symbolic constant represents the address of an
1547  *                          entity (variable or method).  The variable is given
1548  *                          explicitly by a firm entity.
1549  *    - symconst_ofs_ent    The symbolic constant represents the offset of an
1550  *                          entity in its owner type.
1551  *    - symconst_enum_const The symbolic constant is a enumeration constant of
1552  *                          an enumeration type.
1553  *
1554  *    Inputs to the node:
1555  *      No inputs except the block it belongs to.
1556  *    Outputs of the node.
1557  *      An unsigned integer (I_u) or a pointer (P).
1558  *
1559  *    Mention union in declaration so that the firmjni generator recognizes that
1560  *    it can not cast the argument to an int.
1561  *
1562  * @param mode    The mode for the SymConst.
1563  * @param value   A type, ident, entity or enum constant depending on the
1564  *                SymConst kind.
1565  * @param kind    The kind of the symbolic constant, see the list above
1566  */
1567 FIRM_API ir_node *new_SymConst(ir_mode *mode, union symconst_symbol value,
1568                                symconst_kind kind);
1569
1570 /** Constructor for a simpelSel node.
1571  *
1572  *  This is a shortcut for the new_Sel() constructor.  To be used for
1573  *  Sel nodes that do not select from an array, i.e., have no index
1574  *  inputs.  It adds the two parameters 0, NULL.
1575  *
1576  * @param   *store     The memory in which the object the entity should be selected from is allocated.
1577  * @param   *objptr    The object from that the Sel operation selects a single attribute out.
1578  * @param   *ent       The entity to select.
1579  */
1580 FIRM_API ir_node *new_simpleSel(ir_node *store, ir_node *objptr,
1581                                 ir_entity *ent);
1582
1583 /** Constructor for a remainderless Div node.
1584  *
1585  * Adds the node to the block in current_ir_block.
1586  *
1587  * @param   *memop The store needed to model exceptions
1588  * @param   *op1   The first operand.
1589  * @param   *op2   The second operand.
1590  * @param   *mode  The mode of the result.
1591  * @param   state  The pinned state.
1592  */
1593 FIRM_API ir_node *new_DivRL(ir_node *memop, ir_node *op1, ir_node *op2,
1594                             ir_mode *mode, op_pin_state state);
1595
1596 /** Constructor for a strict Conv node.
1597  *
1598  * Adds the node to the block in current_ir_block.
1599  *
1600  * @param   *op          The operand.
1601  * @param   *mode        The mode of this the operand muss be converted.
1602  */
1603 FIRM_API ir_node *new_strictConv(ir_node *op, ir_mode *mode);
1604
1605 /** Constructor for a defaultProj node.
1606  *
1607  * Represents the default control flow of a Switch-Cond node.
1608  * Adds the node to the block in current_ir_block.
1609  *
1610  * @param arg       A node producing a tuple.
1611  * @param max_proj  The end  position of the value in the tuple.
1612  */
1613 FIRM_API ir_node *new_defaultProj(ir_node *arg, long max_proj);
1614
1615 /** Constructor for an ASM pseudo node.
1616  *
1617  * @param arity       The number of data inputs to the node.
1618  * @param *in         The array of length arity of data inputs.
1619  * @param *inputs     The array of length arity of input constraints.
1620  * @param n_outs      The number of data outputs to the node.
1621  * @param *outputs    The array of length n_outs of output constraints.
1622  * @param n_clobber   The number of clobbered registers.
1623  * @param *clobber    The array of length n_clobber of clobbered registers.
1624  * @param *asm_text   The assembler text.
1625  */
1626 FIRM_API ir_node *new_ASM(int arity, ir_node *in[], ir_asm_constraint *inputs,
1627                           int n_outs, ir_asm_constraint *outputs,
1628                           int n_clobber, ident *clobber[], ident *asm_text);
1629
1630 /*---------------------------------------------------------------------*/
1631 /* The comfortable interface.                                          */
1632 /* Supports automatic Phi node construction.                           */
1633 /* All routines of the block oriented interface except new_Block are   */
1634 /* needed also.                                                        */
1635 /*---------------------------------------------------------------------*/
1636
1637 /** Create an immature Block.
1638  *
1639  * An immature Block has an unknown number of predecessors.  Predecessors
1640  * can be added with add_immBlock_pred().  Once all predecessors are
1641  * added the block must be matured.
1642  *
1643  * Adds the block to the graph in current_ir_graph. Can be used with automatic
1644  * Phi node construction.
1645  * This constructor can only be used if the graph is in state_building.
1646  */
1647 FIRM_API ir_node *new_d_immBlock(dbg_info *db);
1648 FIRM_API ir_node *new_immBlock(void);
1649 FIRM_API ir_node *new_r_immBlock(ir_graph *irg);
1650 FIRM_API ir_node *new_rd_immBlock(dbg_info *db, ir_graph *irg);
1651
1652 /** Add a control flow edge to an immature block. */
1653 FIRM_API void add_immBlock_pred(ir_node *immblock, ir_node *jmp);
1654
1655 /** Finalize a Block node, when all control flows are known. */
1656 FIRM_API void mature_immBlock(ir_node *block);
1657
1658 /** Get the current value of a local variable.
1659  *
1660  * Use this function to obtain the last definition of the local variable
1661  * associated with pos.  Pos may not exceed the value passed as n_loc
1662  * to new_ir_graph.  This call automatically inserts Phi nodes.
1663  *
1664  * @param  pos   The position/id of the local variable.
1665  * @param *mode  The mode of the value to get.
1666  */
1667 FIRM_API ir_node *get_value(int pos, ir_mode *mode);
1668 FIRM_API ir_node *get_r_value(ir_graph *irg, int pos, ir_mode *mode);
1669
1670 /**
1671  * Try to guess the mode of a local variable.
1672  * This is done by recursively going up the control flow graph until
1673  * we find a definition for the variable. The mode of the first found
1674  * definition is returned. NULL in case no definition is found.
1675  *
1676  * @param  pos   The position/id of the local variable.
1677  */
1678 FIRM_API ir_mode *ir_guess_mode(int pos);
1679 FIRM_API ir_mode *ir_r_guess_mode(ir_graph *irg, int pos);
1680
1681 /** Remark a new definition of a variable.
1682  *
1683  * Use this function to remember a new definition of the value
1684  * associated with pos. Pos may not exceed the value passed as n_loc
1685  * to new_ir_graph.  This call is needed to automatically inserts Phi
1686  * nodes.
1687  *
1688  * @param  pos   The position/id of the local variable.
1689  * @param *value The new value written to the local variable.
1690  */
1691 FIRM_API void set_value(int pos, ir_node *value);
1692 FIRM_API void set_r_value(ir_graph *irg, int pos, ir_node *value);
1693
1694 /**
1695  * Find the value number for a node in the current block.
1696  *
1697  * @param value  the searched value
1698  *
1699  * @return the value number of the value or -1 if this value has
1700  * no value number in the current block.
1701  */
1702 FIRM_API int find_value(ir_node *value);
1703 FIRM_API int r_find_value(ir_graph *irg, ir_node *value);
1704
1705 /** Get the current memory state.
1706  *
1707  * Use this function to obtain the last definition of the memory
1708  * state.  This call automatically inserts Phi nodes for the memory
1709  * state value.
1710  */
1711 FIRM_API ir_node *get_store(void);
1712 FIRM_API ir_node *get_r_store(ir_graph *irg);
1713
1714 /** Remark a new definition of the memory state.
1715  *
1716  * Use this function to remember a new definition of the memory state.
1717  * This call is needed to automatically inserts Phi nodes.
1718  *
1719  * @param *store The new memory state.
1720  */
1721 FIRM_API void set_store(ir_node *store);
1722 FIRM_API void set_r_store(ir_graph *irg, ir_node *store);
1723
1724 /** keep this node alive even if End is not control-reachable from it
1725  *
1726  * @param ka The node to keep alive.
1727  */
1728 FIRM_API void keep_alive(ir_node *ka);
1729
1730 /* --- initialize and finalize IR construction --- */
1731
1732 /** Puts the graph into state "phase_high" */
1733 FIRM_API void irg_finalize_cons(ir_graph *irg);
1734
1735 /** Puts the program and all graphs into state phase_high.
1736  *
1737  * This also remarks, the construction of types is finished,
1738  * e.g., that no more subtypes will be added.  */
1739 FIRM_API void irp_finalize_cons(void);
1740
1741 FIRM_API void ir_set_uninitialized_local_variable_func(
1742                 uninitialized_local_variable_func_t *func);
1743
1744 #include "end.h"
1745
1746 #endif