OSDN Git Service

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