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