2f4b26cf6c26dc554826adee3531b30d4892aeb4
[libfirm] / ir / ir / ircons.h
1 /* Copyright (C) 1998 - 2000 by Universitaet Karlsruhe
2 ** All rights reserved.
3 **
4 ** Authors: Martin Trapp, Christian Schaefer,
5 **          Goetz Lindenmaier
6 **
7 ** ircons.h ir node construction
8 */
9
10
11 /** !!!
12 *** Ideas for imrovement:
13 ***
14  Handle construction of exceptions more comfortable:
15  Add new constructors that pass the exception region (or better the
16  Phi for the memories, the ex. region can be found from there) as parameter,
17  constructor then adds all Proj nodes and returns the pointer
18  to the Proj node that selects the result of the arithmetic operation.
19
20  Maybe hide the exception region in a global variable, especially if
21  it is always unambiguous.
22 **/
23
24 /**
25 ***  IRCONS
26
27   This file documents all datatypes and constructors needed to
28   build a FIRM representation of a pocedure.  The constructors are
29   also implemented in this file.
30
31   The documentation also gives a short manual how to use the library.
32
33   For extensive documentation of FIRM see UKA Techreport 1999-14.
34
35   DATATYPES
36   =========
37
38   The struct ir_graph
39   -------------------
40
41     This struct contains all information about a procedure.
42     It's allocated directly to memory.
43
44     The fields of ir_graph:
45
46     *ent             The entity describing this procedure.
47
48     The beginning and end of a graph:
49
50     *start_block     This ir_node is the block that contains the unique
51                      start node of the procedure.  With it it contains
52                      the Proj's on starts results.
53                      Further all Const nodes are placed in the start block.
54     *start           This ir_node is the unique start node of the procedure.
55
56     *end_block       This ir_node is the block that contains the unique
57                      end node of the procedure.  This block contains no
58                      further nodes.
59     *end             This ir_node is the unique end node of the procedure.
60
61     The following nodes are Projs from the start node, held in ir_graph for
62     simple access:
63
64     *frame           The ir_node producing the pointer to the stack frame of
65                      the procedure as output.  This is the Proj node on the
66                      third output of the start node.  This output of the start
67                      node is tagged as pns_frame_base.  In FIRM most lokal
68                      variables are modeled as data flow edges.  Static
69                      allocated arrays can not be represented as dataflow
70                      edges. Therefore FIRM has to represent them in the stack
71                      frame.
72
73     *globals         This models a pointer to a space in the memory where
74                      _all_ global things are held.  Select from this pointer
75                      with a Sel node the pointer to a global variable /
76                      procedure / compiler known function... .
77
78     *args            The ir_node that produces the arguments of the method as
79                      it's result.  This is a Proj node on the fourth output of
80                      the start node.  This output is tagged as pns_args.
81
82     *bad             The bad node is an auxiliary node. It is needed only once,
83                      so there is this globally reachable node.
84
85     Datastructures that are private to a graph:
86
87     *obst            An obstack that contains all nodes.
88
89     *current_block   A pointer to the current block.  Any node created with
90                      one of the node constructors (new_<opcode>) are assigned
91                      to this block.  It can be set with switch_block(block).
92                      Only needed for ir construction.
93
94     params/n_loc     An int giving the number of local variables in this
95                      procedure.  This is neede for ir construction. Name will
96                      be changed.
97
98     *value_table     This hash table (pset) is used for global value numbering
99                      for optimizing use in iropt.c.
100
101     *Phi_in_stack;   a stack needed for automatic Phi construction, needed only
102                      during ir construction.
103
104
105   Three kinds of nodes
106   --------------------
107
108     There are three kinds of nodes known to the ir:  entities,
109     types, and ir_nodes
110
111     + ir_nodes are the actual nodes of the FIRM intermediate representation.
112       They represent operations on the data of the program and control flow
113       operations.
114
115     + entity ==> implemented in entity.h
116       Refers to a single entity of the compiled program, e.g. a field of a
117       class or a method.  If a method or variable can not be assigned to
118       a method or class or the like, it is a global object.
119
120     + types ==> implemented in type.h
121       With types type information is represented.  There are several type
122       nodes.
123
124   Implementation of the FIRM operations: ir_node
125   ----------------------------------------------
126
127     Ir_nodes represent operations on the data of the program and control flow
128     operations.  Examples of ir_nodes:  Add, Jmp, Cmp
129
130     FIRM is a dataflow graph.  A dataflow graph is a directed graph,
131     so that every node has incoming and outgoing edges.  A node is
132     executable if every input at it's incoming edges is available.
133     Execution of the dataflow graph is started at the Start node which
134     has no incoming edges and ends when the End node executes, even if
135     there are still executable or not executed nodes.  (Is this true,
136     or must all executable nodes be executed?)  (There are exceptions
137     to the dataflow paradigma that all inputs have to be available
138     before a node can execute: Phi, Block.  See UKA Techreport
139     1999-14.)
140
141     The implementation of FIRM differs from the view as a dataflow
142     graph.  To allow fast traversion of the graph edges are
143     implemented as C-pointers.  Inputs to nodes are not ambiguous, the
144     results can be used by several other nodes.  Each input can be
145     implemented as a single pointer to a predecessor node, outputs
146     need to be lists of pointers to successors.  Therefore a node
147     contains pointers to it's predecessor so that the implementation is a
148     dataflow graph with reversed edges.  It has to be traversed bottom
149     up.
150
151     All nodes of the ir have the same basic structure.  They are
152     distinguished by a field containing the opcode.
153
154     The fields of an ir_node:
155
156     kind             A firm_kind tag containing k_ir_node.  This is useful for
157                      dynamically checking the type of a node.
158
159     *op              This ir_op gives the opcode as a tag and a string
160                      and the number of attributes of an ir_node.  There is
161                      one statically allocated struct ir_op for each opcode.
162
163     *mode            The ir_mode of the operation represented by this firm
164                      node.  The mode of the operation is the mode of it's
165                      result.  A Firm mode is a datatype as known to the target,
166                      not a type of the source language.
167
168     visit            A flag for traversing the ir.
169
170     **in             An array with pointers to the node's predecessors.
171
172     *link            A pointer to an ir_node.  With this pointer all Phi nodes
173                      are attached to a Block, i.e., a Block points to it's
174                      first Phi node, this node points to the second Phi node
175                      in the Block and so fourth.  Used in mature_block
176                      to find all Phi nodes to be matured.  It's also used to
177                      annotate a node with a better, optimized version of it.
178
179     attr             An attr struct containing the attributes of the nodes. The
180                      attributes depend on the opcode of the node.  The number
181                      of these attributes is given in op.
182
183   The struct ir_op
184   ----------------
185                      Not yet documented. See irop.h.
186
187   The struct ir_mode
188   ------------------
189                      Not yet documented. See irmode.h.
190
191   GLOBAL VARIABLES
192   ================
193
194   current_ir_graph   Points to the current ir_graph.  All constructors for
195                      nodes add nodes to this graph.
196
197   ir_visited         An int used as flag to traverse the ir_graph.
198
199   block_visited      An int used as a flag to traverse block nodes in the
200                      graph.
201
202                      Others not yet documented.
203
204
205
206
207   CONSTRUCTOR FOR IR_GRAPH
208   ========================
209
210   ir_graph *new_ir_graph (entity *ent, int params);
211   -------------------------------------------------
212
213   This constructor generates the basic infrastructure needed to
214   represent a procedure in FIRM.
215
216   The parameters of new_ir_graph are:
217
218     *ent             A pointer to an entity representing the procedure.
219
220     params           An integer giving the number of local variables in the
221                      procedure.
222
223   It allocates an ir_graph and sets current_ir_graph to point to this
224   graph.  Further it allocates the following nodes needed for every
225   procedure:
226
227   * The start block containing a start node and Proj nodes for it's
228     five results (X, M, P, P, T).
229   * The end block containing an end node. This block is not matured
230     after executing new_ir_graph as predecessors need to be added to it.
231     (Maturing a block means fixing it's number of predecessors.)
232   * The current block, which is empty and also not matured.
233
234   Further it enters the global store into the datastructure of the start
235   block that contanis all valid values in this block (set_store()).  This
236   datastructure is used to build the Phi nodes and removed after completion
237   of the graph.
238   There is no path from end to start in the graph after calling ir_graph.
239
240
241   PROCEDURE TO CONSTRUCT AN IR GRAPH
242   ==================================
243
244   This library supplies several interfaces to construct a FIRM graph for
245   a program:
246   * A "comfortable" interface generating SSA automatically.  Automatically
247     computed predecessors of nodes need not be specified in the constructors.
248     (new_<Node> constructurs and a set of additional routines.)
249   * A less comfortable interface where all predecessors except the block
250     an operation belongs to need to be specified.  SSA must be constructed
251     by hand.  (new_<Node> constructors and switch_block()).  This interface
252     is called "block oriented".
253   * An even less comfortable interface where the block needs to be specified
254     explicitly.  This is called the "raw" interface. (new_r_<Node>
255     constructors).
256
257   To use the functionality of the comfortable interface correctly the Front
258   End needs to follow certain protocols.  This is explained in the following.
259   To build a correct IR with the other interfaces study the semantics of
260   the firm node (See tech-reprot UKA 1999-44).  For the construction of
261   types and entities see the documentation in those modules.
262
263   First the Frontend needs to decide which variables and values used in
264   a procedure can be represented by dataflow edges.  These are variables
265   that need not be saved to memory as they cause no side effects visible
266   out of the procedure.  In general these are all compiler generated
267   variables and simple local variables of the procedure as integers,
268   reals and pointers.  The frontend has to count and number these variables.
269
270   First an ir_graph needs to be constructed with new_ir_graph.  The
271   constructor gets the number of local variables.  The graph is hold in the
272   global variable irg.
273
274   Now the construction of the procedure can start.  Several basic blocks can
275   be constructed in parallel, but the code within each block needs to
276   be constructed (almost) in program order.
277
278   A global variable holds the current basic block.  All (non block) nodes
279   generated are added to this block.  The current block can be set with
280   switch_block(block).  If several blocks are constructed in parallel block
281   switches need to be performed constantly.
282
283   To generate a Block node (with the comfortable interface) it's predecessor
284   control flow nodes need not be known.  In case of cyclic control flow these
285   can not be known when the block is constructed.  With add_in_edge(block,
286   cfnode) predecessors can be added to the block.  If all predecessors are
287   added to the block mature_block(b) needs to be called.  Calling mature_block
288   early improves the efficiency of the Phi node construction algorithm.
289   But if several  blocks are constructed at once, mature_block must only
290   be called after performing all set_values and set_stores in the block!
291   (See documentation of new_immBlock constructor.)
292
293   The constructors of arithmetic nodes require that their predecessors
294   are mentioned.  Sometimes these are available in the Frontend as the
295   predecessors have just been generated by the frontend.  If they are local
296   values the predecessors can be obtained from the library with a call to
297   get_value(local_val_nr).  (local_val_nr needs to be administered by
298   the Frontend.)  A call to get_value triggers the generation of Phi nodes.
299   If an arithmetic operation produces a local value this value needs to be
300   passed to the library by set_value(node, local_val_nr).
301   In straight line code these two operations just remember and return the
302   pointer to nodes producing the value.  If the value passes block boundaries
303   Phi nodes can be inserted.
304   Similar routines exist to manage the Memory operands: set_store and
305   get_store.
306
307   Several nodes produce more than one result.  An example is the Div node.
308   Such nodes return tuples of values.  From these individual values can be
309   extracted by proj nodes.
310
311   The following example illustrates the construction of a simple basic block
312   with two predecessors stored in variables cf_pred1 and cf_pred2, containing
313   the code
314     a = a div a;
315   and finally jumping to an other block.  The variable a got the local_val_nr
316   42 by the frontend.
317
318   ir_node *this_block, *cf_pred1, *cf_pred2, *a_val, *mem, *div, *res, *cf_op;
319
320   this_block = new_immBlock();
321   add_in_edge(this_block, cf_pred1);
322   add_in_edge(this_block, cf_pred2);
323   mature_block(this_block);
324   a_val = get_value(17, mode_I);
325   mem = get_store();
326   div = new_Div(mem, a_val, a_val);
327   mem = new_Proj(div, mode_M, 0);   * for the numbers for Proj see docu *
328   res = new_Proj(div, mode_I, 2);
329   set_store(mem);
330   set_value(res, 17);
331   cf_op = new_Jmp();
332
333   For further information look at the documentation of the nodes and
334   constructors and at the paragraph COPING WITH DATA OBJECTS at the
335   end of this documentation.
336
337   The comfortable interface contains the following routines further explained
338   below:
339
340   ir_node *new_immBlock  (void);
341   ir_node *new_Start  (void);
342   ir_node *new_End    (void);
343   ir_node *new_Jmp    (void);
344   ir_node *new_Cond   (ir_node *c);
345   ir_node *new_Return (ir_node *store, int arity, ir_node **in);
346   ir_node *new_Raise  (ir_node *store, ir_node *obj);
347   ir_node *new_Const  (ir_mode *mode, tarval *con);
348   ir_node *new_SymConst (type_or_id *value, symconst_kind kind);
349   ir_node *new_simpleSel (ir_node *store, ir_node *objptr, entity *ent);
350   ir_node *new_Sel    (ir_node *store, ir_node *objptr, int arity,
351                        ir_node **in, entity *ent);
352   ir_node *new_Call   (ir_node *store, ir_node *callee, int arity,
353                        ir_node **in, type_method *type);
354   ir_node *new_Add    (ir_node *op1, ir_node *op2, ir_mode *mode);
355   ir_node *new_Sub    (ir_node *op1, ir_node *op2, ir_mode *mode);
356   ir_node *new_Minus  (ir_node *op,  ir_mode *mode);
357   ir_node *new_Mul    (ir_node *op1, ir_node *op2, ir_mode *mode);
358   ir_node *new_Quot   (ir_node *memop, ir_node *op1, ir_node *op2);
359   ir_node *new_DivMod (ir_node *memop, ir_node *op1, ir_node *op2);
360   ir_node *new_Div    (ir_node *memop, ir_node *op1, ir_node *op2);
361   ir_node *new_Mod    (ir_node *memop, ir_node *op1, ir_node *op2);
362   ir_node *new_Abs    (ir_node *op,                ir_mode *mode);
363   ir_node *new_And    (ir_node *op1, ir_node *op2, ir_mode *mode);
364   ir_node *new_Or     (ir_node *op1, ir_node *op2, ir_mode *mode);
365   ir_node *new_Eor    (ir_node *op1, ir_node *op2, ir_mode *mode);
366   ir_node *new_Not    (ir_node *op,                ir_mode *mode);
367   ir_node *new_Shl    (ir_node *op,  ir_node *k,   ir_mode *mode);
368   ir_node *new_Shr    (ir_node *op,  ir_node *k,   ir_mode *mode);
369   ir_node *new_Shrs   (ir_node *op,  ir_node *k,   ir_mode *mode);
370   ir_node *new_Rot    (ir_node *op,  ir_node *k,   ir_mode *mode);
371   ir_node *new_Cmp    (ir_node *op1, ir_node *op2);
372   ir_node *new_Conv   (ir_node *op, ir_mode *mode);
373   ir_node *new_Load   (ir_node *store, ir_node *addr);
374   ir_node *new_Store  (ir_node *store, ir_node *addr, ir_node *val);
375   ir_node *new_Alloc  (ir_node *store, ir_node *size, type *alloc_type,
376                        where_alloc where);
377   ir_node *new_Free   (ir_node *store, ir_node *ptr, ir_node *size,
378                      type *free_type);
379   ir_node *new_Proj   (ir_node *arg, ir_mode *mode, long proj);
380
381   void add_in_edge (ir_node *block, ir_node *jmp);
382   void     mature_block (ir_node *block);
383   void switch_block (ir_node *target);
384   ir_node *get_value (int pos, ir_mode *mode);
385   void set_value (int pos, ir_node *value);
386   ir_node *get_store (void);
387   void set_store (ir_node *store);
388
389
390   IR_NODES AND CONSTRUCTORS FOR IR_NODES
391   =======================================
392
393   All ir_nodes are defined by a common data structure.  They are distinguished
394   by their opcode and differ in the number of their attributes.
395
396   The constructor for the block node sets current_block to itself.
397   Const nodes are always added to the start block.
398   All other constructors add the created node to the current_block.
399   swich_block(block) allows to set the current block to block.
400
401   Watch for my inconsistent use of input and predecessor (dataflow view)
402   and `the node points to' (implementation view).
403
404   The following description of the nodes lists four properties them if these
405   are of interest:
406    - the parameters to the constructor
407    - the inputs of the Firm node
408    - the outputs of the Firm node
409    - attributes to the node
410
411   BASIC BLOCKS
412   ------------
413
414   ir_node *new_immBlock (void)
415   ----------------------------
416
417   Creates a new block.  Sets current_block to itself.  When a new block is
418   created it cannot be known how many predecessors this block will have in the
419   control flow graph. Therefore the list of inputs can not be fixed at
420   creation.  Predecessors can be added with add_in_edge (block, control flow
421   operation).  With every added predecessor the number of inputs to Phi nodes
422   also changes.
423
424   The block can be completed by mature_block(block) if all predecessors are
425   known.  If several blocks are built at once, mature_block can only be called
426   after set_value has been called for all values that are life at the end
427   of the block.  This is necessary so that Phi nodes created by mature_block
428   get the right predecessors in case of cyclic dependencies.  If all set_values
429   of this block are called after maturing it and before calling get_value
430   in some block that is control flow dependent on this block, the construction
431   is correct.
432
433   Example for faulty ir construction:  (draw the graph on a paper and you'll
434                                         get it ;-)
435
436     block_before_loop = new_block();
437     set_value(x);
438     mature_block(block_before_loop);
439     before2header = new_Jmp;
440
441     loop_header = new_block ();
442     header2body - new_Jmp();
443
444     loop_body = new_block ();
445     body2header = new_Jmp();
446
447     add_in_edge(loop_header, before2header);
448     add_in_edge(loop_header, body2header);
449     add_in_edge(loop_body, header2body);
450
451     mature_block(loop_header);
452     mature_block(loop_body);
453
454     get_value(loop_body, x);   // gets the Phi in loop_header
455     set_value(loop_header, x); // sets the value the above get_value should
456     // have returned!!!
457
458   Mature_block also fixes the number of inputs to the Phi nodes.  Mature_block
459   should be called as early as possible, as afterwards the generation of Phi
460   nodes is more efficient.
461
462   Inputs:
463     There is an input for each control flow predecessor of the block.
464     The input points to an instruction producing an output of type X.
465     Possible predecessors:  Start, Jmp, Cond, Raise or Return or any node
466     possibly causing an exception.  (Often the real predecessors are Projs.)
467   Output:
468     Mode BB (R), all nodes belonging to this block should consume this output.
469     As they are strict (except Block and Phi node) it is a necessary condition
470     that the block node executed before any other node in this block executes.
471   Attributes:
472     block.matured  Indicates whether the block is mature.
473     block.**graph_arr
474                     This attribute contains all local values valid in this
475                     block. This is needed to build the Phi nodes and removed
476                     if the graph is complete.  This field is used by the
477                     internal construction algorithm and should not be accessed
478                     from outside.
479
480
481   ir_node *new_Block (int arity, ir_node **in)
482   --------------------------------------------
483
484   Creates a new Block with the given list of predecessors.  This block
485   is mature.
486
487
488   CONTROL FLOW OPERATIONS
489   -----------------------
490
491   In each block there must be exactly one of the control flow
492   operations Start, End, Jmp, Cond, Return or Raise.  The output of a
493   control flow operation points to the block to be executed next.
494
495   ir_node *new_Start (void)
496   -------------------------
497
498   Creates a start node.  Not actually needed public.  There is only one such
499   node in each procedure which is automatically created by new_ir_graph.
500
501   Inputs:
502     No inputs except the block it belogns to.
503   Output:
504     A tuple of 4 (5, 6) distinct values. These are labeled by the following
505     projection numbers (pns_number):
506     * pns_initial_exec
507                      mode X, points to the first block to be executed.
508     * pns_global_store
509                      mode M, the global store
510     * pns_frame_base mode P, a pointer to the base of the procedures
511                              stack frame.
512     * pns_globals    mode P, a pointer to the part of the memory containing
513                              _all_ global things.
514     * pns_args       mode T, a tuple containing all arguments of the procedure.
515
516
517   ir_node *new_End (void)
518   -----------------------
519
520   Creates an end node.  Not actually needed public.  There is only one such
521   node in each procedure which is automatically created by new_ir_graph.
522
523   Inputs:
524     No inputs except the block it belongs to.
525   Output:
526     No output.
527
528   ir_node *new_Jmp (void)
529   -----------------------
530
531   Creates a Jmp node.
532
533   Inputs:
534     The block the node belongs to
535   Output:
536     Control flow to the next block.
537
538   ir_node *new_Cond (ir_node *c)
539   ------------------------------
540
541   Creates a Cond node.  There are two versions of this node.
542
543   The Boolean Cond:
544   Input:
545     A value of mode b.
546   Output:
547     A tuple of two control flows.  The first is taken if the input is
548     false, the second if it is true.
549
550   The Switch Cond:
551   Input:
552     A value of mode I_u. (i)
553   Output:
554     A tuple of n control flows.  If the Cond's input is i, control
555     flow will procede along output i. If the input is >= n control
556     flow proceeds along output n.
557
558   ir_node *new_Return (in_node *store, int arity, ir_node **in)
559   -------------------------------------------------------------
560
561   The return node has as inputs the results of the procedure.  It
562   passes the control flow to the end_block.
563
564   Inputs:
565     The memory state.
566     All results.
567   Output
568     Control flow to the end block.
569
570   ir_node *new_Raise (ir_node *store, ir_node *obj)
571   -------------------------------------------------
572
573   Raises an exception.  Unconditional change of control flow.  Writes
574   an explicit Except variable to memory to pass it to the exception
575   handler.  See TechReport 1999-14, chapter Exceptions.
576
577   Inputs:
578     The memory state.
579     A pointer to the Except variable.
580   Output:
581     A tuple of control flow and the changed memory state.  The control flow
582     points to the exception handler if it is definied in this procedure,
583     else it points to the end_block.
584
585
586   CONSTANTS
587   ---------
588
589   ir_node *new_Const (ir_mode *mode, tarval *con)
590   -----------------------------------------------
591
592   Creates a constant in the constant table and adds a Const node
593   returning this value to the start block.
594
595   Parameters:
596     *mode            The mode of the constant.
597     *con             Points to an entry in the constant table.
598                      This pointer is added to the attributes of
599                      the node (self->attr.con)
600   Inputs:
601     No inputs except the block it belogns to.
602   Output:
603     The constant value.
604   Attribute:
605     attr.con   A tarval* pointer to the proper entry in the constant
606                table.
607
608   ir_node *new_SymConst (type *type, symconst_kind kind)
609   ------------------------------------------------------------
610
611   There are three kinds of symbolic constants:
612     type_tag  The symbolic constant represents a type tag.
613     size      The symbolic constant represents the size of a class.
614     link_info Information for the linker, e.g. the name of a global
615               variable.
616
617   Parameters
618     kind       The kind of the symbolic constant: type_tag, size or link_info.
619     *type      Points to the type the tag stands for or to the type
620                whose size is represented by the constant.
621
622   Inputs:
623     No inputs except the block it belogns to.
624   Output:
625     An unsigned integer (I_u) or a pointer (P).
626
627   Attributes:
628     attr.i.num       The symconst_kind, i.e. one of
629                       - type_tag
630                       - size
631                       - linkage_ptr_info
632       If the attr.i.num is type_tag or size, the node contains an attribute
633     attr.i.*type     A pointer to a type_class.
634       if it is linkage_ptr_info it contains
635     attr.i.*ptrinfo  A ident holding information for the linker.
636
637   THE SELECT NODE
638   ---------------
639
640   ir_node *new_simpleSel (ir_node *store, ir_node *frame, entity *sel)
641   --------------------------------------------------------------------
642
643
644   Selects an entity from a compound type. This entity can be a field or
645   a method.
646
647   Parameters:
648     *store     The memory in which the object the entity should be selected
649                from is allocated.
650     *frame     The pointer to the object.
651     *sel       The entity to select.
652
653   Inputs:
654     The memory containing the object.
655     A pointer to the object.
656     An unsigned integer.
657   Output:
658     A pointer to the selected entity.
659   Attributes:
660     attr.sel   Pointer to the entity
661
662
663   ir_node *new_Sel (ir_node *store, ir_node *frame, int arity, ir_node **in,
664   --------------------------------------------------------------------------
665                     entity *sel)
666                     ------------
667
668   Selects a field from an array type.  The entity has as owner the array, as
669   type the arrays element type.  The indexes to access an array element are
670   given also.
671
672   Parameters:
673     *store     The memory in which the object the entity should be selected from
674                is allocated.
675     *frame     The pointer to the object.
676     *arity     number of array indexes.
677     *in        array with index inputs to the node.
678     *sel       The entity to select.
679
680   Inputs:
681     The memory containing the object.
682     A pointer to the object.
683     As much unsigned integer as there are array expressions.
684   Output:
685     A pointer to the selected entity.
686   Attributes:
687     attr.sel   Pointer to the entity
688
689   The constructors new_Sel and new_simpleSel generate the same ir nodes.
690   simpleSel just sets the arity of the index inputs to zero.
691
692
693   ARITHMETIC OPERATIONS
694   ---------------------
695
696   ir_node *new_Call (ir_node *store, ir_node *callee, int arity, ir_node **in,
697   ----------------------------------------------------------------------------
698                      type_method *type)
699                      ------------------
700
701   Creates a procedure call.
702
703   Parameters
704     *store           The actual store.
705     *callee          A pointer to the called procedure.
706     arity            The number of procedure parameters.
707     **in             An array with the pointers to the parameters.
708                      The constructor copies this array.
709     *type            Type information of the procedure called.
710
711   Inputs:
712     The store, the callee and the parameters.
713   Output:
714     A tuple containing the eventually changed store and the procedure
715     results.
716   Attributes:
717     attr.call        Contains the type information for the procedure.
718
719   ir_node *new_Add (ir_node *op1, ir_node *op2, ir_mode *mode)
720   ------------------------------------------------------------
721
722   Trivial.
723
724   ir_node *new_Sub (ir_node *op1, ir_node *op2, ir_mode *mode)
725   ------------------------------------------------------------
726
727   Trivial.
728
729   ir_node *new_Minus (ir_node *op, ir_mode *mode)
730   -----------------------------------------------
731
732   This constructor is for unary Minus operations on floating point
733   values.  Such a Minus can trap if it is implemented as a Sub from
734   zero due to rounding errors.
735
736   ir_node *new_Mul (ir_node *op1, ir_node *op2, ir_mode *mode)
737   ------------------------------------------------------------
738
739   Trivial.
740
741   ir_node *new_Quot (ir_node *memop, ir_node *op1, ir_node *op2)
742   --------------------------------------------------------------
743
744   Quot performs exact division of floating point numbers.  It's mode
745   is Tuple, the mode of the result must be annotated to the Proj
746   that extracts the result of the arithmetic operations.
747
748   Inputs:
749     The store needed to model exceptions and the two operands.
750   Output:
751     A tuple contaning a memory and a execution for modeling exceptions
752     and the result of the arithmetic operation.
753
754   ir_node *new_DivMod (ir_node *memop, ir_node *op1, ir_node *op2)
755   ----------------------------------------------------------------
756
757   Performs Div and Mod on interger values.
758
759   Output:
760     A tuple contaning a memory and a execution for modeling exceptions
761     and the two result of the arithmetic operations.
762
763   ir_node *new_Div (ir_node *memop, ir_node *op1, ir_node *op2)
764   -------------------------------------------------------------
765
766   Trivial.
767
768   ir_node *new_Mod (ir_node *memop, ir_node *op1, ir_node *op2)
769   -------------------------------------------------------------
770
771   Trivial.
772
773   ir_node *new_Abs (ir_node *op, ir_mode *mode)
774   ---------------------------------------------
775
776   Trivial.
777
778   ir_node *new_And (ir_node *op1, ir_node *op2, ir_mode *mode)
779   ------------------------------------------------------------
780
781   Trivial.
782
783   ir_node *new_Or (ir_node *op1, ir_node *op2, ir_mode *mode)
784   -----------------------------------------------------------
785
786   Trivial.
787
788   ir_node *new_Eor (ir_node *op1, ir_node *op2, ir_mode *mode)
789   ------------------------------------------------------------
790
791   Trivial.
792
793   ir_node *new_Not (ir_node *op, ir_mode *mode)
794   ---------------------------------------------
795
796   This node constructs a constant where all bits are set to one
797   and a Eor of this constant and the operator.  This simulates a
798   Not operation.
799
800   ir_node *new_Shl (ir_node *op, ir_node *k, ir_mode *mode)
801   ---------------------------------------------------------
802
803   Trivial.
804
805   ir_node *new_Shr (ir_node *op, ir_node *k, ir_mode *mode)
806   ---------------------------------------------------------
807
808   Logic shift right, i.e., zero extended.
809
810
811   ir_node *new_Shrs (ir_node *op, ir_node *k, ir_mode *mode)
812   ----------------------------------------------------------
813
814   Arithmetic shift right, i.e., sign extended.
815
816   ir_node *new_Rot (ir_node *op, ir_node *k, ir_mode *mode)
817   ---------------------------------------------------------
818
819   Rotates the operand to the (right??) by k bits.
820
821   ir_node *new_Conv (ir_node *op, ir_mode *mode)
822   ---------------------------------------------
823
824   Mode conversion.  For allowed conversions see UKA Tech Report
825   1999-14.
826
827   ir_node *new_Cmp (ir_node *op1, ir_node *op2)
828   ---------------------------------------------
829
830   Input:
831     The two values to be compared.
832   Output:
833     A 16-tuple containing the results of the 16 different comparisons.
834     The following is a list giving the comparisons and a projection
835     number (pnc_number) to use in Proj nodes to extract the proper result.
836       False     false
837       Eq        equal
838       Lt        less
839       Le        less or equal
840       Gt        greater
841       Ge        greater of equal
842       Lg        less or greater
843       Leg       less, equal or greater = ordered
844       Uo        unordered
845       Ue        unordered or equal
846       Ul        unordered or less
847       Ule       unordered, less or equal
848       Ug        unordered or greater
849       Uge       unordered, greater or equal
850       Ne        unordered, less or greater = not equal
851       True      true
852
853
854
855   THE PHI NODE
856   ------------
857
858   In general, Phi nodes are automaitcally inserted.  In some cases, if
859   all predecessors of a block are known, an explicit Phi node constructor
860   is needed.  E.g., to construct a FIRM graph for a statement as
861     a = (b==c) ? 2 : 5;
862
863   ir_node *new_Phi (int arity, ir_node **in, ir_mode *mode)
864   ---------------------------------------------------------
865
866   Creates a Phi node. The in's order has to correspond to the order
867   of in's of current_block.  This is not checked by the library!
868
869   Parameter
870     arity            number of predecessors
871     **in             array with predecessors
872     *mode            The mode of it's inputs and output.
873   Inputs:
874     A Phi node has as many inputs as the block it belongs to.
875     Each input points to a definition of the same value on a
876     different path in the control flow.
877   Output
878     The definition valid in this block.
879
880
881   OPERATIONS TO MANAGE MEMORY EXPLICITLY
882   --------------------------------------
883
884   ir_node *new_Load (ir_node *store, ir_node *addr)
885   ----------------------------------------------------------------
886
887   The Load operation reads a value from memory.
888
889   Parameters:
890   *store        The current memory.
891   *addr         A pointer to the variable to be read in this memory.
892   *mode         The mode of the loaded value.
893
894   Inputs:
895     The memory and a pointer to a variable in this memory.
896   Output:
897     A tuple of the memory, a control flow to be taken in case of
898     an exception and the loaded value.
899
900   ir_node *new_Store (ir_node *store, ir_node *addr, ir_node *val)
901   ----------------------------------------------------------------
902
903   The Store operation writes a value to a variable in memory.
904
905   Inputs:
906     The memory, a pointer to a variable in this memory and the value
907     to write to this variable.
908   Output:
909     A tuple of the changed memory and a control flow to be taken in
910     case of an exception.
911
912   ir_node *new_Alloc (ir_node *store, ir_node *size, type *alloc_type,
913   --------------------------------------------------------------------
914                       where_alloc where)
915                       ------------------
916
917   The Alloc node allocates a new variable.  It can be specified whether the
918   variable should be allocated to the stack or to the heap.
919
920   Parameters:
921     *store       The memory which shall contain the new variable.
922     **    *size        The number of bytes to allocate. Old. **
923     *size        We decided that the size easily can be derived from the type.
924                  This field is for allocating arrays, i.e., it gives the multiple
925                  of the size of alloc_type to allocate memory for.
926     *alloc_type  The type of the allocated variable.
927     where        Where to allocate the variable, either heap_alloc or stack_alloc.
928
929   Inputs:
930     A memory and an unsigned integer.
931   Output:
932     A tuple of the changed memory, a control flow to be taken in
933     case of an exception and the pointer to the new variable.
934   Attributes:
935     a.where          Indicates where the variable is allocated.
936     a.*type          A pointer to the class the allocated data object
937                      belongs to.
938
939   ir_node *new_Free (ir_node *store, ir_node *ptr, type *free_type)
940   ------------------------------------------------------------------
941
942   The Free node frees memory of the given variable.
943
944   Parameters:
945     *store       The memory which shall contain the new variable.
946     *ptr         The pointer to the object to free.
947     *size        The number of objects of type free_type to free in a sequence.
948     *free_type   The type of the freed variable.
949
950   Inputs:
951     A memory, a pointer and an unsigned integer.
952   Output:
953     The changed memory.
954   Attributes:
955     f.*type          A pointer to the type information of the freed data object.
956
957   Not Implemented!
958
959   ir_node *new_Sync (int arity, ir_node **in)
960   -------------------------------------------
961
962   The Sync operation unifies several partial memory blocks.  These blocks
963   have to be pairwise disjunct or the values in common locations have to
964   be identical.  This operation allows to specify all operations that eventually
965   need several partial memory blocks as input with a single entrance by
966   unifying the memories with a preceding Sync operation.
967
968   Parameters
969     arity    The number of memories to syncronize.
970     **in     An array of pointers to nodes that produce an output of
971              type memory.
972   Inputs
973     Several memories.
974   Output
975     The unified memory.
976
977
978   SPECIAL OPERATIONS
979   ------------------
980
981   ir_node *new_Bad (void)
982   -----------------------
983
984   Returns the unique Bad node current_ir_graph->bad.
985   This node is used to express results of dead code elimination.
986
987   ir_node *new_Proj (ir_node *arg, ir_mode *mode, long proj)
988   ----------------------------------------------------------
989
990   Selects one entry of a tuple.  This is a hidden `fat edge'.
991
992   Parameters
993     *arg      A node producing a tuple.
994     *mode     The mode of the value to project.
995     proj      The position of the value in the tuple.
996   Input:
997     The tuple.
998   Output:
999     The value.
1000
1001   ir_node *new_Tuple (int arity, ir_node **in)
1002   --------------------------------------------
1003
1004   Builds a Tuple from single values.  This is needed to implement
1005   optimizations that remove a node that produced a tuple.  The node can be
1006   replaced by the Tuple operation so that the following Proj nodes have not to
1007   be changed.  (They are hard to find due to the implementation with pointers
1008   in only one direction.)  The Tuple node is smaller than any other
1009   node, so that a node can be changed into a Tuple by just changing it's
1010   opcode and giving it a new in array.
1011
1012   Parameters
1013     arity    The number of tuple elements.
1014     **in     An array containing pointers to the nodes producing the
1015              tuple elements.
1016
1017   ir_node *new_Id (ir_node *val, ir_mode *mode)
1018   ---------------------------------------------
1019
1020   The single output of the Id operation is it's input.  Also needed
1021   for optimizations.
1022
1023
1024   COPING WITH DATA OBJECTS
1025   ========================
1026
1027   Two kinds of data objects have to be distinguished for generating
1028   FIRM.  First there are local variables other than arrays that are
1029   known to be alias free.  Second there are all other data objects.
1030   For the first a common SSA representation is built, the second
1031   are modeled by saving them to memory.  The memory is treated as
1032   a single local variable, the alias problem is hidden in the
1033   content of this variable.
1034
1035   All values known in a Block are listed in the block's attribute,
1036   block.**graph_arr which is used to automatically insert Phi nodes.
1037   The following two funcions can be used to add a newly computed value
1038   to the array, or to get the producer of a value, i.e., the current
1039   live value.
1040
1041   inline void set_value (int pos, ir_node *value)
1042   -----------------------------------------------
1043
1044   Has to be called for every assignment to a local variable.  It
1045   adds the value to the array of used values at position pos.  Pos
1046   has to be a unique identifier for an entry in the procedure's
1047   definition table.  It can be used to access the value again.
1048
1049   ir_node *get_value (int pos, ir_mode *mode)
1050   -------------------------------------------
1051
1052   Returns the node defining the value referred to by pos. If the
1053   value is not defined in this block a Phi node is generated and
1054   all definitions reaching this Phi node are collected.  It can
1055   happen that the algorithm allocates an unnecessary Phi node,
1056   e.g. if there is only one definition of this value, but this
1057   definition reaches the currend block on several different
1058   paths.  This Phi node will be eliminated if optimizations are
1059   turned on right after it's creation.
1060
1061
1062   There are two special routines for the global store:
1063
1064   inline void set_store (ir_node *store)
1065   --------------------------------------
1066
1067   Adds the store to the array of known values at a reserved
1068   position.
1069
1070   inline ir_node *get_store (void)
1071   --------------------------------
1072
1073   Returns the node defining the actual store.
1074
1075 **/
1076
1077
1078 # ifndef _IRCONS_H_
1079 # define _IRCONS_H_
1080
1081 # include "irgraph.h"
1082 # include "irnode.h"
1083 # include "irmode.h"
1084 # include "entity.h"
1085 # include "tv.h"
1086 # include "type.h"
1087 # include "pdeq.h"
1088
1089 #if USE_EXPICIT_PHI_IN_STACK
1090 /* A stack needed for the automatic Phi node construction in constructor
1091    Phi_in. */
1092 typedef struct Phi_in_stack Phi_in_stack;
1093 #endif
1094
1095 /***************************************************************************/
1096 /* The raw interface                                                       */
1097
1098 ir_node *new_r_Block  (ir_graph *irg,  int arity, ir_node **in);
1099 ir_node *new_r_Start  (ir_graph *irg, ir_node *block);
1100 ir_node *new_r_End    (ir_graph *irg, ir_node *block);
1101 ir_node *new_r_Jmp    (ir_graph *irg, ir_node *block);
1102 ir_node *new_r_Cond   (ir_graph *irg, ir_node *block, ir_node *c);
1103 ir_node *new_r_Return (ir_graph *irg, ir_node *block,
1104                        ir_node *store, int arity, ir_node **in);
1105 ir_node *new_r_Raise  (ir_graph *irg, ir_node *block,
1106                        ir_node *store, ir_node *obj);
1107 ir_node *new_r_Const  (ir_graph *irg, ir_node *block,
1108                        ir_mode *mode, tarval *con);
1109 ir_node *new_r_SymConst (ir_graph *irg, ir_node *block,
1110                        type_or_id *value, symconst_kind symkind);
1111 ir_node *new_r_Sel    (ir_graph *irg, ir_node *block, ir_node *store,
1112                        ir_node *objptr, int n_index, ir_node **index,
1113                        entity *ent);
1114 ir_node *new_r_Call   (ir_graph *irg, ir_node *block, ir_node *store,
1115                        ir_node *callee, int arity, ir_node **in,
1116                        type_method *type);
1117 ir_node *new_r_Add    (ir_graph *irg, ir_node *block,
1118                        ir_node *op1, ir_node *op2, ir_mode *mode);
1119 ir_node *new_r_Sub    (ir_graph *irg, ir_node *block,
1120                        ir_node *op1, ir_node *op2, ir_mode *mode);
1121 ir_node *new_r_Minus  (ir_graph *irg, ir_node *block,
1122                        ir_node *op,  ir_mode *mode);
1123 ir_node *new_r_Mul    (ir_graph *irg, ir_node *block,
1124                        ir_node *op1, ir_node *op2, ir_mode *mode);
1125 ir_node *new_r_Quot   (ir_graph *irg, ir_node *block,
1126                        ir_node *memop, ir_node *op1, ir_node *op2);
1127 ir_node *new_r_DivMod (ir_graph *irg, ir_node *block,
1128                        ir_node *memop, ir_node *op1, ir_node *op2);
1129 ir_node *new_r_Div    (ir_graph *irg, ir_node *block,
1130                        ir_node *memop, ir_node *op1, ir_node *op2);
1131 ir_node *new_r_Mod    (ir_graph *irg, ir_node *block,
1132                        ir_node *memop, ir_node *op1, ir_node *op2);
1133 ir_node *new_r_Abs    (ir_graph *irg, ir_node *block,
1134                        ir_node *op, ir_mode *mode);
1135 ir_node *new_r_And    (ir_graph *irg, ir_node *block,
1136                        ir_node *op1, ir_node *op2, ir_mode *mode);
1137 ir_node *new_r_Or     (ir_graph *irg, ir_node *block,
1138                        ir_node *op1, ir_node *op2, ir_mode *mode);
1139 ir_node *new_r_Eor    (ir_graph *irg, ir_node *block,
1140                        ir_node *op1, ir_node *op2, ir_mode *mode);
1141 ir_node *new_r_Not    (ir_graph *irg, ir_node *block,
1142                        ir_node *op, ir_mode *mode);
1143 ir_node *new_r_Cmp    (ir_graph *irg, ir_node *block,
1144                        ir_node *op1, ir_node *op2);
1145 ir_node *new_r_Shl    (ir_graph *irg, ir_node *block,
1146                        ir_node *op, ir_node *k, ir_mode *mode);
1147 ir_node *new_r_Shr    (ir_graph *irg, ir_node *block,
1148                        ir_node *op, ir_node *k, ir_mode *mode);
1149 ir_node *new_r_Shrs   (ir_graph *irg, ir_node *block,
1150                        ir_node *op, ir_node *k, ir_mode *mode);
1151 ir_node *new_r_Rot    (ir_graph *irg, ir_node *block,
1152                        ir_node *op, ir_node *k, ir_mode *mode);
1153 ir_node *new_r_Conv   (ir_graph *irg, ir_node *block,
1154                        ir_node *op, ir_mode *mode);
1155 ir_node *new_r_Phi    (ir_graph *irg, ir_node *block, int arity,
1156                        ir_node **in, ir_mode *mode);
1157 ir_node *new_r_Load   (ir_graph *irg, ir_node *block,
1158                        ir_node *store, ir_node *adr);
1159 ir_node *new_r_Store  (ir_graph *irg, ir_node *block,
1160                        ir_node *store, ir_node *adr, ir_node *val);
1161 ir_node *new_r_Alloc  (ir_graph *irg, ir_node *block, ir_node *store,
1162                        ir_node *size, type *alloc_type, where_alloc where);
1163 ir_node *new_r_Free   (ir_graph *irg, ir_node *block, ir_node *store,
1164                        ir_node *ptr, ir_node *size, type *free_type);
1165 ir_node *new_r_Sync   (ir_graph *irg, ir_node *block, int arity, ir_node **in);
1166 ir_node *new_r_Proj   (ir_graph *irg, ir_node *block, ir_node *arg,
1167                        ir_mode *mode, long proj);
1168 ir_node *new_r_Tuple  (ir_graph *irg, ir_node *block,
1169                        int arity, ir_node **in);
1170 ir_node *new_r_Id     (ir_graph *irg, ir_node *block,
1171                        ir_node *val, ir_mode *mode);
1172 ir_node *new_r_Bad    (ir_node *block);
1173
1174
1175 /*************************************************************************/
1176 /* The block oriented interface                                          */
1177
1178 /* Sets the current block in which the following constructors place the
1179    nodes they construct. */
1180 void switch_block (ir_node *target);
1181
1182 /* Chris: please rename the Block constructor:
1183    new_Block to new_immBlock
1184    and add a new one so dass das dann so aussieht:
1185    passe die Beispeilprogramme an! */
1186 #if 0
1187 ir_node *new_Block(int arity, ir_node **in);     /* creates mature Block */
1188 #else
1189 ir_node *new_Block  (void);
1190 #endif
1191 ir_node *new_Start  (void);
1192 ir_node *new_End    (void);
1193 ir_node *new_Jmp    (void);
1194 ir_node *new_Cond   (ir_node *c);
1195 ir_node *new_Return (ir_node *store, int arity, ir_node **in);
1196 ir_node *new_Raise  (ir_node *store, ir_node *obj);
1197 ir_node *new_Const  (ir_mode *mode, tarval *con);
1198 ir_node *new_SymConst (type_or_id *value, symconst_kind kind);
1199 ir_node *new_simpleSel (ir_node *store, ir_node *objptr, entity *ent);
1200 ir_node *new_Sel    (ir_node *store, ir_node *objptr, int arity, ir_node **in,
1201                      entity *ent);
1202 ir_node *new_Call   (ir_node *store, ir_node *callee, int arity, ir_node **in,
1203                      type_method *type);
1204 ir_node *new_Add    (ir_node *op1, ir_node *op2, ir_mode *mode);
1205 ir_node *new_Sub    (ir_node *op1, ir_node *op2, ir_mode *mode);
1206 ir_node *new_Minus  (ir_node *op,  ir_mode *mode);
1207 ir_node *new_Mul    (ir_node *op1, ir_node *op2, ir_mode *mode);
1208 ir_node *new_Quot   (ir_node *memop, ir_node *op1, ir_node *op2);
1209 ir_node *new_DivMod (ir_node *memop, ir_node *op1, ir_node *op2);
1210 ir_node *new_Div    (ir_node *memop, ir_node *op1, ir_node *op2);
1211 ir_node *new_Mod    (ir_node *memop, ir_node *op1, ir_node *op2);
1212 ir_node *new_Abs    (ir_node *op,                ir_mode *mode);
1213 ir_node *new_And    (ir_node *op1, ir_node *op2, ir_mode *mode);
1214 ir_node *new_Or     (ir_node *op1, ir_node *op2, ir_mode *mode);
1215 ir_node *new_Eor    (ir_node *op1, ir_node *op2, ir_mode *mode);
1216 ir_node *new_Not    (ir_node *op,                ir_mode *mode);
1217 ir_node *new_Shl    (ir_node *op,  ir_node *k,   ir_mode *mode);
1218 ir_node *new_Shr    (ir_node *op,  ir_node *k,   ir_mode *mode);
1219 ir_node *new_Shrs   (ir_node *op,  ir_node *k,   ir_mode *mode);
1220 ir_node *new_Rot    (ir_node *op,  ir_node *k,   ir_mode *mode);
1221 ir_node *new_Cmp    (ir_node *op1, ir_node *op2);
1222 ir_node *new_Conv   (ir_node *op, ir_mode *mode);
1223 ir_node *new_Phi    (int arity, ir_node **in, ir_mode *mode);
1224 ir_node *new_Load   (ir_node *store, ir_node *addr);
1225 ir_node *new_Store  (ir_node *store, ir_node *addr, ir_node *val);
1226 ir_node *new_Alloc  (ir_node *store, ir_node *size, type *alloc_type,
1227                      where_alloc where);
1228 ir_node *new_Free   (ir_node *store, ir_node *ptr, ir_node *size,
1229                      type *free_type);
1230 ir_node *new_Sync   (int arity, ir_node **in);
1231 ir_node *new_Proj   (ir_node *arg, ir_mode *mode, long proj);
1232 ir_node *new_Tuple  (int arity, ir_node **in);
1233 ir_node *new_Id     (ir_node *val, ir_mode *mode);
1234 ir_node *new_Bad    (void);
1235
1236 /***********************************************************************/
1237 /* The comfortable interface.                                          */
1238 /* Supports automatic Phi node construction.                           */
1239 /* All routines of the block oriented interface except new_Block are   */
1240 /* needed also.                                                        */
1241
1242 /** Block construction **/
1243 /* immature Block without predecessors */
1244 ir_node *new_immBlock (void);
1245
1246 /* Add a control flow edge to an immature block. */
1247 void add_in_edge (ir_node *immblock, ir_node *jmp);
1248
1249 /* fixes the number of predecessors of a block. */
1250 void     mature_block (ir_node *block);
1251
1252 /** Parameter administration **/
1253 /* Read a value from the array with the local variables.  Use this
1254    function to obtain the last definition of the value associated with
1255    pos. */
1256 ir_node *get_value (int pos, ir_mode *mode);
1257
1258 /* Write a value in the array with the local variables. Use this function
1259    to remember a new definition of the value associated with pos. */
1260 void set_value (int pos, ir_node *value);
1261
1262 /* Read a store.
1263    Use this function to get the most recent version of the store (type M).
1264    Internally it does the same as get_value. */
1265 ir_node *get_store (void);
1266
1267 /* Write a store. */
1268 void set_store (ir_node *store);
1269
1270
1271 /* This function is for internal use only.  It is visible as it is needed
1272    in irgraph.c to create the stack that is needed for automatic Phi
1273    construction. */
1274 #if USE_EXPICIT_PHI_IN_STACK
1275 Phi_in_stack *new_Phi_in_stack();
1276 #endif
1277
1278 /**************************************************************************/
1279 /* initialize ir construction                                             */
1280 void init_cons (void);
1281
1282
1283 # endif /* _IRCONS_H_ */