OSDN Git Service

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