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