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