1 /****************************************************************************
3 * GNAT COMPILER COMPONENTS *
7 * C Implementation File *
9 * Copyright (C) 1992-2010, Free Software Foundation, Inc. *
11 * GNAT is free software; you can redistribute it and/or modify it under *
12 * terms of the GNU General Public License as published by the Free Soft- *
13 * ware Foundation; either version 3, or (at your option) any later ver- *
14 * sion. GNAT is distributed in the hope that it will be useful, but WITH- *
15 * OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
16 * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License *
17 * for more details. You should have received a copy of the GNU General *
18 * Public License along with GCC; see the file COPYING3. If not see *
19 * <http://www.gnu.org/licenses/>. *
21 * GNAT was originally developed by the GNAT team at New York University. *
22 * Extensive contributions were provided by Ada Core Technologies Inc. *
24 ****************************************************************************/
28 #include "coretypes.h"
36 #include "tree-inline.h"
54 #ifndef MAX_FIXED_MODE_SIZE
55 #define MAX_FIXED_MODE_SIZE GET_MODE_BITSIZE (DImode)
58 /* Convention_Stdcall should be processed in a specific way on Windows targets
59 only. The macro below is a helper to avoid having to check for a Windows
60 specific attribute throughout this unit. */
62 #if TARGET_DLLIMPORT_DECL_ATTRIBUTES
63 #define Has_Stdcall_Convention(E) (Convention (E) == Convention_Stdcall)
65 #define Has_Stdcall_Convention(E) (0)
68 /* Stack realignment for functions with foreign conventions is provided on a
69 per back-end basis now, as it is handled by the prologue expanders and not
70 as part of the function's body any more. It might be requested by way of a
71 dedicated function type attribute on the targets that support it.
73 We need a way to avoid setting the attribute on the targets that don't
74 support it and use FORCE_PREFERRED_STACK_BOUNDARY_IN_MAIN for this purpose.
76 It is defined on targets where the circuitry is available, and indicates
77 whether the realignment is needed for 'main'. We use this to decide for
78 foreign subprograms as well.
80 It is not defined on targets where the circuitry is not implemented, and
81 we just never set the attribute in these cases.
83 Whether it is defined on all targets that would need it in theory is
84 not entirely clear. We currently trust the base GCC settings for this
87 #ifndef FORCE_PREFERRED_STACK_BOUNDARY_IN_MAIN
88 #define FORCE_PREFERRED_STACK_BOUNDARY_IN_MAIN 0
93 struct incomplete *next;
98 /* These variables are used to defer recursively expanding incomplete types
99 while we are processing an array, a record or a subprogram type. */
100 static int defer_incomplete_level = 0;
101 static struct incomplete *defer_incomplete_list;
103 /* This variable is used to delay expanding From_With_Type types until the
105 static struct incomplete *defer_limited_with;
107 /* These variables are used to defer finalizing types. The element of the
108 list is the TYPE_DECL associated with the type. */
109 static int defer_finalize_level = 0;
110 static VEC (tree,heap) *defer_finalize_list;
112 /* A hash table used to cache the result of annotate_value. */
113 static GTY ((if_marked ("tree_int_map_marked_p"),
114 param_is (struct tree_int_map))) htab_t annotate_value_cache;
123 static void relate_alias_sets (tree, tree, enum alias_set_op);
125 static bool allocatable_size_p (tree, bool);
126 static void prepend_one_attribute_to (struct attrib **,
127 enum attr_type, tree, tree, Node_Id);
128 static void prepend_attributes (Entity_Id, struct attrib **);
129 static tree elaborate_expression (Node_Id, Entity_Id, tree, bool, bool, bool);
130 static bool is_variable_size (tree);
131 static tree elaborate_expression_1 (tree, Entity_Id, tree, bool, bool);
132 static tree make_packable_type (tree, bool);
133 static tree gnat_to_gnu_component_type (Entity_Id, bool, bool);
134 static tree gnat_to_gnu_param (Entity_Id, Mechanism_Type, Entity_Id, bool,
136 static tree gnat_to_gnu_field (Entity_Id, tree, int, bool, bool);
137 static bool same_discriminant_p (Entity_Id, Entity_Id);
138 static bool array_type_has_nonaliased_component (tree, Entity_Id);
139 static bool compile_time_known_address_p (Node_Id);
140 static bool cannot_be_superflat_p (Node_Id);
141 static bool constructor_address_p (tree);
142 static void components_to_record (tree, Node_Id, tree, int, bool, tree *,
143 bool, bool, bool, bool, bool);
144 static Uint annotate_value (tree);
145 static void annotate_rep (Entity_Id, tree);
146 static tree build_position_list (tree, bool, tree, tree, unsigned int, tree);
147 static tree build_subst_list (Entity_Id, Entity_Id, bool);
148 static tree build_variant_list (tree, tree, tree);
149 static tree validate_size (Uint, tree, Entity_Id, enum tree_code, bool, bool);
150 static void set_rm_size (Uint, tree, Entity_Id);
151 static tree make_type_from_size (tree, tree, bool);
152 static unsigned int validate_alignment (Uint, Entity_Id, unsigned int);
153 static unsigned int ceil_alignment (unsigned HOST_WIDE_INT);
154 static void check_ok_for_atomic (tree, Entity_Id, bool);
155 static int compatible_signatures_p (tree, tree);
156 static tree create_field_decl_from (tree, tree, tree, tree, tree, tree);
157 static tree get_rep_part (tree);
158 static tree get_variant_part (tree);
159 static tree create_variant_part_from (tree, tree, tree, tree, tree);
160 static void copy_and_substitute_in_size (tree, tree, tree);
161 static void rest_of_type_decl_compilation_no_defer (tree);
163 /* Given GNAT_ENTITY, a GNAT defining identifier node, which denotes some Ada
164 entity, return the equivalent GCC tree for that entity (a ..._DECL node)
165 and associate the ..._DECL node with the input GNAT defining identifier.
167 If GNAT_ENTITY is a variable or a constant declaration, GNU_EXPR gives its
168 initial value (in GCC tree form). This is optional for a variable. For
169 a renamed entity, GNU_EXPR gives the object being renamed.
171 DEFINITION is nonzero if this call is intended for a definition. This is
172 used for separate compilation where it is necessary to know whether an
173 external declaration or a definition must be created if the GCC equivalent
174 was not created previously. The value of 1 is normally used for a nonzero
175 DEFINITION, but a value of 2 is used in special circumstances, defined in
179 gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
181 /* Contains the kind of the input GNAT node. */
182 const Entity_Kind kind = Ekind (gnat_entity);
183 /* True if this is a type. */
184 const bool is_type = IN (kind, Type_Kind);
185 /* True if debug info is requested for this entity. */
186 const bool debug_info_p = Needs_Debug_Info (gnat_entity);
187 /* True if this entity is to be considered as imported. */
188 const bool imported_p
189 = (Is_Imported (gnat_entity) && No (Address_Clause (gnat_entity)));
190 /* For a type, contains the equivalent GNAT node to be used in gigi. */
191 Entity_Id gnat_equiv_type = Empty;
192 /* Temporary used to walk the GNAT tree. */
194 /* Contains the GCC DECL node which is equivalent to the input GNAT node.
195 This node will be associated with the GNAT node by calling at the end
196 of the `switch' statement. */
197 tree gnu_decl = NULL_TREE;
198 /* Contains the GCC type to be used for the GCC node. */
199 tree gnu_type = NULL_TREE;
200 /* Contains the GCC size tree to be used for the GCC node. */
201 tree gnu_size = NULL_TREE;
202 /* Contains the GCC name to be used for the GCC node. */
203 tree gnu_entity_name;
204 /* True if we have already saved gnu_decl as a GNAT association. */
206 /* True if we incremented defer_incomplete_level. */
207 bool this_deferred = false;
208 /* True if we incremented force_global. */
209 bool this_global = false;
210 /* True if we should check to see if elaborated during processing. */
211 bool maybe_present = false;
212 /* True if we made GNU_DECL and its type here. */
213 bool this_made_decl = false;
214 /* Size and alignment of the GCC node, if meaningful. */
215 unsigned int esize = 0, align = 0;
216 /* Contains the list of attributes directly attached to the entity. */
217 struct attrib *attr_list = NULL;
219 /* Since a use of an Itype is a definition, process it as such if it
220 is not in a with'ed unit. */
223 && Is_Itype (gnat_entity)
224 && !present_gnu_tree (gnat_entity)
225 && In_Extended_Main_Code_Unit (gnat_entity))
227 /* Ensure that we are in a subprogram mentioned in the Scope chain of
228 this entity, our current scope is global, or we encountered a task
229 or entry (where we can't currently accurately check scoping). */
230 if (!current_function_decl
231 || DECL_ELABORATION_PROC_P (current_function_decl))
233 process_type (gnat_entity);
234 return get_gnu_tree (gnat_entity);
237 for (gnat_temp = Scope (gnat_entity);
239 gnat_temp = Scope (gnat_temp))
241 if (Is_Type (gnat_temp))
242 gnat_temp = Underlying_Type (gnat_temp);
244 if (Ekind (gnat_temp) == E_Subprogram_Body)
246 = Corresponding_Spec (Parent (Declaration_Node (gnat_temp)));
248 if (IN (Ekind (gnat_temp), Subprogram_Kind)
249 && Present (Protected_Body_Subprogram (gnat_temp)))
250 gnat_temp = Protected_Body_Subprogram (gnat_temp);
252 if (Ekind (gnat_temp) == E_Entry
253 || Ekind (gnat_temp) == E_Entry_Family
254 || Ekind (gnat_temp) == E_Task_Type
255 || (IN (Ekind (gnat_temp), Subprogram_Kind)
256 && present_gnu_tree (gnat_temp)
257 && (current_function_decl
258 == gnat_to_gnu_entity (gnat_temp, NULL_TREE, 0))))
260 process_type (gnat_entity);
261 return get_gnu_tree (gnat_entity);
265 /* This abort means the Itype has an incorrect scope, i.e. that its
266 scope does not correspond to the subprogram it is declared in. */
270 /* If we've already processed this entity, return what we got last time.
271 If we are defining the node, we should not have already processed it.
272 In that case, we will abort below when we try to save a new GCC tree
273 for this object. We also need to handle the case of getting a dummy
274 type when a Full_View exists. */
275 if ((!definition || (is_type && imported_p))
276 && present_gnu_tree (gnat_entity))
278 gnu_decl = get_gnu_tree (gnat_entity);
280 if (TREE_CODE (gnu_decl) == TYPE_DECL
281 && TYPE_IS_DUMMY_P (TREE_TYPE (gnu_decl))
282 && IN (kind, Incomplete_Or_Private_Kind)
283 && Present (Full_View (gnat_entity)))
286 = gnat_to_gnu_entity (Full_View (gnat_entity), NULL_TREE, 0);
287 save_gnu_tree (gnat_entity, NULL_TREE, false);
288 save_gnu_tree (gnat_entity, gnu_decl, false);
294 /* If this is a numeric or enumeral type, or an access type, a nonzero
295 Esize must be specified unless it was specified by the programmer. */
296 gcc_assert (!Unknown_Esize (gnat_entity)
297 || Has_Size_Clause (gnat_entity)
298 || (!IN (kind, Numeric_Kind)
299 && !IN (kind, Enumeration_Kind)
300 && (!IN (kind, Access_Kind)
301 || kind == E_Access_Protected_Subprogram_Type
302 || kind == E_Anonymous_Access_Protected_Subprogram_Type
303 || kind == E_Access_Subtype)));
305 /* The RM size must be specified for all discrete and fixed-point types. */
306 gcc_assert (!(IN (kind, Discrete_Or_Fixed_Point_Kind)
307 && Unknown_RM_Size (gnat_entity)));
309 /* If we get here, it means we have not yet done anything with this entity.
310 If we are not defining it, it must be a type or an entity that is defined
311 elsewhere or externally, otherwise we should have defined it already. */
312 gcc_assert (definition
313 || type_annotate_only
315 || kind == E_Discriminant
316 || kind == E_Component
318 || (kind == E_Constant && Present (Full_View (gnat_entity)))
319 || Is_Public (gnat_entity));
321 /* Get the name of the entity and set up the line number and filename of
322 the original definition for use in any decl we make. */
323 gnu_entity_name = get_entity_name (gnat_entity);
324 Sloc_to_locus (Sloc (gnat_entity), &input_location);
326 /* For cases when we are not defining (i.e., we are referencing from
327 another compilation unit) public entities, show we are at global level
328 for the purpose of computing scopes. Don't do this for components or
329 discriminants since the relevant test is whether or not the record is
332 && kind != E_Component
333 && kind != E_Discriminant
334 && Is_Public (gnat_entity)
335 && !Is_Statically_Allocated (gnat_entity))
336 force_global++, this_global = true;
338 /* Handle any attributes directly attached to the entity. */
339 if (Has_Gigi_Rep_Item (gnat_entity))
340 prepend_attributes (gnat_entity, &attr_list);
342 /* Do some common processing for types. */
345 /* Compute the equivalent type to be used in gigi. */
346 gnat_equiv_type = Gigi_Equivalent_Type (gnat_entity);
348 /* Machine_Attributes on types are expected to be propagated to
349 subtypes. The corresponding Gigi_Rep_Items are only attached
350 to the first subtype though, so we handle the propagation here. */
351 if (Base_Type (gnat_entity) != gnat_entity
352 && !Is_First_Subtype (gnat_entity)
353 && Has_Gigi_Rep_Item (First_Subtype (Base_Type (gnat_entity))))
354 prepend_attributes (First_Subtype (Base_Type (gnat_entity)),
357 /* Compute a default value for the size of the type. */
358 if (Known_Esize (gnat_entity)
359 && UI_Is_In_Int_Range (Esize (gnat_entity)))
361 unsigned int max_esize;
362 esize = UI_To_Int (Esize (gnat_entity));
364 if (IN (kind, Float_Kind))
365 max_esize = fp_prec_to_size (LONG_DOUBLE_TYPE_SIZE);
366 else if (IN (kind, Access_Kind))
367 max_esize = POINTER_SIZE * 2;
369 max_esize = LONG_LONG_TYPE_SIZE;
371 if (esize > max_esize)
375 esize = LONG_LONG_TYPE_SIZE;
381 /* If this is a use of a deferred constant without address clause,
382 get its full definition. */
384 && No (Address_Clause (gnat_entity))
385 && Present (Full_View (gnat_entity)))
388 = gnat_to_gnu_entity (Full_View (gnat_entity), gnu_expr, 0);
393 /* If we have an external constant that we are not defining, get the
394 expression that is was defined to represent. We may throw that
395 expression away later if it is not a constant. Do not retrieve the
396 expression if it is an aggregate or allocator, because in complex
397 instantiation contexts it may not be expanded */
399 && Present (Expression (Declaration_Node (gnat_entity)))
400 && !No_Initialization (Declaration_Node (gnat_entity))
401 && (Nkind (Expression (Declaration_Node (gnat_entity)))
403 && (Nkind (Expression (Declaration_Node (gnat_entity)))
405 gnu_expr = gnat_to_gnu (Expression (Declaration_Node (gnat_entity)));
407 /* Ignore deferred constant definitions without address clause since
408 they are processed fully in the front-end. If No_Initialization
409 is set, this is not a deferred constant but a constant whose value
410 is built manually. And constants that are renamings are handled
414 && No (Address_Clause (gnat_entity))
415 && !No_Initialization (Declaration_Node (gnat_entity))
416 && No (Renamed_Object (gnat_entity)))
418 gnu_decl = error_mark_node;
423 /* Ignore constant definitions already marked with the error node. See
424 the N_Object_Declaration case of gnat_to_gnu for the rationale. */
427 && present_gnu_tree (gnat_entity)
428 && get_gnu_tree (gnat_entity) == error_mark_node)
430 maybe_present = true;
437 /* We used to special case VMS exceptions here to directly map them to
438 their associated condition code. Since this code had to be masked
439 dynamically to strip off the severity bits, this caused trouble in
440 the GCC/ZCX case because the "type" pointers we store in the tables
441 have to be static. We now don't special case here anymore, and let
442 the regular processing take place, which leaves us with a regular
443 exception data object for VMS exceptions too. The condition code
444 mapping is taken care of by the front end and the bitmasking by the
451 /* The GNAT record where the component was defined. */
452 Entity_Id gnat_record = Underlying_Type (Scope (gnat_entity));
454 /* If the variable is an inherited record component (in the case of
455 extended record types), just return the inherited entity, which
456 must be a FIELD_DECL. Likewise for discriminants.
457 For discriminants of untagged records which have explicit
458 stored discriminants, return the entity for the corresponding
459 stored discriminant. Also use Original_Record_Component
460 if the record has a private extension. */
461 if (Present (Original_Record_Component (gnat_entity))
462 && Original_Record_Component (gnat_entity) != gnat_entity)
465 = gnat_to_gnu_entity (Original_Record_Component (gnat_entity),
466 gnu_expr, definition);
471 /* If the enclosing record has explicit stored discriminants,
472 then it is an untagged record. If the Corresponding_Discriminant
473 is not empty then this must be a renamed discriminant and its
474 Original_Record_Component must point to the corresponding explicit
475 stored discriminant (i.e. we should have taken the previous
477 else if (Present (Corresponding_Discriminant (gnat_entity))
478 && Is_Tagged_Type (gnat_record))
480 /* A tagged record has no explicit stored discriminants. */
481 gcc_assert (First_Discriminant (gnat_record)
482 == First_Stored_Discriminant (gnat_record));
484 = gnat_to_gnu_entity (Corresponding_Discriminant (gnat_entity),
485 gnu_expr, definition);
490 else if (Present (CR_Discriminant (gnat_entity))
491 && type_annotate_only)
493 gnu_decl = gnat_to_gnu_entity (CR_Discriminant (gnat_entity),
494 gnu_expr, definition);
499 /* If the enclosing record has explicit stored discriminants, then
500 it is an untagged record. If the Corresponding_Discriminant
501 is not empty then this must be a renamed discriminant and its
502 Original_Record_Component must point to the corresponding explicit
503 stored discriminant (i.e. we should have taken the first
505 else if (Present (Corresponding_Discriminant (gnat_entity))
506 && (First_Discriminant (gnat_record)
507 != First_Stored_Discriminant (gnat_record)))
510 /* Otherwise, if we are not defining this and we have no GCC type
511 for the containing record, make one for it. Then we should
512 have made our own equivalent. */
513 else if (!definition && !present_gnu_tree (gnat_record))
515 /* ??? If this is in a record whose scope is a protected
516 type and we have an Original_Record_Component, use it.
517 This is a workaround for major problems in protected type
519 Entity_Id Scop = Scope (Scope (gnat_entity));
520 if ((Is_Protected_Type (Scop)
521 || (Is_Private_Type (Scop)
522 && Present (Full_View (Scop))
523 && Is_Protected_Type (Full_View (Scop))))
524 && Present (Original_Record_Component (gnat_entity)))
527 = gnat_to_gnu_entity (Original_Record_Component
534 gnat_to_gnu_entity (Scope (gnat_entity), NULL_TREE, 0);
535 gnu_decl = get_gnu_tree (gnat_entity);
541 /* Here we have no GCC type and this is a reference rather than a
542 definition. This should never happen. Most likely the cause is
543 reference before declaration in the gnat tree for gnat_entity. */
547 case E_Loop_Parameter:
548 case E_Out_Parameter:
551 /* Simple variables, loop variables, Out parameters and exceptions. */
555 = ((kind == E_Constant || kind == E_Variable)
556 && Is_True_Constant (gnat_entity)
557 && !Treat_As_Volatile (gnat_entity)
558 && (((Nkind (Declaration_Node (gnat_entity))
559 == N_Object_Declaration)
560 && Present (Expression (Declaration_Node (gnat_entity))))
561 || Present (Renamed_Object (gnat_entity))));
562 bool inner_const_flag = const_flag;
563 bool static_p = Is_Statically_Allocated (gnat_entity);
564 bool mutable_p = false;
565 bool used_by_ref = false;
566 tree gnu_ext_name = NULL_TREE;
567 tree renamed_obj = NULL_TREE;
568 tree gnu_object_size;
570 if (Present (Renamed_Object (gnat_entity)) && !definition)
572 if (kind == E_Exception)
573 gnu_expr = gnat_to_gnu_entity (Renamed_Entity (gnat_entity),
576 gnu_expr = gnat_to_gnu (Renamed_Object (gnat_entity));
579 /* Get the type after elaborating the renamed object. */
580 gnu_type = gnat_to_gnu_type (Etype (gnat_entity));
582 /* For a debug renaming declaration, build a pure debug entity. */
583 if (Present (Debug_Renaming_Link (gnat_entity)))
586 gnu_decl = build_decl (input_location,
587 VAR_DECL, gnu_entity_name, gnu_type);
588 /* The (MEM (CONST (0))) pattern is prescribed by STABS. */
589 if (global_bindings_p ())
590 addr = gen_rtx_CONST (VOIDmode, const0_rtx);
592 addr = stack_pointer_rtx;
593 SET_DECL_RTL (gnu_decl, gen_rtx_MEM (Pmode, addr));
594 gnat_pushdecl (gnu_decl, gnat_entity);
598 /* If this is a loop variable, its type should be the base type.
599 This is because the code for processing a loop determines whether
600 a normal loop end test can be done by comparing the bounds of the
601 loop against those of the base type, which is presumed to be the
602 size used for computation. But this is not correct when the size
603 of the subtype is smaller than the type. */
604 if (kind == E_Loop_Parameter)
605 gnu_type = get_base_type (gnu_type);
607 /* Reject non-renamed objects whose type is an unconstrained array or
608 any object whose type is a dummy type or void. */
609 if ((TREE_CODE (gnu_type) == UNCONSTRAINED_ARRAY_TYPE
610 && No (Renamed_Object (gnat_entity)))
611 || TYPE_IS_DUMMY_P (gnu_type)
612 || TREE_CODE (gnu_type) == VOID_TYPE)
614 gcc_assert (type_annotate_only);
617 return error_mark_node;
620 /* If an alignment is specified, use it if valid. Note that exceptions
621 are objects but don't have an alignment. We must do this before we
622 validate the size, since the alignment can affect the size. */
623 if (kind != E_Exception && Known_Alignment (gnat_entity))
625 gcc_assert (Present (Alignment (gnat_entity)));
626 align = validate_alignment (Alignment (gnat_entity), gnat_entity,
627 TYPE_ALIGN (gnu_type));
629 /* No point in changing the type if there is an address clause
630 as the final type of the object will be a reference type. */
631 if (Present (Address_Clause (gnat_entity)))
635 = maybe_pad_type (gnu_type, NULL_TREE, align, gnat_entity,
636 false, false, definition, true);
639 /* If we are defining the object, see if it has a Size and validate it
640 if so. If we are not defining the object and a Size clause applies,
641 simply retrieve the value. We don't want to ignore the clause and
642 it is expected to have been validated already. Then get the new
645 gnu_size = validate_size (Esize (gnat_entity), gnu_type,
646 gnat_entity, VAR_DECL, false,
647 Has_Size_Clause (gnat_entity));
648 else if (Has_Size_Clause (gnat_entity))
649 gnu_size = UI_To_gnu (Esize (gnat_entity), bitsizetype);
654 = make_type_from_size (gnu_type, gnu_size,
655 Has_Biased_Representation (gnat_entity));
657 if (operand_equal_p (TYPE_SIZE (gnu_type), gnu_size, 0))
658 gnu_size = NULL_TREE;
661 /* If this object has self-referential size, it must be a record with
662 a default discriminant. We are supposed to allocate an object of
663 the maximum size in this case, unless it is a constant with an
664 initializing expression, in which case we can get the size from
665 that. Note that the resulting size may still be a variable, so
666 this may end up with an indirect allocation. */
667 if (No (Renamed_Object (gnat_entity))
668 && CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type)))
670 if (gnu_expr && kind == E_Constant)
672 tree size = TYPE_SIZE (TREE_TYPE (gnu_expr));
673 if (CONTAINS_PLACEHOLDER_P (size))
675 /* If the initializing expression is itself a constant,
676 despite having a nominal type with self-referential
677 size, we can get the size directly from it. */
678 if (TREE_CODE (gnu_expr) == COMPONENT_REF
680 (TREE_TYPE (TREE_OPERAND (gnu_expr, 0)))
681 && TREE_CODE (TREE_OPERAND (gnu_expr, 0)) == VAR_DECL
682 && (TREE_READONLY (TREE_OPERAND (gnu_expr, 0))
683 || DECL_READONLY_ONCE_ELAB
684 (TREE_OPERAND (gnu_expr, 0))))
685 gnu_size = DECL_SIZE (TREE_OPERAND (gnu_expr, 0));
688 = SUBSTITUTE_PLACEHOLDER_IN_EXPR (size, gnu_expr);
693 /* We may have no GNU_EXPR because No_Initialization is
694 set even though there's an Expression. */
695 else if (kind == E_Constant
696 && (Nkind (Declaration_Node (gnat_entity))
697 == N_Object_Declaration)
698 && Present (Expression (Declaration_Node (gnat_entity))))
700 = TYPE_SIZE (gnat_to_gnu_type
702 (Expression (Declaration_Node (gnat_entity)))));
705 gnu_size = max_size (TYPE_SIZE (gnu_type), true);
710 /* If the size is zero byte, make it one byte since some linkers have
711 troubles with zero-sized objects. If the object will have a
712 template, that will make it nonzero so don't bother. Also avoid
713 doing that for an object renaming or an object with an address
714 clause, as we would lose useful information on the view size
715 (e.g. for null array slices) and we are not allocating the object
718 && integer_zerop (gnu_size)
719 && !TREE_OVERFLOW (gnu_size))
720 || (TYPE_SIZE (gnu_type)
721 && integer_zerop (TYPE_SIZE (gnu_type))
722 && !TREE_OVERFLOW (TYPE_SIZE (gnu_type))))
723 && (!Is_Constr_Subt_For_UN_Aliased (Etype (gnat_entity))
724 || !Is_Array_Type (Etype (gnat_entity)))
725 && No (Renamed_Object (gnat_entity))
726 && No (Address_Clause (gnat_entity)))
727 gnu_size = bitsize_unit_node;
729 /* If this is an object with no specified size and alignment, and
730 if either it is atomic or we are not optimizing alignment for
731 space and it is composite and not an exception, an Out parameter
732 or a reference to another object, and the size of its type is a
733 constant, set the alignment to the smallest one which is not
734 smaller than the size, with an appropriate cap. */
735 if (!gnu_size && align == 0
736 && (Is_Atomic (gnat_entity)
737 || (!Optimize_Alignment_Space (gnat_entity)
738 && kind != E_Exception
739 && kind != E_Out_Parameter
740 && Is_Composite_Type (Etype (gnat_entity))
741 && !Is_Constr_Subt_For_UN_Aliased (Etype (gnat_entity))
743 && No (Renamed_Object (gnat_entity))
744 && No (Address_Clause (gnat_entity))))
745 && TREE_CODE (TYPE_SIZE (gnu_type)) == INTEGER_CST)
747 /* No point in jumping through all the hoops needed in order
748 to support BIGGEST_ALIGNMENT if we don't really have to.
749 So we cap to the smallest alignment that corresponds to
750 a known efficient memory access pattern of the target. */
751 unsigned int align_cap = Is_Atomic (gnat_entity)
753 : get_mode_alignment (ptr_mode);
755 if (!host_integerp (TYPE_SIZE (gnu_type), 1)
756 || compare_tree_int (TYPE_SIZE (gnu_type), align_cap) >= 0)
759 align = ceil_alignment (tree_low_cst (TYPE_SIZE (gnu_type), 1));
761 /* But make sure not to under-align the object. */
762 if (align <= TYPE_ALIGN (gnu_type))
765 /* And honor the minimum valid atomic alignment, if any. */
766 #ifdef MINIMUM_ATOMIC_ALIGNMENT
767 else if (align < MINIMUM_ATOMIC_ALIGNMENT)
768 align = MINIMUM_ATOMIC_ALIGNMENT;
772 /* If the object is set to have atomic components, find the component
773 type and validate it.
775 ??? Note that we ignore Has_Volatile_Components on objects; it's
776 not at all clear what to do in that case. */
777 if (Has_Atomic_Components (gnat_entity))
779 tree gnu_inner = (TREE_CODE (gnu_type) == ARRAY_TYPE
780 ? TREE_TYPE (gnu_type) : gnu_type);
782 while (TREE_CODE (gnu_inner) == ARRAY_TYPE
783 && TYPE_MULTI_ARRAY_P (gnu_inner))
784 gnu_inner = TREE_TYPE (gnu_inner);
786 check_ok_for_atomic (gnu_inner, gnat_entity, true);
789 /* Now check if the type of the object allows atomic access. Note
790 that we must test the type, even if this object has size and
791 alignment to allow such access, because we will be going inside
792 the padded record to assign to the object. We could fix this by
793 always copying via an intermediate value, but it's not clear it's
795 if (Is_Atomic (gnat_entity))
796 check_ok_for_atomic (gnu_type, gnat_entity, false);
798 /* If this is an aliased object with an unconstrained nominal subtype,
799 make a type that includes the template. */
800 if (Is_Constr_Subt_For_UN_Aliased (Etype (gnat_entity))
801 && Is_Array_Type (Etype (gnat_entity))
802 && !type_annotate_only)
805 = TREE_TYPE (gnat_to_gnu_type (Base_Type (Etype (gnat_entity))));
808 = build_unc_object_type_from_ptr (gnu_fat, gnu_type,
809 concat_name (gnu_entity_name,
813 #ifdef MINIMUM_ATOMIC_ALIGNMENT
814 /* If the size is a constant and no alignment is specified, force
815 the alignment to be the minimum valid atomic alignment. The
816 restriction on constant size avoids problems with variable-size
817 temporaries; if the size is variable, there's no issue with
818 atomic access. Also don't do this for a constant, since it isn't
819 necessary and can interfere with constant replacement. Finally,
820 do not do it for Out parameters since that creates an
821 size inconsistency with In parameters. */
822 if (align == 0 && MINIMUM_ATOMIC_ALIGNMENT > TYPE_ALIGN (gnu_type)
823 && !FLOAT_TYPE_P (gnu_type)
824 && !const_flag && No (Renamed_Object (gnat_entity))
825 && !imported_p && No (Address_Clause (gnat_entity))
826 && kind != E_Out_Parameter
827 && (gnu_size ? TREE_CODE (gnu_size) == INTEGER_CST
828 : TREE_CODE (TYPE_SIZE (gnu_type)) == INTEGER_CST))
829 align = MINIMUM_ATOMIC_ALIGNMENT;
832 /* Make a new type with the desired size and alignment, if needed.
833 But do not take into account alignment promotions to compute the
834 size of the object. */
835 gnu_object_size = gnu_size ? gnu_size : TYPE_SIZE (gnu_type);
836 if (gnu_size || align > 0)
837 gnu_type = maybe_pad_type (gnu_type, gnu_size, align, gnat_entity,
838 false, false, definition,
839 gnu_size ? true : false);
841 /* If this is a renaming, avoid as much as possible to create a new
842 object. However, in several cases, creating it is required.
843 This processing needs to be applied to the raw expression so
844 as to make it more likely to rename the underlying object. */
845 if (Present (Renamed_Object (gnat_entity)))
847 bool create_normal_object = false;
849 /* If the renamed object had padding, strip off the reference
850 to the inner object and reset our type. */
851 if ((TREE_CODE (gnu_expr) == COMPONENT_REF
852 && TYPE_IS_PADDING_P (TREE_TYPE (TREE_OPERAND (gnu_expr, 0))))
853 /* Strip useless conversions around the object. */
854 || (TREE_CODE (gnu_expr) == NOP_EXPR
855 && gnat_types_compatible_p
856 (TREE_TYPE (gnu_expr),
857 TREE_TYPE (TREE_OPERAND (gnu_expr, 0)))))
859 gnu_expr = TREE_OPERAND (gnu_expr, 0);
860 gnu_type = TREE_TYPE (gnu_expr);
863 /* Case 1: If this is a constant renaming stemming from a function
864 call, treat it as a normal object whose initial value is what
865 is being renamed. RM 3.3 says that the result of evaluating a
866 function call is a constant object. As a consequence, it can
867 be the inner object of a constant renaming. In this case, the
868 renaming must be fully instantiated, i.e. it cannot be a mere
869 reference to (part of) an existing object. */
872 tree inner_object = gnu_expr;
873 while (handled_component_p (inner_object))
874 inner_object = TREE_OPERAND (inner_object, 0);
875 if (TREE_CODE (inner_object) == CALL_EXPR)
876 create_normal_object = true;
879 /* Otherwise, see if we can proceed with a stabilized version of
880 the renamed entity or if we need to make a new object. */
881 if (!create_normal_object)
883 tree maybe_stable_expr = NULL_TREE;
886 /* Case 2: If the renaming entity need not be materialized and
887 the renamed expression is something we can stabilize, use
888 that for the renaming. At the global level, we can only do
889 this if we know no SAVE_EXPRs need be made, because the
890 expression we return might be used in arbitrary conditional
891 branches so we must force the SAVE_EXPRs evaluation
892 immediately and this requires a function context. */
893 if (!Materialize_Entity (gnat_entity)
894 && (!global_bindings_p ()
895 || (staticp (gnu_expr)
896 && !TREE_SIDE_EFFECTS (gnu_expr))))
899 = gnat_stabilize_reference (gnu_expr, true, &stable);
903 /* ??? No DECL_EXPR is created so we need to mark
904 the expression manually lest it is shared. */
905 if (global_bindings_p ())
906 MARK_VISITED (maybe_stable_expr);
907 gnu_decl = maybe_stable_expr;
908 save_gnu_tree (gnat_entity, gnu_decl, true);
910 annotate_object (gnat_entity, gnu_type, NULL_TREE,
915 /* The stabilization failed. Keep maybe_stable_expr
916 untouched here to let the pointer case below know
917 about that failure. */
920 /* Case 3: If this is a constant renaming and creating a
921 new object is allowed and cheap, treat it as a normal
922 object whose initial value is what is being renamed. */
924 && !Is_Composite_Type
925 (Underlying_Type (Etype (gnat_entity))))
928 /* Case 4: Make this into a constant pointer to the object we
929 are to rename and attach the object to the pointer if it is
930 something we can stabilize.
932 From the proper scope, attached objects will be referenced
933 directly instead of indirectly via the pointer to avoid
934 subtle aliasing problems with non-addressable entities.
935 They have to be stable because we must not evaluate the
936 variables in the expression every time the renaming is used.
937 The pointer is called a "renaming" pointer in this case.
939 In the rare cases where we cannot stabilize the renamed
940 object, we just make a "bare" pointer, and the renamed
941 entity is always accessed indirectly through it. */
944 gnu_type = build_reference_type (gnu_type);
945 inner_const_flag = TREE_READONLY (gnu_expr);
948 /* If the previous attempt at stabilizing failed, there
949 is no point in trying again and we reuse the result
950 without attaching it to the pointer. In this case it
951 will only be used as the initializing expression of
952 the pointer and thus needs no special treatment with
953 regard to multiple evaluations. */
954 if (maybe_stable_expr)
957 /* Otherwise, try to stabilize and attach the expression
958 to the pointer if the stabilization succeeds.
960 Note that this might introduce SAVE_EXPRs and we don't
961 check whether we're at the global level or not. This
962 is fine since we are building a pointer initializer and
963 neither the pointer nor the initializing expression can
964 be accessed before the pointer elaboration has taken
965 place in a correct program.
967 These SAVE_EXPRs will be evaluated at the right place
968 by either the evaluation of the initializer for the
969 non-global case or the elaboration code for the global
970 case, and will be attached to the elaboration procedure
971 in the latter case. */
975 = gnat_stabilize_reference (gnu_expr, true, &stable);
978 renamed_obj = maybe_stable_expr;
980 /* Attaching is actually performed downstream, as soon
981 as we have a VAR_DECL for the pointer we make. */
984 gnu_expr = build_unary_op (ADDR_EXPR, gnu_type,
987 gnu_size = NULL_TREE;
993 /* Make a volatile version of this object's type if we are to make
994 the object volatile. We also interpret 13.3(19) conservatively
995 and disallow any optimizations for such a non-constant object. */
996 if ((Treat_As_Volatile (gnat_entity)
998 && (Is_Exported (gnat_entity)
999 || Is_Imported (gnat_entity)
1000 || Present (Address_Clause (gnat_entity)))))
1001 && !TYPE_VOLATILE (gnu_type))
1002 gnu_type = build_qualified_type (gnu_type,
1003 (TYPE_QUALS (gnu_type)
1004 | TYPE_QUAL_VOLATILE));
1006 /* If we are defining an aliased object whose nominal subtype is
1007 unconstrained, the object is a record that contains both the
1008 template and the object. If there is an initializer, it will
1009 have already been converted to the right type, but we need to
1010 create the template if there is no initializer. */
1013 && TREE_CODE (gnu_type) == RECORD_TYPE
1014 && (TYPE_CONTAINS_TEMPLATE_P (gnu_type)
1015 /* Beware that padding might have been introduced above. */
1016 || (TYPE_PADDING_P (gnu_type)
1017 && TREE_CODE (TREE_TYPE (TYPE_FIELDS (gnu_type)))
1019 && TYPE_CONTAINS_TEMPLATE_P
1020 (TREE_TYPE (TYPE_FIELDS (gnu_type))))))
1023 = TYPE_PADDING_P (gnu_type)
1024 ? TYPE_FIELDS (TREE_TYPE (TYPE_FIELDS (gnu_type)))
1025 : TYPE_FIELDS (gnu_type);
1027 = gnat_build_constructor
1031 build_template (TREE_TYPE (template_field),
1032 TREE_TYPE (TREE_CHAIN (template_field)),
1037 /* Convert the expression to the type of the object except in the
1038 case where the object's type is unconstrained or the object's type
1039 is a padded record whose field is of self-referential size. In
1040 the former case, converting will generate unnecessary evaluations
1041 of the CONSTRUCTOR to compute the size and in the latter case, we
1042 want to only copy the actual data. */
1044 && TREE_CODE (gnu_type) != UNCONSTRAINED_ARRAY_TYPE
1045 && !CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type))
1046 && !(TYPE_IS_PADDING_P (gnu_type)
1047 && CONTAINS_PLACEHOLDER_P
1048 (TYPE_SIZE (TREE_TYPE (TYPE_FIELDS (gnu_type))))))
1049 gnu_expr = convert (gnu_type, gnu_expr);
1051 /* If this is a pointer that doesn't have an initializing expression,
1052 initialize it to NULL, unless the object is imported. */
1054 && (POINTER_TYPE_P (gnu_type) || TYPE_IS_FAT_POINTER_P (gnu_type))
1056 && !Is_Imported (gnat_entity))
1057 gnu_expr = integer_zero_node;
1059 /* If we are defining the object and it has an Address clause, we must
1060 either get the address expression from the saved GCC tree for the
1061 object if it has a Freeze node, or elaborate the address expression
1062 here since the front-end has guaranteed that the elaboration has no
1063 effects in this case. */
1064 if (definition && Present (Address_Clause (gnat_entity)))
1066 Node_Id gnat_expr = Expression (Address_Clause (gnat_entity));
1068 = present_gnu_tree (gnat_entity)
1069 ? get_gnu_tree (gnat_entity) : gnat_to_gnu (gnat_expr);
1071 save_gnu_tree (gnat_entity, NULL_TREE, false);
1073 /* Ignore the size. It's either meaningless or was handled
1075 gnu_size = NULL_TREE;
1076 /* Convert the type of the object to a reference type that can
1077 alias everything as per 13.3(19). */
1079 = build_reference_type_for_mode (gnu_type, ptr_mode, true);
1080 gnu_address = convert (gnu_type, gnu_address);
1083 = !Is_Public (gnat_entity)
1084 || compile_time_known_address_p (gnat_expr);
1086 /* If this is a deferred constant, the initializer is attached to
1088 if (kind == E_Constant && Present (Full_View (gnat_entity)))
1091 (Expression (Declaration_Node (Full_View (gnat_entity))));
1093 /* If we don't have an initializing expression for the underlying
1094 variable, the initializing expression for the pointer is the
1095 specified address. Otherwise, we have to make a COMPOUND_EXPR
1096 to assign both the address and the initial value. */
1098 gnu_expr = gnu_address;
1101 = build2 (COMPOUND_EXPR, gnu_type,
1103 (MODIFY_EXPR, NULL_TREE,
1104 build_unary_op (INDIRECT_REF, NULL_TREE,
1110 /* If it has an address clause and we are not defining it, mark it
1111 as an indirect object. Likewise for Stdcall objects that are
1113 if ((!definition && Present (Address_Clause (gnat_entity)))
1114 || (Is_Imported (gnat_entity)
1115 && Has_Stdcall_Convention (gnat_entity)))
1117 /* Convert the type of the object to a reference type that can
1118 alias everything as per 13.3(19). */
1120 = build_reference_type_for_mode (gnu_type, ptr_mode, true);
1121 gnu_size = NULL_TREE;
1123 /* No point in taking the address of an initializing expression
1124 that isn't going to be used. */
1125 gnu_expr = NULL_TREE;
1127 /* If it has an address clause whose value is known at compile
1128 time, make the object a CONST_DECL. This will avoid a
1129 useless dereference. */
1130 if (Present (Address_Clause (gnat_entity)))
1132 Node_Id gnat_address
1133 = Expression (Address_Clause (gnat_entity));
1135 if (compile_time_known_address_p (gnat_address))
1137 gnu_expr = gnat_to_gnu (gnat_address);
1145 /* If we are at top level and this object is of variable size,
1146 make the actual type a hidden pointer to the real type and
1147 make the initializer be a memory allocation and initialization.
1148 Likewise for objects we aren't defining (presumed to be
1149 external references from other packages), but there we do
1150 not set up an initialization.
1152 If the object's size overflows, make an allocator too, so that
1153 Storage_Error gets raised. Note that we will never free
1154 such memory, so we presume it never will get allocated. */
1155 if (!allocatable_size_p (TYPE_SIZE_UNIT (gnu_type),
1156 global_bindings_p ()
1159 || (gnu_size && !allocatable_size_p (gnu_size,
1160 global_bindings_p ()
1164 gnu_type = build_reference_type (gnu_type);
1165 gnu_size = NULL_TREE;
1169 /* In case this was a aliased object whose nominal subtype is
1170 unconstrained, the pointer above will be a thin pointer and
1171 build_allocator will automatically make the template.
1173 If we have a template initializer only (that we made above),
1174 pretend there is none and rely on what build_allocator creates
1175 again anyway. Otherwise (if we have a full initializer), get
1176 the data part and feed that to build_allocator.
1178 If we are elaborating a mutable object, tell build_allocator to
1179 ignore a possibly simpler size from the initializer, if any, as
1180 we must allocate the maximum possible size in this case. */
1183 tree gnu_alloc_type = TREE_TYPE (gnu_type);
1185 if (TREE_CODE (gnu_alloc_type) == RECORD_TYPE
1186 && TYPE_CONTAINS_TEMPLATE_P (gnu_alloc_type))
1189 = TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (gnu_alloc_type)));
1191 if (TREE_CODE (gnu_expr) == CONSTRUCTOR
1192 && 1 == VEC_length (constructor_elt,
1193 CONSTRUCTOR_ELTS (gnu_expr)))
1197 = build_component_ref
1198 (gnu_expr, NULL_TREE,
1199 TREE_CHAIN (TYPE_FIELDS (TREE_TYPE (gnu_expr))),
1203 if (TREE_CODE (TYPE_SIZE_UNIT (gnu_alloc_type)) == INTEGER_CST
1204 && TREE_OVERFLOW (TYPE_SIZE_UNIT (gnu_alloc_type))
1205 && !Is_Imported (gnat_entity))
1206 post_error ("?Storage_Error will be raised at run-time!",
1210 = build_allocator (gnu_alloc_type, gnu_expr, gnu_type,
1211 Empty, Empty, gnat_entity, mutable_p);
1215 gnu_expr = NULL_TREE;
1220 /* If this object would go into the stack and has an alignment larger
1221 than the largest stack alignment the back-end can honor, resort to
1222 a variable of "aligning type". */
1223 if (!global_bindings_p () && !static_p && definition
1224 && !imported_p && TYPE_ALIGN (gnu_type) > BIGGEST_ALIGNMENT)
1226 /* Create the new variable. No need for extra room before the
1227 aligned field as this is in automatic storage. */
1229 = make_aligning_type (gnu_type, TYPE_ALIGN (gnu_type),
1230 TYPE_SIZE_UNIT (gnu_type),
1231 BIGGEST_ALIGNMENT, 0);
1233 = create_var_decl (create_concat_name (gnat_entity, "ALIGN"),
1234 NULL_TREE, gnu_new_type, NULL_TREE, false,
1235 false, false, false, NULL, gnat_entity);
1237 /* Initialize the aligned field if we have an initializer. */
1240 (build_binary_op (MODIFY_EXPR, NULL_TREE,
1242 (gnu_new_var, NULL_TREE,
1243 TYPE_FIELDS (gnu_new_type), false),
1247 /* And setup this entity as a reference to the aligned field. */
1248 gnu_type = build_reference_type (gnu_type);
1251 (ADDR_EXPR, gnu_type,
1252 build_component_ref (gnu_new_var, NULL_TREE,
1253 TYPE_FIELDS (gnu_new_type), false));
1255 gnu_size = NULL_TREE;
1261 gnu_type = build_qualified_type (gnu_type, (TYPE_QUALS (gnu_type)
1262 | TYPE_QUAL_CONST));
1264 /* Convert the expression to the type of the object except in the
1265 case where the object's type is unconstrained or the object's type
1266 is a padded record whose field is of self-referential size. In
1267 the former case, converting will generate unnecessary evaluations
1268 of the CONSTRUCTOR to compute the size and in the latter case, we
1269 want to only copy the actual data. */
1271 && TREE_CODE (gnu_type) != UNCONSTRAINED_ARRAY_TYPE
1272 && !CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type))
1273 && !(TYPE_IS_PADDING_P (gnu_type)
1274 && CONTAINS_PLACEHOLDER_P
1275 (TYPE_SIZE (TREE_TYPE (TYPE_FIELDS (gnu_type))))))
1276 gnu_expr = convert (gnu_type, gnu_expr);
1278 /* If this name is external or there was a name specified, use it,
1279 unless this is a VMS exception object since this would conflict
1280 with the symbol we need to export in addition. Don't use the
1281 Interface_Name if there is an address clause (see CD30005). */
1282 if (!Is_VMS_Exception (gnat_entity)
1283 && ((Present (Interface_Name (gnat_entity))
1284 && No (Address_Clause (gnat_entity)))
1285 || (Is_Public (gnat_entity)
1286 && (!Is_Imported (gnat_entity)
1287 || Is_Exported (gnat_entity)))))
1288 gnu_ext_name = create_concat_name (gnat_entity, NULL);
1290 /* If this is an aggregate constant initialized to a constant, force it
1291 to be statically allocated. This saves an initialization copy. */
1294 && gnu_expr && TREE_CONSTANT (gnu_expr)
1295 && AGGREGATE_TYPE_P (gnu_type)
1296 && host_integerp (TYPE_SIZE_UNIT (gnu_type), 1)
1297 && !(TYPE_IS_PADDING_P (gnu_type)
1298 && !host_integerp (TYPE_SIZE_UNIT
1299 (TREE_TYPE (TYPE_FIELDS (gnu_type))), 1)))
1302 /* Now create the variable or the constant and set various flags. */
1304 = create_var_decl (gnu_entity_name, gnu_ext_name, gnu_type,
1305 gnu_expr, const_flag, Is_Public (gnat_entity),
1306 imported_p || !definition, static_p, attr_list,
1308 DECL_BY_REF_P (gnu_decl) = used_by_ref;
1309 DECL_POINTS_TO_READONLY_P (gnu_decl) = used_by_ref && inner_const_flag;
1311 /* If we are defining an Out parameter and optimization isn't enabled,
1312 create a fake PARM_DECL for debugging purposes and make it point to
1313 the VAR_DECL. Suppress debug info for the latter but make sure it
1314 will live on the stack so that it can be accessed from within the
1315 debugger through the PARM_DECL. */
1316 if (kind == E_Out_Parameter && definition && !optimize && debug_info_p)
1318 tree param = create_param_decl (gnu_entity_name, gnu_type, false);
1319 gnat_pushdecl (param, gnat_entity);
1320 SET_DECL_VALUE_EXPR (param, gnu_decl);
1321 DECL_HAS_VALUE_EXPR_P (param) = 1;
1322 DECL_IGNORED_P (gnu_decl) = 1;
1323 TREE_ADDRESSABLE (gnu_decl) = 1;
1326 /* If this is a renaming pointer, attach the renamed object to it and
1327 register it if we are at top level. */
1328 if (TREE_CODE (gnu_decl) == VAR_DECL && renamed_obj)
1330 SET_DECL_RENAMED_OBJECT (gnu_decl, renamed_obj);
1331 if (global_bindings_p ())
1333 DECL_RENAMING_GLOBAL_P (gnu_decl) = 1;
1334 record_global_renaming_pointer (gnu_decl);
1338 /* If this is a constant and we are defining it or it generates a real
1339 symbol at the object level and we are referencing it, we may want
1340 or need to have a true variable to represent it:
1341 - if optimization isn't enabled, for debugging purposes,
1342 - if the constant is public and not overlaid on something else,
1343 - if its address is taken,
1344 - if either itself or its type is aliased. */
1345 if (TREE_CODE (gnu_decl) == CONST_DECL
1346 && (definition || Sloc (gnat_entity) > Standard_Location)
1347 && ((!optimize && debug_info_p)
1348 || (Is_Public (gnat_entity)
1349 && No (Address_Clause (gnat_entity)))
1350 || Address_Taken (gnat_entity)
1351 || Is_Aliased (gnat_entity)
1352 || Is_Aliased (Etype (gnat_entity))))
1355 = create_true_var_decl (gnu_entity_name, gnu_ext_name, gnu_type,
1356 gnu_expr, true, Is_Public (gnat_entity),
1357 !definition, static_p, attr_list,
1360 SET_DECL_CONST_CORRESPONDING_VAR (gnu_decl, gnu_corr_var);
1362 /* As debugging information will be generated for the variable,
1363 do not generate debugging information for the constant. */
1365 DECL_IGNORED_P (gnu_decl) = 1;
1367 DECL_IGNORED_P (gnu_corr_var) = 1;
1370 /* If this is a constant, even if we don't need a true variable, we
1371 may need to avoid returning the initializer in every case. That
1372 can happen for the address of a (constant) constructor because,
1373 upon dereferencing it, the constructor will be reinjected in the
1374 tree, which may not be valid in every case; see lvalue_required_p
1375 for more details. */
1376 if (TREE_CODE (gnu_decl) == CONST_DECL)
1377 DECL_CONST_ADDRESS_P (gnu_decl) = constructor_address_p (gnu_expr);
1379 /* If this object is declared in a block that contains a block with an
1380 exception handler, and we aren't using the GCC exception mechanism,
1381 we must force this variable in memory in order to avoid an invalid
1383 if (Exception_Mechanism != Back_End_Exceptions
1384 && Has_Nested_Block_With_Handler (Scope (gnat_entity)))
1385 TREE_ADDRESSABLE (gnu_decl) = 1;
1387 /* If we are defining an object with variable size or an object with
1388 fixed size that will be dynamically allocated, and we are using the
1389 setjmp/longjmp exception mechanism, update the setjmp buffer. */
1391 && Exception_Mechanism == Setjmp_Longjmp
1392 && get_block_jmpbuf_decl ()
1393 && DECL_SIZE_UNIT (gnu_decl)
1394 && (TREE_CODE (DECL_SIZE_UNIT (gnu_decl)) != INTEGER_CST
1395 || (flag_stack_check == GENERIC_STACK_CHECK
1396 && compare_tree_int (DECL_SIZE_UNIT (gnu_decl),
1397 STACK_CHECK_MAX_VAR_SIZE) > 0)))
1398 add_stmt_with_node (build_call_1_expr
1399 (update_setjmp_buf_decl,
1400 build_unary_op (ADDR_EXPR, NULL_TREE,
1401 get_block_jmpbuf_decl ())),
1404 /* Back-annotate Esize and Alignment of the object if not already
1405 known. Note that we pick the values of the type, not those of
1406 the object, to shield ourselves from low-level platform-dependent
1407 adjustments like alignment promotion. This is both consistent with
1408 all the treatment above, where alignment and size are set on the
1409 type of the object and not on the object directly, and makes it
1410 possible to support all confirming representation clauses. */
1411 annotate_object (gnat_entity, TREE_TYPE (gnu_decl), gnu_object_size,
1417 /* Return a TYPE_DECL for "void" that we previously made. */
1418 gnu_decl = TYPE_NAME (void_type_node);
1421 case E_Enumeration_Type:
1422 /* A special case: for the types Character and Wide_Character in
1423 Standard, we do not list all the literals. So if the literals
1424 are not specified, make this an unsigned type. */
1425 if (No (First_Literal (gnat_entity)))
1427 gnu_type = make_unsigned_type (esize);
1428 TYPE_NAME (gnu_type) = gnu_entity_name;
1430 /* Set TYPE_STRING_FLAG for Character and Wide_Character types.
1431 This is needed by the DWARF-2 back-end to distinguish between
1432 unsigned integer types and character types. */
1433 TYPE_STRING_FLAG (gnu_type) = 1;
1438 /* We have a list of enumeral constants in First_Literal. We make a
1439 CONST_DECL for each one and build into GNU_LITERAL_LIST the list to
1440 be placed into TYPE_FIELDS. Each node in the list is a TREE_LIST
1441 whose TREE_VALUE is the literal name and whose TREE_PURPOSE is the
1442 value of the literal. But when we have a regular boolean type, we
1443 simplify this a little by using a BOOLEAN_TYPE. */
1444 bool is_boolean = Is_Boolean_Type (gnat_entity)
1445 && !Has_Non_Standard_Rep (gnat_entity);
1446 tree gnu_literal_list = NULL_TREE;
1447 Entity_Id gnat_literal;
1449 if (Is_Unsigned_Type (gnat_entity))
1450 gnu_type = make_unsigned_type (esize);
1452 gnu_type = make_signed_type (esize);
1454 TREE_SET_CODE (gnu_type, is_boolean ? BOOLEAN_TYPE : ENUMERAL_TYPE);
1456 for (gnat_literal = First_Literal (gnat_entity);
1457 Present (gnat_literal);
1458 gnat_literal = Next_Literal (gnat_literal))
1461 = UI_To_gnu (Enumeration_Rep (gnat_literal), gnu_type);
1463 = create_var_decl (get_entity_name (gnat_literal), NULL_TREE,
1464 gnu_type, gnu_value, true, false, false,
1465 false, NULL, gnat_literal);
1467 save_gnu_tree (gnat_literal, gnu_literal, false);
1468 gnu_literal_list = tree_cons (DECL_NAME (gnu_literal),
1469 gnu_value, gnu_literal_list);
1473 TYPE_VALUES (gnu_type) = nreverse (gnu_literal_list);
1475 /* Note that the bounds are updated at the end of this function
1476 to avoid an infinite recursion since they refer to the type. */
1480 case E_Signed_Integer_Type:
1481 case E_Ordinary_Fixed_Point_Type:
1482 case E_Decimal_Fixed_Point_Type:
1483 /* For integer types, just make a signed type the appropriate number
1485 gnu_type = make_signed_type (esize);
1488 case E_Modular_Integer_Type:
1490 /* For modular types, make the unsigned type of the proper number
1491 of bits and then set up the modulus, if required. */
1492 tree gnu_modulus, gnu_high = NULL_TREE;
1494 /* Packed array types are supposed to be subtypes only. */
1495 gcc_assert (!Is_Packed_Array_Type (gnat_entity));
1497 gnu_type = make_unsigned_type (esize);
1499 /* Get the modulus in this type. If it overflows, assume it is because
1500 it is equal to 2**Esize. Note that there is no overflow checking
1501 done on unsigned type, so we detect the overflow by looking for
1502 a modulus of zero, which is otherwise invalid. */
1503 gnu_modulus = UI_To_gnu (Modulus (gnat_entity), gnu_type);
1505 if (!integer_zerop (gnu_modulus))
1507 TYPE_MODULAR_P (gnu_type) = 1;
1508 SET_TYPE_MODULUS (gnu_type, gnu_modulus);
1509 gnu_high = fold_build2 (MINUS_EXPR, gnu_type, gnu_modulus,
1510 convert (gnu_type, integer_one_node));
1513 /* If the upper bound is not maximal, make an extra subtype. */
1515 && !tree_int_cst_equal (gnu_high, TYPE_MAX_VALUE (gnu_type)))
1517 tree gnu_subtype = make_unsigned_type (esize);
1518 SET_TYPE_RM_MAX_VALUE (gnu_subtype, gnu_high);
1519 TREE_TYPE (gnu_subtype) = gnu_type;
1520 TYPE_EXTRA_SUBTYPE_P (gnu_subtype) = 1;
1521 TYPE_NAME (gnu_type) = create_concat_name (gnat_entity, "UMT");
1522 gnu_type = gnu_subtype;
1527 case E_Signed_Integer_Subtype:
1528 case E_Enumeration_Subtype:
1529 case E_Modular_Integer_Subtype:
1530 case E_Ordinary_Fixed_Point_Subtype:
1531 case E_Decimal_Fixed_Point_Subtype:
1533 /* For integral subtypes, we make a new INTEGER_TYPE. Note that we do
1534 not want to call create_range_type since we would like each subtype
1535 node to be distinct. ??? Historically this was in preparation for
1536 when memory aliasing is implemented, but that's obsolete now given
1537 the call to relate_alias_sets below.
1539 The TREE_TYPE field of the INTEGER_TYPE points to the base type;
1540 this fact is used by the arithmetic conversion functions.
1542 We elaborate the Ancestor_Subtype if it is not in the current unit
1543 and one of our bounds is non-static. We do this to ensure consistent
1544 naming in the case where several subtypes share the same bounds, by
1545 elaborating the first such subtype first, thus using its name. */
1548 && Present (Ancestor_Subtype (gnat_entity))
1549 && !In_Extended_Main_Code_Unit (Ancestor_Subtype (gnat_entity))
1550 && (!Compile_Time_Known_Value (Type_Low_Bound (gnat_entity))
1551 || !Compile_Time_Known_Value (Type_High_Bound (gnat_entity))))
1552 gnat_to_gnu_entity (Ancestor_Subtype (gnat_entity), gnu_expr, 0);
1554 /* Set the precision to the Esize except for bit-packed arrays. */
1555 if (Is_Packed_Array_Type (gnat_entity)
1556 && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)))
1557 esize = UI_To_Int (RM_Size (gnat_entity));
1559 /* This should be an unsigned type if the base type is unsigned or
1560 if the lower bound is constant and non-negative or if the type
1562 if (Is_Unsigned_Type (Etype (gnat_entity))
1563 || Is_Unsigned_Type (gnat_entity)
1564 || Has_Biased_Representation (gnat_entity))
1565 gnu_type = make_unsigned_type (esize);
1567 gnu_type = make_signed_type (esize);
1568 TREE_TYPE (gnu_type) = get_unpadded_type (Etype (gnat_entity));
1570 SET_TYPE_RM_MIN_VALUE
1572 convert (TREE_TYPE (gnu_type),
1573 elaborate_expression (Type_Low_Bound (gnat_entity),
1574 gnat_entity, get_identifier ("L"),
1576 Needs_Debug_Info (gnat_entity))));
1578 SET_TYPE_RM_MAX_VALUE
1580 convert (TREE_TYPE (gnu_type),
1581 elaborate_expression (Type_High_Bound (gnat_entity),
1582 gnat_entity, get_identifier ("U"),
1584 Needs_Debug_Info (gnat_entity))));
1586 /* One of the above calls might have caused us to be elaborated,
1587 so don't blow up if so. */
1588 if (present_gnu_tree (gnat_entity))
1590 maybe_present = true;
1594 TYPE_BIASED_REPRESENTATION_P (gnu_type)
1595 = Has_Biased_Representation (gnat_entity);
1597 /* Attach the TYPE_STUB_DECL in case we have a parallel type. */
1598 TYPE_STUB_DECL (gnu_type)
1599 = create_type_stub_decl (gnu_entity_name, gnu_type);
1601 /* Inherit our alias set from what we're a subtype of. Subtypes
1602 are not different types and a pointer can designate any instance
1603 within a subtype hierarchy. */
1604 relate_alias_sets (gnu_type, TREE_TYPE (gnu_type), ALIAS_SET_COPY);
1606 /* For a packed array, make the original array type a parallel type. */
1608 && Is_Packed_Array_Type (gnat_entity)
1609 && present_gnu_tree (Original_Array_Type (gnat_entity)))
1610 add_parallel_type (TYPE_STUB_DECL (gnu_type),
1612 (Original_Array_Type (gnat_entity)));
1614 /* We have to handle clauses that under-align the type specially. */
1615 if ((Present (Alignment_Clause (gnat_entity))
1616 || (Is_Packed_Array_Type (gnat_entity)
1618 (Alignment_Clause (Original_Array_Type (gnat_entity)))))
1619 && UI_Is_In_Int_Range (Alignment (gnat_entity)))
1621 align = UI_To_Int (Alignment (gnat_entity)) * BITS_PER_UNIT;
1622 if (align >= TYPE_ALIGN (gnu_type))
1626 /* If the type we are dealing with represents a bit-packed array,
1627 we need to have the bits left justified on big-endian targets
1628 and right justified on little-endian targets. We also need to
1629 ensure that when the value is read (e.g. for comparison of two
1630 such values), we only get the good bits, since the unused bits
1631 are uninitialized. Both goals are accomplished by wrapping up
1632 the modular type in an enclosing record type. */
1633 if (Is_Packed_Array_Type (gnat_entity)
1634 && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)))
1636 tree gnu_field_type, gnu_field;
1638 /* Set the RM size before wrapping up the original type. */
1639 SET_TYPE_RM_SIZE (gnu_type,
1640 UI_To_gnu (RM_Size (gnat_entity), bitsizetype));
1641 TYPE_PACKED_ARRAY_TYPE_P (gnu_type) = 1;
1643 /* Create a stripped-down declaration, mainly for debugging. */
1644 create_type_decl (gnu_entity_name, gnu_type, NULL, true,
1645 debug_info_p, gnat_entity);
1647 /* Now save it and build the enclosing record type. */
1648 gnu_field_type = gnu_type;
1650 gnu_type = make_node (RECORD_TYPE);
1651 TYPE_NAME (gnu_type) = create_concat_name (gnat_entity, "JM");
1652 TYPE_PACKED (gnu_type) = 1;
1653 TYPE_SIZE (gnu_type) = TYPE_SIZE (gnu_field_type);
1654 TYPE_SIZE_UNIT (gnu_type) = TYPE_SIZE_UNIT (gnu_field_type);
1655 SET_TYPE_ADA_SIZE (gnu_type, TYPE_RM_SIZE (gnu_field_type));
1657 /* Propagate the alignment of the modular type to the record type,
1658 unless there is an alignment clause that under-aligns the type.
1659 This means that bit-packed arrays are given "ceil" alignment for
1660 their size by default, which may seem counter-intuitive but makes
1661 it possible to overlay them on modular types easily. */
1662 TYPE_ALIGN (gnu_type)
1663 = align > 0 ? align : TYPE_ALIGN (gnu_field_type);
1665 relate_alias_sets (gnu_type, gnu_field_type, ALIAS_SET_COPY);
1667 /* Don't notify the field as "addressable", since we won't be taking
1668 it's address and it would prevent create_field_decl from making a
1670 gnu_field = create_field_decl (get_identifier ("OBJECT"),
1671 gnu_field_type, gnu_type, 1,
1672 NULL_TREE, bitsize_zero_node, 0);
1674 /* Do not emit debug info until after the parallel type is added. */
1675 finish_record_type (gnu_type, gnu_field, 2, false);
1676 compute_record_mode (gnu_type);
1677 TYPE_JUSTIFIED_MODULAR_P (gnu_type) = 1;
1681 /* Make the original array type a parallel type. */
1682 if (present_gnu_tree (Original_Array_Type (gnat_entity)))
1683 add_parallel_type (TYPE_STUB_DECL (gnu_type),
1685 (Original_Array_Type (gnat_entity)));
1687 rest_of_record_type_compilation (gnu_type);
1691 /* If the type we are dealing with has got a smaller alignment than the
1692 natural one, we need to wrap it up in a record type and under-align
1693 the latter. We reuse the padding machinery for this purpose. */
1696 tree gnu_field_type, gnu_field;
1698 /* Set the RM size before wrapping up the type. */
1699 SET_TYPE_RM_SIZE (gnu_type,
1700 UI_To_gnu (RM_Size (gnat_entity), bitsizetype));
1702 /* Create a stripped-down declaration, mainly for debugging. */
1703 create_type_decl (gnu_entity_name, gnu_type, NULL, true,
1704 debug_info_p, gnat_entity);
1706 /* Now save it and build the enclosing record type. */
1707 gnu_field_type = gnu_type;
1709 gnu_type = make_node (RECORD_TYPE);
1710 TYPE_NAME (gnu_type) = create_concat_name (gnat_entity, "PAD");
1711 TYPE_PACKED (gnu_type) = 1;
1712 TYPE_SIZE (gnu_type) = TYPE_SIZE (gnu_field_type);
1713 TYPE_SIZE_UNIT (gnu_type) = TYPE_SIZE_UNIT (gnu_field_type);
1714 SET_TYPE_ADA_SIZE (gnu_type, TYPE_RM_SIZE (gnu_field_type));
1715 TYPE_ALIGN (gnu_type) = align;
1716 relate_alias_sets (gnu_type, gnu_field_type, ALIAS_SET_COPY);
1718 /* Don't notify the field as "addressable", since we won't be taking
1719 it's address and it would prevent create_field_decl from making a
1721 gnu_field = create_field_decl (get_identifier ("F"),
1722 gnu_field_type, gnu_type, 1,
1723 NULL_TREE, bitsize_zero_node, 0);
1725 finish_record_type (gnu_type, gnu_field, 2, debug_info_p);
1726 compute_record_mode (gnu_type);
1727 TYPE_PADDING_P (gnu_type) = 1;
1732 case E_Floating_Point_Type:
1733 /* If this is a VAX floating-point type, use an integer of the proper
1734 size. All the operations will be handled with ASM statements. */
1735 if (Vax_Float (gnat_entity))
1737 gnu_type = make_signed_type (esize);
1738 TYPE_VAX_FLOATING_POINT_P (gnu_type) = 1;
1739 SET_TYPE_DIGITS_VALUE (gnu_type,
1740 UI_To_gnu (Digits_Value (gnat_entity),
1745 /* The type of the Low and High bounds can be our type if this is
1746 a type from Standard, so set them at the end of the function. */
1747 gnu_type = make_node (REAL_TYPE);
1748 TYPE_PRECISION (gnu_type) = fp_size_to_prec (esize);
1749 layout_type (gnu_type);
1752 case E_Floating_Point_Subtype:
1753 if (Vax_Float (gnat_entity))
1755 gnu_type = gnat_to_gnu_type (Etype (gnat_entity));
1761 && Present (Ancestor_Subtype (gnat_entity))
1762 && !In_Extended_Main_Code_Unit (Ancestor_Subtype (gnat_entity))
1763 && (!Compile_Time_Known_Value (Type_Low_Bound (gnat_entity))
1764 || !Compile_Time_Known_Value (Type_High_Bound (gnat_entity))))
1765 gnat_to_gnu_entity (Ancestor_Subtype (gnat_entity),
1768 gnu_type = make_node (REAL_TYPE);
1769 TREE_TYPE (gnu_type) = get_unpadded_type (Etype (gnat_entity));
1770 TYPE_PRECISION (gnu_type) = fp_size_to_prec (esize);
1771 TYPE_GCC_MIN_VALUE (gnu_type)
1772 = TYPE_GCC_MIN_VALUE (TREE_TYPE (gnu_type));
1773 TYPE_GCC_MAX_VALUE (gnu_type)
1774 = TYPE_GCC_MAX_VALUE (TREE_TYPE (gnu_type));
1775 layout_type (gnu_type);
1777 SET_TYPE_RM_MIN_VALUE
1779 convert (TREE_TYPE (gnu_type),
1780 elaborate_expression (Type_Low_Bound (gnat_entity),
1781 gnat_entity, get_identifier ("L"),
1783 Needs_Debug_Info (gnat_entity))));
1785 SET_TYPE_RM_MAX_VALUE
1787 convert (TREE_TYPE (gnu_type),
1788 elaborate_expression (Type_High_Bound (gnat_entity),
1789 gnat_entity, get_identifier ("U"),
1791 Needs_Debug_Info (gnat_entity))));
1793 /* One of the above calls might have caused us to be elaborated,
1794 so don't blow up if so. */
1795 if (present_gnu_tree (gnat_entity))
1797 maybe_present = true;
1801 /* Inherit our alias set from what we're a subtype of, as for
1802 integer subtypes. */
1803 relate_alias_sets (gnu_type, TREE_TYPE (gnu_type), ALIAS_SET_COPY);
1807 /* Array and String Types and Subtypes
1809 Unconstrained array types are represented by E_Array_Type and
1810 constrained array types are represented by E_Array_Subtype. There
1811 are no actual objects of an unconstrained array type; all we have
1812 are pointers to that type.
1814 The following fields are defined on array types and subtypes:
1816 Component_Type Component type of the array.
1817 Number_Dimensions Number of dimensions (an int).
1818 First_Index Type of first index. */
1823 Entity_Id gnat_index, gnat_name;
1824 const bool convention_fortran_p
1825 = (Convention (gnat_entity) == Convention_Fortran);
1826 const int ndim = Number_Dimensions (gnat_entity);
1827 tree gnu_template_fields = NULL_TREE;
1828 tree gnu_template_type = make_node (RECORD_TYPE);
1829 tree gnu_template_reference;
1830 tree gnu_ptr_template = build_pointer_type (gnu_template_type);
1831 tree gnu_fat_type = make_node (RECORD_TYPE);
1832 tree *gnu_index_types = (tree *) alloca (ndim * sizeof (tree));
1833 tree *gnu_temp_fields = (tree *) alloca (ndim * sizeof (tree));
1834 tree gnu_max_size = size_one_node, gnu_max_size_unit, tem;
1837 TYPE_NAME (gnu_template_type)
1838 = create_concat_name (gnat_entity, "XUB");
1840 /* Make a node for the array. If we are not defining the array
1841 suppress expanding incomplete types. */
1842 gnu_type = make_node (UNCONSTRAINED_ARRAY_TYPE);
1846 defer_incomplete_level++;
1847 this_deferred = true;
1850 /* Build the fat pointer type. Use a "void *" object instead of
1851 a pointer to the array type since we don't have the array type
1852 yet (it will reference the fat pointer via the bounds). */
1853 tem = chainon (chainon (NULL_TREE,
1854 create_field_decl (get_identifier ("P_ARRAY"),
1857 NULL_TREE, NULL_TREE, 0)),
1858 create_field_decl (get_identifier ("P_BOUNDS"),
1861 NULL_TREE, NULL_TREE, 0));
1863 /* Make sure we can put this into a register. */
1864 TYPE_ALIGN (gnu_fat_type) = MIN (BIGGEST_ALIGNMENT, 2 * POINTER_SIZE);
1866 /* Do not emit debug info for this record type since the types of its
1867 fields are still incomplete at this point. */
1868 finish_record_type (gnu_fat_type, tem, 0, false);
1869 TYPE_FAT_POINTER_P (gnu_fat_type) = 1;
1871 /* Build a reference to the template from a PLACEHOLDER_EXPR that
1872 is the fat pointer. This will be used to access the individual
1873 fields once we build them. */
1874 tem = build3 (COMPONENT_REF, gnu_ptr_template,
1875 build0 (PLACEHOLDER_EXPR, gnu_fat_type),
1876 TREE_CHAIN (TYPE_FIELDS (gnu_fat_type)), NULL_TREE);
1877 gnu_template_reference
1878 = build_unary_op (INDIRECT_REF, gnu_template_type, tem);
1879 TREE_READONLY (gnu_template_reference) = 1;
1881 /* Now create the GCC type for each index and add the fields for that
1882 index to the template. */
1883 for (index = (convention_fortran_p ? ndim - 1 : 0),
1884 gnat_index = First_Index (gnat_entity);
1885 0 <= index && index < ndim;
1886 index += (convention_fortran_p ? - 1 : 1),
1887 gnat_index = Next_Index (gnat_index))
1889 char field_name[16];
1890 tree gnu_index_base_type
1891 = get_unpadded_type (Base_Type (Etype (gnat_index)));
1892 tree gnu_lb_field, gnu_hb_field, gnu_orig_min, gnu_orig_max;
1893 tree gnu_min, gnu_max, gnu_high;
1895 /* Make the FIELD_DECLs for the low and high bounds of this
1896 type and then make extractions of these fields from the
1898 sprintf (field_name, "LB%d", index);
1899 gnu_lb_field = create_field_decl (get_identifier (field_name),
1900 gnu_index_base_type,
1901 gnu_template_type, 0,
1902 NULL_TREE, NULL_TREE, 0);
1903 Sloc_to_locus (Sloc (gnat_entity),
1904 &DECL_SOURCE_LOCATION (gnu_lb_field));
1906 field_name[0] = 'U';
1907 gnu_hb_field = create_field_decl (get_identifier (field_name),
1908 gnu_index_base_type,
1909 gnu_template_type, 0,
1910 NULL_TREE, NULL_TREE, 0);
1911 Sloc_to_locus (Sloc (gnat_entity),
1912 &DECL_SOURCE_LOCATION (gnu_hb_field));
1914 gnu_temp_fields[index] = chainon (gnu_lb_field, gnu_hb_field);
1916 /* We can't use build_component_ref here since the template type
1917 isn't complete yet. */
1918 gnu_orig_min = build3 (COMPONENT_REF, gnu_index_base_type,
1919 gnu_template_reference, gnu_lb_field,
1921 gnu_orig_max = build3 (COMPONENT_REF, gnu_index_base_type,
1922 gnu_template_reference, gnu_hb_field,
1924 TREE_READONLY (gnu_orig_min) = TREE_READONLY (gnu_orig_max) = 1;
1926 gnu_min = convert (sizetype, gnu_orig_min);
1927 gnu_max = convert (sizetype, gnu_orig_max);
1929 /* Compute the size of this dimension. See the E_Array_Subtype
1930 case below for the rationale. */
1932 = build3 (COND_EXPR, sizetype,
1933 build2 (GE_EXPR, boolean_type_node,
1934 gnu_orig_max, gnu_orig_min),
1936 size_binop (MINUS_EXPR, gnu_min, size_one_node));
1938 /* Make a range type with the new range in the Ada base type.
1939 Then make an index type with the size range in sizetype. */
1940 gnu_index_types[index]
1941 = create_index_type (gnu_min, gnu_high,
1942 create_range_type (gnu_index_base_type,
1947 /* Update the maximum size of the array in elements. */
1950 tree gnu_index_type = get_unpadded_type (Etype (gnat_index));
1952 = convert (sizetype, TYPE_MIN_VALUE (gnu_index_type));
1954 = convert (sizetype, TYPE_MAX_VALUE (gnu_index_type));
1956 = size_binop (MAX_EXPR,
1957 size_binop (PLUS_EXPR, size_one_node,
1958 size_binop (MINUS_EXPR,
1962 if (TREE_CODE (gnu_this_max) == INTEGER_CST
1963 && TREE_OVERFLOW (gnu_this_max))
1964 gnu_max_size = NULL_TREE;
1967 = size_binop (MULT_EXPR, gnu_max_size, gnu_this_max);
1970 TYPE_NAME (gnu_index_types[index])
1971 = create_concat_name (gnat_entity, field_name);
1974 for (index = 0; index < ndim; index++)
1976 = chainon (gnu_template_fields, gnu_temp_fields[index]);
1978 /* Install all the fields into the template. */
1979 finish_record_type (gnu_template_type, gnu_template_fields, 0,
1981 TYPE_READONLY (gnu_template_type) = 1;
1983 /* Now make the array of arrays and update the pointer to the array
1984 in the fat pointer. Note that it is the first field. */
1985 tem = gnat_to_gnu_component_type (gnat_entity, definition,
1988 /* If Component_Size is not already specified, annotate it with the
1989 size of the component. */
1990 if (Unknown_Component_Size (gnat_entity))
1991 Set_Component_Size (gnat_entity, annotate_value (TYPE_SIZE (tem)));
1993 /* Compute the maximum size of the array in units and bits. */
1996 gnu_max_size_unit = size_binop (MULT_EXPR, gnu_max_size,
1997 TYPE_SIZE_UNIT (tem));
1998 gnu_max_size = size_binop (MULT_EXPR,
1999 convert (bitsizetype, gnu_max_size),
2003 gnu_max_size_unit = NULL_TREE;
2005 /* Now build the array type. */
2006 for (index = ndim - 1; index >= 0; index--)
2008 tem = build_array_type (tem, gnu_index_types[index]);
2009 TYPE_MULTI_ARRAY_P (tem) = (index > 0);
2010 if (array_type_has_nonaliased_component (tem, gnat_entity))
2011 TYPE_NONALIASED_COMPONENT (tem) = 1;
2014 /* If an alignment is specified, use it if valid. But ignore it
2015 for the original type of packed array types. If the alignment
2016 was requested with an explicit alignment clause, state so. */
2017 if (No (Packed_Array_Type (gnat_entity))
2018 && Known_Alignment (gnat_entity))
2021 = validate_alignment (Alignment (gnat_entity), gnat_entity,
2023 if (Present (Alignment_Clause (gnat_entity)))
2024 TYPE_USER_ALIGN (tem) = 1;
2027 TYPE_CONVENTION_FORTRAN_P (tem) = convention_fortran_p;
2028 TREE_TYPE (TYPE_FIELDS (gnu_fat_type)) = build_pointer_type (tem);
2030 /* The result type is an UNCONSTRAINED_ARRAY_TYPE that indicates the
2031 corresponding fat pointer. */
2032 TREE_TYPE (gnu_type) = TYPE_POINTER_TO (gnu_type)
2033 = TYPE_REFERENCE_TO (gnu_type) = gnu_fat_type;
2034 SET_TYPE_MODE (gnu_type, BLKmode);
2035 TYPE_ALIGN (gnu_type) = TYPE_ALIGN (tem);
2036 SET_TYPE_UNCONSTRAINED_ARRAY (gnu_fat_type, gnu_type);
2038 /* If the maximum size doesn't overflow, use it. */
2040 && TREE_CODE (gnu_max_size) == INTEGER_CST
2041 && !TREE_OVERFLOW (gnu_max_size)
2042 && TREE_CODE (gnu_max_size_unit) == INTEGER_CST
2043 && !TREE_OVERFLOW (gnu_max_size_unit))
2045 TYPE_SIZE (tem) = size_binop (MIN_EXPR, gnu_max_size,
2047 TYPE_SIZE_UNIT (tem) = size_binop (MIN_EXPR, gnu_max_size_unit,
2048 TYPE_SIZE_UNIT (tem));
2051 create_type_decl (create_concat_name (gnat_entity, "XUA"),
2052 tem, NULL, !Comes_From_Source (gnat_entity),
2053 debug_info_p, gnat_entity);
2055 /* Give the fat pointer type a name. If this is a packed type, tell
2056 the debugger how to interpret the underlying bits. */
2057 if (Present (Packed_Array_Type (gnat_entity)))
2058 gnat_name = Packed_Array_Type (gnat_entity);
2060 gnat_name = gnat_entity;
2061 create_type_decl (create_concat_name (gnat_name, "XUP"),
2062 gnu_fat_type, NULL, true,
2063 debug_info_p, gnat_entity);
2065 /* Create the type to be used as what a thin pointer designates:
2066 a record type for the object and its template with the fields
2067 shifted to have the template at a negative offset. */
2068 tem = build_unc_object_type (gnu_template_type, tem,
2069 create_concat_name (gnat_name, "XUT"));
2070 shift_unc_components_for_thin_pointers (tem);
2072 SET_TYPE_UNCONSTRAINED_ARRAY (tem, gnu_type);
2073 TYPE_OBJECT_RECORD_TYPE (gnu_type) = tem;
2077 case E_String_Subtype:
2078 case E_Array_Subtype:
2080 /* This is the actual data type for array variables. Multidimensional
2081 arrays are implemented as arrays of arrays. Note that arrays which
2082 have sparse enumeration subtypes as index components create sparse
2083 arrays, which is obviously space inefficient but so much easier to
2086 Also note that the subtype never refers to the unconstrained array
2087 type, which is somewhat at variance with Ada semantics.
2089 First check to see if this is simply a renaming of the array type.
2090 If so, the result is the array type. */
2092 gnu_type = gnat_to_gnu_type (Etype (gnat_entity));
2093 if (!Is_Constrained (gnat_entity))
2097 Entity_Id gnat_index, gnat_base_index;
2098 const bool convention_fortran_p
2099 = (Convention (gnat_entity) == Convention_Fortran);
2100 const int ndim = Number_Dimensions (gnat_entity);
2101 tree gnu_base_type = gnu_type;
2102 tree *gnu_index_types = (tree *) alloca (ndim * sizeof (tree));
2103 tree gnu_max_size = size_one_node, gnu_max_size_unit;
2104 bool need_index_type_struct = false;
2107 /* First create the GCC type for each index and find out whether
2108 special types are needed for debugging information. */
2109 for (index = (convention_fortran_p ? ndim - 1 : 0),
2110 gnat_index = First_Index (gnat_entity),
2112 = First_Index (Implementation_Base_Type (gnat_entity));
2113 0 <= index && index < ndim;
2114 index += (convention_fortran_p ? - 1 : 1),
2115 gnat_index = Next_Index (gnat_index),
2116 gnat_base_index = Next_Index (gnat_base_index))
2118 tree gnu_index_type = get_unpadded_type (Etype (gnat_index));
2119 tree gnu_orig_min = TYPE_MIN_VALUE (gnu_index_type);
2120 tree gnu_orig_max = TYPE_MAX_VALUE (gnu_index_type);
2121 tree gnu_min = convert (sizetype, gnu_orig_min);
2122 tree gnu_max = convert (sizetype, gnu_orig_max);
2123 tree gnu_base_index_type
2124 = get_unpadded_type (Etype (gnat_base_index));
2125 tree gnu_base_orig_min = TYPE_MIN_VALUE (gnu_base_index_type);
2126 tree gnu_base_orig_max = TYPE_MAX_VALUE (gnu_base_index_type);
2129 /* See if the base array type is already flat. If it is, we
2130 are probably compiling an ACATS test but it will cause the
2131 code below to malfunction if we don't handle it specially. */
2132 if (TREE_CODE (gnu_base_orig_min) == INTEGER_CST
2133 && TREE_CODE (gnu_base_orig_max) == INTEGER_CST
2134 && tree_int_cst_lt (gnu_base_orig_max, gnu_base_orig_min))
2136 gnu_min = size_one_node;
2137 gnu_max = size_zero_node;
2141 /* Similarly, if one of the values overflows in sizetype and the
2142 range is null, use 1..0 for the sizetype bounds. */
2143 else if (TREE_CODE (gnu_min) == INTEGER_CST
2144 && TREE_CODE (gnu_max) == INTEGER_CST
2145 && (TREE_OVERFLOW (gnu_min) || TREE_OVERFLOW (gnu_max))
2146 && tree_int_cst_lt (gnu_orig_max, gnu_orig_min))
2148 gnu_min = size_one_node;
2149 gnu_max = size_zero_node;
2153 /* If the minimum and maximum values both overflow in sizetype,
2154 but the difference in the original type does not overflow in
2155 sizetype, ignore the overflow indication. */
2156 else if (TREE_CODE (gnu_min) == INTEGER_CST
2157 && TREE_CODE (gnu_max) == INTEGER_CST
2158 && TREE_OVERFLOW (gnu_min) && TREE_OVERFLOW (gnu_max)
2161 fold_build2 (MINUS_EXPR, gnu_index_type,
2165 TREE_OVERFLOW (gnu_min) = 0;
2166 TREE_OVERFLOW (gnu_max) = 0;
2170 /* Compute the size of this dimension in the general case. We
2171 need to provide GCC with an upper bound to use but have to
2172 deal with the "superflat" case. There are three ways to do
2173 this. If we can prove that the array can never be superflat,
2174 we can just use the high bound of the index type. */
2175 else if ((Nkind (gnat_index) == N_Range
2176 && cannot_be_superflat_p (gnat_index))
2177 /* Packed Array Types are never superflat. */
2178 || Is_Packed_Array_Type (gnat_entity))
2181 /* Otherwise, if the high bound is constant but the low bound is
2182 not, we use the expression (hb >= lb) ? lb : hb + 1 for the
2183 lower bound. Note that the comparison must be done in the
2184 original type to avoid any overflow during the conversion. */
2185 else if (TREE_CODE (gnu_max) == INTEGER_CST
2186 && TREE_CODE (gnu_min) != INTEGER_CST)
2190 = build_cond_expr (sizetype,
2191 build_binary_op (GE_EXPR,
2196 size_binop (PLUS_EXPR, gnu_max,
2200 /* Finally we use (hb >= lb) ? hb : lb - 1 for the upper bound
2201 in all the other cases. Note that, here as well as above,
2202 the condition used in the comparison must be equivalent to
2203 the condition (length != 0). This is relied upon in order
2204 to optimize array comparisons in compare_arrays. */
2207 = build_cond_expr (sizetype,
2208 build_binary_op (GE_EXPR,
2213 size_binop (MINUS_EXPR, gnu_min,
2216 /* Reuse the index type for the range type. Then make an index
2217 type with the size range in sizetype. */
2218 gnu_index_types[index]
2219 = create_index_type (gnu_min, gnu_high, gnu_index_type,
2222 /* Update the maximum size of the array in elements. Here we
2223 see if any constraint on the index type of the base type
2224 can be used in the case of self-referential bound on the
2225 index type of the subtype. We look for a non-"infinite"
2226 and non-self-referential bound from any type involved and
2227 handle each bound separately. */
2230 tree gnu_base_min = convert (sizetype, gnu_base_orig_min);
2231 tree gnu_base_max = convert (sizetype, gnu_base_orig_max);
2232 tree gnu_base_index_base_type
2233 = get_base_type (gnu_base_index_type);
2234 tree gnu_base_base_min
2235 = convert (sizetype,
2236 TYPE_MIN_VALUE (gnu_base_index_base_type));
2237 tree gnu_base_base_max
2238 = convert (sizetype,
2239 TYPE_MAX_VALUE (gnu_base_index_base_type));
2241 if (!CONTAINS_PLACEHOLDER_P (gnu_min)
2242 || !(TREE_CODE (gnu_base_min) == INTEGER_CST
2243 && !TREE_OVERFLOW (gnu_base_min)))
2244 gnu_base_min = gnu_min;
2246 if (!CONTAINS_PLACEHOLDER_P (gnu_max)
2247 || !(TREE_CODE (gnu_base_max) == INTEGER_CST
2248 && !TREE_OVERFLOW (gnu_base_max)))
2249 gnu_base_max = gnu_max;
2251 if ((TREE_CODE (gnu_base_min) == INTEGER_CST
2252 && TREE_OVERFLOW (gnu_base_min))
2253 || operand_equal_p (gnu_base_min, gnu_base_base_min, 0)
2254 || (TREE_CODE (gnu_base_max) == INTEGER_CST
2255 && TREE_OVERFLOW (gnu_base_max))
2256 || operand_equal_p (gnu_base_max, gnu_base_base_max, 0))
2257 gnu_max_size = NULL_TREE;
2261 = size_binop (MAX_EXPR,
2262 size_binop (PLUS_EXPR, size_one_node,
2263 size_binop (MINUS_EXPR,
2268 if (TREE_CODE (gnu_this_max) == INTEGER_CST
2269 && TREE_OVERFLOW (gnu_this_max))
2270 gnu_max_size = NULL_TREE;
2273 = size_binop (MULT_EXPR, gnu_max_size, gnu_this_max);
2277 /* We need special types for debugging information to point to
2278 the index types if they have variable bounds, are not integer
2279 types, are biased or are wider than sizetype. */
2280 if (!integer_onep (gnu_orig_min)
2281 || TREE_CODE (gnu_orig_max) != INTEGER_CST
2282 || TREE_CODE (gnu_index_type) != INTEGER_TYPE
2283 || (TREE_TYPE (gnu_index_type)
2284 && TREE_CODE (TREE_TYPE (gnu_index_type))
2286 || TYPE_BIASED_REPRESENTATION_P (gnu_index_type)
2287 || compare_tree_int (rm_size (gnu_index_type),
2288 TYPE_PRECISION (sizetype)) > 0)
2289 need_index_type_struct = true;
2292 /* Then flatten: create the array of arrays. For an array type
2293 used to implement a packed array, get the component type from
2294 the original array type since the representation clauses that
2295 can affect it are on the latter. */
2296 if (Is_Packed_Array_Type (gnat_entity)
2297 && !Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)))
2299 gnu_type = gnat_to_gnu_type (Original_Array_Type (gnat_entity));
2300 for (index = ndim - 1; index >= 0; index--)
2301 gnu_type = TREE_TYPE (gnu_type);
2303 /* One of the above calls might have caused us to be elaborated,
2304 so don't blow up if so. */
2305 if (present_gnu_tree (gnat_entity))
2307 maybe_present = true;
2313 gnu_type = gnat_to_gnu_component_type (gnat_entity, definition,
2316 /* One of the above calls might have caused us to be elaborated,
2317 so don't blow up if so. */
2318 if (present_gnu_tree (gnat_entity))
2320 maybe_present = true;
2325 /* Compute the maximum size of the array in units and bits. */
2328 gnu_max_size_unit = size_binop (MULT_EXPR, gnu_max_size,
2329 TYPE_SIZE_UNIT (gnu_type));
2330 gnu_max_size = size_binop (MULT_EXPR,
2331 convert (bitsizetype, gnu_max_size),
2332 TYPE_SIZE (gnu_type));
2335 gnu_max_size_unit = NULL_TREE;
2337 /* Now build the array type. */
2338 for (index = ndim - 1; index >= 0; index --)
2340 gnu_type = build_array_type (gnu_type, gnu_index_types[index]);
2341 TYPE_MULTI_ARRAY_P (gnu_type) = (index > 0);
2342 if (array_type_has_nonaliased_component (gnu_type, gnat_entity))
2343 TYPE_NONALIASED_COMPONENT (gnu_type) = 1;
2346 /* Attach the TYPE_STUB_DECL in case we have a parallel type. */
2347 TYPE_STUB_DECL (gnu_type)
2348 = create_type_stub_decl (gnu_entity_name, gnu_type);
2350 /* If we are at file level and this is a multi-dimensional array,
2351 we need to make a variable corresponding to the stride of the
2352 inner dimensions. */
2353 if (global_bindings_p () && ndim > 1)
2355 tree gnu_str_name = get_identifier ("ST");
2358 for (gnu_arr_type = TREE_TYPE (gnu_type);
2359 TREE_CODE (gnu_arr_type) == ARRAY_TYPE;
2360 gnu_arr_type = TREE_TYPE (gnu_arr_type),
2361 gnu_str_name = concat_name (gnu_str_name, "ST"))
2363 tree eltype = TREE_TYPE (gnu_arr_type);
2365 TYPE_SIZE (gnu_arr_type)
2366 = elaborate_expression_1 (TYPE_SIZE (gnu_arr_type),
2367 gnat_entity, gnu_str_name,
2370 /* ??? For now, store the size as a multiple of the
2371 alignment of the element type in bytes so that we
2372 can see the alignment from the tree. */
2373 TYPE_SIZE_UNIT (gnu_arr_type)
2375 (MULT_EXPR, sizetype,
2376 elaborate_expression_1
2377 (build_binary_op (EXACT_DIV_EXPR, sizetype,
2378 TYPE_SIZE_UNIT (gnu_arr_type),
2379 size_int (TYPE_ALIGN (eltype)
2381 gnat_entity, concat_name (gnu_str_name, "A_U"),
2383 size_int (TYPE_ALIGN (eltype) / BITS_PER_UNIT));
2385 /* ??? create_type_decl is not invoked on the inner types so
2386 the MULT_EXPR node built above will never be marked. */
2387 MARK_VISITED (TYPE_SIZE_UNIT (gnu_arr_type));
2391 /* If we need to write out a record type giving the names of the
2392 bounds for debugging purposes, do it now and make the record
2393 type a parallel type. This is not needed for a packed array
2394 since the bounds are conveyed by the original array type. */
2395 if (need_index_type_struct
2397 && !Is_Packed_Array_Type (gnat_entity))
2399 tree gnu_bound_rec = make_node (RECORD_TYPE);
2400 tree gnu_field_list = NULL_TREE;
2403 TYPE_NAME (gnu_bound_rec)
2404 = create_concat_name (gnat_entity, "XA");
2406 for (index = ndim - 1; index >= 0; index--)
2408 tree gnu_index = TYPE_INDEX_TYPE (gnu_index_types[index]);
2409 tree gnu_index_name = TYPE_NAME (gnu_index);
2411 if (TREE_CODE (gnu_index_name) == TYPE_DECL)
2412 gnu_index_name = DECL_NAME (gnu_index_name);
2414 /* Make sure to reference the types themselves, and not just
2415 their names, as the debugger may fall back on them. */
2416 gnu_field = create_field_decl (gnu_index_name, gnu_index,
2418 0, NULL_TREE, NULL_TREE, 0);
2419 TREE_CHAIN (gnu_field) = gnu_field_list;
2420 gnu_field_list = gnu_field;
2423 finish_record_type (gnu_bound_rec, gnu_field_list, 0, true);
2424 add_parallel_type (TYPE_STUB_DECL (gnu_type), gnu_bound_rec);
2427 /* Otherwise, for a packed array, make the original array type a
2429 else if (debug_info_p
2430 && Is_Packed_Array_Type (gnat_entity)
2431 && present_gnu_tree (Original_Array_Type (gnat_entity)))
2432 add_parallel_type (TYPE_STUB_DECL (gnu_type),
2434 (Original_Array_Type (gnat_entity)));
2436 TYPE_CONVENTION_FORTRAN_P (gnu_type) = convention_fortran_p;
2437 TYPE_PACKED_ARRAY_TYPE_P (gnu_type)
2438 = (Is_Packed_Array_Type (gnat_entity)
2439 && Is_Bit_Packed_Array (Original_Array_Type (gnat_entity)));
2441 /* If the size is self-referential and the maximum size doesn't
2442 overflow, use it. */
2443 if (CONTAINS_PLACEHOLDER_P (TYPE_SIZE (gnu_type))
2445 && !(TREE_CODE (gnu_max_size) == INTEGER_CST
2446 && TREE_OVERFLOW (gnu_max_size))
2447 && !(TREE_CODE (gnu_max_size_unit) == INTEGER_CST
2448 && TREE_OVERFLOW (gnu_max_size_unit)))
2450 TYPE_SIZE (gnu_type) = size_binop (MIN_EXPR, gnu_max_size,
2451 TYPE_SIZE (gnu_type));
2452 TYPE_SIZE_UNIT (gnu_type)
2453 = size_binop (MIN_EXPR, gnu_max_size_unit,
2454 TYPE_SIZE_UNIT (gnu_type));
2457 /* Set our alias set to that of our base type. This gives all
2458 array subtypes the same alias set. */
2459 relate_alias_sets (gnu_type, gnu_base_type, ALIAS_SET_COPY);
2461 /* If this is a packed type, make this type the same as the packed
2462 array type, but do some adjusting in the type first. */
2463 if (Present (Packed_Array_Type (gnat_entity)))
2465 Entity_Id gnat_index;
2468 /* First finish the type we had been making so that we output
2469 debugging information for it. */
2470 if (Treat_As_Volatile (gnat_entity))
2472 = build_qualified_type (gnu_type,
2473 TYPE_QUALS (gnu_type)
2474 | TYPE_QUAL_VOLATILE);
2476 /* Make it artificial only if the base type was artificial too.
2477 That's sort of "morally" true and will make it possible for
2478 the debugger to look it up by name in DWARF, which is needed
2479 in order to decode the packed array type. */
2481 = create_type_decl (gnu_entity_name, gnu_type, attr_list,
2482 !Comes_From_Source (Etype (gnat_entity))
2483 && !Comes_From_Source (gnat_entity),
2484 debug_info_p, gnat_entity);
2486 /* Save it as our equivalent in case the call below elaborates
2488 save_gnu_tree (gnat_entity, gnu_decl, false);
2490 gnu_decl = gnat_to_gnu_entity (Packed_Array_Type (gnat_entity),
2492 this_made_decl = true;
2493 gnu_type = TREE_TYPE (gnu_decl);
2494 save_gnu_tree (gnat_entity, NULL_TREE, false);
2496 gnu_inner = gnu_type;
2497 while (TREE_CODE (gnu_inner) == RECORD_TYPE
2498 && (TYPE_JUSTIFIED_MODULAR_P (gnu_inner)
2499 || TYPE_PADDING_P (gnu_inner)))
2500 gnu_inner = TREE_TYPE (TYPE_FIELDS (gnu_inner));
2502 /* We need to attach the index type to the type we just made so
2503 that the actual bounds can later be put into a template. */
2504 if ((TREE_CODE (gnu_inner) == ARRAY_TYPE
2505 && !TYPE_ACTUAL_BOUNDS (gnu_inner))
2506 || (TREE_CODE (gnu_inner) == INTEGER_TYPE
2507 && !TYPE_HAS_ACTUAL_BOUNDS_P (gnu_inner)))
2509 if (TREE_CODE (gnu_inner) == INTEGER_TYPE)
2511 /* The TYPE_ACTUAL_BOUNDS field is overloaded with the
2512 TYPE_MODULUS for modular types so we make an extra
2513 subtype if necessary. */
2514 if (TYPE_MODULAR_P (gnu_inner))
2517 = make_unsigned_type (TYPE_PRECISION (gnu_inner));
2518 TREE_TYPE (gnu_subtype) = gnu_inner;
2519 TYPE_EXTRA_SUBTYPE_P (gnu_subtype) = 1;
2520 SET_TYPE_RM_MIN_VALUE (gnu_subtype,
2521 TYPE_MIN_VALUE (gnu_inner));
2522 SET_TYPE_RM_MAX_VALUE (gnu_subtype,
2523 TYPE_MAX_VALUE (gnu_inner));
2524 gnu_inner = gnu_subtype;
2527 TYPE_HAS_ACTUAL_BOUNDS_P (gnu_inner) = 1;
2529 #ifdef ENABLE_CHECKING
2530 /* Check for other cases of overloading. */
2531 gcc_assert (!TYPE_ACTUAL_BOUNDS (gnu_inner));
2535 for (gnat_index = First_Index (gnat_entity);
2536 Present (gnat_index);
2537 gnat_index = Next_Index (gnat_index))
2538 SET_TYPE_ACTUAL_BOUNDS
2540 tree_cons (NULL_TREE,
2541 get_unpadded_type (Etype (gnat_index)),
2542 TYPE_ACTUAL_BOUNDS (gnu_inner)));
2544 if (Convention (gnat_entity) != Convention_Fortran)
2545 SET_TYPE_ACTUAL_BOUNDS
2546 (gnu_inner, nreverse (TYPE_ACTUAL_BOUNDS (gnu_inner)));
2548 if (TREE_CODE (gnu_type) == RECORD_TYPE
2549 && TYPE_JUSTIFIED_MODULAR_P (gnu_type))
2550 TREE_TYPE (TYPE_FIELDS (gnu_type)) = gnu_inner;
2555 /* Abort if packed array with no Packed_Array_Type field set. */
2556 gcc_assert (!Is_Packed (gnat_entity));
2560 case E_String_Literal_Subtype:
2561 /* Create the type for a string literal. */
2563 Entity_Id gnat_full_type
2564 = (IN (Ekind (Etype (gnat_entity)), Private_Kind)
2565 && Present (Full_View (Etype (gnat_entity)))
2566 ? Full_View (Etype (gnat_entity)) : Etype (gnat_entity));
2567 tree gnu_string_type = get_unpadded_type (gnat_full_type);
2568 tree gnu_string_array_type
2569 = TREE_TYPE (TREE_TYPE (TYPE_FIELDS (TREE_TYPE (gnu_string_type))));
2570 tree gnu_string_index_type
2571 = get_base_type (TREE_TYPE (TYPE_INDEX_TYPE
2572 (TYPE_DOMAIN (gnu_string_array_type))));
2573 tree gnu_lower_bound
2574 = convert (gnu_string_index_type,
2575 gnat_to_gnu (String_Literal_Low_Bound (gnat_entity)));
2576 int length = UI_To_Int (String_Literal_Length (gnat_entity));
2577 tree gnu_length = ssize_int (length - 1);
2578 tree gnu_upper_bound
2579 = build_binary_op (PLUS_EXPR, gnu_string_index_type,
2581 convert (gnu_string_index_type, gnu_length));
2583 = create_index_type (convert (sizetype, gnu_lower_bound),
2584 convert (sizetype, gnu_upper_bound),
2585 create_range_type (gnu_string_index_type,
2591 = build_array_type (gnat_to_gnu_type (Component_Type (gnat_entity)),
2593 if (array_type_has_nonaliased_component (gnu_type, gnat_entity))
2594 TYPE_NONALIASED_COMPONENT (gnu_type) = 1;
2595 relate_alias_sets (gnu_type, gnu_string_type, ALIAS_SET_COPY);
2599 /* Record Types and Subtypes
2601 The following fields are defined on record types:
2603 Has_Discriminants True if the record has discriminants
2604 First_Discriminant Points to head of list of discriminants
2605 First_Entity Points to head of list of fields
2606 Is_Tagged_Type True if the record is tagged
2608 Implementation of Ada records and discriminated records:
2610 A record type definition is transformed into the equivalent of a C
2611 struct definition. The fields that are the discriminants which are
2612 found in the Full_Type_Declaration node and the elements of the
2613 Component_List found in the Record_Type_Definition node. The
2614 Component_List can be a recursive structure since each Variant of
2615 the Variant_Part of the Component_List has a Component_List.
2617 Processing of a record type definition comprises starting the list of
2618 field declarations here from the discriminants and the calling the
2619 function components_to_record to add the rest of the fields from the
2620 component list and return the gnu type node. The function
2621 components_to_record will call itself recursively as it traverses
2625 if (Has_Complex_Representation (gnat_entity))
2628 = build_complex_type
2630 (Etype (Defining_Entity
2631 (First (Component_Items
2634 (Declaration_Node (gnat_entity)))))))));
2640 Node_Id full_definition = Declaration_Node (gnat_entity);
2641 Node_Id record_definition = Type_Definition (full_definition);
2642 Entity_Id gnat_field;
2643 tree gnu_field, gnu_field_list = NULL_TREE, gnu_get_parent;
2644 /* Set PACKED in keeping with gnat_to_gnu_field. */
2646 = Is_Packed (gnat_entity)
2648 : Component_Alignment (gnat_entity) == Calign_Storage_Unit
2650 : (Known_Alignment (gnat_entity)
2651 || (Strict_Alignment (gnat_entity)
2652 && Known_Static_Esize (gnat_entity)))
2655 bool has_discr = Has_Discriminants (gnat_entity);
2656 bool has_rep = Has_Specified_Layout (gnat_entity);
2657 bool all_rep = has_rep;
2659 = (Is_Tagged_Type (gnat_entity)
2660 && Nkind (record_definition) == N_Derived_Type_Definition);
2661 bool is_unchecked_union = Is_Unchecked_Union (gnat_entity);
2663 /* See if all fields have a rep clause. Stop when we find one
2666 for (gnat_field = First_Entity (gnat_entity);
2667 Present (gnat_field);
2668 gnat_field = Next_Entity (gnat_field))
2669 if ((Ekind (gnat_field) == E_Component
2670 || Ekind (gnat_field) == E_Discriminant)
2671 && No (Component_Clause (gnat_field)))
2677 /* If this is a record extension, go a level further to find the
2678 record definition. Also, verify we have a Parent_Subtype. */
2681 if (!type_annotate_only
2682 || Present (Record_Extension_Part (record_definition)))
2683 record_definition = Record_Extension_Part (record_definition);
2685 gcc_assert (type_annotate_only
2686 || Present (Parent_Subtype (gnat_entity)));
2689 /* Make a node for the record. If we are not defining the record,
2690 suppress expanding incomplete types. */
2691 gnu_type = make_node (tree_code_for_record_type (gnat_entity));
2692 TYPE_NAME (gnu_type) = gnu_entity_name;
2693 TYPE_PACKED (gnu_type) = (packed != 0) || has_rep;
2697 defer_incomplete_level++;
2698 this_deferred = true;
2701 /* If both a size and rep clause was specified, put the size in
2702 the record type now so that it can get the proper mode. */
2703 if (has_rep && Known_Esize (gnat_entity))
2704 TYPE_SIZE (gnu_type) = UI_To_gnu (Esize (gnat_entity), sizetype);
2706 /* Always set the alignment here so that it can be used to
2707 set the mode, if it is making the alignment stricter. If
2708 it is invalid, it will be checked again below. If this is to
2709 be Atomic, choose a default alignment of a word unless we know
2710 the size and it's smaller. */
2711 if (Known_Alignment (gnat_entity))
2712 TYPE_ALIGN (gnu_type)
2713 = validate_alignment (Alignment (gnat_entity), gnat_entity, 0);
2714 else if (Is_Atomic (gnat_entity))
2715 TYPE_ALIGN (gnu_type)
2716 = esize >= BITS_PER_WORD ? BITS_PER_WORD : ceil_alignment (esize);
2717 /* If a type needs strict alignment, the minimum size will be the
2718 type size instead of the RM size (see validate_size). Cap the
2719 alignment, lest it causes this type size to become too large. */
2720 else if (Strict_Alignment (gnat_entity)
2721 && Known_Static_Esize (gnat_entity))
2723 unsigned int raw_size = UI_To_Int (Esize (gnat_entity));
2724 unsigned int raw_align = raw_size & -raw_size;
2725 if (raw_align < BIGGEST_ALIGNMENT)
2726 TYPE_ALIGN (gnu_type) = raw_align;
2729 TYPE_ALIGN (gnu_type) = 0;
2731 /* If we have a Parent_Subtype, make a field for the parent. If
2732 this record has rep clauses, force the position to zero. */
2733 if (Present (Parent_Subtype (gnat_entity)))
2735 Entity_Id gnat_parent = Parent_Subtype (gnat_entity);
2738 /* A major complexity here is that the parent subtype will
2739 reference our discriminants in its Discriminant_Constraint
2740 list. But those must reference the parent component of this
2741 record which is of the parent subtype we have not built yet!
2742 To break the circle we first build a dummy COMPONENT_REF which
2743 represents the "get to the parent" operation and initialize
2744 each of those discriminants to a COMPONENT_REF of the above
2745 dummy parent referencing the corresponding discriminant of the
2746 base type of the parent subtype. */
2747 gnu_get_parent = build3 (COMPONENT_REF, void_type_node,
2748 build0 (PLACEHOLDER_EXPR, gnu_type),
2749 build_decl (input_location,
2750 FIELD_DECL, NULL_TREE,
2755 for (gnat_field = First_Stored_Discriminant (gnat_entity);
2756 Present (gnat_field);
2757 gnat_field = Next_Stored_Discriminant (gnat_field))
2758 if (Present (Corresponding_Discriminant (gnat_field)))
2761 = gnat_to_gnu_field_decl (Corresponding_Discriminant
2765 build3 (COMPONENT_REF, TREE_TYPE (gnu_field),
2766 gnu_get_parent, gnu_field, NULL_TREE),
2770 /* Then we build the parent subtype. If it has discriminants but
2771 the type itself has unknown discriminants, this means that it
2772 doesn't contain information about how the discriminants are
2773 derived from those of the ancestor type, so it cannot be used
2774 directly. Instead it is built by cloning the parent subtype
2775 of the underlying record view of the type, for which the above
2776 derivation of discriminants has been made explicit. */
2777 if (Has_Discriminants (gnat_parent)
2778 && Has_Unknown_Discriminants (gnat_entity))
2780 Entity_Id gnat_uview = Underlying_Record_View (gnat_entity);
2782 /* If we are defining the type, the underlying record
2783 view must already have been elaborated at this point.
2784 Otherwise do it now as its parent subtype cannot be
2785 technically elaborated on its own. */
2787 gcc_assert (present_gnu_tree (gnat_uview));
2789 gnat_to_gnu_entity (gnat_uview, NULL_TREE, 0);
2791 gnu_parent = gnat_to_gnu_type (Parent_Subtype (gnat_uview));
2793 /* Substitute the "get to the parent" of the type for that
2794 of its underlying record view in the cloned type. */
2795 for (gnat_field = First_Stored_Discriminant (gnat_uview);
2796 Present (gnat_field);
2797 gnat_field = Next_Stored_Discriminant (gnat_field))
2798 if (Present (Corresponding_Discriminant (gnat_field)))
2800 tree gnu_field = gnat_to_gnu_field_decl (gnat_field);
2802 = build3 (COMPONENT_REF, TREE_TYPE (gnu_field),
2803 gnu_get_parent, gnu_field, NULL_TREE);
2805 = substitute_in_type (gnu_parent, gnu_field, gnu_ref);
2809 gnu_parent = gnat_to_gnu_type (gnat_parent);
2811 /* Finally we fix up both kinds of twisted COMPONENT_REF we have
2812 initially built. The discriminants must reference the fields
2813 of the parent subtype and not those of its base type for the
2814 placeholder machinery to properly work. */
2817 /* The actual parent subtype is the full view. */
2818 if (IN (Ekind (gnat_parent), Private_Kind))
2820 if (Present (Full_View (gnat_parent)))
2821 gnat_parent = Full_View (gnat_parent);
2823 gnat_parent = Underlying_Full_View (gnat_parent);
2826 for (gnat_field = First_Stored_Discriminant (gnat_entity);
2827 Present (gnat_field);
2828 gnat_field = Next_Stored_Discriminant (gnat_field))
2829 if (Present (Corresponding_Discriminant (gnat_field)))
2831 Entity_Id field = Empty;
2832 for (field = First_Stored_Discriminant (gnat_parent);
2834 field = Next_Stored_Discriminant (field))
2835 if (same_discriminant_p (gnat_field, field))
2837 gcc_assert (Present (field));
2838 TREE_OPERAND (get_gnu_tree (gnat_field), 1)
2839 = gnat_to_gnu_field_decl (field);
2843 /* The "get to the parent" COMPONENT_REF must be given its
2845 TREE_TYPE (gnu_get_parent) = gnu_parent;
2847 /* ...and reference the _Parent field of this record. */
2849 = create_field_decl (parent_name_id,
2850 gnu_parent, gnu_type, 0,
2852 ? TYPE_SIZE (gnu_parent) : NULL_TREE,
2854 ? bitsize_zero_node : NULL_TREE, 1);
2855 DECL_INTERNAL_P (gnu_field) = 1;
2856 TREE_OPERAND (gnu_get_parent, 1) = gnu_field;
2857 TYPE_FIELDS (gnu_type) = gnu_field;
2860 /* Make the fields for the discriminants and put them into the record
2861 unless it's an Unchecked_Union. */
2863 for (gnat_field = First_Stored_Discriminant (gnat_entity);
2864 Present (gnat_field);
2865 gnat_field = Next_Stored_Discriminant (gnat_field))
2867 /* If this is a record extension and this discriminant is the
2868 renaming of another discriminant, we've handled it above. */
2869 if (Present (Parent_Subtype (gnat_entity))
2870 && Present (Corresponding_Discriminant (gnat_field)))
2874 = gnat_to_gnu_field (gnat_field, gnu_type, packed, definition,
2877 /* Make an expression using a PLACEHOLDER_EXPR from the
2878 FIELD_DECL node just created and link that with the
2879 corresponding GNAT defining identifier. */
2880 save_gnu_tree (gnat_field,