OSDN Git Service

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