OSDN Git Service

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