OSDN Git Service

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