OSDN Git Service

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