OSDN Git Service

2009-04-08 Tristan Gingold <gingold@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / gcc-interface / decl.c
1 /****************************************************************************
2  *                                                                          *
3  *                         GNAT COMPILER COMPONENTS                         *
4  *                                                                          *
5  *                                 D E C L                                  *
6  *                                                                          *
7  *                          C Implementation File                           *
8  *                                                                          *
9  *          Copyright (C) 1992-2009, Free Software Foundation, Inc.         *
10  *                                                                          *
11  * GNAT is free software;  you can  redistribute it  and/or modify it under *
12  * terms of the  GNU General Public License as published  by the Free Soft- *
13  * ware  Foundation;  either version 3,  or (at your option) any later ver- *
14  * sion.  GNAT is distributed in the hope that it will be useful, but WITH- *
15  * OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY *
16  * or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License *
17  * for  more details.  You should have received a copy of the GNU General   *
18  * Public License along with GCC; see the file COPYING3.  If not see        *
19  * <http://www.gnu.org/licenses/>.                                          *
20  *                                                                          *
21  * GNAT was originally developed  by the GNAT team at  New York University. *
22  * Extensive contributions were provided by Ada Core Technologies Inc.      *
23  *                                                                          *
24  ****************************************************************************/
25
26 #include "config.h"
27 #include "system.h"
28 #include "coretypes.h"
29 #include "tm.h"
30 #include "tree.h"
31 #include "flags.h"
32 #include "toplev.h"
33 #include "convert.h"
34 #include "ggc.h"
35 #include "obstack.h"
36 #include "target.h"
37 #include "expr.h"
38
39 #include "ada.h"
40 #include "types.h"
41 #include "atree.h"
42 #include "elists.h"
43 #include "namet.h"
44 #include "nlists.h"
45 #include "repinfo.h"
46 #include "snames.h"
47 #include "stringt.h"
48 #include "uintp.h"
49 #include "fe.h"
50 #include "sinfo.h"
51 #include "einfo.h"
52 #include "hashtab.h"
53 #include "ada-tree.h"
54 #include "gigi.h"
55
56 #ifndef MAX_FIXED_MODE_SIZE
57 #define MAX_FIXED_MODE_SIZE GET_MODE_BITSIZE (DImode)
58 #endif
59
60 /* Convention_Stdcall should be processed in a specific way on Windows targets
61    only.  The macro below is a helper to avoid having to check for a Windows
62    specific attribute throughout this unit.  */
63
64 #if TARGET_DLLIMPORT_DECL_ATTRIBUTES
65 #define Has_Stdcall_Convention(E) (Convention (E) == Convention_Stdcall)
66 #else
67 #define Has_Stdcall_Convention(E) (0)
68 #endif
69
70 /* Stack realignment for functions with foreign conventions is provided on a
71    per back-end basis now, as it is handled by the prologue expanders and not
72    as part of the function's body any more.  It might be requested by way of a
73    dedicated function type attribute on the targets that support it.
74
75    We need a way to avoid setting the attribute on the targets that don't
76    support it and use FORCE_PREFERRED_STACK_BOUNDARY_IN_MAIN for this purpose.
77
78    It is defined on targets where the circuitry is available, and indicates
79    whether the realignment is needed for 'main'.  We use this to decide for
80    foreign subprograms as well.
81
82    It is not defined on targets where the circuitry is not implemented, and
83    we just never set the attribute in these cases.
84
85    Whether it is defined on all targets that would need it in theory is
86    not entirely clear.  We currently trust the base GCC settings for this
87    purpose.  */
88
89 #ifndef FORCE_PREFERRED_STACK_BOUNDARY_IN_MAIN
90 #define FORCE_PREFERRED_STACK_BOUNDARY_IN_MAIN 0
91 #endif
92
93 struct incomplete
94 {
95   struct incomplete *next;
96   tree old_type;
97   Entity_Id full_type;
98 };
99
100 /* These variables are used to defer recursively expanding incomplete types
101    while we are processing an array, a record or a subprogram type.  */
102 static int defer_incomplete_level = 0;
103 static struct incomplete *defer_incomplete_list;
104
105 /* This variable is used to delay expanding From_With_Type types until the
106    end of the spec.  */
107 static struct incomplete *defer_limited_with;
108
109 /* These variables are used to defer finalizing types.  The element of the
110    list is the TYPE_DECL associated with the type.  */
111 static int defer_finalize_level = 0;
112 static VEC (tree,heap) *defer_finalize_list;
113
114 /* A hash table used to cache the result of annotate_value.  */
115 static GTY ((if_marked ("tree_int_map_marked_p"),
116              param_is (struct tree_int_map))) htab_t annotate_value_cache;
117
118 enum alias_set_op
119 {
120   ALIAS_SET_COPY,
121   ALIAS_SET_SUBSET,
122   ALIAS_SET_SUPERSET
123 };
124
125 static void relate_alias_sets (tree, tree, enum alias_set_op);
126
127 static tree substitution_list (Entity_Id, Entity_Id, tree, bool);
128 static bool allocatable_size_p (tree, bool);
129 static void prepend_one_attribute_to (struct attrib **,
130                                       enum attr_type, tree, tree, Node_Id);
131 static void prepend_attributes (Entity_Id, struct attrib **);
132 static tree elaborate_expression (Node_Id, Entity_Id, tree, bool, bool, bool);
133 static bool is_variable_size (tree);
134 static tree elaborate_expression_1 (Node_Id, Entity_Id, tree, tree,
135                                     bool, bool);
136 static tree make_packable_type (tree, bool);
137 static tree gnat_to_gnu_field (Entity_Id, tree, int, bool);
138 static tree gnat_to_gnu_param (Entity_Id, Mechanism_Type, Entity_Id, bool,
139                                bool *);
140 static bool same_discriminant_p (Entity_Id, Entity_Id);
141 static bool array_type_has_nonaliased_component (Entity_Id, tree);
142 static bool compile_time_known_address_p (Node_Id);
143 static void components_to_record (tree, Node_Id, tree, int, bool, tree *,
144                                   bool, bool, bool, bool);
145 static Uint annotate_value (tree);
146 static void annotate_rep (Entity_Id, tree);
147 static tree compute_field_positions (tree, tree, tree, tree, unsigned int);
148 static tree validate_size (Uint, tree, Entity_Id, enum tree_code, bool, bool);
149 static void set_rm_size (Uint, tree, Entity_Id);
150 static tree make_type_from_size (tree, tree, bool);
151 static unsigned int validate_alignment (Uint, Entity_Id, unsigned int);
152 static unsigned int ceil_alignment (unsigned HOST_WIDE_INT);
153 static void check_ok_for_atomic (tree, Entity_Id, bool);
154 static int compatible_signatures_p (tree ftype1, tree ftype2);
155 static void rest_of_type_decl_compilation_no_defer (tree);
156 \f
157 /* Given GNAT_ENTITY, a GNAT defining identifier node, which denotes some Ada
158    entity, return the equivalent GCC tree for that entity (a ..._DECL node)
159    and associate the ..._DECL node with the input GNAT defining identifier.
160
161    If GNAT_ENTITY is a variable or a constant declaration, GNU_EXPR gives its
162    initial value (in GCC tree form).  This is optional for a variable.  For
163    a renamed entity, GNU_EXPR gives the object being renamed.
164
165    DEFINITION is nonzero if this call is intended for a definition.  This is
166    used for separate compilation where it is necessary to know whether an
167    external declaration or a definition must be created if the GCC equivalent
168    was not created previously.  The value of 1 is normally used for a nonzero
169    DEFINITION, but a value of 2 is used in special circumstances, defined in
170    the code.  */
171
172 tree
173 gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
174 {
175   Entity_Id gnat_equiv_type = Gigi_Equivalent_Type (gnat_entity);
176   Entity_Id gnat_temp;
177   Entity_Kind kind = Ekind (gnat_entity);
178   /* Contains the GCC DECL node which is equivalent to the input GNAT node.
179      This node will be associated with the GNAT node by calling at the end
180      of the `switch' statement.  */
181   tree gnu_decl = NULL_TREE;
182   /* Contains the GCC type to be used for the GCC node.  */
183   tree gnu_type = NULL_TREE;
184   /* Contains the GCC size tree to be used for the GCC node.  */
185   tree gnu_size = NULL_TREE;
186   /* Contains the GCC name to be used for the GCC node.  */
187   tree gnu_entity_id;
188   /* True if we have already saved gnu_decl as a GNAT association.  */
189   bool saved = false;
190   /* True if we incremented defer_incomplete_level.  */
191   bool this_deferred = false;
192   /* True if we incremented force_global.  */
193   bool this_global = false;
194   /* True if we should check to see if elaborated during processing.  */
195   bool maybe_present = false;
196   /* True if we made GNU_DECL and its type here.  */
197   bool this_made_decl = false;
198   /* True if debug info is requested for this entity.  */
199   bool debug_info_p = (Needs_Debug_Info (gnat_entity)
200                        || debug_info_level == DINFO_LEVEL_VERBOSE);
201   /* True if this entity is to be considered as imported.  */
202   bool imported_p = (Is_Imported (gnat_entity)
203                      && No (Address_Clause (gnat_entity)));
204   unsigned int esize
205     = ((Known_Esize (gnat_entity)
206         && UI_Is_In_Int_Range (Esize (gnat_entity)))
207        ? MIN (UI_To_Int (Esize (gnat_entity)),
208               IN (kind, Float_Kind)
209               ? fp_prec_to_size (LONG_DOUBLE_TYPE_SIZE)
210               : IN (kind, Access_Kind) ? POINTER_SIZE * 2
211               : LONG_LONG_TYPE_SIZE)
212        : LONG_LONG_TYPE_SIZE);
213   unsigned int align = 0;
214   struct attrib *attr_list = NULL;
215
216   /* Since a use of an Itype is a definition, process it as such if it
217      is not in a with'ed unit.  */
218   if (!definition
219       && Is_Itype (gnat_entity)
220       && !present_gnu_tree (gnat_entity)
221       && In_Extended_Main_Code_Unit (gnat_entity))
222     {
223       /* Ensure that we are in a subprogram mentioned in the Scope chain of
224          this entity, our current scope is global, or we encountered a task
225          or entry (where we can't currently accurately check scoping).  */
226       if (!current_function_decl
227           || DECL_ELABORATION_PROC_P (current_function_decl))
228         {
229           process_type (gnat_entity);
230           return get_gnu_tree (gnat_entity);
231         }
232
233       for (gnat_temp = Scope (gnat_entity);
234            Present (gnat_temp);
235            gnat_temp = Scope (gnat_temp))
236         {
237           if (Is_Type (gnat_temp))
238             gnat_temp = Underlying_Type (gnat_temp);
239
240           if (Ekind (gnat_temp) == E_Subprogram_Body)
241             gnat_temp
242               = Corresponding_Spec (Parent (Declaration_Node (gnat_temp)));
243
244           if (IN (Ekind (gnat_temp), Subprogram_Kind)
245               && Present (Protected_Body_Subprogram (gnat_temp)))
246             gnat_temp = Protected_Body_Subprogram (gnat_temp);
247
248           if (Ekind (gnat_temp) == E_Entry
249               || Ekind (gnat_temp) == E_Entry_Family
250               || Ekind (gnat_temp) == E_Task_Type
251               || (IN (Ekind (gnat_temp), Subprogram_Kind)
252                   && present_gnu_tree (gnat_temp)
253                   && (current_function_decl
254                       == gnat_to_gnu_entity (gnat_temp, NULL_TREE, 0))))
255             {
256               process_type (gnat_entity);
257               return get_gnu_tree (gnat_entity);
258             }
259         }
260
261       /* This abort means the entity has an incorrect scope, i.e. that its
262          scope does not correspond to the subprogram it is declared in.  */
263       gcc_unreachable ();
264     }
265
266   /* If the entiy is not present, something went badly wrong.  */
267   gcc_assert (Present (gnat_entity));
268
269   /* If we've already processed this entity, return what we got last time.
270      If we are defining the node, we should not have already processed it.
271      In that case, we will abort below when we try to save a new GCC tree
272      for this object.  We also need to handle the case of getting a dummy
273      type when a Full_View exists.  */
274   if (present_gnu_tree (gnat_entity)
275       && (!definition || (Is_Type (gnat_entity) && imported_p)))
276     {
277       gnu_decl = get_gnu_tree (gnat_entity);
278
279       if (TREE_CODE (gnu_decl) == TYPE_DECL
280           && TYPE_IS_DUMMY_P (TREE_TYPE (gnu_decl))
281           && IN (kind, Incomplete_Or_Private_Kind)
282           && Present (Full_View (gnat_entity)))
283         {
284           gnu_decl
285             = gnat_to_gnu_entity (Full_View (gnat_entity), NULL_TREE, 0);
286           save_gnu_tree (gnat_entity, NULL_TREE, false);
287           save_gnu_tree (gnat_entity, gnu_decl, false);
288         }
289
290       return gnu_decl;
291     }
292
293   /* If this is a numeric or enumeral type, or an access type, a nonzero
294      Esize must be specified unless it was specified by the programmer.  */
295   gcc_assert (!Unknown_Esize (gnat_entity)
296               || Has_Size_Clause (gnat_entity)
297               || (!IN (kind, Numeric_Kind)
298                   && !IN (kind, Enumeration_Kind)
299                   && (!IN (kind, Access_Kind)
300                       || kind == E_Access_Protected_Subprogram_Type
301                       || kind == E_Anonymous_Access_Protected_Subprogram_Type
302                       || kind == E_Access_Subtype)));
303
304   /* RM_Size must be specified for all discrete and fixed-point types.  */
305   gcc_assert (!IN (kind, Discrete_Or_Fixed_Point_Kind)
306               || !Unknown_RM_Size (gnat_entity));
307
308   /* Get the name of the entity and set up the line number and filename of
309      the original definition for use in any decl we make.  */
310   gnu_entity_id = get_entity_name (gnat_entity);
311   Sloc_to_locus (Sloc (gnat_entity), &input_location);
312
313   /* If we get here, it means we have not yet done anything with this
314      entity.  If we are not defining it here, it must be external,
315      otherwise we should have defined it already.  */
316   gcc_assert (definition || Is_Public (gnat_entity) || type_annotate_only
317               || kind == E_Discriminant || kind == E_Component
318               || kind == E_Label
319               || (kind == E_Constant && Present (Full_View (gnat_entity)))
320               || IN (kind, Type_Kind));
321
322   /* For cases when we are not defining (i.e., we are referencing from
323      another compilation unit) public entities, show we are at global level
324      for the purpose of computing scopes.  Don't do this for components or
325      discriminants since the relevant test is whether or not the record is
326      being defined.  But do this for Imported functions or procedures in
327      all cases.  */
328   if ((!definition && Is_Public (gnat_entity)
329        && !Is_Statically_Allocated (gnat_entity)
330        && kind != E_Discriminant && kind != E_Component)
331       || (Is_Imported (gnat_entity)
332           && (kind == E_Function || kind == E_Procedure)))
333     force_global++, this_global = true;
334
335   /* Handle any attributes directly attached to the entity.  */
336   if (Has_Gigi_Rep_Item (gnat_entity))
337     prepend_attributes (gnat_entity, &attr_list);
338
339   /* Machine_Attributes on types are expected to be propagated to subtypes.
340      The corresponding Gigi_Rep_Items are only attached to the first subtype
341      though, so we handle the propagation here.  */
342   if (Is_Type (gnat_entity) && Base_Type (gnat_entity) != gnat_entity
343       && !Is_First_Subtype (gnat_entity)
344       && Has_Gigi_Rep_Item (First_Subtype (Base_Type (gnat_entity))))
345     prepend_attributes (First_Subtype (Base_Type (gnat_entity)), &attr_list);
346
347   switch (kind)
348     {
349     case E_Constant:
350       /* If this is a use of a deferred constant without address clause,
351          get its full definition.  */
352       if (!definition
353           && No (Address_Clause (gnat_entity))
354           && Present (Full_View (gnat_entity)))
355         {
356           gnu_decl
357             = gnat_to_gnu_entity (Full_View (gnat_entity), gnu_expr, 0);
358           saved = true;
359           break;
360         }
361
362       /* If we have an external constant that we are not defining, get the
363          expression that is was defined to represent.  We may throw that
364          expression away later if it is not a constant.  Do not retrieve the
365          expression if it is an aggregate or allocator, because in complex
366          instantiation contexts it may not be expanded  */
367       if (!definition
368           && Present (Expression (Declaration_Node (gnat_entity)))
369           && !No_Initialization (Declaration_Node (gnat_entity))
370           && (Nkind (Expression (Declaration_Node (gnat_entity)))
371               != N_Aggregate)
372           && (Nkind (Expression (Declaration_Node (gnat_entity)))
373               != N_Allocator))
374         gnu_expr = gnat_to_gnu (Expression (Declaration_Node (gnat_entity)));
375
376       /* Ignore deferred constant definitions without address clause since
377          they are processed fully in the front-end.  If No_Initialization
378          is set, this is not a deferred constant but a constant whose value
379          is built manually.  And constants that are renamings are handled
380          like variables.  */
381       if (definition
382           && !gnu_expr
383           && No (Address_Clause (gnat_entity))
384           && !No_Initialization (Declaration_Node (gnat_entity))
385           && No (Renamed_Object (gnat_entity)))
386         {
387           gnu_decl = error_mark_node;
388           saved = true;
389           break;
390         }
391
392       /* Ignore constant definitions already marked with the error node.  See
393          the N_Object_Declaration case of gnat_to_gnu for the rationale.  */
394       if (definition
395           && gnu_expr
396           && present_gnu_tree (gnat_entity)
397           && get_gnu_tree (gnat_entity) == error_mark_node)
398         {
399           maybe_present = true;
400           break;
401         }
402
403       goto object;
404
405     case E_Exception:
406       /* We used to special case VMS exceptions here to directly map them to
407          their associated condition code.  Since this code had to be masked
408          dynamically to strip off the severity bits, this caused trouble in
409          the GCC/ZCX case because the "type" pointers we store in the tables
410          have to be static.  We now don't special case here anymore, and let
411          the regular processing take place, which leaves us with a regular
412          exception data object for VMS exceptions too.  The condition code
413          mapping is taken care of by the front end and the bitmasking by the
414          runtime library.  */
415       goto object;
416
417     case E_Discriminant:
418     case E_Component:
419       {
420         /* The GNAT record where the component was defined.  */
421         Entity_Id gnat_record = Underlying_Type (Scope (gnat_entity));
422
423         /* If the variable is an inherited record component (in the case of
424            extended record types), just return the inherited entity, which
425            must be a FIELD_DECL.  Likewise for discriminants.
426            For discriminants of untagged records which have explicit
427            stored discriminants, return the entity for the corresponding
428            stored discriminant.  Also use Original_Record_Component
429            if the record has a private extension.  */
430         if (Present (Original_Record_Component (gnat_entity))
431             && Original_Record_Component (gnat_entity) != gnat_entity)
432           {
433             gnu_decl
434               = gnat_to_gnu_entity (Original_Record_Component (gnat_entity),
435                                     gnu_expr, definition);
436             saved = true;
437             break;
438           }
439
440         /* If the enclosing record has explicit stored discriminants,
441            then it is an untagged record.  If the Corresponding_Discriminant
442            is not empty then this must be a renamed discriminant and its
443            Original_Record_Component must point to the corresponding explicit
444            stored discriminant (i.e. we should have taken the previous
445            branch).  */
446         else if (Present (Corresponding_Discriminant (gnat_entity))
447                  && Is_Tagged_Type (gnat_record))
448           {
449             /* A tagged record has no explicit stored discriminants.  */
450             gcc_assert (First_Discriminant (gnat_record)
451                        == First_Stored_Discriminant (gnat_record));
452             gnu_decl
453               = gnat_to_gnu_entity (Corresponding_Discriminant (gnat_entity),
454                                     gnu_expr, definition);
455             saved = true;
456             break;
457           }
458
459         else if (Present (CR_Discriminant (gnat_entity))
460                  && type_annotate_only)
461           {
462             gnu_decl = gnat_to_gnu_entity (CR_Discriminant (gnat_entity),
463                                            gnu_expr, definition);
464             saved = true;
465             break;
466           }
467
468         /* If the enclosing record has explicit stored discriminants, then
469            it is an untagged record.  If the Corresponding_Discriminant
470            is not empty then this must be a renamed discriminant and its
471            Original_Record_Component must point to the corresponding explicit
472            stored discriminant (i.e. we should have taken the first
473            branch).  */
474         else if (Present (Corresponding_Discriminant (gnat_entity))
475                  && (First_Discriminant (gnat_record)
476                      != First_Stored_Discriminant (gnat_record)))
477           gcc_unreachable ();
478
479         /* Otherwise, if we are not defining this and we have no GCC type
480            for the containing record, make one for it.  Then we should
481            have made our own equivalent.  */
482         else if (!definition && !present_gnu_tree (gnat_record))
483           {
484             /* ??? If this is in a record whose scope is a protected
485                type and we have an Original_Record_Component, use it.
486                This is a workaround for major problems in protected type
487                handling.  */
488             Entity_Id Scop = Scope (Scope (gnat_entity));
489             if ((Is_Protected_Type (Scop)
490                  || (Is_Private_Type (Scop)
491                      && Present (Full_View (Scop))
492                      && Is_Protected_Type (Full_View (Scop))))
493                 && Present (Original_Record_Component (gnat_entity)))
494               {
495                 gnu_decl
496                   = gnat_to_gnu_entity (Original_Record_Component
497                                         (gnat_entity),
498                                         gnu_expr, 0);
499                 saved = true;
500                 break;
501               }
502
503             gnat_to_gnu_entity (Scope (gnat_entity), NULL_TREE, 0);
504             gnu_decl = get_gnu_tree (gnat_entity);
505             saved = true;
506             break;
507           }
508
509         else
510           /* Here we have no GCC type and this is a reference rather than a
511              definition.  This should never happen.  Most likely the cause is
512              reference before declaration in the gnat tree for gnat_entity.  */
513           gcc_unreachable ();
514       }
515
516     case E_Loop_Parameter:
517     case E_Out_Parameter:
518     case E_Variable:
519
520       /* Simple variables, loop variables, Out parameters, and exceptions.  */
521     object:
522       {
523         bool used_by_ref = false;
524         bool const_flag
525           = ((kind == E_Constant || kind == E_Variable)
526              && Is_True_Constant (gnat_entity)
527              && !Treat_As_Volatile (gnat_entity)
528              && (((Nkind (Declaration_Node (gnat_entity))
529                    == N_Object_Declaration)
530                   && Present (Expression (Declaration_Node (gnat_entity))))
531                  || Present (Renamed_Object (gnat_entity))));
532         bool inner_const_flag = const_flag;
533         bool static_p = Is_Statically_Allocated (gnat_entity);
534         bool mutable_p = false;
535         tree gnu_ext_name = NULL_TREE;
536         tree renamed_obj = NULL_TREE;
537         tree gnu_object_size;
538
539         if (Present (Renamed_Object (gnat_entity)) && !definition)
540           {
541             if (kind == E_Exception)
542               gnu_expr = gnat_to_gnu_entity (Renamed_Entity (gnat_entity),
543                                              NULL_TREE, 0);
544             else
545               gnu_expr = gnat_to_gnu (Renamed_Object (gnat_entity));
546           }
547
548         /* Get the type after elaborating the renamed object.  */
549         gnu_type = gnat_to_gnu_type (Etype (gnat_entity));
550
551         /* For a debug renaming declaration, build a pure debug entity.  */
552         if (Present (Debug_Renaming_Link (gnat_entity)))
553           {
554             rtx addr;
555             gnu_decl = build_decl (VAR_DECL, gnu_entity_id, gnu_type);
556             /* The (MEM (CONST (0))) pattern is prescribed by STABS.  */
557             if (global_bindings_p ())
558               addr = gen_rtx_CONST (VOIDmode, const0_rtx);
559             else
560               addr = stack_pointer_rtx;
561             SET_DECL_RTL (gnu_decl, gen_rtx_MEM (Pmode, addr));
562             gnat_pushdecl (gnu_decl, gnat_entity);
563             break;
564           }
565
566         /* If this is a loop variable, its type should be the base type.
567            This is because the code for processing a loop determines whether
568            a normal loop end test can be done by comparing the bounds of the
569            loop against those of the base type, which is presumed to be the
570            size used for computation.  But this is not correct when the size
571            of the subtype is smaller than the type.  */
572         if (kind == E_Loop_Parameter)
573           gnu_type = get_base_type (gnu_type);
574
575         /* Reject non-renamed objects whose types are unconstrained arrays or
576            any object whose type is a dummy type or VOID_TYPE.  */
577
578         if ((TREE_CODE (gnu_type) == UNCONSTRAINED_ARRAY_TYPE
579              && No (Renamed_Object (gnat_entity)))
580             || TYPE_IS_DUMMY_P (gnu_type)
581             || TREE_CODE (gnu_type) == VOID_TYPE)
582           {
583             gcc_assert (type_annotate_only);
584             if (this_global)
585               force_global--;
586             return error_mark_node;
587           }
588
589         /* If an alignment is specified, use it if valid.   Note that
590            exceptions are objects but don't have alignments.  We must do this
591            before we validate the size, since the alignment can affect the
592            size.  */
593         if (kind != E_Exception && Known_Alignment (gnat_entity))
594           {
595             gcc_assert (Present (Alignment (gnat_entity)));
596             align = validate_alignment (Alignment (gnat_entity), gnat_entity,
597                                         TYPE_ALIGN (gnu_type));
598             gnu_type = maybe_pad_type (gnu_type, NULL_TREE, align, gnat_entity,
599                                        "PAD", false, definition, true);
600           }
601
602         /* If we are defining the object, see if it has a Size value and
603            validate it if so.  If we are not defining the object and a Size
604            clause applies, simply retrieve the value.  We don't want to ignore
605            the clause and it is expected to have been validated already.  Then
606            get the new type, if any.  */
607         if (definition)
608           gnu_size = validate_size (Esize (gnat_entity), gnu_type,
609                                     gnat_entity, VAR_DECL, false,
610                                     Has_Size_Clause (gnat_entity));
611         else if (Has_Size_Clause (gnat_entity))
612           gnu_size = UI_To_gnu (Esize (gnat_entity), bitsizetype);
613
614         if (gnu_size)
615           {
616             gnu_type
617               = make_type_from_size (gnu_type, gnu_size,
618                                      Has_Biased_Representation (gnat_entity));
619
620             if (operand_equal_p (TYPE_SIZE (gnu_type), gnu_size, 0))
621               gnu_size = NULL_TREE;
622           }
623
624         /* If this object has self-referential size, it must be a record with
625            a default value.  We are supposed to allocate an object of the
626            maximum size in this case unless it is a constant with an
627            initializing expression, in which case we can get the size from
628            that.  Note that the resulting size may still be a variable, so
629            this may end up with an indirect allocation.  */
630         if (No (Renamed_Object (gnat_entity))
631             && CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type)))
632           {
633             if (gnu_expr && kind == E_Constant)
634               {
635                 tree size = TYPE_SIZE (TREE_TYPE (gnu_expr));
636                 if (CONTAINS_PLACEHOLDER_P (size))
637                   {
638                     /* If the initializing expression is itself a constant,
639                        despite having a nominal type with self-referential
640                        size, we can get the size directly from it.  */
641                     if (TREE_CODE (gnu_expr) == COMPONENT_REF
642                         && TREE_CODE (TREE_TYPE (TREE_OPERAND (gnu_expr, 0)))
643                            == RECORD_TYPE
644                         && TYPE_IS_PADDING_P
645                            (TREE_TYPE (TREE_OPERAND (gnu_expr, 0)))
646                         && TREE_CODE (TREE_OPERAND (gnu_expr, 0)) == VAR_DECL
647                         && (TREE_READONLY (TREE_OPERAND (gnu_expr, 0))
648                             || DECL_READONLY_ONCE_ELAB
649                                (TREE_OPERAND (gnu_expr, 0))))
650                       gnu_size = DECL_SIZE (TREE_OPERAND (gnu_expr, 0));
651                     else
652                       gnu_size
653                         = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, gnu_expr);
654                   }
655                 else
656                   gnu_size = size;
657               }
658             /* We may have no GNU_EXPR because No_Initialization is
659                set even though there's an Expression.  */
660             else if (kind == E_Constant
661                      && (Nkind (Declaration_Node (gnat_entity))
662                          == N_Object_Declaration)
663                      && Present (Expression (Declaration_Node (gnat_entity))))
664               gnu_size
665                 = TYPE_SIZE (gnat_to_gnu_type
666                              (Etype
667                               (Expression (Declaration_Node (gnat_entity)))));
668             else
669               {
670                 gnu_size = max_size (TYPE_SIZE (gnu_type), true);
671                 mutable_p = true;
672               }
673           }
674
675         /* If the size is zero bytes, make it one byte since some linkers have
676            trouble with zero-sized objects.  If the object will have a
677            template, that will make it nonzero so don't bother.  Also avoid
678            doing that for an object renaming or an object with an address
679            clause, as we would lose useful information on the view size
680            (e.g. for null array slices) and we are not allocating the object
681            here anyway.  */
682         if (((gnu_size
683               && integer_zerop (gnu_size)
684               && !TREE_OVERFLOW (gnu_size))
685              || (TYPE_SIZE (gnu_type)
686                  && integer_zerop (TYPE_SIZE (gnu_type))
687                  && !TREE_OVERFLOW (TYPE_SIZE (gnu_type))))
688             && (!Is_Constr_Subt_For_UN_Aliased (Etype (gnat_entity))
689                 || !Is_Array_Type (Etype (gnat_entity)))
690             && !Present (Renamed_Object (gnat_entity))
691             && !Present (Address_Clause (gnat_entity)))
692           gnu_size = bitsize_unit_node;
693
694         /* If this is an object with no specified size and alignment, and
695            if either it is atomic or we are not optimizing alignment for
696            space and it is composite and not an exception, an Out parameter
697            or a reference to another object, and the size of its type is a
698            constant, set the alignment to the smallest one which is not
699            smaller than the size, with an appropriate cap.  */
700         if (!gnu_size && align == 0
701             && (Is_Atomic (gnat_entity)
702                 || (!Optimize_Alignment_Space (gnat_entity)
703                     && kind != E_Exception
704                     && kind != E_Out_Parameter
705                     && Is_Composite_Type (Etype (gnat_entity))
706                     && !Is_Constr_Subt_For_UN_Aliased (Etype (gnat_entity))
707                     && !imported_p
708                     && No (Renamed_Object (gnat_entity))
709                     && No (Address_Clause (gnat_entity))))
710             && TREE_CODE (TYPE_SIZE (gnu_type)) == INTEGER_CST)
711           {
712             /* No point in jumping through all the hoops needed in order
713                to support BIGGEST_ALIGNMENT if we don't really have to.
714                So we cap to the smallest alignment that corresponds to
715                a known efficient memory access pattern of the target.  */
716             unsigned int align_cap = Is_Atomic (gnat_entity)
717                                      ? BIGGEST_ALIGNMENT
718                                      : get_mode_alignment (ptr_mode);
719
720             if (!host_integerp (TYPE_SIZE (gnu_type), 1)
721                 || compare_tree_int (TYPE_SIZE (gnu_type), align_cap) >= 0)
722               align = align_cap;
723             else
724               align = ceil_alignment (tree_low_cst (TYPE_SIZE (gnu_type), 1));
725
726             /* But make sure not to under-align the object.  */
727             if (align <= TYPE_ALIGN (gnu_type))
728               align = 0;
729
730             /* And honor the minimum valid atomic alignment, if any.  */
731 #ifdef MINIMUM_ATOMIC_ALIGNMENT
732             else if (align < MINIMUM_ATOMIC_ALIGNMENT)
733               align = MINIMUM_ATOMIC_ALIGNMENT;
734 #endif
735           }
736
737         /* If the object is set to have atomic components, find the component
738            type and validate it.
739
740            ??? Note that we ignore Has_Volatile_Components on objects; it's
741            not at all clear what to do in that case.  */
742
743         if (Has_Atomic_Components (gnat_entity))
744           {
745             tree gnu_inner = (TREE_CODE (gnu_type) == ARRAY_TYPE
746                               ? TREE_TYPE (gnu_type) : gnu_type);
747
748             while (TREE_CODE (gnu_inner) == ARRAY_TYPE
749                    && TYPE_MULTI_ARRAY_P (gnu_inner))
750               gnu_inner = TREE_TYPE (gnu_inner);
751
752             check_ok_for_atomic (gnu_inner, gnat_entity, true);
753           }
754
755         /* Now check if the type of the object allows atomic access.  Note
756            that we must test the type, even if this object has size and
757            alignment to allow such access, because we will be going
758            inside the padded record to assign to the object.  We could fix
759            this by always copying via an intermediate value, but it's not
760            clear it's worth the effort.  */
761         if (Is_Atomic (gnat_entity))
762           check_ok_for_atomic (gnu_type, gnat_entity, false);
763
764         /* If this is an aliased object with an unconstrained nominal subtype,
765            make a type that includes the template.  */
766         if (Is_Constr_Subt_For_UN_Aliased (Etype (gnat_entity))
767             && Is_Array_Type (Etype (gnat_entity))
768             && !type_annotate_only)
769         {
770           tree gnu_fat
771             = TREE_TYPE (gnat_to_gnu_type (Base_Type (Etype (gnat_entity))));
772
773           gnu_type
774             = build_unc_object_type_from_ptr (gnu_fat, gnu_type,
775                                      concat_id_with_name (gnu_entity_id,
776                                                           "UNC"));
777         }
778
779 #ifdef MINIMUM_ATOMIC_ALIGNMENT
780         /* If the size is a constant and no alignment is specified, force
781            the alignment to be the minimum valid atomic alignment.  The
782            restriction on constant size avoids problems with variable-size
783            temporaries; if the size is variable, there's no issue with
784            atomic access.  Also don't do this for a constant, since it isn't
785            necessary and can interfere with constant replacement.  Finally,
786            do not do it for Out parameters since that creates an
787            size inconsistency with In parameters.  */
788         if (align == 0 && MINIMUM_ATOMIC_ALIGNMENT > TYPE_ALIGN (gnu_type)
789             && !FLOAT_TYPE_P (gnu_type)
790             && !const_flag && No (Renamed_Object (gnat_entity))
791             && !imported_p && No (Address_Clause (gnat_entity))
792             && kind != E_Out_Parameter
793             && (gnu_size ? TREE_CODE (gnu_size) == INTEGER_CST
794                 : TREE_CODE (TYPE_SIZE (gnu_type)) == INTEGER_CST))
795           align = MINIMUM_ATOMIC_ALIGNMENT;
796 #endif
797
798         /* Make a new type with the desired size and alignment, if needed.
799            But do not take into account alignment promotions to compute the
800            size of the object.  */
801         gnu_object_size = gnu_size ? gnu_size : TYPE_SIZE (gnu_type);
802         if (gnu_size || align > 0)
803           gnu_type = maybe_pad_type (gnu_type, gnu_size, align, gnat_entity,
804                                      "PAD", false, definition,
805                                      gnu_size ? true : false);
806
807         /* If this is a renaming, avoid as much as possible to create a new
808            object.  However, in several cases, creating it is required.
809            This processing needs to be applied to the raw expression so
810            as to make it more likely to rename the underlying object.  */
811         if (Present (Renamed_Object (gnat_entity)))
812           {
813             bool create_normal_object = false;
814
815             /* If the renamed object had padding, strip off the reference
816                to the inner object and reset our type.  */
817             if ((TREE_CODE (gnu_expr) == COMPONENT_REF
818                  && TREE_CODE (TREE_TYPE (TREE_OPERAND (gnu_expr, 0)))
819                     == RECORD_TYPE
820                  && TYPE_IS_PADDING_P (TREE_TYPE (TREE_OPERAND (gnu_expr, 0))))
821                 /* Strip useless conversions around the object.  */
822                 || (TREE_CODE (gnu_expr) == NOP_EXPR
823                     && gnat_types_compatible_p
824                        (TREE_TYPE (gnu_expr),
825                         TREE_TYPE (TREE_OPERAND (gnu_expr, 0)))))
826               {
827                 gnu_expr = TREE_OPERAND (gnu_expr, 0);
828                 gnu_type = TREE_TYPE (gnu_expr);
829               }
830
831             /* Case 1: If this is a constant renaming stemming from a function
832                call, treat it as a normal object whose initial value is what
833                is being renamed.  RM 3.3 says that the result of evaluating a
834                function call is a constant object.  As a consequence, it can
835                be the inner object of a constant renaming.  In this case, the
836                renaming must be fully instantiated, i.e. it cannot be a mere
837                reference to (part of) an existing object.  */
838             if (const_flag)
839               {
840                 tree inner_object = gnu_expr;
841                 while (handled_component_p (inner_object))
842                   inner_object = TREE_OPERAND (inner_object, 0);
843                 if (TREE_CODE (inner_object) == CALL_EXPR)
844                   create_normal_object = true;
845               }
846
847             /* Otherwise, see if we can proceed with a stabilized version of
848                the renamed entity or if we need to make a new object.  */
849             if (!create_normal_object)
850               {
851                 tree maybe_stable_expr = NULL_TREE;
852                 bool stable = false;
853
854                 /* Case 2: If the renaming entity need not be materialized and
855                    the renamed expression is something we can stabilize, use
856                    that for the renaming.  At the global level, we can only do
857                    this if we know no SAVE_EXPRs need be made, because the
858                    expression we return might be used in arbitrary conditional
859                    branches so we must force the SAVE_EXPRs evaluation
860                    immediately and this requires a function context.  */
861                 if (!Materialize_Entity (gnat_entity)
862                     && (!global_bindings_p ()
863                         || (staticp (gnu_expr)
864                             && !TREE_SIDE_EFFECTS (gnu_expr))))
865                   {
866                     maybe_stable_expr
867                       = maybe_stabilize_reference (gnu_expr, true, &stable);
868
869                     if (stable)
870                       {
871                         gnu_decl = maybe_stable_expr;
872                         /* ??? No DECL_EXPR is created so we need to mark
873                            the expression manually lest it is shared.  */
874                         if (global_bindings_p ())
875                           mark_visited (&gnu_decl);
876                         save_gnu_tree (gnat_entity, gnu_decl, true);
877                         saved = true;
878                         break;
879                       }
880
881                     /* The stabilization failed.  Keep maybe_stable_expr
882                        untouched here to let the pointer case below know
883                        about that failure.  */
884                   }
885
886                 /* Case 3: If this is a constant renaming and creating a
887                    new object is allowed and cheap, treat it as a normal
888                    object whose initial value is what is being renamed.  */
889                 if (const_flag
890                     && !Is_Composite_Type
891                         (Underlying_Type (Etype (gnat_entity))))
892                   ;
893
894                 /* Case 4: Make this into a constant pointer to the object we
895                    are to rename and attach the object to the pointer if it is
896                    something we can stabilize.
897
898                    From the proper scope, attached objects will be referenced
899                    directly instead of indirectly via the pointer to avoid
900                    subtle aliasing problems with non-addressable entities.
901                    They have to be stable because we must not evaluate the
902                    variables in the expression every time the renaming is used.
903                    The pointer is called a "renaming" pointer in this case.
904
905                    In the rare cases where we cannot stabilize the renamed
906                    object, we just make a "bare" pointer, and the renamed
907                    entity is always accessed indirectly through it.  */
908                 else
909                   {
910                     gnu_type = build_reference_type (gnu_type);
911                     inner_const_flag = TREE_READONLY (gnu_expr);
912                     const_flag = true;
913
914                     /* If the previous attempt at stabilizing failed, there
915                        is no point in trying again and we reuse the result
916                        without attaching it to the pointer.  In this case it
917                        will only be used as the initializing expression of
918                        the pointer and thus needs no special treatment with
919                        regard to multiple evaluations.  */
920                     if (maybe_stable_expr)
921                       ;
922
923                     /* Otherwise, try to stabilize and attach the expression
924                        to the pointer if the stabilization succeeds.
925
926                        Note that this might introduce SAVE_EXPRs and we don't
927                        check whether we're at the global level or not.  This
928                        is fine since we are building a pointer initializer and
929                        neither the pointer nor the initializing expression can
930                        be accessed before the pointer elaboration has taken
931                        place in a correct program.
932
933                        These SAVE_EXPRs will be evaluated at the right place
934                        by either the evaluation of the initializer for the
935                        non-global case or the elaboration code for the global
936                        case, and will be attached to the elaboration procedure
937                        in the latter case.  */
938                     else
939                      {
940                         maybe_stable_expr
941                           = maybe_stabilize_reference (gnu_expr, true, &stable);
942
943                         if (stable)
944                           renamed_obj = maybe_stable_expr;
945
946                         /* Attaching is actually performed downstream, as soon
947                            as we have a VAR_DECL for the pointer we make.  */
948                       }
949
950                     gnu_expr
951                       = build_unary_op (ADDR_EXPR, gnu_type, maybe_stable_expr);
952
953                     gnu_size = NULL_TREE;
954                     used_by_ref = true;
955                   }
956               }
957           }
958
959         /* Make a volatile version of this object's type if we are to make
960            the object volatile.  We also interpret 13.3(19) conservatively
961            and disallow any optimizations for an object covered by it.  */
962         if ((Treat_As_Volatile (gnat_entity)
963              || (Is_Exported (gnat_entity)
964                  /* Exclude exported constants created by the compiler,
965                     which should boil down to static dispatch tables and
966                     make it possible to put them in read-only memory.  */
967                  && (Comes_From_Source (gnat_entity) || !const_flag))
968              || Is_Imported (gnat_entity)
969              || Present (Address_Clause (gnat_entity)))
970             && !TYPE_VOLATILE (gnu_type))
971           gnu_type = build_qualified_type (gnu_type,
972                                            (TYPE_QUALS (gnu_type)
973                                             | TYPE_QUAL_VOLATILE));
974
975         /* If we are defining an aliased object whose nominal subtype is
976            unconstrained, the object is a record that contains both the
977            template and the object.  If there is an initializer, it will
978            have already been converted to the right type, but we need to
979            create the template if there is no initializer.  */
980         if (definition
981             && !gnu_expr
982             && TREE_CODE (gnu_type) == RECORD_TYPE
983             && (TYPE_CONTAINS_TEMPLATE_P (gnu_type)
984                 /* Beware that padding might have been introduced
985                    via maybe_pad_type above.  */
986                 || (TYPE_IS_PADDING_P (gnu_type)
987                     && TREE_CODE (TREE_TYPE (TYPE_FIELDS (gnu_type)))
988                        == RECORD_TYPE
989                     && TYPE_CONTAINS_TEMPLATE_P
990                        (TREE_TYPE (TYPE_FIELDS (gnu_type))))))
991           {
992             tree template_field
993               = TYPE_IS_PADDING_P (gnu_type)
994                 ? TYPE_FIELDS (TREE_TYPE (TYPE_FIELDS (gnu_type)))
995                 : TYPE_FIELDS (gnu_type);
996
997             gnu_expr
998               = gnat_build_constructor
999               (gnu_type,
1000                tree_cons
1001                (template_field,
1002                 build_template (TREE_TYPE (template_field),
1003                                 TREE_TYPE (TREE_CHAIN (template_field)),
1004                                 NULL_TREE),
1005                 NULL_TREE));
1006           }
1007
1008         /* Convert the expression to the type of the object except in the
1009            case where the object's type is unconstrained or the object's type
1010            is a padded record whose field is of self-referential size.  In
1011            the former case, converting will generate unnecessary evaluations
1012            of the CONSTRUCTOR to compute the size and in the latter case, we
1013            want to only copy the actual data.  */
1014         if (gnu_expr
1015             && TREE_CODE (gnu_type) != UNCONSTRAINED_ARRAY_TYPE
1016             && !CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type))
1017             && !(TREE_CODE (gnu_type) == RECORD_TYPE
1018                  && TYPE_IS_PADDING_P (gnu_type)
1019                  && (CONTAINS_PLACEHOLDER_P
1020                      (TYPE_SIZE (TREE_TYPE (TYPE_FIELDS (gnu_type)))))))
1021           gnu_expr = convert (gnu_type, gnu_expr);
1022
1023         /* If this is a pointer and it does not have an initializing
1024            expression, initialize it to NULL, unless the object is
1025            imported.  */
1026         if (definition
1027             && (POINTER_TYPE_P (gnu_type) || TYPE_FAT_POINTER_P (gnu_type))
1028             && !Is_Imported (gnat_entity) && !gnu_expr)
1029           gnu_expr = integer_zero_node;
1030
1031         /* If we are defining the object and it has an Address clause, we must
1032            either get the address expression from the saved GCC tree for the
1033            object if it has a Freeze node, or elaborate the address expression
1034            here since the front-end has guaranteed that the elaboration has no
1035            effects in this case.  */
1036         if (definition && Present (Address_Clause (gnat_entity)))
1037           {
1038             tree gnu_address
1039               = present_gnu_tree (gnat_entity)
1040                 ? get_gnu_tree (gnat_entity)
1041                 : gnat_to_gnu (Expression (Address_Clause (gnat_entity)));
1042
1043             save_gnu_tree (gnat_entity, NULL_TREE, false);
1044
1045             /* Ignore the size.  It's either meaningless or was handled
1046                above.  */
1047             gnu_size = NULL_TREE;
1048             /* Convert the type of the object to a reference type that can
1049                alias everything as per 13.3(19).  */
1050             gnu_type
1051               = build_reference_type_for_mode (gnu_type, ptr_mode, true);
1052             gnu_address = convert (gnu_type, gnu_address);
1053             used_by_ref = true;
1054             const_flag = !Is_Public (gnat_entity)
1055               || compile_time_known_address_p (Expression (Address_Clause
1056                                                            (gnat_entity)));
1057
1058             /* If this is a deferred constant, the initializer is attached to
1059                the full view.  */
1060             if (kind == E_Constant && Present (Full_View (gnat_entity)))
1061               gnu_expr
1062                 = gnat_to_gnu
1063                     (Expression (Declaration_Node (Full_View (gnat_entity))));
1064
1065             /* If we don't have an initializing expression for the underlying
1066                variable, the initializing expression for the pointer is the
1067                specified address.  Otherwise, we have to make a COMPOUND_EXPR
1068                to assign both the address and the initial value.  */
1069             if (!gnu_expr)
1070               gnu_expr = gnu_address;
1071             else
1072               gnu_expr
1073                 = build2 (COMPOUND_EXPR, gnu_type,
1074                           build_binary_op
1075                           (MODIFY_EXPR, NULL_TREE,
1076                            build_unary_op (INDIRECT_REF, NULL_TREE,
1077                                            gnu_address),
1078                            gnu_expr),
1079                           gnu_address);
1080           }
1081
1082         /* If it has an address clause and we are not defining it, mark it
1083            as an indirect object.  Likewise for Stdcall objects that are
1084            imported.  */
1085         if ((!definition && Present (Address_Clause (gnat_entity)))
1086             || (Is_Imported (gnat_entity)
1087                 && Has_Stdcall_Convention (gnat_entity)))
1088           {
1089             /* Convert the type of the object to a reference type that can
1090                alias everything as per 13.3(19).  */
1091             gnu_type
1092               = build_reference_type_for_mode (gnu_type, ptr_mode, true);
1093             gnu_size = NULL_TREE;
1094
1095             /* No point in taking the address of an initializing expression
1096                that isn't going to be used.  */
1097             gnu_expr = NULL_TREE;
1098
1099             /* If it has an address clause whose value is known at compile
1100                time, make the object a CONST_DECL.  This will avoid a
1101                useless dereference.  */
1102             if (Present (Address_Clause (gnat_entity)))
1103               {
1104                 Node_Id gnat_address
1105                   = Expression (Address_Clause (gnat_entity));
1106
1107                 if (compile_time_known_address_p (gnat_address))
1108                   {
1109                     gnu_expr = gnat_to_gnu (gnat_address);
1110                     const_flag = true;
1111                   }
1112               }
1113
1114             used_by_ref = true;
1115           }
1116
1117         /* If we are at top level and this object is of variable size,
1118            make the actual type a hidden pointer to the real type and
1119            make the initializer be a memory allocation and initialization.
1120            Likewise for objects we aren't defining (presumed to be
1121            external references from other packages), but there we do
1122            not set up an initialization.
1123
1124            If the object's size overflows, make an allocator too, so that
1125            Storage_Error gets raised.  Note that we will never free
1126            such memory, so we presume it never will get allocated.  */
1127
1128         if (!allocatable_size_p (TYPE_SIZE_UNIT (gnu_type),
1129                                  global_bindings_p () || !definition
1130                                  || static_p)
1131             || (gnu_size
1132                 && ! allocatable_size_p (gnu_size,
1133                                          global_bindings_p () || !definition
1134                                          || static_p)))
1135           {
1136             gnu_type = build_reference_type (gnu_type);
1137             gnu_size = NULL_TREE;
1138             used_by_ref = true;
1139             const_flag = true;
1140
1141             /* In case this was a aliased object whose nominal subtype is
1142                unconstrained, the pointer above will be a thin pointer and
1143                build_allocator will automatically make the template.
1144
1145                If we have a template initializer only (that we made above),
1146                pretend there is none and rely on what build_allocator creates
1147                again anyway.  Otherwise (if we have a full initializer), get
1148                the data part and feed that to build_allocator.
1149
1150                If we are elaborating a mutable object, tell build_allocator to
1151                ignore a possibly simpler size from the initializer, if any, as
1152                we must allocate the maximum possible size in this case.  */
1153
1154             if (definition)
1155               {
1156                 tree gnu_alloc_type = TREE_TYPE (gnu_type);
1157
1158                 if (TREE_CODE (gnu_alloc_type) == RECORD_TYPE
1159                     && TYPE_CONTAINS_TEMPLATE_P (gnu_alloc_type))
1160                   {
1161                     gnu_alloc_type
1162                       = TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (gnu_alloc_type)));
1163
1164                     if (TREE_CODE (gnu_expr) == CONSTRUCTOR
1165                         && 1 == VEC_length (constructor_elt,
1166                                             CONSTRUCTOR_ELTS (gnu_expr)))
1167                       gnu_expr = 0;
1168                     else
1169                       gnu_expr
1170                         = build_component_ref
1171                             (gnu_expr, NULL_TREE,
1172                              TREE_CHAIN (TYPE_FIELDS (TREE_TYPE (gnu_expr))),
1173                              false);
1174                   }
1175
1176                 if (TREE_CODE (TYPE_SIZE_UNIT (gnu_alloc_type)) == INTEGER_CST
1177                     && TREE_OVERFLOW (TYPE_SIZE_UNIT (gnu_alloc_type))
1178                     && !Is_Imported (gnat_entity))
1179                   post_error ("?Storage_Error will be raised at run-time!",
1180                               gnat_entity);
1181
1182                 gnu_expr = build_allocator (gnu_alloc_type, gnu_expr, gnu_type,
1183                                             0, 0, gnat_entity, mutable_p);
1184               }
1185             else
1186               {
1187                 gnu_expr = NULL_TREE;
1188                 const_flag = false;
1189               }
1190           }
1191
1192         /* If this object would go into the stack and has an alignment larger
1193            than the largest stack alignment the back-end can honor, resort to
1194            a variable of "aligning type".  */
1195         if (!global_bindings_p () && !static_p && definition
1196             && !imported_p && TYPE_ALIGN (gnu_type) > BIGGEST_ALIGNMENT)
1197           {
1198             /* Create the new variable.  No need for extra room before the
1199                aligned field as this is in automatic storage.  */
1200             tree gnu_new_type
1201               = make_aligning_type (gnu_type, TYPE_ALIGN (gnu_type),
1202                                     TYPE_SIZE_UNIT (gnu_type),
1203                                     BIGGEST_ALIGNMENT, 0);
1204             tree gnu_new_var
1205               = create_var_decl (create_concat_name (gnat_entity, "ALIGN"),
1206                                  NULL_TREE, gnu_new_type, NULL_TREE, false,
1207                                  false, false, false, NULL, gnat_entity);
1208
1209             /* Initialize the aligned field if we have an initializer.  */
1210             if (gnu_expr)
1211               add_stmt_with_node
1212                 (build_binary_op (MODIFY_EXPR, NULL_TREE,
1213                                   build_component_ref
1214                                   (gnu_new_var, NULL_TREE,
1215                                    TYPE_FIELDS (gnu_new_type), false),
1216                                   gnu_expr),
1217                  gnat_entity);
1218
1219             /* And setup this entity as a reference to the aligned field.  */
1220             gnu_type = build_reference_type (gnu_type);
1221             gnu_expr
1222               = build_unary_op
1223                 (ADDR_EXPR, gnu_type,
1224                  build_component_ref (gnu_new_var, NULL_TREE,
1225                                       TYPE_FIELDS (gnu_new_type), false));
1226
1227             gnu_size = NULL_TREE;
1228             used_by_ref = true;
1229             const_flag = true;
1230           }
1231
1232         if (const_flag)
1233           gnu_type = build_qualified_type (gnu_type, (TYPE_QUALS (gnu_type)
1234                                                       | TYPE_QUAL_CONST));
1235
1236         /* Convert the expression to the type of the object except in the
1237            case where the object's type is unconstrained or the object's type
1238            is a padded record whose field is of self-referential size.  In
1239            the former case, converting will generate unnecessary evaluations
1240            of the CONSTRUCTOR to compute the size and in the latter case, we
1241            want to only copy the actual data.  */
1242         if (gnu_expr
1243             && TREE_CODE (gnu_type) != UNCONSTRAINED_ARRAY_TYPE
1244             && !CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type))
1245             && !(TREE_CODE (gnu_type) == RECORD_TYPE
1246                  && TYPE_IS_PADDING_P (gnu_type)
1247                  && (CONTAINS_PLACEHOLDER_P
1248                      (TYPE_SIZE (TREE_TYPE (TYPE_FIELDS (gnu_type)))))))
1249           gnu_expr = convert (gnu_type, gnu_expr);
1250
1251         /* If this name is external or there was a name specified, use it,
1252            unless this is a VMS exception object since this would conflict
1253            with the symbol we need to export in addition.  Don't use the
1254            Interface_Name if there is an address clause (see CD30005).  */
1255         if (!Is_VMS_Exception (gnat_entity)
1256             && ((Present (Interface_Name (gnat_entity))
1257                  && No (Address_Clause (gnat_entity)))
1258                 || (Is_Public (gnat_entity)
1259                     && (!Is_Imported (gnat_entity)
1260                         || Is_Exported (gnat_entity)))))
1261           gnu_ext_name = create_concat_name (gnat_entity, 0);
1262
1263         /* If this is constant initialized to a static constant and the
1264            object has an aggregate type, force it to be statically
1265            allocated.  This will avoid an initialization copy.  */
1266         if (!static_p && const_flag
1267             && gnu_expr && TREE_CONSTANT (gnu_expr)
1268             && AGGREGATE_TYPE_P (gnu_type)
1269             && host_integerp (TYPE_SIZE_UNIT (gnu_type), 1)
1270             && !(TREE_CODE (gnu_type) == RECORD_TYPE
1271                  && TYPE_IS_PADDING_P (gnu_type)
1272                  && !host_integerp (TYPE_SIZE_UNIT
1273                                     (TREE_TYPE (TYPE_FIELDS (gnu_type))), 1)))
1274           static_p = true;
1275
1276         gnu_decl = create_var_decl (gnu_entity_id, gnu_ext_name, gnu_type,
1277                                     gnu_expr, const_flag,
1278                                     Is_Public (gnat_entity),
1279                                     imported_p || !definition,
1280                                     static_p, attr_list, gnat_entity);
1281         DECL_BY_REF_P (gnu_decl) = used_by_ref;
1282         DECL_POINTS_TO_READONLY_P (gnu_decl) = used_by_ref && inner_const_flag;
1283         if (TREE_CODE (gnu_decl) == VAR_DECL && renamed_obj)
1284           {
1285             SET_DECL_RENAMED_OBJECT (gnu_decl, renamed_obj);
1286             if (global_bindings_p ())
1287               {
1288                 DECL_RENAMING_GLOBAL_P (gnu_decl) = 1;
1289                 record_global_renaming_pointer (gnu_decl);
1290               }
1291           }
1292
1293         if (definition && DECL_SIZE_UNIT (gnu_decl)
1294             && get_block_jmpbuf_decl ()
1295             && (TREE_CODE (DECL_SIZE_UNIT (gnu_decl)) != INTEGER_CST
1296                 || (flag_stack_check == GENERIC_STACK_CHECK
1297                     && compare_tree_int (DECL_SIZE_UNIT (gnu_decl),
1298                                          STACK_CHECK_MAX_VAR_SIZE) > 0)))
1299           add_stmt_with_node (build_call_1_expr
1300                               (update_setjmp_buf_decl,
1301                                build_unary_op (ADDR_EXPR, NULL_TREE,
1302                                                get_block_jmpbuf_decl ())),
1303                               gnat_entity);
1304
1305         /* If we are defining an Out parameter and we're not optimizing,
1306            create a fake PARM_DECL for debugging purposes and make it
1307            point to the VAR_DECL.  Suppress debug info for the latter
1308            but make sure it will still live on the stack so it can be
1309            accessed from within the debugger through the PARM_DECL.  */
1310         if (kind == E_Out_Parameter && definition && !optimize)
1311           {
1312             tree param = create_param_decl (gnu_entity_id, gnu_type, false);
1313             gnat_pushdecl (param, gnat_entity);
1314             SET_DECL_VALUE_EXPR (param, gnu_decl);
1315             DECL_HAS_VALUE_EXPR_P (param) = 1;
1316             if (debug_info_p)
1317               debug_info_p = false;
1318             else
1319               DECL_IGNORED_P (param) = 1;
1320             TREE_ADDRESSABLE (gnu_decl) = 1;
1321           }
1322
1323         /* If this is a public constant or we're not optimizing and we're not
1324            making a VAR_DECL for it, make one just for export or debugger use.
1325            Likewise if the address is taken or if either the object or type is
1326            aliased.  Make an external declaration for a reference, unless this
1327            is a Standard entity since there no real symbol at the object level
1328            for these.  */
1329         if (TREE_CODE (gnu_decl) == CONST_DECL
1330             && (definition || Sloc (gnat_entity) > Standard_Location)
1331             && ((Is_Public (gnat_entity)
1332                  && !Present (Address_Clause (gnat_entity)))
1333                 || !optimize
1334                 || Address_Taken (gnat_entity)
1335                 || Is_Aliased (gnat_entity)
1336                 || Is_Aliased (Etype (gnat_entity))))
1337           {
1338             tree gnu_corr_var
1339               = create_true_var_decl (gnu_entity_id, gnu_ext_name, gnu_type,
1340                                       gnu_expr, true, Is_Public (gnat_entity),
1341                                       !definition, static_p, NULL,
1342                                       gnat_entity);
1343
1344             SET_DECL_CONST_CORRESPONDING_VAR (gnu_decl, gnu_corr_var);
1345
1346             /* As debugging information will be generated for the variable,
1347                do not generate information for the constant.  */
1348             DECL_IGNORED_P (gnu_decl) = 1;
1349           }
1350
1351         /* If this is declared in a block that contains a block with an
1352            exception handler, we must force this variable in memory to
1353            suppress an invalid optimization.  */
1354         if (Has_Nested_Block_With_Handler (Scope (gnat_entity))
1355             && Exception_Mechanism != Back_End_Exceptions)
1356           TREE_ADDRESSABLE (gnu_decl) = 1;
1357
1358         gnu_type = TREE_TYPE (gnu_decl);
1359
1360         /* Back-annotate Alignment and Esize of the object if not already
1361            known, except for when the object is actually a pointer to the
1362            real object, since alignment and size of a pointer don't have
1363            anything to do with those of the designated object.  Note that
1364            we pick the values of the type, not those of the object, to
1365            shield ourselves from low-level platform-dependent adjustments
1366            like alignment promotion.  This is both consistent with all the
1367            treatment above, where alignment and size are set on the type of
1368            the object and not on the object directly, and makes it possible
1369            to support confirming representation clauses in all cases.  */
1370
1371         if (!used_by_ref && Unknown_Alignment (gnat_entity))
1372           Set_Alignment (gnat_entity,
1373                          UI_From_Int (TYPE_ALIGN (gnu_type) / BITS_PER_UNIT));
1374
1375         if (!used_by_ref && Unknown_Esize (gnat_entity))
1376           {
1377             if (TREE_CODE (gnu_type) == RECORD_TYPE
1378                 && TYPE_CONTAINS_TEMPLATE_P (gnu_type))
1379               gnu_object_size
1380                 = TYPE_SIZE (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (gnu_type))));
1381
1382             Set_Esize (gnat_entity, annotate_value (gnu_object_size));
1383           }
1384       }
1385       break;
1386
1387     case E_Void:
1388       /* Return a TYPE_DECL for "void" that we previously made.  */
1389       gnu_decl = TYPE_NAME (void_type_node);
1390       break;
1391
1392     case E_Enumeration_Type:
1393       /* A special case, for the types Character and Wide_Character in
1394          Standard, we do not list all the literals.  So if the literals
1395          are not specified, make this an unsigned type.  */
1396       if (No (First_Literal (gnat_entity)))
1397         {
1398           gnu_type = make_unsigned_type (esize);
1399           TYPE_NAME (gnu_type) = gnu_entity_id;
1400
1401           /* Set TYPE_STRING_FLAG for Ada Character and Wide_Character types.
1402              This is needed by the DWARF-2 back-end to distinguish between
1403              unsigned integer types and character types.  */
1404           TYPE_STRING_FLAG (gnu_type) = 1;
1405           break;
1406         }
1407
1408       /* Normal case of non-character type, or non-Standard character type */
1409       {
1410         /* Here we have a list of enumeral constants in First_Literal.
1411            We make a CONST_DECL for each and build into GNU_LITERAL_LIST
1412            the list to be places into TYPE_FIELDS.  Each node in the list
1413            is a TREE_LIST node whose TREE_VALUE is the literal name
1414            and whose TREE_PURPOSE is the value of the literal.
1415
1416            Esize contains the number of bits needed to represent the enumeral
1417            type, Type_Low_Bound also points to the first literal and
1418            Type_High_Bound points to the last literal.  */
1419
1420         Entity_Id gnat_literal;
1421         tree gnu_literal_list = NULL_TREE;
1422
1423         if (Is_Unsigned_Type (gnat_entity))
1424           gnu_type = make_unsigned_type (esize);
1425         else
1426           gnu_type = make_signed_type (esize);
1427
1428         TREE_SET_CODE (gnu_type, ENUMERAL_TYPE);
1429
1430         for (gnat_literal = First_Literal (gnat_entity);
1431              Present (gnat_literal);
1432              gnat_literal = Next_Literal (gnat_literal))
1433           {
1434             tree gnu_value = UI_To_gnu (Enumeration_Rep (gnat_literal),
1435                                         gnu_type);
1436             tree gnu_literal
1437               = create_var_decl (get_entity_name (gnat_literal), NULL_TREE,
1438                                  gnu_type, gnu_value, true, false, false,
1439                                  false, NULL, gnat_literal);
1440
1441             save_gnu_tree (gnat_literal, gnu_literal, false);
1442             gnu_literal_list = tree_cons (DECL_NAME (gnu_literal),
1443                                           gnu_value, gnu_literal_list);
1444           }
1445
1446         TYPE_VALUES (gnu_type) = nreverse (gnu_literal_list);
1447
1448         /* Note that the bounds are updated at the end of this function
1449            because to avoid an infinite recursion when we get the bounds of
1450            this type, since those bounds are objects of this type.    */
1451       }
1452       break;
1453
1454     case E_Signed_Integer_Type:
1455     case E_Ordinary_Fixed_Point_Type:
1456     case E_Decimal_Fixed_Point_Type:
1457       /* For integer types, just make a signed type the appropriate number
1458          of bits.  */
1459       gnu_type = make_signed_type (esize);
1460       break;
1461
1462     case E_Modular_Integer_Type:
1463       /* For modular types, make the unsigned type of the proper number of
1464          bits and then set up the modulus, if required.  */
1465       {
1466         enum machine_mode mode;
1467         tree gnu_modulus;
1468         tree gnu_high = 0;
1469
1470         if (Is_Packed_Array_Type (gnat_entity))
1471           esize = UI_To_Int (RM_Size (gnat_entity));
1472
1473         /* Find the smallest mode at least ESIZE bits wide and make a class
1474            using that mode.  */
1475
1476         for (mode = GET_CLASS_NARROWEST_MODE (MODE_INT);
1477              GET_MODE_BITSIZE (mode) < esize;
1478              mode = GET_MODE_WIDER_MODE (mode))
1479           ;
1480
1481         gnu_type = make_unsigned_type (GET_MODE_BITSIZE (mode));
1482         TYPE_PACKED_ARRAY_TYPE_P (gnu_type)
1483           = (Is_Packed_Array_Type (gnat_entity)
1484              && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)));
1485
1486         /* Get the modulus in this type.  If it overflows, assume it is because
1487            it is equal to 2**Esize.  Note that there is no overflow checking
1488            done on unsigned type, so we detect the overflow by looking for
1489            a modulus of zero, which is otherwise invalid.  */
1490         gnu_modulus = UI_To_gnu (Modulus (gnat_entity), gnu_type);
1491
1492         if (!integer_zerop (gnu_modulus))
1493           {
1494             TYPE_MODULAR_P (gnu_type) = 1;
1495             SET_TYPE_MODULUS (gnu_type, gnu_modulus);
1496             gnu_high = fold_build2 (MINUS_EXPR, gnu_type, gnu_modulus,
1497                                     convert (gnu_type, integer_one_node));
1498           }
1499
1500         /* If we have to set TYPE_PRECISION different from its natural value,
1501            make a subtype to do do.  Likewise if there is a modulus and
1502            it is not one greater than TYPE_MAX_VALUE.  */
1503         if (TYPE_PRECISION (gnu_type) != esize
1504             || (TYPE_MODULAR_P (gnu_type)
1505                 && !tree_int_cst_equal (TYPE_MAX_VALUE (gnu_type), gnu_high)))
1506           {
1507             tree gnu_subtype = make_node (INTEGER_TYPE);
1508
1509             TYPE_NAME (gnu_type) = create_concat_name (gnat_entity, "UMT");
1510             TREE_TYPE (gnu_subtype) = gnu_type;
1511             TYPE_MIN_VALUE (gnu_subtype) = TYPE_MIN_VALUE (gnu_type);
1512             TYPE_MAX_VALUE (gnu_subtype)
1513               = TYPE_MODULAR_P (gnu_type)
1514                 ? gnu_high : TYPE_MAX_VALUE (gnu_type);
1515             TYPE_PRECISION (gnu_subtype) = esize;
1516             TYPE_UNSIGNED (gnu_subtype) = 1;
1517             TYPE_EXTRA_SUBTYPE_P (gnu_subtype) = 1;
1518             TYPE_PACKED_ARRAY_TYPE_P (gnu_subtype)
1519               = (Is_Packed_Array_Type (gnat_entity)
1520                  && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)));
1521             layout_type (gnu_subtype);
1522
1523             gnu_type = gnu_subtype;
1524           }
1525       }
1526       break;
1527
1528     case E_Signed_Integer_Subtype:
1529     case E_Enumeration_Subtype:
1530     case E_Modular_Integer_Subtype:
1531     case E_Ordinary_Fixed_Point_Subtype:
1532     case E_Decimal_Fixed_Point_Subtype:
1533
1534       /* For integral subtypes, we make a new INTEGER_TYPE.  Note
1535          that we do not want to call build_range_type since we would
1536          like each subtype node to be distinct.  This will be important
1537          when memory aliasing is implemented.
1538
1539          The TREE_TYPE field of the INTEGER_TYPE we make points to the
1540          parent type; this fact is used by the arithmetic conversion
1541          functions.
1542
1543          We elaborate the Ancestor_Subtype if it is not in the current
1544          unit and one of our bounds is non-static.  We do this to ensure
1545          consistent naming in the case where several subtypes share the same
1546          bounds by always elaborating the first such subtype first, thus
1547          using its name.  */
1548
1549       if (!definition
1550           && Present (Ancestor_Subtype (gnat_entity))
1551           && !In_Extended_Main_Code_Unit (Ancestor_Subtype (gnat_entity))
1552           && (!Compile_Time_Known_Value (Type_Low_Bound (gnat_entity))
1553               || !Compile_Time_Known_Value (Type_High_Bound (gnat_entity))))
1554         gnat_to_gnu_entity (Ancestor_Subtype (gnat_entity),
1555                             gnu_expr, 0);
1556
1557       gnu_type = make_node (INTEGER_TYPE);
1558       TREE_TYPE (gnu_type) = get_unpadded_type (Etype (gnat_entity));
1559
1560       /* Set the precision to the Esize except for bit-packed arrays and
1561          subtypes of Standard.Boolean.  */
1562       if (Is_Packed_Array_Type (gnat_entity)
1563           && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)))
1564         {
1565           esize = UI_To_Int (RM_Size (gnat_entity));
1566           TYPE_PACKED_ARRAY_TYPE_P (gnu_type) = 1;
1567         }
1568       else if (TREE_CODE (TREE_TYPE (gnu_type)) == BOOLEAN_TYPE)
1569         esize = 1;
1570
1571       TYPE_PRECISION (gnu_type) = esize;
1572
1573       TYPE_MIN_VALUE (gnu_type)
1574         = convert (TREE_TYPE (gnu_type),
1575                    elaborate_expression (Type_Low_Bound (gnat_entity),
1576                                          gnat_entity,
1577                                          get_identifier ("L"), definition, 1,
1578                                          Needs_Debug_Info (gnat_entity)));
1579
1580       TYPE_MAX_VALUE (gnu_type)
1581         = convert (TREE_TYPE (gnu_type),
1582                    elaborate_expression (Type_High_Bound (gnat_entity),
1583                                          gnat_entity,
1584                                          get_identifier ("U"), definition, 1,
1585                                          Needs_Debug_Info (gnat_entity)));
1586
1587       /* One of the above calls might have caused us to be elaborated,
1588          so don't blow up if so.  */
1589       if (present_gnu_tree (gnat_entity))
1590         {
1591           maybe_present = true;
1592           break;
1593         }
1594
1595       TYPE_BIASED_REPRESENTATION_P (gnu_type)
1596         = Has_Biased_Representation (gnat_entity);
1597
1598      /* This should be an unsigned type if the lower bound is constant
1599          and non-negative or if the base type is unsigned; a signed type
1600          otherwise.    */
1601       TYPE_UNSIGNED (gnu_type)
1602         = (TYPE_UNSIGNED (TREE_TYPE (gnu_type))
1603            || (TREE_CODE (TYPE_MIN_VALUE (gnu_type)) == INTEGER_CST
1604                && TREE_INT_CST_HIGH (TYPE_MIN_VALUE (gnu_type)) >= 0)
1605            || TYPE_BIASED_REPRESENTATION_P (gnu_type)
1606            || Is_Unsigned_Type (gnat_entity));
1607
1608       layout_type (gnu_type);
1609
1610       /* Inherit our alias set from what we're a subtype of.  Subtypes
1611          are not different types and a pointer can designate any instance
1612          within a subtype hierarchy.  */
1613       relate_alias_sets (gnu_type, TREE_TYPE (gnu_type), ALIAS_SET_COPY);
1614
1615       /* If the type we are dealing with is to represent a packed array,
1616          we need to have the bits left justified on big-endian targets
1617          and right justified on little-endian targets.  We also need to
1618          ensure that when the value is read (e.g. for comparison of two
1619          such values), we only get the good bits, since the unused bits
1620          are uninitialized.  Both goals are accomplished by wrapping the
1621          modular value in an enclosing struct.  */
1622       if (Is_Packed_Array_Type (gnat_entity)
1623           && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)))
1624         {
1625           tree gnu_field_type = gnu_type;
1626           tree gnu_field;
1627
1628           TYPE_RM_SIZE_NUM (gnu_field_type)
1629             = UI_To_gnu (RM_Size (gnat_entity), bitsizetype);
1630           gnu_type = make_node (RECORD_TYPE);
1631           TYPE_NAME (gnu_type) = create_concat_name (gnat_entity, "JM");
1632
1633           /* Propagate the alignment of the modular type to the record.
1634              This means that bitpacked arrays have "ceil" alignment for
1635              their size, which may seem counter-intuitive but makes it
1636              possible to easily overlay them on modular types.  */
1637           TYPE_ALIGN (gnu_type) = TYPE_ALIGN (gnu_field_type);
1638           TYPE_PACKED (gnu_type) = 1;
1639
1640           /* Create a stripped-down declaration of the original type, mainly
1641              for debugging.  */
1642           create_type_decl (get_entity_name (gnat_entity), gnu_field_type,
1643                             NULL, true, debug_info_p, gnat_entity);
1644
1645           /* Don't notify the field as "addressable", since we won't be taking
1646              it's address and it would prevent create_field_decl from making a
1647              bitfield.  */
1648           gnu_field = create_field_decl (get_identifier ("OBJECT"),
1649                                          gnu_field_type, gnu_type, 1, 0, 0, 0);
1650
1651           finish_record_type (gnu_type, gnu_field, 0, false);
1652           TYPE_JUSTIFIED_MODULAR_P (gnu_type) = 1;
1653           SET_TYPE_ADA_SIZE (gnu_type, bitsize_int (esize));
1654
1655           relate_alias_sets (gnu_type, gnu_field_type, ALIAS_SET_COPY);
1656         }
1657
1658       /* If the type we are dealing with has got a smaller alignment than the
1659          natural one, we need to wrap it up in a record type and under-align
1660          the latter.  We reuse the padding machinery for this purpose.  */
1661       else if (Known_Alignment (gnat_entity)
1662                && UI_Is_In_Int_Range (Alignment (gnat_entity))
1663                && (align = UI_To_Int (Alignment (gnat_entity)) * BITS_PER_UNIT)
1664                && align < TYPE_ALIGN (gnu_type))
1665         {
1666           tree gnu_field_type = gnu_type;
1667           tree gnu_field;
1668
1669           gnu_type = make_node (RECORD_TYPE);
1670           TYPE_NAME (gnu_type) = create_concat_name (gnat_entity, "PAD");
1671
1672           TYPE_ALIGN (gnu_type) = align;
1673           TYPE_PACKED (gnu_type) = 1;
1674
1675           /* Create a stripped-down declaration of the original type, mainly
1676              for debugging.  */
1677           create_type_decl (get_entity_name (gnat_entity), gnu_field_type,
1678                             NULL, true, debug_info_p, gnat_entity);
1679
1680           /* Don't notify the field as "addressable", since we won't be taking
1681              it's address and it would prevent create_field_decl from making a
1682              bitfield.  */
1683           gnu_field = create_field_decl (get_identifier ("OBJECT"),
1684                                          gnu_field_type, gnu_type, 1, 0, 0, 0);
1685
1686           finish_record_type (gnu_type, gnu_field, 0, false);
1687           TYPE_IS_PADDING_P (gnu_type) = 1;
1688           SET_TYPE_ADA_SIZE (gnu_type, bitsize_int (esize));
1689
1690           relate_alias_sets (gnu_type, gnu_field_type, ALIAS_SET_COPY);
1691         }
1692
1693       /* Otherwise reset the alignment lest we computed it above.  */
1694       else
1695         align = 0;
1696
1697       break;
1698
1699     case E_Floating_Point_Type:
1700       /* If this is a VAX floating-point type, use an integer of the proper
1701          size.  All the operations will be handled with ASM statements.  */
1702       if (Vax_Float (gnat_entity))
1703         {
1704           gnu_type = make_signed_type (esize);
1705           TYPE_VAX_FLOATING_POINT_P (gnu_type) = 1;
1706           SET_TYPE_DIGITS_VALUE (gnu_type,
1707                                  UI_To_gnu (Digits_Value (gnat_entity),
1708                                             sizetype));
1709           break;
1710         }
1711
1712       /* The type of the Low and High bounds can be our type if this is
1713          a type from Standard, so set them at the end of the function.  */
1714       gnu_type = make_node (REAL_TYPE);
1715       TYPE_PRECISION (gnu_type) = fp_size_to_prec (esize);
1716       layout_type (gnu_type);
1717       break;
1718
1719     case E_Floating_Point_Subtype:
1720       if (Vax_Float (gnat_entity))
1721         {
1722           gnu_type = gnat_to_gnu_type (Etype (gnat_entity));
1723           break;
1724         }
1725
1726       {
1727         if (!definition
1728             && Present (Ancestor_Subtype (gnat_entity))
1729             && !In_Extended_Main_Code_Unit (Ancestor_Subtype (gnat_entity))
1730             && (!Compile_Time_Known_Value (Type_Low_Bound (gnat_entity))
1731                 || !Compile_Time_Known_Value (Type_High_Bound (gnat_entity))))
1732           gnat_to_gnu_entity (Ancestor_Subtype (gnat_entity),
1733                               gnu_expr, 0);
1734
1735         gnu_type = make_node (REAL_TYPE);
1736         TREE_TYPE (gnu_type) = get_unpadded_type (Etype (gnat_entity));
1737         TYPE_PRECISION (gnu_type) = fp_size_to_prec (esize);
1738
1739         TYPE_MIN_VALUE (gnu_type)
1740           = convert (TREE_TYPE (gnu_type),
1741                      elaborate_expression (Type_Low_Bound (gnat_entity),
1742                                            gnat_entity, get_identifier ("L"),
1743                                            definition, 1,
1744                                            Needs_Debug_Info (gnat_entity)));
1745
1746         TYPE_MAX_VALUE (gnu_type)
1747           = convert (TREE_TYPE (gnu_type),
1748                      elaborate_expression (Type_High_Bound (gnat_entity),
1749                                            gnat_entity, get_identifier ("U"),
1750                                            definition, 1,
1751                                            Needs_Debug_Info (gnat_entity)));
1752
1753         /* One of the above calls might have caused us to be elaborated,
1754            so don't blow up if so.  */
1755         if (present_gnu_tree (gnat_entity))
1756           {
1757             maybe_present = true;
1758             break;
1759           }
1760
1761         layout_type (gnu_type);
1762
1763         /* Inherit our alias set from what we're a subtype of, as for
1764            integer subtypes.  */
1765         relate_alias_sets (gnu_type, TREE_TYPE (gnu_type), ALIAS_SET_COPY);
1766       }
1767     break;
1768
1769       /* Array and String Types and Subtypes
1770
1771          Unconstrained array types are represented by E_Array_Type and
1772          constrained array types are represented by E_Array_Subtype.  There
1773          are no actual objects of an unconstrained array type; all we have
1774          are pointers to that type.
1775
1776          The following fields are defined on array types and subtypes:
1777
1778                 Component_Type     Component type of the array.
1779                 Number_Dimensions  Number of dimensions (an int).
1780                 First_Index        Type of first index.  */
1781
1782     case E_String_Type:
1783     case E_Array_Type:
1784       {
1785         tree gnu_template_fields = NULL_TREE;
1786         tree gnu_template_type = make_node (RECORD_TYPE);
1787         tree gnu_ptr_template = build_pointer_type (gnu_template_type);
1788         tree gnu_fat_type = make_node (RECORD_TYPE);
1789         int ndim = Number_Dimensions (gnat_entity);
1790         int firstdim
1791           = (Convention (gnat_entity) == Convention_Fortran) ? ndim - 1 : 0;
1792         int nextdim
1793           = (Convention (gnat_entity) == Convention_Fortran) ? - 1 : 1;
1794         int index;
1795         tree *gnu_index_types = (tree *) alloca (ndim * sizeof (tree *));
1796         tree *gnu_temp_fields = (tree *) alloca (ndim * sizeof (tree *));
1797         tree gnu_comp_size = 0;
1798         tree gnu_max_size = size_one_node;
1799         tree gnu_max_size_unit;
1800         Entity_Id gnat_ind_subtype;
1801         Entity_Id gnat_ind_base_subtype;
1802         tree gnu_template_reference;
1803         tree tem;
1804
1805         TYPE_NAME (gnu_template_type)
1806           = create_concat_name (gnat_entity, "XUB");
1807
1808         /* Make a node for the array.  If we are not defining the array
1809            suppress expanding incomplete types.  */
1810         gnu_type = make_node (UNCONSTRAINED_ARRAY_TYPE);
1811
1812         if (!definition)
1813           defer_incomplete_level++, this_deferred = true;
1814
1815         /* Build the fat pointer type.  Use a "void *" object instead of
1816            a pointer to the array type since we don't have the array type
1817            yet (it will reference the fat pointer via the bounds).  */
1818         tem = chainon (chainon (NULL_TREE,
1819                                 create_field_decl (get_identifier ("P_ARRAY"),
1820                                                    ptr_void_type_node,
1821                                                    gnu_fat_type, 0, 0, 0, 0)),
1822                        create_field_decl (get_identifier ("P_BOUNDS"),
1823                                           gnu_ptr_template,
1824                                           gnu_fat_type, 0, 0, 0, 0));
1825
1826         /* Make sure we can put this into a register.  */
1827         TYPE_ALIGN (gnu_fat_type) = MIN (BIGGEST_ALIGNMENT, 2 * POINTER_SIZE);
1828
1829         /* Do not finalize this record type since the types of its fields
1830            are still incomplete at this point.  */
1831         finish_record_type (gnu_fat_type, tem, 0, true);
1832         TYPE_IS_FAT_POINTER_P (gnu_fat_type) = 1;
1833
1834         /* Build a reference to the template from a PLACEHOLDER_EXPR that
1835            is the fat pointer.  This will be used to access the individual
1836            fields once we build them.  */
1837         tem = build3 (COMPONENT_REF, gnu_ptr_template,
1838                       build0 (PLACEHOLDER_EXPR, gnu_fat_type),
1839                       TREE_CHAIN (TYPE_FIELDS (gnu_fat_type)), NULL_TREE);
1840         gnu_template_reference
1841           = build_unary_op (INDIRECT_REF, gnu_template_type, tem);
1842         TREE_READONLY (gnu_template_reference) = 1;
1843
1844         /* Now create the GCC type for each index and add the fields for
1845            that index to the template.  */
1846         for (index = firstdim, gnat_ind_subtype = First_Index (gnat_entity),
1847              gnat_ind_base_subtype
1848                = First_Index (Implementation_Base_Type (gnat_entity));
1849              index < ndim && index >= 0;
1850              index += nextdim,
1851              gnat_ind_subtype = Next_Index (gnat_ind_subtype),
1852              gnat_ind_base_subtype = Next_Index (gnat_ind_base_subtype))
1853           {
1854             char field_name[10];
1855             tree gnu_ind_subtype
1856               = get_unpadded_type (Base_Type (Etype (gnat_ind_subtype)));
1857             tree gnu_base_subtype
1858               = get_unpadded_type (Etype (gnat_ind_base_subtype));
1859             tree gnu_base_min
1860               = convert (sizetype, TYPE_MIN_VALUE (gnu_base_subtype));
1861             tree gnu_base_max
1862               = convert (sizetype, TYPE_MAX_VALUE (gnu_base_subtype));
1863             tree gnu_min_field, gnu_max_field, gnu_min, gnu_max;
1864
1865             /* Make the FIELD_DECLs for the minimum and maximum of this
1866                type and then make extractions of that field from the
1867                template.  */
1868             sprintf (field_name, "LB%d", index);
1869             gnu_min_field = create_field_decl (get_identifier (field_name),
1870                                                gnu_ind_subtype,
1871                                                gnu_template_type, 0, 0, 0, 0);
1872             field_name[0] = 'U';
1873             gnu_max_field = create_field_decl (get_identifier (field_name),
1874                                                gnu_ind_subtype,
1875                                                gnu_template_type, 0, 0, 0, 0);
1876
1877             Sloc_to_locus (Sloc (gnat_entity),
1878                            &DECL_SOURCE_LOCATION (gnu_min_field));
1879             Sloc_to_locus (Sloc (gnat_entity),
1880                            &DECL_SOURCE_LOCATION (gnu_max_field));
1881             gnu_temp_fields[index] = chainon (gnu_min_field, gnu_max_field);
1882
1883             /* We can't use build_component_ref here since the template
1884                type isn't complete yet.  */
1885             gnu_min = build3 (COMPONENT_REF, gnu_ind_subtype,
1886                               gnu_template_reference, gnu_min_field,
1887                               NULL_TREE);
1888             gnu_max = build3 (COMPONENT_REF, gnu_ind_subtype,
1889                               gnu_template_reference, gnu_max_field,
1890                               NULL_TREE);
1891             TREE_READONLY (gnu_min) = TREE_READONLY (gnu_max) = 1;
1892
1893             /* Make a range type with the new ranges, but using
1894                the Ada subtype.  Then we convert to sizetype.  */
1895             gnu_index_types[index]
1896               = create_index_type (convert (sizetype, gnu_min),
1897                                    convert (sizetype, gnu_max),
1898                                    build_range_type (gnu_ind_subtype,
1899                                                      gnu_min, gnu_max),
1900                                    gnat_entity);
1901             /* Update the maximum size of the array, in elements.  */
1902             gnu_max_size
1903               = size_binop (MULT_EXPR, gnu_max_size,
1904                             size_binop (PLUS_EXPR, size_one_node,
1905                                         size_binop (MINUS_EXPR, gnu_base_max,
1906                                                     gnu_base_min)));
1907
1908             TYPE_NAME (gnu_index_types[index])
1909               = create_concat_name (gnat_entity, field_name);
1910           }
1911
1912         for (index = 0; index < ndim; index++)
1913           gnu_template_fields
1914             = chainon (gnu_template_fields, gnu_temp_fields[index]);
1915
1916         /* Install all the fields into the template.  */
1917         finish_record_type (gnu_template_type, gnu_template_fields, 0, false);
1918         TYPE_READONLY (gnu_template_type) = 1;
1919
1920         /* Now make the array of arrays and update the pointer to the array
1921            in the fat pointer.  Note that it is the first field.  */
1922         tem = gnat_to_gnu_type (Component_Type (gnat_entity));
1923
1924         /* Try to get a smaller form of the component if needed.  */
1925         if ((Is_Packed (gnat_entity)
1926              || Has_Component_Size_Clause (gnat_entity))
1927             && !Is_Bit_Packed_Array (gnat_entity)
1928             && !Has_Aliased_Components (gnat_entity)
1929             && !Strict_Alignment (Component_Type (gnat_entity))
1930             && TREE_CODE (tem) == RECORD_TYPE
1931             && !TYPE_IS_FAT_POINTER_P (tem)
1932             && host_integerp (TYPE_SIZE (tem), 1))
1933           tem = make_packable_type (tem, false);
1934
1935         if (Has_Atomic_Components (gnat_entity))
1936           check_ok_for_atomic (tem, gnat_entity, true);
1937
1938         /* Get and validate any specified Component_Size, but if Packed,
1939            ignore it since the front end will have taken care of it.  */
1940         gnu_comp_size
1941           = validate_size (Component_Size (gnat_entity), tem,
1942                            gnat_entity,
1943                            (Is_Bit_Packed_Array (gnat_entity)
1944                             ? TYPE_DECL : VAR_DECL),
1945                            true, Has_Component_Size_Clause (gnat_entity));
1946
1947         /* If the component type is a RECORD_TYPE that has a self-referential
1948            size, use the maximum size.  */
1949         if (!gnu_comp_size && TREE_CODE (tem) == RECORD_TYPE
1950             && CONTAINS_PLACEHOLDER_P (TYPE_SIZE (tem)))
1951           gnu_comp_size = max_size (TYPE_SIZE (tem), true);
1952
1953         if (gnu_comp_size && !Is_Bit_Packed_Array (gnat_entity))
1954           {
1955             tree orig_tem;
1956             tem = make_type_from_size (tem, gnu_comp_size, false);
1957             orig_tem = tem;
1958             tem = maybe_pad_type (tem, gnu_comp_size, 0, gnat_entity,
1959                                   "C_PAD", false, definition, true);
1960             /* If a padding record was made, declare it now since it will
1961                never be declared otherwise.  This is necessary to ensure
1962                that its subtrees are properly marked.  */
1963             if (tem != orig_tem)
1964               create_type_decl (TYPE_NAME (tem), tem, NULL, true,
1965                                 debug_info_p, gnat_entity);
1966           }
1967
1968         if (Has_Volatile_Components (gnat_entity))
1969           tem = build_qualified_type (tem,
1970                                       TYPE_QUALS (tem) | TYPE_QUAL_VOLATILE);
1971
1972         /* If Component_Size is not already specified, annotate it with the
1973            size of the component.  */
1974         if (Unknown_Component_Size (gnat_entity))
1975           Set_Component_Size (gnat_entity, annotate_value (TYPE_SIZE (tem)));
1976
1977         gnu_max_size_unit = size_binop (MAX_EXPR, size_zero_node,
1978                                         size_binop (MULT_EXPR, gnu_max_size,
1979                                                     TYPE_SIZE_UNIT (tem)));
1980         gnu_max_size = size_binop (MAX_EXPR, bitsize_zero_node,
1981                                    size_binop (MULT_EXPR,
1982                                                convert (bitsizetype,
1983                                                         gnu_max_size),
1984                                                TYPE_SIZE (tem)));
1985
1986         for (index = ndim - 1; index >= 0; index--)
1987           {
1988             tem = build_array_type (tem, gnu_index_types[index]);
1989             TYPE_MULTI_ARRAY_P (tem) = (index > 0);
1990             if (array_type_has_nonaliased_component (gnat_entity, tem))
1991               TYPE_NONALIASED_COMPONENT (tem) = 1;
1992           }
1993
1994         /* If an alignment is specified, use it if valid.  But ignore it for
1995            types that represent the unpacked base type for packed arrays.  If
1996            the alignment was requested with an explicit user alignment clause,
1997            state so.  */
1998         if (No (Packed_Array_Type (gnat_entity))
1999             && Known_Alignment (gnat_entity))
2000           {
2001             gcc_assert (Present (Alignment (gnat_entity)));
2002             TYPE_ALIGN (tem)
2003               = validate_alignment (Alignment (gnat_entity), gnat_entity,
2004                                     TYPE_ALIGN (tem));
2005             if (Present (Alignment_Clause (gnat_entity)))
2006               TYPE_USER_ALIGN (tem) = 1;
2007           }
2008
2009         TYPE_CONVENTION_FORTRAN_P (tem)
2010           = (Convention (gnat_entity) == Convention_Fortran);
2011         TREE_TYPE (TYPE_FIELDS (gnu_fat_type)) = build_pointer_type (tem);
2012
2013         /* The result type is an UNCONSTRAINED_ARRAY_TYPE that indicates the
2014            corresponding fat pointer.  */
2015         TREE_TYPE (gnu_type) = TYPE_POINTER_TO (gnu_type)
2016           = TYPE_REFERENCE_TO (gnu_type) = gnu_fat_type;
2017         SET_TYPE_MODE (gnu_type, BLKmode);
2018         TYPE_ALIGN (gnu_type) = TYPE_ALIGN (tem);
2019         SET_TYPE_UNCONSTRAINED_ARRAY (gnu_fat_type, gnu_type);
2020
2021         /* If the maximum size doesn't overflow, use it.  */
2022         if (TREE_CODE (gnu_max_size) == INTEGER_CST
2023             && !TREE_OVERFLOW (gnu_max_size))
2024           TYPE_SIZE (tem)
2025             = size_binop (MIN_EXPR, gnu_max_size, TYPE_SIZE (tem));
2026         if (TREE_CODE (gnu_max_size_unit) == INTEGER_CST
2027             && !TREE_OVERFLOW (gnu_max_size_unit))
2028           TYPE_SIZE_UNIT (tem)
2029             = size_binop (MIN_EXPR, gnu_max_size_unit,
2030                           TYPE_SIZE_UNIT (tem));
2031
2032         create_type_decl (create_concat_name (gnat_entity, "XUA"),
2033                           tem, NULL, !Comes_From_Source (gnat_entity),
2034                           debug_info_p, gnat_entity);
2035
2036         /* Give the fat pointer type a name.  */
2037         create_type_decl (create_concat_name (gnat_entity, "XUP"),
2038                           gnu_fat_type, NULL, true,
2039                           debug_info_p, gnat_entity);
2040
2041        /* Create the type to be used as what a thin pointer designates: an
2042           record type for the object and its template with the field offsets
2043           shifted to have the template at a negative offset.  */
2044         tem = build_unc_object_type (gnu_template_type, tem,
2045                                      create_concat_name (gnat_entity, "XUT"));
2046         shift_unc_components_for_thin_pointers (tem);
2047
2048         SET_TYPE_UNCONSTRAINED_ARRAY (tem, gnu_type);
2049         TYPE_OBJECT_RECORD_TYPE (gnu_type) = tem;
2050
2051         /* Give the thin pointer type a name.  */
2052         create_type_decl (create_concat_name (gnat_entity, "XUX"),
2053                           build_pointer_type (tem), NULL, true,
2054                           debug_info_p, gnat_entity);
2055       }
2056       break;
2057
2058     case E_String_Subtype:
2059     case E_Array_Subtype:
2060
2061       /* This is the actual data type for array variables.  Multidimensional
2062          arrays are implemented in the gnu tree as arrays of arrays.  Note
2063          that for the moment arrays which have sparse enumeration subtypes as
2064          index components create sparse arrays, which is obviously space
2065          inefficient but so much easier to code for now.
2066
2067          Also note that the subtype never refers to the unconstrained
2068          array type, which is somewhat at variance with Ada semantics.
2069
2070          First check to see if this is simply a renaming of the array
2071          type.  If so, the result is the array type.  */
2072
2073       gnu_type = gnat_to_gnu_type (Etype (gnat_entity));
2074       if (!Is_Constrained (gnat_entity))
2075         break;
2076       else
2077         {
2078           int index;
2079           int array_dim = Number_Dimensions (gnat_entity);
2080           int first_dim
2081             = ((Convention (gnat_entity) == Convention_Fortran)
2082                ? array_dim - 1 : 0);
2083           int next_dim
2084             = (Convention (gnat_entity) == Convention_Fortran) ? -1 : 1;
2085           Entity_Id gnat_ind_subtype;
2086           Entity_Id gnat_ind_base_subtype;
2087           tree gnu_base_type = gnu_type;
2088           tree *gnu_index_type = (tree *) alloca (array_dim * sizeof (tree *));
2089           tree gnu_comp_size = NULL_TREE;
2090           tree gnu_max_size = size_one_node;
2091           tree gnu_max_size_unit;
2092           bool need_index_type_struct = false;
2093           bool max_overflow = false;
2094
2095           /* First create the gnu types for each index.  Create types for
2096              debugging information to point to the index types if the
2097              are not integer types, have variable bounds, or are
2098              wider than sizetype.  */
2099
2100           for (index = first_dim, gnat_ind_subtype = First_Index (gnat_entity),
2101                gnat_ind_base_subtype
2102                  = First_Index (Implementation_Base_Type (gnat_entity));
2103                index < array_dim && index >= 0;
2104                index += next_dim,
2105                gnat_ind_subtype = Next_Index (gnat_ind_subtype),
2106                gnat_ind_base_subtype = Next_Index (gnat_ind_base_subtype))
2107             {
2108               tree gnu_index_subtype
2109                 = get_unpadded_type (Etype (gnat_ind_subtype));
2110               tree gnu_min
2111                 = convert (sizetype, TYPE_MIN_VALUE (gnu_index_subtype));
2112               tree gnu_max
2113                 = convert (sizetype, TYPE_MAX_VALUE (gnu_index_subtype));
2114               tree gnu_base_subtype
2115                 = get_unpadded_type (Etype (gnat_ind_base_subtype));
2116               tree gnu_base_min
2117                 = convert (sizetype, TYPE_MIN_VALUE (gnu_base_subtype));
2118               tree gnu_base_max
2119                 = convert (sizetype, TYPE_MAX_VALUE (gnu_base_subtype));
2120               tree gnu_base_type = get_base_type (gnu_base_subtype);
2121               tree gnu_base_base_min
2122                 = convert (sizetype, TYPE_MIN_VALUE (gnu_base_type));
2123               tree gnu_base_base_max
2124                 = convert (sizetype, TYPE_MAX_VALUE (gnu_base_type));
2125               tree gnu_high;
2126               tree gnu_this_max;
2127
2128               /* If the minimum and maximum values both overflow in
2129                  SIZETYPE, but the difference in the original type
2130                  does not overflow in SIZETYPE, ignore the overflow
2131                  indications.  */
2132               if ((TYPE_PRECISION (gnu_index_subtype)
2133                    > TYPE_PRECISION (sizetype)
2134                    || TYPE_UNSIGNED (gnu_index_subtype)
2135                       != TYPE_UNSIGNED (sizetype))
2136                   && TREE_CODE (gnu_min) == INTEGER_CST
2137                   && TREE_CODE (gnu_max) == INTEGER_CST
2138                   && TREE_OVERFLOW (gnu_min) && TREE_OVERFLOW (gnu_max)
2139                   && (!TREE_OVERFLOW
2140                       (fold_build2 (MINUS_EXPR, gnu_index_subtype,
2141                                     TYPE_MAX_VALUE (gnu_index_subtype),
2142                                     TYPE_MIN_VALUE (gnu_index_subtype)))))
2143                 {
2144                   TREE_OVERFLOW (gnu_min) = 0;
2145                   TREE_OVERFLOW (gnu_max) = 0;
2146                 }
2147
2148               /* Similarly, if the range is null, use bounds of 1..0 for
2149                  the sizetype bounds.  */
2150               else if ((TYPE_PRECISION (gnu_index_subtype)
2151                         > TYPE_PRECISION (sizetype)
2152                        || TYPE_UNSIGNED (gnu_index_subtype)
2153                           != TYPE_UNSIGNED (sizetype))
2154                        && TREE_CODE (gnu_min) == INTEGER_CST
2155                        && TREE_CODE (gnu_max) == INTEGER_CST
2156                        && (TREE_OVERFLOW (gnu_min) || TREE_OVERFLOW (gnu_max))
2157                        && tree_int_cst_lt (TYPE_MAX_VALUE (gnu_index_subtype),
2158                                            TYPE_MIN_VALUE (gnu_index_subtype)))
2159                 gnu_min = size_one_node, gnu_max = size_zero_node;
2160
2161               /* Now compute the size of this bound.  We need to provide
2162                  GCC with an upper bound to use but have to deal with the
2163                  "superflat" case.  There are three ways to do this.  If we
2164                  can prove that the array can never be superflat, we can
2165                  just use the high bound of the index subtype.  If we can
2166                  prove that the low bound minus one can't overflow, we
2167                  can do this as MAX (hb, lb - 1).  Otherwise, we have to use
2168                  the expression hb >= lb ? hb : lb - 1.  */
2169               gnu_high = size_binop (MINUS_EXPR, gnu_min, size_one_node);
2170
2171               /* See if the base array type is already flat.  If it is, we
2172                  are probably compiling an ACVC test, but it will cause the
2173                  code below to malfunction if we don't handle it specially.  */
2174               if (TREE_CODE (gnu_base_min) == INTEGER_CST
2175                   && TREE_CODE (gnu_base_max) == INTEGER_CST
2176                   && !TREE_OVERFLOW (gnu_base_min)
2177                   && !TREE_OVERFLOW (gnu_base_max)
2178                   && tree_int_cst_lt (gnu_base_max, gnu_base_min))
2179                 gnu_high = size_zero_node, gnu_min = size_one_node;
2180
2181               /* If gnu_high is now an integer which overflowed, the array
2182                  cannot be superflat.  */
2183               else if (TREE_CODE (gnu_high) == INTEGER_CST
2184                        && TREE_OVERFLOW (gnu_high))
2185                 gnu_high = gnu_max;
2186               else if (TYPE_UNSIGNED (gnu_base_subtype)
2187                        || TREE_CODE (gnu_high) == INTEGER_CST)
2188                 gnu_high = size_binop (MAX_EXPR, gnu_max, gnu_high);
2189               else
2190                 gnu_high
2191                   = build_cond_expr
2192                     (sizetype, build_binary_op (GE_EXPR, integer_type_node,
2193                                                 gnu_max, gnu_min),
2194                      gnu_max, gnu_high);
2195
2196               gnu_index_type[index]
2197                 = create_index_type (gnu_min, gnu_high, gnu_index_subtype,
2198                                      gnat_entity);
2199
2200               /* Also compute the maximum size of the array.  Here we
2201                  see if any constraint on the index type of the base type
2202                  can be used in the case of self-referential bound on
2203                  the index type of the subtype.  We look for a non-"infinite"
2204                  and non-self-referential bound from any type involved and
2205                  handle each bound separately.  */
2206
2207               if ((TREE_CODE (gnu_min) == INTEGER_CST
2208                    && !TREE_OVERFLOW (gnu_min)
2209                    && !operand_equal_p (gnu_min, gnu_base_base_min, 0))
2210                   || !CONTAINS_PLACEHOLDER_P (gnu_min)
2211                   || !(TREE_CODE (gnu_base_min) == INTEGER_CST
2212                        && !TREE_OVERFLOW (gnu_base_min)))
2213                 gnu_base_min = gnu_min;
2214
2215               if ((TREE_CODE (gnu_max) == INTEGER_CST
2216                    && !TREE_OVERFLOW (gnu_max)
2217                    && !operand_equal_p (gnu_max, gnu_base_base_max, 0))
2218                   || !CONTAINS_PLACEHOLDER_P (gnu_max)
2219                   || !(TREE_CODE (gnu_base_max) == INTEGER_CST
2220                        && !TREE_OVERFLOW (gnu_base_max)))
2221                 gnu_base_max = gnu_max;
2222
2223               if ((TREE_CODE (gnu_base_min) == INTEGER_CST
2224                    && TREE_OVERFLOW (gnu_base_min))
2225                   || operand_equal_p (gnu_base_min, gnu_base_base_min, 0)
2226                   || (TREE_CODE (gnu_base_max) == INTEGER_CST
2227                       && TREE_OVERFLOW (gnu_base_max))
2228                   || operand_equal_p (gnu_base_max, gnu_base_base_max, 0))
2229                 max_overflow = true;
2230
2231               gnu_base_min = size_binop (MAX_EXPR, gnu_base_min, gnu_min);
2232               gnu_base_max = size_binop (MIN_EXPR, gnu_base_max, gnu_max);
2233
2234               gnu_this_max
2235                 = size_binop (MAX_EXPR,
2236                               size_binop (PLUS_EXPR, size_one_node,
2237                                           size_binop (MINUS_EXPR, gnu_base_max,
2238                                                       gnu_base_min)),
2239                               size_zero_node);
2240
2241               if (TREE_CODE (gnu_this_max) == INTEGER_CST
2242                   && TREE_OVERFLOW (gnu_this_max))
2243                 max_overflow = true;
2244
2245               gnu_max_size
2246                 = size_binop (MULT_EXPR, gnu_max_size, gnu_this_max);
2247
2248               if (!integer_onep (TYPE_MIN_VALUE (gnu_index_subtype))
2249                   || (TREE_CODE (TYPE_MAX_VALUE (gnu_index_subtype))
2250                       != INTEGER_CST)
2251                   || TREE_CODE (gnu_index_subtype) != INTEGER_TYPE
2252                   || (TREE_TYPE (gnu_index_subtype)
2253                       && (TREE_CODE (TREE_TYPE (gnu_index_subtype))
2254                           != INTEGER_TYPE))
2255                   || TYPE_BIASED_REPRESENTATION_P (gnu_index_subtype)
2256                   || (TYPE_PRECISION (gnu_index_subtype)
2257                       > TYPE_PRECISION (sizetype)))
2258                 need_index_type_struct = true;
2259             }
2260
2261           /* Then flatten: create the array of arrays.  For an array type
2262              used to implement a packed array, get the component type from
2263              the original array type since the representation clauses that
2264              can affect it are on the latter.  */
2265           if (Is_Packed_Array_Type (gnat_entity)
2266               && !Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)))
2267             {
2268               gnu_type = gnat_to_gnu_type (Original_Array_Type (gnat_entity));
2269               for (index = array_dim - 1; index >= 0; index--)
2270                 gnu_type = TREE_TYPE (gnu_type);
2271
2272               /* One of the above calls might have caused us to be elaborated,
2273                  so don't blow up if so.  */
2274               if (present_gnu_tree (gnat_entity))
2275                 {
2276                   maybe_present = true;
2277                   break;
2278                 }
2279             }
2280           else
2281             {
2282               gnu_type = gnat_to_gnu_type (Component_Type (gnat_entity));
2283
2284               /* One of the above calls might have caused us to be elaborated,
2285                  so don't blow up if so.  */
2286               if (present_gnu_tree (gnat_entity))
2287                 {
2288                   maybe_present = true;
2289                   break;
2290                 }
2291
2292               /* Try to get a smaller form of the component if needed.  */
2293               if ((Is_Packed (gnat_entity)
2294                    || Has_Component_Size_Clause (gnat_entity))
2295                   && !Is_Bit_Packed_Array (gnat_entity)
2296                   && !Has_Aliased_Components (gnat_entity)
2297                   && !Strict_Alignment (Component_Type (gnat_entity))
2298                   && TREE_CODE (gnu_type) == RECORD_TYPE
2299                   && !TYPE_IS_FAT_POINTER_P (gnu_type)
2300                   && host_integerp (TYPE_SIZE (gnu_type), 1))
2301                 gnu_type = make_packable_type (gnu_type, false);
2302
2303               /* Get and validate any specified Component_Size, but if Packed,
2304                  ignore it since the front end will have taken care of it.  */
2305               gnu_comp_size
2306                 = validate_size (Component_Size (gnat_entity), gnu_type,
2307                                  gnat_entity,
2308                                  (Is_Bit_Packed_Array (gnat_entity)
2309                                   ? TYPE_DECL : VAR_DECL), true,
2310                                  Has_Component_Size_Clause (gnat_entity));
2311
2312               /* If the component type is a RECORD_TYPE that has a
2313                  self-referential size, use the maximum size.  */
2314               if (!gnu_comp_size
2315                   && TREE_CODE (gnu_type) == RECORD_TYPE
2316                   && CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type)))
2317                 gnu_comp_size = max_size (TYPE_SIZE (gnu_type), true);
2318
2319               if (gnu_comp_size && !Is_Bit_Packed_Array (gnat_entity))
2320                 {
2321                   tree orig_gnu_type;
2322                   gnu_type
2323                     = make_type_from_size (gnu_type, gnu_comp_size, false);
2324                   orig_gnu_type = gnu_type;
2325                   gnu_type = maybe_pad_type (gnu_type, gnu_comp_size, 0,
2326                                              gnat_entity, "C_PAD", false,
2327                                              definition, true);
2328                   /* If a padding record was made, declare it now since it
2329                      will never be declared otherwise.  This is necessary
2330                      to ensure that its subtrees are properly marked.  */
2331                   if (gnu_type != orig_gnu_type)
2332                     create_type_decl (TYPE_NAME (gnu_type), gnu_type, NULL,
2333                                       true, debug_info_p, gnat_entity);
2334                 }
2335
2336               if (Has_Volatile_Components (Base_Type (gnat_entity)))
2337                 gnu_type = build_qualified_type (gnu_type,
2338                                                  (TYPE_QUALS (gnu_type)
2339                                                   | TYPE_QUAL_VOLATILE));
2340             }
2341
2342           gnu_max_size_unit = size_binop (MULT_EXPR, gnu_max_size,
2343                                           TYPE_SIZE_UNIT (gnu_type));
2344           gnu_max_size = size_binop (MULT_EXPR,
2345                                      convert (bitsizetype, gnu_max_size),
2346                                      TYPE_SIZE (gnu_type));
2347
2348           for (index = array_dim - 1; index >= 0; index --)
2349             {
2350               gnu_type = build_array_type (gnu_type, gnu_index_type[index]);
2351               TYPE_MULTI_ARRAY_P (gnu_type) = (index > 0);
2352               if (array_type_has_nonaliased_component (gnat_entity, gnu_type))
2353                 TYPE_NONALIASED_COMPONENT (gnu_type) = 1;
2354             }
2355
2356           /* Attach the TYPE_STUB_DECL in case we have a parallel type.  */
2357           if (need_index_type_struct)
2358             TYPE_STUB_DECL (gnu_type)
2359               = create_type_stub_decl (gnu_entity_id, gnu_type);
2360
2361           /* If we are at file level and this is a multi-dimensional array, we
2362              need to make a variable corresponding to the stride of the
2363              inner dimensions.   */
2364           if (global_bindings_p () && array_dim > 1)
2365             {
2366               tree gnu_str_name = get_identifier ("ST");
2367               tree gnu_arr_type;
2368
2369               for (gnu_arr_type = TREE_TYPE (gnu_type);
2370                    TREE_CODE (gnu_arr_type) == ARRAY_TYPE;
2371                    gnu_arr_type = TREE_TYPE (gnu_arr_type),
2372                    gnu_str_name = concat_id_with_name (gnu_str_name, "ST"))
2373                 {
2374                   tree eltype = TREE_TYPE (gnu_arr_type);
2375
2376                   TYPE_SIZE (gnu_arr_type)
2377                     = elaborate_expression_1 (gnat_entity, gnat_entity,
2378                                               TYPE_SIZE (gnu_arr_type),
2379                                               gnu_str_name, definition, 0);
2380
2381                   /* ??? For now, store the size as a multiple of the
2382                      alignment of the element type in bytes so that we
2383                      can see the alignment from the tree.  */
2384                   TYPE_SIZE_UNIT (gnu_arr_type)
2385                     = build_binary_op
2386                       (MULT_EXPR, sizetype,
2387                        elaborate_expression_1
2388                        (gnat_entity, gnat_entity,
2389                         build_binary_op (EXACT_DIV_EXPR, sizetype,
2390                                          TYPE_SIZE_UNIT (gnu_arr_type),
2391                                          size_int (TYPE_ALIGN (eltype)
2392                                                    / BITS_PER_UNIT)),
2393                         concat_id_with_name (gnu_str_name, "A_U"),
2394                         definition, 0),
2395                        size_int (TYPE_ALIGN (eltype) / BITS_PER_UNIT));
2396
2397                   /* ??? create_type_decl is not invoked on the inner types so
2398                      the MULT_EXPR node built above will never be marked.  */
2399                   mark_visited (&TYPE_SIZE_UNIT (gnu_arr_type));
2400                 }
2401             }
2402
2403           /* If we need to write out a record type giving the names of
2404              the bounds, do it now.  Make sure to reference the index
2405              types themselves, not just their names, as the debugger
2406              may fall back on them in some cases.  */
2407           if (need_index_type_struct && debug_info_p)
2408             {
2409               tree gnu_bound_rec = make_node (RECORD_TYPE);
2410               tree gnu_field_list = NULL_TREE;
2411               tree gnu_field;
2412
2413               TYPE_NAME (gnu_bound_rec)
2414                 = create_concat_name (gnat_entity, "XA");
2415
2416               for (index = array_dim - 1; index >= 0; index--)
2417                 {
2418                   tree gnu_index = TYPE_INDEX_TYPE (gnu_index_type[index]);
2419                   tree gnu_index_name = TYPE_NAME (gnu_index);
2420
2421                   if (TREE_CODE (gnu_index_name) == TYPE_DECL)
2422                     gnu_index_name = DECL_NAME (gnu_index_name);
2423
2424                   gnu_field = create_field_decl (gnu_index_name, gnu_index,
2425                                                  gnu_bound_rec,
2426                                                  0, NULL_TREE, NULL_TREE, 0);
2427                   TREE_CHAIN (gnu_field) = gnu_field_list;
2428                   gnu_field_list = gnu_field;
2429                 }
2430
2431               finish_record_type (gnu_bound_rec, gnu_field_list, 0, false);
2432               add_parallel_type (TYPE_STUB_DECL (gnu_type), gnu_bound_rec);
2433             }
2434
2435           TYPE_CONVENTION_FORTRAN_P (gnu_type)
2436             = (Convention (gnat_entity) == Convention_Fortran);
2437           TYPE_PACKED_ARRAY_TYPE_P (gnu_type)
2438             = (Is_Packed_Array_Type (gnat_entity)
2439                && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)));
2440
2441           /* If our size depends on a placeholder and the maximum size doesn't
2442              overflow, use it.  */
2443           if (CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type))
2444               && !(TREE_CODE (gnu_max_size) == INTEGER_CST
2445                    && TREE_OVERFLOW (gnu_max_size))
2446               && !(TREE_CODE (gnu_max_size_unit) == INTEGER_CST
2447                    && TREE_OVERFLOW (gnu_max_size_unit))
2448               && !max_overflow)
2449             {
2450               TYPE_SIZE (gnu_type) = size_binop (MIN_EXPR, gnu_max_size,
2451                                                  TYPE_SIZE (gnu_type));
2452               TYPE_SIZE_UNIT (gnu_type)
2453                 = size_binop (MIN_EXPR, gnu_max_size_unit,
2454                               TYPE_SIZE_UNIT (gnu_type));
2455             }
2456
2457           /* Set our alias set to that of our base type.  This gives all
2458              array subtypes the same alias set.  */
2459           relate_alias_sets (gnu_type, gnu_base_type, ALIAS_SET_COPY);
2460         }
2461
2462       /* If this is a packed type, make this type the same as the packed
2463          array type, but do some adjusting in the type first.  */
2464       if (Present (Packed_Array_Type (gnat_entity)))
2465         {
2466           Entity_Id gnat_index;
2467           tree gnu_inner_type;
2468
2469           /* First finish the type we had been making so that we output
2470              debugging information for it.  */
2471           gnu_type
2472             = build_qualified_type (gnu_type,
2473                                     (TYPE_QUALS (gnu_type)
2474                                      | (TYPE_QUAL_VOLATILE
2475                                         * Treat_As_Volatile (gnat_entity))));
2476
2477           /* Make it artificial only if the base type was artificial as well.
2478              That's sort of "morally" true and will make it possible for the
2479              debugger to look it up by name in DWARF more easily.  */
2480           gnu_decl
2481             = create_type_decl (gnu_entity_id, gnu_type, attr_list,
2482                                 !Comes_From_Source (gnat_entity)
2483                                 && !Comes_From_Source (Etype (gnat_entity)),
2484                                 debug_info_p, gnat_entity);
2485
2486           /* Save it as our equivalent in case the call below elaborates
2487              this type again.  */
2488           save_gnu_tree (gnat_entity, gnu_decl, false);
2489
2490           gnu_decl = gnat_to_gnu_entity (Packed_Array_Type (gnat_entity),
2491                                          NULL_TREE, 0);
2492           this_made_decl = true;
2493           gnu_type = TREE_TYPE (gnu_decl);
2494           save_gnu_tree (gnat_entity, NULL_TREE, false);
2495
2496           gnu_inner_type = gnu_type;
2497           while (TREE_CODE (gnu_inner_type) == RECORD_TYPE
2498                  && (TYPE_JUSTIFIED_MODULAR_P (gnu_inner_type)
2499                      || TYPE_IS_PADDING_P (gnu_inner_type)))
2500             gnu_inner_type = TREE_TYPE (TYPE_FIELDS (gnu_inner_type));
2501
2502           /* We need to point the type we just made to our index type so
2503              the actual bounds can be put into a template.  */
2504
2505           if ((TREE_CODE (gnu_inner_type) == ARRAY_TYPE
2506                && !TYPE_ACTUAL_BOUNDS (gnu_inner_type))
2507               || (TREE_CODE (gnu_inner_type) == INTEGER_TYPE
2508                   && !TYPE_HAS_ACTUAL_BOUNDS_P (gnu_inner_type)))
2509             {
2510               if (TREE_CODE (gnu_inner_type) == INTEGER_TYPE)
2511                 {
2512                   /* The TYPE_ACTUAL_BOUNDS field is also used for the modulus.
2513                      If it is, we need to make another type.  */
2514                   if (TYPE_MODULAR_P (gnu_inner_type))
2515                     {
2516                       tree gnu_subtype;
2517
2518                       gnu_subtype = make_node (INTEGER_TYPE);
2519
2520                       TREE_TYPE (gnu_subtype) = gnu_inner_type;
2521                       TYPE_MIN_VALUE (gnu_subtype)
2522                         = TYPE_MIN_VALUE (gnu_inner_type);
2523                       TYPE_MAX_VALUE (gnu_subtype)
2524                         = TYPE_MAX_VALUE (gnu_inner_type);
2525                       TYPE_PRECISION (gnu_subtype)
2526                         = TYPE_PRECISION (gnu_inner_type);
2527                       TYPE_UNSIGNED (gnu_subtype)
2528                         = TYPE_UNSIGNED (gnu_inner_type);
2529                       TYPE_EXTRA_SUBTYPE_P (gnu_subtype) = 1;
2530                       layout_type (gnu_subtype);
2531
2532                       gnu_inner_type = gnu_subtype;
2533                     }
2534
2535                   TYPE_HAS_ACTUAL_BOUNDS_P (gnu_inner_type) = 1;
2536                 }
2537
2538               SET_TYPE_ACTUAL_BOUNDS (gnu_inner_type, NULL_TREE);
2539
2540               for (gnat_index = First_Index (gnat_entity);
2541                    Present (gnat_index); gnat_index = Next_Index (gnat_index))
2542                 SET_TYPE_ACTUAL_BOUNDS
2543                   (gnu_inner_type,
2544                    tree_cons (NULL_TREE,
2545                               get_unpadded_type (Etype (gnat_index)),
2546                               TYPE_ACTUAL_BOUNDS (gnu_inner_type)));
2547
2548               if (Convention (gnat_entity) != Convention_Fortran)
2549                 SET_TYPE_ACTUAL_BOUNDS
2550                   (gnu_inner_type,
2551                    nreverse (TYPE_ACTUAL_BOUNDS (gnu_inner_type)));
2552
2553               if (TREE_CODE (gnu_type) == RECORD_TYPE
2554                   && TYPE_JUSTIFIED_MODULAR_P (gnu_type))
2555                 TREE_TYPE (TYPE_FIELDS (gnu_type)) = gnu_inner_type;
2556             }
2557         }
2558
2559       /* Abort if packed array with no packed array type field set.  */
2560       else
2561         gcc_assert (!Is_Packed (gnat_entity));
2562
2563       break;
2564
2565     case E_String_Literal_Subtype:
2566       /* Create the type for a string literal.  */
2567       {
2568         Entity_Id gnat_full_type
2569           = (IN (Ekind (Etype (gnat_entity)), Private_Kind)
2570              && Present (Full_View (Etype (gnat_entity)))
2571              ? Full_View (Etype (gnat_entity)) : Etype (gnat_entity));
2572         tree gnu_string_type = get_unpadded_type (gnat_full_type);
2573         tree gnu_string_array_type
2574           = TREE_TYPE (TREE_TYPE (TYPE_FIELDS (TREE_TYPE (gnu_string_type))));
2575         tree gnu_string_index_type
2576           = get_base_type (TREE_TYPE (TYPE_INDEX_TYPE
2577                                       (TYPE_DOMAIN (gnu_string_array_type))));
2578         tree gnu_lower_bound
2579           = convert (gnu_string_index_type,
2580                      gnat_to_gnu (String_Literal_Low_Bound (gnat_entity)));
2581         int length = UI_To_Int (String_Literal_Length (gnat_entity));
2582         tree gnu_length = ssize_int (length - 1);
2583         tree gnu_upper_bound
2584           = build_binary_op (PLUS_EXPR, gnu_string_index_type,
2585                              gnu_lower_bound,
2586                              convert (gnu_string_index_type, gnu_length));
2587         tree gnu_range_type
2588           = build_range_type (gnu_string_index_type,
2589                               gnu_lower_bound, gnu_upper_bound);
2590         tree gnu_index_type
2591           = create_index_type (convert (sizetype,
2592                                         TYPE_MIN_VALUE (gnu_range_type)),
2593                                convert (sizetype,
2594                                         TYPE_MAX_VALUE (gnu_range_type)),
2595                                gnu_range_type, gnat_entity);
2596
2597         gnu_type
2598           = build_array_type (gnat_to_gnu_type (Component_Type (gnat_entity)),
2599                               gnu_index_type);
2600         if (array_type_has_nonaliased_component (gnat_entity, gnu_type))
2601           TYPE_NONALIASED_COMPONENT (gnu_type) = 1;
2602         relate_alias_sets (gnu_type, gnu_string_type, ALIAS_SET_COPY);
2603       }
2604       break;
2605
2606     /* Record Types and Subtypes
2607
2608        The following fields are defined on record types:
2609
2610                 Has_Discriminants       True if the record has discriminants
2611                 First_Discriminant      Points to head of list of discriminants
2612                 First_Entity            Points to head of list of fields
2613                 Is_Tagged_Type          True if the record is tagged
2614
2615        Implementation of Ada records and discriminated records:
2616
2617        A record type definition is transformed into the equivalent of a C
2618        struct definition.  The fields that are the discriminants which are
2619        found in the Full_Type_Declaration node and the elements of the
2620        Component_List found in the Record_Type_Definition node.  The
2621        Component_List can be a recursive structure since each Variant of
2622        the Variant_Part of the Component_List has a Component_List.
2623
2624        Processing of a record type definition comprises starting the list of
2625        field declarations here from the discriminants and the calling the
2626        function components_to_record to add the rest of the fields from the
2627        component list and return the gnu type node.  The function
2628        components_to_record will call itself recursively as it traverses
2629        the tree.  */
2630
2631     case E_Record_Type:
2632       if (Has_Complex_Representation (gnat_entity))
2633         {
2634           gnu_type
2635             = build_complex_type
2636               (get_unpadded_type
2637                (Etype (Defining_Entity
2638                        (First (Component_Items
2639                                (Component_List
2640                                 (Type_Definition
2641                                  (Declaration_Node (gnat_entity)))))))));
2642
2643           break;
2644         }
2645
2646       {
2647         Node_Id full_definition = Declaration_Node (gnat_entity);
2648         Node_Id record_definition = Type_Definition (full_definition);
2649         Entity_Id gnat_field;
2650         tree gnu_field;
2651         tree gnu_field_list = NULL_TREE;
2652         tree gnu_get_parent;
2653         /* Set PACKED in keeping with gnat_to_gnu_field.  */
2654         int packed
2655           = Is_Packed (gnat_entity)
2656             ? 1
2657             : Component_Alignment (gnat_entity) == Calign_Storage_Unit
2658               ? -1
2659               : (Known_Alignment (gnat_entity)
2660                  || (Strict_Alignment (gnat_entity)
2661                      && Known_Static_Esize (gnat_entity)))
2662                 ? -2
2663                 : 0;
2664         bool has_rep = Has_Specified_Layout (gnat_entity);
2665         bool all_rep = has_rep;
2666         bool is_extension
2667           = (Is_Tagged_Type (gnat_entity)
2668              && Nkind (record_definition) == N_Derived_Type_Definition);
2669
2670         /* See if all fields have a rep clause.  Stop when we find one
2671            that doesn't.  */
2672         for (gnat_field = First_Entity (gnat_entity);
2673              Present (gnat_field) && all_rep;
2674              gnat_field = Next_Entity (gnat_field))
2675           if ((Ekind (gnat_field) == E_Component
2676                || Ekind (gnat_field) == E_Discriminant)
2677               && No (Component_Clause (gnat_field)))
2678             all_rep = false;
2679
2680         /* If this is a record extension, go a level further to find the
2681            record definition.  Also, verify we have a Parent_Subtype.  */
2682         if (is_extension)
2683           {
2684             if (!type_annotate_only
2685                 || Present (Record_Extension_Part (record_definition)))
2686               record_definition = Record_Extension_Part (record_definition);
2687
2688             gcc_assert (type_annotate_only
2689                         || Present (Parent_Subtype (gnat_entity)));
2690           }
2691
2692         /* Make a node for the record.  If we are not defining the record,
2693            suppress expanding incomplete types.  */
2694         gnu_type = make_node (tree_code_for_record_type (gnat_entity));
2695         TYPE_NAME (gnu_type) = gnu_entity_id;
2696         TYPE_PACKED (gnu_type) = (packed != 0) || has_rep;
2697
2698         if (!definition)
2699           defer_incomplete_level++, this_deferred = true;
2700
2701         /* If both a size and rep clause was specified, put the size in
2702            the record type now so that it can get the proper mode.  */
2703         if (has_rep && Known_Esize (gnat_entity))
2704           TYPE_SIZE (gnu_type) = UI_To_gnu (Esize (gnat_entity), sizetype);
2705
2706         /* Always set the alignment here so that it can be used to
2707            set the mode, if it is making the alignment stricter.  If
2708            it is invalid, it will be checked again below.  If this is to
2709            be Atomic, choose a default alignment of a word unless we know
2710            the size and it's smaller.  */
2711         if (Known_Alignment (gnat_entity))
2712           TYPE_ALIGN (gnu_type)
2713             = validate_alignment (Alignment (gnat_entity), gnat_entity, 0);
2714         else if (Is_Atomic (gnat_entity))
2715           TYPE_ALIGN (gnu_type)
2716             = esize >= BITS_PER_WORD ? BITS_PER_WORD : ceil_alignment (esize);
2717         /* If a type needs strict alignment, the minimum size will be the
2718            type size instead of the RM size (see validate_size).  Cap the
2719            alignment, lest it causes this type size to become too large.  */
2720         else if (Strict_Alignment (gnat_entity)
2721                  && Known_Static_Esize (gnat_entity))
2722           {
2723             unsigned int raw_size = UI_To_Int (Esize (gnat_entity));
2724             unsigned int raw_align = raw_size & -raw_size;
2725             if (raw_align < BIGGEST_ALIGNMENT)
2726               TYPE_ALIGN (gnu_type) = raw_align;
2727           }
2728         else
2729           TYPE_ALIGN (gnu_type) = 0;
2730
2731         /* If we have a Parent_Subtype, make a field for the parent.  If
2732            this record has rep clauses, force the position to zero.  */
2733         if (Present (Parent_Subtype (gnat_entity)))
2734           {
2735             Entity_Id gnat_parent = Parent_Subtype (gnat_entity);
2736             tree gnu_parent;
2737
2738             /* A major complexity here is that the parent subtype will
2739                reference our discriminants in its Discriminant_Constraint
2740                list.  But those must reference the parent component of this
2741                record which is of the parent subtype we have not built yet!
2742                To break the circle we first build a dummy COMPONENT_REF which
2743                represents the "get to the parent" operation and initialize
2744                each of those discriminants to a COMPONENT_REF of the above
2745                dummy parent referencing the corresponding discriminant of the
2746                base type of the parent subtype.  */
2747             gnu_get_parent = build3 (COMPONENT_REF, void_type_node,
2748                                      build0 (PLACEHOLDER_EXPR, gnu_type),
2749                                      build_decl (FIELD_DECL, NULL_TREE,
2750                                                  void_type_node),
2751                                      NULL_TREE);
2752
2753             if (Has_Discriminants (gnat_entity))
2754               for (gnat_field = First_Stored_Discriminant (gnat_entity);
2755                    Present (gnat_field);
2756                    gnat_field = Next_Stored_Discriminant (gnat_field))
2757                 if (Present (Corresponding_Discriminant (gnat_field)))
2758                   save_gnu_tree
2759                     (gnat_field,
2760                      build3 (COMPONENT_REF,
2761                              get_unpadded_type (Etype (gnat_field)),
2762                              gnu_get_parent,
2763                              gnat_to_gnu_field_decl (Corresponding_Discriminant
2764                                                      (gnat_field)),
2765                              NULL_TREE),
2766                      true);
2767
2768             /* Then we build the parent subtype.  */
2769             gnu_parent = gnat_to_gnu_type (gnat_parent);
2770
2771             /* Finally we fix up both kinds of twisted COMPONENT_REF we have
2772                initially built.  The discriminants must reference the fields
2773                of the parent subtype and not those of its base type for the
2774                placeholder machinery to properly work.  */
2775             if (Has_Discriminants (gnat_entity))
2776               for (gnat_field = First_Stored_Discriminant (gnat_entity);
2777                    Present (gnat_field);
2778                    gnat_field = Next_Stored_Discriminant (gnat_field))
2779                 if (Present (Corresponding_Discriminant (gnat_field)))
2780                   {
2781                     Entity_Id field = Empty;
2782                     for (field = First_Stored_Discriminant (gnat_parent);
2783                          Present (field);
2784                          field = Next_Stored_Discriminant (field))
2785                       if (same_discriminant_p (gnat_field, field))
2786                         break;
2787                     gcc_assert (Present (field));
2788                     TREE_OPERAND (get_gnu_tree (gnat_field), 1)
2789                       = gnat_to_gnu_field_decl (field);
2790                   }
2791
2792             /* The "get to the parent" COMPONENT_REF must be given its
2793                proper type...  */
2794             TREE_TYPE (gnu_get_parent) = gnu_parent;
2795
2796             /* ...and reference the _parent field of this record.  */
2797             gnu_field_list
2798               = create_field_decl (get_identifier
2799                                    (Get_Name_String (Name_uParent)),
2800                                    gnu_parent, gnu_type, 0,
2801                                    has_rep ? TYPE_SIZE (gnu_parent) : 0,
2802                                    has_rep ? bitsize_zero_node : 0, 1);
2803             DECL_INTERNAL_P (gnu_field_list) = 1;
2804             TREE_OPERAND (gnu_get_parent, 1) = gnu_field_list;
2805           }
2806
2807         /* Make the fields for the discriminants and put them into the record
2808            unless it's an Unchecked_Union.  */
2809         if (Has_Discriminants (gnat_entity))
2810           for (gnat_field = First_Stored_Discriminant (gnat_entity);
2811                Present (gnat_field);
2812                gnat_field = Next_Stored_Discriminant (gnat_field))
2813             {
2814               /* If this is a record extension and this discriminant
2815                  is the renaming of another discriminant, we've already
2816                  handled the discriminant above.  */
2817               if (Present (Parent_Subtype (gnat_entity))
2818                   && Present (Corresponding_Discriminant (gnat_field)))
2819                 continue;
2820
2821               gnu_field
2822                 = gnat_to_gnu_field (gnat_field, gnu_type, packed, definition);
2823
2824               /* Make an expression using a PLACEHOLDER_EXPR from the
2825                  FIELD_DECL node just created and link that with the
2826                  corresponding GNAT defining identifier.  Then add to the
2827                  list of fields.  */
2828               save_gnu_tree (gnat_field,
2829                              build3 (COMPONENT_REF, TREE_TYPE (gnu_field),
2830                                      build0 (PLACEHOLDER_EXPR,
2831                                              DECL_CONTEXT (gnu_field)),
2832                                      gnu_field, NULL_TREE),
2833                              true);
2834
2835               if (!Is_Unchecked_Union (gnat_entity))
2836                 {
2837                   TREE_CHAIN (gnu_field) = gnu_field_list;
2838                   gnu_field_list = gnu_field;
2839                 }
2840             }
2841
2842         /* Put the discriminants into the record (backwards), so we can
2843            know the appropriate discriminant to use for the names of the
2844            variants.  */
2845         TYPE_FIELDS (gnu_type) = gnu_field_list;
2846
2847         /* Add the listed fields into the record and finish it up.  */
2848         components_to_record (gnu_type, Component_List (record_definition),
2849                               gnu_field_list, packed, definition, NULL,
2850                               false, all_rep, false,
2851                               Is_Unchecked_Union (gnat_entity));
2852
2853         /* We used to remove the associations of the discriminants and
2854            _Parent for validity checking, but we may need them if there's
2855            Freeze_Node for a subtype used in this record.  */
2856         TYPE_VOLATILE (gnu_type) = Treat_As_Volatile (gnat_entity);
2857         TYPE_BY_REFERENCE_P (gnu_type) = Is_By_Reference_Type (gnat_entity);
2858
2859         /* If it is a tagged record force the type to BLKmode to insure
2860            that these objects will always be placed in memory.  Do the
2861            same thing for limited record types.  */
2862         if (Is_Tagged_Type (gnat_entity) || Is_Limited_Record (gnat_entity))
2863           SET_TYPE_MODE (gnu_type, BLKmode);
2864
2865         /* Fill in locations of fields.  */
2866         annotate_rep (gnat_entity, gnu_type);
2867
2868         /* If there are any entities in the chain corresponding to
2869            components that we did not elaborate, ensure we elaborate their
2870            types if they are Itypes.  */
2871         for (gnat_temp = First_Entity (gnat_entity);
2872              Present (gnat_temp); gnat_temp = Next_Entity (gnat_temp))
2873           if ((Ekind (gnat_temp) == E_Component
2874                || Ekind (gnat_temp) == E_Discriminant)
2875               && Is_Itype (Etype (gnat_temp))
2876               && !present_gnu_tree (gnat_temp))
2877             gnat_to_gnu_entity (Etype (gnat_temp), NULL_TREE, 0);
2878       }
2879       break;
2880
2881     case E_Class_Wide_Subtype:
2882       /* If an equivalent type is present, that is what we should use.
2883          Otherwise, fall through to handle this like a record subtype
2884          since it may have constraints.  */
2885       if (gnat_equiv_type != gnat_entity)
2886         {
2887           gnu_decl = gnat_to_gnu_entity (gnat_equiv_type, NULL_TREE, 0);
2888           maybe_present = true;
2889           break;
2890         }
2891
2892       /* ... fall through ... */
2893
2894     case E_Record_Subtype:
2895
2896       /* If Cloned_Subtype is Present it means this record subtype has
2897          identical layout to that type or subtype and we should use
2898          that GCC type for this one.  The front end guarantees that
2899          the component list is shared.  */
2900       if (Present (Cloned_Subtype (gnat_entity)))
2901         {
2902           gnu_decl = gnat_to_gnu_entity (Cloned_Subtype (gnat_entity),
2903                                          NULL_TREE, 0);
2904           maybe_present = true;
2905         }
2906
2907       /* Otherwise, first ensure the base type is elaborated.  Then, if we are
2908          changing the type, make a new type with each field having the
2909          type of the field in the new subtype but having the position
2910          computed by transforming every discriminant reference according
2911          to the constraints.  We don't see any difference between
2912          private and nonprivate type here since derivations from types should
2913          have been deferred until the completion of the private type.  */
2914       else
2915         {
2916           Entity_Id gnat_base_type = Implementation_Base_Type (gnat_entity);
2917           tree gnu_base_type;
2918           tree gnu_orig_type;
2919
2920           if (!definition)
2921             defer_incomplete_level++, this_deferred = true;
2922
2923           /* Get the base type initially for its alignment and sizes.  But
2924              if it is a padded type, we do all the other work with the
2925              unpadded type.  */
2926           gnu_base_type = gnat_to_gnu_type (gnat_base_type);
2927
2928           if (TREE_CODE (gnu_base_type) == RECORD_TYPE
2929               && TYPE_IS_PADDING_P (gnu_base_type))
2930             gnu_type = gnu_orig_type = TREE_TYPE (TYPE_FIELDS (gnu_base_type));
2931           else
2932             gnu_type = gnu_orig_type = gnu_base_type;
2933
2934           if (present_gnu_tree (gnat_entity))
2935             {
2936               maybe_present = true;
2937               break;
2938             }
2939
2940           /* When the type has discriminants, and these discriminants
2941              affect the shape of what it built, factor them in.
2942
2943              If we are making a subtype of an Unchecked_Union (must be an
2944              Itype), just return the type.
2945
2946              We can't just use Is_Constrained because private subtypes without
2947              discriminants of full types with discriminants with default
2948              expressions are Is_Constrained but aren't constrained!  */
2949
2950           if (IN (Ekind (gnat_base_type), Record_Kind)
2951               && !Is_For_Access_Subtype (gnat_entity)
2952               && !Is_Unchecked_Union (gnat_base_type)
2953               && Is_Constrained (gnat_entity)
2954               && Stored_Constraint (gnat_entity) != No_Elist
2955               && Present (Discriminant_Constraint (gnat_entity)))
2956             {
2957               Entity_Id gnat_field;
2958               tree gnu_field_list = 0;
2959               tree gnu_pos_list
2960                 = compute_field_positions (gnu_orig_type, NULL_TREE,
2961                                            size_zero_node, bitsize_zero_node,
2962                                            BIGGEST_ALIGNMENT);
2963               tree gnu_subst_list
2964                 = substitution_list (gnat_entity, gnat_base_type, NULL_TREE,
2965                                      definition);
2966               tree gnu_temp;
2967
2968               gnu_type = make_node (RECORD_TYPE);
2969               TYPE_NAME (gnu_type) = gnu_entity_id;
2970               TYPE_VOLATILE (gnu_type) = Treat_As_Volatile (gnat_entity);
2971
2972               /* Set the size, alignment and alias set of the new type to
2973                  match that of the old one, doing required substitutions.
2974                  We do it this early because we need the size of the new
2975                  type below to discard old fields if necessary.  */
2976               TYPE_SIZE (gnu_type) = TYPE_SIZE (gnu_base_type);
2977               TYPE_SIZE_UNIT (gnu_type) = TYPE_SIZE_UNIT (gnu_base_type);
2978               SET_TYPE_ADA_SIZE (gnu_type, TYPE_ADA_SIZE (gnu_base_type));
2979               TYPE_ALIGN (gnu_type) = TYPE_ALIGN (gnu_base_type);
2980               relate_alias_sets (gnu_type, gnu_base_type, ALIAS_SET_COPY);
2981
2982               if (CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type)))
2983                 for (gnu_temp = gnu_subst_list;
2984                      gnu_temp; gnu_temp = TREE_CHAIN (gnu_temp))
2985                   TYPE_SIZE (gnu_type)
2986                     = substitute_in_expr (TYPE_SIZE (gnu_type),
2987                                           TREE_PURPOSE (gnu_temp),
2988                                           TREE_VALUE (gnu_temp));
2989
2990               if (CONTAINS_PLACEHOLDER_P (TYPE_SIZE_UNIT (gnu_type)))
2991                 for (gnu_temp = gnu_subst_list;
2992                      gnu_temp; gnu_temp = TREE_CHAIN (gnu_temp))
2993                   TYPE_SIZE_UNIT (gnu_type)
2994                     = substitute_in_expr (TYPE_SIZE_UNIT (gnu_type),
2995                                           TREE_PURPOSE (gnu_temp),
2996                                           TREE_VALUE (gnu_temp));
2997
2998               if (CONTAINS_PLACEHOLDER_P (TYPE_ADA_SIZE (gnu_type)))
2999                 for (gnu_temp = gnu_subst_list;
3000                      gnu_temp; gnu_temp = TREE_CHAIN (gnu_temp))
3001                   SET_TYPE_ADA_SIZE
3002                     (gnu_type, substitute_in_expr (TYPE_ADA_SIZE (gnu_type),
3003                                                    TREE_PURPOSE (gnu_temp),
3004                                                    TREE_VALUE (gnu_temp)));
3005
3006               for (gnat_field = First_Entity (gnat_entity);
3007                    Present (gnat_field); gnat_field = Next_Entity (gnat_field))
3008                 if ((Ekind (gnat_field) == E_Component
3009                      || Ekind (gnat_field) == E_Discriminant)
3010                     && (Underlying_Type (Scope (Original_Record_Component
3011                                                 (gnat_field)))
3012                         == gnat_base_type)
3013                     && (No (Corresponding_Discriminant (gnat_field))
3014                         || !Is_Tagged_Type (gnat_base_type)))
3015                   {
3016                     tree gnu_old_field
3017                       = gnat_to_gnu_field_decl (Original_Record_Component
3018                                                 (gnat_field));
3019                     tree gnu_offset
3020                       = TREE_VALUE (purpose_member (gnu_old_field,
3021                                                     gnu_pos_list));
3022                     tree gnu_pos = TREE_PURPOSE (gnu_offset);
3023                     tree gnu_bitpos = TREE_VALUE (TREE_VALUE (gnu_offset));
3024                     tree gnu_field_type
3025                       = gnat_to_gnu_type (Etype (gnat_field));
3026                     tree gnu_size = TYPE_SIZE (gnu_field_type);
3027                     tree gnu_new_pos = NULL_TREE;
3028                     unsigned int offset_align
3029                       = tree_low_cst (TREE_PURPOSE (TREE_VALUE (gnu_offset)),
3030                                       1);
3031                     tree gnu_field;
3032
3033                     /* If there was a component clause, the field types must be
3034                        the same for the type and subtype, so copy the data from
3035                        the old field to avoid recomputation here.  Also if the
3036                        field is justified modular and the optimization in
3037                        gnat_to_gnu_field was applied.  */
3038                     if (Present (Component_Clause
3039                                  (Original_Record_Component (gnat_field)))
3040                         || (TREE_CODE (gnu_field_type) == RECORD_TYPE
3041                             && TYPE_JUSTIFIED_MODULAR_P (gnu_field_type)
3042                             && TREE_TYPE (TYPE_FIELDS (gnu_field_type))
3043                                == TREE_TYPE (gnu_old_field)))
3044                       {
3045                         gnu_size = DECL_SIZE (gnu_old_field);
3046                         gnu_field_type = TREE_TYPE (gnu_old_field);
3047                       }
3048
3049                     /* If the old field was packed and of constant size, we
3050                        have to get the old size here, as it might differ from
3051                        what the Etype conveys and the latter might overlap
3052                        onto the following field.  Try to arrange the type for
3053                        possible better packing along the way.  */
3054                     else if (DECL_PACKED (gnu_old_field)
3055                              && TREE_CODE (DECL_SIZE (gnu_old_field))
3056                                 == INTEGER_CST)
3057                       {
3058                         gnu_size = DECL_SIZE (gnu_old_field);
3059                         if (TREE_CODE (gnu_field_type) == RECORD_TYPE
3060                             && !TYPE_IS_FAT_POINTER_P (gnu_field_type)
3061                             && host_integerp (TYPE_SIZE (gnu_field_type), 1))
3062                           gnu_field_type
3063                             = make_packable_type (gnu_field_type, true);
3064                       }
3065
3066                     if (CONTAINS_PLACEHOLDER_P (gnu_pos))
3067                       for (gnu_temp = gnu_subst_list;
3068                            gnu_temp; gnu_temp = TREE_CHAIN (gnu_temp))
3069                         gnu_pos = substitute_in_expr (gnu_pos,
3070                                                       TREE_PURPOSE (gnu_temp),
3071                                                       TREE_VALUE (gnu_temp));
3072
3073                     /* If the position is now a constant, we can set it as the
3074                        position of the field when we make it.  Otherwise, we need
3075                        to deal with it specially below.  */
3076                     if (TREE_CONSTANT (gnu_pos))
3077                       {
3078                         gnu_new_pos = bit_from_pos (gnu_pos, gnu_bitpos);
3079
3080                         /* Discard old fields that are outside the new type.
3081                            This avoids confusing code scanning it to decide
3082                            how to pass it to functions on some platforms.  */
3083                         if (TREE_CODE (gnu_new_pos) == INTEGER_CST
3084                             && TREE_CODE (TYPE_SIZE (gnu_type)) == INTEGER_CST
3085                             && !integer_zerop (gnu_size)
3086                             && !tree_int_cst_lt (gnu_new_pos,
3087                                                  TYPE_SIZE (gnu_type)))
3088                           continue;
3089                       }
3090
3091                     gnu_field
3092                       = create_field_decl
3093                         (DECL_NAME (gnu_old_field), gnu_field_type, gnu_type,
3094                          DECL_PACKED (gnu_old_field), gnu_size, gnu_new_pos,
3095                          !DECL_NONADDRESSABLE_P (gnu_old_field));
3096
3097                     if (!TREE_CONSTANT (gnu_pos))
3098                       {
3099                         normalize_offset (&gnu_pos, &gnu_bitpos, offset_align);
3100                         DECL_FIELD_OFFSET (gnu_field) = gnu_pos;
3101                         DECL_FIELD_BIT_OFFSET (gnu_field) = gnu_bitpos;
3102                         SET_DECL_OFFSET_ALIGN (gnu_field, offset_align);
3103                         DECL_SIZE (gnu_field) = gnu_size;
3104                         DECL_SIZE_UNIT (gnu_field)
3105                           = convert (sizetype,
3106                                      size_binop (CEIL_DIV_EXPR, gnu_size,
3107                                                  bitsize_unit_node));
3108                         layout_decl (gnu_field, DECL_OFFSET_ALIGN (gnu_field));
3109                       }
3110
3111                     DECL_INTERNAL_P (gnu_field)
3112                       = DECL_INTERNAL_P (gnu_old_field);
3113                     SET_DECL_ORIGINAL_FIELD
3114                       (gnu_field, (DECL_ORIGINAL_FIELD (gnu_old_field)
3115                                    ? DECL_ORIGINAL_FIELD (gnu_old_field)
3116                                    : gnu_old_field));
3117                     DECL_DISCRIMINANT_NUMBER (gnu_field)
3118                       = DECL_DISCRIMINANT_NUMBER (gnu_old_field);
3119                     TREE_THIS_VOLATILE (gnu_field)
3120                       = TREE_THIS_VOLATILE (gnu_old_field);
3121
3122                     /* To match the layout crafted in components_to_record, if
3123                        this is the _Tag field, put it before any discriminants
3124                        instead of after them as for all other fields.  */
3125                     if (Chars (gnat_field) == Name_uTag)
3126                       gnu_field_list = chainon (gnu_field_list, gnu_field);
3127                     else
3128                       {
3129                         TREE_CHAIN (gnu_field) = gnu_field_list;
3130                         gnu_field_list = gnu_field;
3131                       }
3132
3133                     save_gnu_tree (gnat_field, gnu_field, false);
3134                   }
3135
3136               /* Now go through the entities again looking for Itypes that
3137                  we have not elaborated but should (e.g., Etypes of fields
3138                  that have Original_Components).  */
3139               for (gnat_field = First_Entity (gnat_entity);
3140                    Present (gnat_field); gnat_field = Next_Entity (gnat_field))
3141                 if ((Ekind (gnat_field) == E_Discriminant
3142                      || Ekind (gnat_field) == E_Component)
3143                     && !present_gnu_tree (Etype (gnat_field)))
3144                   gnat_to_gnu_entity (Etype (gnat_field), NULL_TREE, 0);
3145
3146               /* Do not finalize it since we're going to modify it below.  */
3147               gnu_field_list = nreverse (gnu_field_list);
3148               finish_record_type (gnu_type, gnu_field_list, 2, true);
3149
3150               /* Finalize size and mode.  */
3151               TYPE_SIZE (gnu_type) = variable_size (TYPE_SIZE (gnu_type));
3152               TYPE_SIZE_UNIT (gnu_type)
3153                 = variable_size (TYPE_SIZE_UNIT (gnu_type));
3154
3155               compute_record_mode (gnu_type);
3156
3157               /* Fill in locations of fields.  */
3158               annotate_rep (gnat_entity, gnu_type);
3159
3160               /* We've built a new type, make an XVS type to show what this
3161                  is a subtype of.  Some debuggers require the XVS type to be
3162                  output first, so do it in that order.  */
3163               if (debug_info_p)
3164                 {
3165                   tree gnu_subtype_marker = make_node (RECORD_TYPE);
3166                   tree gnu_orig_name = TYPE_NAME (gnu_orig_type);
3167
3168                   if (TREE_CODE (gnu_orig_name) == TYPE_DECL)
3169                     gnu_orig_name = DECL_NAME (gnu_orig_name);
3170
3171                   TYPE_NAME (gnu_subtype_marker)
3172                     = create_concat_name (gnat_entity, "XVS");
3173                   finish_record_type (gnu_subtype_marker,
3174                                       create_field_decl (gnu_orig_name,
3175                                                          integer_type_node,
3176                                                          gnu_subtype_marker,
3177                                                          0, NULL_TREE,
3178                                                          NULL_TREE, 0),
3179                                       0, false);
3180
3181                   add_parallel_type (TYPE_STUB_DECL (gnu_type),
3182                                      gnu_subtype_marker);
3183                 }
3184
3185               /* Now we can finalize it.  */
3186               rest_of_record_type_compilation (gnu_type);
3187             }
3188
3189           /* Otherwise, go down all the components in the new type and
3190              make them equivalent to those in the base type.  */
3191           else
3192             for (gnat_temp = First_Entity (gnat_entity); Present (gnat_temp);
3193                  gnat_temp = Next_Entity (gnat_temp))
3194               if ((Ekind (gnat_temp) == E_Discriminant
3195                    && !Is_Unchecked_Union (gnat_base_type))
3196                   || Ekind (gnat_temp) == E_Component)
3197                 save_gnu_tree (gnat_temp,
3198                                gnat_to_gnu_field_decl
3199                                (Original_Record_Component (gnat_temp)), false);
3200         }
3201       break;
3202
3203     case E_Access_Subprogram_Type:
3204       /* Use the special descriptor type for dispatch tables if needed,
3205          that is to say for the Prim_Ptr of a-tags.ads and its clones.
3206          Note that we are only required to do so for static tables in
3207          order to be compatible with the C++ ABI, but Ada 2005 allows
3208          to extend library level tagged types at the local level so
3209          we do it in the non-static case as well.  */
3210       if (TARGET_VTABLE_USES_DESCRIPTORS
3211           && Is_Dispatch_Table_Entity (gnat_entity))
3212         {
3213             gnu_type = fdesc_type_node;
3214             gnu_size = TYPE_SIZE (gnu_type);
3215             break;
3216         }
3217
3218       /* ... fall through ... */
3219
3220     case E_Anonymous_Access_Subprogram_Type:
3221       /* If we are not defining this entity, and we have incomplete
3222          entities being processed above us, make a dummy type and
3223          fill it in later.  */
3224       if (!definition && defer_incomplete_level != 0)
3225         {
3226           struct incomplete *p
3227             = (struct incomplete *) xmalloc (sizeof (struct incomplete));
3228
3229           gnu_type
3230             = build_pointer_type
3231               (make_dummy_type (Directly_Designated_Type (gnat_entity)));
3232           gnu_decl = create_type_decl (gnu_entity_id, gnu_type, attr_list,
3233                                        !Comes_From_Source (gnat_entity),
3234                                        debug_info_p, gnat_entity);
3235           this_made_decl = true;
3236           gnu_type = TREE_TYPE (gnu_decl);
3237           save_gnu_tree (gnat_entity, gnu_decl, false);
3238           saved = true;
3239
3240           p->old_type = TREE_TYPE (gnu_type);
3241           p->full_type = Directly_Designated_Type (gnat_entity);
3242           p->next = defer_incomplete_list;
3243           defer_incomplete_list = p;
3244           break;
3245         }
3246
3247       /* ... fall through ... */
3248
3249     case E_Allocator_Type:
3250     case E_Access_Type:
3251     case E_Access_Attribute_Type:
3252     case E_Anonymous_Access_Type:
3253     case E_General_Access_Type:
3254       {
3255         Entity_Id gnat_desig_type = Directly_Designated_Type (gnat_entity);
3256         Entity_Id gnat_desig_equiv = Gigi_Equivalent_Type (gnat_desig_type);
3257         bool is_from_limited_with
3258           = (IN (Ekind (gnat_desig_equiv), Incomplete_Kind)
3259              && From_With_Type (gnat_desig_equiv));
3260
3261         /* Get the "full view" of this entity.  If this is an incomplete
3262            entity from a limited with, treat its non-limited view as the full
3263            view.  Otherwise, if this is an incomplete or private type, use the
3264            full view.  In the former case, we might point to a private type,
3265            in which case, we need its full view.  Also, we want to look at the
3266            actual type used for the representation, so this takes a total of
3267            three steps.  */
3268         Entity_Id gnat_desig_full_direct_first
3269           = (is_from_limited_with ? Non_Limited_View (gnat_desig_equiv)
3270              : (IN (Ekind (gnat_desig_equiv), Incomplete_Or_Private_Kind)
3271                 ? Full_View (gnat_desig_equiv) : Empty));
3272         Entity_Id gnat_desig_full_direct
3273           = ((is_from_limited_with
3274               && Present (gnat_desig_full_direct_first)
3275               && IN (Ekind (gnat_desig_full_direct_first), Private_Kind))
3276              ? Full_View (gnat_desig_full_direct_first)
3277              : gnat_desig_full_direct_first);
3278         Entity_Id gnat_desig_full
3279           = Gigi_Equivalent_Type (gnat_desig_full_direct);
3280
3281         /* This the type actually used to represent the designated type,
3282            either gnat_desig_full or gnat_desig_equiv.  */
3283         Entity_Id gnat_desig_rep;
3284
3285         /* True if this is a pointer to an unconstrained array.  */
3286         bool is_unconstrained_array;
3287
3288         /* We want to know if we'll be seeing the freeze node for any
3289            incomplete type we may be pointing to.  */
3290         bool in_main_unit
3291           = (Present (gnat_desig_full)
3292              ? In_Extended_Main_Code_Unit (gnat_desig_full)
3293              : In_Extended_Main_Code_Unit (gnat_desig_type));
3294
3295         /* True if we make a dummy type here.  */
3296         bool got_fat_p = false;
3297         /* True if the dummy is a fat pointer.  */
3298         bool made_dummy = false;
3299         tree gnu_desig_type = NULL_TREE;
3300         enum machine_mode p_mode = mode_for_size (esize, MODE_INT, 0);
3301
3302         if (!targetm.valid_pointer_mode (p_mode))
3303           p_mode = ptr_mode;
3304
3305         /* If either the designated type or its full view is an unconstrained
3306            array subtype, replace it with the type it's a subtype of.  This
3307            avoids problems with multiple copies of unconstrained array types.
3308            Likewise, if the designated type is a subtype of an incomplete
3309            record type, use the parent type to avoid order of elaboration
3310            issues.  This can lose some code efficiency, but there is no
3311            alternative.  */
3312         if (Ekind (gnat_desig_equiv) == E_Array_Subtype
3313             && ! Is_Constrained (gnat_desig_equiv))
3314           gnat_desig_equiv = Etype (gnat_desig_equiv);
3315         if (Present (gnat_desig_full)
3316             && ((Ekind (gnat_desig_full) == E_Array_Subtype
3317                  && ! Is_Constrained (gnat_desig_full))
3318                 || (Ekind (gnat_desig_full) == E_Record_Subtype
3319                     && Ekind (Etype (gnat_desig_full)) == E_Record_Type)))
3320           gnat_desig_full = Etype (gnat_desig_full);
3321
3322         /* Now set the type that actually marks the representation of
3323            the designated type and also flag whether we have a unconstrained
3324            array.  */
3325         gnat_desig_rep = gnat_desig_full ? gnat_desig_full : gnat_desig_equiv;
3326         is_unconstrained_array
3327           = (Is_Array_Type (gnat_desig_rep)
3328              && ! Is_Constrained (gnat_desig_rep));
3329
3330         /* If we are pointing to an incomplete type whose completion is an
3331            unconstrained array, make a fat pointer type.  The two types in our
3332            fields will be pointers to dummy nodes and will be replaced in
3333            update_pointer_to.  Similarly, if the type itself is a dummy type or
3334            an unconstrained array.  Also make a dummy TYPE_OBJECT_RECORD_TYPE
3335            in case we have any thin pointers to it.  */
3336         if (is_unconstrained_array
3337             && (Present (gnat_desig_full)
3338                 || (present_gnu_tree (gnat_desig_equiv)
3339                     && TYPE_IS_DUMMY_P (TREE_TYPE
3340                                         (get_gnu_tree (gnat_desig_equiv))))
3341                 || (No (gnat_desig_full) && ! in_main_unit
3342                     && defer_incomplete_level != 0
3343                     && ! present_gnu_tree (gnat_desig_equiv))
3344                 || (in_main_unit && is_from_limited_with
3345                     && Present (Freeze_Node (gnat_desig_rep)))))
3346           {
3347             tree gnu_old
3348               = (present_gnu_tree (gnat_desig_rep)
3349                  ? TREE_TYPE (get_gnu_tree (gnat_desig_rep))
3350                  : make_dummy_type (gnat_desig_rep));
3351             tree fields;
3352
3353             /* Show the dummy we get will be a fat pointer.  */
3354             got_fat_p = made_dummy = true;
3355
3356             /* If the call above got something that has a pointer, that
3357                pointer is our type.  This could have happened either
3358                because the type was elaborated or because somebody
3359                else executed the code below.  */
3360             gnu_type = TYPE_POINTER_TO (gnu_old);
3361             if (!gnu_type)
3362               {
3363                 tree gnu_template_type = make_node (ENUMERAL_TYPE);
3364                 tree gnu_ptr_template = build_pointer_type (gnu_template_type);
3365                 tree gnu_array_type = make_node (ENUMERAL_TYPE);
3366                 tree gnu_ptr_array = build_pointer_type (gnu_array_type);
3367
3368                 TYPE_NAME (gnu_template_type)
3369                   = concat_id_with_name (get_entity_name (gnat_desig_equiv),
3370                                          "XUB");
3371                 TYPE_DUMMY_P (gnu_template_type) = 1;
3372
3373                 TYPE_NAME (gnu_array_type)
3374                   = concat_id_with_name (get_entity_name (gnat_desig_equiv),
3375                                          "XUA");
3376                 TYPE_DUMMY_P (gnu_array_type) = 1;
3377
3378                 gnu_type = make_node (RECORD_TYPE);
3379                 SET_TYPE_UNCONSTRAINED_ARRAY (gnu_type, gnu_old);
3380                 TYPE_POINTER_TO (gnu_old) = gnu_type;
3381
3382                 Sloc_to_locus (Sloc (gnat_entity), &input_location);
3383                 fields
3384                   = chainon (chainon (NULL_TREE,
3385                                       create_field_decl
3386                                       (get_identifier ("P_ARRAY"),
3387                                        gnu_ptr_array,
3388                                        gnu_type, 0, 0, 0, 0)),
3389                              create_field_decl (get_identifier ("P_BOUNDS"),
3390                                                 gnu_ptr_template,
3391                                                 gnu_type, 0, 0, 0, 0));
3392
3393                 /* Make sure we can place this into a register.  */
3394                 TYPE_ALIGN (gnu_type)
3395                   = MIN (BIGGEST_ALIGNMENT, 2 * POINTER_SIZE);
3396                 TYPE_IS_FAT_POINTER_P (gnu_type) = 1;
3397
3398                 /* Do not finalize this record type since the types of
3399                    its fields are incomplete.  */
3400                 finish_record_type (gnu_type, fields, 0, true);
3401
3402                 TYPE_OBJECT_RECORD_TYPE (gnu_old) = make_node (RECORD_TYPE);
3403                 TYPE_NAME (TYPE_OBJECT_RECORD_TYPE (gnu_old))
3404                   = concat_id_with_name (get_entity_name (gnat_desig_equiv),
3405                                          "XUT");
3406                 TYPE_DUMMY_P (TYPE_OBJECT_RECORD_TYPE (gnu_old)) = 1;
3407               }
3408           }
3409
3410         /* If we already know what the full type is, use it.  */
3411         else if (Present (gnat_desig_full)
3412                  && present_gnu_tree (gnat_desig_full))
3413           gnu_desig_type = TREE_TYPE (get_gnu_tree (gnat_desig_full));
3414
3415         /* Get the type of the thing we are to point to and build a pointer
3416            to it.  If it is a reference to an incomplete or private type with a
3417            full view that is a record, make a dummy type node and get the
3418            actual type later when we have verified it is safe.  */
3419         else if ((! in_main_unit
3420                   && ! present_gnu_tree (gnat_desig_equiv)
3421                   && Present (gnat_desig_full)
3422                   && ! present_gnu_tree (gnat_desig_full)
3423                   && Is_Record_Type (gnat_desig_full))
3424                  /* Likewise if we are pointing to a record or array and we
3425                     are to defer elaborating incomplete types.  We do this
3426                     since this access type may be the full view of some
3427                     private type.  Note that the unconstrained array case is
3428                     handled above.  */
3429                  || ((! in_main_unit || imported_p)
3430                      && defer_incomplete_level != 0
3431                      && ! present_gnu_tree (gnat_desig_equiv)
3432                      && ((Is_Record_Type (gnat_desig_rep)
3433                           || Is_Array_Type (gnat_desig_rep))))
3434                  /* If this is a reference from a limited_with type back to our
3435                     main unit and there's a Freeze_Node for it, either we have
3436                     already processed the declaration and made the dummy type,
3437                     in which case we just reuse the latter, or we have not yet,
3438                     in which case we make the dummy type and it will be reused
3439                     when the declaration is processed.  In both cases, the
3440                     pointer eventually created below will be automatically
3441                     adjusted when the Freeze_Node is processed.  Note that the
3442                     unconstrained array case is handled above.  */
3443                  ||  (in_main_unit && is_from_limited_with
3444                       && Present (Freeze_Node (gnat_desig_rep))))
3445           {
3446             gnu_desig_type = make_dummy_type (gnat_desig_equiv);
3447             made_dummy = true;
3448           }
3449
3450         /* Otherwise handle the case of a pointer to itself.  */
3451         else if (gnat_desig_equiv == gnat_entity)
3452           {
3453             gnu_type
3454               = build_pointer_type_for_mode (void_type_node, p_mode,
3455                                              No_Strict_Aliasing (gnat_entity));
3456             TREE_TYPE (gnu_type) = TYPE_POINTER_TO (gnu_type) = gnu_type;
3457           }
3458
3459         /* If expansion is disabled, the equivalent type of a concurrent
3460            type is absent, so build a dummy pointer type.  */
3461         else if (type_annotate_only && No (gnat_desig_equiv))
3462           gnu_type = ptr_void_type_node;
3463
3464         /* Finally, handle the straightforward case where we can just
3465            elaborate our designated type and point to it.  */
3466         else
3467           gnu_desig_type = gnat_to_gnu_type (gnat_desig_equiv);
3468
3469         /* It is possible that a call to gnat_to_gnu_type above resolved our
3470            type.  If so, just return it.  */
3471         if (present_gnu_tree (gnat_entity))
3472           {
3473             maybe_present = true;
3474             break;
3475           }
3476
3477         /* If we have a GCC type for the designated type, possibly modify it
3478            if we are pointing only to constant objects and then make a pointer
3479            to it.  Don't do this for unconstrained arrays.  */
3480         if (!gnu_type && gnu_desig_type)
3481           {
3482             if (Is_Access_Constant (gnat_entity)
3483                 && TREE_CODE (gnu_desig_type) != UNCONSTRAINED_ARRAY_TYPE)
3484               {
3485                 gnu_desig_type
3486                   = build_qualified_type
3487                     (gnu_desig_type,
3488                      TYPE_QUALS (gnu_desig_type) | TYPE_QUAL_CONST);
3489
3490                 /* Some extra processing is required if we are building a
3491                    pointer to an incomplete type (in the GCC sense).  We might
3492                    have such a type if we just made a dummy, or directly out
3493                    of the call to gnat_to_gnu_type above if we are processing
3494                    an access type for a record component designating the
3495                    record type itself.  */
3496                 if (TYPE_MODE (gnu_desig_type) == VOIDmode)
3497                   {
3498                     /* We must ensure that the pointer to variant we make will
3499                        be processed by update_pointer_to when the initial type
3500                        is completed.  Pretend we made a dummy and let further
3501                        processing act as usual.  */
3502                     made_dummy = true;
3503
3504                     /* We must ensure that update_pointer_to will not retrieve
3505                        the dummy variant when building a properly qualified
3506                        version of the complete type.  We take advantage of the
3507                        fact that get_qualified_type is requiring TYPE_NAMEs to
3508                        match to influence build_qualified_type and then also
3509                        update_pointer_to here.  */
3510                     TYPE_NAME (gnu_desig_type)
3511                       = create_concat_name (gnat_desig_type, "INCOMPLETE_CST");
3512                   }
3513               }
3514
3515             gnu_type
3516               = build_pointer_type_for_mode (gnu_desig_type, p_mode,
3517                                              No_Strict_Aliasing (gnat_entity));
3518           }
3519
3520         /* If we are not defining this object and we made a dummy pointer,
3521            save our current definition, evaluate the actual type, and replace
3522            the tentative type we made with the actual one.  If we are to defer
3523            actually looking up the actual type, make an entry in the
3524            deferred list.  If this is from a limited with, we have to defer
3525            to the end of the current spec in two cases: first if the
3526            designated type is in the current unit and second if the access
3527            type is.  */
3528         if ((! in_main_unit || is_from_limited_with) && made_dummy)
3529           {
3530             tree gnu_old_type
3531               = TYPE_FAT_POINTER_P (gnu_type)
3532                 ? TYPE_UNCONSTRAINED_ARRAY (gnu_type) : TREE_TYPE (gnu_type);
3533
3534             if (esize == POINTER_SIZE
3535                 && (got_fat_p || TYPE_FAT_POINTER_P (gnu_type)))
3536               gnu_type
3537                 = build_pointer_type
3538                   (TYPE_OBJECT_RECORD_TYPE
3539                    (TYPE_UNCONSTRAINED_ARRAY (gnu_type)));
3540
3541             gnu_decl = create_type_decl (gnu_entity_id, gnu_type, attr_list,
3542                                          !Comes_From_Source (gnat_entity),
3543                                          debug_info_p, gnat_entity);
3544             this_made_decl = true;
3545             gnu_type = TREE_TYPE (gnu_decl);
3546             save_gnu_tree (gnat_entity, gnu_decl, false);
3547             saved = true;
3548
3549             if (defer_incomplete_level == 0
3550                 && ! (is_from_limited_with
3551                       && (in_main_unit
3552                           || In_Extended_Main_Code_Unit (gnat_entity))))
3553               update_pointer_to (TYPE_MAIN_VARIANT (gnu_old_type),
3554                                  gnat_to_gnu_type (gnat_desig_equiv));
3555
3556               /* Note that the call to gnat_to_gnu_type here might have
3557                  updated gnu_old_type directly, in which case it is not a
3558                  dummy type any more when we get into update_pointer_to.
3559
3560                  This may happen for instance when the designated type is a
3561                  record type, because their elaboration starts with an
3562                  initial node from make_dummy_type, which may yield the same
3563                  node as the one we got.
3564
3565                  Besides, variants of this non-dummy type might have been
3566                  created along the way.  update_pointer_to is expected to
3567                  properly take care of those situations.  */
3568             else
3569               {
3570                 struct incomplete *p
3571                   = (struct incomplete *) xmalloc (sizeof
3572                                                    (struct incomplete));
3573                 struct incomplete **head
3574                   = (is_from_limited_with
3575                      && (in_main_unit
3576                          || In_Extended_Main_Code_Unit (gnat_entity))
3577                      ? &defer_limited_with : &defer_incomplete_list);
3578
3579                 p->old_type = gnu_old_type;
3580                 p->full_type = gnat_desig_equiv;
3581                 p->next = *head;
3582                 *head = p;
3583               }
3584           }
3585       }
3586       break;
3587
3588     case E_Access_Protected_Subprogram_Type:
3589     case E_Anonymous_Access_Protected_Subprogram_Type:
3590       if (type_annotate_only && No (gnat_equiv_type))
3591         gnu_type = ptr_void_type_node;
3592       else
3593         {
3594           /* The runtime representation is the equivalent type.  */
3595           gnu_type = gnat_to_gnu_type (gnat_equiv_type);
3596           maybe_present = true;
3597         }
3598
3599       if (Is_Itype (Directly_Designated_Type (gnat_entity))
3600           && !present_gnu_tree (Directly_Designated_Type (gnat_entity))
3601           && No (Freeze_Node (Directly_Designated_Type (gnat_entity)))
3602           && !Is_Record_Type (Scope (Directly_Designated_Type (gnat_entity))))
3603         gnat_to_gnu_entity (Directly_Designated_Type (gnat_entity),
3604                             NULL_TREE, 0);
3605
3606       break;
3607
3608     case E_Access_Subtype:
3609
3610       /* We treat this as identical to its base type; any constraint is
3611          meaningful only to the front end.
3612
3613          The designated type must be elaborated as well, if it does
3614          not have its own freeze node.  Designated (sub)types created
3615          for constrained components of records with discriminants are
3616          not frozen by the front end and thus not elaborated by gigi,
3617          because their use may appear before the base type is frozen,
3618          and because it is not clear that they are needed anywhere in
3619          Gigi.  With the current model, there is no correct place where
3620          they could be elaborated.  */
3621
3622       gnu_type = gnat_to_gnu_type (Etype (gnat_entity));
3623       if (Is_Itype (Directly_Designated_Type (gnat_entity))
3624           && !present_gnu_tree (Directly_Designated_Type (gnat_entity))
3625           && Is_Frozen (Directly_Designated_Type (gnat_entity))
3626           && No (Freeze_Node (Directly_Designated_Type (gnat_entity))))
3627         {
3628           /* If we are not defining this entity, and we have incomplete
3629              entities being processed above us, make a dummy type and
3630              elaborate it later.  */
3631           if (!definition && defer_incomplete_level != 0)
3632             {
3633               struct incomplete *p
3634                 = (struct incomplete *) xmalloc (sizeof (struct incomplete));
3635               tree gnu_ptr_type
3636                 = build_pointer_type
3637                   (make_dummy_type (Directly_Designated_Type (gnat_entity)));
3638
3639               p->old_type = TREE_TYPE (gnu_ptr_type);
3640               p->full_type = Directly_Designated_Type (gnat_entity);
3641               p->next = defer_incomplete_list;
3642               defer_incomplete_list = p;
3643             }
3644           else if (!IN (Ekind (Base_Type
3645                               (Directly_Designated_Type (gnat_entity))),
3646                        Incomplete_Or_Private_Kind))
3647             gnat_to_gnu_entity (Directly_Designated_Type (gnat_entity),
3648                                 NULL_TREE, 0);
3649         }
3650
3651       maybe_present = true;
3652       break;
3653
3654     /* Subprogram Entities
3655
3656        The following access functions are defined for subprograms (functions
3657        or procedures):
3658
3659                 First_Formal    The first formal parameter.
3660                 Is_Imported     Indicates that the subprogram has appeared in
3661                                 an INTERFACE or IMPORT pragma.  For now we
3662                                 assume that the external language is C.
3663                 Is_Exported     Likewise but for an EXPORT pragma.
3664                 Is_Inlined      True if the subprogram is to be inlined.
3665
3666        In addition for function subprograms we have:
3667
3668                 Etype           Return type of the function.
3669
3670        Each parameter is first checked by calling must_pass_by_ref on its
3671        type to determine if it is passed by reference.  For parameters which
3672        are copied in, if they are Ada In Out or Out parameters, their return
3673        value becomes part of a record which becomes the return type of the
3674        function (C function - note that this applies only to Ada procedures
3675        so there is no Ada return type).  Additional code to store back the
3676        parameters will be generated on the caller side.  This transformation
3677        is done here, not in the front-end.
3678
3679        The intended result of the transformation can be seen from the
3680        equivalent source rewritings that follow:
3681
3682                                                 struct temp {int a,b};
3683        procedure P (A,B: In Out ...) is         temp P (int A,B)
3684        begin                                    {
3685          ..                                       ..
3686        end P;                                     return {A,B};
3687                                                 }
3688
3689                                                 temp t;
3690        P(X,Y);                                  t = P(X,Y);
3691                                                 X = t.a , Y = t.b;
3692
3693        For subprogram types we need to perform mainly the same conversions to
3694        GCC form that are needed for procedures and function declarations.  The
3695        only difference is that at the end, we make a type declaration instead
3696        of a function declaration.  */
3697
3698     case E_Subprogram_Type:
3699     case E_Function:
3700     case E_Procedure:
3701       {
3702         /* The first GCC parameter declaration (a PARM_DECL node).  The
3703            PARM_DECL nodes are chained through the TREE_CHAIN field, so this
3704            actually is the head of this parameter list.  */
3705         tree gnu_param_list = NULL_TREE;
3706         /* Likewise for the stub associated with an exported procedure.  */
3707         tree gnu_stub_param_list = NULL_TREE;
3708         /* The type returned by a function.  If the subprogram is a procedure
3709            this type should be void_type_node.  */
3710         tree gnu_return_type = void_type_node;
3711         /* List of fields in return type of procedure with copy-in copy-out
3712            parameters.  */
3713         tree gnu_field_list = NULL_TREE;
3714         /* Non-null for subprograms containing parameters passed by copy-in
3715            copy-out (Ada In Out or Out parameters not passed by reference),
3716            in which case it is the list of nodes used to specify the values of
3717            the in out/out parameters that are returned as a record upon
3718            procedure return.  The TREE_PURPOSE of an element of this list is
3719            a field of the record and the TREE_VALUE is the PARM_DECL
3720            corresponding to that field.  This list will be saved in the
3721            TYPE_CI_CO_LIST field of the FUNCTION_TYPE node we create.  */
3722         tree gnu_return_list = NULL_TREE;
3723         /* If an import pragma asks to map this subprogram to a GCC builtin,
3724            this is the builtin DECL node.  */
3725         tree gnu_builtin_decl = NULL_TREE;
3726         /* For the stub associated with an exported procedure.  */
3727         tree gnu_stub_type = NULL_TREE, gnu_stub_name = NULL_TREE;
3728         tree gnu_ext_name = create_concat_name (gnat_entity, NULL);
3729         Entity_Id gnat_param;
3730         bool inline_flag = Is_Inlined (gnat_entity);
3731         bool public_flag = Is_Public (gnat_entity) || imported_p;
3732         bool extern_flag
3733           = (Is_Public (gnat_entity) && !definition) || imported_p;
3734
3735        /* The semantics of "pure" in Ada essentially matches that of "const"
3736           in the back-end.  In particular, both properties are orthogonal to
3737           the "nothrow" property if the EH circuitry is explicit in the
3738           internal representation of the back-end.  If we are to completely
3739           hide the EH circuitry from it, we need to declare that calls to pure
3740           Ada subprograms that can throw have side effects since they can
3741           trigger an "abnormal" transfer of control flow; thus they can be
3742           neither "const" nor "pure" in the back-end sense.  */
3743         bool const_flag
3744           = (Exception_Mechanism == Back_End_Exceptions
3745              && Is_Pure (gnat_entity));
3746
3747         bool volatile_flag = No_Return (gnat_entity);
3748         bool returns_by_ref = false;
3749         bool returns_unconstrained = false;
3750         bool returns_by_target_ptr = false;
3751         bool has_copy_in_out = false;
3752         bool has_stub = false;
3753         int parmnum;
3754
3755         if (kind == E_Subprogram_Type && !definition)
3756           /* A parameter may refer to this type, so defer completion
3757              of any incomplete types.  */
3758           defer_incomplete_level++, this_deferred = true;
3759
3760         /* If the subprogram has an alias, it is probably inherited, so
3761            we can use the original one.  If the original "subprogram"
3762            is actually an enumeration literal, it may be the first use
3763            of its type, so we must elaborate that type now.  */
3764         if (Present (Alias (gnat_entity)))
3765           {
3766             if (Ekind (Alias (gnat_entity)) == E_Enumeration_Literal)
3767               gnat_to_gnu_entity (Etype (Alias (gnat_entity)), NULL_TREE, 0);
3768
3769             gnu_decl = gnat_to_gnu_entity (Alias (gnat_entity),
3770                                            gnu_expr, 0);
3771
3772             /* Elaborate any Itypes in the parameters of this entity.  */
3773             for (gnat_temp = First_Formal_With_Extras (gnat_entity);
3774                  Present (gnat_temp);
3775                  gnat_temp = Next_Formal_With_Extras (gnat_temp))
3776               if (Is_Itype (Etype (gnat_temp)))
3777                 gnat_to_gnu_entity (Etype (gnat_temp), NULL_TREE, 0);
3778
3779             break;
3780           }
3781
3782         /* If this subprogram is expectedly bound to a GCC builtin, fetch the
3783            corresponding DECL node.
3784
3785            We still want the parameter associations to take place because the
3786            proper generation of calls depends on it (a GNAT parameter without
3787            a corresponding GCC tree has a very specific meaning), so we don't
3788            just break here.  */
3789         if (Convention (gnat_entity) == Convention_Intrinsic)
3790           gnu_builtin_decl = builtin_decl_for (gnu_ext_name);
3791
3792         /* ??? What if we don't find the builtin node above ? warn ? err ?
3793            In the current state we neither warn nor err, and calls will just
3794            be handled as for regular subprograms.  */
3795
3796         if (kind == E_Function || kind == E_Subprogram_Type)
3797           gnu_return_type = gnat_to_gnu_type (Etype (gnat_entity));
3798
3799         /* If this function returns by reference, make the actual
3800            return type of this function the pointer and mark the decl.  */
3801         if (Returns_By_Ref (gnat_entity))
3802           {
3803             returns_by_ref = true;
3804             gnu_return_type = build_pointer_type (gnu_return_type);
3805           }
3806
3807         /* If the Mechanism is By_Reference, ensure the return type uses
3808            the machine's by-reference mechanism, which may not the same
3809            as above (e.g., it might be by passing a fake parameter).  */
3810         else if (kind == E_Function
3811                  && Mechanism (gnat_entity) == By_Reference)
3812           {
3813             TREE_ADDRESSABLE (gnu_return_type) = 1;
3814
3815             /* We expect this bit to be reset by gigi shortly, so can avoid a
3816                type node copy here.  This actually also prevents troubles with
3817                the generation of debug information for the function, because
3818                we might have issued such info for this type already, and would
3819                be attaching a distinct type node to the function if we made a
3820                copy here.  */
3821           }
3822
3823         /* If we are supposed to return an unconstrained array,
3824            actually return a fat pointer and make a note of that.  Return
3825            a pointer to an unconstrained record of variable size.  */
3826         else if (TREE_CODE (gnu_return_type) == UNCONSTRAINED_ARRAY_TYPE)
3827           {
3828             gnu_return_type = TREE_TYPE (gnu_return_type);
3829             returns_unconstrained = true;
3830           }
3831
3832         /* If the type requires a transient scope, the result is allocated
3833            on the secondary stack, so the result type of the function is
3834            just a pointer.  */
3835         else if (Requires_Transient_Scope (Etype (gnat_entity)))
3836           {
3837             gnu_return_type = build_pointer_type (gnu_return_type);
3838             returns_unconstrained = true;
3839           }
3840
3841         /* If the type is a padded type and the underlying type would not
3842            be passed by reference or this function has a foreign convention,
3843            return the underlying type.  */
3844         else if (TREE_CODE (gnu_return_type) == RECORD_TYPE
3845                  && TYPE_IS_PADDING_P (gnu_return_type)
3846                  && (!default_pass_by_ref (TREE_TYPE
3847                                            (TYPE_FIELDS (gnu_return_type)))
3848                      || Has_Foreign_Convention (gnat_entity)))
3849           gnu_return_type = TREE_TYPE (TYPE_FIELDS (gnu_return_type));
3850
3851         /* If the return type has a non-constant size, we convert the function
3852            into a procedure and its caller will pass a pointer to an object as
3853            the first parameter when we call the function.  This can happen for
3854            an unconstrained type with a maximum size or a constrained type with
3855            a size not known at compile time.  */
3856         if (TYPE_SIZE_UNIT (gnu_return_type)
3857             && !TREE_CONSTANT (TYPE_SIZE_UNIT (gnu_return_type)))
3858           {
3859             returns_by_target_ptr = true;
3860             gnu_param_list
3861               = create_param_decl (get_identifier ("TARGET"),
3862                                    build_reference_type (gnu_return_type),
3863                                    true);
3864             gnu_return_type = void_type_node;
3865           }
3866
3867         /* If the return type has a size that overflows, we cannot have
3868            a function that returns that type.  This usage doesn't make
3869            sense anyway, so give an error here.  */
3870         if (TYPE_SIZE_UNIT (gnu_return_type)
3871             && TREE_CONSTANT (TYPE_SIZE_UNIT (gnu_return_type))
3872             && TREE_OVERFLOW (TYPE_SIZE_UNIT (gnu_return_type)))
3873           {
3874             post_error ("cannot return type whose size overflows",
3875                         gnat_entity);
3876             gnu_return_type = copy_node (gnu_return_type);
3877             TYPE_SIZE (gnu_return_type) = bitsize_zero_node;
3878             TYPE_SIZE_UNIT (gnu_return_type) = size_zero_node;
3879             TYPE_MAIN_VARIANT (gnu_return_type) = gnu_return_type;
3880             TYPE_NEXT_VARIANT (gnu_return_type) = NULL_TREE;
3881           }
3882
3883         /* Look at all our parameters and get the type of
3884            each.  While doing this, build a copy-out structure if
3885            we need one.  */
3886
3887         /* Loop over the parameters and get their associated GCC tree.
3888            While doing this, build a copy-out structure if we need one.  */
3889         for (gnat_param = First_Formal_With_Extras (gnat_entity), parmnum = 0;
3890              Present (gnat_param);
3891              gnat_param = Next_Formal_With_Extras (gnat_param), parmnum++)
3892           {
3893             tree gnu_param_name = get_entity_name (gnat_param);
3894             tree gnu_param_type = gnat_to_gnu_type (Etype (gnat_param));
3895             tree gnu_param, gnu_field;
3896             bool copy_in_copy_out = false;
3897             Mechanism_Type mech = Mechanism (gnat_param);
3898
3899             /* Builtins are expanded inline and there is no real call sequence
3900                involved.  So the type expected by the underlying expander is
3901                always the type of each argument "as is".  */
3902             if (gnu_builtin_decl)
3903               mech = By_Copy;
3904             /* Handle the first parameter of a valued procedure specially.  */
3905             else if (Is_Valued_Procedure (gnat_entity) && parmnum == 0)
3906               mech = By_Copy_Return;
3907             /* Otherwise, see if a Mechanism was supplied that forced this
3908                parameter to be passed one way or another.  */
3909             else if (mech == Default
3910                      || mech == By_Copy || mech == By_Reference)
3911               ;
3912             else if (By_Descriptor_Last <= mech && mech <= By_Descriptor)
3913               mech = By_Descriptor;
3914
3915             else if (By_Short_Descriptor_Last <= mech &&
3916                      mech <= By_Short_Descriptor)
3917               mech = By_Short_Descriptor;
3918
3919             else if (mech > 0)
3920               {
3921                 if (TREE_CODE (gnu_param_type) == UNCONSTRAINED_ARRAY_TYPE
3922                     || TREE_CODE (TYPE_SIZE (gnu_param_type)) != INTEGER_CST
3923                     || 0 < compare_tree_int (TYPE_SIZE (gnu_param_type),
3924                                              mech))
3925                   mech = By_Reference;
3926                 else
3927                   mech = By_Copy;
3928               }
3929             else
3930               {
3931                 post_error ("unsupported mechanism for&", gnat_param);
3932                 mech = Default;
3933               }
3934
3935             gnu_param
3936               = gnat_to_gnu_param (gnat_param, mech, gnat_entity,
3937                                    Has_Foreign_Convention (gnat_entity),
3938                                    &copy_in_copy_out);
3939
3940             /* We are returned either a PARM_DECL or a type if no parameter
3941                needs to be passed; in either case, adjust the type.  */
3942             if (DECL_P (gnu_param))
3943               gnu_param_type = TREE_TYPE (gnu_param);
3944             else
3945               {
3946                 gnu_param_type = gnu_param;
3947                 gnu_param = NULL_TREE;
3948               }
3949
3950             if (gnu_param)
3951               {
3952                 /* If it's an exported subprogram, we build a parameter list
3953                    in parallel, in case we need to emit a stub for it.  */
3954                 if (Is_Exported (gnat_entity))
3955                   {
3956                     gnu_stub_param_list
3957                       = chainon (gnu_param, gnu_stub_param_list);
3958                     /* Change By_Descriptor parameter to By_Reference for
3959                        the internal version of an exported subprogram.  */
3960                     if (mech == By_Descriptor || mech == By_Short_Descriptor)
3961                       {
3962                         gnu_param
3963                           = gnat_to_gnu_param (gnat_param, By_Reference,
3964                                                gnat_entity, false,
3965                                                &copy_in_copy_out);
3966                         has_stub = true;
3967                       }
3968                     else
3969                       gnu_param = copy_node (gnu_param);
3970                   }
3971
3972                 gnu_param_list = chainon (gnu_param, gnu_param_list);
3973                 Sloc_to_locus (Sloc (gnat_param),
3974                                &DECL_SOURCE_LOCATION (gnu_param));
3975                 save_gnu_tree (gnat_param, gnu_param, false);
3976
3977                 /* If a parameter is a pointer, this function may modify
3978                    memory through it and thus shouldn't be considered
3979                    a const function.  Also, the memory may be modified
3980                    between two calls, so they can't be CSE'ed.  The latter
3981                    case also handles by-ref parameters.  */
3982                 if (POINTER_TYPE_P (gnu_param_type)
3983                     || TYPE_FAT_POINTER_P (gnu_param_type))
3984                   const_flag = false;
3985               }
3986
3987             if (copy_in_copy_out)
3988               {
3989                 if (!has_copy_in_out)
3990                   {
3991                     gcc_assert (TREE_CODE (gnu_return_type) == VOID_TYPE);
3992                     gnu_return_type = make_node (RECORD_TYPE);
3993                     TYPE_NAME (gnu_return_type) = get_identifier ("RETURN");
3994                     has_copy_in_out = true;
3995                   }
3996
3997                 gnu_field = create_field_decl (gnu_param_name, gnu_param_type,
3998                                                gnu_return_type, 0, 0, 0, 0);
3999                 Sloc_to_locus (Sloc (gnat_param),
4000                                &DECL_SOURCE_LOCATION (gnu_field));
4001                 TREE_CHAIN (gnu_field) = gnu_field_list;
4002                 gnu_field_list = gnu_field;
4003                 gnu_return_list = tree_cons (gnu_field, gnu_param,
4004                                              gnu_return_list);
4005               }
4006           }
4007
4008         /* Do not compute record for out parameters if subprogram is
4009            stubbed since structures are incomplete for the back-end.  */
4010         if (gnu_field_list && Convention (gnat_entity) != Convention_Stubbed)
4011           finish_record_type (gnu_return_type, nreverse (gnu_field_list),
4012                               0, false);
4013
4014         /* If we have a CICO list but it has only one entry, we convert
4015            this function into a function that simply returns that one
4016            object.  */
4017         if (list_length (gnu_return_list) == 1)
4018           gnu_return_type = TREE_TYPE (TREE_PURPOSE (gnu_return_list));
4019
4020         if (Has_Stdcall_Convention (gnat_entity))
4021           prepend_one_attribute_to
4022             (&attr_list, ATTR_MACHINE_ATTRIBUTE,
4023              get_identifier ("stdcall"), NULL_TREE,
4024              gnat_entity);
4025
4026         /* If we are on a target where stack realignment is needed for 'main'
4027            to honor GCC's implicit expectations (stack alignment greater than
4028            what the base ABI guarantees), ensure we do the same for foreign
4029            convention subprograms as they might be used as callbacks from code
4030            breaking such expectations.  Note that this applies to task entry
4031            points in particular.  */
4032         if (FORCE_PREFERRED_STACK_BOUNDARY_IN_MAIN
4033             && Has_Foreign_Convention (gnat_entity))
4034           prepend_one_attribute_to
4035             (&attr_list, ATTR_MACHINE_ATTRIBUTE,
4036              get_identifier ("force_align_arg_pointer"), NULL_TREE,
4037              gnat_entity);
4038
4039         /* The lists have been built in reverse.  */
4040         gnu_param_list = nreverse (gnu_param_list);
4041         if (has_stub)
4042           gnu_stub_param_list = nreverse (gnu_stub_param_list);
4043         gnu_return_list = nreverse (gnu_return_list);
4044
4045         if (Ekind (gnat_entity) == E_Function)
4046           Set_Mechanism (gnat_entity,
4047                          (returns_by_ref || returns_unconstrained
4048                           ? By_Reference : By_Copy));
4049         gnu_type
4050           = create_subprog_type (gnu_return_type, gnu_param_list,
4051                                  gnu_return_list, returns_unconstrained,
4052                                  returns_by_ref, returns_by_target_ptr);
4053
4054         if (has_stub)
4055           gnu_stub_type
4056             = create_subprog_type (gnu_return_type, gnu_stub_param_list,
4057                                    gnu_return_list, returns_unconstrained,
4058                                    returns_by_ref, returns_by_target_ptr);
4059
4060         /* A subprogram (something that doesn't return anything) shouldn't
4061            be considered const since there would be no reason for such a
4062            subprogram.  Note that procedures with Out (or In Out) parameters
4063            have already been converted into a function with a return type.  */
4064         if (TREE_CODE (gnu_return_type) == VOID_TYPE)
4065           const_flag = false;
4066
4067         gnu_type
4068           = build_qualified_type (gnu_type,
4069                                   TYPE_QUALS (gnu_type)
4070                                   | (TYPE_QUAL_CONST * const_flag)
4071                                   | (TYPE_QUAL_VOLATILE * volatile_flag));
4072
4073         Sloc_to_locus (Sloc (gnat_entity), &input_location);
4074
4075         if (has_stub)
4076           gnu_stub_type
4077             = build_qualified_type (gnu_stub_type,
4078                                     TYPE_QUALS (gnu_stub_type)
4079                                     | (TYPE_QUAL_CONST * const_flag)
4080                                     | (TYPE_QUAL_VOLATILE * volatile_flag));
4081
4082         /* If we have a builtin decl for that function, check the signatures
4083            compatibilities.  If the signatures are compatible, use the builtin
4084            decl.  If they are not, we expect the checker predicate to have
4085            posted the appropriate errors, and just continue with what we have
4086            so far.  */
4087         if (gnu_builtin_decl)
4088           {
4089             tree gnu_builtin_type = TREE_TYPE (gnu_builtin_decl);
4090
4091             if (compatible_signatures_p (gnu_type, gnu_builtin_type))
4092               {
4093                 gnu_decl = gnu_builtin_decl;
4094                 gnu_type = gnu_builtin_type;
4095                 break;
4096               }
4097           }
4098
4099         /* If there was no specified Interface_Name and the external and
4100            internal names of the subprogram are the same, only use the
4101            internal name to allow disambiguation of nested subprograms.  */
4102         if (No (Interface_Name (gnat_entity)) && gnu_ext_name == gnu_entity_id)
4103           gnu_ext_name = NULL_TREE;
4104
4105         /* If we are defining the subprogram and it has an Address clause
4106            we must get the address expression from the saved GCC tree for the
4107            subprogram if it has a Freeze_Node.  Otherwise, we elaborate
4108            the address expression here since the front-end has guaranteed
4109            in that case that the elaboration has no effects.  If there is
4110            an Address clause and we are not defining the object, just
4111            make it a constant.  */
4112         if (Present (Address_Clause (gnat_entity)))
4113           {
4114             tree gnu_address = NULL_TREE;
4115
4116             if (definition)
4117               gnu_address
4118                 = (present_gnu_tree (gnat_entity)
4119                    ? get_gnu_tree (gnat_entity)
4120                    : gnat_to_gnu (Expression (Address_Clause (gnat_entity))));
4121
4122             save_gnu_tree (gnat_entity, NULL_TREE, false);
4123
4124             /* Convert the type of the object to a reference type that can
4125                alias everything as per 13.3(19).  */
4126             gnu_type
4127               = build_reference_type_for_mode (gnu_type, ptr_mode, true);
4128             if (gnu_address)
4129               gnu_address = convert (gnu_type, gnu_address);
4130
4131             gnu_decl
4132               = create_var_decl (gnu_entity_id, gnu_ext_name, gnu_type,
4133                                  gnu_address, false, Is_Public (gnat_entity),
4134                                  extern_flag, false, NULL, gnat_entity);
4135             DECL_BY_REF_P (gnu_decl) = 1;
4136           }
4137
4138         else if (kind == E_Subprogram_Type)
4139           gnu_decl = create_type_decl (gnu_entity_id, gnu_type, attr_list,
4140                                        !Comes_From_Source (gnat_entity),
4141                                        debug_info_p, gnat_entity);
4142         else
4143           {
4144             if (has_stub)
4145               {
4146                 gnu_stub_name = gnu_ext_name;
4147                 gnu_ext_name = create_concat_name (gnat_entity, "internal");
4148                 public_flag = false;
4149               }
4150
4151             gnu_decl = create_subprog_decl (gnu_entity_id, gnu_ext_name,
4152                                             gnu_type, gnu_param_list,
4153                                             inline_flag, public_flag,
4154                                             extern_flag, attr_list,
4155                                             gnat_entity);
4156             if (has_stub)
4157               {
4158                 tree gnu_stub_decl
4159                   = create_subprog_decl (gnu_entity_id, gnu_stub_name,
4160                                          gnu_stub_type, gnu_stub_param_list,
4161                                          inline_flag, true,
4162                                          extern_flag, attr_list,
4163                                          gnat_entity);
4164                 SET_DECL_FUNCTION_STUB (gnu_decl, gnu_stub_decl);
4165               }
4166
4167             /* This is unrelated to the stub built right above.  */
4168             DECL_STUBBED_P (gnu_decl)
4169               = Convention (gnat_entity) == Convention_Stubbed;
4170           }
4171       }
4172       break;
4173
4174     case E_Incomplete_Type:
4175     case E_Incomplete_Subtype:
4176     case E_Private_Type:
4177     case E_Private_Subtype:
4178     case E_Limited_Private_Type:
4179     case E_Limited_Private_Subtype:
4180     case E_Record_Type_With_Private:
4181     case E_Record_Subtype_With_Private:
4182       {
4183         /* Get the "full view" of this entity.  If this is an incomplete
4184            entity from a limited with, treat its non-limited view as the
4185            full view.  Otherwise, use either the full view or the underlying
4186            full view, whichever is present.  This is used in all the tests
4187            below.  */
4188         Entity_Id full_view
4189           = (IN (Ekind (gnat_entity), Incomplete_Kind)
4190              && From_With_Type (gnat_entity))
4191             ? Non_Limited_View (gnat_entity)
4192             : Present (Full_View (gnat_entity))
4193               ? Full_View (gnat_entity)
4194               : Underlying_Full_View (gnat_entity);
4195
4196         /* If this is an incomplete type with no full view, it must be a Taft
4197            Amendment type, in which case we return a dummy type.  Otherwise,
4198            just get the type from its Etype.  */
4199         if (No (full_view))
4200           {
4201             if (kind == E_Incomplete_Type)
4202               {
4203                 gnu_type = make_dummy_type (gnat_entity);
4204                 gnu_decl = TYPE_STUB_DECL (gnu_type);
4205               }
4206             else
4207               {
4208                 gnu_decl = gnat_to_gnu_entity (Etype (gnat_entity),
4209                                                NULL_TREE, 0);
4210                 maybe_present = true;
4211               }
4212             break;
4213           }
4214
4215         /* If we already made a type for the full view, reuse it.  */
4216         else if (present_gnu_tree (full_view))
4217           {
4218             gnu_decl = get_gnu_tree (full_view);
4219             break;
4220           }
4221
4222         /* Otherwise, if we are not defining the type now, get the type
4223            from the full view.  But always get the type from the full view
4224            for define on use types, since otherwise we won't see them!  */
4225         else if (!definition
4226                  || (Is_Itype (full_view)
4227                    && No (Freeze_Node (gnat_entity)))
4228                  || (Is_Itype (gnat_entity)
4229                    && No (Freeze_Node (full_view))))
4230           {
4231             gnu_decl = gnat_to_gnu_entity (full_view, NULL_TREE, 0);
4232             maybe_present = true;
4233             break;
4234           }
4235
4236         /* For incomplete types, make a dummy type entry which will be
4237            replaced later.  Save it as the full declaration's type so
4238            we can do any needed updates when we see it.  */
4239         gnu_type = make_dummy_type (gnat_entity);
4240         gnu_decl = TYPE_STUB_DECL (gnu_type);
4241         save_gnu_tree (full_view, gnu_decl, 0);
4242         break;
4243       }
4244
4245       /* Simple class_wide types are always viewed as their root_type
4246          by Gigi unless an Equivalent_Type is specified.  */
4247     case E_Class_Wide_Type:
4248       gnu_decl = gnat_to_gnu_entity (gnat_equiv_type, NULL_TREE, 0);
4249       maybe_present = true;
4250       break;
4251
4252     case E_Task_Type:
4253     case E_Task_Subtype:
4254     case E_Protected_Type:
4255     case E_Protected_Subtype:
4256       if (type_annotate_only && No (gnat_equiv_type))
4257         gnu_type = void_type_node;
4258       else
4259         gnu_type = gnat_to_gnu_type (gnat_equiv_type);
4260
4261       maybe_present = true;
4262       break;
4263
4264     case E_Label:
4265       gnu_decl = create_label_decl (gnu_entity_id);
4266       break;
4267
4268     case E_Block:
4269     case E_Loop:
4270       /* Nothing at all to do here, so just return an ERROR_MARK and claim
4271          we've already saved it, so we don't try to.  */
4272       gnu_decl = error_mark_node;
4273       saved = true;
4274       break;
4275
4276     default:
4277       gcc_unreachable ();
4278     }
4279
4280   /* If we had a case where we evaluated another type and it might have
4281      defined this one, handle it here.  */
4282   if (maybe_present && present_gnu_tree (gnat_entity))
4283     {
4284       gnu_decl = get_gnu_tree (gnat_entity);
4285       saved = true;
4286     }
4287
4288   /* If we are processing a type and there is either no decl for it or
4289      we just made one, do some common processing for the type, such as
4290      handling alignment and possible padding.  */
4291
4292   if ((!gnu_decl || this_made_decl) && IN (kind, Type_Kind))
4293     {
4294       if (Is_Tagged_Type (gnat_entity)
4295           || Is_Class_Wide_Equivalent_Type (gnat_entity))
4296         TYPE_ALIGN_OK (gnu_type) = 1;
4297
4298       if (AGGREGATE_TYPE_P (gnu_type) && Is_By_Reference_Type (gnat_entity))
4299         TYPE_BY_REFERENCE_P (gnu_type) = 1;
4300
4301       /* ??? Don't set the size for a String_Literal since it is either
4302          confirming or we don't handle it properly (if the low bound is
4303          non-constant).  */
4304       if (!gnu_size && kind != E_String_Literal_Subtype)
4305         gnu_size = validate_size (Esize (gnat_entity), gnu_type, gnat_entity,
4306                                   TYPE_DECL, false,
4307                                   Has_Size_Clause (gnat_entity));
4308
4309       /* If a size was specified, see if we can make a new type of that size
4310          by rearranging the type, for example from a fat to a thin pointer.  */
4311       if (gnu_size)
4312         {
4313           gnu_type
4314             = make_type_from_size (gnu_type, gnu_size,
4315                                    Has_Biased_Representation (gnat_entity));
4316
4317           if (operand_equal_p (TYPE_SIZE (gnu_type), gnu_size, 0)
4318               && operand_equal_p (rm_size (gnu_type), gnu_size, 0))
4319             gnu_size = 0;
4320         }
4321
4322       /* If the alignment hasn't already been processed and this is
4323          not an unconstrained array, see if an alignment is specified.
4324          If not, we pick a default alignment for atomic objects.  */
4325       if (align != 0 || TREE_CODE (gnu_type) == UNCONSTRAINED_ARRAY_TYPE)
4326         ;
4327       else if (Known_Alignment (gnat_entity))
4328         {
4329           align = validate_alignment (Alignment (gnat_entity), gnat_entity,
4330                                       TYPE_ALIGN (gnu_type));
4331
4332           /* Warn on suspiciously large alignments.  This should catch
4333              errors about the (alignment,byte)/(size,bit) discrepancy.  */
4334           if (align > BIGGEST_ALIGNMENT && Has_Alignment_Clause (gnat_entity))
4335             {
4336               tree size;
4337
4338               /* If a size was specified, take it into account.  Otherwise
4339                  use the RM size for records as the type size has already
4340                  been adjusted to the alignment.  */
4341               if (gnu_size)
4342                 size = gnu_size;
4343               else if ((TREE_CODE (gnu_type) == RECORD_TYPE
4344                         || TREE_CODE (gnu_type) == UNION_TYPE
4345                         || TREE_CODE (gnu_type) == QUAL_UNION_TYPE)
4346                        && !TYPE_IS_FAT_POINTER_P (gnu_type))
4347                 size = rm_size (gnu_type);
4348               else
4349                 size = TYPE_SIZE (gnu_type);
4350
4351               /* Consider an alignment as suspicious if the alignment/size
4352                  ratio is greater or equal to the byte/bit ratio.  */
4353               if (host_integerp (size, 1)
4354                   && align >= TREE_INT_CST_LOW (size) * BITS_PER_UNIT)
4355                 post_error_ne ("?suspiciously large alignment specified for&",
4356                                Expression (Alignment_Clause (gnat_entity)),
4357                                gnat_entity);
4358             }
4359         }
4360       else if (Is_Atomic (gnat_entity) && !gnu_size
4361                && host_integerp (TYPE_SIZE (gnu_type), 1)
4362                && integer_pow2p (TYPE_SIZE (gnu_type)))
4363         align = MIN (BIGGEST_ALIGNMENT,
4364                      tree_low_cst (TYPE_SIZE (gnu_type), 1));
4365       else if (Is_Atomic (gnat_entity) && gnu_size
4366                && host_integerp (gnu_size, 1)
4367                && integer_pow2p (gnu_size))
4368         align = MIN (BIGGEST_ALIGNMENT, tree_low_cst (gnu_size, 1));
4369
4370       /* See if we need to pad the type.  If we did, and made a record,
4371          the name of the new type may be changed.  So get it back for
4372          us when we make the new TYPE_DECL below.  */
4373       if (gnu_size || align > 0)
4374         gnu_type = maybe_pad_type (gnu_type, gnu_size, align, gnat_entity,
4375                                    "PAD", true, definition, false);
4376
4377       if (TREE_CODE (gnu_type) == RECORD_TYPE
4378           && TYPE_IS_PADDING_P (gnu_type))
4379         {
4380           gnu_entity_id = TYPE_NAME (gnu_type);
4381           if (TREE_CODE (gnu_entity_id) == TYPE_DECL)
4382             gnu_entity_id = DECL_NAME (gnu_entity_id);
4383         }
4384
4385       set_rm_size (RM_Size (gnat_entity), gnu_type, gnat_entity);
4386
4387       /* If we are at global level, GCC will have applied variable_size to
4388          the type, but that won't have done anything.  So, if it's not
4389          a constant or self-referential, call elaborate_expression_1 to
4390          make a variable for the size rather than calculating it each time.
4391          Handle both the RM size and the actual size.  */
4392       if (global_bindings_p ()
4393           && TYPE_SIZE (gnu_type)
4394           && !TREE_CONSTANT (TYPE_SIZE (gnu_type))
4395           && !CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type)))
4396         {
4397           if (TREE_CODE (gnu_type) == RECORD_TYPE
4398               && operand_equal_p (TYPE_ADA_SIZE (gnu_type),
4399                                   TYPE_SIZE (gnu_type), 0))
4400             {
4401               TYPE_SIZE (gnu_type)
4402                 = elaborate_expression_1 (gnat_entity, gnat_entity,
4403                                           TYPE_SIZE (gnu_type),
4404                                           get_identifier ("SIZE"),
4405                                           definition, 0);
4406               SET_TYPE_ADA_SIZE (gnu_type, TYPE_SIZE (gnu_type));
4407             }
4408           else
4409             {
4410               TYPE_SIZE (gnu_type)
4411                 = elaborate_expression_1 (gnat_entity, gnat_entity,
4412                                           TYPE_SIZE (gnu_type),
4413                                           get_identifier ("SIZE"),
4414                                           definition, 0);
4415
4416               /* ??? For now, store the size as a multiple of the alignment
4417                  in bytes so that we can see the alignment from the tree.  */
4418               TYPE_SIZE_UNIT (gnu_type)
4419                 = build_binary_op
4420                   (MULT_EXPR, sizetype,
4421                    elaborate_expression_1
4422                    (gnat_entity, gnat_entity,
4423                     build_binary_op (EXACT_DIV_EXPR, sizetype,
4424                                      TYPE_SIZE_UNIT (gnu_type),
4425                                      size_int (TYPE_ALIGN (gnu_type)
4426                                                / BITS_PER_UNIT)),
4427                     get_identifier ("SIZE_A_UNIT"),
4428                     definition, 0),
4429                    size_int (TYPE_ALIGN (gnu_type) / BITS_PER_UNIT));
4430
4431               if (TREE_CODE (gnu_type) == RECORD_TYPE)
4432                 SET_TYPE_ADA_SIZE
4433                   (gnu_type,
4434                    elaborate_expression_1 (gnat_entity,
4435                                            gnat_entity,
4436                                            TYPE_ADA_SIZE (gnu_type),
4437                                            get_identifier ("RM_SIZE"),
4438                                            definition, 0));
4439                  }
4440         }
4441
4442       /* If this is a record type or subtype, call elaborate_expression_1 on
4443          any field position.  Do this for both global and local types.
4444          Skip any fields that we haven't made trees for to avoid problems with
4445          class wide types.  */
4446       if (IN (kind, Record_Kind))
4447         for (gnat_temp = First_Entity (gnat_entity); Present (gnat_temp);
4448              gnat_temp = Next_Entity (gnat_temp))
4449           if (Ekind (gnat_temp) == E_Component && present_gnu_tree (gnat_temp))
4450             {
4451               tree gnu_field = get_gnu_tree (gnat_temp);
4452
4453               /* ??? Unfortunately, GCC needs to be able to prove the
4454                  alignment of this offset and if it's a variable, it can't.
4455                  In GCC 3.4, we'll use DECL_OFFSET_ALIGN in some way, but
4456                  right now, we have to put in an explicit multiply and
4457                  divide by that value.  */
4458               if (!CONTAINS_PLACEHOLDER_P (DECL_FIELD_OFFSET (gnu_field)))
4459                 {
4460                 DECL_FIELD_OFFSET (gnu_field)
4461                   = build_binary_op
4462                     (MULT_EXPR, sizetype,
4463                      elaborate_expression_1
4464                      (gnat_temp, gnat_temp,
4465                       build_binary_op (EXACT_DIV_EXPR, sizetype,
4466                                        DECL_FIELD_OFFSET (gnu_field),
4467                                        size_int (DECL_OFFSET_ALIGN (gnu_field)
4468                                                  / BITS_PER_UNIT)),
4469                       get_identifier ("OFFSET"),
4470                       definition, 0),
4471                      size_int (DECL_OFFSET_ALIGN (gnu_field) / BITS_PER_UNIT));
4472
4473                 /* ??? The context of gnu_field is not necessarily gnu_type so
4474                    the MULT_EXPR node built above may not be marked by the call
4475                    to create_type_decl below.  */
4476                 if (global_bindings_p ())
4477                   mark_visited (&DECL_FIELD_OFFSET (gnu_field));
4478                 }
4479             }
4480
4481       gnu_type = build_qualified_type (gnu_type,
4482                                        (TYPE_QUALS (gnu_type)
4483                                         | (TYPE_QUAL_VOLATILE
4484                                            * Treat_As_Volatile (gnat_entity))));
4485
4486       if (Is_Atomic (gnat_entity))
4487         check_ok_for_atomic (gnu_type, gnat_entity, false);
4488
4489       if (Present (Alignment_Clause (gnat_entity)))
4490         TYPE_USER_ALIGN (gnu_type) = 1;
4491
4492       if (Universal_Aliasing (gnat_entity))
4493         TYPE_UNIVERSAL_ALIASING_P (TYPE_MAIN_VARIANT (gnu_type)) = 1;
4494
4495       if (!gnu_decl)
4496         gnu_decl = create_type_decl (gnu_entity_id, gnu_type, attr_list,
4497                                      !Comes_From_Source (gnat_entity),
4498                                      debug_info_p, gnat_entity);
4499       else
4500         TREE_TYPE (gnu_decl) = gnu_type;
4501     }
4502
4503   if (IN (kind, Type_Kind) && !TYPE_IS_DUMMY_P (TREE_TYPE (gnu_decl)))
4504     {
4505       gnu_type = TREE_TYPE (gnu_decl);
4506
4507       /* If this is a derived type, relate its alias set to that of its parent
4508          to avoid troubles when a call to an inherited primitive is inlined in
4509          a context where a derived object is accessed.  The inlined code works
4510          on the parent view so the resulting code may access the same object
4511          using both the parent and the derived alias sets, which thus have to
4512          conflict.  As the same issue arises with component references, the
4513          parent alias set also has to conflict with composite types enclosing
4514          derived components.  For instance, if we have:
4515
4516             type D is new T;
4517             type R is record
4518                Component : D;
4519             end record;
4520
4521          we want T to conflict with both D and R, in addition to R being a
4522          superset of D by record/component construction.
4523
4524          One way to achieve this is to perform an alias set copy from the
4525          parent to the derived type.  This is not quite appropriate, though,
4526          as we don't want separate derived types to conflict with each other:
4527
4528             type I1 is new Integer;
4529             type I2 is new Integer;
4530
4531          We want I1 and I2 to both conflict with Integer but we do not want
4532          I1 to conflict with I2, and an alias set copy on derivation would
4533          have that effect.
4534
4535          The option chosen is to make the alias set of the derived type a
4536          superset of that of its parent type.  It trivially fulfills the
4537          simple requirement for the Integer derivation example above, and
4538          the component case as well by superset transitivity:
4539
4540                    superset      superset
4541                 R ----------> D ----------> T
4542
4543          The language rules ensure the parent type is already frozen here.  */
4544       if (Is_Derived_Type (gnat_entity))
4545         {
4546           tree gnu_parent_type = gnat_to_gnu_type (Etype (gnat_entity));
4547           relate_alias_sets (gnu_type, gnu_parent_type, ALIAS_SET_SUPERSET);
4548         }
4549
4550       /* Back-annotate the Alignment of the type if not already in the
4551          tree.  Likewise for sizes.  */
4552       if (Unknown_Alignment (gnat_entity))
4553         Set_Alignment (gnat_entity,
4554                        UI_From_Int (TYPE_ALIGN (gnu_type) / BITS_PER_UNIT));
4555
4556       if (Unknown_Esize (gnat_entity) && TYPE_SIZE (gnu_type))
4557         {
4558           /* If the size is self-referential, we annotate the maximum
4559              value of that size.  */
4560           tree gnu_size = TYPE_SIZE (gnu_type);
4561
4562           if (CONTAINS_PLACEHOLDER_P (gnu_size))
4563             gnu_size = max_size (gnu_size, true);
4564
4565           Set_Esize (gnat_entity, annotate_value (gnu_size));
4566
4567           if (type_annotate_only && Is_Tagged_Type (gnat_entity))
4568             {
4569               /* In this mode the tag and the parent components are not
4570                  generated by the front-end, so the sizes must be adjusted
4571                  explicitly now.  */
4572               int size_offset, new_size;
4573
4574               if (Is_Derived_Type (gnat_entity))
4575                 {
4576                   size_offset
4577                     = UI_To_Int (Esize (Etype (Base_Type (gnat_entity))));
4578                   Set_Alignment (gnat_entity,
4579                                  Alignment (Etype (Base_Type (gnat_entity))));
4580                 }
4581               else
4582                 size_offset = POINTER_SIZE;
4583
4584               new_size = UI_To_Int (Esize (gnat_entity)) + size_offset;
4585               Set_Esize (gnat_entity,
4586                          UI_From_Int (((new_size + (POINTER_SIZE - 1))
4587                                        / POINTER_SIZE) * POINTER_SIZE));
4588               Set_RM_Size (gnat_entity, Esize (gnat_entity));
4589             }
4590         }
4591
4592       if (Unknown_RM_Size (gnat_entity) && rm_size (gnu_type))
4593         Set_RM_Size (gnat_entity, annotate_value (rm_size (gnu_type)));
4594     }
4595
4596   if (!Comes_From_Source (gnat_entity) && DECL_P (gnu_decl))
4597     DECL_ARTIFICIAL (gnu_decl) = 1;
4598
4599   if (!debug_info_p && DECL_P (gnu_decl)
4600       && TREE_CODE (gnu_decl) != FUNCTION_DECL
4601       && No (Renamed_Object (gnat_entity)))
4602     DECL_IGNORED_P (gnu_decl) = 1;
4603
4604   /* If we haven't already, associate the ..._DECL node that we just made with
4605      the input GNAT entity node.  */
4606   if (!saved)
4607     save_gnu_tree (gnat_entity, gnu_decl, false);
4608
4609   /* If this is an enumeral or floating-point type, we were not able to set
4610      the bounds since they refer to the type.  These bounds are always static.
4611
4612      For enumeration types, also write debugging information and declare the
4613      enumeration literal  table, if needed.  */
4614
4615   if ((kind == E_Enumeration_Type && Present (First_Literal (gnat_entity)))
4616       || (kind == E_Floating_Point_Type && !Vax_Float (gnat_entity)))
4617     {
4618       tree gnu_scalar_type = gnu_type;
4619
4620       /* If this is a padded type, we need to use the underlying type.  */
4621       if (TREE_CODE (gnu_scalar_type) == RECORD_TYPE
4622           && TYPE_IS_PADDING_P (gnu_scalar_type))
4623         gnu_scalar_type = TREE_TYPE (TYPE_FIELDS (gnu_scalar_type));
4624
4625       /* If this is a floating point type and we haven't set a floating
4626          point type yet, use this in the evaluation of the bounds.  */
4627       if (!longest_float_type_node && kind == E_Floating_Point_Type)
4628         longest_float_type_node = gnu_type;
4629
4630       TYPE_MIN_VALUE (gnu_scalar_type)
4631         = gnat_to_gnu (Type_Low_Bound (gnat_entity));
4632       TYPE_MAX_VALUE (gnu_scalar_type)
4633         = gnat_to_gnu (Type_High_Bound (gnat_entity));
4634
4635       if (TREE_CODE (gnu_scalar_type) == ENUMERAL_TYPE)
4636         {
4637           /* Since this has both a typedef and a tag, avoid outputting
4638              the name twice.  */
4639           DECL_ARTIFICIAL (gnu_decl) = 1;
4640           rest_of_type_decl_compilation (gnu_decl);
4641         }
4642     }
4643
4644   /* If we deferred processing of incomplete types, re-enable it.  If there
4645      were no other disables and we have some to process, do so.  */
4646   if (this_deferred && --defer_incomplete_level == 0)
4647     {
4648       if (defer_incomplete_list)
4649         {
4650           struct incomplete *incp, *next;
4651
4652           /* We are back to level 0 for the deferring of incomplete types.
4653              But processing these incomplete types below may itself require
4654              deferring, so preserve what we have and restart from scratch.  */
4655           incp = defer_incomplete_list;
4656           defer_incomplete_list = NULL;
4657
4658           /* For finalization, however, all types must be complete so we
4659              cannot do the same because deferred incomplete types may end up
4660              referencing each other.  Process them all recursively first.  */
4661           defer_finalize_level++;
4662
4663           for (; incp; incp = next)
4664             {
4665               next = incp->next;
4666
4667               if (incp->old_type)
4668                 update_pointer_to (TYPE_MAIN_VARIANT (incp->old_type),
4669                                    gnat_to_gnu_type (incp->full_type));
4670               free (incp);
4671             }
4672
4673           defer_finalize_level--;
4674         }
4675
4676       /* All the deferred incomplete types have been processed so we can
4677          now proceed with the finalization of the deferred types.  */
4678       if (defer_finalize_level == 0 && defer_finalize_list)
4679         {
4680           unsigned int i;
4681           tree t;
4682
4683           for (i = 0; VEC_iterate (tree, defer_finalize_list, i, t); i++)
4684             rest_of_type_decl_compilation_no_defer (t);
4685
4686           VEC_free (tree, heap, defer_finalize_list);
4687         }
4688     }
4689
4690   /* If we are not defining this type, see if it's in the incomplete list.
4691      If so, handle that list entry now.  */
4692   else if (!definition)
4693     {
4694       struct incomplete *incp;
4695
4696       for (incp = defer_incomplete_list; incp; incp = incp->next)
4697         if (incp->old_type && incp->full_type == gnat_entity)
4698           {
4699             update_pointer_to (TYPE_MAIN_VARIANT (incp->old_type),
4700                                TREE_TYPE (gnu_decl));
4701             incp->old_type = NULL_TREE;
4702           }
4703     }
4704
4705   if (this_global)
4706     force_global--;
4707
4708   if (Is_Packed_Array_Type (gnat_entity)
4709       && Is_Itype (Associated_Node_For_Itype (gnat_entity))
4710       && No (Freeze_Node (Associated_Node_For_Itype (gnat_entity)))
4711       && !present_gnu_tree (Associated_Node_For_Itype (gnat_entity)))
4712     gnat_to_gnu_entity (Associated_Node_For_Itype (gnat_entity), NULL_TREE, 0);
4713
4714   return gnu_decl;
4715 }
4716
4717 /* Similar, but if the returned value is a COMPONENT_REF, return the
4718    FIELD_DECL.  */
4719
4720 tree
4721 gnat_to_gnu_field_decl (Entity_Id gnat_entity)
4722 {
4723   tree gnu_field = gnat_to_gnu_entity (gnat_entity, NULL_TREE, 0);
4724
4725   if (TREE_CODE (gnu_field) == COMPONENT_REF)
4726     gnu_field = TREE_OPERAND (gnu_field, 1);
4727
4728   return gnu_field;
4729 }
4730
4731 /* Similar, but GNAT_ENTITY is assumed to refer to a GNAT type.  Return
4732    the GCC type corresponding to that entity.  */
4733
4734 tree
4735 gnat_to_gnu_type (Entity_Id gnat_entity)
4736 {
4737   tree gnu_decl;
4738
4739   /* The back end never attempts to annotate generic types.  */
4740   if (Is_Generic_Type (gnat_entity) && type_annotate_only)
4741      return void_type_node;
4742
4743   gnu_decl = gnat_to_gnu_entity (gnat_entity, NULL_TREE, 0);
4744   gcc_assert (TREE_CODE (gnu_decl) == TYPE_DECL);
4745
4746   return TREE_TYPE (gnu_decl);
4747 }
4748
4749 /* Similar, but GNAT_ENTITY is assumed to refer to a GNAT type.  Return
4750    the unpadded version of the GCC type corresponding to that entity.  */
4751
4752 tree
4753 get_unpadded_type (Entity_Id gnat_entity)
4754 {
4755   tree type = gnat_to_gnu_type (gnat_entity);
4756
4757   if (TREE_CODE (type) == RECORD_TYPE && TYPE_IS_PADDING_P (type))
4758     type = TREE_TYPE (TYPE_FIELDS (type));
4759
4760   return type;
4761 }
4762 \f
4763 /* Wrap up compilation of DECL, a TYPE_DECL, possibly deferring it.
4764    Every TYPE_DECL generated for a type definition must be passed
4765    to this function once everything else has been done for it.  */
4766
4767 void
4768 rest_of_type_decl_compilation (tree decl)
4769 {
4770   /* We need to defer finalizing the type if incomplete types
4771      are being deferred or if they are being processed.  */
4772   if (defer_incomplete_level || defer_finalize_level)
4773     VEC_safe_push (tree, heap, defer_finalize_list, decl);
4774   else
4775     rest_of_type_decl_compilation_no_defer (decl);
4776 }
4777
4778 /* Same as above but without deferring the compilation.  This
4779    function should not be invoked directly on a TYPE_DECL.  */
4780
4781 static void
4782 rest_of_type_decl_compilation_no_defer (tree decl)
4783 {
4784   const int toplev = global_bindings_p ();
4785   tree t = TREE_TYPE (decl);
4786
4787   rest_of_decl_compilation (decl, toplev, 0);
4788
4789   /* Now process all the variants.  This is needed for STABS.  */
4790   for (t = TYPE_MAIN_VARIANT (t); t; t = TYPE_NEXT_VARIANT (t))
4791     {
4792       if (t == TREE_TYPE (decl))
4793         continue;
4794
4795       if (!TYPE_STUB_DECL (t))
4796         TYPE_STUB_DECL (t) = create_type_stub_decl (DECL_NAME (decl), t);
4797
4798       rest_of_type_compilation (t, toplev);
4799     }
4800 }
4801
4802 /* Finalize any From_With_Type incomplete types.  We do this after processing
4803    our compilation unit and after processing its spec, if this is a body.  */
4804
4805 void
4806 finalize_from_with_types (void)
4807 {
4808   struct incomplete *incp = defer_limited_with;
4809   struct incomplete *next;
4810
4811   defer_limited_with = 0;
4812   for (; incp; incp = next)
4813     {
4814       next = incp->next;
4815
4816       if (incp->old_type != 0)
4817         update_pointer_to (TYPE_MAIN_VARIANT (incp->old_type),
4818                            gnat_to_gnu_type (incp->full_type));
4819       free (incp);
4820     }
4821 }
4822
4823 /* Return the equivalent type to be used for GNAT_ENTITY, if it's a
4824    kind of type (such E_Task_Type) that has a different type which Gigi
4825    uses for its representation.  If the type does not have a special type
4826    for its representation, return GNAT_ENTITY.  If a type is supposed to
4827    exist, but does not, abort unless annotating types, in which case
4828    return Empty.  If GNAT_ENTITY is Empty, return Empty.  */
4829
4830 Entity_Id
4831 Gigi_Equivalent_Type (Entity_Id gnat_entity)
4832 {
4833   Entity_Id gnat_equiv = gnat_entity;
4834
4835   if (No (gnat_entity))
4836     return gnat_entity;
4837
4838   switch (Ekind (gnat_entity))
4839     {
4840     case E_Class_Wide_Subtype:
4841       if (Present (Equivalent_Type (gnat_entity)))
4842         gnat_equiv = Equivalent_Type (gnat_entity);
4843       break;
4844
4845     case E_Access_Protected_Subprogram_Type:
4846     case E_Anonymous_Access_Protected_Subprogram_Type:
4847       gnat_equiv = Equivalent_Type (gnat_entity);
4848       break;
4849
4850     case E_Class_Wide_Type:
4851       gnat_equiv = ((Present (Equivalent_Type (gnat_entity)))
4852                     ? Equivalent_Type (gnat_entity)
4853                     : Root_Type (gnat_entity));
4854       break;
4855
4856     case E_Task_Type:
4857     case E_Task_Subtype:
4858     case E_Protected_Type:
4859     case E_Protected_Subtype:
4860       gnat_equiv = Corresponding_Record_Type (gnat_entity);
4861       break;
4862
4863     default:
4864       break;
4865     }
4866
4867   gcc_assert (Present (gnat_equiv) || type_annotate_only);
4868   return gnat_equiv;
4869 }
4870
4871 /* Return a GCC tree for a parameter corresponding to GNAT_PARAM and
4872    using MECH as its passing mechanism, to be placed in the parameter
4873    list built for GNAT_SUBPROG.  Assume a foreign convention for the
4874    latter if FOREIGN is true.  Also set CICO to true if the parameter
4875    must use the copy-in copy-out implementation mechanism.
4876
4877    The returned tree is a PARM_DECL, except for those cases where no
4878    parameter needs to be actually passed to the subprogram; the type
4879    of this "shadow" parameter is then returned instead.  */
4880
4881 static tree
4882 gnat_to_gnu_param (Entity_Id gnat_param, Mechanism_Type mech,
4883                    Entity_Id gnat_subprog, bool foreign, bool *cico)
4884 {
4885   tree gnu_param_name = get_entity_name (gnat_param);
4886   tree gnu_param_type = gnat_to_gnu_type (Etype (gnat_param));
4887   tree gnu_param_type_alt = NULL_TREE;
4888   bool in_param = (Ekind (gnat_param) == E_In_Parameter);
4889   /* The parameter can be indirectly modified if its address is taken.  */
4890   bool ro_param = in_param && !Address_Taken (gnat_param);
4891   bool by_return = false, by_component_ptr = false, by_ref = false;
4892   tree gnu_param;
4893
4894   /* Copy-return is used only for the first parameter of a valued procedure.
4895      It's a copy mechanism for which a parameter is never allocated.  */
4896   if (mech == By_Copy_Return)
4897     {
4898       gcc_assert (Ekind (gnat_param) == E_Out_Parameter);
4899       mech = By_Copy;
4900       by_return = true;
4901     }
4902
4903   /* If this is either a foreign function or if the underlying type won't
4904      be passed by reference, strip off possible padding type.  */
4905   if (TREE_CODE (gnu_param_type) == RECORD_TYPE
4906       && TYPE_IS_PADDING_P (gnu_param_type))
4907     {
4908       tree unpadded_type = TREE_TYPE (TYPE_FIELDS (gnu_param_type));
4909
4910       if (mech == By_Reference
4911           || foreign
4912           || (!must_pass_by_ref (unpadded_type)
4913               && (mech == By_Copy || !default_pass_by_ref (unpadded_type))))
4914         gnu_param_type = unpadded_type;
4915     }
4916
4917   /* If this is a read-only parameter, make a variant of the type that is
4918      read-only.  ??? However, if this is an unconstrained array, that type
4919      can be very complex, so skip it for now.  Likewise for any other
4920      self-referential type.  */
4921   if (ro_param
4922       && TREE_CODE (gnu_param_type) != UNCONSTRAINED_ARRAY_TYPE
4923       && !CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_param_type)))
4924     gnu_param_type = build_qualified_type (gnu_param_type,
4925                                            (TYPE_QUALS (gnu_param_type)
4926                                             | TYPE_QUAL_CONST));
4927
4928   /* For foreign conventions, pass arrays as pointers to the element type.
4929      First check for unconstrained array and get the underlying array.  */
4930   if (foreign && TREE_CODE (gnu_param_type) == UNCONSTRAINED_ARRAY_TYPE)
4931     gnu_param_type
4932       = TREE_TYPE (TREE_TYPE (TYPE_FIELDS (TREE_TYPE (gnu_param_type))));
4933
4934   /* VMS descriptors are themselves passed by reference.  */
4935   if (mech == By_Short_Descriptor ||
4936       (mech == By_Descriptor && TARGET_ABI_OPEN_VMS && !TARGET_MALLOC64))
4937     gnu_param_type
4938       = build_pointer_type (build_vms_descriptor32 (gnu_param_type,
4939                                                     Mechanism (gnat_param),
4940                                                     gnat_subprog));
4941   else if (mech == By_Descriptor)
4942     {
4943       /* Build both a 32-bit and 64-bit descriptor, one of which will be
4944          chosen in fill_vms_descriptor.  */
4945       gnu_param_type_alt
4946         = build_pointer_type (build_vms_descriptor32 (gnu_param_type,
4947                                                       Mechanism (gnat_param),
4948                                                       gnat_subprog));
4949       gnu_param_type
4950         = build_pointer_type (build_vms_descriptor (gnu_param_type,
4951                                                     Mechanism (gnat_param),
4952                                                     gnat_subprog));
4953     }
4954
4955   /* Arrays are passed as pointers to element type for foreign conventions.  */
4956   else if (foreign
4957            && mech != By_Copy
4958            && TREE_CODE (gnu_param_type) == ARRAY_TYPE)
4959     {
4960       /* Strip off any multi-dimensional entries, then strip
4961          off the last array to get the component type.  */
4962       while (TREE_CODE (TREE_TYPE (gnu_param_type)) == ARRAY_TYPE
4963              && TYPE_MULTI_ARRAY_P (TREE_TYPE (gnu_param_type)))
4964         gnu_param_type = TREE_TYPE (gnu_param_type);
4965
4966       by_component_ptr = true;
4967       gnu_param_type = TREE_TYPE (gnu_param_type);
4968
4969       if (ro_param)
4970         gnu_param_type = build_qualified_type (gnu_param_type,
4971                                                (TYPE_QUALS (gnu_param_type)
4972                                                 | TYPE_QUAL_CONST));
4973
4974       gnu_param_type = build_pointer_type (gnu_param_type);
4975     }
4976
4977   /* Fat pointers are passed as thin pointers for foreign conventions.  */
4978   else if (foreign && TYPE_FAT_POINTER_P (gnu_param_type))
4979     gnu_param_type
4980       = make_type_from_size (gnu_param_type, size_int (POINTER_SIZE), 0);
4981
4982   /* If we must pass or were requested to pass by reference, do so.
4983      If we were requested to pass by copy, do so.
4984      Otherwise, for foreign conventions, pass In Out or Out parameters
4985      or aggregates by reference.  For COBOL and Fortran, pass all
4986      integer and FP types that way too.  For Convention Ada, use
4987      the standard Ada default.  */
4988   else if (must_pass_by_ref (gnu_param_type)
4989            || mech == By_Reference
4990            || (mech != By_Copy
4991                && ((foreign
4992                     && (!in_param || AGGREGATE_TYPE_P (gnu_param_type)))
4993                    || (foreign
4994                        && (Convention (gnat_subprog) == Convention_Fortran
4995                            || Convention (gnat_subprog) == Convention_COBOL)
4996                        && (INTEGRAL_TYPE_P (gnu_param_type)
4997                            || FLOAT_TYPE_P (gnu_param_type)))
4998                    || (!foreign
4999                        && default_pass_by_ref (gnu_param_type)))))
5000     {
5001       gnu_param_type = build_reference_type (gnu_param_type);
5002       by_ref = true;
5003     }
5004
5005   /* Pass In Out or Out parameters using copy-in copy-out mechanism.  */
5006   else if (!in_param)
5007     *cico = true;
5008
5009   if (mech == By_Copy && (by_ref || by_component_ptr))
5010     post_error ("?cannot pass & by copy", gnat_param);
5011
5012   /* If this is an Out parameter that isn't passed by reference and isn't
5013      a pointer or aggregate, we don't make a PARM_DECL for it.  Instead,
5014      it will be a VAR_DECL created when we process the procedure, so just
5015      return its type.  For the special parameter of a valued procedure,
5016      never pass it in.
5017
5018      An exception is made to cover the RM-6.4.1 rule requiring "by copy"
5019      Out parameters with discriminants or implicit initial values to be
5020      handled like In Out parameters.  These type are normally built as
5021      aggregates, hence passed by reference, except for some packed arrays
5022      which end up encoded in special integer types.
5023
5024      The exception we need to make is then for packed arrays of records
5025      with discriminants or implicit initial values.  We have no light/easy
5026      way to check for the latter case, so we merely check for packed arrays
5027      of records.  This may lead to useless copy-in operations, but in very
5028      rare cases only, as these would be exceptions in a set of already
5029      exceptional situations.  */
5030   if (Ekind (gnat_param) == E_Out_Parameter
5031       && !by_ref
5032       && (by_return
5033           || (mech != By_Descriptor
5034               && mech != By_Short_Descriptor
5035               && !POINTER_TYPE_P (gnu_param_type)
5036               && !AGGREGATE_TYPE_P (gnu_param_type)))
5037       && !(Is_Array_Type (Etype (gnat_param))
5038            && Is_Packed (Etype (gnat_param))
5039            && Is_Composite_Type (Component_Type (Etype (gnat_param)))))
5040     return gnu_param_type;
5041
5042   gnu_param = create_param_decl (gnu_param_name, gnu_param_type,
5043                                  ro_param || by_ref || by_component_ptr);
5044   DECL_BY_REF_P (gnu_param) = by_ref;
5045   DECL_BY_COMPONENT_PTR_P (gnu_param) = by_component_ptr;
5046   DECL_BY_DESCRIPTOR_P (gnu_param) = (mech == By_Descriptor ||
5047                                       mech == By_Short_Descriptor);
5048   DECL_POINTS_TO_READONLY_P (gnu_param)
5049     = (ro_param && (by_ref || by_component_ptr));
5050
5051   /* Save the alternate descriptor type, if any.  */
5052   if (gnu_param_type_alt)
5053     SET_DECL_PARM_ALT_TYPE (gnu_param, gnu_param_type_alt);
5054
5055   /* If no Mechanism was specified, indicate what we're using, then
5056      back-annotate it.  */
5057   if (mech == Default)
5058     mech = (by_ref || by_component_ptr) ? By_Reference : By_Copy;
5059
5060   Set_Mechanism (gnat_param, mech);
5061   return gnu_param;
5062 }
5063
5064 /* Return true if DISCR1 and DISCR2 represent the same discriminant.  */
5065
5066 static bool
5067 same_discriminant_p (Entity_Id discr1, Entity_Id discr2)
5068 {
5069   while (Present (Corresponding_Discriminant (discr1)))
5070     discr1 = Corresponding_Discriminant (discr1);
5071
5072   while (Present (Corresponding_Discriminant (discr2)))
5073     discr2 = Corresponding_Discriminant (discr2);
5074
5075   return
5076     Original_Record_Component (discr1) == Original_Record_Component (discr2);
5077 }
5078
5079 /* Return true if the array type specified by GNAT_TYPE and GNU_TYPE has
5080    a non-aliased component in the back-end sense.  */
5081
5082 static bool
5083 array_type_has_nonaliased_component (Entity_Id gnat_type, tree gnu_type)
5084 {
5085   /* If the type below this is a multi-array type, then
5086      this does not have aliased components.  */
5087   if (TREE_CODE (TREE_TYPE (gnu_type)) == ARRAY_TYPE
5088       && TYPE_MULTI_ARRAY_P (TREE_TYPE (gnu_type)))
5089     return true;
5090
5091   if (Has_Aliased_Components (gnat_type))
5092     return false;
5093
5094   return type_for_nonaliased_component_p (TREE_TYPE (gnu_type));
5095 }
5096
5097 /* Return true if GNAT_ADDRESS is a value known at compile-time.  */
5098
5099 static bool
5100 compile_time_known_address_p (Node_Id gnat_address)
5101 {
5102   /* Catch System'To_Address.  */
5103   if (Nkind (gnat_address) == N_Unchecked_Type_Conversion)
5104     gnat_address = Expression (gnat_address);
5105
5106   return Compile_Time_Known_Value (gnat_address);
5107 }
5108 \f
5109 /* Given GNAT_ENTITY, elaborate all expressions that are required to
5110    be elaborated at the point of its definition, but do nothing else.  */
5111
5112 void
5113 elaborate_entity (Entity_Id gnat_entity)
5114 {
5115   switch (Ekind (gnat_entity))
5116     {
5117     case E_Signed_Integer_Subtype:
5118     case E_Modular_Integer_Subtype:
5119     case E_Enumeration_Subtype:
5120     case E_Ordinary_Fixed_Point_Subtype:
5121     case E_Decimal_Fixed_Point_Subtype:
5122     case E_Floating_Point_Subtype:
5123       {
5124         Node_Id gnat_lb = Type_Low_Bound (gnat_entity);
5125         Node_Id gnat_hb = Type_High_Bound (gnat_entity);
5126
5127         /* ??? Tests for avoiding static constraint error expression
5128            is needed until the front stops generating bogus conversions
5129            on bounds of real types.  */
5130
5131         if (!Raises_Constraint_Error (gnat_lb))
5132           elaborate_expression (gnat_lb, gnat_entity, get_identifier ("L"),
5133                                 1, 0, Needs_Debug_Info (gnat_entity));
5134         if (!Raises_Constraint_Error (gnat_hb))
5135           elaborate_expression (gnat_hb, gnat_entity, get_identifier ("U"),
5136                                 1, 0, Needs_Debug_Info (gnat_entity));
5137       break;
5138       }
5139
5140     case E_Record_Type:
5141       {
5142         Node_Id full_definition = Declaration_Node (gnat_entity);
5143         Node_Id record_definition = Type_Definition (full_definition);
5144
5145         /* If this is a record extension, go a level further to find the
5146            record definition.  */
5147         if (Nkind (record_definition) == N_Derived_Type_Definition)
5148           record_definition = Record_Extension_Part (record_definition);
5149       }
5150       break;
5151
5152     case E_Record_Subtype:
5153     case E_Private_Subtype:
5154     case E_Limited_Private_Subtype:
5155     case E_Record_Subtype_With_Private:
5156       if (Is_Constrained (gnat_entity)
5157           && Has_Discriminants (Base_Type (gnat_entity))
5158           && Present (Discriminant_Constraint (gnat_entity)))
5159         {
5160           Node_Id gnat_discriminant_expr;
5161           Entity_Id gnat_field;
5162
5163           for (gnat_field = First_Discriminant (Base_Type (gnat_entity)),
5164                gnat_discriminant_expr
5165                = First_Elmt (Discriminant_Constraint (gnat_entity));
5166                Present (gnat_field);
5167                gnat_field = Next_Discriminant (gnat_field),
5168                gnat_discriminant_expr = Next_Elmt (gnat_discriminant_expr))
5169             /* ??? For now, ignore access discriminants.  */
5170             if (!Is_Access_Type (Etype (Node (gnat_discriminant_expr))))
5171               elaborate_expression (Node (gnat_discriminant_expr),
5172                                     gnat_entity,
5173                                     get_entity_name (gnat_field), 1, 0, 0);
5174         }
5175       break;
5176
5177     }
5178 }
5179 \f
5180 /* Mark GNAT_ENTITY as going out of scope at this point.  Recursively mark
5181    any entities on its entity chain similarly.  */
5182
5183 void
5184 mark_out_of_scope (Entity_Id gnat_entity)
5185 {
5186   Entity_Id gnat_sub_entity;
5187   unsigned int kind = Ekind (gnat_entity);
5188
5189   /* If this has an entity list, process all in the list.  */
5190   if (IN (kind, Class_Wide_Kind) || IN (kind, Concurrent_Kind)
5191       || IN (kind, Private_Kind)
5192       || kind == E_Block || kind == E_Entry || kind == E_Entry_Family
5193       || kind == E_Function || kind == E_Generic_Function
5194       || kind == E_Generic_Package || kind == E_Generic_Procedure
5195       || kind == E_Loop || kind == E_Operator || kind == E_Package
5196       || kind == E_Package_Body || kind == E_Procedure
5197       || kind == E_Record_Type || kind == E_Record_Subtype
5198       || kind == E_Subprogram_Body || kind == E_Subprogram_Type)
5199     for (gnat_sub_entity = First_Entity (gnat_entity);
5200          Present (gnat_sub_entity);
5201          gnat_sub_entity = Next_Entity (gnat_sub_entity))
5202       if (Scope (gnat_sub_entity) == gnat_entity
5203           && gnat_sub_entity != gnat_entity)
5204         mark_out_of_scope (gnat_sub_entity);
5205
5206   /* Now clear this if it has been defined, but only do so if it isn't
5207      a subprogram or parameter.  We could refine this, but it isn't
5208      worth it.  If this is statically allocated, it is supposed to
5209      hang around out of cope.  */
5210   if (present_gnu_tree (gnat_entity) && !Is_Statically_Allocated (gnat_entity)
5211       && kind != E_Procedure && kind != E_Function && !IN (kind, Formal_Kind))
5212     {
5213       save_gnu_tree (gnat_entity, NULL_TREE, true);
5214       save_gnu_tree (gnat_entity, error_mark_node, true);
5215     }
5216 }
5217 \f
5218 /* Relate the alias sets of GNU_NEW_TYPE and GNU_OLD_TYPE according to OP.
5219    If this is a multi-dimensional array type, do this recursively.
5220
5221    OP may be
5222    - ALIAS_SET_COPY:     the new set is made a copy of the old one.
5223    - ALIAS_SET_SUPERSET: the new set is made a superset of the old one.
5224    - ALIAS_SET_SUBSET:   the new set is made a subset of the old one.  */
5225
5226 static void
5227 relate_alias_sets (tree gnu_new_type, tree gnu_old_type, enum alias_set_op op)
5228 {
5229   /* Remove any padding from GNU_OLD_TYPE.  It doesn't matter in the case
5230      of a one-dimensional array, since the padding has the same alias set
5231      as the field type, but if it's a multi-dimensional array, we need to
5232      see the inner types.  */
5233   while (TREE_CODE (gnu_old_type) == RECORD_TYPE
5234          && (TYPE_JUSTIFIED_MODULAR_P (gnu_old_type)
5235              || TYPE_IS_PADDING_P (gnu_old_type)))
5236     gnu_old_type = TREE_TYPE (TYPE_FIELDS (gnu_old_type));
5237
5238   /* Unconstrained array types are deemed incomplete and would thus be given
5239      alias set 0.  Retrieve the underlying array type.  */
5240   if (TREE_CODE (gnu_old_type) == UNCONSTRAINED_ARRAY_TYPE)
5241     gnu_old_type
5242       = TREE_TYPE (TREE_TYPE (TYPE_FIELDS (TREE_TYPE (gnu_old_type))));
5243   if (TREE_CODE (gnu_new_type) == UNCONSTRAINED_ARRAY_TYPE)
5244     gnu_new_type
5245       = TREE_TYPE (TREE_TYPE (TYPE_FIELDS (TREE_TYPE (gnu_new_type))));
5246
5247   if (TREE_CODE (gnu_new_type) == ARRAY_TYPE
5248       && TREE_CODE (TREE_TYPE (gnu_new_type)) == ARRAY_TYPE
5249       && TYPE_MULTI_ARRAY_P (TREE_TYPE (gnu_new_type)))
5250     relate_alias_sets (TREE_TYPE (gnu_new_type), TREE_TYPE (gnu_old_type), op);
5251
5252   switch (op)
5253     {
5254     case ALIAS_SET_COPY:
5255       /* The alias set shouldn't be copied between array types with different
5256          aliasing settings because this can break the aliasing relationship
5257          between the array type and its element type.  */
5258 #ifndef ENABLE_CHECKING
5259       if (flag_strict_aliasing)
5260 #endif
5261         gcc_assert (!(TREE_CODE (gnu_new_type) == ARRAY_TYPE
5262                       && TREE_CODE (gnu_old_type) == ARRAY_TYPE
5263                       && TYPE_NONALIASED_COMPONENT (gnu_new_type)
5264                          != TYPE_NONALIASED_COMPONENT (gnu_old_type)));
5265
5266       TYPE_ALIAS_SET (gnu_new_type) = get_alias_set (gnu_old_type);
5267       break;
5268
5269     case ALIAS_SET_SUBSET:
5270     case ALIAS_SET_SUPERSET:
5271       {
5272         alias_set_type old_set = get_alias_set (gnu_old_type);
5273         alias_set_type new_set = get_alias_set (gnu_new_type);
5274
5275         /* Do nothing if the alias sets conflict.  This ensures that we
5276            never call record_alias_subset several times for the same pair
5277            or at all for alias set 0.  */
5278         if (!alias_sets_conflict_p (old_set, new_set))
5279           {
5280             if (op == ALIAS_SET_SUBSET)
5281               record_alias_subset (old_set, new_set);
5282             else
5283               record_alias_subset (new_set, old_set);
5284           }
5285       }
5286       break;
5287
5288     default:
5289       gcc_unreachable ();
5290     }
5291
5292   record_component_aliases (gnu_new_type);
5293 }
5294 \f
5295 /* Return a TREE_LIST describing the substitutions needed to reflect
5296    discriminant substitutions from GNAT_SUBTYPE to GNAT_TYPE and add
5297    them to GNU_LIST.  If GNAT_TYPE is not specified, use the base type
5298    of GNAT_SUBTYPE.  The substitutions can be in any order.  TREE_PURPOSE
5299    gives the tree for the discriminant and TREE_VALUES is the replacement
5300    value.  They are in the form of operands to substitute_in_expr.
5301    DEFINITION is as in gnat_to_gnu_entity.  */
5302
5303 static tree
5304 substitution_list (Entity_Id gnat_subtype, Entity_Id gnat_type,
5305                    tree gnu_list, bool definition)
5306 {
5307   Entity_Id gnat_discrim;
5308   Node_Id gnat_value;
5309
5310   if (No (gnat_type))
5311     gnat_type = Implementation_Base_Type (gnat_subtype);
5312
5313   if (Has_Discriminants (gnat_type))
5314     for (gnat_discrim = First_Stored_Discriminant (gnat_type),
5315          gnat_value = First_Elmt (Stored_Constraint (gnat_subtype));
5316          Present (gnat_discrim);
5317          gnat_discrim = Next_Stored_Discriminant (gnat_discrim),
5318          gnat_value = Next_Elmt (gnat_value))
5319       /* Ignore access discriminants.  */
5320       if (!Is_Access_Type (Etype (Node (gnat_value))))
5321         gnu_list = tree_cons (gnat_to_gnu_field_decl (gnat_discrim),
5322                               elaborate_expression
5323                               (Node (gnat_value), gnat_subtype,
5324                                get_entity_name (gnat_discrim), definition,
5325                                1, 0),
5326                               gnu_list);
5327
5328   return gnu_list;
5329 }
5330 \f
5331 /* Return true if the size represented by GNU_SIZE can be handled by an
5332    allocation.  If STATIC_P is true, consider only what can be done with a
5333    static allocation.  */
5334
5335 static bool
5336 allocatable_size_p (tree gnu_size, bool static_p)
5337 {
5338   HOST_WIDE_INT our_size;
5339
5340   /* If this is not a static allocation, the only case we want to forbid
5341      is an overflowing size.  That will be converted into a raise a
5342      Storage_Error.  */
5343   if (!static_p)
5344     return !(TREE_CODE (gnu_size) == INTEGER_CST
5345              && TREE_OVERFLOW (gnu_size));
5346
5347   /* Otherwise, we need to deal with both variable sizes and constant
5348      sizes that won't fit in a host int.  We use int instead of HOST_WIDE_INT
5349      since assemblers may not like very large sizes.  */
5350   if (!host_integerp (gnu_size, 1))
5351     return false;
5352
5353   our_size = tree_low_cst (gnu_size, 1);
5354   return (int) our_size == our_size;
5355 }
5356 \f
5357 /* Prepend to ATTR_LIST an entry for an attribute with provided TYPE,
5358    NAME, ARGS and ERROR_POINT.  */
5359
5360 static void
5361 prepend_one_attribute_to (struct attrib ** attr_list,
5362                           enum attr_type attr_type,
5363                           tree attr_name,
5364                           tree attr_args,
5365                           Node_Id attr_error_point)
5366 {
5367   struct attrib * attr = (struct attrib *) xmalloc (sizeof (struct attrib));
5368
5369   attr->type = attr_type;
5370   attr->name = attr_name;
5371   attr->args = attr_args;
5372   attr->error_point = attr_error_point;
5373
5374   attr->next = *attr_list;
5375   *attr_list = attr;
5376 }
5377
5378 /* Prepend to ATTR_LIST the list of attributes for GNAT_ENTITY, if any.  */
5379
5380 static void
5381 prepend_attributes (Entity_Id gnat_entity, struct attrib ** attr_list)
5382 {
5383   Node_Id gnat_temp;
5384
5385   for (gnat_temp = First_Rep_Item (gnat_entity); Present (gnat_temp);
5386        gnat_temp = Next_Rep_Item (gnat_temp))
5387     if (Nkind (gnat_temp) == N_Pragma)
5388       {
5389         tree gnu_arg0 = NULL_TREE, gnu_arg1 = NULL_TREE;
5390         Node_Id gnat_assoc = Pragma_Argument_Associations (gnat_temp);
5391         enum attr_type etype;
5392
5393         if (Present (gnat_assoc) && Present (First (gnat_assoc))
5394             && Present (Next (First (gnat_assoc)))
5395             && (Nkind (Expression (Next (First (gnat_assoc))))
5396                 == N_String_Literal))
5397           {
5398             gnu_arg0 = get_identifier (TREE_STRING_POINTER
5399                                        (gnat_to_gnu
5400                                         (Expression (Next
5401                                                      (First (gnat_assoc))))));
5402             if (Present (Next (Next (First (gnat_assoc))))
5403                 && (Nkind (Expression (Next (Next (First (gnat_assoc)))))
5404                     == N_String_Literal))
5405               gnu_arg1 = get_identifier (TREE_STRING_POINTER
5406                                          (gnat_to_gnu
5407                                           (Expression
5408                                            (Next (Next
5409                                                   (First (gnat_assoc)))))));
5410           }
5411
5412         switch (Get_Pragma_Id (Chars (Pragma_Identifier (gnat_temp))))
5413           {
5414           case Pragma_Machine_Attribute:
5415             etype = ATTR_MACHINE_ATTRIBUTE;
5416             break;
5417
5418           case Pragma_Linker_Alias:
5419             etype = ATTR_LINK_ALIAS;
5420             break;
5421
5422           case Pragma_Linker_Section:
5423             etype = ATTR_LINK_SECTION;
5424             break;
5425
5426           case Pragma_Linker_Constructor:
5427             etype = ATTR_LINK_CONSTRUCTOR;
5428             break;
5429
5430           case Pragma_Linker_Destructor:
5431             etype = ATTR_LINK_DESTRUCTOR;
5432             break;
5433
5434           case Pragma_Weak_External:
5435             etype = ATTR_WEAK_EXTERNAL;
5436             break;
5437
5438           case Pragma_Thread_Local_Storage:
5439             etype = ATTR_THREAD_LOCAL_STORAGE;
5440             break;
5441
5442           default:
5443             continue;
5444           }
5445
5446
5447         /* Prepend to the list now.  Make a list of the argument we might
5448            have, as GCC expects it.  */
5449         prepend_one_attribute_to
5450           (attr_list,
5451            etype, gnu_arg0,
5452            (gnu_arg1 != NULL_TREE)
5453            ? build_tree_list (NULL_TREE, gnu_arg1) : NULL_TREE,
5454            Present (Next (First (gnat_assoc)))
5455            ? Expression (Next (First (gnat_assoc))) : gnat_temp);
5456       }
5457 }
5458 \f
5459 /* Called when we need to protect a variable object using a save_expr.  */
5460
5461 tree
5462 maybe_variable (tree gnu_operand)
5463 {
5464   if (TREE_CONSTANT (gnu_operand) || TREE_READONLY (gnu_operand)
5465       || TREE_CODE (gnu_operand) == SAVE_EXPR
5466       || TREE_CODE (gnu_operand) == NULL_EXPR)
5467     return gnu_operand;
5468
5469   if (TREE_CODE (gnu_operand) == UNCONSTRAINED_ARRAY_REF)
5470     {
5471       tree gnu_result = build1 (UNCONSTRAINED_ARRAY_REF,
5472                                 TREE_TYPE (gnu_operand),
5473                                 variable_size (TREE_OPERAND (gnu_operand, 0)));
5474
5475       TREE_READONLY (gnu_result) = TREE_STATIC (gnu_result)
5476         = TYPE_READONLY (TREE_TYPE (TREE_TYPE (gnu_operand)));
5477       return gnu_result;
5478     }
5479   else
5480     return variable_size (gnu_operand);
5481 }
5482 \f
5483 /* Given a GNAT tree GNAT_EXPR, for an expression which is a value within a
5484    type definition (either a bound or a discriminant value) for GNAT_ENTITY,
5485    return the GCC tree to use for that expression.  GNU_NAME is the
5486    qualification to use if an external name is appropriate and DEFINITION is
5487    true if this is a definition of GNAT_ENTITY.  If NEED_VALUE is true, we
5488    need a result.  Otherwise, we are just elaborating this for side-effects.
5489    If NEED_DEBUG is true we need the symbol for debugging purposes even if it
5490    isn't needed for code generation.  */
5491
5492 static tree
5493 elaborate_expression (Node_Id gnat_expr, Entity_Id gnat_entity,
5494                       tree gnu_name, bool definition, bool need_value,
5495                       bool need_debug)
5496 {
5497   tree gnu_expr;
5498
5499   /* If we already elaborated this expression (e.g., it was involved
5500      in the definition of a private type), use the old value.  */
5501   if (present_gnu_tree (gnat_expr))
5502     return get_gnu_tree (gnat_expr);
5503
5504   /* If we don't need a value and this is static or a discriminant, we
5505      don't need to do anything.  */
5506   else if (!need_value
5507            && (Is_OK_Static_Expression (gnat_expr)
5508                || (Nkind (gnat_expr) == N_Identifier
5509                    && Ekind (Entity (gnat_expr)) == E_Discriminant)))
5510     return 0;
5511
5512   /* Otherwise, convert this tree to its GCC equivalent.  */
5513   gnu_expr
5514     = elaborate_expression_1 (gnat_expr, gnat_entity, gnat_to_gnu (gnat_expr),
5515                               gnu_name, definition, need_debug);
5516
5517   /* Save the expression in case we try to elaborate this entity again.  Since
5518      it's not a DECL, don't check it.  Don't save if it's a discriminant.  */
5519   if (!CONTAINS_PLACEHOLDER_P (gnu_expr))
5520     save_gnu_tree (gnat_expr, gnu_expr, true);
5521
5522   return need_value ? gnu_expr : error_mark_node;
5523 }
5524
5525 /* Similar, but take a GNU expression.  */
5526
5527 static tree
5528 elaborate_expression_1 (Node_Id gnat_expr, Entity_Id gnat_entity,
5529                         tree gnu_expr, tree gnu_name, bool definition,
5530                         bool need_debug)
5531 {
5532   tree gnu_decl = NULL_TREE;
5533   /* Skip any conversions and simple arithmetics to see if the expression
5534      is a read-only variable.
5535      ??? This really should remain read-only, but we have to think about
5536      the typing of the tree here.  */
5537   tree gnu_inner_expr
5538     = skip_simple_arithmetic (remove_conversions (gnu_expr, true));
5539   bool expr_global = Is_Public (gnat_entity) || global_bindings_p ();
5540   bool expr_variable;
5541
5542   /* In most cases, we won't see a naked FIELD_DECL here because a
5543      discriminant reference will have been replaced with a COMPONENT_REF
5544      when the type is being elaborated.  However, there are some cases
5545      involving child types where we will.  So convert it to a COMPONENT_REF
5546      here.  We have to hope it will be at the highest level of the
5547      expression in these cases.  */
5548   if (TREE_CODE (gnu_expr) == FIELD_DECL)
5549     gnu_expr = build3 (COMPONENT_REF, TREE_TYPE (gnu_expr),
5550                        build0 (PLACEHOLDER_EXPR, DECL_CONTEXT (gnu_expr)),
5551                        gnu_expr, NULL_TREE);
5552
5553   /* If GNU_EXPR is neither a placeholder nor a constant, nor a variable
5554      that is read-only, make a variable that is initialized to contain the
5555      bound when the package containing the definition is elaborated.  If
5556      this entity is defined at top level and a bound or discriminant value
5557      isn't a constant or a reference to a discriminant, replace the bound
5558      by the variable; otherwise use a SAVE_EXPR if needed.  Note that we
5559      rely here on the fact that an expression cannot contain both the
5560      discriminant and some other variable.  */
5561
5562   expr_variable = (!CONSTANT_CLASS_P (gnu_expr)
5563                    && !(TREE_CODE (gnu_inner_expr) == VAR_DECL
5564                         && (TREE_READONLY (gnu_inner_expr)
5565                             || DECL_READONLY_ONCE_ELAB (gnu_inner_expr)))
5566                    && !CONTAINS_PLACEHOLDER_P (gnu_expr));
5567
5568   /* If this is a static expression or contains a discriminant, we don't
5569      need the variable for debugging (and can't elaborate anyway if a
5570      discriminant).  */
5571   if (need_debug
5572       && (Is_OK_Static_Expression (gnat_expr)
5573           || CONTAINS_PLACEHOLDER_P (gnu_expr)))
5574     need_debug = false;
5575
5576   /* Now create the variable if we need it.  */
5577   if (need_debug || (expr_variable && expr_global))
5578     gnu_decl
5579       = create_var_decl (create_concat_name (gnat_entity,
5580                                              IDENTIFIER_POINTER (gnu_name)),
5581                          NULL_TREE, TREE_TYPE (gnu_expr), gnu_expr,
5582                          !need_debug, Is_Public (gnat_entity),
5583                          !definition, false, NULL, gnat_entity);
5584
5585   /* We only need to use this variable if we are in global context since GCC
5586      can do the right thing in the local case.  */
5587   if (expr_global && expr_variable)
5588     return gnu_decl;
5589   else if (!expr_variable)
5590     return gnu_expr;
5591   else
5592     return maybe_variable (gnu_expr);
5593 }
5594 \f
5595 /* Create a record type that contains a SIZE bytes long field of TYPE with a
5596    starting bit position so that it is aligned to ALIGN bits, and leaving at
5597    least ROOM bytes free before the field.  BASE_ALIGN is the alignment the
5598    record is guaranteed to get.  */
5599
5600 tree
5601 make_aligning_type (tree type, unsigned int align, tree size,
5602                     unsigned int base_align, int room)
5603 {
5604   /* We will be crafting a record type with one field at a position set to be
5605      the next multiple of ALIGN past record'address + room bytes.  We use a
5606      record placeholder to express record'address.  */
5607
5608   tree record_type = make_node (RECORD_TYPE);
5609   tree record = build0 (PLACEHOLDER_EXPR, record_type);
5610
5611   tree record_addr_st
5612     = convert (sizetype, build_unary_op (ADDR_EXPR, NULL_TREE, record));
5613
5614   /* The diagram below summarizes the shape of what we manipulate:
5615
5616                     <--------- pos ---------->
5617                 {  +------------+-------------+-----------------+
5618       record  =>{  |############|     ...     | field (type)    |
5619                 {  +------------+-------------+-----------------+
5620                    |<-- room -->|<- voffset ->|<---- size ----->|
5621                    o            o
5622                    |            |
5623                    record_addr  vblock_addr
5624
5625      Every length is in sizetype bytes there, except "pos" which has to be
5626      set as a bit position in the GCC tree for the record.  */
5627
5628   tree room_st = size_int (room);
5629   tree vblock_addr_st = size_binop (PLUS_EXPR, record_addr_st, room_st);
5630   tree voffset_st, pos, field;
5631
5632   tree name = TYPE_NAME (type);
5633
5634   if (TREE_CODE (name) == TYPE_DECL)
5635     name = DECL_NAME (name);
5636
5637   TYPE_NAME (record_type) = concat_id_with_name (name, "_ALIGN");
5638
5639   /* Compute VOFFSET and then POS.  The next byte position multiple of some
5640      alignment after some address is obtained by "and"ing the alignment minus
5641      1 with the two's complement of the address.   */
5642
5643   voffset_st = size_binop (BIT_AND_EXPR,
5644                            size_diffop (size_zero_node, vblock_addr_st),
5645                            ssize_int ((align / BITS_PER_UNIT) - 1));
5646
5647   /* POS = (ROOM + VOFFSET) * BIT_PER_UNIT, in bitsizetype.  */
5648
5649   pos = size_binop (MULT_EXPR,
5650                     convert (bitsizetype,
5651                              size_binop (PLUS_EXPR, room_st, voffset_st)),
5652                     bitsize_unit_node);
5653
5654   /* Craft the GCC record representation.  We exceptionally do everything
5655      manually here because 1) our generic circuitry is not quite ready to
5656      handle the complex position/size expressions we are setting up, 2) we
5657      have a strong simplifying factor at hand: we know the maximum possible
5658      value of voffset, and 3) we have to set/reset at least the sizes in
5659      accordance with this maximum value anyway, as we need them to convey
5660      what should be "alloc"ated for this type.
5661
5662      Use -1 as the 'addressable' indication for the field to prevent the
5663      creation of a bitfield.  We don't need one, it would have damaging
5664      consequences on the alignment computation, and create_field_decl would
5665      make one without this special argument, for instance because of the
5666      complex position expression.  */
5667
5668   field = create_field_decl (get_identifier ("F"), type, record_type,
5669                              1, size, pos, -1);
5670   TYPE_FIELDS (record_type) = field;
5671
5672   TYPE_ALIGN (record_type) = base_align;
5673   TYPE_USER_ALIGN (record_type) = 1;
5674
5675   TYPE_SIZE (record_type)
5676     = size_binop (PLUS_EXPR,
5677                   size_binop (MULT_EXPR, convert (bitsizetype, size),
5678                               bitsize_unit_node),
5679                   bitsize_int (align + room * BITS_PER_UNIT));
5680   TYPE_SIZE_UNIT (record_type)
5681     = size_binop (PLUS_EXPR, size,
5682                   size_int (room + align / BITS_PER_UNIT));
5683
5684   SET_TYPE_MODE (record_type, BLKmode);
5685
5686   relate_alias_sets (record_type, type, ALIAS_SET_COPY);
5687   return record_type;
5688 }
5689 \f
5690 /* Return the result of rounding T up to ALIGN.  */
5691
5692 static inline unsigned HOST_WIDE_INT
5693 round_up_to_align (unsigned HOST_WIDE_INT t, unsigned int align)
5694 {
5695   t += align - 1;
5696   t /= align;
5697   t *= align;
5698   return t;
5699 }
5700
5701 /* TYPE is a RECORD_TYPE, UNION_TYPE or QUAL_UNION_TYPE that is being used
5702    as the field type of a packed record if IN_RECORD is true, or as the
5703    component type of a packed array if IN_RECORD is false.  See if we can
5704    rewrite it either as a type that has a non-BLKmode, which we can pack
5705    tighter in the packed record case, or as a smaller type.  If so, return
5706    the new type.  If not, return the original type.  */
5707
5708 static tree
5709 make_packable_type (tree type, bool in_record)
5710 {
5711   unsigned HOST_WIDE_INT size = tree_low_cst (TYPE_SIZE (type), 1);
5712   unsigned HOST_WIDE_INT new_size;
5713   tree new_type, old_field, field_list = NULL_TREE;
5714
5715   /* No point in doing anything if the size is zero.  */
5716   if (size == 0)
5717     return type;
5718
5719   new_type = make_node (TREE_CODE (type));
5720
5721   /* Copy the name and flags from the old type to that of the new.
5722      Note that we rely on the pointer equality created here for
5723      TYPE_NAME to look through conversions in various places.  */
5724   TYPE_NAME (new_type) = TYPE_NAME (type);
5725   TYPE_JUSTIFIED_MODULAR_P (new_type) = TYPE_JUSTIFIED_MODULAR_P (type);
5726   TYPE_CONTAINS_TEMPLATE_P (new_type) = TYPE_CONTAINS_TEMPLATE_P (type);
5727   if (TREE_CODE (type) == RECORD_TYPE)
5728     TYPE_IS_PADDING_P (new_type) = TYPE_IS_PADDING_P (type);
5729
5730   /* If we are in a record and have a small size, set the alignment to
5731      try for an integral mode.  Otherwise set it to try for a smaller
5732      type with BLKmode.  */
5733   if (in_record && size <= MAX_FIXED_MODE_SIZE)
5734     {
5735       TYPE_ALIGN (new_type) = ceil_alignment (size);
5736       new_size = round_up_to_align (size, TYPE_ALIGN (new_type));
5737     }
5738   else
5739     {
5740       unsigned HOST_WIDE_INT align;
5741
5742       /* Do not try to shrink the size if the RM size is not constant.  */
5743       if (TYPE_CONTAINS_TEMPLATE_P (type)
5744           || !host_integerp (TYPE_ADA_SIZE (type), 1))
5745         return type;
5746
5747       /* Round the RM size up to a unit boundary to get the minimal size
5748          for a BLKmode record.  Give up if it's already the size.  */
5749       new_size = TREE_INT_CST_LOW (TYPE_ADA_SIZE (type));
5750       new_size = round_up_to_align (new_size, BITS_PER_UNIT);
5751       if (new_size == size)
5752         return type;
5753
5754       align = new_size & -new_size;
5755       TYPE_ALIGN (new_type) = MIN (TYPE_ALIGN (type), align);
5756     }
5757
5758   TYPE_USER_ALIGN (new_type) = 1;
5759
5760   /* Now copy the fields, keeping the position and size as we don't want
5761      to change the layout by propagating the packedness downwards.  */
5762   for (old_field = TYPE_FIELDS (type); old_field;
5763        old_field = TREE_CHAIN (old_field))
5764     {
5765       tree new_field_type = TREE_TYPE (old_field);
5766       tree new_field, new_size;
5767
5768       if ((TREE_CODE (new_field_type) == RECORD_TYPE
5769            || TREE_CODE (new_field_type) == UNION_TYPE
5770            || TREE_CODE (new_field_type) == QUAL_UNION_TYPE)
5771           && !TYPE_IS_FAT_POINTER_P (new_field_type)
5772           && host_integerp (TYPE_SIZE (new_field_type), 1))
5773         new_field_type = make_packable_type (new_field_type, true);
5774
5775       /* However, for the last field in a not already packed record type
5776          that is of an aggregate type, we need to use the RM_Size in the
5777          packable version of the record type, see finish_record_type.  */
5778       if (!TREE_CHAIN (old_field)
5779           && !TYPE_PACKED (type)
5780           && (TREE_CODE (new_field_type) == RECORD_TYPE
5781               || TREE_CODE (new_field_type) == UNION_TYPE
5782               || TREE_CODE (new_field_type) == QUAL_UNION_TYPE)
5783           && !TYPE_IS_FAT_POINTER_P (new_field_type)
5784           && !TYPE_CONTAINS_TEMPLATE_P (new_field_type)
5785           && TYPE_ADA_SIZE (new_field_type))
5786         new_size = TYPE_ADA_SIZE (new_field_type);
5787       else
5788         new_size = DECL_SIZE (old_field);
5789
5790       new_field = create_field_decl (DECL_NAME (old_field), new_field_type,
5791                                      new_type, TYPE_PACKED (type), new_size,
5792                                      bit_position (old_field),
5793                                      !DECL_NONADDRESSABLE_P (old_field));
5794
5795       DECL_INTERNAL_P (new_field) = DECL_INTERNAL_P (old_field);
5796       SET_DECL_ORIGINAL_FIELD
5797         (new_field, (DECL_ORIGINAL_FIELD (old_field)
5798                      ? DECL_ORIGINAL_FIELD (old_field) : old_field));
5799
5800       if (TREE_CODE (new_type) == QUAL_UNION_TYPE)
5801         DECL_QUALIFIER (new_field) = DECL_QUALIFIER (old_field);
5802
5803       TREE_CHAIN (new_field) = field_list;
5804       field_list = new_field;
5805     }
5806
5807   finish_record_type (new_type, nreverse (field_list), 2, true);
5808   relate_alias_sets (new_type, type, ALIAS_SET_COPY);
5809
5810   /* If this is a padding record, we never want to make the size smaller
5811      than what was specified.  For QUAL_UNION_TYPE, also copy the size.  */
5812   if ((TREE_CODE (type) == RECORD_TYPE && TYPE_IS_PADDING_P (type))
5813       || TREE_CODE (type) == QUAL_UNION_TYPE)
5814     {
5815       TYPE_SIZE (new_type) = TYPE_SIZE (type);
5816       TYPE_SIZE_UNIT (new_type) = TYPE_SIZE_UNIT (type);
5817     }
5818   else
5819     {
5820       TYPE_SIZE (new_type) = bitsize_int (new_size);
5821       TYPE_SIZE_UNIT (new_type)
5822         = size_int ((new_size + BITS_PER_UNIT - 1) / BITS_PER_UNIT);
5823     }
5824
5825   if (!TYPE_CONTAINS_TEMPLATE_P (type))
5826     SET_TYPE_ADA_SIZE (new_type, TYPE_ADA_SIZE (type));
5827
5828   compute_record_mode (new_type);
5829
5830   /* Try harder to get a packable type if necessary, for example
5831      in case the record itself contains a BLKmode field.  */
5832   if (in_record && TYPE_MODE (new_type) == BLKmode)
5833     SET_TYPE_MODE (new_type,
5834                    mode_for_size_tree (TYPE_SIZE (new_type), MODE_INT, 1));
5835
5836   /* If neither the mode nor the size has shrunk, return the old type.  */
5837   if (TYPE_MODE (new_type) == BLKmode && new_size >= size)
5838     return type;
5839
5840   return new_type;
5841 }
5842 \f
5843 /* Ensure that TYPE has SIZE and ALIGN.  Make and return a new padded type
5844    if needed.  We have already verified that SIZE and TYPE are large enough.
5845
5846    GNAT_ENTITY and NAME_TRAILER are used to name the resulting record and
5847    to issue a warning.
5848
5849    IS_USER_TYPE is true if we must complete the original type.
5850
5851    DEFINITION is true if this type is being defined.
5852
5853    SAME_RM_SIZE is true if the RM_Size of the resulting type is to be set
5854    to SIZE too; otherwise, it's set to the RM_Size of the original type.  */
5855
5856 tree
5857 maybe_pad_type (tree type, tree size, unsigned int align,
5858                 Entity_Id gnat_entity, const char *name_trailer,
5859                 bool is_user_type, bool definition, bool same_rm_size)
5860 {
5861   tree orig_rm_size = same_rm_size ? NULL_TREE : rm_size (type);
5862   tree orig_size = TYPE_SIZE (type);
5863   unsigned int orig_align = align;
5864   tree record, field;
5865
5866   /* If TYPE is a padded type, see if it agrees with any size and alignment
5867      we were given.  If so, return the original type.  Otherwise, strip
5868      off the padding, since we will either be returning the inner type
5869      or repadding it.  If no size or alignment is specified, use that of
5870      the original padded type.  */
5871   if (TREE_CODE (type) == RECORD_TYPE && TYPE_IS_PADDING_P (type))
5872     {
5873       if ((!size
5874            || operand_equal_p (round_up (size,
5875                                          MAX (align, TYPE_ALIGN (type))),
5876                                round_up (TYPE_SIZE (type),
5877                                          MAX (align, TYPE_ALIGN (type))),
5878                                0))
5879           && (align == 0 || align == TYPE_ALIGN (type)))
5880         return type;
5881
5882       if (!size)
5883         size = TYPE_SIZE (type);
5884       if (align == 0)
5885         align = TYPE_ALIGN (type);
5886
5887       type = TREE_TYPE (TYPE_FIELDS (type));
5888       orig_size = TYPE_SIZE (type);
5889     }
5890
5891   /* If the size is either not being changed or is being made smaller (which
5892      is not done here (and is only valid for bitfields anyway), show the size
5893      isn't changing.  Likewise, clear the alignment if it isn't being
5894      changed.  Then return if we aren't doing anything.  */
5895   if (size
5896       && (operand_equal_p (size, orig_size, 0)
5897           || (TREE_CODE (orig_size) == INTEGER_CST
5898               && tree_int_cst_lt (size, orig_size))))
5899     size = NULL_TREE;
5900
5901   if (align == TYPE_ALIGN (type))
5902     align = 0;
5903
5904   if (align == 0 && !size)
5905     return type;
5906
5907   /* If requested, complete the original type and give it a name.  */
5908   if (is_user_type)
5909     create_type_decl (get_entity_name (gnat_entity), type,
5910                       NULL, !Comes_From_Source (gnat_entity),
5911                       !(TYPE_NAME (type)
5912                         && TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
5913                         && DECL_IGNORED_P (TYPE_NAME (type))),
5914                       gnat_entity);
5915
5916   /* We used to modify the record in place in some cases, but that could
5917      generate incorrect debugging information.  So make a new record
5918      type and name.  */
5919   record = make_node (RECORD_TYPE);
5920   TYPE_IS_PADDING_P (record) = 1;
5921
5922   if (Present (gnat_entity))
5923     TYPE_NAME (record) = create_concat_name (gnat_entity, name_trailer);
5924
5925   TYPE_VOLATILE (record)
5926     = Present (gnat_entity) && Treat_As_Volatile (gnat_entity);
5927
5928   TYPE_ALIGN (record) = align;
5929   if (orig_align)
5930     TYPE_USER_ALIGN (record) = align;
5931
5932   TYPE_SIZE (record) = size ? size : orig_size;
5933   TYPE_SIZE_UNIT (record)
5934     = convert (sizetype,
5935                size_binop (CEIL_DIV_EXPR, TYPE_SIZE (record),
5936                            bitsize_unit_node));
5937
5938   /* If we are changing the alignment and the input type is a record with
5939      BLKmode and a small constant size, try to make a form that has an
5940      integral mode.  This might allow the padding record to also have an
5941      integral mode, which will be much more efficient.  There is no point
5942      in doing so if a size is specified unless it is also a small constant
5943      size and it is incorrect to do so if we cannot guarantee that the mode
5944      will be naturally aligned since the field must always be addressable.
5945
5946      ??? This might not always be a win when done for a stand-alone object:
5947      since the nominal and the effective type of the object will now have
5948      different modes, a VIEW_CONVERT_EXPR will be required for converting
5949      between them and it might be hard to overcome afterwards, including
5950      at the RTL level when the stand-alone object is accessed as a whole.  */
5951   if (align != 0
5952       && TREE_CODE (type) == RECORD_TYPE
5953       && TYPE_MODE (type) == BLKmode
5954       && TREE_CODE (orig_size) == INTEGER_CST
5955       && !TREE_OVERFLOW (orig_size)
5956       && compare_tree_int (orig_size, MAX_FIXED_MODE_SIZE) <= 0
5957       && (!size
5958           || (TREE_CODE (size) == INTEGER_CST
5959               && compare_tree_int (size, MAX_FIXED_MODE_SIZE) <= 0)))
5960     {
5961       tree packable_type = make_packable_type (type, true);
5962       if (TYPE_MODE (packable_type) != BLKmode
5963           && align >= TYPE_ALIGN (packable_type))
5964         type = packable_type;
5965     }
5966
5967   /* Now create the field with the original size.  */
5968   field  = create_field_decl (get_identifier ("F"), type, record, 0,
5969                               orig_size, bitsize_zero_node, 1);
5970   DECL_INTERNAL_P (field) = 1;
5971
5972   /* Do not finalize it until after the auxiliary record is built.  */
5973   finish_record_type (record, field, 1, true);
5974
5975   /* Set the same size for its RM_size if requested; otherwise reuse
5976      the RM_size of the original type.  */
5977   SET_TYPE_ADA_SIZE (record, same_rm_size ? size : orig_rm_size);
5978
5979   /* Unless debugging information isn't being written for the input type,
5980      write a record that shows what we are a subtype of and also make a
5981      variable that indicates our size, if still variable.  */
5982   if (TYPE_NAME (record)
5983       && AGGREGATE_TYPE_P (type)
5984       && TREE_CODE (orig_size) != INTEGER_CST
5985       && !(TREE_CODE (TYPE_NAME (type)) == TYPE_DECL
5986            && DECL_IGNORED_P (TYPE_NAME (type))))
5987     {
5988       tree marker = make_node (RECORD_TYPE);
5989       tree name = TYPE_NAME (record);
5990       tree orig_name = TYPE_NAME (type);
5991
5992       if (TREE_CODE (name) == TYPE_DECL)
5993         name = DECL_NAME (name);
5994
5995       if (TREE_CODE (orig_name) == TYPE_DECL)
5996         orig_name = DECL_NAME (orig_name);
5997
5998       TYPE_NAME (marker) = concat_id_with_name (name, "XVS");
5999       finish_record_type (marker,
6000                           create_field_decl (orig_name, integer_type_node,
6001                                              marker, 0, NULL_TREE, NULL_TREE,
6002                                              0),
6003                           0, false);
6004
6005       add_parallel_type (TYPE_STUB_DECL (record), marker);
6006
6007       if (size && TREE_CODE (size) != INTEGER_CST && definition)
6008         create_var_decl (concat_id_with_name (name, "XVZ"), NULL_TREE,
6009                          sizetype, TYPE_SIZE_UNIT (record), false, false,
6010                          false, false, NULL, gnat_entity);
6011     }
6012
6013   rest_of_record_type_compilation (record);
6014
6015   /* If the size was widened explicitly, maybe give a warning.  Take the
6016      original size as the maximum size of the input if there was an
6017      unconstrained record involved and round it up to the specified alignment,
6018      if one was specified.  */
6019   if (CONTAINS_PLACEHOLDER_P (orig_size))
6020     orig_size = max_size (orig_size, true);
6021
6022   if (align)
6023     orig_size = round_up (orig_size, align);
6024
6025   if (size && Present (gnat_entity)
6026       && !operand_equal_p (size, orig_size, 0)
6027       && !(TREE_CODE (size) == INTEGER_CST
6028            && TREE_CODE (orig_size) == INTEGER_CST
6029            && tree_int_cst_lt (size, orig_size)))
6030     {
6031       Node_Id gnat_error_node = Empty;
6032
6033       if (Is_Packed_Array_Type (gnat_entity))
6034         gnat_entity = Original_Array_Type (gnat_entity);
6035
6036       if ((Ekind (gnat_entity) == E_Component
6037            || Ekind (gnat_entity) == E_Discriminant)
6038           && Present (Component_Clause (gnat_entity)))
6039         gnat_error_node = Last_Bit (Component_Clause (gnat_entity));
6040       else if (Present (Size_Clause (gnat_entity)))
6041         gnat_error_node = Expression (Size_Clause (gnat_entity));
6042
6043       /* Generate message only for entities that come from source, since
6044          if we have an entity created by expansion, the message will be
6045          generated for some other corresponding source entity.  */
6046       if (Comes_From_Source (gnat_entity) && Present (gnat_error_node))
6047         post_error_ne_tree ("{^ }bits of & unused?", gnat_error_node,
6048                             gnat_entity,
6049                             size_diffop (size, orig_size));
6050
6051       else if (*name_trailer == 'C' && !Is_Internal (gnat_entity))
6052         post_error_ne_tree ("component of& padded{ by ^ bits}?",
6053                             gnat_entity, gnat_entity,
6054                             size_diffop (size, orig_size));
6055     }
6056
6057   return record;
6058 }
6059 \f
6060 /* Given a GNU tree and a GNAT list of choices, generate an expression to test
6061    the value passed against the list of choices.  */
6062
6063 tree
6064 choices_to_gnu (tree operand, Node_Id choices)
6065 {
6066   Node_Id choice;
6067   Node_Id gnat_temp;
6068   tree result = integer_zero_node;
6069   tree this_test, low = 0, high = 0, single = 0;
6070
6071   for (choice = First (choices); Present (choice); choice = Next (choice))
6072     {
6073       switch (Nkind (choice))
6074         {
6075         case N_Range:
6076           low = gnat_to_gnu (Low_Bound (choice));
6077           high = gnat_to_gnu (High_Bound (choice));
6078
6079           /* There's no good type to use here, so we might as well use
6080              integer_type_node.  */
6081           this_test
6082             = build_binary_op (TRUTH_ANDIF_EXPR, integer_type_node,
6083                                build_binary_op (GE_EXPR, integer_type_node,
6084                                                 operand, low),
6085                                build_binary_op (LE_EXPR, integer_type_node,
6086                                                 operand, high));
6087
6088           break;
6089
6090         case N_Subtype_Indication:
6091           gnat_temp = Range_Expression (Constraint (choice));
6092           low = gnat_to_gnu (Low_Bound (gnat_temp));
6093           high = gnat_to_gnu (High_Bound (gnat_temp));
6094
6095           this_test
6096             = build_binary_op (TRUTH_ANDIF_EXPR, integer_type_node,
6097                                build_binary_op (GE_EXPR, integer_type_node,
6098                                                 operand, low),
6099                                build_binary_op (LE_EXPR, integer_type_node,
6100                                                 operand, high));
6101           break;
6102
6103         case N_Identifier:
6104         case N_Expanded_Name:
6105           /* This represents either a subtype range, an enumeration
6106              literal, or a constant  Ekind says which.  If an enumeration
6107              literal or constant, fall through to the next case.  */
6108           if (Ekind (Entity (choice)) != E_Enumeration_Literal
6109               && Ekind (Entity (choice)) != E_Constant)
6110             {
6111               tree type = gnat_to_gnu_type (Entity (choice));
6112
6113               low = TYPE_MIN_VALUE (type);
6114               high = TYPE_MAX_VALUE (type);
6115
6116               this_test
6117                 = build_binary_op (TRUTH_ANDIF_EXPR, integer_type_node,
6118                                    build_binary_op (GE_EXPR, integer_type_node,
6119                                                     operand, low),
6120                                    build_binary_op (LE_EXPR, integer_type_node,
6121                                                     operand, high));
6122               break;
6123             }
6124
6125           /* ... fall through ... */
6126
6127         case N_Character_Literal:
6128         case N_Integer_Literal:
6129           single = gnat_to_gnu (choice);
6130           this_test = build_binary_op (EQ_EXPR, integer_type_node, operand,
6131                                        single);
6132           break;
6133
6134         case N_Others_Choice:
6135           this_test = integer_one_node;
6136           break;
6137
6138         default:
6139           gcc_unreachable ();
6140         }
6141
6142       result = build_binary_op (TRUTH_ORIF_EXPR, integer_type_node,
6143                                 result, this_test);
6144     }
6145
6146   return result;
6147 }
6148 \f
6149 /* Adjust PACKED setting as passed to gnat_to_gnu_field for a field of
6150    type FIELD_TYPE to be placed in RECORD_TYPE.  Return the result.  */
6151
6152 static int
6153 adjust_packed (tree field_type, tree record_type, int packed)
6154 {
6155   /* If the field contains an item of variable size, we cannot pack it
6156      because we cannot create temporaries of non-fixed size in case
6157      we need to take the address of the field.  See addressable_p and
6158      the notes on the addressability issues for further details.  */
6159   if (is_variable_size (field_type))
6160     return 0;
6161
6162   /* If the alignment of the record is specified and the field type
6163      is over-aligned, request Storage_Unit alignment for the field.  */
6164   if (packed == -2)
6165     {
6166       if (TYPE_ALIGN (field_type) > TYPE_ALIGN (record_type))
6167         return -1;
6168       else
6169         return 0;
6170     }
6171
6172   return packed;
6173 }
6174
6175 /* Return a GCC tree for a field corresponding to GNAT_FIELD to be
6176    placed in GNU_RECORD_TYPE.
6177
6178    PACKED is 1 if the enclosing record is packed, -1 if the enclosing
6179    record has Component_Alignment of Storage_Unit, -2 if the enclosing
6180    record has a specified alignment.
6181
6182    DEFINITION is true if this field is for a record being defined.  */
6183
6184 static tree
6185 gnat_to_gnu_field (Entity_Id gnat_field, tree gnu_record_type, int packed,
6186                    bool definition)
6187 {
6188   tree gnu_field_id = get_entity_name (gnat_field);
6189   tree gnu_field_type = gnat_to_gnu_type (Etype (gnat_field));
6190   tree gnu_field, gnu_size, gnu_pos;
6191   bool needs_strict_alignment
6192     = (Is_Aliased (gnat_field) || Strict_Alignment (Etype (gnat_field))
6193        || Treat_As_Volatile (gnat_field));
6194
6195   /* If this field requires strict alignment, we cannot pack it because
6196      it would very likely be under-aligned in the record.  */
6197   if (needs_strict_alignment)
6198     packed = 0;
6199   else
6200     packed = adjust_packed (gnu_field_type, gnu_record_type, packed);
6201
6202   /* If a size is specified, use it.  Otherwise, if the record type is packed,
6203      use the official RM size.  See "Handling of Type'Size Values" in Einfo
6204      for further details.  */
6205   if (Known_Static_Esize (gnat_field))
6206     gnu_size = validate_size (Esize (gnat_field), gnu_field_type,
6207                               gnat_field, FIELD_DECL, false, true);
6208   else if (packed == 1)
6209     gnu_size = validate_size (RM_Size (Etype (gnat_field)), gnu_field_type,
6210                               gnat_field, FIELD_DECL, false, true);
6211   else
6212     gnu_size = NULL_TREE;
6213
6214   /* If we have a specified size that's smaller than that of the field type,
6215      or a position is specified, and the field type is a record, see if we can
6216      get either an integral mode form of the type or a smaller form.  If we
6217      can, show a size was specified for the field if there wasn't one already,
6218      so we know to make this a bitfield and avoid making things wider.
6219
6220      Doing this is first useful if the record is packed because we may then
6221      place the field at a non-byte-aligned position and so achieve tighter
6222      packing.
6223
6224      This is in addition *required* if the field shares a byte with another
6225      field and the front-end lets the back-end handle the references, because
6226      GCC does not handle BLKmode bitfields properly.
6227
6228      We avoid the transformation if it is not required or potentially useful,
6229      as it might entail an increase of the field's alignment and have ripple
6230      effects on the outer record type.  A typical case is a field known to be
6231      byte aligned and not to share a byte with another field.
6232
6233      Besides, we don't even look the possibility of a transformation in cases
6234      known to be in error already, for instance when an invalid size results
6235      from a component clause.  */
6236
6237   if (TREE_CODE (gnu_field_type) == RECORD_TYPE
6238       && !TYPE_IS_FAT_POINTER_P (gnu_field_type)
6239       && host_integerp (TYPE_SIZE (gnu_field_type), 1)
6240       && (packed == 1
6241           || (gnu_size
6242               && (tree_int_cst_lt (gnu_size, TYPE_SIZE (gnu_field_type))
6243                   || Present (Component_Clause (gnat_field))))))
6244     {
6245       /* See what the alternate type and size would be.  */
6246       tree gnu_packable_type = make_packable_type (gnu_field_type, true);
6247
6248       bool has_byte_aligned_clause
6249         = Present (Component_Clause (gnat_field))
6250           && (UI_To_Int (Component_Bit_Offset (gnat_field))
6251               % BITS_PER_UNIT == 0);
6252
6253       /* Compute whether we should avoid the substitution.  */
6254       bool reject
6255         /* There is no point substituting if there is no change...  */
6256         = (gnu_packable_type == gnu_field_type)
6257          /* ... nor when the field is known to be byte aligned and not to
6258             share a byte with another field.  */
6259           || (has_byte_aligned_clause
6260               && value_factor_p (gnu_size, BITS_PER_UNIT))
6261          /* The size of an aliased field must be an exact multiple of the
6262             type's alignment, which the substitution might increase.  Reject
6263             substitutions that would so invalidate a component clause when the
6264             specified position is byte aligned, as the change would have no
6265             real benefit from the packing standpoint anyway.  */
6266           || (Is_Aliased (gnat_field)
6267               && has_byte_aligned_clause
6268               && !value_factor_p (gnu_size, TYPE_ALIGN (gnu_packable_type)));
6269
6270       /* Substitute unless told otherwise.  */
6271       if (!reject)
6272         {
6273           gnu_field_type = gnu_packable_type;
6274
6275           if (!gnu_size)
6276             gnu_size = rm_size (gnu_field_type);
6277         }
6278     }
6279
6280   /* If we are packing the record and the field is BLKmode, round the
6281      size up to a byte boundary.  */
6282   if (packed && TYPE_MODE (gnu_field_type) == BLKmode && gnu_size)
6283     gnu_size = round_up (gnu_size, BITS_PER_UNIT);
6284
6285   if (Present (Component_Clause (gnat_field)))
6286     {
6287       gnu_pos = UI_To_gnu (Component_Bit_Offset (gnat_field), bitsizetype);
6288       gnu_size = validate_size (Esize (gnat_field), gnu_field_type,
6289                                 gnat_field, FIELD_DECL, false, true);
6290
6291       /* Ensure the position does not overlap with the parent subtype,
6292          if there is one.  */
6293       if (Present (Parent_Subtype (Underlying_Type (Scope (gnat_field)))))
6294         {
6295           tree gnu_parent
6296             = gnat_to_gnu_type (Parent_Subtype
6297                                 (Underlying_Type (Scope (gnat_field))));
6298
6299           if (TREE_CODE (TYPE_SIZE (gnu_parent)) == INTEGER_CST
6300               && tree_int_cst_lt (gnu_pos, TYPE_SIZE (gnu_parent)))
6301             {
6302               post_error_ne_tree
6303                 ("offset of& must be beyond parent{, minimum allowed is ^}",
6304                  First_Bit (Component_Clause (gnat_field)), gnat_field,
6305                  TYPE_SIZE_UNIT (gnu_parent));
6306             }
6307         }
6308
6309       /* If this field needs strict alignment, ensure the record is
6310          sufficiently aligned and that that position and size are
6311          consistent with the alignment.  */
6312       if (needs_strict_alignment)
6313         {
6314           TYPE_ALIGN (gnu_record_type)
6315             = MAX (TYPE_ALIGN (gnu_record_type), TYPE_ALIGN (gnu_field_type));
6316
6317           if (gnu_size
6318               && !operand_equal_p (gnu_size, TYPE_SIZE (gnu_field_type), 0))
6319             {
6320               if (Is_Atomic (gnat_field) || Is_Atomic (Etype (gnat_field)))
6321                 post_error_ne_tree
6322                   ("atomic field& must be natural size of type{ (^)}",
6323                    Last_Bit (Component_Clause (gnat_field)), gnat_field,
6324                    TYPE_SIZE (gnu_field_type));
6325
6326               else if (Is_Aliased (gnat_field))
6327                 post_error_ne_tree
6328                   ("size of aliased field& must be ^ bits",
6329                    Last_Bit (Component_Clause (gnat_field)), gnat_field,
6330                    TYPE_SIZE (gnu_field_type));
6331
6332               else if (Strict_Alignment (Etype (gnat_field)))
6333                 post_error_ne_tree
6334                   ("size of & with aliased or tagged components not ^ bits",
6335                    Last_Bit (Component_Clause (gnat_field)), gnat_field,
6336                    TYPE_SIZE (gnu_field_type));
6337
6338               gnu_size = NULL_TREE;
6339             }
6340
6341           if (!integer_zerop (size_binop
6342                               (TRUNC_MOD_EXPR, gnu_pos,
6343                                bitsize_int (TYPE_ALIGN (gnu_field_type)))))
6344             {
6345               if (Is_Aliased (gnat_field))
6346                 post_error_ne_num
6347                   ("position of aliased field& must be multiple of ^ bits",
6348                    First_Bit (Component_Clause (gnat_field)), gnat_field,
6349                    TYPE_ALIGN (gnu_field_type));
6350
6351               else if (Treat_As_Volatile (gnat_field))
6352                 post_error_ne_num
6353                   ("position of volatile field& must be multiple of ^ bits",
6354                    First_Bit (Component_Clause (gnat_field)), gnat_field,
6355                    TYPE_ALIGN (gnu_field_type));
6356
6357               else if (Strict_Alignment (Etype (gnat_field)))
6358                 post_error_ne_num
6359   ("position of & with aliased or tagged components not multiple of ^ bits",
6360                    First_Bit (Component_Clause (gnat_field)), gnat_field,
6361                    TYPE_ALIGN (gnu_field_type));
6362
6363               else
6364                 gcc_unreachable ();
6365
6366               gnu_pos = NULL_TREE;
6367             }
6368         }
6369
6370       if (Is_Atomic (gnat_field))
6371         check_ok_for_atomic (gnu_field_type, gnat_field, false);
6372     }
6373
6374   /* If the record has rep clauses and this is the tag field, make a rep
6375      clause for it as well.  */
6376   else if (Has_Specified_Layout (Scope (gnat_field))
6377            && Chars (gnat_field) == Name_uTag)
6378     {
6379       gnu_pos = bitsize_zero_node;
6380       gnu_size = TYPE_SIZE (gnu_field_type);
6381     }
6382
6383   else
6384     gnu_pos = NULL_TREE;
6385
6386   /* We need to make the size the maximum for the type if it is
6387      self-referential and an unconstrained type.  In that case, we can't
6388      pack the field since we can't make a copy to align it.  */
6389   if (TREE_CODE (gnu_field_type) == RECORD_TYPE
6390       && !gnu_size
6391       && CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_field_type))
6392       && !Is_Constrained (Underlying_Type (Etype (gnat_field))))
6393     {
6394       gnu_size = max_size (TYPE_SIZE (gnu_field_type), true);
6395       packed = 0;
6396     }
6397
6398   /* If a size is specified, adjust the field's type to it.  */
6399   if (gnu_size)
6400     {
6401       /* If the field's type is justified modular, we would need to remove
6402          the wrapper to (better) meet the layout requirements.  However we
6403          can do so only if the field is not aliased to preserve the unique
6404          layout and if the prescribed size is not greater than that of the
6405          packed array to preserve the justification.  */
6406       if (!needs_strict_alignment
6407           && TREE_CODE (gnu_field_type) == RECORD_TYPE
6408           && TYPE_JUSTIFIED_MODULAR_P (gnu_field_type)
6409           && tree_int_cst_compare (gnu_size, TYPE_ADA_SIZE (gnu_field_type))
6410                <= 0)
6411         gnu_field_type = TREE_TYPE (TYPE_FIELDS (gnu_field_type));
6412
6413       gnu_field_type
6414         = make_type_from_size (gnu_field_type, gnu_size,
6415                                Has_Biased_Representation (gnat_field));
6416       gnu_field_type = maybe_pad_type (gnu_field_type, gnu_size, 0, gnat_field,
6417                                        "PAD", false, definition, true);
6418     }
6419
6420   /* Otherwise (or if there was an error), don't specify a position.  */
6421   else
6422     gnu_pos = NULL_TREE;
6423
6424   gcc_assert (TREE_CODE (gnu_field_type) != RECORD_TYPE
6425               || !TYPE_CONTAINS_TEMPLATE_P (gnu_field_type));
6426
6427   /* Now create the decl for the field.  */
6428   gnu_field = create_field_decl (gnu_field_id, gnu_field_type, gnu_record_type,
6429                                  packed, gnu_size, gnu_pos,
6430                                  Is_Aliased (gnat_field));
6431   Sloc_to_locus (Sloc (gnat_field), &DECL_SOURCE_LOCATION (gnu_field));
6432   TREE_THIS_VOLATILE (gnu_field) = Treat_As_Volatile (gnat_field);
6433
6434   if (Ekind (gnat_field) == E_Discriminant)
6435     DECL_DISCRIMINANT_NUMBER (gnu_field)
6436       = UI_To_gnu (Discriminant_Number (gnat_field), sizetype);
6437
6438   return gnu_field;
6439 }
6440 \f
6441 /* Return true if TYPE is a type with variable size, a padding type with a
6442    field of variable size or is a record that has a field such a field.  */
6443
6444 static bool
6445 is_variable_size (tree type)
6446 {
6447   tree field;
6448
6449   if (!TREE_CONSTANT (TYPE_SIZE (type)))
6450     return true;
6451
6452   if (TREE_CODE (type) == RECORD_TYPE
6453       && TYPE_IS_PADDING_P (type)
6454       && !TREE_CONSTANT (DECL_SIZE (TYPE_FIELDS (type))))
6455     return true;
6456
6457   if (TREE_CODE (type) != RECORD_TYPE
6458       && TREE_CODE (type) != UNION_TYPE
6459       && TREE_CODE (type) != QUAL_UNION_TYPE)
6460     return false;
6461
6462   for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
6463     if (is_variable_size (TREE_TYPE (field)))
6464       return true;
6465
6466   return false;
6467 }
6468 \f
6469 /* qsort comparer for the bit positions of two record components.  */
6470
6471 static int
6472 compare_field_bitpos (const PTR rt1, const PTR rt2)
6473 {
6474   const_tree const field1 = * (const_tree const *) rt1;
6475   const_tree const field2 = * (const_tree const *) rt2;
6476   const int ret
6477     = tree_int_cst_compare (bit_position (field1), bit_position (field2));
6478
6479   return ret ? ret : (int) (DECL_UID (field1) - DECL_UID (field2));
6480 }
6481
6482 /* Return a GCC tree for a record type given a GNAT Component_List and a chain
6483    of GCC trees for fields that are in the record and have already been
6484    processed.  When called from gnat_to_gnu_entity during the processing of a
6485    record type definition, the GCC nodes for the discriminants will be on
6486    the chain.  The other calls to this function are recursive calls from
6487    itself for the Component_List of a variant and the chain is empty.
6488
6489    PACKED is 1 if this is for a packed record, -1 if this is for a record
6490    with Component_Alignment of Storage_Unit, -2 if this is for a record
6491    with a specified alignment.
6492
6493    DEFINITION is true if we are defining this record.
6494
6495    P_GNU_REP_LIST, if nonzero, is a pointer to a list to which each field
6496    with a rep clause is to be added.  If it is nonzero, that is all that
6497    should be done with such fields.
6498
6499    CANCEL_ALIGNMENT, if true, means the alignment should be zeroed before
6500    laying out the record.  This means the alignment only serves to force fields
6501    to be bitfields, but not require the record to be that aligned.  This is
6502    used for variants.
6503
6504    ALL_REP, if true, means a rep clause was found for all the fields.  This
6505    simplifies the logic since we know we're not in the mixed case.
6506
6507    DO_NOT_FINALIZE, if true, means that the record type is expected to be
6508    modified afterwards so it will not be sent to the back-end for finalization.
6509
6510    UNCHECKED_UNION, if true, means that we are building a type for a record
6511    with a Pragma Unchecked_Union.
6512
6513    The processing of the component list fills in the chain with all of the
6514    fields of the record and then the record type is finished.  */
6515
6516 static void
6517 components_to_record (tree gnu_record_type, Node_Id component_list,
6518                       tree gnu_field_list, int packed, bool definition,
6519                       tree *p_gnu_rep_list, bool cancel_alignment,
6520                       bool all_rep, bool do_not_finalize, bool unchecked_union)
6521 {
6522   Node_Id component_decl;
6523   Entity_Id gnat_field;
6524   Node_Id variant_part;
6525   tree gnu_our_rep_list = NULL_TREE;
6526   tree gnu_field, gnu_last;
6527   bool layout_with_rep = false;
6528   bool all_rep_and_size = all_rep && TYPE_SIZE (gnu_record_type);
6529
6530   /* For each variable within each component declaration create a GCC field
6531      and add it to the list, skipping any pragmas in the list.  */
6532   if (Present (Component_Items (component_list)))
6533     for (component_decl = First_Non_Pragma (Component_Items (component_list));
6534          Present (component_decl);
6535          component_decl = Next_Non_Pragma (component_decl))
6536       {
6537         gnat_field = Defining_Entity (component_decl);
6538
6539         if (Chars (gnat_field) == Name_uParent)
6540           gnu_field = tree_last (TYPE_FIELDS (gnu_record_type));
6541         else
6542           {
6543             gnu_field = gnat_to_gnu_field (gnat_field, gnu_record_type,
6544                                            packed, definition);
6545
6546             /* If this is the _Tag field, put it before any discriminants,
6547                instead of after them as is the case for all other fields.  */
6548             if (Chars (gnat_field) == Name_uTag)
6549               gnu_field_list = chainon (gnu_field_list, gnu_field);
6550             else
6551               {
6552                 TREE_CHAIN (gnu_field) = gnu_field_list;
6553                 gnu_field_list = gnu_field;
6554               }
6555           }
6556
6557         save_gnu_tree (gnat_field, gnu_field, false);
6558       }
6559
6560   /* At the end of the component list there may be a variant part.  */
6561   variant_part = Variant_Part (component_list);
6562
6563   /* We create a QUAL_UNION_TYPE for the variant part since the variants are
6564      mutually exclusive and should go in the same memory.  To do this we need
6565      to treat each variant as a record whose elements are created from the
6566      component list for the variant.  So here we create the records from the
6567      lists for the variants and put them all into the QUAL_UNION_TYPE.
6568      If this is an Unchecked_Union, we make a UNION_TYPE instead or
6569      use GNU_RECORD_TYPE if there are no fields so far.  */
6570   if (Present (variant_part))
6571     {
6572       tree gnu_discriminant = gnat_to_gnu (Name (variant_part));
6573       Node_Id variant;
6574       tree gnu_name = TYPE_NAME (gnu_record_type);
6575       tree gnu_var_name
6576         = concat_id_with_name (get_identifier (Get_Name_String
6577                                                (Chars (Name (variant_part)))),
6578                                "XVN");
6579       tree gnu_union_type;
6580       tree gnu_union_name;
6581       tree gnu_union_field;
6582       tree gnu_variant_list = NULL_TREE;
6583
6584       if (TREE_CODE (gnu_name) == TYPE_DECL)
6585         gnu_name = DECL_NAME (gnu_name);
6586
6587       gnu_union_name = concat_id_with_name (gnu_name,
6588                                             IDENTIFIER_POINTER (gnu_var_name));
6589
6590       /* Reuse an enclosing union if all fields are in the variant part
6591          and there is no representation clause on the record, to match
6592          the layout of C unions.  There is an associated check below.  */
6593       if (!gnu_field_list
6594           && TREE_CODE (gnu_record_type) == UNION_TYPE
6595           && !TYPE_PACKED (gnu_record_type))
6596         gnu_union_type = gnu_record_type;
6597       else
6598         {
6599           gnu_union_type
6600             = make_node (unchecked_union ? UNION_TYPE : QUAL_UNION_TYPE);
6601
6602           TYPE_NAME (gnu_union_type) = gnu_union_name;
6603           TYPE_ALIGN (gnu_union_type) = 0;
6604           TYPE_PACKED (gnu_union_type) = TYPE_PACKED (gnu_record_type);
6605         }
6606
6607       for (variant = First_Non_Pragma (Variants (variant_part));
6608            Present (variant);
6609            variant = Next_Non_Pragma (variant))
6610         {
6611           tree gnu_variant_type = make_node (RECORD_TYPE);
6612           tree gnu_inner_name;
6613           tree gnu_qual;
6614
6615           Get_Variant_Encoding (variant);
6616           gnu_inner_name = get_identifier (Name_Buffer);
6617           TYPE_NAME (gnu_variant_type)
6618             = concat_id_with_name (gnu_union_name,
6619                                    IDENTIFIER_POINTER (gnu_inner_name));
6620
6621           /* Set the alignment of the inner type in case we need to make
6622              inner objects into bitfields, but then clear it out
6623              so the record actually gets only the alignment required.  */
6624           TYPE_ALIGN (gnu_variant_type) = TYPE_ALIGN (gnu_record_type);
6625           TYPE_PACKED (gnu_variant_type) = TYPE_PACKED (gnu_record_type);
6626
6627           /* Similarly, if the outer record has a size specified and all fields
6628              have record rep clauses, we can propagate the size into the
6629              variant part.  */
6630           if (all_rep_and_size)
6631             {
6632               TYPE_SIZE (gnu_variant_type) = TYPE_SIZE (gnu_record_type);
6633               TYPE_SIZE_UNIT (gnu_variant_type)
6634                 = TYPE_SIZE_UNIT (gnu_record_type);
6635             }
6636
6637           /* Create the record type for the variant.  Note that we defer
6638              finalizing it until after we are sure to actually use it.  */
6639           components_to_record (gnu_variant_type, Component_List (variant),
6640                                 NULL_TREE, packed, definition,
6641                                 &gnu_our_rep_list, !all_rep_and_size, all_rep,
6642                                 true, unchecked_union);
6643
6644           gnu_qual = choices_to_gnu (gnu_discriminant,
6645                                      Discrete_Choices (variant));
6646
6647           Set_Present_Expr (variant, annotate_value (gnu_qual));
6648
6649           /* If this is an Unchecked_Union and we have exactly one field,
6650              use this field directly to match the layout of C unions.  */
6651           if (unchecked_union
6652               && TYPE_FIELDS (gnu_variant_type)
6653               && !TREE_CHAIN (TYPE_FIELDS (gnu_variant_type)))
6654             gnu_field = TYPE_FIELDS (gnu_variant_type);
6655           else
6656             {
6657               /* Deal with packedness like in gnat_to_gnu_field.  */
6658               int field_packed
6659                 = adjust_packed (gnu_variant_type, gnu_record_type, packed);
6660
6661               /* Finalize the record type now.  We used to throw away
6662                  empty records but we no longer do that because we need
6663                  them to generate complete debug info for the variant;
6664                  otherwise, the union type definition will be lacking
6665                  the fields associated with these empty variants.  */
6666               rest_of_record_type_compilation (gnu_variant_type);
6667
6668               gnu_field = create_field_decl (gnu_inner_name, gnu_variant_type,
6669                                              gnu_union_type, field_packed,
6670                                              (all_rep_and_size
6671                                               ? TYPE_SIZE (gnu_variant_type)
6672                                               : 0),
6673                                              (all_rep_and_size
6674                                               ? bitsize_zero_node : 0),
6675                                              0);
6676
6677               DECL_INTERNAL_P (gnu_field) = 1;
6678
6679               if (!unchecked_union)
6680                 DECL_QUALIFIER (gnu_field) = gnu_qual;
6681             }
6682
6683           TREE_CHAIN (gnu_field) = gnu_variant_list;
6684           gnu_variant_list = gnu_field;
6685         }
6686
6687       /* Only make the QUAL_UNION_TYPE if there are any non-empty variants.  */
6688       if (gnu_variant_list)
6689         {
6690           int union_field_packed;
6691
6692           if (all_rep_and_size)
6693             {
6694               TYPE_SIZE (gnu_union_type) = TYPE_SIZE (gnu_record_type);
6695               TYPE_SIZE_UNIT (gnu_union_type)
6696                 = TYPE_SIZE_UNIT (gnu_record_type);
6697             }
6698
6699           finish_record_type (gnu_union_type, nreverse (gnu_variant_list),
6700                               all_rep_and_size ? 1 : 0, false);
6701
6702           /* If GNU_UNION_TYPE is our record type, it means we must have an
6703              Unchecked_Union with no fields.  Verify that and, if so, just
6704              return.  */
6705           if (gnu_union_type == gnu_record_type)
6706             {
6707               gcc_assert (unchecked_union
6708                           && !gnu_field_list
6709                           && !gnu_our_rep_list);
6710               return;
6711             }
6712
6713           /* Deal with packedness like in gnat_to_gnu_field.  */
6714           union_field_packed
6715             = adjust_packed (gnu_union_type, gnu_record_type, packed);
6716
6717           gnu_union_field
6718             = create_field_decl (gnu_var_name, gnu_union_type, gnu_record_type,
6719                                  union_field_packed,
6720                                  all_rep ? TYPE_SIZE (gnu_union_type) : 0,
6721                                  all_rep ? bitsize_zero_node : 0, 0);
6722
6723           DECL_INTERNAL_P (gnu_union_field) = 1;
6724           TREE_CHAIN (gnu_union_field) = gnu_field_list;
6725           gnu_field_list = gnu_union_field;
6726         }
6727     }
6728
6729   /* Scan GNU_FIELD_LIST and see if any fields have rep clauses.  If they
6730      do, pull them out and put them into GNU_OUR_REP_LIST.  We have to do this
6731      in a separate pass since we want to handle the discriminants but can't
6732      play with them until we've used them in debugging data above.
6733
6734      ??? Note: if we then reorder them, debugging information will be wrong,
6735      but there's nothing that can be done about this at the moment.  */
6736   for (gnu_field = gnu_field_list, gnu_last = NULL_TREE; gnu_field; )
6737     {
6738       if (DECL_FIELD_OFFSET (gnu_field))
6739         {
6740           tree gnu_next = TREE_CHAIN (gnu_field);
6741
6742           if (!gnu_last)
6743             gnu_field_list = gnu_next;
6744           else
6745             TREE_CHAIN (gnu_last) = gnu_next;
6746
6747           TREE_CHAIN (gnu_field) = gnu_our_rep_list;
6748           gnu_our_rep_list = gnu_field;
6749           gnu_field = gnu_next;
6750         }
6751       else
6752         {
6753           gnu_last = gnu_field;
6754           gnu_field = TREE_CHAIN (gnu_field);
6755         }
6756     }
6757
6758   /* If we have any items in our rep'ed field list, it is not the case that all
6759      the fields in the record have rep clauses, and P_REP_LIST is nonzero,
6760      set it and ignore the items.  */
6761   if (gnu_our_rep_list && p_gnu_rep_list && !all_rep)
6762     *p_gnu_rep_list = chainon (*p_gnu_rep_list, gnu_our_rep_list);
6763   else if (gnu_our_rep_list)
6764     {
6765       /* Otherwise, sort the fields by bit position and put them into their
6766          own record if we have any fields without rep clauses.  */
6767       tree gnu_rep_type
6768         = (gnu_field_list ? make_node (RECORD_TYPE) : gnu_record_type);
6769       int len = list_length (gnu_our_rep_list);
6770       tree *gnu_arr = (tree *) alloca (sizeof (tree) * len);
6771       int i;
6772
6773       for (i = 0, gnu_field = gnu_our_rep_list; gnu_field;
6774            gnu_field = TREE_CHAIN (gnu_field), i++)
6775         gnu_arr[i] = gnu_field;
6776
6777       qsort (gnu_arr, len, sizeof (tree), compare_field_bitpos);
6778
6779       /* Put the fields in the list in order of increasing position, which
6780          means we start from the end.  */
6781       gnu_our_rep_list = NULL_TREE;
6782       for (i = len - 1; i >= 0; i--)
6783         {
6784           TREE_CHAIN (gnu_arr[i]) = gnu_our_rep_list;
6785           gnu_our_rep_list = gnu_arr[i];
6786           DECL_CONTEXT (gnu_arr[i]) = gnu_rep_type;
6787         }
6788
6789       if (gnu_field_list)
6790         {
6791           finish_record_type (gnu_rep_type, gnu_our_rep_list, 1, false);
6792           gnu_field = create_field_decl (get_identifier ("REP"), gnu_rep_type,
6793                                          gnu_record_type, 0, 0, 0, 1);
6794           DECL_INTERNAL_P (gnu_field) = 1;
6795           gnu_field_list = chainon (gnu_field_list, gnu_field);
6796         }
6797       else
6798         {
6799           layout_with_rep = true;
6800           gnu_field_list = nreverse (gnu_our_rep_list);
6801         }
6802     }
6803
6804   if (cancel_alignment)
6805     TYPE_ALIGN (gnu_record_type) = 0;
6806
6807   finish_record_type (gnu_record_type, nreverse (gnu_field_list),
6808                       layout_with_rep ? 1 : 0, do_not_finalize);
6809 }
6810 \f
6811 /* Given GNU_SIZE, a GCC tree representing a size, return a Uint to be
6812    placed into an Esize, Component_Bit_Offset, or Component_Size value
6813    in the GNAT tree.  */
6814
6815 static Uint
6816 annotate_value (tree gnu_size)
6817 {
6818   int len = TREE_CODE_LENGTH (TREE_CODE (gnu_size));
6819   TCode tcode;
6820   Node_Ref_Or_Val ops[3], ret;
6821   int i;
6822   int size;
6823   struct tree_int_map **h = NULL;
6824
6825   /* See if we've already saved the value for this node.  */
6826   if (EXPR_P (gnu_size))
6827     {
6828       struct tree_int_map in;
6829       if (!annotate_value_cache)
6830         annotate_value_cache = htab_create_ggc (512, tree_int_map_hash,
6831                                                 tree_int_map_eq, 0);
6832       in.base.from = gnu_size;
6833       h = (struct tree_int_map **)
6834             htab_find_slot (annotate_value_cache, &in, INSERT);
6835
6836       if (*h)
6837         return (Node_Ref_Or_Val) (*h)->to;
6838     }
6839
6840   /* If we do not return inside this switch, TCODE will be set to the
6841      code to use for a Create_Node operand and LEN (set above) will be
6842      the number of recursive calls for us to make.  */
6843
6844   switch (TREE_CODE (gnu_size))
6845     {
6846     case INTEGER_CST:
6847       if (TREE_OVERFLOW (gnu_size))
6848         return No_Uint;
6849
6850       /* This may have come from a conversion from some smaller type,
6851          so ensure this is in bitsizetype.  */
6852       gnu_size = convert (bitsizetype, gnu_size);
6853
6854       /* For negative values, use NEGATE_EXPR of the supplied value.  */
6855       if (tree_int_cst_sgn (gnu_size) < 0)
6856         {
6857           /* The ridiculous code below is to handle the case of the largest
6858              negative integer.  */
6859           tree negative_size = size_diffop (bitsize_zero_node, gnu_size);
6860           bool adjust = false;
6861           tree temp;
6862
6863           if (TREE_OVERFLOW (negative_size))
6864             {
6865               negative_size
6866                 = size_binop (MINUS_EXPR, bitsize_zero_node,
6867                               size_binop (PLUS_EXPR, gnu_size,
6868                                           bitsize_one_node));
6869               adjust = true;
6870             }
6871
6872           temp = build1 (NEGATE_EXPR, bitsizetype, negative_size);
6873           if (adjust)
6874             temp = build2 (MINUS_EXPR, bitsizetype, temp, bitsize_one_node);
6875
6876           return annotate_value (temp);
6877         }
6878
6879       if (!host_integerp (gnu_size, 1))
6880         return No_Uint;
6881
6882       size = tree_low_cst (gnu_size, 1);
6883
6884       /* This peculiar test is to make sure that the size fits in an int
6885          on machines where HOST_WIDE_INT is not "int".  */
6886       if (tree_low_cst (gnu_size, 1) == size)
6887         return UI_From_Int (size);
6888       else
6889         return No_Uint;
6890
6891     case COMPONENT_REF:
6892       /* The only case we handle here is a simple discriminant reference.  */
6893       if (TREE_CODE (TREE_OPERAND (gnu_size, 0)) == PLACEHOLDER_EXPR
6894           && TREE_CODE (TREE_OPERAND (gnu_size, 1)) == FIELD_DECL
6895           && DECL_DISCRIMINANT_NUMBER (TREE_OPERAND (gnu_size, 1)))
6896         return Create_Node (Discrim_Val,
6897                             annotate_value (DECL_DISCRIMINANT_NUMBER
6898                                             (TREE_OPERAND (gnu_size, 1))),
6899                             No_Uint, No_Uint);
6900       else
6901         return No_Uint;
6902
6903     CASE_CONVERT:   case NON_LVALUE_EXPR:
6904       return annotate_value (TREE_OPERAND (gnu_size, 0));
6905
6906       /* Now just list the operations we handle.  */
6907     case COND_EXPR:             tcode = Cond_Expr; break;
6908     case PLUS_EXPR:             tcode = Plus_Expr; break;
6909     case MINUS_EXPR:            tcode = Minus_Expr; break;
6910     case MULT_EXPR:             tcode = Mult_Expr; break;
6911     case TRUNC_DIV_EXPR:        tcode = Trunc_Div_Expr; break;
6912     case CEIL_DIV_EXPR:         tcode = Ceil_Div_Expr; break;
6913     case FLOOR_DIV_EXPR:        tcode = Floor_Div_Expr; break;
6914     case TRUNC_MOD_EXPR:        tcode = Trunc_Mod_Expr; break;
6915     case CEIL_MOD_EXPR:         tcode = Ceil_Mod_Expr; break;
6916     case FLOOR_MOD_EXPR:        tcode = Floor_Mod_Expr; break;
6917     case EXACT_DIV_EXPR:        tcode = Exact_Div_Expr; break;
6918     case NEGATE_EXPR:           tcode = Negate_Expr; break;
6919     case MIN_EXPR:              tcode = Min_Expr; break;
6920     case MAX_EXPR:              tcode = Max_Expr; break;
6921     case ABS_EXPR:              tcode = Abs_Expr; break;
6922     case TRUTH_ANDIF_EXPR:      tcode = Truth_Andif_Expr; break;
6923     case TRUTH_ORIF_EXPR:       tcode = Truth_Orif_Expr; break;
6924     case TRUTH_AND_EXPR:        tcode = Truth_And_Expr; break;
6925     case TRUTH_OR_EXPR:         tcode = Truth_Or_Expr; break;
6926     case TRUTH_XOR_EXPR:        tcode = Truth_Xor_Expr; break;
6927     case TRUTH_NOT_EXPR:        tcode = Truth_Not_Expr; break;
6928     case BIT_AND_EXPR:          tcode = Bit_And_Expr; break;
6929     case LT_EXPR:               tcode = Lt_Expr; break;
6930     case LE_EXPR:               tcode = Le_Expr; break;
6931     case GT_EXPR:               tcode = Gt_Expr; break;
6932     case GE_EXPR:               tcode = Ge_Expr; break;
6933     case EQ_EXPR:               tcode = Eq_Expr; break;
6934     case NE_EXPR:               tcode = Ne_Expr; break;
6935
6936     default:
6937       return No_Uint;
6938     }
6939
6940   /* Now get each of the operands that's relevant for this code.  If any
6941      cannot be expressed as a repinfo node, say we can't.  */
6942   for (i = 0; i < 3; i++)
6943     ops[i] = No_Uint;
6944
6945   for (i = 0; i < len; i++)
6946     {
6947       ops[i] = annotate_value (TREE_OPERAND (gnu_size, i));
6948       if (ops[i] == No_Uint)
6949         return No_Uint;
6950     }
6951
6952   ret = Create_Node (tcode, ops[0], ops[1], ops[2]);
6953
6954   /* Save the result in the cache.  */
6955   if (h)
6956     {
6957       *h = GGC_NEW (struct tree_int_map);
6958       (*h)->base.from = gnu_size;
6959       (*h)->to = ret;
6960     }
6961
6962   return ret;
6963 }
6964
6965 /* Given GNAT_ENTITY, a record type, and GNU_TYPE, its corresponding
6966    GCC type, set Component_Bit_Offset and Esize to the position and size
6967    used by Gigi.  */
6968
6969 static void
6970 annotate_rep (Entity_Id gnat_entity, tree gnu_type)
6971 {
6972   tree gnu_list;
6973   tree gnu_entry;
6974   Entity_Id gnat_field;
6975
6976   /* We operate by first making a list of all fields and their positions
6977      (we can get the sizes easily at any time) by a recursive call
6978      and then update all the sizes into the tree.  */
6979   gnu_list = compute_field_positions (gnu_type, NULL_TREE,
6980                                       size_zero_node, bitsize_zero_node,
6981                                       BIGGEST_ALIGNMENT);
6982
6983   for (gnat_field = First_Entity (gnat_entity); Present (gnat_field);
6984        gnat_field = Next_Entity (gnat_field))
6985     if ((Ekind (gnat_field) == E_Component
6986          || (Ekind (gnat_field) == E_Discriminant
6987              && !Is_Unchecked_Union (Scope (gnat_field)))))
6988       {
6989         tree parent_offset = bitsize_zero_node;
6990
6991         gnu_entry = purpose_member (gnat_to_gnu_field_decl (gnat_field),
6992                                     gnu_list);
6993
6994         if (gnu_entry)
6995           {
6996             if (type_annotate_only && Is_Tagged_Type (gnat_entity))
6997               {
6998                 /* In this mode the tag and parent components have not been
6999                    generated, so we add the appropriate offset to each
7000                    component.  For a component appearing in the current
7001                    extension, the offset is the size of the parent.  */
7002             if (Is_Derived_Type (gnat_entity)
7003                 && Original_Record_Component (gnat_field) == gnat_field)
7004               parent_offset
7005                 = UI_To_gnu (Esize (Etype (Base_Type (gnat_entity))),
7006                              bitsizetype);
7007             else
7008               parent_offset = bitsize_int (POINTER_SIZE);
7009               }
7010
7011           Set_Component_Bit_Offset
7012             (gnat_field,
7013              annotate_value
7014              (size_binop (PLUS_EXPR,
7015                           bit_from_pos (TREE_PURPOSE (TREE_VALUE (gnu_entry)),
7016                                         TREE_VALUE (TREE_VALUE
7017                                                     (TREE_VALUE (gnu_entry)))),
7018                           parent_offset)));
7019
7020             Set_Esize (gnat_field,
7021                        annotate_value (DECL_SIZE (TREE_PURPOSE (gnu_entry))));
7022           }
7023         else if (Is_Tagged_Type (gnat_entity)
7024                  && Is_Derived_Type (gnat_entity))
7025           {
7026             /* If there is no gnu_entry, this is an inherited component whose
7027                position is the same as in the parent type.  */
7028             Set_Component_Bit_Offset
7029               (gnat_field,
7030                Component_Bit_Offset (Original_Record_Component (gnat_field)));
7031             Set_Esize (gnat_field,
7032                        Esize (Original_Record_Component (gnat_field)));
7033           }
7034       }
7035 }
7036
7037 /* Scan all fields in GNU_TYPE and build entries where TREE_PURPOSE is the
7038    FIELD_DECL and TREE_VALUE a TREE_LIST with TREE_PURPOSE being the byte
7039    position and TREE_VALUE being a TREE_LIST with TREE_PURPOSE the value to be
7040    placed into DECL_OFFSET_ALIGN and TREE_VALUE the bit position.  GNU_POS is
7041    to be added to the position, GNU_BITPOS to the bit position, OFFSET_ALIGN is
7042    the present value of DECL_OFFSET_ALIGN and GNU_LIST is a list of the entries
7043    so far.  */
7044
7045 static tree
7046 compute_field_positions (tree gnu_type, tree gnu_list, tree gnu_pos,
7047                          tree gnu_bitpos, unsigned int offset_align)
7048 {
7049   tree gnu_field;
7050   tree gnu_result = gnu_list;
7051
7052   for (gnu_field = TYPE_FIELDS (gnu_type); gnu_field;
7053        gnu_field = TREE_CHAIN (gnu_field))
7054     {
7055       tree gnu_our_bitpos = size_binop (PLUS_EXPR, gnu_bitpos,
7056                                         DECL_FIELD_BIT_OFFSET (gnu_field));
7057       tree gnu_our_offset = size_binop (PLUS_EXPR, gnu_pos,
7058                                         DECL_FIELD_OFFSET (gnu_field));
7059       unsigned int our_offset_align
7060         = MIN (offset_align, DECL_OFFSET_ALIGN (gnu_field));
7061
7062       gnu_result
7063         = tree_cons (gnu_field,
7064                      tree_cons (gnu_our_offset,
7065                                 tree_cons (size_int (our_offset_align),
7066                                            gnu_our_bitpos, NULL_TREE),
7067                                 NULL_TREE),
7068                      gnu_result);
7069
7070       if (DECL_INTERNAL_P (gnu_field))
7071         gnu_result
7072           = compute_field_positions (TREE_TYPE (gnu_field), gnu_result,
7073                                      gnu_our_offset, gnu_our_bitpos,
7074                                      our_offset_align);
7075     }
7076
7077   return gnu_result;
7078 }
7079 \f
7080 /* UINT_SIZE is a Uint giving the specified size for an object of GNU_TYPE
7081    corresponding to GNAT_OBJECT.  If size is valid, return a tree corresponding
7082    to its value.  Otherwise return 0.  KIND is VAR_DECL is we are specifying
7083    the size for an object, TYPE_DECL for the size of a type, and FIELD_DECL
7084    for the size of a field.  COMPONENT_P is true if we are being called
7085    to process the Component_Size of GNAT_OBJECT.  This is used for error
7086    message handling and to indicate to use the object size of GNU_TYPE.
7087    ZERO_OK is true if a size of zero is permitted; if ZERO_OK is false,
7088    it means that a size of zero should be treated as an unspecified size.  */
7089
7090 static tree
7091 validate_size (Uint uint_size, tree gnu_type, Entity_Id gnat_object,
7092                enum tree_code kind, bool component_p, bool zero_ok)
7093 {
7094   Node_Id gnat_error_node;
7095   tree type_size, size;
7096
7097   if (kind == VAR_DECL
7098       /* If a type needs strict alignment, a component of this type in
7099          a packed record cannot be packed and thus uses the type size.  */
7100       || (kind == TYPE_DECL && Strict_Alignment (gnat_object)))
7101     type_size = TYPE_SIZE (gnu_type);
7102   else
7103     type_size = rm_size (gnu_type);
7104
7105   /* Find the node to use for errors.  */
7106   if ((Ekind (gnat_object) == E_Component
7107        || Ekind (gnat_object) == E_Discriminant)
7108       && Present (Component_Clause (gnat_object)))
7109     gnat_error_node = Last_Bit (Component_Clause (gnat_object));
7110   else if (Present (Size_Clause (gnat_object)))
7111     gnat_error_node = Expression (Size_Clause (gnat_object));
7112   else
7113     gnat_error_node = gnat_object;
7114
7115   /* Return 0 if no size was specified, either because Esize was not Present or
7116      the specified size was zero.  */
7117   if (No (uint_size) || uint_size == No_Uint)
7118     return NULL_TREE;
7119
7120   /* Get the size as a tree.  Give an error if a size was specified, but cannot
7121      be represented as in sizetype.  */
7122   size = UI_To_gnu (uint_size, bitsizetype);
7123   if (TREE_OVERFLOW (size))
7124     {
7125       post_error_ne (component_p ? "component size of & is too large"
7126                      : "size of & is too large",
7127                      gnat_error_node, gnat_object);
7128       return NULL_TREE;
7129     }
7130
7131   /* Ignore a negative size since that corresponds to our back-annotation.
7132      Also ignore a zero size unless a size clause exists.  */
7133   else if (tree_int_cst_sgn (size) < 0 || (integer_zerop (size) && !zero_ok))
7134     return NULL_TREE;
7135
7136   /* The size of objects is always a multiple of a byte.  */
7137   if (kind == VAR_DECL
7138       && !integer_zerop (size_binop (TRUNC_MOD_EXPR, size, bitsize_unit_node)))
7139     {
7140       if (component_p)
7141         post_error_ne ("component size for& is not a multiple of Storage_Unit",
7142                        gnat_error_node, gnat_object);
7143       else
7144         post_error_ne ("size for& is not a multiple of Storage_Unit",
7145                        gnat_error_node, gnat_object);
7146       return NULL_TREE;
7147     }
7148
7149   /* If this is an integral type or a packed array type, the front-end has
7150      verified the size, so we need not do it here (which would entail
7151      checking against the bounds).  However, if this is an aliased object, it
7152      may not be smaller than the type of the object.  */
7153   if ((INTEGRAL_TYPE_P (gnu_type) || TYPE_IS_PACKED_ARRAY_TYPE_P (gnu_type))
7154       && !(kind == VAR_DECL && Is_Aliased (gnat_object)))
7155     return size;
7156
7157   /* If the object is a record that contains a template, add the size of
7158      the template to the specified size.  */
7159   if (TREE_CODE (gnu_type) == RECORD_TYPE
7160       && TYPE_CONTAINS_TEMPLATE_P (gnu_type))
7161     size = size_binop (PLUS_EXPR, DECL_SIZE (TYPE_FIELDS (gnu_type)), size);
7162
7163   /* Modify the size of the type to be that of the maximum size if it has a
7164      discriminant.  */
7165   if (type_size && CONTAINS_PLACEHOLDER_P (type_size))
7166     type_size = max_size (type_size, true);
7167
7168   /* If this is an access type or a fat pointer, the minimum size is that given
7169      by the smallest integral mode that's valid for pointers.  */
7170   if ((TREE_CODE (gnu_type) == POINTER_TYPE) || TYPE_FAT_POINTER_P (gnu_type))
7171     {
7172       enum machine_mode p_mode;
7173
7174       for (p_mode = GET_CLASS_NARROWEST_MODE (MODE_INT);
7175            !targetm.valid_pointer_mode (p_mode);
7176            p_mode = GET_MODE_WIDER_MODE (p_mode))
7177         ;
7178
7179       type_size = bitsize_int (GET_MODE_BITSIZE (p_mode));
7180     }
7181
7182   /* If the size of the object is a constant, the new size must not be
7183      smaller.  */
7184   if (TREE_CODE (type_size) != INTEGER_CST
7185       || TREE_OVERFLOW (type_size)
7186       || tree_int_cst_lt (size, type_size))
7187     {
7188       if (component_p)
7189         post_error_ne_tree
7190           ("component size for& too small{, minimum allowed is ^}",
7191            gnat_error_node, gnat_object, type_size);
7192       else
7193         post_error_ne_tree ("size for& too small{, minimum allowed is ^}",
7194                             gnat_error_node, gnat_object, type_size);
7195
7196       if (kind == VAR_DECL && !component_p
7197           && TREE_CODE (rm_size (gnu_type)) == INTEGER_CST
7198           && !tree_int_cst_lt (size, rm_size (gnu_type)))
7199         post_error_ne_tree_2
7200           ("\\size of ^ is not a multiple of alignment (^ bits)",
7201            gnat_error_node, gnat_object, rm_size (gnu_type),
7202            TYPE_ALIGN (gnu_type));
7203
7204       else if (INTEGRAL_TYPE_P (gnu_type))
7205         post_error_ne ("\\size would be legal if & were not aliased!",
7206                        gnat_error_node, gnat_object);
7207
7208       return NULL_TREE;
7209     }
7210
7211   return size;
7212 }
7213 \f
7214 /* Similarly, but both validate and process a value of RM_Size.  This
7215    routine is only called for types.  */
7216
7217 static void
7218 set_rm_size (Uint uint_size, tree gnu_type, Entity_Id gnat_entity)
7219 {
7220   /* Only give an error if a Value_Size clause was explicitly given.
7221      Otherwise, we'd be duplicating an error on the Size clause.  */
7222   Node_Id gnat_attr_node
7223     = Get_Attribute_Definition_Clause (gnat_entity, Attr_Value_Size);
7224   tree old_size = rm_size (gnu_type);
7225   tree size;
7226
7227   /* Get the size as a tree.  Do nothing if none was specified, either
7228      because RM_Size was not Present or if the specified size was zero.
7229      Give an error if a size was specified, but cannot be represented as
7230      in sizetype.  */
7231   if (No (uint_size) || uint_size == No_Uint)
7232     return;
7233
7234   size = UI_To_gnu (uint_size, bitsizetype);
7235   if (TREE_OVERFLOW (size))
7236     {
7237       if (Present (gnat_attr_node))
7238         post_error_ne ("Value_Size of & is too large", gnat_attr_node,
7239                        gnat_entity);
7240
7241       return;
7242     }
7243
7244   /* Ignore a negative size since that corresponds to our back-annotation.
7245      Also ignore a zero size unless a size clause exists, a Value_Size
7246      clause exists, or this is an integer type, in which case the
7247      front end will have always set it.  */
7248   else if (tree_int_cst_sgn (size) < 0
7249            || (integer_zerop (size) && No (gnat_attr_node)
7250                && !Has_Size_Clause (gnat_entity)
7251                && !Is_Discrete_Or_Fixed_Point_Type (gnat_entity)))
7252     return;
7253
7254   /* If the old size is self-referential, get the maximum size.  */
7255   if (CONTAINS_PLACEHOLDER_P (old_size))
7256     old_size = max_size (old_size, true);
7257
7258   /* If the size of the object is a constant, the new size must not be
7259      smaller (the front end checks this for scalar types).  */
7260   if (TREE_CODE (old_size) != INTEGER_CST
7261       || TREE_OVERFLOW (old_size)
7262       || (AGGREGATE_TYPE_P (gnu_type)
7263           && tree_int_cst_lt (size, old_size)))
7264     {
7265       if (Present (gnat_attr_node))
7266         post_error_ne_tree
7267           ("Value_Size for& too small{, minimum allowed is ^}",
7268            gnat_attr_node, gnat_entity, old_size);
7269
7270       return;
7271     }
7272
7273   /* Otherwise, set the RM_Size.  */
7274   if (TREE_CODE (gnu_type) == INTEGER_TYPE
7275       && Is_Discrete_Or_Fixed_Point_Type (gnat_entity))
7276     TYPE_RM_SIZE_NUM (gnu_type) = size;
7277   else if (TREE_CODE (gnu_type) == ENUMERAL_TYPE
7278            || TREE_CODE (gnu_type) == BOOLEAN_TYPE)
7279     TYPE_RM_SIZE_NUM (gnu_type) = size;
7280   else if ((TREE_CODE (gnu_type) == RECORD_TYPE
7281             || TREE_CODE (gnu_type) == UNION_TYPE
7282             || TREE_CODE (gnu_type) == QUAL_UNION_TYPE)
7283            && !TYPE_IS_FAT_POINTER_P (gnu_type))
7284     SET_TYPE_ADA_SIZE (gnu_type, size);
7285 }
7286 \f
7287 /* Given a type TYPE, return a new type whose size is appropriate for SIZE.
7288    If TYPE is the best type, return it.  Otherwise, make a new type.  We
7289    only support new integral and pointer types.  FOR_BIASED is true if
7290    we are making a biased type.  */
7291
7292 static tree
7293 make_type_from_size (tree type, tree size_tree, bool for_biased)
7294 {
7295   unsigned HOST_WIDE_INT size;
7296   bool biased_p;
7297   tree new_type;
7298
7299   /* If size indicates an error, just return TYPE to avoid propagating
7300      the error.  Likewise if it's too large to represent.  */
7301   if (!size_tree || !host_integerp (size_tree, 1))
7302     return type;
7303
7304   size = tree_low_cst (size_tree, 1);
7305
7306   switch (TREE_CODE (type))
7307     {
7308     case INTEGER_TYPE:
7309     case ENUMERAL_TYPE:
7310     case BOOLEAN_TYPE:
7311       biased_p = (TREE_CODE (type) == INTEGER_TYPE
7312                   && TYPE_BIASED_REPRESENTATION_P (type));
7313
7314       /* Only do something if the type is not a packed array type and
7315          doesn't already have the proper size.  */
7316       if (TYPE_PACKED_ARRAY_TYPE_P (type)
7317           || (TYPE_PRECISION (type) == size && biased_p == for_biased))
7318         break;
7319
7320       biased_p |= for_biased;
7321       size = MIN (size, LONG_LONG_TYPE_SIZE);
7322
7323       if (TYPE_UNSIGNED (type) || biased_p)
7324         new_type = make_unsigned_type (size);
7325       else
7326         new_type = make_signed_type (size);
7327       TREE_TYPE (new_type) = TREE_TYPE (type) ? TREE_TYPE (type) : type;
7328       TYPE_MIN_VALUE (new_type)
7329         = convert (TREE_TYPE (new_type), TYPE_MIN_VALUE (type));
7330       TYPE_MAX_VALUE (new_type)
7331         = convert (TREE_TYPE (new_type), TYPE_MAX_VALUE (type));
7332       /* Propagate the name to avoid creating a fake subrange type.  */
7333       if (TYPE_NAME (type))
7334         {
7335           if (TREE_CODE (TYPE_NAME (type)) == TYPE_DECL)
7336             TYPE_NAME (new_type) = DECL_NAME (TYPE_NAME (type));
7337           else
7338             TYPE_NAME (new_type) = TYPE_NAME (type);
7339         }
7340       TYPE_BIASED_REPRESENTATION_P (new_type) = biased_p;
7341       TYPE_RM_SIZE_NUM (new_type) = bitsize_int (size);
7342       return new_type;
7343
7344     case RECORD_TYPE:
7345       /* Do something if this is a fat pointer, in which case we
7346          may need to return the thin pointer.  */
7347       if (TYPE_IS_FAT_POINTER_P (type) && size < POINTER_SIZE * 2)
7348         {
7349           enum machine_mode p_mode = mode_for_size (size, MODE_INT, 0);
7350           if (!targetm.valid_pointer_mode (p_mode))
7351             p_mode = ptr_mode;
7352           return
7353             build_pointer_type_for_mode
7354               (TYPE_OBJECT_RECORD_TYPE (TYPE_UNCONSTRAINED_ARRAY (type)),
7355                p_mode, 0);
7356         }
7357       break;
7358
7359     case POINTER_TYPE:
7360       /* Only do something if this is a thin pointer, in which case we
7361          may need to return the fat pointer.  */
7362       if (TYPE_THIN_POINTER_P (type) && size >= POINTER_SIZE * 2)
7363         return
7364           build_pointer_type (TYPE_UNCONSTRAINED_ARRAY (TREE_TYPE (type)));
7365       break;
7366
7367     default:
7368       break;
7369     }
7370
7371   return type;
7372 }
7373 \f
7374 /* ALIGNMENT is a Uint giving the alignment specified for GNAT_ENTITY,
7375    a type or object whose present alignment is ALIGN.  If this alignment is
7376    valid, return it.  Otherwise, give an error and return ALIGN.  */
7377
7378 static unsigned int
7379 validate_alignment (Uint alignment, Entity_Id gnat_entity, unsigned int align)
7380 {
7381   unsigned int max_allowed_alignment = get_target_maximum_allowed_alignment ();
7382   unsigned int new_align;
7383   Node_Id gnat_error_node;
7384
7385   /* Don't worry about checking alignment if alignment was not specified
7386      by the source program and we already posted an error for this entity.  */
7387   if (Error_Posted (gnat_entity) && !Has_Alignment_Clause (gnat_entity))
7388     return align;
7389
7390   /* Post the error on the alignment clause if any.  */
7391   if (Present (Alignment_Clause (gnat_entity)))
7392     gnat_error_node = Expression (Alignment_Clause (gnat_entity));
7393   else
7394     gnat_error_node = gnat_entity;
7395
7396   /* Within GCC, an alignment is an integer, so we must make sure a value is
7397      specified that fits in that range.  Also, there is an upper bound to
7398      alignments we can support/allow.  */
7399   if (!UI_Is_In_Int_Range (alignment)
7400       || ((new_align = UI_To_Int (alignment)) > max_allowed_alignment))
7401     post_error_ne_num ("largest supported alignment for& is ^",
7402                        gnat_error_node, gnat_entity, max_allowed_alignment);
7403   else if (!(Present (Alignment_Clause (gnat_entity))
7404              && From_At_Mod (Alignment_Clause (gnat_entity)))
7405            && new_align * BITS_PER_UNIT < align)
7406     post_error_ne_num ("alignment for& must be at least ^",
7407                        gnat_error_node, gnat_entity,
7408                        align / BITS_PER_UNIT);
7409   else
7410     {
7411       new_align = (new_align > 0 ? new_align * BITS_PER_UNIT : 1);
7412       if (new_align > align)
7413         align = new_align;
7414     }
7415
7416   return align;
7417 }
7418
7419 /* Return the smallest alignment not less than SIZE.  */
7420
7421 static unsigned int
7422 ceil_alignment (unsigned HOST_WIDE_INT size)
7423 {
7424   return (unsigned int) 1 << (floor_log2 (size - 1) + 1);
7425 }
7426 \f
7427 /* Verify that OBJECT, a type or decl, is something we can implement
7428    atomically.  If not, give an error for GNAT_ENTITY.  COMP_P is true
7429    if we require atomic components.  */
7430
7431 static void
7432 check_ok_for_atomic (tree object, Entity_Id gnat_entity, bool comp_p)
7433 {
7434   Node_Id gnat_error_point = gnat_entity;
7435   Node_Id gnat_node;
7436   enum machine_mode mode;
7437   unsigned int align;
7438   tree size;
7439
7440   /* There are three case of what OBJECT can be.  It can be a type, in which
7441      case we take the size, alignment and mode from the type.  It can be a
7442      declaration that was indirect, in which case the relevant values are
7443      that of the type being pointed to, or it can be a normal declaration,
7444      in which case the values are of the decl.  The code below assumes that
7445      OBJECT is either a type or a decl.  */
7446   if (TYPE_P (object))
7447     {
7448       mode = TYPE_MODE (object);
7449       align = TYPE_ALIGN (object);
7450       size = TYPE_SIZE (object);
7451     }
7452   else if (DECL_BY_REF_P (object))
7453     {
7454       mode = TYPE_MODE (TREE_TYPE (TREE_TYPE (object)));
7455       align = TYPE_ALIGN (TREE_TYPE (TREE_TYPE (object)));
7456       size = TYPE_SIZE (TREE_TYPE (TREE_TYPE (object)));
7457     }
7458   else
7459     {
7460       mode = DECL_MODE (object);
7461       align = DECL_ALIGN (object);
7462       size = DECL_SIZE (object);
7463     }
7464
7465   /* Consider all floating-point types atomic and any types that that are
7466      represented by integers no wider than a machine word.  */
7467   if (GET_MODE_CLASS (mode) == MODE_FLOAT
7468       || ((GET_MODE_CLASS (mode) == MODE_INT
7469            || GET_MODE_CLASS (mode) == MODE_PARTIAL_INT)
7470           && GET_MODE_BITSIZE (mode) <= BITS_PER_WORD))
7471     return;
7472
7473   /* For the moment, also allow anything that has an alignment equal
7474      to its size and which is smaller than a word.  */
7475   if (size && TREE_CODE (size) == INTEGER_CST
7476       && compare_tree_int (size, align) == 0
7477       && align <= BITS_PER_WORD)
7478     return;
7479
7480   for (gnat_node = First_Rep_Item (gnat_entity); Present (gnat_node);
7481        gnat_node = Next_Rep_Item (gnat_node))
7482     {
7483       if (!comp_p && Nkind (gnat_node) == N_Pragma
7484           && (Get_Pragma_Id (Chars (Pragma_Identifier (gnat_node)))
7485               == Pragma_Atomic))
7486         gnat_error_point = First (Pragma_Argument_Associations (gnat_node));
7487       else if (comp_p && Nkind (gnat_node) == N_Pragma
7488                && (Get_Pragma_Id (Chars (Pragma_Identifier (gnat_node)))
7489                    == Pragma_Atomic_Components))
7490         gnat_error_point = First (Pragma_Argument_Associations (gnat_node));
7491     }
7492
7493   if (comp_p)
7494     post_error_ne ("atomic access to component of & cannot be guaranteed",
7495                    gnat_error_point, gnat_entity);
7496   else
7497     post_error_ne ("atomic access to & cannot be guaranteed",
7498                    gnat_error_point, gnat_entity);
7499 }
7500 \f
7501 /* Check if FTYPE1 and FTYPE2, two potentially different function type nodes,
7502    have compatible signatures so that a call using one type may be safely
7503    issued if the actual target function type is the other.  Return 1 if it is
7504    the case, 0 otherwise, and post errors on the incompatibilities.
7505
7506    This is used when an Ada subprogram is mapped onto a GCC builtin, to ensure
7507    that calls to the subprogram will have arguments suitable for the later
7508    underlying builtin expansion.  */
7509
7510 static int
7511 compatible_signatures_p (tree ftype1, tree ftype2)
7512 {
7513   /* As of now, we only perform very trivial tests and consider it's the
7514      programmer's responsibility to ensure the type correctness in the Ada
7515      declaration, as in the regular Import cases.
7516
7517      Mismatches typically result in either error messages from the builtin
7518      expander, internal compiler errors, or in a real call sequence.  This
7519      should be refined to issue diagnostics helping error detection and
7520      correction.  */
7521
7522   /* Almost fake test, ensuring a use of each argument.  */
7523   if (ftype1 == ftype2)
7524     return 1;
7525
7526   return 1;
7527 }
7528 \f
7529 /* Given a type T, a FIELD_DECL F, and a replacement value R, return a new
7530    type with all size expressions that contain F updated by replacing F
7531    with R.  If F is NULL_TREE, always make a new RECORD_TYPE, even if
7532    nothing has changed.  */
7533
7534 tree
7535 substitute_in_type (tree t, tree f, tree r)
7536 {
7537   tree new = t;
7538   tree tem;
7539
7540   switch (TREE_CODE (t))
7541     {
7542     case INTEGER_TYPE:
7543     case ENUMERAL_TYPE:
7544     case BOOLEAN_TYPE:
7545       if (CONTAINS_PLACEHOLDER_P (TYPE_MIN_VALUE (t))
7546           || CONTAINS_PLACEHOLDER_P (TYPE_MAX_VALUE (t)))
7547         {
7548           tree low = SUBSTITUTE_IN_EXPR (TYPE_MIN_VALUE (t), f, r);
7549           tree high = SUBSTITUTE_IN_EXPR (TYPE_MAX_VALUE (t), f, r);
7550
7551           if (low == TYPE_MIN_VALUE (t) && high == TYPE_MAX_VALUE (t))
7552             return t;
7553
7554           new = build_range_type (TREE_TYPE (t), low, high);
7555           if (TYPE_INDEX_TYPE (t))
7556             SET_TYPE_INDEX_TYPE
7557               (new, substitute_in_type (TYPE_INDEX_TYPE (t), f, r));
7558           return new;
7559         }
7560
7561       return t;
7562
7563     case REAL_TYPE:
7564       if (CONTAINS_PLACEHOLDER_P (TYPE_MIN_VALUE (t))
7565           || CONTAINS_PLACEHOLDER_P (TYPE_MAX_VALUE (t)))
7566         {
7567           tree low = NULL_TREE, high = NULL_TREE;
7568
7569           if (TYPE_MIN_VALUE (t))
7570             low = SUBSTITUTE_IN_EXPR (TYPE_MIN_VALUE (t), f, r);
7571           if (TYPE_MAX_VALUE (t))
7572             high = SUBSTITUTE_IN_EXPR (TYPE_MAX_VALUE (t), f, r);
7573
7574           if (low == TYPE_MIN_VALUE (t) && high == TYPE_MAX_VALUE (t))
7575             return t;
7576
7577           t = copy_type (t);
7578           TYPE_MIN_VALUE (t) = low;
7579           TYPE_MAX_VALUE (t) = high;
7580         }
7581       return t;
7582
7583     case COMPLEX_TYPE:
7584       tem = substitute_in_type (TREE_TYPE (t), f, r);
7585       if (tem == TREE_TYPE (t))
7586         return t;
7587
7588       return build_complex_type (tem);
7589
7590     case OFFSET_TYPE:
7591     case METHOD_TYPE:
7592     case FUNCTION_TYPE:
7593     case LANG_TYPE:
7594       /* Don't know how to do these yet.  */
7595       gcc_unreachable ();
7596
7597     case ARRAY_TYPE:
7598       {
7599         tree component = substitute_in_type (TREE_TYPE (t), f, r);
7600         tree domain = substitute_in_type (TYPE_DOMAIN (t), f, r);
7601
7602         if (component == TREE_TYPE (t) && domain == TYPE_DOMAIN (t))
7603           return t;
7604
7605         new = build_array_type (component, domain);
7606         TYPE_SIZE (new) = 0;
7607         TYPE_NONALIASED_COMPONENT (new) = TYPE_NONALIASED_COMPONENT (t);
7608         TYPE_MULTI_ARRAY_P (new) = TYPE_MULTI_ARRAY_P (t);
7609         TYPE_CONVENTION_FORTRAN_P (new) = TYPE_CONVENTION_FORTRAN_P (t);
7610         layout_type (new);
7611         TYPE_ALIGN (new) = TYPE_ALIGN (t);
7612         TYPE_USER_ALIGN (new) = TYPE_USER_ALIGN (t);
7613
7614         /* If we had bounded the sizes of T by a constant, bound the sizes of
7615            NEW by the same constant.  */
7616         if (TREE_CODE (TYPE_SIZE (t)) == MIN_EXPR)
7617           TYPE_SIZE (new)
7618             = size_binop (MIN_EXPR, TREE_OPERAND (TYPE_SIZE (t), 1),
7619                           TYPE_SIZE (new));
7620         if (TREE_CODE (TYPE_SIZE_UNIT (t)) == MIN_EXPR)
7621           TYPE_SIZE_UNIT (new)
7622             = size_binop (MIN_EXPR, TREE_OPERAND (TYPE_SIZE_UNIT (t), 1),
7623                           TYPE_SIZE_UNIT (new));
7624         return new;
7625       }
7626
7627     case RECORD_TYPE:
7628     case UNION_TYPE:
7629     case QUAL_UNION_TYPE:
7630       {
7631         tree field;
7632         bool changed_field
7633           = (f == NULL_TREE && !TREE_CONSTANT (TYPE_SIZE (t)));
7634         bool field_has_rep = false;
7635         tree last_field = NULL_TREE;
7636
7637         tree new = copy_type (t);
7638
7639         /* Start out with no fields, make new fields, and chain them
7640            in.  If we haven't actually changed the type of any field,
7641            discard everything we've done and return the old type.  */
7642
7643         TYPE_FIELDS (new) = NULL_TREE;
7644         TYPE_SIZE (new) = NULL_TREE;
7645
7646         for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
7647           {
7648             tree new_field = copy_node (field);
7649
7650             TREE_TYPE (new_field)
7651               = substitute_in_type (TREE_TYPE (new_field), f, r);
7652
7653             if (DECL_HAS_REP_P (field) && !DECL_INTERNAL_P (field))
7654               field_has_rep = true;
7655             else if (TREE_TYPE (new_field) != TREE_TYPE (field))
7656               changed_field = true;
7657
7658             /* If this is an internal field and the type of this field is
7659                a UNION_TYPE or RECORD_TYPE with no elements, ignore it.  If
7660                the type just has one element, treat that as the field.
7661                But don't do this if we are processing a QUAL_UNION_TYPE.  */
7662             if (TREE_CODE (t) != QUAL_UNION_TYPE
7663                 && DECL_INTERNAL_P (new_field)
7664                 && (TREE_CODE (TREE_TYPE (new_field)) == UNION_TYPE
7665                     || TREE_CODE (TREE_TYPE (new_field)) == RECORD_TYPE))
7666               {
7667                 if (!TYPE_FIELDS (TREE_TYPE (new_field)))
7668                   continue;
7669
7670                 if (!TREE_CHAIN (TYPE_FIELDS (TREE_TYPE (new_field))))
7671                   {
7672                     tree next_new_field
7673                       = copy_node (TYPE_FIELDS (TREE_TYPE (new_field)));
7674
7675                     /* Make sure omitting the union doesn't change
7676                        the layout.  */
7677                     DECL_ALIGN (next_new_field) = DECL_ALIGN (new_field);
7678                     new_field = next_new_field;
7679                   }
7680               }
7681
7682             DECL_CONTEXT (new_field) = new;
7683             SET_DECL_ORIGINAL_FIELD (new_field,
7684                                      (DECL_ORIGINAL_FIELD (field)
7685                                       ? DECL_ORIGINAL_FIELD (field) : field));
7686
7687             /* If the size of the old field was set at a constant,
7688                propagate the size in case the type's size was variable.
7689                (This occurs in the case of a variant or discriminated
7690                record with a default size used as a field of another
7691                record.)  */
7692             DECL_SIZE (new_field)
7693               = TREE_CODE (DECL_SIZE (field)) == INTEGER_CST
7694                 ? DECL_SIZE (field) : NULL_TREE;
7695             DECL_SIZE_UNIT (new_field)
7696               = TREE_CODE (DECL_SIZE_UNIT (field)) == INTEGER_CST
7697                 ? DECL_SIZE_UNIT (field) : NULL_TREE;
7698
7699             if (TREE_CODE (t) == QUAL_UNION_TYPE)
7700               {
7701                 tree new_q = SUBSTITUTE_IN_EXPR (DECL_QUALIFIER (field), f, r);
7702
7703                 if (new_q != DECL_QUALIFIER (new_field))
7704                   changed_field = true;
7705
7706                 /* Do the substitution inside the qualifier and if we find
7707                    that this field will not be present, omit it.  */
7708                 DECL_QUALIFIER (new_field) = new_q;
7709
7710                 if (integer_zerop (DECL_QUALIFIER (new_field)))
7711                   continue;
7712               }
7713
7714             if (!last_field)
7715               TYPE_FIELDS (new) = new_field;
7716             else
7717               TREE_CHAIN (last_field) = new_field;
7718
7719             last_field = new_field;
7720
7721             /* If this is a qualified type and this field will always be
7722                present, we are done.  */
7723             if (TREE_CODE (t) == QUAL_UNION_TYPE
7724                 && integer_onep (DECL_QUALIFIER (new_field)))
7725               break;
7726           }
7727
7728         /* If this used to be a qualified union type, but we now know what
7729            field will be present, make this a normal union.  */
7730         if (changed_field && TREE_CODE (new) == QUAL_UNION_TYPE
7731             && (!TYPE_FIELDS (new)
7732                 || integer_onep (DECL_QUALIFIER (TYPE_FIELDS (new)))))
7733           TREE_SET_CODE (new, UNION_TYPE);
7734         else if (!changed_field)
7735           return t;
7736
7737         gcc_assert (!field_has_rep);
7738         layout_type (new);
7739
7740         /* If the size was originally a constant use it.  */
7741         if (TYPE_SIZE (t) && TREE_CODE (TYPE_SIZE (t)) == INTEGER_CST
7742             && TREE_CODE (TYPE_SIZE (new)) != INTEGER_CST)
7743           {
7744             TYPE_SIZE (new) = TYPE_SIZE (t);
7745             TYPE_SIZE_UNIT (new) = TYPE_SIZE_UNIT (t);
7746             SET_TYPE_ADA_SIZE (new, TYPE_ADA_SIZE (t));
7747           }
7748
7749         return new;
7750       }
7751
7752     default:
7753       return t;
7754     }
7755 }
7756 \f
7757 /* Return the "RM size" of GNU_TYPE.  This is the actual number of bits
7758    needed to represent the object.  */
7759
7760 tree
7761 rm_size (tree gnu_type)
7762 {
7763   /* For integer types, this is the precision.  For record types, we store
7764      the size explicitly.  For other types, this is just the size.  */
7765
7766   if (INTEGRAL_TYPE_P (gnu_type) && TYPE_RM_SIZE (gnu_type))
7767     return TYPE_RM_SIZE (gnu_type);
7768   else if (TREE_CODE (gnu_type) == RECORD_TYPE
7769            && TYPE_CONTAINS_TEMPLATE_P (gnu_type))
7770     /* Return the rm_size of the actual data plus the size of the template.  */
7771     return
7772       size_binop (PLUS_EXPR,
7773                   rm_size (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (gnu_type)))),
7774                   DECL_SIZE (TYPE_FIELDS (gnu_type)));
7775   else if ((TREE_CODE (gnu_type) == RECORD_TYPE
7776             || TREE_CODE (gnu_type) == UNION_TYPE
7777             || TREE_CODE (gnu_type) == QUAL_UNION_TYPE)
7778            && !TYPE_IS_FAT_POINTER_P (gnu_type)
7779            && TYPE_ADA_SIZE (gnu_type))
7780     return TYPE_ADA_SIZE (gnu_type);
7781   else
7782     return TYPE_SIZE (gnu_type);
7783 }
7784 \f
7785 /* Return an identifier representing the external name to be used for
7786    GNAT_ENTITY.  If SUFFIX is specified, the name is followed by "___"
7787    and the specified suffix.  */
7788
7789 tree
7790 create_concat_name (Entity_Id gnat_entity, const char *suffix)
7791 {
7792   Entity_Kind kind = Ekind (gnat_entity);
7793
7794   const char *str = (!suffix ? "" : suffix);
7795   String_Template temp = {1, strlen (str)};
7796   Fat_Pointer fp = {str, &temp};
7797
7798   Get_External_Name_With_Suffix (gnat_entity, fp);
7799
7800   /* A variable using the Stdcall convention (meaning we are running
7801      on a Windows box) live in a DLL.  Here we adjust its name to use
7802      the jump-table, the _imp__NAME contains the address for the NAME
7803      variable.  */
7804   if ((kind == E_Variable || kind == E_Constant)
7805       && Has_Stdcall_Convention (gnat_entity))
7806     {
7807       const char *prefix = "_imp__";
7808       int k, plen = strlen (prefix);
7809
7810       for (k = 0; k <= Name_Len; k++)
7811         Name_Buffer [Name_Len - k + plen] = Name_Buffer [Name_Len - k];
7812       strncpy (Name_Buffer, prefix, plen);
7813     }
7814
7815   return get_identifier (Name_Buffer);
7816 }
7817
7818 /* Return the name to be used for GNAT_ENTITY.  If a type, create a
7819    fully-qualified name, possibly with type information encoding.
7820    Otherwise, return the name.  */
7821
7822 tree
7823 get_entity_name (Entity_Id gnat_entity)
7824 {
7825   Get_Encoded_Name (gnat_entity);
7826   return get_identifier (Name_Buffer);
7827 }
7828
7829 /* Given GNU_ID, an IDENTIFIER_NODE containing a name and SUFFIX, a
7830    string, return a new IDENTIFIER_NODE that is the concatenation of
7831    the name in GNU_ID and SUFFIX.  */
7832
7833 tree
7834 concat_id_with_name (tree gnu_id, const char *suffix)
7835 {
7836   int len = IDENTIFIER_LENGTH (gnu_id);
7837
7838   strncpy (Name_Buffer, IDENTIFIER_POINTER (gnu_id), len);
7839   strncpy (Name_Buffer + len, "___", 3);
7840   len += 3;
7841   strcpy (Name_Buffer + len, suffix);
7842   return get_identifier (Name_Buffer);
7843 }
7844
7845 #include "gt-ada-decl.h"