OSDN Git Service

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