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