1--  DO NOT MODIFY - this file was generated from:
2--  ortho_nodes.common.ads and ortho_llvm.private.ads
3--
4--  LLVM back-end for ortho.
5--  Copyright (C) 2014 Tristan Gingold
6--
7--  This program is free software: you can redistribute it and/or modify
8--  it under the terms of the GNU General Public License as published by
9--  the Free Software Foundation, either version 2 of the License, or
10--  (at your option) any later version.
11--
12--  This program is distributed in the hope that it will be useful,
13--  but WITHOUT ANY WARRANTY; without even the implied warranty of
14--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15--  GNU General Public License for more details.
16--
17--  You should have received a copy of the GNU General Public License
18--  along with this program.  If not, see <gnu.org/licenses>.
19
20with Interfaces; use Interfaces;
21with Interfaces.C; use Interfaces.C;
22with Ortho_Ident; use Ortho_Ident;
23with LLVM.Core; use LLVM.Core;
24with LLVM.TargetMachine;
25with LLVM.Target;
26
27--  Interface to create nodes.
28package Ortho_LLVM is
29   procedure Init;
30   procedure Finish_Debug;
31
32   --  LLVM specific: the module.
33   Module : ModuleRef;
34
35   --  Descriptor for the layout.
36   Target_Data : LLVM.Target.TargetDataRef;
37
38   Target_Machine : LLVM.TargetMachine.TargetMachineRef;
39
40   --  Optimization level
41   Optimization : LLVM.TargetMachine.CodeGenOptLevel :=
42     LLVM.TargetMachine.CodeGenLevelDefault;
43
44   --  Set by -g to generate full debug info.
45   Flag_Debug : Boolean := False;
46
47   --  Set by -g or -glines to generate line debug info.
48   Flag_Debug_Line : Boolean := False;
49
50--  Start of common part
51
52   type O_Enode is private;
53   type O_Cnode is private;
54   type O_Lnode is private;
55   type O_Tnode is private;
56   type O_Snode is private;
57   type O_Dnode is private;
58   type O_Gnode is private;
59   type O_Fnode is private;
60
61   O_Cnode_Null : constant O_Cnode;
62   O_Dnode_Null : constant O_Dnode;
63   O_Gnode_Null : constant O_Gnode;
64   O_Enode_Null : constant O_Enode;
65   O_Fnode_Null : constant O_Fnode;
66   O_Lnode_Null : constant O_Lnode;
67   O_Snode_Null : constant O_Snode;
68   O_Tnode_Null : constant O_Tnode;
69
70   --  True if the code generated supports nested subprograms.
71   Has_Nested_Subprograms : constant Boolean;
72
73   ------------------------
74   --  Type definitions  --
75   ------------------------
76
77   type O_Element_List is limited private;
78
79   --  Build a record type.
80   procedure Start_Record_Type (Elements : out O_Element_List);
81   --  Add a field in the record; not constrained array are prohibited, since
82   --  its size is unlimited.
83   procedure New_Record_Field
84     (Elements : in out O_Element_List;
85      El : out O_Fnode;
86      Ident : O_Ident; Etype : O_Tnode);
87   --  Finish the record type.
88   procedure Finish_Record_Type
89     (Elements : in out O_Element_List; Res : out O_Tnode);
90
91   -- Build an uncomplete record type:
92   -- First call NEW_UNCOMPLETE_RECORD_TYPE, which returns a record type.
93   -- This type can be declared or used to define access types on it.
94   -- Then, complete (if necessary) the record type, by calling
95   -- START_UNCOMPLETE_RECORD_TYPE, NEW_RECORD_FIELD and FINISH_RECORD_TYPE.
96   procedure New_Uncomplete_Record_Type (Res : out O_Tnode);
97   procedure Start_Uncomplete_Record_Type (Res : O_Tnode;
98                                           Elements : out O_Element_List);
99
100   --  Build an union type.
101   procedure Start_Union_Type (Elements : out O_Element_List);
102   procedure New_Union_Field
103     (Elements : in out O_Element_List;
104      El : out O_Fnode;
105      Ident : O_Ident;
106      Etype : O_Tnode);
107   procedure Finish_Union_Type
108     (Elements : in out O_Element_List; Res : out O_Tnode);
109
110   --  Build an access type.
111   --  DTYPE may be O_tnode_null in order to build an incomplete access type.
112   --  It is completed with finish_access_type.
113   function New_Access_Type (Dtype : O_Tnode) return O_Tnode;
114   procedure Finish_Access_Type (Atype : O_Tnode; Dtype : O_Tnode);
115
116   --  Build an array type.
117   --  The array is not constrained and unidimensional.
118   function New_Array_Type (El_Type : O_Tnode; Index_Type : O_Tnode)
119     return O_Tnode;
120
121   --  Build a constrained array type.
122   function New_Constrained_Array_Type (Atype : O_Tnode; Length : O_Cnode)
123     return O_Tnode;
124
125   --  Build a scalar type; size may be 8, 16, 32 or 64.
126   function New_Unsigned_Type (Size : Natural) return O_Tnode;
127   function New_Signed_Type (Size : Natural) return O_Tnode;
128
129   --  Build a float type.
130   function New_Float_Type return O_Tnode;
131
132   --  Build a boolean type.
133   procedure New_Boolean_Type (Res : out O_Tnode;
134                               False_Id : O_Ident;
135                               False_E : out O_Cnode;
136                               True_Id : O_Ident;
137                               True_E : out O_Cnode);
138
139   --  Create an enumeration
140   type O_Enum_List is limited private;
141
142   --  Elements are declared in order, the first is ordered from 0.
143   procedure Start_Enum_Type (List : out O_Enum_List; Size : Natural);
144   procedure New_Enum_Literal (List : in out O_Enum_List;
145                               Ident : O_Ident; Res : out O_Cnode);
146   procedure Finish_Enum_Type (List : in out O_Enum_List; Res : out O_Tnode);
147
148   ----------------
149   --  Literals  --
150   ----------------
151
152   --  Create a literal from an integer.
153   function New_Signed_Literal (Ltype : O_Tnode; Value : Integer_64)
154     return O_Cnode;
155   function New_Unsigned_Literal (Ltype : O_Tnode; Value : Unsigned_64)
156     return O_Cnode;
157
158   function New_Float_Literal (Ltype : O_Tnode; Value : IEEE_Float_64)
159     return O_Cnode;
160
161   --  Create a null access literal.
162   function New_Null_Access (Ltype : O_Tnode) return O_Cnode;
163
164   --  Create a literal with default (null) values.  Can only be used to
165   --  define the initial value of a static decalaration.
166   function New_Default_Value (Ltype : O_Tnode) return O_Cnode;
167
168   --  Build a record/array aggregate.
169   --  The aggregate is constant, and therefore can be only used to initialize
170   --  constant declaration.
171   --  ATYPE must be either a record type or an array subtype.
172   --  Elements must be added in the order, and must be literals or aggregates.
173   type O_Record_Aggr_List is limited private;
174   type O_Array_Aggr_List is limited private;
175
176   procedure Start_Record_Aggr (List : out O_Record_Aggr_List;
177                                Atype : O_Tnode);
178   procedure New_Record_Aggr_El (List : in out O_Record_Aggr_List;
179                                 Value : O_Cnode);
180   procedure Finish_Record_Aggr (List : in out O_Record_Aggr_List;
181                                 Res : out O_Cnode);
182
183   procedure Start_Array_Aggr
184     (List : out O_Array_Aggr_List; Atype : O_Tnode; Len : Unsigned_32);
185   procedure New_Array_Aggr_El (List : in out O_Array_Aggr_List;
186                                Value : O_Cnode);
187   procedure Finish_Array_Aggr (List : in out O_Array_Aggr_List;
188                                Res : out O_Cnode);
189
190   --  Build an union aggregate.
191   function New_Union_Aggr (Atype : O_Tnode; Field : O_Fnode; Value : O_Cnode)
192                           return O_Cnode;
193
194   --  Returns the size in bytes of ATYPE.  The result is a literal of
195   --  unsigned type RTYPE
196   --  ATYPE cannot be an unconstrained array type.
197   function New_Sizeof (Atype : O_Tnode; Rtype : O_Tnode) return O_Cnode;
198
199   --  Returns the alignment in bytes for ATYPE.  The result is a literal of
200   --  unsgined type RTYPE.
201   function New_Alignof (Atype : O_Tnode; Rtype : O_Tnode) return O_Cnode;
202
203   --  Returns the offset of FIELD in its record ATYPE.  The result is a
204   --  literal of unsigned type or access type RTYPE.
205   function New_Offsetof (Atype : O_Tnode; Field : O_Fnode; Rtype : O_Tnode)
206                         return O_Cnode;
207
208   --  Get the address of a subprogram.
209   function New_Subprogram_Address (Subprg : O_Dnode; Atype : O_Tnode)
210                                   return O_Cnode;
211
212   --  Get the address of LVALUE.
213   --  ATYPE must be a type access whose designated type is the type of LVALUE.
214   --  FIXME: what about arrays.
215   function New_Global_Address (Lvalue : O_Gnode; Atype : O_Tnode)
216                               return O_Cnode;
217
218   --  Same as New_Address but without any restriction.
219   function New_Global_Unchecked_Address (Lvalue : O_Gnode; Atype : O_Tnode)
220                                         return O_Cnode;
221
222   -------------------
223   --  Expressions  --
224   -------------------
225
226   type ON_Op_Kind is
227     (
228      --  Not an operation; invalid.
229      ON_Nil,
230
231      --  Dyadic operations.
232      ON_Add_Ov,                --  ON_Dyadic_Op_Kind
233      ON_Sub_Ov,                --  ON_Dyadic_Op_Kind
234      ON_Mul_Ov,                --  ON_Dyadic_Op_Kind
235      ON_Div_Ov,                --  ON_Dyadic_Op_Kind
236      ON_Rem_Ov,                --  ON_Dyadic_Op_Kind
237      ON_Mod_Ov,                --  ON_Dyadic_Op_Kind
238
239      --  Binary operations.
240      ON_And,                   --  ON_Dyadic_Op_Kind
241      ON_Or,                    --  ON_Dyadic_Op_Kind
242      ON_Xor,                   --  ON_Dyadic_Op_Kind
243
244      --  Monadic operations.
245      ON_Not,                   --  ON_Monadic_Op_Kind
246      ON_Neg_Ov,                --  ON_Monadic_Op_Kind
247      ON_Abs_Ov,                --  ON_Monadic_Op_Kind
248
249      --  Comparaisons
250      ON_Eq,                    --  ON_Compare_Op_Kind
251      ON_Neq,                   --  ON_Compare_Op_Kind
252      ON_Le,                    --  ON_Compare_Op_Kind
253      ON_Lt,                    --  ON_Compare_Op_Kind
254      ON_Ge,                    --  ON_Compare_Op_Kind
255      ON_Gt                     --  ON_Compare_Op_Kind
256      );
257
258   subtype ON_Dyadic_Op_Kind is ON_Op_Kind range ON_Add_Ov .. ON_Xor;
259   subtype ON_Monadic_Op_Kind is ON_Op_Kind range ON_Not .. ON_Abs_Ov;
260   subtype ON_Compare_Op_Kind is ON_Op_Kind range ON_Eq .. ON_Gt;
261
262   type O_Storage is (O_Storage_External,
263                      O_Storage_Public,
264                      O_Storage_Private,
265                      O_Storage_Local);
266   --  Specifies the storage kind of a declaration.
267   --  O_STORAGE_EXTERNAL:
268   --    The declaration do not either reserve memory nor generate code, and
269   --    is imported either from an other file or from a later place in the
270   --    current file.
271   --  O_STORAGE_PUBLIC, O_STORAGE_PRIVATE:
272   --    The declaration reserves memory or generates code.
273   --    With O_STORAGE_PUBLIC, the declaration is exported outside of the
274   --    file while with O_STORAGE_PRIVATE, the declaration is local to the
275   --    file.
276
277   Type_Error : exception;
278   Syntax_Error : exception;
279
280   --  Create a value from a literal.
281   function New_Lit (Lit : O_Cnode) return O_Enode;
282
283   --  Create a dyadic operation.
284   --  Left and right nodes must have the same type.
285   --  Binary operation is allowed only on boolean types.
286   --  The result is of the type of the operands.
287   function New_Dyadic_Op (Kind : ON_Dyadic_Op_Kind; Left, Right : O_Enode)
288     return O_Enode;
289
290   --  Create a monadic operation.
291   --  Result is of the type of operand.
292   function New_Monadic_Op (Kind : ON_Monadic_Op_Kind; Operand : O_Enode)
293     return O_Enode;
294
295   --  Create a comparaison operator.
296   --  NTYPE is the type of the result and must be a boolean type.
297   function New_Compare_Op
298     (Kind : ON_Compare_Op_Kind; Left, Right : O_Enode; Ntype : O_Tnode)
299     return O_Enode;
300
301
302   type O_Inter_List is limited private;
303   type O_Assoc_List is limited private;
304   type O_If_Block is limited private;
305   type O_Case_Block is limited private;
306
307
308   --  Get an element of an array.
309   --  INDEX must be of the type of the array index.
310   function New_Indexed_Element (Arr : O_Lnode; Index : O_Enode)
311     return O_Lnode;
312
313   --  Get a slice of an array; this is equivalent to a conversion between
314   --  an array or an array subtype and an array subtype.
315   --  RES_TYPE must be an array_sub_type whose base type is the same as the
316   --  base type of ARR.
317   --  INDEX must be of the type of the array index.
318   function New_Slice (Arr : O_Lnode; Res_Type : O_Tnode; Index : O_Enode)
319                      return O_Lnode;
320
321   --  Get an element of a record or a union.
322   --  Type of REC must be a record or a union type.
323   function New_Selected_Element (Rec : O_Lnode; El : O_Fnode)
324                                 return O_Lnode;
325
326   function New_Global_Selected_Element (Rec : O_Gnode; El : O_Fnode)
327                                        return O_Gnode;
328
329   --  Reference an access.
330   --  Type of ACC must be an access type.
331   function New_Access_Element (Acc : O_Enode) return O_Lnode;
332
333   --  Do a conversion.
334   --  Allowed conversions are:
335   --  FIXME: to write.
336   function New_Convert_Ov (Val : O_Enode; Rtype : O_Tnode) return O_Enode;
337   function New_Convert (Val : O_Enode; Rtype : O_Tnode) return O_Enode;
338
339   --  Get the address of LVALUE.
340   --  ATYPE must be a type access whose designated type is the type of LVALUE.
341   --  FIXME: what about arrays.
342   function New_Address (Lvalue : O_Lnode; Atype : O_Tnode) return O_Enode;
343
344   --  Same as New_Address but without any restriction.
345   function New_Unchecked_Address (Lvalue : O_Lnode; Atype : O_Tnode)
346     return O_Enode;
347
348   --  Get the value of an Lvalue.
349   function New_Value (Lvalue : O_Lnode) return O_Enode;
350   function New_Obj_Value (Obj : O_Dnode) return O_Enode;
351
352   --  Get an lvalue from a declaration.
353   function New_Obj (Obj : O_Dnode) return O_Lnode;
354
355   --  Get a global lvalue from a declaration.
356   function New_Global (Decl : O_Dnode) return O_Gnode;
357
358   --  Return a pointer of type RTPE to SIZE bytes allocated on the stack.
359   function New_Alloca (Rtype : O_Tnode; Size : O_Enode) return O_Enode;
360
361   --  Declare a type.
362   --  This simply gives a name to a type.
363   procedure New_Type_Decl (Ident : O_Ident; Atype : O_Tnode);
364
365   ---------------------
366   --  Declarations.  --
367   ---------------------
368
369   --  Filename of the next declaration.
370   procedure New_Debug_Filename_Decl (Filename : String);
371
372   --  Line number of the next declaration.
373   procedure New_Debug_Line_Decl (Line : Natural);
374
375   --  Add a comment in the declarative region.
376   procedure New_Debug_Comment_Decl (Comment : String);
377
378   --  Declare a constant.
379   --  This simply gives a name to a constant value or aggregate.
380   --  A constant cannot be modified and its storage cannot be local.
381   --  ATYPE must be constrained.
382   procedure New_Const_Decl
383     (Res : out O_Dnode;
384      Ident : O_Ident;
385      Storage : O_Storage;
386      Atype : O_Tnode);
387
388   --  Set the value of a non-external constant or variable.
389   procedure Start_Init_Value (Decl : in out O_Dnode);
390   procedure Finish_Init_Value (Decl : in out O_Dnode; Val : O_Cnode);
391
392   --  Create a variable declaration.
393   --  A variable can be local only inside a function.
394   --  ATYPE must be constrained.
395   procedure New_Var_Decl
396     (Res : out O_Dnode;
397      Ident : O_Ident;
398      Storage : O_Storage;
399      Atype : O_Tnode);
400
401   --  Start a subprogram declaration.
402   --  Note: nested subprograms are allowed, ie o_storage_local subprograms can
403   --   be declared inside a subprograms.  It is not allowed to declare
404   --   o_storage_external subprograms inside a subprograms.
405   --  Return type and interfaces cannot be a composite type.
406   procedure Start_Function_Decl
407     (Interfaces : out O_Inter_List;
408      Ident : O_Ident;
409      Storage : O_Storage;
410      Rtype : O_Tnode);
411   --  For a subprogram without return value.
412   procedure Start_Procedure_Decl
413     (Interfaces : out O_Inter_List;
414      Ident : O_Ident;
415      Storage : O_Storage);
416
417   --  Add an interface declaration to INTERFACES.
418   procedure New_Interface_Decl
419     (Interfaces : in out O_Inter_List;
420      Res : out O_Dnode;
421      Ident : O_Ident;
422      Atype : O_Tnode);
423   --  Finish the function declaration, get the node and a statement list.
424   procedure Finish_Subprogram_Decl
425     (Interfaces : in out O_Inter_List; Res : out O_Dnode);
426   --  Start a subprogram body.
427   --  Note: the declaration may have an external storage, in this case it
428   --  becomes public.
429   procedure Start_Subprogram_Body (Func : O_Dnode);
430   --  Finish a subprogram body.
431   procedure Finish_Subprogram_Body;
432
433
434   -------------------
435   --  Statements.  --
436   -------------------
437
438   --  Add a line number as a statement.
439   procedure New_Debug_Line_Stmt (Line : Natural);
440
441   --  Add a comment as a statement.
442   procedure New_Debug_Comment_Stmt (Comment : String);
443
444   --  Start a declarative region.
445   procedure Start_Declare_Stmt;
446   procedure Finish_Declare_Stmt;
447
448   --  Create a function call or a procedure call.
449   procedure Start_Association (Assocs : out O_Assoc_List; Subprg : O_Dnode);
450   procedure New_Association (Assocs : in out O_Assoc_List; Val : O_Enode);
451   function New_Function_Call (Assocs : O_Assoc_List) return O_Enode;
452   procedure New_Procedure_Call (Assocs : in out O_Assoc_List);
453
454   --  Assign VALUE to TARGET, type must be the same or compatible.
455   --  FIXME: what about slice assignment?
456   procedure New_Assign_Stmt (Target : O_Lnode; Value : O_Enode);
457
458   --  Exit from the subprogram and return VALUE.
459   procedure New_Return_Stmt (Value : O_Enode);
460   --  Exit from the subprogram, which doesn't return value.
461   procedure New_Return_Stmt;
462
463   --  Build an IF statement.
464   procedure Start_If_Stmt (Block : in out O_If_Block; Cond : O_Enode);
465   procedure New_Else_Stmt (Block : in out O_If_Block);
466   procedure Finish_If_Stmt (Block : in out O_If_Block);
467
468   --  Create a infinite loop statement.
469   procedure Start_Loop_Stmt (Label : out O_Snode);
470   procedure Finish_Loop_Stmt (Label : in out O_Snode);
471
472   --  Exit from a loop stmt or from a for stmt.
473   procedure New_Exit_Stmt (L : O_Snode);
474   --  Go to the start of a loop stmt or of a for stmt.
475   --  Loops/Fors between L and the current points are exited.
476   procedure New_Next_Stmt (L : O_Snode);
477
478   --  Case statement.
479   --  VALUE is the selector and must be a discrete type.
480   procedure Start_Case_Stmt (Block : in out O_Case_Block; Value : O_Enode);
481   --  A choice branch is composed of expr, range or default choices.
482   --  A choice branch is enclosed between a Start_Choice and a Finish_Choice.
483   --  The statements are after the finish_choice.
484   procedure Start_Choice (Block : in out O_Case_Block);
485   procedure New_Expr_Choice (Block : in out O_Case_Block; Expr : O_Cnode);
486   procedure New_Range_Choice (Block : in out O_Case_Block;
487                               Low, High : O_Cnode);
488   procedure New_Default_Choice (Block : in out O_Case_Block);
489   procedure Finish_Choice (Block : in out O_Case_Block);
490   procedure Finish_Case_Stmt (Block : in out O_Case_Block);
491
492--  End of common part
493private
494   --  No support for nested subprograms in LLVM.
495   Has_Nested_Subprograms : constant Boolean := False;
496
497   type O_Tnode_Type (<>);
498   type O_Tnode is access O_Tnode_Type;
499   O_Tnode_Null : constant O_Tnode := null;
500
501   type ON_Type_Kind is
502     (ON_No_Type,
503      ON_Unsigned_Type, ON_Signed_Type, ON_Enum_Type, ON_Boolean_Type,
504      ON_Float_Type,
505      ON_Array_Type, ON_Array_Sub_Type,
506      ON_Incomplete_Record_Type,
507      ON_Record_Type, ON_Union_Type,
508      ON_Incomplete_Access_Type, ON_Access_Type);
509
510   subtype ON_Scalar_Types is ON_Type_Kind range
511     ON_Unsigned_Type .. ON_Float_Type;
512
513   subtype ON_Integer_Types is ON_Type_Kind range
514     ON_Unsigned_Type .. ON_Boolean_Type;
515
516   type O_Tnode_Type (Kind : ON_Type_Kind := ON_No_Type) is record
517      LLVM : TypeRef;
518      Dbg : ValueRef;
519      case Kind is
520         when ON_No_Type =>
521            null;
522         when ON_Union_Type =>
523            Un_Size : unsigned;
524            Un_Main_Field : TypeRef;
525         when ON_Access_Type
526           | ON_Incomplete_Access_Type =>
527            Acc_Type : O_Tnode;
528         when ON_Scalar_Types =>
529            Scal_Size : Natural;
530         when ON_Array_Type
531           | ON_Array_Sub_Type =>
532            --  Type of the element
533            Arr_El_Type : O_Tnode;
534         when ON_Record_Type
535           | ON_Incomplete_Record_Type =>
536            null;
537      end case;
538   end record;
539
540   type O_Inter;
541   type O_Inter_Acc is access O_Inter;
542   type O_Inter is record
543      Itype : O_Tnode;
544      Ival : ValueRef;
545      Ident : O_Ident;
546      Next : O_Inter_Acc;
547   end record;
548
549   type On_Decl_Kind is
550     (ON_Type_Decl, ON_Completed_Type_Decl,
551      ON_Const_Decl,
552      ON_Var_Decl, ON_Local_Decl, ON_Interface_Decl,
553      ON_Subprg_Decl,
554      ON_No_Decl);
555
556   type O_Dnode (Kind : On_Decl_Kind := ON_No_Decl) is record
557      Dtype : O_Tnode;
558      LLVM : ValueRef;
559      case Kind is
560         when ON_Var_Decl
561           | ON_Const_Decl
562           | ON_Local_Decl =>
563            null;
564         when ON_Subprg_Decl =>
565            Subprg_Id : O_Ident;
566            Nbr_Args : unsigned;
567            Subprg_Inters : O_Inter_Acc;
568         when ON_Interface_Decl =>
569            Inter : O_Inter_Acc;
570         when others =>
571            null;
572      end case;
573   end record;
574
575   O_Dnode_Null : constant O_Dnode := (Kind => ON_No_Decl,
576                                       Dtype => O_Tnode_Null,
577                                       LLVM => Null_ValueRef);
578
579   type OF_Kind is (OF_None, OF_Record, OF_Union);
580   type O_Fnode (Kind : OF_Kind := OF_None) is record
581      --  Type of the field.
582      Ftype : O_Tnode;
583      case Kind is
584         when OF_None =>
585            null;
586         when OF_Record =>
587            --  Field index (starting from 0).
588            Index : Natural;
589         when OF_Union =>
590            Utype : TypeRef;
591            Ptr_Type : TypeRef;
592      end case;
593   end record;
594
595   O_Fnode_Null : constant O_Fnode := (Kind => OF_None,
596                                       Ftype => O_Tnode_Null);
597
598   type O_Anode_Type;
599   type O_Anode is access O_Anode_Type;
600   type O_Anode_Type is record
601      Next : O_Anode;
602      Formal : O_Dnode;
603      Actual : O_Enode;
604   end record;
605
606   type O_Cnode is record
607      LLVM : ValueRef;
608      Ctype : O_Tnode;
609   end record;
610   O_Cnode_Null : constant O_Cnode := (LLVM => Null_ValueRef,
611                                       Ctype => O_Tnode_Null);
612
613   type O_Enode is record
614      LLVM : ValueRef;
615      Etype : O_Tnode;
616   end record;
617   O_Enode_Null : constant O_Enode := (LLVM => Null_ValueRef,
618                                       Etype => O_Tnode_Null);
619
620
621   type O_Lnode is record
622      --  If True, the LLVM component is the value (used for arguments).
623      --  If False, the LLVM component is the address of the value (used
624      --   for everything else).
625      Direct : Boolean;
626      LLVM : ValueRef;
627      Ltype : O_Tnode;
628   end record;
629
630   O_Lnode_Null : constant O_Lnode := (False, Null_ValueRef, O_Tnode_Null);
631
632   type O_Gnode is record
633      LLVM : ValueRef;
634      Ltype : O_Tnode;
635   end record;
636
637   O_Gnode_Null : constant O_Gnode := (Null_ValueRef, O_Tnode_Null);
638
639   type O_Snode is record
640      --  First BB in the loop body.
641      Bb_Entry : BasicBlockRef;
642
643      --  BB after the loop.
644      Bb_Exit : BasicBlockRef;
645   end record;
646
647   O_Snode_Null : constant O_Snode := (Null_BasicBlockRef,
648                                       Null_BasicBlockRef);
649
650   type O_Inter_List is record
651      Ident : O_Ident;
652      Storage : O_Storage;
653      Res_Type : O_Tnode;
654      Nbr_Inter : Natural;
655      First_Inter, Last_Inter : O_Inter_Acc;
656   end record;
657
658   type O_Element;
659   type O_Element_Acc is access O_Element;
660   type O_Element is record
661      --  Identifier for the element
662      Ident : O_Ident;
663
664      --  Type of the element
665      Etype : O_Tnode;
666
667      --  Next element (in the linked list)
668      Next : O_Element_Acc;
669   end record;
670
671   --  Record and union builder.
672   type O_Element_List is record
673      Kind : OF_Kind;
674
675      --  Number of fields.
676      Nbr_Elements : Natural;
677
678      --  For record: the access to the incomplete (but named) type.
679      Rec_Type : O_Tnode;
680
681      --  For unions: biggest for size and alignment
682      Size : unsigned;
683      Align : Unsigned_32;
684      Align_Type : TypeRef;
685
686      First_Elem, Last_Elem : O_Element_Acc;
687   end record;
688
689   type ValueRefArray_Acc is access ValueRefArray;
690
691   type O_Record_Aggr_List is record
692      --  Current number of elements in Vals.
693      Len : unsigned;
694
695      --  Value of elements.
696      Vals : ValueRefArray_Acc;
697
698      --  Type of the aggregate.
699      Atype : O_Tnode;
700   end record;
701
702   type O_Array_Aggr_List is record
703      --  Current number of elements in Vals.
704      Len : unsigned;
705
706      --  Value of elements.
707      Vals : ValueRefArray_Acc;
708      El_Type : TypeRef;
709
710      --  Type of the aggregate.
711      Atype : O_Tnode;
712   end record;
713
714   type O_Assoc_List is record
715      Subprg : O_Dnode;
716      Idx : unsigned;
717      Vals : ValueRefArray_Acc;
718   end record;
719
720   type O_Enum_List is record
721      LLVM : TypeRef;
722      Num : Natural;
723      Etype : O_Tnode;
724   end record;
725
726   type O_Choice_Type is record
727      Low, High : ValueRef;
728      Bb : BasicBlockRef;
729   end record;
730
731   type O_Choice_Array is array (Natural range <>) of O_Choice_Type;
732   type O_Choice_Array_Acc is access O_Choice_Array;
733
734   type O_Case_Block is record
735      --  BB before the case.
736      BB_Prev : BasicBlockRef;
737
738      --  Select expression
739      Value : ValueRef;
740      Vtype : O_Tnode;
741
742      --  BB after the case statement.
743      BB_Next : BasicBlockRef;
744
745      --  BB for others
746      BB_Others : BasicBlockRef;
747
748      --  BB for the current choice
749      BB_Choice : BasicBlockRef;
750
751      --  List of choices.
752      Nbr_Choices : Natural;
753      Choices : O_Choice_Array_Acc;
754   end record;
755
756   type O_If_Block is record
757      --  The next basic block.
758      --  After the 'If', this is the BB for the else part.  If there is no
759      --   else part, this is the BB for statements after the if.
760      --  After the 'else', this is the BB for statements after the if.
761      Bb : BasicBlockRef;
762   end record;
763
764   function Get_LLVM_Type (Atype : O_Tnode) return TypeRef;
765end Ortho_LLVM;
766