2017-09-18 Bob Duff <duff@adacore.com>
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob0fcf7235eee4eb5cf3ab6d96e190fcc3d6ec0518
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ C H 3 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2017, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Aspects; use Aspects;
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Aggr; use Exp_Aggr;
32 with Exp_Atag; use Exp_Atag;
33 with Exp_Ch4; use Exp_Ch4;
34 with Exp_Ch6; use Exp_Ch6;
35 with Exp_Ch7; use Exp_Ch7;
36 with Exp_Ch9; use Exp_Ch9;
37 with Exp_Dbug; use Exp_Dbug;
38 with Exp_Disp; use Exp_Disp;
39 with Exp_Dist; use Exp_Dist;
40 with Exp_Smem; use Exp_Smem;
41 with Exp_Strm; use Exp_Strm;
42 with Exp_Tss; use Exp_Tss;
43 with Exp_Util; use Exp_Util;
44 with Freeze; use Freeze;
45 with Ghost; use Ghost;
46 with Namet; use Namet;
47 with Nlists; use Nlists;
48 with Nmake; use Nmake;
49 with Opt; use Opt;
50 with Restrict; use Restrict;
51 with Rident; use Rident;
52 with Rtsfind; use Rtsfind;
53 with Sem; use Sem;
54 with Sem_Aux; use Sem_Aux;
55 with Sem_Attr; use Sem_Attr;
56 with Sem_Cat; use Sem_Cat;
57 with Sem_Ch3; use Sem_Ch3;
58 with Sem_Ch6; use Sem_Ch6;
59 with Sem_Ch8; use Sem_Ch8;
60 with Sem_Disp; use Sem_Disp;
61 with Sem_Eval; use Sem_Eval;
62 with Sem_Mech; use Sem_Mech;
63 with Sem_Res; use Sem_Res;
64 with Sem_SCIL; use Sem_SCIL;
65 with Sem_Type; use Sem_Type;
66 with Sem_Util; use Sem_Util;
67 with Sinfo; use Sinfo;
68 with Stand; use Stand;
69 with Snames; use Snames;
70 with Tbuild; use Tbuild;
71 with Ttypes; use Ttypes;
72 with Validsw; use Validsw;
74 package body Exp_Ch3 is
76 -----------------------
77 -- Local Subprograms --
78 -----------------------
80 procedure Adjust_Discriminants (Rtype : Entity_Id);
81 -- This is used when freezing a record type. It attempts to construct
82 -- more restrictive subtypes for discriminants so that the max size of
83 -- the record can be calculated more accurately. See the body of this
84 -- procedure for details.
86 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
87 -- Build initialization procedure for given array type. Nod is a node
88 -- used for attachment of any actions required in its construction.
89 -- It also supplies the source location used for the procedure.
91 function Build_Discriminant_Formals
92 (Rec_Id : Entity_Id;
93 Use_Dl : Boolean) return List_Id;
94 -- This function uses the discriminants of a type to build a list of
95 -- formal parameters, used in Build_Init_Procedure among other places.
96 -- If the flag Use_Dl is set, the list is built using the already
97 -- defined discriminals of the type, as is the case for concurrent
98 -- types with discriminants. Otherwise new identifiers are created,
99 -- with the source names of the discriminants.
101 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
102 -- This function builds a static aggregate that can serve as the initial
103 -- value for an array type whose bounds are static, and whose component
104 -- type is a composite type that has a static equivalent aggregate.
105 -- The equivalent array aggregate is used both for object initialization
106 -- and for component initialization, when used in the following function.
108 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
109 -- This function builds a static aggregate that can serve as the initial
110 -- value for a record type whose components are scalar and initialized
111 -- with compile-time values, or arrays with similar initialization or
112 -- defaults. When possible, initialization of an object of the type can
113 -- be achieved by using a copy of the aggregate as an initial value, thus
114 -- removing the implicit call that would otherwise constitute elaboration
115 -- code.
117 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id);
118 -- Build record initialization procedure. N is the type declaration
119 -- node, and Rec_Ent is the corresponding entity for the record type.
121 procedure Build_Slice_Assignment (Typ : Entity_Id);
122 -- Build assignment procedure for one-dimensional arrays of controlled
123 -- types. Other array and slice assignments are expanded in-line, but
124 -- the code expansion for controlled components (when control actions
125 -- are active) can lead to very large blocks that GCC3 handles poorly.
127 procedure Build_Untagged_Equality (Typ : Entity_Id);
128 -- AI05-0123: Equality on untagged records composes. This procedure
129 -- builds the equality routine for an untagged record that has components
130 -- of a record type that has user-defined primitive equality operations.
131 -- The resulting operation is a TSS subprogram.
133 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
134 -- Create An Equality function for the untagged variant record Typ and
135 -- attach it to the TSS list
137 procedure Check_Stream_Attributes (Typ : Entity_Id);
138 -- Check that if a limited extension has a parent with user-defined stream
139 -- attributes, and does not itself have user-defined stream-attributes,
140 -- then any limited component of the extension also has the corresponding
141 -- user-defined stream attributes.
143 procedure Clean_Task_Names
144 (Typ : Entity_Id;
145 Proc_Id : Entity_Id);
146 -- If an initialization procedure includes calls to generate names
147 -- for task subcomponents, indicate that secondary stack cleanup is
148 -- needed after an initialization. Typ is the component type, and Proc_Id
149 -- the initialization procedure for the enclosing composite type.
151 procedure Expand_Freeze_Array_Type (N : Node_Id);
152 -- Freeze an array type. Deals with building the initialization procedure,
153 -- creating the packed array type for a packed array and also with the
154 -- creation of the controlling procedures for the controlled case. The
155 -- argument N is the N_Freeze_Entity node for the type.
157 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id);
158 -- Freeze a class-wide type. Build routine Finalize_Address for the purpose
159 -- of finalizing controlled derivations from the class-wide's root type.
161 procedure Expand_Freeze_Enumeration_Type (N : Node_Id);
162 -- Freeze enumeration type with non-standard representation. Builds the
163 -- array and function needed to convert between enumeration pos and
164 -- enumeration representation values. N is the N_Freeze_Entity node
165 -- for the type.
167 procedure Expand_Freeze_Record_Type (N : Node_Id);
168 -- Freeze record type. Builds all necessary discriminant checking
169 -- and other ancillary functions, and builds dispatch tables where
170 -- needed. The argument N is the N_Freeze_Entity node. This processing
171 -- applies only to E_Record_Type entities, not to class wide types,
172 -- record subtypes, or private types.
174 procedure Expand_Tagged_Root (T : Entity_Id);
175 -- Add a field _Tag at the beginning of the record. This field carries
176 -- the value of the access to the Dispatch table. This procedure is only
177 -- called on root type, the _Tag field being inherited by the descendants.
179 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
180 -- Treat user-defined stream operations as renaming_as_body if the
181 -- subprogram they rename is not frozen when the type is frozen.
183 procedure Initialization_Warning (E : Entity_Id);
184 -- If static elaboration of the package is requested, indicate
185 -- when a type does meet the conditions for static initialization. If
186 -- E is a type, it has components that have no static initialization.
187 -- if E is an entity, its initial expression is not compile-time known.
189 function Init_Formals (Typ : Entity_Id) return List_Id;
190 -- This function builds the list of formals for an initialization routine.
191 -- The first formal is always _Init with the given type. For task value
192 -- record types and types containing tasks, three additional formals are
193 -- added:
195 -- _Master : Master_Id
196 -- _Chain : in out Activation_Chain
197 -- _Task_Name : String
199 -- The caller must append additional entries for discriminants if required.
201 function Inline_Init_Proc (Typ : Entity_Id) return Boolean;
202 -- Returns true if the initialization procedure of Typ should be inlined
204 function In_Runtime (E : Entity_Id) return Boolean;
205 -- Check if E is defined in the RTL (in a child of Ada or System). Used
206 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
208 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean;
209 -- Returns true if Prim is a user defined equality function
211 function Make_Eq_Body
212 (Typ : Entity_Id;
213 Eq_Name : Name_Id) return Node_Id;
214 -- Build the body of a primitive equality operation for a tagged record
215 -- type, or in Ada 2012 for any record type that has components with a
216 -- user-defined equality. Factored out of Predefined_Primitive_Bodies.
218 function Make_Eq_Case
219 (E : Entity_Id;
220 CL : Node_Id;
221 Discrs : Elist_Id := New_Elmt_List) return List_Id;
222 -- Building block for variant record equality. Defined to share the code
223 -- between the tagged and untagged case. Given a Component_List node CL,
224 -- it generates an 'if' followed by a 'case' statement that compares all
225 -- components of local temporaries named X and Y (that are declared as
226 -- formals at some upper level). E provides the Sloc to be used for the
227 -- generated code.
229 -- IF E is an unchecked_union, Discrs is the list of formals created for
230 -- the inferred discriminants of one operand. These formals are used in
231 -- the generated case statements for each variant of the unchecked union.
233 function Make_Eq_If
234 (E : Entity_Id;
235 L : List_Id) return Node_Id;
236 -- Building block for variant record equality. Defined to share the code
237 -- between the tagged and untagged case. Given the list of components
238 -- (or discriminants) L, it generates a return statement that compares all
239 -- components of local temporaries named X and Y (that are declared as
240 -- formals at some upper level). E provides the Sloc to be used for the
241 -- generated code.
243 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id;
244 -- Search for a renaming of the inequality dispatching primitive of
245 -- this tagged type. If found then build and return the corresponding
246 -- rename-as-body inequality subprogram; otherwise return Empty.
248 procedure Make_Predefined_Primitive_Specs
249 (Tag_Typ : Entity_Id;
250 Predef_List : out List_Id;
251 Renamed_Eq : out Entity_Id);
252 -- Create a list with the specs of the predefined primitive operations.
253 -- For tagged types that are interfaces all these primitives are defined
254 -- abstract.
256 -- The following entries are present for all tagged types, and provide
257 -- the results of the corresponding attribute applied to the object.
258 -- Dispatching is required in general, since the result of the attribute
259 -- will vary with the actual object subtype.
261 -- _size provides result of 'Size attribute
262 -- typSR provides result of 'Read attribute
263 -- typSW provides result of 'Write attribute
264 -- typSI provides result of 'Input attribute
265 -- typSO provides result of 'Output attribute
267 -- The following entries are additionally present for non-limited tagged
268 -- types, and implement additional dispatching operations for predefined
269 -- operations:
271 -- _equality implements "=" operator
272 -- _assign implements assignment operation
273 -- typDF implements deep finalization
274 -- typDA implements deep adjust
276 -- The latter two are empty procedures unless the type contains some
277 -- controlled components that require finalization actions (the deep
278 -- in the name refers to the fact that the action applies to components).
280 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
281 -- returns the value Empty, or else the defining unit name for the
282 -- predefined equality function in the case where the type has a primitive
283 -- operation that is a renaming of predefined equality (but only if there
284 -- is also an overriding user-defined equality function). The returned
285 -- Renamed_Eq will be passed to the corresponding parameter of
286 -- Predefined_Primitive_Bodies.
288 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
289 -- Returns True if there are representation clauses for type T that are not
290 -- inherited. If the result is false, the init_proc and the discriminant
291 -- checking functions of the parent can be reused by a derived type.
293 procedure Make_Controlling_Function_Wrappers
294 (Tag_Typ : Entity_Id;
295 Decl_List : out List_Id;
296 Body_List : out List_Id);
297 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
298 -- associated with inherited functions with controlling results which
299 -- are not overridden. The body of each wrapper function consists solely
300 -- of a return statement whose expression is an extension aggregate
301 -- invoking the inherited subprogram's parent subprogram and extended
302 -- with a null association list.
304 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id;
305 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
306 -- null procedures inherited from an interface type that have not been
307 -- overridden. Only one null procedure will be created for a given set of
308 -- inherited null procedures with homographic profiles.
310 function Predef_Spec_Or_Body
311 (Loc : Source_Ptr;
312 Tag_Typ : Entity_Id;
313 Name : Name_Id;
314 Profile : List_Id;
315 Ret_Type : Entity_Id := Empty;
316 For_Body : Boolean := False) return Node_Id;
317 -- This function generates the appropriate expansion for a predefined
318 -- primitive operation specified by its name, parameter profile and
319 -- return type (Empty means this is a procedure). If For_Body is false,
320 -- then the returned node is a subprogram declaration. If For_Body is
321 -- true, then the returned node is a empty subprogram body containing
322 -- no declarations and no statements.
324 function Predef_Stream_Attr_Spec
325 (Loc : Source_Ptr;
326 Tag_Typ : Entity_Id;
327 Name : TSS_Name_Type;
328 For_Body : Boolean := False) return Node_Id;
329 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
330 -- input and output attribute whose specs are constructed in Exp_Strm.
332 function Predef_Deep_Spec
333 (Loc : Source_Ptr;
334 Tag_Typ : Entity_Id;
335 Name : TSS_Name_Type;
336 For_Body : Boolean := False) return Node_Id;
337 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
338 -- and _deep_finalize
340 function Predefined_Primitive_Bodies
341 (Tag_Typ : Entity_Id;
342 Renamed_Eq : Entity_Id) return List_Id;
343 -- Create the bodies of the predefined primitives that are described in
344 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
345 -- the defining unit name of the type's predefined equality as returned
346 -- by Make_Predefined_Primitive_Specs.
348 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
349 -- Freeze entities of all predefined primitive operations. This is needed
350 -- because the bodies of these operations do not normally do any freezing.
352 function Stream_Operation_OK
353 (Typ : Entity_Id;
354 Operation : TSS_Name_Type) return Boolean;
355 -- Check whether the named stream operation must be emitted for a given
356 -- type. The rules for inheritance of stream attributes by type extensions
357 -- are enforced by this function. Furthermore, various restrictions prevent
358 -- the generation of these operations, as a useful optimization or for
359 -- certification purposes and to save unnecessary generated code.
361 --------------------------
362 -- Adjust_Discriminants --
363 --------------------------
365 -- This procedure attempts to define subtypes for discriminants that are
366 -- more restrictive than those declared. Such a replacement is possible if
367 -- we can demonstrate that values outside the restricted range would cause
368 -- constraint errors in any case. The advantage of restricting the
369 -- discriminant types in this way is that the maximum size of the variant
370 -- record can be calculated more conservatively.
372 -- An example of a situation in which we can perform this type of
373 -- restriction is the following:
375 -- subtype B is range 1 .. 10;
376 -- type Q is array (B range <>) of Integer;
378 -- type V (N : Natural) is record
379 -- C : Q (1 .. N);
380 -- end record;
382 -- In this situation, we can restrict the upper bound of N to 10, since
383 -- any larger value would cause a constraint error in any case.
385 -- There are many situations in which such restriction is possible, but
386 -- for now, we just look for cases like the above, where the component
387 -- in question is a one dimensional array whose upper bound is one of
388 -- the record discriminants. Also the component must not be part of
389 -- any variant part, since then the component does not always exist.
391 procedure Adjust_Discriminants (Rtype : Entity_Id) is
392 Loc : constant Source_Ptr := Sloc (Rtype);
393 Comp : Entity_Id;
394 Ctyp : Entity_Id;
395 Ityp : Entity_Id;
396 Lo : Node_Id;
397 Hi : Node_Id;
398 P : Node_Id;
399 Loval : Uint;
400 Discr : Entity_Id;
401 Dtyp : Entity_Id;
402 Dhi : Node_Id;
403 Dhiv : Uint;
404 Ahi : Node_Id;
405 Ahiv : Uint;
406 Tnn : Entity_Id;
408 begin
409 Comp := First_Component (Rtype);
410 while Present (Comp) loop
412 -- If our parent is a variant, quit, we do not look at components
413 -- that are in variant parts, because they may not always exist.
415 P := Parent (Comp); -- component declaration
416 P := Parent (P); -- component list
418 exit when Nkind (Parent (P)) = N_Variant;
420 -- We are looking for a one dimensional array type
422 Ctyp := Etype (Comp);
424 if not Is_Array_Type (Ctyp) or else Number_Dimensions (Ctyp) > 1 then
425 goto Continue;
426 end if;
428 -- The lower bound must be constant, and the upper bound is a
429 -- discriminant (which is a discriminant of the current record).
431 Ityp := Etype (First_Index (Ctyp));
432 Lo := Type_Low_Bound (Ityp);
433 Hi := Type_High_Bound (Ityp);
435 if not Compile_Time_Known_Value (Lo)
436 or else Nkind (Hi) /= N_Identifier
437 or else No (Entity (Hi))
438 or else Ekind (Entity (Hi)) /= E_Discriminant
439 then
440 goto Continue;
441 end if;
443 -- We have an array with appropriate bounds
445 Loval := Expr_Value (Lo);
446 Discr := Entity (Hi);
447 Dtyp := Etype (Discr);
449 -- See if the discriminant has a known upper bound
451 Dhi := Type_High_Bound (Dtyp);
453 if not Compile_Time_Known_Value (Dhi) then
454 goto Continue;
455 end if;
457 Dhiv := Expr_Value (Dhi);
459 -- See if base type of component array has known upper bound
461 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
463 if not Compile_Time_Known_Value (Ahi) then
464 goto Continue;
465 end if;
467 Ahiv := Expr_Value (Ahi);
469 -- The condition for doing the restriction is that the high bound
470 -- of the discriminant is greater than the low bound of the array,
471 -- and is also greater than the high bound of the base type index.
473 if Dhiv > Loval and then Dhiv > Ahiv then
475 -- We can reset the upper bound of the discriminant type to
476 -- whichever is larger, the low bound of the component, or
477 -- the high bound of the base type array index.
479 -- We build a subtype that is declared as
481 -- subtype Tnn is discr_type range discr_type'First .. max;
483 -- And insert this declaration into the tree. The type of the
484 -- discriminant is then reset to this more restricted subtype.
486 Tnn := Make_Temporary (Loc, 'T');
488 Insert_Action (Declaration_Node (Rtype),
489 Make_Subtype_Declaration (Loc,
490 Defining_Identifier => Tnn,
491 Subtype_Indication =>
492 Make_Subtype_Indication (Loc,
493 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
494 Constraint =>
495 Make_Range_Constraint (Loc,
496 Range_Expression =>
497 Make_Range (Loc,
498 Low_Bound =>
499 Make_Attribute_Reference (Loc,
500 Attribute_Name => Name_First,
501 Prefix => New_Occurrence_Of (Dtyp, Loc)),
502 High_Bound =>
503 Make_Integer_Literal (Loc,
504 Intval => UI_Max (Loval, Ahiv)))))));
506 Set_Etype (Discr, Tnn);
507 end if;
509 <<Continue>>
510 Next_Component (Comp);
511 end loop;
512 end Adjust_Discriminants;
514 ---------------------------
515 -- Build_Array_Init_Proc --
516 ---------------------------
518 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
519 Comp_Type : constant Entity_Id := Component_Type (A_Type);
520 Body_Stmts : List_Id;
521 Has_Default_Init : Boolean;
522 Index_List : List_Id;
523 Loc : Source_Ptr;
524 Proc_Id : Entity_Id;
526 function Init_Component return List_Id;
527 -- Create one statement to initialize one array component, designated
528 -- by a full set of indexes.
530 function Init_One_Dimension (N : Int) return List_Id;
531 -- Create loop to initialize one dimension of the array. The single
532 -- statement in the loop body initializes the inner dimensions if any,
533 -- or else the single component. Note that this procedure is called
534 -- recursively, with N being the dimension to be initialized. A call
535 -- with N greater than the number of dimensions simply generates the
536 -- component initialization, terminating the recursion.
538 --------------------
539 -- Init_Component --
540 --------------------
542 function Init_Component return List_Id is
543 Comp : Node_Id;
545 begin
546 Comp :=
547 Make_Indexed_Component (Loc,
548 Prefix => Make_Identifier (Loc, Name_uInit),
549 Expressions => Index_List);
551 if Has_Default_Aspect (A_Type) then
552 Set_Assignment_OK (Comp);
553 return New_List (
554 Make_Assignment_Statement (Loc,
555 Name => Comp,
556 Expression =>
557 Convert_To (Comp_Type,
558 Default_Aspect_Component_Value (First_Subtype (A_Type)))));
560 elsif Needs_Simple_Initialization (Comp_Type) then
561 Set_Assignment_OK (Comp);
562 return New_List (
563 Make_Assignment_Statement (Loc,
564 Name => Comp,
565 Expression =>
566 Get_Simple_Init_Val
567 (Comp_Type, Nod, Component_Size (A_Type))));
569 else
570 Clean_Task_Names (Comp_Type, Proc_Id);
571 return
572 Build_Initialization_Call
573 (Loc, Comp, Comp_Type,
574 In_Init_Proc => True,
575 Enclos_Type => A_Type);
576 end if;
577 end Init_Component;
579 ------------------------
580 -- Init_One_Dimension --
581 ------------------------
583 function Init_One_Dimension (N : Int) return List_Id is
584 Index : Entity_Id;
586 begin
587 -- If the component does not need initializing, then there is nothing
588 -- to do here, so we return a null body. This occurs when generating
589 -- the dummy Init_Proc needed for Initialize_Scalars processing.
591 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
592 and then not Needs_Simple_Initialization (Comp_Type)
593 and then not Has_Task (Comp_Type)
594 and then not Has_Default_Aspect (A_Type)
595 then
596 return New_List (Make_Null_Statement (Loc));
598 -- If all dimensions dealt with, we simply initialize the component
600 elsif N > Number_Dimensions (A_Type) then
601 return Init_Component;
603 -- Here we generate the required loop
605 else
606 Index :=
607 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
609 Append (New_Occurrence_Of (Index, Loc), Index_List);
611 return New_List (
612 Make_Implicit_Loop_Statement (Nod,
613 Identifier => Empty,
614 Iteration_Scheme =>
615 Make_Iteration_Scheme (Loc,
616 Loop_Parameter_Specification =>
617 Make_Loop_Parameter_Specification (Loc,
618 Defining_Identifier => Index,
619 Discrete_Subtype_Definition =>
620 Make_Attribute_Reference (Loc,
621 Prefix =>
622 Make_Identifier (Loc, Name_uInit),
623 Attribute_Name => Name_Range,
624 Expressions => New_List (
625 Make_Integer_Literal (Loc, N))))),
626 Statements => Init_One_Dimension (N + 1)));
627 end if;
628 end Init_One_Dimension;
630 -- Start of processing for Build_Array_Init_Proc
632 begin
633 -- The init proc is created when analyzing the freeze node for the type,
634 -- but it properly belongs with the array type declaration. However, if
635 -- the freeze node is for a subtype of a type declared in another unit
636 -- it seems preferable to use the freeze node as the source location of
637 -- the init proc. In any case this is preferable for gcov usage, and
638 -- the Sloc is not otherwise used by the compiler.
640 if In_Open_Scopes (Scope (A_Type)) then
641 Loc := Sloc (A_Type);
642 else
643 Loc := Sloc (Nod);
644 end if;
646 -- Nothing to generate in the following cases:
648 -- 1. Initialization is suppressed for the type
649 -- 2. An initialization already exists for the base type
651 if Initialization_Suppressed (A_Type)
652 or else Present (Base_Init_Proc (A_Type))
653 then
654 return;
655 end if;
657 Index_List := New_List;
659 -- We need an initialization procedure if any of the following is true:
661 -- 1. The component type has an initialization procedure
662 -- 2. The component type needs simple initialization
663 -- 3. Tasks are present
664 -- 4. The type is marked as a public entity
665 -- 5. The array type has a Default_Component_Value aspect
667 -- The reason for the public entity test is to deal properly with the
668 -- Initialize_Scalars pragma. This pragma can be set in the client and
669 -- not in the declaring package, this means the client will make a call
670 -- to the initialization procedure (because one of conditions 1-3 must
671 -- apply in this case), and we must generate a procedure (even if it is
672 -- null) to satisfy the call in this case.
674 -- Exception: do not build an array init_proc for a type whose root
675 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
676 -- is no place to put the code, and in any case we handle initialization
677 -- of such types (in the Initialize_Scalars case, that's the only time
678 -- the issue arises) in a special manner anyway which does not need an
679 -- init_proc.
681 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
682 or else Needs_Simple_Initialization (Comp_Type)
683 or else Has_Task (Comp_Type)
684 or else Has_Default_Aspect (A_Type);
686 if Has_Default_Init
687 or else (not Restriction_Active (No_Initialize_Scalars)
688 and then Is_Public (A_Type)
689 and then not Is_Standard_String_Type (A_Type))
690 then
691 Proc_Id :=
692 Make_Defining_Identifier (Loc,
693 Chars => Make_Init_Proc_Name (A_Type));
695 -- If No_Default_Initialization restriction is active, then we don't
696 -- want to build an init_proc, but we need to mark that an init_proc
697 -- would be needed if this restriction was not active (so that we can
698 -- detect attempts to call it), so set a dummy init_proc in place.
699 -- This is only done though when actual default initialization is
700 -- needed (and not done when only Is_Public is True), since otherwise
701 -- objects such as arrays of scalars could be wrongly flagged as
702 -- violating the restriction.
704 if Restriction_Active (No_Default_Initialization) then
705 if Has_Default_Init then
706 Set_Init_Proc (A_Type, Proc_Id);
707 end if;
709 return;
710 end if;
712 Body_Stmts := Init_One_Dimension (1);
714 Discard_Node (
715 Make_Subprogram_Body (Loc,
716 Specification =>
717 Make_Procedure_Specification (Loc,
718 Defining_Unit_Name => Proc_Id,
719 Parameter_Specifications => Init_Formals (A_Type)),
720 Declarations => New_List,
721 Handled_Statement_Sequence =>
722 Make_Handled_Sequence_Of_Statements (Loc,
723 Statements => Body_Stmts)));
725 Set_Ekind (Proc_Id, E_Procedure);
726 Set_Is_Public (Proc_Id, Is_Public (A_Type));
727 Set_Is_Internal (Proc_Id);
728 Set_Has_Completion (Proc_Id);
730 if not Debug_Generated_Code then
731 Set_Debug_Info_Off (Proc_Id);
732 end if;
734 -- Set Inlined on Init_Proc if it is set on the Init_Proc of the
735 -- component type itself (see also Build_Record_Init_Proc).
737 Set_Is_Inlined (Proc_Id, Inline_Init_Proc (Comp_Type));
739 -- Associate Init_Proc with type, and determine if the procedure
740 -- is null (happens because of the Initialize_Scalars pragma case,
741 -- where we have to generate a null procedure in case it is called
742 -- by a client with Initialize_Scalars set). Such procedures have
743 -- to be generated, but do not have to be called, so we mark them
744 -- as null to suppress the call.
746 Set_Init_Proc (A_Type, Proc_Id);
748 if List_Length (Body_Stmts) = 1
750 -- We must skip SCIL nodes because they may have been added to this
751 -- list by Insert_Actions.
753 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
754 then
755 Set_Is_Null_Init_Proc (Proc_Id);
757 else
758 -- Try to build a static aggregate to statically initialize
759 -- objects of the type. This can only be done for constrained
760 -- one-dimensional arrays with static bounds.
762 Set_Static_Initialization
763 (Proc_Id,
764 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
765 end if;
766 end if;
767 end Build_Array_Init_Proc;
769 --------------------------------
770 -- Build_Discr_Checking_Funcs --
771 --------------------------------
773 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
774 Rec_Id : Entity_Id;
775 Loc : Source_Ptr;
776 Enclosing_Func_Id : Entity_Id;
777 Sequence : Nat := 1;
778 Type_Def : Node_Id;
779 V : Node_Id;
781 function Build_Case_Statement
782 (Case_Id : Entity_Id;
783 Variant : Node_Id) return Node_Id;
784 -- Build a case statement containing only two alternatives. The first
785 -- alternative corresponds exactly to the discrete choices given on the
786 -- variant with contains the components that we are generating the
787 -- checks for. If the discriminant is one of these return False. The
788 -- second alternative is an OTHERS choice that will return True
789 -- indicating the discriminant did not match.
791 function Build_Dcheck_Function
792 (Case_Id : Entity_Id;
793 Variant : Node_Id) return Entity_Id;
794 -- Build the discriminant checking function for a given variant
796 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
797 -- Builds the discriminant checking function for each variant of the
798 -- given variant part of the record type.
800 --------------------------
801 -- Build_Case_Statement --
802 --------------------------
804 function Build_Case_Statement
805 (Case_Id : Entity_Id;
806 Variant : Node_Id) return Node_Id
808 Alt_List : constant List_Id := New_List;
809 Actuals_List : List_Id;
810 Case_Node : Node_Id;
811 Case_Alt_Node : Node_Id;
812 Choice : Node_Id;
813 Choice_List : List_Id;
814 D : Entity_Id;
815 Return_Node : Node_Id;
817 begin
818 Case_Node := New_Node (N_Case_Statement, Loc);
820 -- Replace the discriminant which controls the variant with the name
821 -- of the formal of the checking function.
823 Set_Expression (Case_Node, Make_Identifier (Loc, Chars (Case_Id)));
825 Choice := First (Discrete_Choices (Variant));
827 if Nkind (Choice) = N_Others_Choice then
828 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
829 else
830 Choice_List := New_Copy_List (Discrete_Choices (Variant));
831 end if;
833 if not Is_Empty_List (Choice_List) then
834 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
835 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
837 -- In case this is a nested variant, we need to return the result
838 -- of the discriminant checking function for the immediately
839 -- enclosing variant.
841 if Present (Enclosing_Func_Id) then
842 Actuals_List := New_List;
844 D := First_Discriminant (Rec_Id);
845 while Present (D) loop
846 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
847 Next_Discriminant (D);
848 end loop;
850 Return_Node :=
851 Make_Simple_Return_Statement (Loc,
852 Expression =>
853 Make_Function_Call (Loc,
854 Name =>
855 New_Occurrence_Of (Enclosing_Func_Id, Loc),
856 Parameter_Associations =>
857 Actuals_List));
859 else
860 Return_Node :=
861 Make_Simple_Return_Statement (Loc,
862 Expression =>
863 New_Occurrence_Of (Standard_False, Loc));
864 end if;
866 Set_Statements (Case_Alt_Node, New_List (Return_Node));
867 Append (Case_Alt_Node, Alt_List);
868 end if;
870 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
871 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
872 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
874 Return_Node :=
875 Make_Simple_Return_Statement (Loc,
876 Expression =>
877 New_Occurrence_Of (Standard_True, Loc));
879 Set_Statements (Case_Alt_Node, New_List (Return_Node));
880 Append (Case_Alt_Node, Alt_List);
882 Set_Alternatives (Case_Node, Alt_List);
883 return Case_Node;
884 end Build_Case_Statement;
886 ---------------------------
887 -- Build_Dcheck_Function --
888 ---------------------------
890 function Build_Dcheck_Function
891 (Case_Id : Entity_Id;
892 Variant : Node_Id) return Entity_Id
894 Body_Node : Node_Id;
895 Func_Id : Entity_Id;
896 Parameter_List : List_Id;
897 Spec_Node : Node_Id;
899 begin
900 Body_Node := New_Node (N_Subprogram_Body, Loc);
901 Sequence := Sequence + 1;
903 Func_Id :=
904 Make_Defining_Identifier (Loc,
905 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
906 Set_Is_Discriminant_Check_Function (Func_Id);
908 Spec_Node := New_Node (N_Function_Specification, Loc);
909 Set_Defining_Unit_Name (Spec_Node, Func_Id);
911 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
913 Set_Parameter_Specifications (Spec_Node, Parameter_List);
914 Set_Result_Definition (Spec_Node,
915 New_Occurrence_Of (Standard_Boolean, Loc));
916 Set_Specification (Body_Node, Spec_Node);
917 Set_Declarations (Body_Node, New_List);
919 Set_Handled_Statement_Sequence (Body_Node,
920 Make_Handled_Sequence_Of_Statements (Loc,
921 Statements => New_List (
922 Build_Case_Statement (Case_Id, Variant))));
924 Set_Ekind (Func_Id, E_Function);
925 Set_Mechanism (Func_Id, Default_Mechanism);
926 Set_Is_Inlined (Func_Id, True);
927 Set_Is_Pure (Func_Id, True);
928 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
929 Set_Is_Internal (Func_Id, True);
931 if not Debug_Generated_Code then
932 Set_Debug_Info_Off (Func_Id);
933 end if;
935 Analyze (Body_Node);
937 Append_Freeze_Action (Rec_Id, Body_Node);
938 Set_Dcheck_Function (Variant, Func_Id);
939 return Func_Id;
940 end Build_Dcheck_Function;
942 ----------------------------
943 -- Build_Dcheck_Functions --
944 ----------------------------
946 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
947 Component_List_Node : Node_Id;
948 Decl : Entity_Id;
949 Discr_Name : Entity_Id;
950 Func_Id : Entity_Id;
951 Variant : Node_Id;
952 Saved_Enclosing_Func_Id : Entity_Id;
954 begin
955 -- Build the discriminant-checking function for each variant, and
956 -- label all components of that variant with the function's name.
957 -- We only Generate a discriminant-checking function when the
958 -- variant is not empty, to prevent the creation of dead code.
960 Discr_Name := Entity (Name (Variant_Part_Node));
961 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
963 while Present (Variant) loop
964 Component_List_Node := Component_List (Variant);
966 if not Null_Present (Component_List_Node) then
967 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
969 Decl :=
970 First_Non_Pragma (Component_Items (Component_List_Node));
971 while Present (Decl) loop
972 Set_Discriminant_Checking_Func
973 (Defining_Identifier (Decl), Func_Id);
974 Next_Non_Pragma (Decl);
975 end loop;
977 if Present (Variant_Part (Component_List_Node)) then
978 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
979 Enclosing_Func_Id := Func_Id;
980 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
981 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
982 end if;
983 end if;
985 Next_Non_Pragma (Variant);
986 end loop;
987 end Build_Dcheck_Functions;
989 -- Start of processing for Build_Discr_Checking_Funcs
991 begin
992 -- Only build if not done already
994 if not Discr_Check_Funcs_Built (N) then
995 Type_Def := Type_Definition (N);
997 if Nkind (Type_Def) = N_Record_Definition then
998 if No (Component_List (Type_Def)) then -- null record.
999 return;
1000 else
1001 V := Variant_Part (Component_List (Type_Def));
1002 end if;
1004 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1005 if No (Component_List (Record_Extension_Part (Type_Def))) then
1006 return;
1007 else
1008 V := Variant_Part
1009 (Component_List (Record_Extension_Part (Type_Def)));
1010 end if;
1011 end if;
1013 Rec_Id := Defining_Identifier (N);
1015 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1016 Loc := Sloc (N);
1017 Enclosing_Func_Id := Empty;
1018 Build_Dcheck_Functions (V);
1019 end if;
1021 Set_Discr_Check_Funcs_Built (N);
1022 end if;
1023 end Build_Discr_Checking_Funcs;
1025 --------------------------------
1026 -- Build_Discriminant_Formals --
1027 --------------------------------
1029 function Build_Discriminant_Formals
1030 (Rec_Id : Entity_Id;
1031 Use_Dl : Boolean) return List_Id
1033 Loc : Source_Ptr := Sloc (Rec_Id);
1034 Parameter_List : constant List_Id := New_List;
1035 D : Entity_Id;
1036 Formal : Entity_Id;
1037 Formal_Type : Entity_Id;
1038 Param_Spec_Node : Node_Id;
1040 begin
1041 if Has_Discriminants (Rec_Id) then
1042 D := First_Discriminant (Rec_Id);
1043 while Present (D) loop
1044 Loc := Sloc (D);
1046 if Use_Dl then
1047 Formal := Discriminal (D);
1048 Formal_Type := Etype (Formal);
1049 else
1050 Formal := Make_Defining_Identifier (Loc, Chars (D));
1051 Formal_Type := Etype (D);
1052 end if;
1054 Param_Spec_Node :=
1055 Make_Parameter_Specification (Loc,
1056 Defining_Identifier => Formal,
1057 Parameter_Type =>
1058 New_Occurrence_Of (Formal_Type, Loc));
1059 Append (Param_Spec_Node, Parameter_List);
1060 Next_Discriminant (D);
1061 end loop;
1062 end if;
1064 return Parameter_List;
1065 end Build_Discriminant_Formals;
1067 --------------------------------------
1068 -- Build_Equivalent_Array_Aggregate --
1069 --------------------------------------
1071 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1072 Loc : constant Source_Ptr := Sloc (T);
1073 Comp_Type : constant Entity_Id := Component_Type (T);
1074 Index_Type : constant Entity_Id := Etype (First_Index (T));
1075 Proc : constant Entity_Id := Base_Init_Proc (T);
1076 Lo, Hi : Node_Id;
1077 Aggr : Node_Id;
1078 Expr : Node_Id;
1080 begin
1081 if not Is_Constrained (T)
1082 or else Number_Dimensions (T) > 1
1083 or else No (Proc)
1084 then
1085 Initialization_Warning (T);
1086 return Empty;
1087 end if;
1089 Lo := Type_Low_Bound (Index_Type);
1090 Hi := Type_High_Bound (Index_Type);
1092 if not Compile_Time_Known_Value (Lo)
1093 or else not Compile_Time_Known_Value (Hi)
1094 then
1095 Initialization_Warning (T);
1096 return Empty;
1097 end if;
1099 if Is_Record_Type (Comp_Type)
1100 and then Present (Base_Init_Proc (Comp_Type))
1101 then
1102 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1104 if No (Expr) then
1105 Initialization_Warning (T);
1106 return Empty;
1107 end if;
1109 else
1110 Initialization_Warning (T);
1111 return Empty;
1112 end if;
1114 Aggr := Make_Aggregate (Loc, No_List, New_List);
1115 Set_Etype (Aggr, T);
1116 Set_Aggregate_Bounds (Aggr,
1117 Make_Range (Loc,
1118 Low_Bound => New_Copy (Lo),
1119 High_Bound => New_Copy (Hi)));
1120 Set_Parent (Aggr, Parent (Proc));
1122 Append_To (Component_Associations (Aggr),
1123 Make_Component_Association (Loc,
1124 Choices =>
1125 New_List (
1126 Make_Range (Loc,
1127 Low_Bound => New_Copy (Lo),
1128 High_Bound => New_Copy (Hi))),
1129 Expression => Expr));
1131 if Static_Array_Aggregate (Aggr) then
1132 return Aggr;
1133 else
1134 Initialization_Warning (T);
1135 return Empty;
1136 end if;
1137 end Build_Equivalent_Array_Aggregate;
1139 ---------------------------------------
1140 -- Build_Equivalent_Record_Aggregate --
1141 ---------------------------------------
1143 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1144 Agg : Node_Id;
1145 Comp : Entity_Id;
1146 Comp_Type : Entity_Id;
1148 -- Start of processing for Build_Equivalent_Record_Aggregate
1150 begin
1151 if not Is_Record_Type (T)
1152 or else Has_Discriminants (T)
1153 or else Is_Limited_Type (T)
1154 or else Has_Non_Standard_Rep (T)
1155 then
1156 Initialization_Warning (T);
1157 return Empty;
1158 end if;
1160 Comp := First_Component (T);
1162 -- A null record needs no warning
1164 if No (Comp) then
1165 return Empty;
1166 end if;
1168 while Present (Comp) loop
1170 -- Array components are acceptable if initialized by a positional
1171 -- aggregate with static components.
1173 if Is_Array_Type (Etype (Comp)) then
1174 Comp_Type := Component_Type (Etype (Comp));
1176 if Nkind (Parent (Comp)) /= N_Component_Declaration
1177 or else No (Expression (Parent (Comp)))
1178 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1179 then
1180 Initialization_Warning (T);
1181 return Empty;
1183 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1184 and then
1185 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1186 or else
1187 not Compile_Time_Known_Value (Type_High_Bound (Comp_Type)))
1188 then
1189 Initialization_Warning (T);
1190 return Empty;
1192 elsif
1193 not Static_Array_Aggregate (Expression (Parent (Comp)))
1194 then
1195 Initialization_Warning (T);
1196 return Empty;
1197 end if;
1199 elsif Is_Scalar_Type (Etype (Comp)) then
1200 Comp_Type := Etype (Comp);
1202 if Nkind (Parent (Comp)) /= N_Component_Declaration
1203 or else No (Expression (Parent (Comp)))
1204 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1205 or else not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1206 or else not
1207 Compile_Time_Known_Value (Type_High_Bound (Comp_Type))
1208 then
1209 Initialization_Warning (T);
1210 return Empty;
1211 end if;
1213 -- For now, other types are excluded
1215 else
1216 Initialization_Warning (T);
1217 return Empty;
1218 end if;
1220 Next_Component (Comp);
1221 end loop;
1223 -- All components have static initialization. Build positional aggregate
1224 -- from the given expressions or defaults.
1226 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1227 Set_Parent (Agg, Parent (T));
1229 Comp := First_Component (T);
1230 while Present (Comp) loop
1231 Append
1232 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1233 Next_Component (Comp);
1234 end loop;
1236 Analyze_And_Resolve (Agg, T);
1237 return Agg;
1238 end Build_Equivalent_Record_Aggregate;
1240 -------------------------------
1241 -- Build_Initialization_Call --
1242 -------------------------------
1244 -- References to a discriminant inside the record type declaration can
1245 -- appear either in the subtype_indication to constrain a record or an
1246 -- array, or as part of a larger expression given for the initial value
1247 -- of a component. In both of these cases N appears in the record
1248 -- initialization procedure and needs to be replaced by the formal
1249 -- parameter of the initialization procedure which corresponds to that
1250 -- discriminant.
1252 -- In the example below, references to discriminants D1 and D2 in proc_1
1253 -- are replaced by references to formals with the same name
1254 -- (discriminals)
1256 -- A similar replacement is done for calls to any record initialization
1257 -- procedure for any components that are themselves of a record type.
1259 -- type R (D1, D2 : Integer) is record
1260 -- X : Integer := F * D1;
1261 -- Y : Integer := F * D2;
1262 -- end record;
1264 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1265 -- begin
1266 -- Out_2.D1 := D1;
1267 -- Out_2.D2 := D2;
1268 -- Out_2.X := F * D1;
1269 -- Out_2.Y := F * D2;
1270 -- end;
1272 function Build_Initialization_Call
1273 (Loc : Source_Ptr;
1274 Id_Ref : Node_Id;
1275 Typ : Entity_Id;
1276 In_Init_Proc : Boolean := False;
1277 Enclos_Type : Entity_Id := Empty;
1278 Discr_Map : Elist_Id := New_Elmt_List;
1279 With_Default_Init : Boolean := False;
1280 Constructor_Ref : Node_Id := Empty) return List_Id
1282 Res : constant List_Id := New_List;
1284 Full_Type : Entity_Id;
1286 procedure Check_Predicated_Discriminant
1287 (Val : Node_Id;
1288 Discr : Entity_Id);
1289 -- Discriminants whose subtypes have predicates are checked in two
1290 -- cases:
1291 -- a) When an object is default-initialized and assertions are enabled
1292 -- we check that the value of the discriminant obeys the predicate.
1294 -- b) In all cases, if the discriminant controls a variant and the
1295 -- variant has no others_choice, Constraint_Error must be raised if
1296 -- the predicate is violated, because there is no variant covered
1297 -- by the illegal discriminant value.
1299 -----------------------------------
1300 -- Check_Predicated_Discriminant --
1301 -----------------------------------
1303 procedure Check_Predicated_Discriminant
1304 (Val : Node_Id;
1305 Discr : Entity_Id)
1307 Typ : constant Entity_Id := Etype (Discr);
1309 procedure Check_Missing_Others (V : Node_Id);
1310 -- ???
1312 --------------------------
1313 -- Check_Missing_Others --
1314 --------------------------
1316 procedure Check_Missing_Others (V : Node_Id) is
1317 Alt : Node_Id;
1318 Choice : Node_Id;
1319 Last_Var : Node_Id;
1321 begin
1322 Last_Var := Last_Non_Pragma (Variants (V));
1323 Choice := First (Discrete_Choices (Last_Var));
1325 -- An others_choice is added during expansion for gcc use, but
1326 -- does not cover the illegality.
1328 if Entity (Name (V)) = Discr then
1329 if Present (Choice)
1330 and then (Nkind (Choice) /= N_Others_Choice
1331 or else not Comes_From_Source (Choice))
1332 then
1333 Check_Expression_Against_Static_Predicate (Val, Typ);
1335 if not Is_Static_Expression (Val) then
1336 Prepend_To (Res,
1337 Make_Raise_Constraint_Error (Loc,
1338 Condition =>
1339 Make_Op_Not (Loc,
1340 Right_Opnd => Make_Predicate_Call (Typ, Val)),
1341 Reason => CE_Invalid_Data));
1342 end if;
1343 end if;
1344 end if;
1346 -- Check whether some nested variant is ruled by the predicated
1347 -- discriminant.
1349 Alt := First (Variants (V));
1350 while Present (Alt) loop
1351 if Nkind (Alt) = N_Variant
1352 and then Present (Variant_Part (Component_List (Alt)))
1353 then
1354 Check_Missing_Others
1355 (Variant_Part (Component_List (Alt)));
1356 end if;
1358 Next (Alt);
1359 end loop;
1360 end Check_Missing_Others;
1362 -- Local variables
1364 Def : Node_Id;
1366 -- Start of processing for Check_Predicated_Discriminant
1368 begin
1369 if Ekind (Base_Type (Full_Type)) = E_Record_Type then
1370 Def := Type_Definition (Parent (Base_Type (Full_Type)));
1371 else
1372 return;
1373 end if;
1375 if Policy_In_Effect (Name_Assert) = Name_Check
1376 and then not Predicates_Ignored (Etype (Discr))
1377 then
1378 Prepend_To (Res, Make_Predicate_Check (Typ, Val));
1379 end if;
1381 -- If discriminant controls a variant, verify that predicate is
1382 -- obeyed or else an Others_Choice is present.
1384 if Nkind (Def) = N_Record_Definition
1385 and then Present (Variant_Part (Component_List (Def)))
1386 and then Policy_In_Effect (Name_Assert) = Name_Ignore
1387 then
1388 Check_Missing_Others (Variant_Part (Component_List (Def)));
1389 end if;
1390 end Check_Predicated_Discriminant;
1392 -- Local variables
1394 Arg : Node_Id;
1395 Args : List_Id;
1396 Decls : List_Id;
1397 Decl : Node_Id;
1398 Discr : Entity_Id;
1399 First_Arg : Node_Id;
1400 Full_Init_Type : Entity_Id;
1401 Init_Call : Node_Id;
1402 Init_Type : Entity_Id;
1403 Proc : Entity_Id;
1405 -- Start of processing for Build_Initialization_Call
1407 begin
1408 pragma Assert (Constructor_Ref = Empty
1409 or else Is_CPP_Constructor_Call (Constructor_Ref));
1411 if No (Constructor_Ref) then
1412 Proc := Base_Init_Proc (Typ);
1413 else
1414 Proc := Base_Init_Proc (Typ, Entity (Name (Constructor_Ref)));
1415 end if;
1417 pragma Assert (Present (Proc));
1418 Init_Type := Etype (First_Formal (Proc));
1419 Full_Init_Type := Underlying_Type (Init_Type);
1421 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1422 -- is active (in which case we make the call anyway, since in the
1423 -- actual compiled client it may be non null).
1425 if Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars then
1426 return Empty_List;
1428 -- Nothing to do for an array of controlled components that have only
1429 -- the inherited Initialize primitive. This is a useful optimization
1430 -- for CodePeer.
1432 elsif Is_Trivial_Subprogram (Proc)
1433 and then Is_Array_Type (Full_Init_Type)
1434 then
1435 return New_List (Make_Null_Statement (Loc));
1436 end if;
1438 -- Use the [underlying] full view when dealing with a private type. This
1439 -- may require several steps depending on derivations.
1441 Full_Type := Typ;
1442 loop
1443 if Is_Private_Type (Full_Type) then
1444 if Present (Full_View (Full_Type)) then
1445 Full_Type := Full_View (Full_Type);
1447 elsif Present (Underlying_Full_View (Full_Type)) then
1448 Full_Type := Underlying_Full_View (Full_Type);
1450 -- When a private type acts as a generic actual and lacks a full
1451 -- view, use the base type.
1453 elsif Is_Generic_Actual_Type (Full_Type) then
1454 Full_Type := Base_Type (Full_Type);
1456 elsif Ekind (Full_Type) = E_Private_Subtype
1457 and then (not Has_Discriminants (Full_Type)
1458 or else No (Discriminant_Constraint (Full_Type)))
1459 then
1460 Full_Type := Etype (Full_Type);
1462 -- The loop has recovered the [underlying] full view, stop the
1463 -- traversal.
1465 else
1466 exit;
1467 end if;
1469 -- The type is not private, nothing to do
1471 else
1472 exit;
1473 end if;
1474 end loop;
1476 -- If Typ is derived, the procedure is the initialization procedure for
1477 -- the root type. Wrap the argument in an conversion to make it type
1478 -- honest. Actually it isn't quite type honest, because there can be
1479 -- conflicts of views in the private type case. That is why we set
1480 -- Conversion_OK in the conversion node.
1482 if (Is_Record_Type (Typ)
1483 or else Is_Array_Type (Typ)
1484 or else Is_Private_Type (Typ))
1485 and then Init_Type /= Base_Type (Typ)
1486 then
1487 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1488 Set_Etype (First_Arg, Init_Type);
1490 else
1491 First_Arg := Id_Ref;
1492 end if;
1494 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1496 -- In the tasks case, add _Master as the value of the _Master parameter
1497 -- and _Chain as the value of the _Chain parameter. At the outer level,
1498 -- these will be variables holding the corresponding values obtained
1499 -- from GNARL. At inner levels, they will be the parameters passed down
1500 -- through the outer routines.
1502 if Has_Task (Full_Type) then
1503 if Restriction_Active (No_Task_Hierarchy) then
1504 Append_To (Args,
1505 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
1506 else
1507 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1508 end if;
1510 -- Add _Chain (not done for sequential elaboration policy, see
1511 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
1513 if Partition_Elaboration_Policy /= 'S' then
1514 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1515 end if;
1517 -- Ada 2005 (AI-287): In case of default initialized components
1518 -- with tasks, we generate a null string actual parameter.
1519 -- This is just a workaround that must be improved later???
1521 if With_Default_Init then
1522 Append_To (Args,
1523 Make_String_Literal (Loc,
1524 Strval => ""));
1526 else
1527 Decls :=
1528 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1529 Decl := Last (Decls);
1531 Append_To (Args,
1532 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1533 Append_List (Decls, Res);
1534 end if;
1536 else
1537 Decls := No_List;
1538 Decl := Empty;
1539 end if;
1541 -- Add discriminant values if discriminants are present
1543 if Has_Discriminants (Full_Init_Type) then
1544 Discr := First_Discriminant (Full_Init_Type);
1545 while Present (Discr) loop
1547 -- If this is a discriminated concurrent type, the init_proc
1548 -- for the corresponding record is being called. Use that type
1549 -- directly to find the discriminant value, to handle properly
1550 -- intervening renamed discriminants.
1552 declare
1553 T : Entity_Id := Full_Type;
1555 begin
1556 if Is_Protected_Type (T) then
1557 T := Corresponding_Record_Type (T);
1558 end if;
1560 Arg :=
1561 Get_Discriminant_Value (
1562 Discr,
1564 Discriminant_Constraint (Full_Type));
1565 end;
1567 -- If the target has access discriminants, and is constrained by
1568 -- an access to the enclosing construct, i.e. a current instance,
1569 -- replace the reference to the type by a reference to the object.
1571 if Nkind (Arg) = N_Attribute_Reference
1572 and then Is_Access_Type (Etype (Arg))
1573 and then Is_Entity_Name (Prefix (Arg))
1574 and then Is_Type (Entity (Prefix (Arg)))
1575 then
1576 Arg :=
1577 Make_Attribute_Reference (Loc,
1578 Prefix => New_Copy (Prefix (Id_Ref)),
1579 Attribute_Name => Name_Unrestricted_Access);
1581 elsif In_Init_Proc then
1583 -- Replace any possible references to the discriminant in the
1584 -- call to the record initialization procedure with references
1585 -- to the appropriate formal parameter.
1587 if Nkind (Arg) = N_Identifier
1588 and then Ekind (Entity (Arg)) = E_Discriminant
1589 then
1590 Arg := New_Occurrence_Of (Discriminal (Entity (Arg)), Loc);
1592 -- Otherwise make a copy of the default expression. Note that
1593 -- we use the current Sloc for this, because we do not want the
1594 -- call to appear to be at the declaration point. Within the
1595 -- expression, replace discriminants with their discriminals.
1597 else
1598 Arg :=
1599 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1600 end if;
1602 else
1603 if Is_Constrained (Full_Type) then
1604 Arg := Duplicate_Subexpr_No_Checks (Arg);
1605 else
1606 -- The constraints come from the discriminant default exps,
1607 -- they must be reevaluated, so we use New_Copy_Tree but we
1608 -- ensure the proper Sloc (for any embedded calls).
1609 -- In addition, if a predicate check is needed on the value
1610 -- of the discriminant, insert it ahead of the call.
1612 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1613 end if;
1615 if Has_Predicates (Etype (Discr)) then
1616 Check_Predicated_Discriminant (Arg, Discr);
1617 end if;
1618 end if;
1620 -- Ada 2005 (AI-287): In case of default initialized components,
1621 -- if the component is constrained with a discriminant of the
1622 -- enclosing type, we need to generate the corresponding selected
1623 -- component node to access the discriminant value. In other cases
1624 -- this is not required, either because we are inside the init
1625 -- proc and we use the corresponding formal, or else because the
1626 -- component is constrained by an expression.
1628 if With_Default_Init
1629 and then Nkind (Id_Ref) = N_Selected_Component
1630 and then Nkind (Arg) = N_Identifier
1631 and then Ekind (Entity (Arg)) = E_Discriminant
1632 then
1633 Append_To (Args,
1634 Make_Selected_Component (Loc,
1635 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1636 Selector_Name => Arg));
1637 else
1638 Append_To (Args, Arg);
1639 end if;
1641 Next_Discriminant (Discr);
1642 end loop;
1643 end if;
1645 -- If this is a call to initialize the parent component of a derived
1646 -- tagged type, indicate that the tag should not be set in the parent.
1648 if Is_Tagged_Type (Full_Init_Type)
1649 and then not Is_CPP_Class (Full_Init_Type)
1650 and then Nkind (Id_Ref) = N_Selected_Component
1651 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1652 then
1653 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1655 elsif Present (Constructor_Ref) then
1656 Append_List_To (Args,
1657 New_Copy_List (Parameter_Associations (Constructor_Ref)));
1658 end if;
1660 Append_To (Res,
1661 Make_Procedure_Call_Statement (Loc,
1662 Name => New_Occurrence_Of (Proc, Loc),
1663 Parameter_Associations => Args));
1665 if Needs_Finalization (Typ)
1666 and then Nkind (Id_Ref) = N_Selected_Component
1667 then
1668 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1669 Init_Call :=
1670 Make_Init_Call
1671 (Obj_Ref => New_Copy_Tree (First_Arg),
1672 Typ => Typ);
1674 -- Guard against a missing [Deep_]Initialize when the type was not
1675 -- properly frozen.
1677 if Present (Init_Call) then
1678 Append_To (Res, Init_Call);
1679 end if;
1680 end if;
1681 end if;
1683 return Res;
1685 exception
1686 when RE_Not_Available =>
1687 return Empty_List;
1688 end Build_Initialization_Call;
1690 ----------------------------
1691 -- Build_Record_Init_Proc --
1692 ----------------------------
1694 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id) is
1695 Decls : constant List_Id := New_List;
1696 Discr_Map : constant Elist_Id := New_Elmt_List;
1697 Loc : constant Source_Ptr := Sloc (Rec_Ent);
1698 Counter : Nat := 0;
1699 Proc_Id : Entity_Id;
1700 Rec_Type : Entity_Id;
1701 Set_Tag : Entity_Id := Empty;
1703 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1704 -- Build an assignment statement which assigns the default expression
1705 -- to its corresponding record component if defined. The left hand side
1706 -- of the assignment is marked Assignment_OK so that initialization of
1707 -- limited private records works correctly. This routine may also build
1708 -- an adjustment call if the component is controlled.
1710 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1711 -- If the record has discriminants, add assignment statements to
1712 -- Statement_List to initialize the discriminant values from the
1713 -- arguments of the initialization procedure.
1715 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1716 -- Build a list representing a sequence of statements which initialize
1717 -- components of the given component list. This may involve building
1718 -- case statements for the variant parts. Append any locally declared
1719 -- objects on list Decls.
1721 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1722 -- Given an untagged type-derivation that declares discriminants, e.g.
1724 -- type R (R1, R2 : Integer) is record ... end record;
1725 -- type D (D1 : Integer) is new R (1, D1);
1727 -- we make the _init_proc of D be
1729 -- procedure _init_proc (X : D; D1 : Integer) is
1730 -- begin
1731 -- _init_proc (R (X), 1, D1);
1732 -- end _init_proc;
1734 -- This function builds the call statement in this _init_proc.
1736 procedure Build_CPP_Init_Procedure;
1737 -- Build the tree corresponding to the procedure specification and body
1738 -- of the IC procedure that initializes the C++ part of the dispatch
1739 -- table of an Ada tagged type that is a derivation of a CPP type.
1740 -- Install it as the CPP_Init TSS.
1742 procedure Build_Init_Procedure;
1743 -- Build the tree corresponding to the procedure specification and body
1744 -- of the initialization procedure and install it as the _init TSS.
1746 procedure Build_Offset_To_Top_Functions;
1747 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1748 -- and body of Offset_To_Top, a function used in conjuction with types
1749 -- having secondary dispatch tables.
1751 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1752 -- Add range checks to components of discriminated records. S is a
1753 -- subtype indication of a record component. Check_List is a list
1754 -- to which the check actions are appended.
1756 function Component_Needs_Simple_Initialization
1757 (T : Entity_Id) return Boolean;
1758 -- Determine if a component needs simple initialization, given its type
1759 -- T. This routine is the same as Needs_Simple_Initialization except for
1760 -- components of type Tag and Interface_Tag. These two access types do
1761 -- not require initialization since they are explicitly initialized by
1762 -- other means.
1764 function Parent_Subtype_Renaming_Discrims return Boolean;
1765 -- Returns True for base types N that rename discriminants, else False
1767 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1768 -- Determine whether a record initialization procedure needs to be
1769 -- generated for the given record type.
1771 ----------------------
1772 -- Build_Assignment --
1773 ----------------------
1775 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1776 N_Loc : constant Source_Ptr := Sloc (N);
1777 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1779 Adj_Call : Node_Id;
1780 Exp : Node_Id := N;
1781 Kind : Node_Kind := Nkind (N);
1782 Lhs : Node_Id;
1783 Res : List_Id;
1785 function Replace_Discr_Ref (N : Node_Id) return Traverse_Result;
1786 -- Analysis of the aggregate has replaced discriminants by their
1787 -- corresponding discriminals, but these are irrelevant when the
1788 -- component has a mutable type and is initialized with an aggregate.
1789 -- Instead, they must be replaced by the values supplied in the
1790 -- aggregate, that will be assigned during the expansion of the
1791 -- assignment.
1793 -----------------------
1794 -- Replace_Discr_Ref --
1795 -----------------------
1797 function Replace_Discr_Ref (N : Node_Id) return Traverse_Result is
1798 Val : Node_Id;
1799 begin
1800 if Is_Entity_Name (N)
1801 and then Present (Entity (N))
1802 and then Is_Formal (Entity (N))
1803 and then Present (Discriminal_Link (Entity (N)))
1804 then
1805 Val :=
1806 Make_Selected_Component (N_Loc,
1807 Prefix => New_Copy_Tree (Lhs),
1808 Selector_Name => New_Occurrence_Of
1809 (Discriminal_Link (Entity (N)), N_Loc));
1810 if Present (Val) then
1811 Rewrite (N, New_Copy_Tree (Val));
1812 end if;
1813 end if;
1815 return OK;
1816 end Replace_Discr_Ref;
1818 procedure Replace_Discriminant_References is
1819 new Traverse_Proc (Replace_Discr_Ref);
1821 begin
1822 Lhs :=
1823 Make_Selected_Component (N_Loc,
1824 Prefix => Make_Identifier (Loc, Name_uInit),
1825 Selector_Name => New_Occurrence_Of (Id, N_Loc));
1826 Set_Assignment_OK (Lhs);
1828 if Nkind (Exp) = N_Aggregate
1829 and then Has_Discriminants (Typ)
1830 and then not Is_Constrained (Base_Type (Typ))
1831 then
1832 -- The aggregate may provide new values for the discriminants
1833 -- of the component, and other components may depend on those
1834 -- discriminants. Previous analysis of those expressions have
1835 -- replaced the discriminants by the formals of the initialization
1836 -- procedure for the type, but these are irrelevant in the
1837 -- enclosing initialization procedure: those discriminant
1838 -- references must be replaced by the values provided in the
1839 -- aggregate.
1841 Replace_Discriminant_References (Exp);
1842 end if;
1844 -- Case of an access attribute applied to the current instance.
1845 -- Replace the reference to the type by a reference to the actual
1846 -- object. (Note that this handles the case of the top level of
1847 -- the expression being given by such an attribute, but does not
1848 -- cover uses nested within an initial value expression. Nested
1849 -- uses are unlikely to occur in practice, but are theoretically
1850 -- possible.) It is not clear how to handle them without fully
1851 -- traversing the expression. ???
1853 if Kind = N_Attribute_Reference
1854 and then Nam_In (Attribute_Name (N), Name_Unchecked_Access,
1855 Name_Unrestricted_Access)
1856 and then Is_Entity_Name (Prefix (N))
1857 and then Is_Type (Entity (Prefix (N)))
1858 and then Entity (Prefix (N)) = Rec_Type
1859 then
1860 Exp :=
1861 Make_Attribute_Reference (N_Loc,
1862 Prefix =>
1863 Make_Identifier (N_Loc, Name_uInit),
1864 Attribute_Name => Name_Unrestricted_Access);
1865 end if;
1867 -- Take a copy of Exp to ensure that later copies of this component
1868 -- declaration in derived types see the original tree, not a node
1869 -- rewritten during expansion of the init_proc. If the copy contains
1870 -- itypes, the scope of the new itypes is the init_proc being built.
1872 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id);
1874 Res := New_List (
1875 Make_Assignment_Statement (Loc,
1876 Name => Lhs,
1877 Expression => Exp));
1879 Set_No_Ctrl_Actions (First (Res));
1881 -- Adjust the tag if tagged (because of possible view conversions).
1882 -- Suppress the tag adjustment when not Tagged_Type_Expansion because
1883 -- tags are represented implicitly in objects.
1885 if Is_Tagged_Type (Typ) and then Tagged_Type_Expansion then
1886 Append_To (Res,
1887 Make_Assignment_Statement (N_Loc,
1888 Name =>
1889 Make_Selected_Component (N_Loc,
1890 Prefix =>
1891 New_Copy_Tree (Lhs, New_Scope => Proc_Id),
1892 Selector_Name =>
1893 New_Occurrence_Of (First_Tag_Component (Typ), N_Loc)),
1895 Expression =>
1896 Unchecked_Convert_To (RTE (RE_Tag),
1897 New_Occurrence_Of
1898 (Node
1899 (First_Elmt
1900 (Access_Disp_Table (Underlying_Type (Typ)))),
1901 N_Loc))));
1902 end if;
1904 -- Adjust the component if controlled except if it is an aggregate
1905 -- that will be expanded inline.
1907 if Kind = N_Qualified_Expression then
1908 Kind := Nkind (Expression (N));
1909 end if;
1911 if Needs_Finalization (Typ)
1912 and then not (Nkind_In (Kind, N_Aggregate, N_Extension_Aggregate))
1913 and then not Is_Limited_View (Typ)
1914 then
1915 Adj_Call :=
1916 Make_Adjust_Call
1917 (Obj_Ref => New_Copy_Tree (Lhs),
1918 Typ => Etype (Id));
1920 -- Guard against a missing [Deep_]Adjust when the component type
1921 -- was not properly frozen.
1923 if Present (Adj_Call) then
1924 Append_To (Res, Adj_Call);
1925 end if;
1926 end if;
1928 -- If a component type has a predicate, add check to the component
1929 -- assignment. Discriminants are handled at the point of the call,
1930 -- which provides for a better error message.
1932 if Comes_From_Source (Exp)
1933 and then Has_Predicates (Typ)
1934 and then not Predicate_Checks_Suppressed (Empty)
1935 and then not Predicates_Ignored (Typ)
1936 then
1937 Append (Make_Predicate_Check (Typ, Exp), Res);
1938 end if;
1940 return Res;
1942 exception
1943 when RE_Not_Available =>
1944 return Empty_List;
1945 end Build_Assignment;
1947 ------------------------------------
1948 -- Build_Discriminant_Assignments --
1949 ------------------------------------
1951 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1952 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1953 D : Entity_Id;
1954 D_Loc : Source_Ptr;
1956 begin
1957 if Has_Discriminants (Rec_Type)
1958 and then not Is_Unchecked_Union (Rec_Type)
1959 then
1960 D := First_Discriminant (Rec_Type);
1961 while Present (D) loop
1963 -- Don't generate the assignment for discriminants in derived
1964 -- tagged types if the discriminant is a renaming of some
1965 -- ancestor discriminant. This initialization will be done
1966 -- when initializing the _parent field of the derived record.
1968 if Is_Tagged
1969 and then Present (Corresponding_Discriminant (D))
1970 then
1971 null;
1973 else
1974 D_Loc := Sloc (D);
1975 Append_List_To (Statement_List,
1976 Build_Assignment (D,
1977 New_Occurrence_Of (Discriminal (D), D_Loc)));
1978 end if;
1980 Next_Discriminant (D);
1981 end loop;
1982 end if;
1983 end Build_Discriminant_Assignments;
1985 --------------------------
1986 -- Build_Init_Call_Thru --
1987 --------------------------
1989 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1990 Parent_Proc : constant Entity_Id :=
1991 Base_Init_Proc (Etype (Rec_Type));
1993 Parent_Type : constant Entity_Id :=
1994 Etype (First_Formal (Parent_Proc));
1996 Uparent_Type : constant Entity_Id :=
1997 Underlying_Type (Parent_Type);
1999 First_Discr_Param : Node_Id;
2001 Arg : Node_Id;
2002 Args : List_Id;
2003 First_Arg : Node_Id;
2004 Parent_Discr : Entity_Id;
2005 Res : List_Id;
2007 begin
2008 -- First argument (_Init) is the object to be initialized.
2009 -- ??? not sure where to get a reasonable Loc for First_Arg
2011 First_Arg :=
2012 OK_Convert_To (Parent_Type,
2013 New_Occurrence_Of
2014 (Defining_Identifier (First (Parameters)), Loc));
2016 Set_Etype (First_Arg, Parent_Type);
2018 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
2020 -- In the tasks case,
2021 -- add _Master as the value of the _Master parameter
2022 -- add _Chain as the value of the _Chain parameter.
2023 -- add _Task_Name as the value of the _Task_Name parameter.
2024 -- At the outer level, these will be variables holding the
2025 -- corresponding values obtained from GNARL or the expander.
2027 -- At inner levels, they will be the parameters passed down through
2028 -- the outer routines.
2030 First_Discr_Param := Next (First (Parameters));
2032 if Has_Task (Rec_Type) then
2033 if Restriction_Active (No_Task_Hierarchy) then
2034 Append_To (Args,
2035 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
2036 else
2037 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
2038 end if;
2040 -- Add _Chain (not done for sequential elaboration policy, see
2041 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
2043 if Partition_Elaboration_Policy /= 'S' then
2044 Append_To (Args, Make_Identifier (Loc, Name_uChain));
2045 end if;
2047 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
2048 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
2049 end if;
2051 -- Append discriminant values
2053 if Has_Discriminants (Uparent_Type) then
2054 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2056 Parent_Discr := First_Discriminant (Uparent_Type);
2057 while Present (Parent_Discr) loop
2059 -- Get the initial value for this discriminant
2060 -- ??? needs to be cleaned up to use parent_Discr_Constr
2061 -- directly.
2063 declare
2064 Discr : Entity_Id :=
2065 First_Stored_Discriminant (Uparent_Type);
2067 Discr_Value : Elmt_Id :=
2068 First_Elmt (Stored_Constraint (Rec_Type));
2070 begin
2071 while Original_Record_Component (Parent_Discr) /= Discr loop
2072 Next_Stored_Discriminant (Discr);
2073 Next_Elmt (Discr_Value);
2074 end loop;
2076 Arg := Node (Discr_Value);
2077 end;
2079 -- Append it to the list
2081 if Nkind (Arg) = N_Identifier
2082 and then Ekind (Entity (Arg)) = E_Discriminant
2083 then
2084 Append_To (Args,
2085 New_Occurrence_Of (Discriminal (Entity (Arg)), Loc));
2087 -- Case of access discriminants. We replace the reference
2088 -- to the type by a reference to the actual object.
2090 -- Is above comment right??? Use of New_Copy below seems mighty
2091 -- suspicious ???
2093 else
2094 Append_To (Args, New_Copy (Arg));
2095 end if;
2097 Next_Discriminant (Parent_Discr);
2098 end loop;
2099 end if;
2101 Res :=
2102 New_List (
2103 Make_Procedure_Call_Statement (Loc,
2104 Name =>
2105 New_Occurrence_Of (Parent_Proc, Loc),
2106 Parameter_Associations => Args));
2108 return Res;
2109 end Build_Init_Call_Thru;
2111 -----------------------------------
2112 -- Build_Offset_To_Top_Functions --
2113 -----------------------------------
2115 procedure Build_Offset_To_Top_Functions is
2117 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2118 -- Generate:
2119 -- function Fxx (O : Address) return Storage_Offset is
2120 -- type Acc is access all <Typ>;
2121 -- begin
2122 -- return Acc!(O).Iface_Comp'Position;
2123 -- end Fxx;
2125 ----------------------------------
2126 -- Build_Offset_To_Top_Function --
2127 ----------------------------------
2129 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2130 Body_Node : Node_Id;
2131 Func_Id : Entity_Id;
2132 Spec_Node : Node_Id;
2133 Acc_Type : Entity_Id;
2135 begin
2136 Func_Id := Make_Temporary (Loc, 'F');
2137 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2139 -- Generate
2140 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2142 Spec_Node := New_Node (N_Function_Specification, Loc);
2143 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2144 Set_Parameter_Specifications (Spec_Node, New_List (
2145 Make_Parameter_Specification (Loc,
2146 Defining_Identifier =>
2147 Make_Defining_Identifier (Loc, Name_uO),
2148 In_Present => True,
2149 Parameter_Type =>
2150 New_Occurrence_Of (RTE (RE_Address), Loc))));
2151 Set_Result_Definition (Spec_Node,
2152 New_Occurrence_Of (RTE (RE_Storage_Offset), Loc));
2154 -- Generate
2155 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2156 -- begin
2157 -- return O.Iface_Comp'Position;
2158 -- end Fxx;
2160 Body_Node := New_Node (N_Subprogram_Body, Loc);
2161 Set_Specification (Body_Node, Spec_Node);
2163 Acc_Type := Make_Temporary (Loc, 'T');
2164 Set_Declarations (Body_Node, New_List (
2165 Make_Full_Type_Declaration (Loc,
2166 Defining_Identifier => Acc_Type,
2167 Type_Definition =>
2168 Make_Access_To_Object_Definition (Loc,
2169 All_Present => True,
2170 Null_Exclusion_Present => False,
2171 Constant_Present => False,
2172 Subtype_Indication =>
2173 New_Occurrence_Of (Rec_Type, Loc)))));
2175 Set_Handled_Statement_Sequence (Body_Node,
2176 Make_Handled_Sequence_Of_Statements (Loc,
2177 Statements => New_List (
2178 Make_Simple_Return_Statement (Loc,
2179 Expression =>
2180 Make_Attribute_Reference (Loc,
2181 Prefix =>
2182 Make_Selected_Component (Loc,
2183 Prefix =>
2184 Unchecked_Convert_To (Acc_Type,
2185 Make_Identifier (Loc, Name_uO)),
2186 Selector_Name =>
2187 New_Occurrence_Of (Iface_Comp, Loc)),
2188 Attribute_Name => Name_Position)))));
2190 Set_Ekind (Func_Id, E_Function);
2191 Set_Mechanism (Func_Id, Default_Mechanism);
2192 Set_Is_Internal (Func_Id, True);
2194 if not Debug_Generated_Code then
2195 Set_Debug_Info_Off (Func_Id);
2196 end if;
2198 Analyze (Body_Node);
2200 Append_Freeze_Action (Rec_Type, Body_Node);
2201 end Build_Offset_To_Top_Function;
2203 -- Local variables
2205 Iface_Comp : Node_Id;
2206 Iface_Comp_Elmt : Elmt_Id;
2207 Ifaces_Comp_List : Elist_Id;
2209 -- Start of processing for Build_Offset_To_Top_Functions
2211 begin
2212 -- Offset_To_Top_Functions are built only for derivations of types
2213 -- with discriminants that cover interface types.
2214 -- Nothing is needed either in case of virtual targets, since
2215 -- interfaces are handled directly by the target.
2217 if not Is_Tagged_Type (Rec_Type)
2218 or else Etype (Rec_Type) = Rec_Type
2219 or else not Has_Discriminants (Etype (Rec_Type))
2220 or else not Tagged_Type_Expansion
2221 then
2222 return;
2223 end if;
2225 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2227 -- For each interface type with secondary dispatch table we generate
2228 -- the Offset_To_Top_Functions (required to displace the pointer in
2229 -- interface conversions)
2231 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2232 while Present (Iface_Comp_Elmt) loop
2233 Iface_Comp := Node (Iface_Comp_Elmt);
2234 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2236 -- If the interface is a parent of Rec_Type it shares the primary
2237 -- dispatch table and hence there is no need to build the function
2239 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type,
2240 Use_Full_View => True)
2241 then
2242 Build_Offset_To_Top_Function (Iface_Comp);
2243 end if;
2245 Next_Elmt (Iface_Comp_Elmt);
2246 end loop;
2247 end Build_Offset_To_Top_Functions;
2249 ------------------------------
2250 -- Build_CPP_Init_Procedure --
2251 ------------------------------
2253 procedure Build_CPP_Init_Procedure is
2254 Body_Node : Node_Id;
2255 Body_Stmts : List_Id;
2256 Flag_Id : Entity_Id;
2257 Handled_Stmt_Node : Node_Id;
2258 Init_Tags_List : List_Id;
2259 Proc_Id : Entity_Id;
2260 Proc_Spec_Node : Node_Id;
2262 begin
2263 -- Check cases requiring no IC routine
2265 if not Is_CPP_Class (Root_Type (Rec_Type))
2266 or else Is_CPP_Class (Rec_Type)
2267 or else CPP_Num_Prims (Rec_Type) = 0
2268 or else not Tagged_Type_Expansion
2269 or else No_Run_Time_Mode
2270 then
2271 return;
2272 end if;
2274 -- Generate:
2276 -- Flag : Boolean := False;
2278 -- procedure Typ_IC is
2279 -- begin
2280 -- if not Flag then
2281 -- Copy C++ dispatch table slots from parent
2282 -- Update C++ slots of overridden primitives
2283 -- end if;
2284 -- end;
2286 Flag_Id := Make_Temporary (Loc, 'F');
2288 Append_Freeze_Action (Rec_Type,
2289 Make_Object_Declaration (Loc,
2290 Defining_Identifier => Flag_Id,
2291 Object_Definition =>
2292 New_Occurrence_Of (Standard_Boolean, Loc),
2293 Expression =>
2294 New_Occurrence_Of (Standard_True, Loc)));
2296 Body_Stmts := New_List;
2297 Body_Node := New_Node (N_Subprogram_Body, Loc);
2299 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2301 Proc_Id :=
2302 Make_Defining_Identifier (Loc,
2303 Chars => Make_TSS_Name (Rec_Type, TSS_CPP_Init_Proc));
2305 Set_Ekind (Proc_Id, E_Procedure);
2306 Set_Is_Internal (Proc_Id);
2308 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2310 Set_Parameter_Specifications (Proc_Spec_Node, New_List);
2311 Set_Specification (Body_Node, Proc_Spec_Node);
2312 Set_Declarations (Body_Node, New_List);
2314 Init_Tags_List := Build_Inherit_CPP_Prims (Rec_Type);
2316 Append_To (Init_Tags_List,
2317 Make_Assignment_Statement (Loc,
2318 Name =>
2319 New_Occurrence_Of (Flag_Id, Loc),
2320 Expression =>
2321 New_Occurrence_Of (Standard_False, Loc)));
2323 Append_To (Body_Stmts,
2324 Make_If_Statement (Loc,
2325 Condition => New_Occurrence_Of (Flag_Id, Loc),
2326 Then_Statements => Init_Tags_List));
2328 Handled_Stmt_Node :=
2329 New_Node (N_Handled_Sequence_Of_Statements, Loc);
2330 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2331 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2332 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2334 if not Debug_Generated_Code then
2335 Set_Debug_Info_Off (Proc_Id);
2336 end if;
2338 -- Associate CPP_Init_Proc with type
2340 Set_Init_Proc (Rec_Type, Proc_Id);
2341 end Build_CPP_Init_Procedure;
2343 --------------------------
2344 -- Build_Init_Procedure --
2345 --------------------------
2347 procedure Build_Init_Procedure is
2348 Body_Stmts : List_Id;
2349 Body_Node : Node_Id;
2350 Handled_Stmt_Node : Node_Id;
2351 Init_Tags_List : List_Id;
2352 Parameters : List_Id;
2353 Proc_Spec_Node : Node_Id;
2354 Record_Extension_Node : Node_Id;
2356 begin
2357 Body_Stmts := New_List;
2358 Body_Node := New_Node (N_Subprogram_Body, Loc);
2359 Set_Ekind (Proc_Id, E_Procedure);
2361 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2362 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2364 Parameters := Init_Formals (Rec_Type);
2365 Append_List_To (Parameters,
2366 Build_Discriminant_Formals (Rec_Type, True));
2368 -- For tagged types, we add a flag to indicate whether the routine
2369 -- is called to initialize a parent component in the init_proc of
2370 -- a type extension. If the flag is false, we do not set the tag
2371 -- because it has been set already in the extension.
2373 if Is_Tagged_Type (Rec_Type) then
2374 Set_Tag := Make_Temporary (Loc, 'P');
2376 Append_To (Parameters,
2377 Make_Parameter_Specification (Loc,
2378 Defining_Identifier => Set_Tag,
2379 Parameter_Type =>
2380 New_Occurrence_Of (Standard_Boolean, Loc),
2381 Expression =>
2382 New_Occurrence_Of (Standard_True, Loc)));
2383 end if;
2385 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2386 Set_Specification (Body_Node, Proc_Spec_Node);
2387 Set_Declarations (Body_Node, Decls);
2389 -- N is a Derived_Type_Definition that renames the parameters of the
2390 -- ancestor type. We initialize it by expanding our discriminants and
2391 -- call the ancestor _init_proc with a type-converted object.
2393 if Parent_Subtype_Renaming_Discrims then
2394 Append_List_To (Body_Stmts, Build_Init_Call_Thru (Parameters));
2396 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2397 Build_Discriminant_Assignments (Body_Stmts);
2399 if not Null_Present (Type_Definition (N)) then
2400 Append_List_To (Body_Stmts,
2401 Build_Init_Statements (Component_List (Type_Definition (N))));
2402 end if;
2404 -- N is a Derived_Type_Definition with a possible non-empty
2405 -- extension. The initialization of a type extension consists in the
2406 -- initialization of the components in the extension.
2408 else
2409 Build_Discriminant_Assignments (Body_Stmts);
2411 Record_Extension_Node :=
2412 Record_Extension_Part (Type_Definition (N));
2414 if not Null_Present (Record_Extension_Node) then
2415 declare
2416 Stmts : constant List_Id :=
2417 Build_Init_Statements (
2418 Component_List (Record_Extension_Node));
2420 begin
2421 -- The parent field must be initialized first because the
2422 -- offset of the new discriminants may depend on it. This is
2423 -- not needed if the parent is an interface type because in
2424 -- such case the initialization of the _parent field was not
2425 -- generated.
2427 if not Is_Interface (Etype (Rec_Ent)) then
2428 declare
2429 Parent_IP : constant Name_Id :=
2430 Make_Init_Proc_Name (Etype (Rec_Ent));
2431 Stmt : Node_Id;
2432 IP_Call : Node_Id;
2433 IP_Stmts : List_Id;
2435 begin
2436 -- Look for a call to the parent IP at the beginning
2437 -- of Stmts associated with the record extension
2439 Stmt := First (Stmts);
2440 IP_Call := Empty;
2441 while Present (Stmt) loop
2442 if Nkind (Stmt) = N_Procedure_Call_Statement
2443 and then Chars (Name (Stmt)) = Parent_IP
2444 then
2445 IP_Call := Stmt;
2446 exit;
2447 end if;
2449 Next (Stmt);
2450 end loop;
2452 -- If found then move it to the beginning of the
2453 -- statements of this IP routine
2455 if Present (IP_Call) then
2456 IP_Stmts := New_List;
2457 loop
2458 Stmt := Remove_Head (Stmts);
2459 Append_To (IP_Stmts, Stmt);
2460 exit when Stmt = IP_Call;
2461 end loop;
2463 Prepend_List_To (Body_Stmts, IP_Stmts);
2464 end if;
2465 end;
2466 end if;
2468 Append_List_To (Body_Stmts, Stmts);
2469 end;
2470 end if;
2471 end if;
2473 -- Add here the assignment to instantiate the Tag
2475 -- The assignment corresponds to the code:
2477 -- _Init._Tag := Typ'Tag;
2479 -- Suppress the tag assignment when not Tagged_Type_Expansion because
2480 -- tags are represented implicitly in objects. It is also suppressed
2481 -- in case of CPP_Class types because in this case the tag is
2482 -- initialized in the C++ side.
2484 if Is_Tagged_Type (Rec_Type)
2485 and then Tagged_Type_Expansion
2486 and then not No_Run_Time_Mode
2487 then
2488 -- Case 1: Ada tagged types with no CPP ancestor. Set the tags of
2489 -- the actual object and invoke the IP of the parent (in this
2490 -- order). The tag must be initialized before the call to the IP
2491 -- of the parent and the assignments to other components because
2492 -- the initial value of the components may depend on the tag (eg.
2493 -- through a dispatching operation on an access to the current
2494 -- type). The tag assignment is not done when initializing the
2495 -- parent component of a type extension, because in that case the
2496 -- tag is set in the extension.
2498 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2500 -- Initialize the primary tag component
2502 Init_Tags_List := New_List (
2503 Make_Assignment_Statement (Loc,
2504 Name =>
2505 Make_Selected_Component (Loc,
2506 Prefix => Make_Identifier (Loc, Name_uInit),
2507 Selector_Name =>
2508 New_Occurrence_Of
2509 (First_Tag_Component (Rec_Type), Loc)),
2510 Expression =>
2511 New_Occurrence_Of
2512 (Node
2513 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2515 -- Ada 2005 (AI-251): Initialize the secondary tags components
2516 -- located at fixed positions (tags whose position depends on
2517 -- variable size components are initialized later ---see below)
2519 if Ada_Version >= Ada_2005
2520 and then not Is_Interface (Rec_Type)
2521 and then Has_Interfaces (Rec_Type)
2522 then
2523 declare
2524 Elab_Sec_DT_Stmts_List : constant List_Id := New_List;
2526 begin
2527 Init_Secondary_Tags
2528 (Typ => Rec_Type,
2529 Target => Make_Identifier (Loc, Name_uInit),
2530 Init_Tags_List => Init_Tags_List,
2531 Stmts_List => Elab_Sec_DT_Stmts_List,
2532 Fixed_Comps => True,
2533 Variable_Comps => False);
2535 Append_To (Elab_Sec_DT_Stmts_List,
2536 Make_Assignment_Statement (Loc,
2537 Name =>
2538 New_Occurrence_Of
2539 (Access_Disp_Table_Elab_Flag (Rec_Type), Loc),
2540 Expression =>
2541 New_Occurrence_Of (Standard_False, Loc)));
2543 Prepend_List_To (Body_Stmts, New_List (
2544 Make_If_Statement (Loc,
2545 Condition => New_Occurrence_Of (Set_Tag, Loc),
2546 Then_Statements => Init_Tags_List),
2548 Make_If_Statement (Loc,
2549 Condition =>
2550 New_Occurrence_Of
2551 (Access_Disp_Table_Elab_Flag (Rec_Type), Loc),
2552 Then_Statements => Elab_Sec_DT_Stmts_List)));
2553 end;
2554 else
2555 Prepend_To (Body_Stmts,
2556 Make_If_Statement (Loc,
2557 Condition => New_Occurrence_Of (Set_Tag, Loc),
2558 Then_Statements => Init_Tags_List));
2559 end if;
2561 -- Case 2: CPP type. The imported C++ constructor takes care of
2562 -- tags initialization. No action needed here because the IP
2563 -- is built by Set_CPP_Constructors; in this case the IP is a
2564 -- wrapper that invokes the C++ constructor and copies the C++
2565 -- tags locally. Done to inherit the C++ slots in Ada derivations
2566 -- (see case 3).
2568 elsif Is_CPP_Class (Rec_Type) then
2569 pragma Assert (False);
2570 null;
2572 -- Case 3: Combined hierarchy containing C++ types and Ada tagged
2573 -- type derivations. Derivations of imported C++ classes add a
2574 -- complication, because we cannot inhibit tag setting in the
2575 -- constructor for the parent. Hence we initialize the tag after
2576 -- the call to the parent IP (that is, in reverse order compared
2577 -- with pure Ada hierarchies ---see comment on case 1).
2579 else
2580 -- Initialize the primary tag
2582 Init_Tags_List := New_List (
2583 Make_Assignment_Statement (Loc,
2584 Name =>
2585 Make_Selected_Component (Loc,
2586 Prefix => Make_Identifier (Loc, Name_uInit),
2587 Selector_Name =>
2588 New_Occurrence_Of
2589 (First_Tag_Component (Rec_Type), Loc)),
2590 Expression =>
2591 New_Occurrence_Of
2592 (Node
2593 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2595 -- Ada 2005 (AI-251): Initialize the secondary tags components
2596 -- located at fixed positions (tags whose position depends on
2597 -- variable size components are initialized later ---see below)
2599 if Ada_Version >= Ada_2005
2600 and then not Is_Interface (Rec_Type)
2601 and then Has_Interfaces (Rec_Type)
2602 then
2603 Init_Secondary_Tags
2604 (Typ => Rec_Type,
2605 Target => Make_Identifier (Loc, Name_uInit),
2606 Init_Tags_List => Init_Tags_List,
2607 Stmts_List => Init_Tags_List,
2608 Fixed_Comps => True,
2609 Variable_Comps => False);
2610 end if;
2612 -- Initialize the tag component after invocation of parent IP.
2614 -- Generate:
2615 -- parent_IP(_init.parent); // Invokes the C++ constructor
2616 -- [ typIC; ] // Inherit C++ slots from parent
2617 -- init_tags
2619 declare
2620 Ins_Nod : Node_Id;
2622 begin
2623 -- Search for the call to the IP of the parent. We assume
2624 -- that the first init_proc call is for the parent.
2626 Ins_Nod := First (Body_Stmts);
2627 while Present (Next (Ins_Nod))
2628 and then (Nkind (Ins_Nod) /= N_Procedure_Call_Statement
2629 or else not Is_Init_Proc (Name (Ins_Nod)))
2630 loop
2631 Next (Ins_Nod);
2632 end loop;
2634 -- The IC routine copies the inherited slots of the C+ part
2635 -- of the dispatch table from the parent and updates the
2636 -- overridden C++ slots.
2638 if CPP_Num_Prims (Rec_Type) > 0 then
2639 declare
2640 Init_DT : Entity_Id;
2641 New_Nod : Node_Id;
2643 begin
2644 Init_DT := CPP_Init_Proc (Rec_Type);
2645 pragma Assert (Present (Init_DT));
2647 New_Nod :=
2648 Make_Procedure_Call_Statement (Loc,
2649 New_Occurrence_Of (Init_DT, Loc));
2650 Insert_After (Ins_Nod, New_Nod);
2652 -- Update location of init tag statements
2654 Ins_Nod := New_Nod;
2655 end;
2656 end if;
2658 Insert_List_After (Ins_Nod, Init_Tags_List);
2659 end;
2660 end if;
2662 -- Ada 2005 (AI-251): Initialize the secondary tag components
2663 -- located at variable positions. We delay the generation of this
2664 -- code until here because the value of the attribute 'Position
2665 -- applied to variable size components of the parent type that
2666 -- depend on discriminants is only safely read at runtime after
2667 -- the parent components have been initialized.
2669 if Ada_Version >= Ada_2005
2670 and then not Is_Interface (Rec_Type)
2671 and then Has_Interfaces (Rec_Type)
2672 and then Has_Discriminants (Etype (Rec_Type))
2673 and then Is_Variable_Size_Record (Etype (Rec_Type))
2674 then
2675 Init_Tags_List := New_List;
2677 Init_Secondary_Tags
2678 (Typ => Rec_Type,
2679 Target => Make_Identifier (Loc, Name_uInit),
2680 Init_Tags_List => Init_Tags_List,
2681 Stmts_List => Init_Tags_List,
2682 Fixed_Comps => False,
2683 Variable_Comps => True);
2685 if Is_Non_Empty_List (Init_Tags_List) then
2686 Append_List_To (Body_Stmts, Init_Tags_List);
2687 end if;
2688 end if;
2689 end if;
2691 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2692 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2694 -- Generate:
2695 -- Deep_Finalize (_init, C1, ..., CN);
2696 -- raise;
2698 if Counter > 0
2699 and then Needs_Finalization (Rec_Type)
2700 and then not Is_Abstract_Type (Rec_Type)
2701 and then not Restriction_Active (No_Exception_Propagation)
2702 then
2703 declare
2704 DF_Call : Node_Id;
2705 DF_Id : Entity_Id;
2707 begin
2708 -- Create a local version of Deep_Finalize which has indication
2709 -- of partial initialization state.
2711 DF_Id := Make_Temporary (Loc, 'F');
2713 Append_To (Decls, Make_Local_Deep_Finalize (Rec_Type, DF_Id));
2715 DF_Call :=
2716 Make_Procedure_Call_Statement (Loc,
2717 Name => New_Occurrence_Of (DF_Id, Loc),
2718 Parameter_Associations => New_List (
2719 Make_Identifier (Loc, Name_uInit),
2720 New_Occurrence_Of (Standard_False, Loc)));
2722 -- Do not emit warnings related to the elaboration order when a
2723 -- controlled object is declared before the body of Finalize is
2724 -- seen.
2726 Set_No_Elaboration_Check (DF_Call);
2728 Set_Exception_Handlers (Handled_Stmt_Node, New_List (
2729 Make_Exception_Handler (Loc,
2730 Exception_Choices => New_List (
2731 Make_Others_Choice (Loc)),
2732 Statements => New_List (
2733 DF_Call,
2734 Make_Raise_Statement (Loc)))));
2735 end;
2736 else
2737 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2738 end if;
2740 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2742 if not Debug_Generated_Code then
2743 Set_Debug_Info_Off (Proc_Id);
2744 end if;
2746 -- Associate Init_Proc with type, and determine if the procedure
2747 -- is null (happens because of the Initialize_Scalars pragma case,
2748 -- where we have to generate a null procedure in case it is called
2749 -- by a client with Initialize_Scalars set). Such procedures have
2750 -- to be generated, but do not have to be called, so we mark them
2751 -- as null to suppress the call.
2753 Set_Init_Proc (Rec_Type, Proc_Id);
2755 if List_Length (Body_Stmts) = 1
2757 -- We must skip SCIL nodes because they may have been added to this
2758 -- list by Insert_Actions.
2760 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
2761 then
2762 Set_Is_Null_Init_Proc (Proc_Id);
2763 end if;
2764 end Build_Init_Procedure;
2766 ---------------------------
2767 -- Build_Init_Statements --
2768 ---------------------------
2770 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2771 Checks : constant List_Id := New_List;
2772 Actions : List_Id := No_List;
2773 Counter_Id : Entity_Id := Empty;
2774 Comp_Loc : Source_Ptr;
2775 Decl : Node_Id;
2776 Has_POC : Boolean;
2777 Id : Entity_Id;
2778 Parent_Stmts : List_Id;
2779 Stmts : List_Id;
2780 Typ : Entity_Id;
2782 procedure Increment_Counter (Loc : Source_Ptr);
2783 -- Generate an "increment by one" statement for the current counter
2784 -- and append it to the list Stmts.
2786 procedure Make_Counter (Loc : Source_Ptr);
2787 -- Create a new counter for the current component list. The routine
2788 -- creates a new defining Id, adds an object declaration and sets
2789 -- the Id generator for the next variant.
2791 -----------------------
2792 -- Increment_Counter --
2793 -----------------------
2795 procedure Increment_Counter (Loc : Source_Ptr) is
2796 begin
2797 -- Generate:
2798 -- Counter := Counter + 1;
2800 Append_To (Stmts,
2801 Make_Assignment_Statement (Loc,
2802 Name => New_Occurrence_Of (Counter_Id, Loc),
2803 Expression =>
2804 Make_Op_Add (Loc,
2805 Left_Opnd => New_Occurrence_Of (Counter_Id, Loc),
2806 Right_Opnd => Make_Integer_Literal (Loc, 1))));
2807 end Increment_Counter;
2809 ------------------
2810 -- Make_Counter --
2811 ------------------
2813 procedure Make_Counter (Loc : Source_Ptr) is
2814 begin
2815 -- Increment the Id generator
2817 Counter := Counter + 1;
2819 -- Create the entity and declaration
2821 Counter_Id :=
2822 Make_Defining_Identifier (Loc,
2823 Chars => New_External_Name ('C', Counter));
2825 -- Generate:
2826 -- Cnn : Integer := 0;
2828 Append_To (Decls,
2829 Make_Object_Declaration (Loc,
2830 Defining_Identifier => Counter_Id,
2831 Object_Definition =>
2832 New_Occurrence_Of (Standard_Integer, Loc),
2833 Expression =>
2834 Make_Integer_Literal (Loc, 0)));
2835 end Make_Counter;
2837 -- Start of processing for Build_Init_Statements
2839 begin
2840 if Null_Present (Comp_List) then
2841 return New_List (Make_Null_Statement (Loc));
2842 end if;
2844 Parent_Stmts := New_List;
2845 Stmts := New_List;
2847 -- Loop through visible declarations of task types and protected
2848 -- types moving any expanded code from the spec to the body of the
2849 -- init procedure.
2851 if Is_Task_Record_Type (Rec_Type)
2852 or else Is_Protected_Record_Type (Rec_Type)
2853 then
2854 declare
2855 Decl : constant Node_Id :=
2856 Parent (Corresponding_Concurrent_Type (Rec_Type));
2857 Def : Node_Id;
2858 N1 : Node_Id;
2859 N2 : Node_Id;
2861 begin
2862 if Is_Task_Record_Type (Rec_Type) then
2863 Def := Task_Definition (Decl);
2864 else
2865 Def := Protected_Definition (Decl);
2866 end if;
2868 if Present (Def) then
2869 N1 := First (Visible_Declarations (Def));
2870 while Present (N1) loop
2871 N2 := N1;
2872 N1 := Next (N1);
2874 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2875 or else Nkind (N2) in N_Raise_xxx_Error
2876 or else Nkind (N2) = N_Procedure_Call_Statement
2877 then
2878 Append_To (Stmts,
2879 New_Copy_Tree (N2, New_Scope => Proc_Id));
2880 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2881 Analyze (N2);
2882 end if;
2883 end loop;
2884 end if;
2885 end;
2886 end if;
2888 -- Loop through components, skipping pragmas, in 2 steps. The first
2889 -- step deals with regular components. The second step deals with
2890 -- components that have per object constraints and no explicit
2891 -- initialization.
2893 Has_POC := False;
2895 -- First pass : regular components
2897 Decl := First_Non_Pragma (Component_Items (Comp_List));
2898 while Present (Decl) loop
2899 Comp_Loc := Sloc (Decl);
2900 Build_Record_Checks
2901 (Subtype_Indication (Component_Definition (Decl)), Checks);
2903 Id := Defining_Identifier (Decl);
2904 Typ := Etype (Id);
2906 -- Leave any processing of per-object constrained component for
2907 -- the second pass.
2909 if Has_Access_Constraint (Id) and then No (Expression (Decl)) then
2910 Has_POC := True;
2912 -- Regular component cases
2914 else
2915 -- In the context of the init proc, references to discriminants
2916 -- resolve to denote the discriminals: this is where we can
2917 -- freeze discriminant dependent component subtypes.
2919 if not Is_Frozen (Typ) then
2920 Append_List_To (Stmts, Freeze_Entity (Typ, N));
2921 end if;
2923 -- Explicit initialization
2925 if Present (Expression (Decl)) then
2926 if Is_CPP_Constructor_Call (Expression (Decl)) then
2927 Actions :=
2928 Build_Initialization_Call
2929 (Comp_Loc,
2930 Id_Ref =>
2931 Make_Selected_Component (Comp_Loc,
2932 Prefix =>
2933 Make_Identifier (Comp_Loc, Name_uInit),
2934 Selector_Name =>
2935 New_Occurrence_Of (Id, Comp_Loc)),
2936 Typ => Typ,
2937 In_Init_Proc => True,
2938 Enclos_Type => Rec_Type,
2939 Discr_Map => Discr_Map,
2940 Constructor_Ref => Expression (Decl));
2941 else
2942 Actions := Build_Assignment (Id, Expression (Decl));
2943 end if;
2945 -- CPU, Dispatching_Domain, Priority, and Secondary_Stack_Size
2946 -- components are filled in with the corresponding rep-item
2947 -- expression of the concurrent type (if any).
2949 elsif Ekind (Scope (Id)) = E_Record_Type
2950 and then Present (Corresponding_Concurrent_Type (Scope (Id)))
2951 and then Nam_In (Chars (Id), Name_uCPU,
2952 Name_uDispatching_Domain,
2953 Name_uPriority,
2954 Name_uSecondary_Stack_Size)
2955 then
2956 declare
2957 Exp : Node_Id;
2958 Nam : Name_Id;
2959 pragma Warnings (Off, Nam);
2960 Ritem : Node_Id;
2962 begin
2963 if Chars (Id) = Name_uCPU then
2964 Nam := Name_CPU;
2966 elsif Chars (Id) = Name_uDispatching_Domain then
2967 Nam := Name_Dispatching_Domain;
2969 elsif Chars (Id) = Name_uPriority then
2970 Nam := Name_Priority;
2972 elsif Chars (Id) = Name_uSecondary_Stack_Size then
2973 Nam := Name_Secondary_Stack_Size;
2974 end if;
2976 -- Get the Rep Item (aspect specification, attribute
2977 -- definition clause or pragma) of the corresponding
2978 -- concurrent type.
2980 Ritem :=
2981 Get_Rep_Item
2982 (Corresponding_Concurrent_Type (Scope (Id)),
2983 Nam,
2984 Check_Parents => False);
2986 if Present (Ritem) then
2988 -- Pragma case
2990 if Nkind (Ritem) = N_Pragma then
2991 Exp := First (Pragma_Argument_Associations (Ritem));
2993 if Nkind (Exp) = N_Pragma_Argument_Association then
2994 Exp := Expression (Exp);
2995 end if;
2997 -- Conversion for Priority expression
2999 if Nam = Name_Priority then
3000 if Pragma_Name (Ritem) = Name_Priority
3001 and then not GNAT_Mode
3002 then
3003 Exp := Convert_To (RTE (RE_Priority), Exp);
3004 else
3005 Exp :=
3006 Convert_To (RTE (RE_Any_Priority), Exp);
3007 end if;
3008 end if;
3010 -- Aspect/Attribute definition clause case
3012 else
3013 Exp := Expression (Ritem);
3015 -- Conversion for Priority expression
3017 if Nam = Name_Priority then
3018 if Chars (Ritem) = Name_Priority
3019 and then not GNAT_Mode
3020 then
3021 Exp := Convert_To (RTE (RE_Priority), Exp);
3022 else
3023 Exp :=
3024 Convert_To (RTE (RE_Any_Priority), Exp);
3025 end if;
3026 end if;
3027 end if;
3029 -- Conversion for Dispatching_Domain value
3031 if Nam = Name_Dispatching_Domain then
3032 Exp :=
3033 Unchecked_Convert_To
3034 (RTE (RE_Dispatching_Domain_Access), Exp);
3036 -- Conversion for Secondary_Stack_Size value
3038 elsif Nam = Name_Secondary_Stack_Size then
3039 Exp := Convert_To (RTE (RE_Size_Type), Exp);
3040 end if;
3042 Actions := Build_Assignment (Id, Exp);
3044 -- Nothing needed if no Rep Item
3046 else
3047 Actions := No_List;
3048 end if;
3049 end;
3051 -- Composite component with its own Init_Proc
3053 elsif not Is_Interface (Typ)
3054 and then Has_Non_Null_Base_Init_Proc (Typ)
3055 then
3056 Actions :=
3057 Build_Initialization_Call
3058 (Comp_Loc,
3059 Make_Selected_Component (Comp_Loc,
3060 Prefix =>
3061 Make_Identifier (Comp_Loc, Name_uInit),
3062 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3063 Typ,
3064 In_Init_Proc => True,
3065 Enclos_Type => Rec_Type,
3066 Discr_Map => Discr_Map);
3068 Clean_Task_Names (Typ, Proc_Id);
3070 -- Simple initialization
3072 elsif Component_Needs_Simple_Initialization (Typ) then
3073 Actions :=
3074 Build_Assignment
3075 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
3077 -- Nothing needed for this case
3079 else
3080 Actions := No_List;
3081 end if;
3083 if Present (Checks) then
3084 if Chars (Id) = Name_uParent then
3085 Append_List_To (Parent_Stmts, Checks);
3086 else
3087 Append_List_To (Stmts, Checks);
3088 end if;
3089 end if;
3091 if Present (Actions) then
3092 if Chars (Id) = Name_uParent then
3093 Append_List_To (Parent_Stmts, Actions);
3095 else
3096 Append_List_To (Stmts, Actions);
3098 -- Preserve initialization state in the current counter
3100 if Needs_Finalization (Typ) then
3101 if No (Counter_Id) then
3102 Make_Counter (Comp_Loc);
3103 end if;
3105 Increment_Counter (Comp_Loc);
3106 end if;
3107 end if;
3108 end if;
3109 end if;
3111 Next_Non_Pragma (Decl);
3112 end loop;
3114 -- The parent field must be initialized first because variable
3115 -- size components of the parent affect the location of all the
3116 -- new components.
3118 Prepend_List_To (Stmts, Parent_Stmts);
3120 -- Set up tasks and protected object support. This needs to be done
3121 -- before any component with a per-object access discriminant
3122 -- constraint, or any variant part (which may contain such
3123 -- components) is initialized, because the initialization of these
3124 -- components may reference the enclosing concurrent object.
3126 -- For a task record type, add the task create call and calls to bind
3127 -- any interrupt (signal) entries.
3129 if Is_Task_Record_Type (Rec_Type) then
3131 -- In the case of the restricted run time the ATCB has already
3132 -- been preallocated.
3134 if Restricted_Profile then
3135 Append_To (Stmts,
3136 Make_Assignment_Statement (Loc,
3137 Name =>
3138 Make_Selected_Component (Loc,
3139 Prefix => Make_Identifier (Loc, Name_uInit),
3140 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
3141 Expression =>
3142 Make_Attribute_Reference (Loc,
3143 Prefix =>
3144 Make_Selected_Component (Loc,
3145 Prefix => Make_Identifier (Loc, Name_uInit),
3146 Selector_Name => Make_Identifier (Loc, Name_uATCB)),
3147 Attribute_Name => Name_Unchecked_Access)));
3148 end if;
3150 Append_To (Stmts, Make_Task_Create_Call (Rec_Type));
3152 declare
3153 Task_Type : constant Entity_Id :=
3154 Corresponding_Concurrent_Type (Rec_Type);
3155 Task_Decl : constant Node_Id := Parent (Task_Type);
3156 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
3157 Decl_Loc : Source_Ptr;
3158 Ent : Entity_Id;
3159 Vis_Decl : Node_Id;
3161 begin
3162 if Present (Task_Def) then
3163 Vis_Decl := First (Visible_Declarations (Task_Def));
3164 while Present (Vis_Decl) loop
3165 Decl_Loc := Sloc (Vis_Decl);
3167 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
3168 if Get_Attribute_Id (Chars (Vis_Decl)) =
3169 Attribute_Address
3170 then
3171 Ent := Entity (Name (Vis_Decl));
3173 if Ekind (Ent) = E_Entry then
3174 Append_To (Stmts,
3175 Make_Procedure_Call_Statement (Decl_Loc,
3176 Name =>
3177 New_Occurrence_Of (RTE (
3178 RE_Bind_Interrupt_To_Entry), Decl_Loc),
3179 Parameter_Associations => New_List (
3180 Make_Selected_Component (Decl_Loc,
3181 Prefix =>
3182 Make_Identifier (Decl_Loc, Name_uInit),
3183 Selector_Name =>
3184 Make_Identifier
3185 (Decl_Loc, Name_uTask_Id)),
3186 Entry_Index_Expression
3187 (Decl_Loc, Ent, Empty, Task_Type),
3188 Expression (Vis_Decl))));
3189 end if;
3190 end if;
3191 end if;
3193 Next (Vis_Decl);
3194 end loop;
3195 end if;
3196 end;
3197 end if;
3199 -- For a protected type, add statements generated by
3200 -- Make_Initialize_Protection.
3202 if Is_Protected_Record_Type (Rec_Type) then
3203 Append_List_To (Stmts,
3204 Make_Initialize_Protection (Rec_Type));
3205 end if;
3207 -- Second pass: components with per-object constraints
3209 if Has_POC then
3210 Decl := First_Non_Pragma (Component_Items (Comp_List));
3211 while Present (Decl) loop
3212 Comp_Loc := Sloc (Decl);
3213 Id := Defining_Identifier (Decl);
3214 Typ := Etype (Id);
3216 if Has_Access_Constraint (Id)
3217 and then No (Expression (Decl))
3218 then
3219 if Has_Non_Null_Base_Init_Proc (Typ) then
3220 Append_List_To (Stmts,
3221 Build_Initialization_Call (Comp_Loc,
3222 Make_Selected_Component (Comp_Loc,
3223 Prefix =>
3224 Make_Identifier (Comp_Loc, Name_uInit),
3225 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3226 Typ,
3227 In_Init_Proc => True,
3228 Enclos_Type => Rec_Type,
3229 Discr_Map => Discr_Map));
3231 Clean_Task_Names (Typ, Proc_Id);
3233 -- Preserve initialization state in the current counter
3235 if Needs_Finalization (Typ) then
3236 if No (Counter_Id) then
3237 Make_Counter (Comp_Loc);
3238 end if;
3240 Increment_Counter (Comp_Loc);
3241 end if;
3243 elsif Component_Needs_Simple_Initialization (Typ) then
3244 Append_List_To (Stmts,
3245 Build_Assignment
3246 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
3247 end if;
3248 end if;
3250 Next_Non_Pragma (Decl);
3251 end loop;
3252 end if;
3254 -- Process the variant part
3256 if Present (Variant_Part (Comp_List)) then
3257 declare
3258 Variant_Alts : constant List_Id := New_List;
3259 Var_Loc : Source_Ptr := No_Location;
3260 Variant : Node_Id;
3262 begin
3263 Variant :=
3264 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3265 while Present (Variant) loop
3266 Var_Loc := Sloc (Variant);
3267 Append_To (Variant_Alts,
3268 Make_Case_Statement_Alternative (Var_Loc,
3269 Discrete_Choices =>
3270 New_Copy_List (Discrete_Choices (Variant)),
3271 Statements =>
3272 Build_Init_Statements (Component_List (Variant))));
3273 Next_Non_Pragma (Variant);
3274 end loop;
3276 -- The expression of the case statement which is a reference
3277 -- to one of the discriminants is replaced by the appropriate
3278 -- formal parameter of the initialization procedure.
3280 Append_To (Stmts,
3281 Make_Case_Statement (Var_Loc,
3282 Expression =>
3283 New_Occurrence_Of (Discriminal (
3284 Entity (Name (Variant_Part (Comp_List)))), Var_Loc),
3285 Alternatives => Variant_Alts));
3286 end;
3287 end if;
3289 -- If no initializations when generated for component declarations
3290 -- corresponding to this Stmts, append a null statement to Stmts to
3291 -- to make it a valid Ada tree.
3293 if Is_Empty_List (Stmts) then
3294 Append (Make_Null_Statement (Loc), Stmts);
3295 end if;
3297 return Stmts;
3299 exception
3300 when RE_Not_Available =>
3301 return Empty_List;
3302 end Build_Init_Statements;
3304 -------------------------
3305 -- Build_Record_Checks --
3306 -------------------------
3308 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
3309 Subtype_Mark_Id : Entity_Id;
3311 procedure Constrain_Array
3312 (SI : Node_Id;
3313 Check_List : List_Id);
3314 -- Apply a list of index constraints to an unconstrained array type.
3315 -- The first parameter is the entity for the resulting subtype.
3316 -- Check_List is a list to which the check actions are appended.
3318 ---------------------
3319 -- Constrain_Array --
3320 ---------------------
3322 procedure Constrain_Array
3323 (SI : Node_Id;
3324 Check_List : List_Id)
3326 C : constant Node_Id := Constraint (SI);
3327 Number_Of_Constraints : Nat := 0;
3328 Index : Node_Id;
3329 S, T : Entity_Id;
3331 procedure Constrain_Index
3332 (Index : Node_Id;
3333 S : Node_Id;
3334 Check_List : List_Id);
3335 -- Process an index constraint in a constrained array declaration.
3336 -- The constraint can be either a subtype name or a range with or
3337 -- without an explicit subtype mark. Index is the corresponding
3338 -- index of the unconstrained array. S is the range expression.
3339 -- Check_List is a list to which the check actions are appended.
3341 ---------------------
3342 -- Constrain_Index --
3343 ---------------------
3345 procedure Constrain_Index
3346 (Index : Node_Id;
3347 S : Node_Id;
3348 Check_List : List_Id)
3350 T : constant Entity_Id := Etype (Index);
3352 begin
3353 if Nkind (S) = N_Range then
3354 Process_Range_Expr_In_Decl (S, T, Check_List => Check_List);
3355 end if;
3356 end Constrain_Index;
3358 -- Start of processing for Constrain_Array
3360 begin
3361 T := Entity (Subtype_Mark (SI));
3363 if Is_Access_Type (T) then
3364 T := Designated_Type (T);
3365 end if;
3367 S := First (Constraints (C));
3368 while Present (S) loop
3369 Number_Of_Constraints := Number_Of_Constraints + 1;
3370 Next (S);
3371 end loop;
3373 -- In either case, the index constraint must provide a discrete
3374 -- range for each index of the array type and the type of each
3375 -- discrete range must be the same as that of the corresponding
3376 -- index. (RM 3.6.1)
3378 S := First (Constraints (C));
3379 Index := First_Index (T);
3380 Analyze (Index);
3382 -- Apply constraints to each index type
3384 for J in 1 .. Number_Of_Constraints loop
3385 Constrain_Index (Index, S, Check_List);
3386 Next (Index);
3387 Next (S);
3388 end loop;
3389 end Constrain_Array;
3391 -- Start of processing for Build_Record_Checks
3393 begin
3394 if Nkind (S) = N_Subtype_Indication then
3395 Find_Type (Subtype_Mark (S));
3396 Subtype_Mark_Id := Entity (Subtype_Mark (S));
3398 -- Remaining processing depends on type
3400 case Ekind (Subtype_Mark_Id) is
3401 when Array_Kind =>
3402 Constrain_Array (S, Check_List);
3404 when others =>
3405 null;
3406 end case;
3407 end if;
3408 end Build_Record_Checks;
3410 -------------------------------------------
3411 -- Component_Needs_Simple_Initialization --
3412 -------------------------------------------
3414 function Component_Needs_Simple_Initialization
3415 (T : Entity_Id) return Boolean
3417 begin
3418 return
3419 Needs_Simple_Initialization (T)
3420 and then not Is_RTE (T, RE_Tag)
3422 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
3424 and then not Is_RTE (T, RE_Interface_Tag);
3425 end Component_Needs_Simple_Initialization;
3427 --------------------------------------
3428 -- Parent_Subtype_Renaming_Discrims --
3429 --------------------------------------
3431 function Parent_Subtype_Renaming_Discrims return Boolean is
3432 De : Entity_Id;
3433 Dp : Entity_Id;
3435 begin
3436 if Base_Type (Rec_Ent) /= Rec_Ent then
3437 return False;
3438 end if;
3440 if Etype (Rec_Ent) = Rec_Ent
3441 or else not Has_Discriminants (Rec_Ent)
3442 or else Is_Constrained (Rec_Ent)
3443 or else Is_Tagged_Type (Rec_Ent)
3444 then
3445 return False;
3446 end if;
3448 -- If there are no explicit stored discriminants we have inherited
3449 -- the root type discriminants so far, so no renamings occurred.
3451 if First_Discriminant (Rec_Ent) =
3452 First_Stored_Discriminant (Rec_Ent)
3453 then
3454 return False;
3455 end if;
3457 -- Check if we have done some trivial renaming of the parent
3458 -- discriminants, i.e. something like
3460 -- type DT (X1, X2: int) is new PT (X1, X2);
3462 De := First_Discriminant (Rec_Ent);
3463 Dp := First_Discriminant (Etype (Rec_Ent));
3464 while Present (De) loop
3465 pragma Assert (Present (Dp));
3467 if Corresponding_Discriminant (De) /= Dp then
3468 return True;
3469 end if;
3471 Next_Discriminant (De);
3472 Next_Discriminant (Dp);
3473 end loop;
3475 return Present (Dp);
3476 end Parent_Subtype_Renaming_Discrims;
3478 ------------------------
3479 -- Requires_Init_Proc --
3480 ------------------------
3482 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3483 Comp_Decl : Node_Id;
3484 Id : Entity_Id;
3485 Typ : Entity_Id;
3487 begin
3488 -- Definitely do not need one if specifically suppressed
3490 if Initialization_Suppressed (Rec_Id) then
3491 return False;
3492 end if;
3494 -- If it is a type derived from a type with unknown discriminants,
3495 -- we cannot build an initialization procedure for it.
3497 if Has_Unknown_Discriminants (Rec_Id)
3498 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3499 then
3500 return False;
3501 end if;
3503 -- Otherwise we need to generate an initialization procedure if
3504 -- Is_CPP_Class is False and at least one of the following applies:
3506 -- 1. Discriminants are present, since they need to be initialized
3507 -- with the appropriate discriminant constraint expressions.
3508 -- However, the discriminant of an unchecked union does not
3509 -- count, since the discriminant is not present.
3511 -- 2. The type is a tagged type, since the implicit Tag component
3512 -- needs to be initialized with a pointer to the dispatch table.
3514 -- 3. The type contains tasks
3516 -- 4. One or more components has an initial value
3518 -- 5. One or more components is for a type which itself requires
3519 -- an initialization procedure.
3521 -- 6. One or more components is a type that requires simple
3522 -- initialization (see Needs_Simple_Initialization), except
3523 -- that types Tag and Interface_Tag are excluded, since fields
3524 -- of these types are initialized by other means.
3526 -- 7. The type is the record type built for a task type (since at
3527 -- the very least, Create_Task must be called)
3529 -- 8. The type is the record type built for a protected type (since
3530 -- at least Initialize_Protection must be called)
3532 -- 9. The type is marked as a public entity. The reason we add this
3533 -- case (even if none of the above apply) is to properly handle
3534 -- Initialize_Scalars. If a package is compiled without an IS
3535 -- pragma, and the client is compiled with an IS pragma, then
3536 -- the client will think an initialization procedure is present
3537 -- and call it, when in fact no such procedure is required, but
3538 -- since the call is generated, there had better be a routine
3539 -- at the other end of the call, even if it does nothing).
3541 -- Note: the reason we exclude the CPP_Class case is because in this
3542 -- case the initialization is performed by the C++ constructors, and
3543 -- the IP is built by Set_CPP_Constructors.
3545 if Is_CPP_Class (Rec_Id) then
3546 return False;
3548 elsif Is_Interface (Rec_Id) then
3549 return False;
3551 elsif (Has_Discriminants (Rec_Id)
3552 and then not Is_Unchecked_Union (Rec_Id))
3553 or else Is_Tagged_Type (Rec_Id)
3554 or else Is_Concurrent_Record_Type (Rec_Id)
3555 or else Has_Task (Rec_Id)
3556 then
3557 return True;
3558 end if;
3560 Id := First_Component (Rec_Id);
3561 while Present (Id) loop
3562 Comp_Decl := Parent (Id);
3563 Typ := Etype (Id);
3565 if Present (Expression (Comp_Decl))
3566 or else Has_Non_Null_Base_Init_Proc (Typ)
3567 or else Component_Needs_Simple_Initialization (Typ)
3568 then
3569 return True;
3570 end if;
3572 Next_Component (Id);
3573 end loop;
3575 -- As explained above, a record initialization procedure is needed
3576 -- for public types in case Initialize_Scalars applies to a client.
3577 -- However, such a procedure is not needed in the case where either
3578 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3579 -- applies. No_Initialize_Scalars excludes the possibility of using
3580 -- Initialize_Scalars in any partition, and No_Default_Initialization
3581 -- implies that no initialization should ever be done for objects of
3582 -- the type, so is incompatible with Initialize_Scalars.
3584 if not Restriction_Active (No_Initialize_Scalars)
3585 and then not Restriction_Active (No_Default_Initialization)
3586 and then Is_Public (Rec_Id)
3587 then
3588 return True;
3589 end if;
3591 return False;
3592 end Requires_Init_Proc;
3594 -- Start of processing for Build_Record_Init_Proc
3596 begin
3597 Rec_Type := Defining_Identifier (N);
3599 -- This may be full declaration of a private type, in which case
3600 -- the visible entity is a record, and the private entity has been
3601 -- exchanged with it in the private part of the current package.
3602 -- The initialization procedure is built for the record type, which
3603 -- is retrievable from the private entity.
3605 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3606 Rec_Type := Underlying_Type (Rec_Type);
3607 end if;
3609 -- If we have a variant record with restriction No_Implicit_Conditionals
3610 -- in effect, then we skip building the procedure. This is safe because
3611 -- if we can see the restriction, so can any caller, calls to initialize
3612 -- such records are not allowed for variant records if this restriction
3613 -- is active.
3615 if Has_Variant_Part (Rec_Type)
3616 and then Restriction_Active (No_Implicit_Conditionals)
3617 then
3618 return;
3619 end if;
3621 -- If there are discriminants, build the discriminant map to replace
3622 -- discriminants by their discriminals in complex bound expressions.
3623 -- These only arise for the corresponding records of synchronized types.
3625 if Is_Concurrent_Record_Type (Rec_Type)
3626 and then Has_Discriminants (Rec_Type)
3627 then
3628 declare
3629 Disc : Entity_Id;
3630 begin
3631 Disc := First_Discriminant (Rec_Type);
3632 while Present (Disc) loop
3633 Append_Elmt (Disc, Discr_Map);
3634 Append_Elmt (Discriminal (Disc), Discr_Map);
3635 Next_Discriminant (Disc);
3636 end loop;
3637 end;
3638 end if;
3640 -- Derived types that have no type extension can use the initialization
3641 -- procedure of their parent and do not need a procedure of their own.
3642 -- This is only correct if there are no representation clauses for the
3643 -- type or its parent, and if the parent has in fact been frozen so
3644 -- that its initialization procedure exists.
3646 if Is_Derived_Type (Rec_Type)
3647 and then not Is_Tagged_Type (Rec_Type)
3648 and then not Is_Unchecked_Union (Rec_Type)
3649 and then not Has_New_Non_Standard_Rep (Rec_Type)
3650 and then not Parent_Subtype_Renaming_Discrims
3651 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3652 then
3653 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3655 -- Otherwise if we need an initialization procedure, then build one,
3656 -- mark it as public and inlinable and as having a completion.
3658 elsif Requires_Init_Proc (Rec_Type)
3659 or else Is_Unchecked_Union (Rec_Type)
3660 then
3661 Proc_Id :=
3662 Make_Defining_Identifier (Loc,
3663 Chars => Make_Init_Proc_Name (Rec_Type));
3665 -- If No_Default_Initialization restriction is active, then we don't
3666 -- want to build an init_proc, but we need to mark that an init_proc
3667 -- would be needed if this restriction was not active (so that we can
3668 -- detect attempts to call it), so set a dummy init_proc in place.
3670 if Restriction_Active (No_Default_Initialization) then
3671 Set_Init_Proc (Rec_Type, Proc_Id);
3672 return;
3673 end if;
3675 Build_Offset_To_Top_Functions;
3676 Build_CPP_Init_Procedure;
3677 Build_Init_Procedure;
3679 Set_Is_Public (Proc_Id, Is_Public (Rec_Ent));
3680 Set_Is_Internal (Proc_Id);
3681 Set_Has_Completion (Proc_Id);
3683 if not Debug_Generated_Code then
3684 Set_Debug_Info_Off (Proc_Id);
3685 end if;
3687 Set_Is_Inlined (Proc_Id, Inline_Init_Proc (Rec_Type));
3689 -- Do not build an aggregate if Modify_Tree_For_C, this isn't
3690 -- needed and may generate early references to non frozen types
3691 -- since we expand aggregate much more systematically.
3693 if Modify_Tree_For_C then
3694 return;
3695 end if;
3697 declare
3698 Agg : constant Node_Id :=
3699 Build_Equivalent_Record_Aggregate (Rec_Type);
3701 procedure Collect_Itypes (Comp : Node_Id);
3702 -- Generate references to itypes in the aggregate, because
3703 -- the first use of the aggregate may be in a nested scope.
3705 --------------------
3706 -- Collect_Itypes --
3707 --------------------
3709 procedure Collect_Itypes (Comp : Node_Id) is
3710 Ref : Node_Id;
3711 Sub_Aggr : Node_Id;
3712 Typ : constant Entity_Id := Etype (Comp);
3714 begin
3715 if Is_Array_Type (Typ) and then Is_Itype (Typ) then
3716 Ref := Make_Itype_Reference (Loc);
3717 Set_Itype (Ref, Typ);
3718 Append_Freeze_Action (Rec_Type, Ref);
3720 Ref := Make_Itype_Reference (Loc);
3721 Set_Itype (Ref, Etype (First_Index (Typ)));
3722 Append_Freeze_Action (Rec_Type, Ref);
3724 -- Recurse on nested arrays
3726 Sub_Aggr := First (Expressions (Comp));
3727 while Present (Sub_Aggr) loop
3728 Collect_Itypes (Sub_Aggr);
3729 Next (Sub_Aggr);
3730 end loop;
3731 end if;
3732 end Collect_Itypes;
3734 begin
3735 -- If there is a static initialization aggregate for the type,
3736 -- generate itype references for the types of its (sub)components,
3737 -- to prevent out-of-scope errors in the resulting tree.
3738 -- The aggregate may have been rewritten as a Raise node, in which
3739 -- case there are no relevant itypes.
3741 if Present (Agg) and then Nkind (Agg) = N_Aggregate then
3742 Set_Static_Initialization (Proc_Id, Agg);
3744 declare
3745 Comp : Node_Id;
3746 begin
3747 Comp := First (Component_Associations (Agg));
3748 while Present (Comp) loop
3749 Collect_Itypes (Expression (Comp));
3750 Next (Comp);
3751 end loop;
3752 end;
3753 end if;
3754 end;
3755 end if;
3756 end Build_Record_Init_Proc;
3758 ----------------------------
3759 -- Build_Slice_Assignment --
3760 ----------------------------
3762 -- Generates the following subprogram:
3764 -- procedure Assign
3765 -- (Source, Target : Array_Type,
3766 -- Left_Lo, Left_Hi : Index;
3767 -- Right_Lo, Right_Hi : Index;
3768 -- Rev : Boolean)
3769 -- is
3770 -- Li1 : Index;
3771 -- Ri1 : Index;
3773 -- begin
3775 -- if Left_Hi < Left_Lo then
3776 -- return;
3777 -- end if;
3779 -- if Rev then
3780 -- Li1 := Left_Hi;
3781 -- Ri1 := Right_Hi;
3782 -- else
3783 -- Li1 := Left_Lo;
3784 -- Ri1 := Right_Lo;
3785 -- end if;
3787 -- loop
3788 -- Target (Li1) := Source (Ri1);
3790 -- if Rev then
3791 -- exit when Li1 = Left_Lo;
3792 -- Li1 := Index'pred (Li1);
3793 -- Ri1 := Index'pred (Ri1);
3794 -- else
3795 -- exit when Li1 = Left_Hi;
3796 -- Li1 := Index'succ (Li1);
3797 -- Ri1 := Index'succ (Ri1);
3798 -- end if;
3799 -- end loop;
3800 -- end Assign;
3802 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3803 Loc : constant Source_Ptr := Sloc (Typ);
3804 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3806 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
3807 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
3808 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
3809 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
3810 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
3811 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
3812 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
3813 -- Formal parameters of procedure
3815 Proc_Name : constant Entity_Id :=
3816 Make_Defining_Identifier (Loc,
3817 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3819 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3820 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3821 -- Subscripts for left and right sides
3823 Decls : List_Id;
3824 Loops : Node_Id;
3825 Stats : List_Id;
3827 begin
3828 -- Build declarations for indexes
3830 Decls := New_List;
3832 Append_To (Decls,
3833 Make_Object_Declaration (Loc,
3834 Defining_Identifier => Lnn,
3835 Object_Definition =>
3836 New_Occurrence_Of (Index, Loc)));
3838 Append_To (Decls,
3839 Make_Object_Declaration (Loc,
3840 Defining_Identifier => Rnn,
3841 Object_Definition =>
3842 New_Occurrence_Of (Index, Loc)));
3844 Stats := New_List;
3846 -- Build test for empty slice case
3848 Append_To (Stats,
3849 Make_If_Statement (Loc,
3850 Condition =>
3851 Make_Op_Lt (Loc,
3852 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
3853 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3854 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
3856 -- Build initializations for indexes
3858 declare
3859 F_Init : constant List_Id := New_List;
3860 B_Init : constant List_Id := New_List;
3862 begin
3863 Append_To (F_Init,
3864 Make_Assignment_Statement (Loc,
3865 Name => New_Occurrence_Of (Lnn, Loc),
3866 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3868 Append_To (F_Init,
3869 Make_Assignment_Statement (Loc,
3870 Name => New_Occurrence_Of (Rnn, Loc),
3871 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3873 Append_To (B_Init,
3874 Make_Assignment_Statement (Loc,
3875 Name => New_Occurrence_Of (Lnn, Loc),
3876 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3878 Append_To (B_Init,
3879 Make_Assignment_Statement (Loc,
3880 Name => New_Occurrence_Of (Rnn, Loc),
3881 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3883 Append_To (Stats,
3884 Make_If_Statement (Loc,
3885 Condition => New_Occurrence_Of (Rev, Loc),
3886 Then_Statements => B_Init,
3887 Else_Statements => F_Init));
3888 end;
3890 -- Now construct the assignment statement
3892 Loops :=
3893 Make_Loop_Statement (Loc,
3894 Statements => New_List (
3895 Make_Assignment_Statement (Loc,
3896 Name =>
3897 Make_Indexed_Component (Loc,
3898 Prefix => New_Occurrence_Of (Larray, Loc),
3899 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3900 Expression =>
3901 Make_Indexed_Component (Loc,
3902 Prefix => New_Occurrence_Of (Rarray, Loc),
3903 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3904 End_Label => Empty);
3906 -- Build the exit condition and increment/decrement statements
3908 declare
3909 F_Ass : constant List_Id := New_List;
3910 B_Ass : constant List_Id := New_List;
3912 begin
3913 Append_To (F_Ass,
3914 Make_Exit_Statement (Loc,
3915 Condition =>
3916 Make_Op_Eq (Loc,
3917 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3918 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3920 Append_To (F_Ass,
3921 Make_Assignment_Statement (Loc,
3922 Name => New_Occurrence_Of (Lnn, Loc),
3923 Expression =>
3924 Make_Attribute_Reference (Loc,
3925 Prefix =>
3926 New_Occurrence_Of (Index, Loc),
3927 Attribute_Name => Name_Succ,
3928 Expressions => New_List (
3929 New_Occurrence_Of (Lnn, Loc)))));
3931 Append_To (F_Ass,
3932 Make_Assignment_Statement (Loc,
3933 Name => New_Occurrence_Of (Rnn, Loc),
3934 Expression =>
3935 Make_Attribute_Reference (Loc,
3936 Prefix =>
3937 New_Occurrence_Of (Index, Loc),
3938 Attribute_Name => Name_Succ,
3939 Expressions => New_List (
3940 New_Occurrence_Of (Rnn, Loc)))));
3942 Append_To (B_Ass,
3943 Make_Exit_Statement (Loc,
3944 Condition =>
3945 Make_Op_Eq (Loc,
3946 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3947 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3949 Append_To (B_Ass,
3950 Make_Assignment_Statement (Loc,
3951 Name => New_Occurrence_Of (Lnn, Loc),
3952 Expression =>
3953 Make_Attribute_Reference (Loc,
3954 Prefix =>
3955 New_Occurrence_Of (Index, Loc),
3956 Attribute_Name => Name_Pred,
3957 Expressions => New_List (
3958 New_Occurrence_Of (Lnn, Loc)))));
3960 Append_To (B_Ass,
3961 Make_Assignment_Statement (Loc,
3962 Name => New_Occurrence_Of (Rnn, Loc),
3963 Expression =>
3964 Make_Attribute_Reference (Loc,
3965 Prefix =>
3966 New_Occurrence_Of (Index, Loc),
3967 Attribute_Name => Name_Pred,
3968 Expressions => New_List (
3969 New_Occurrence_Of (Rnn, Loc)))));
3971 Append_To (Statements (Loops),
3972 Make_If_Statement (Loc,
3973 Condition => New_Occurrence_Of (Rev, Loc),
3974 Then_Statements => B_Ass,
3975 Else_Statements => F_Ass));
3976 end;
3978 Append_To (Stats, Loops);
3980 declare
3981 Spec : Node_Id;
3982 Formals : List_Id := New_List;
3984 begin
3985 Formals := New_List (
3986 Make_Parameter_Specification (Loc,
3987 Defining_Identifier => Larray,
3988 Out_Present => True,
3989 Parameter_Type =>
3990 New_Occurrence_Of (Base_Type (Typ), Loc)),
3992 Make_Parameter_Specification (Loc,
3993 Defining_Identifier => Rarray,
3994 Parameter_Type =>
3995 New_Occurrence_Of (Base_Type (Typ), Loc)),
3997 Make_Parameter_Specification (Loc,
3998 Defining_Identifier => Left_Lo,
3999 Parameter_Type =>
4000 New_Occurrence_Of (Index, Loc)),
4002 Make_Parameter_Specification (Loc,
4003 Defining_Identifier => Left_Hi,
4004 Parameter_Type =>
4005 New_Occurrence_Of (Index, Loc)),
4007 Make_Parameter_Specification (Loc,
4008 Defining_Identifier => Right_Lo,
4009 Parameter_Type =>
4010 New_Occurrence_Of (Index, Loc)),
4012 Make_Parameter_Specification (Loc,
4013 Defining_Identifier => Right_Hi,
4014 Parameter_Type =>
4015 New_Occurrence_Of (Index, Loc)));
4017 Append_To (Formals,
4018 Make_Parameter_Specification (Loc,
4019 Defining_Identifier => Rev,
4020 Parameter_Type =>
4021 New_Occurrence_Of (Standard_Boolean, Loc)));
4023 Spec :=
4024 Make_Procedure_Specification (Loc,
4025 Defining_Unit_Name => Proc_Name,
4026 Parameter_Specifications => Formals);
4028 Discard_Node (
4029 Make_Subprogram_Body (Loc,
4030 Specification => Spec,
4031 Declarations => Decls,
4032 Handled_Statement_Sequence =>
4033 Make_Handled_Sequence_Of_Statements (Loc,
4034 Statements => Stats)));
4035 end;
4037 Set_TSS (Typ, Proc_Name);
4038 Set_Is_Pure (Proc_Name);
4039 end Build_Slice_Assignment;
4041 -----------------------------
4042 -- Build_Untagged_Equality --
4043 -----------------------------
4045 procedure Build_Untagged_Equality (Typ : Entity_Id) is
4046 Build_Eq : Boolean;
4047 Comp : Entity_Id;
4048 Decl : Node_Id;
4049 Op : Entity_Id;
4050 Prim : Elmt_Id;
4051 Eq_Op : Entity_Id;
4053 function User_Defined_Eq (T : Entity_Id) return Entity_Id;
4054 -- Check whether the type T has a user-defined primitive equality. If so
4055 -- return it, else return Empty. If true for a component of Typ, we have
4056 -- to build the primitive equality for it.
4058 ---------------------
4059 -- User_Defined_Eq --
4060 ---------------------
4062 function User_Defined_Eq (T : Entity_Id) return Entity_Id is
4063 Prim : Elmt_Id;
4064 Op : Entity_Id;
4066 begin
4067 Op := TSS (T, TSS_Composite_Equality);
4069 if Present (Op) then
4070 return Op;
4071 end if;
4073 Prim := First_Elmt (Collect_Primitive_Operations (T));
4074 while Present (Prim) loop
4075 Op := Node (Prim);
4077 if Chars (Op) = Name_Op_Eq
4078 and then Etype (Op) = Standard_Boolean
4079 and then Etype (First_Formal (Op)) = T
4080 and then Etype (Next_Formal (First_Formal (Op))) = T
4081 then
4082 return Op;
4083 end if;
4085 Next_Elmt (Prim);
4086 end loop;
4088 return Empty;
4089 end User_Defined_Eq;
4091 -- Start of processing for Build_Untagged_Equality
4093 begin
4094 -- If a record component has a primitive equality operation, we must
4095 -- build the corresponding one for the current type.
4097 Build_Eq := False;
4098 Comp := First_Component (Typ);
4099 while Present (Comp) loop
4100 if Is_Record_Type (Etype (Comp))
4101 and then Present (User_Defined_Eq (Etype (Comp)))
4102 then
4103 Build_Eq := True;
4104 end if;
4106 Next_Component (Comp);
4107 end loop;
4109 -- If there is a user-defined equality for the type, we do not create
4110 -- the implicit one.
4112 Prim := First_Elmt (Collect_Primitive_Operations (Typ));
4113 Eq_Op := Empty;
4114 while Present (Prim) loop
4115 if Chars (Node (Prim)) = Name_Op_Eq
4116 and then Comes_From_Source (Node (Prim))
4118 -- Don't we also need to check formal types and return type as in
4119 -- User_Defined_Eq above???
4121 then
4122 Eq_Op := Node (Prim);
4123 Build_Eq := False;
4124 exit;
4125 end if;
4127 Next_Elmt (Prim);
4128 end loop;
4130 -- If the type is derived, inherit the operation, if present, from the
4131 -- parent type. It may have been declared after the type derivation. If
4132 -- the parent type itself is derived, it may have inherited an operation
4133 -- that has itself been overridden, so update its alias and related
4134 -- flags. Ditto for inequality.
4136 if No (Eq_Op) and then Is_Derived_Type (Typ) then
4137 Prim := First_Elmt (Collect_Primitive_Operations (Etype (Typ)));
4138 while Present (Prim) loop
4139 if Chars (Node (Prim)) = Name_Op_Eq then
4140 Copy_TSS (Node (Prim), Typ);
4141 Build_Eq := False;
4143 declare
4144 Op : constant Entity_Id := User_Defined_Eq (Typ);
4145 Eq_Op : constant Entity_Id := Node (Prim);
4146 NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
4148 begin
4149 if Present (Op) then
4150 Set_Alias (Op, Eq_Op);
4151 Set_Is_Abstract_Subprogram
4152 (Op, Is_Abstract_Subprogram (Eq_Op));
4154 if Chars (Next_Entity (Op)) = Name_Op_Ne then
4155 Set_Is_Abstract_Subprogram
4156 (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
4157 end if;
4158 end if;
4159 end;
4161 exit;
4162 end if;
4164 Next_Elmt (Prim);
4165 end loop;
4166 end if;
4168 -- If not inherited and not user-defined, build body as for a type with
4169 -- tagged components.
4171 if Build_Eq then
4172 Decl :=
4173 Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
4174 Op := Defining_Entity (Decl);
4175 Set_TSS (Typ, Op);
4176 Set_Is_Pure (Op);
4178 if Is_Library_Level_Entity (Typ) then
4179 Set_Is_Public (Op);
4180 end if;
4181 end if;
4182 end Build_Untagged_Equality;
4184 -----------------------------------
4185 -- Build_Variant_Record_Equality --
4186 -----------------------------------
4188 -- Generates:
4190 -- function _Equality (X, Y : T) return Boolean is
4191 -- begin
4192 -- -- Compare discriminants
4194 -- if X.D1 /= Y.D1 or else X.D2 /= Y.D2 or else ... then
4195 -- return False;
4196 -- end if;
4198 -- -- Compare components
4200 -- if X.C1 /= Y.C1 or else X.C2 /= Y.C2 or else ... then
4201 -- return False;
4202 -- end if;
4204 -- -- Compare variant part
4206 -- case X.D1 is
4207 -- when V1 =>
4208 -- if X.C2 /= Y.C2 or else X.C3 /= Y.C3 or else ... then
4209 -- return False;
4210 -- end if;
4211 -- ...
4212 -- when Vn =>
4213 -- if X.Cn /= Y.Cn or else ... then
4214 -- return False;
4215 -- end if;
4216 -- end case;
4218 -- return True;
4219 -- end _Equality;
4221 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
4222 Loc : constant Source_Ptr := Sloc (Typ);
4224 F : constant Entity_Id :=
4225 Make_Defining_Identifier (Loc,
4226 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
4228 X : constant Entity_Id := Make_Defining_Identifier (Loc, Name_X);
4229 Y : constant Entity_Id := Make_Defining_Identifier (Loc, Name_Y);
4231 Def : constant Node_Id := Parent (Typ);
4232 Comps : constant Node_Id := Component_List (Type_Definition (Def));
4233 Stmts : constant List_Id := New_List;
4234 Pspecs : constant List_Id := New_List;
4236 begin
4237 -- If we have a variant record with restriction No_Implicit_Conditionals
4238 -- in effect, then we skip building the procedure. This is safe because
4239 -- if we can see the restriction, so can any caller, calls to equality
4240 -- test routines are not allowed for variant records if this restriction
4241 -- is active.
4243 if Restriction_Active (No_Implicit_Conditionals) then
4244 return;
4245 end if;
4247 -- Derived Unchecked_Union types no longer inherit the equality function
4248 -- of their parent.
4250 if Is_Derived_Type (Typ)
4251 and then not Is_Unchecked_Union (Typ)
4252 and then not Has_New_Non_Standard_Rep (Typ)
4253 then
4254 declare
4255 Parent_Eq : constant Entity_Id :=
4256 TSS (Root_Type (Typ), TSS_Composite_Equality);
4257 begin
4258 if Present (Parent_Eq) then
4259 Copy_TSS (Parent_Eq, Typ);
4260 return;
4261 end if;
4262 end;
4263 end if;
4265 Discard_Node (
4266 Make_Subprogram_Body (Loc,
4267 Specification =>
4268 Make_Function_Specification (Loc,
4269 Defining_Unit_Name => F,
4270 Parameter_Specifications => Pspecs,
4271 Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
4272 Declarations => New_List,
4273 Handled_Statement_Sequence =>
4274 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
4276 Append_To (Pspecs,
4277 Make_Parameter_Specification (Loc,
4278 Defining_Identifier => X,
4279 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4281 Append_To (Pspecs,
4282 Make_Parameter_Specification (Loc,
4283 Defining_Identifier => Y,
4284 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4286 -- Unchecked_Unions require additional machinery to support equality.
4287 -- Two extra parameters (A and B) are added to the equality function
4288 -- parameter list for each discriminant of the type, in order to
4289 -- capture the inferred values of the discriminants in equality calls.
4290 -- The names of the parameters match the names of the corresponding
4291 -- discriminant, with an added suffix.
4293 if Is_Unchecked_Union (Typ) then
4294 declare
4295 Discr : Entity_Id;
4296 Discr_Type : Entity_Id;
4297 A, B : Entity_Id;
4298 New_Discrs : Elist_Id;
4300 begin
4301 New_Discrs := New_Elmt_List;
4303 Discr := First_Discriminant (Typ);
4304 while Present (Discr) loop
4305 Discr_Type := Etype (Discr);
4306 A := Make_Defining_Identifier (Loc,
4307 Chars => New_External_Name (Chars (Discr), 'A'));
4309 B := Make_Defining_Identifier (Loc,
4310 Chars => New_External_Name (Chars (Discr), 'B'));
4312 -- Add new parameters to the parameter list
4314 Append_To (Pspecs,
4315 Make_Parameter_Specification (Loc,
4316 Defining_Identifier => A,
4317 Parameter_Type =>
4318 New_Occurrence_Of (Discr_Type, Loc)));
4320 Append_To (Pspecs,
4321 Make_Parameter_Specification (Loc,
4322 Defining_Identifier => B,
4323 Parameter_Type =>
4324 New_Occurrence_Of (Discr_Type, Loc)));
4326 Append_Elmt (A, New_Discrs);
4328 -- Generate the following code to compare each of the inferred
4329 -- discriminants:
4331 -- if a /= b then
4332 -- return False;
4333 -- end if;
4335 Append_To (Stmts,
4336 Make_If_Statement (Loc,
4337 Condition =>
4338 Make_Op_Ne (Loc,
4339 Left_Opnd => New_Occurrence_Of (A, Loc),
4340 Right_Opnd => New_Occurrence_Of (B, Loc)),
4341 Then_Statements => New_List (
4342 Make_Simple_Return_Statement (Loc,
4343 Expression =>
4344 New_Occurrence_Of (Standard_False, Loc)))));
4345 Next_Discriminant (Discr);
4346 end loop;
4348 -- Generate component-by-component comparison. Note that we must
4349 -- propagate the inferred discriminants formals to act as
4350 -- the case statement switch. Their value is added when an
4351 -- equality call on unchecked unions is expanded.
4353 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps, New_Discrs));
4354 end;
4356 -- Normal case (not unchecked union)
4358 else
4359 Append_To (Stmts,
4360 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
4361 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
4362 end if;
4364 Append_To (Stmts,
4365 Make_Simple_Return_Statement (Loc,
4366 Expression => New_Occurrence_Of (Standard_True, Loc)));
4368 Set_TSS (Typ, F);
4369 Set_Is_Pure (F);
4371 if not Debug_Generated_Code then
4372 Set_Debug_Info_Off (F);
4373 end if;
4374 end Build_Variant_Record_Equality;
4376 -----------------------------
4377 -- Check_Stream_Attributes --
4378 -----------------------------
4380 procedure Check_Stream_Attributes (Typ : Entity_Id) is
4381 Comp : Entity_Id;
4382 Par_Read : constant Boolean :=
4383 Stream_Attribute_Available (Typ, TSS_Stream_Read)
4384 and then not Has_Specified_Stream_Read (Typ);
4385 Par_Write : constant Boolean :=
4386 Stream_Attribute_Available (Typ, TSS_Stream_Write)
4387 and then not Has_Specified_Stream_Write (Typ);
4389 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4390 -- Check that Comp has a user-specified Nam stream attribute
4392 ----------------
4393 -- Check_Attr --
4394 ----------------
4396 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4397 begin
4398 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4399 Error_Msg_Name_1 := Nam;
4400 Error_Msg_N
4401 ("|component& in limited extension must have% attribute", Comp);
4402 end if;
4403 end Check_Attr;
4405 -- Start of processing for Check_Stream_Attributes
4407 begin
4408 if Par_Read or else Par_Write then
4409 Comp := First_Component (Typ);
4410 while Present (Comp) loop
4411 if Comes_From_Source (Comp)
4412 and then Original_Record_Component (Comp) = Comp
4413 and then Is_Limited_Type (Etype (Comp))
4414 then
4415 if Par_Read then
4416 Check_Attr (Name_Read, TSS_Stream_Read);
4417 end if;
4419 if Par_Write then
4420 Check_Attr (Name_Write, TSS_Stream_Write);
4421 end if;
4422 end if;
4424 Next_Component (Comp);
4425 end loop;
4426 end if;
4427 end Check_Stream_Attributes;
4429 ----------------------
4430 -- Clean_Task_Names --
4431 ----------------------
4433 procedure Clean_Task_Names
4434 (Typ : Entity_Id;
4435 Proc_Id : Entity_Id)
4437 begin
4438 if Has_Task (Typ)
4439 and then not Restriction_Active (No_Implicit_Heap_Allocations)
4440 and then not Global_Discard_Names
4441 and then Tagged_Type_Expansion
4442 then
4443 Set_Uses_Sec_Stack (Proc_Id);
4444 end if;
4445 end Clean_Task_Names;
4447 ------------------------------
4448 -- Expand_Freeze_Array_Type --
4449 ------------------------------
4451 procedure Expand_Freeze_Array_Type (N : Node_Id) is
4452 Typ : constant Entity_Id := Entity (N);
4453 Base : constant Entity_Id := Base_Type (Typ);
4454 Comp_Typ : constant Entity_Id := Component_Type (Typ);
4456 begin
4457 if not Is_Bit_Packed_Array (Typ) then
4459 -- If the component contains tasks, so does the array type. This may
4460 -- not be indicated in the array type because the component may have
4461 -- been a private type at the point of definition. Same if component
4462 -- type is controlled or contains protected objects.
4464 Propagate_Concurrent_Flags (Base, Comp_Typ);
4465 Set_Has_Controlled_Component
4466 (Base, Has_Controlled_Component (Comp_Typ)
4467 or else Is_Controlled (Comp_Typ));
4469 if No (Init_Proc (Base)) then
4471 -- If this is an anonymous array created for a declaration with
4472 -- an initial value, its init_proc will never be called. The
4473 -- initial value itself may have been expanded into assignments,
4474 -- in which case the object declaration is carries the
4475 -- No_Initialization flag.
4477 if Is_Itype (Base)
4478 and then Nkind (Associated_Node_For_Itype (Base)) =
4479 N_Object_Declaration
4480 and then
4481 (Present (Expression (Associated_Node_For_Itype (Base)))
4482 or else No_Initialization (Associated_Node_For_Itype (Base)))
4483 then
4484 null;
4486 -- We do not need an init proc for string or wide [wide] string,
4487 -- since the only time these need initialization in normalize or
4488 -- initialize scalars mode, and these types are treated specially
4489 -- and do not need initialization procedures.
4491 elsif Is_Standard_String_Type (Base) then
4492 null;
4494 -- Otherwise we have to build an init proc for the subtype
4496 else
4497 Build_Array_Init_Proc (Base, N);
4498 end if;
4499 end if;
4501 if Typ = Base and then Has_Controlled_Component (Base) then
4502 Build_Controlling_Procs (Base);
4504 if not Is_Limited_Type (Comp_Typ)
4505 and then Number_Dimensions (Typ) = 1
4506 then
4507 Build_Slice_Assignment (Typ);
4508 end if;
4509 end if;
4511 -- For packed case, default initialization, except if the component type
4512 -- is itself a packed structure with an initialization procedure, or
4513 -- initialize/normalize scalars active, and we have a base type, or the
4514 -- type is public, because in that case a client might specify
4515 -- Normalize_Scalars and there better be a public Init_Proc for it.
4517 elsif (Present (Init_Proc (Component_Type (Base)))
4518 and then No (Base_Init_Proc (Base)))
4519 or else (Init_Or_Norm_Scalars and then Base = Typ)
4520 or else Is_Public (Typ)
4521 then
4522 Build_Array_Init_Proc (Base, N);
4523 end if;
4524 end Expand_Freeze_Array_Type;
4526 -----------------------------------
4527 -- Expand_Freeze_Class_Wide_Type --
4528 -----------------------------------
4530 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id) is
4531 function Is_C_Derivation (Typ : Entity_Id) return Boolean;
4532 -- Given a type, determine whether it is derived from a C or C++ root
4534 ---------------------
4535 -- Is_C_Derivation --
4536 ---------------------
4538 function Is_C_Derivation (Typ : Entity_Id) return Boolean is
4539 T : Entity_Id;
4541 begin
4542 T := Typ;
4543 loop
4544 if Is_CPP_Class (T)
4545 or else Convention (T) = Convention_C
4546 or else Convention (T) = Convention_CPP
4547 then
4548 return True;
4549 end if;
4551 exit when T = Etype (T);
4553 T := Etype (T);
4554 end loop;
4556 return False;
4557 end Is_C_Derivation;
4559 -- Local variables
4561 Typ : constant Entity_Id := Entity (N);
4562 Root : constant Entity_Id := Root_Type (Typ);
4564 -- Start of processing for Expand_Freeze_Class_Wide_Type
4566 begin
4567 -- Certain run-time configurations and targets do not provide support
4568 -- for controlled types.
4570 if Restriction_Active (No_Finalization) then
4571 return;
4573 -- Do not create TSS routine Finalize_Address when dispatching calls are
4574 -- disabled since the core of the routine is a dispatching call.
4576 elsif Restriction_Active (No_Dispatching_Calls) then
4577 return;
4579 -- Do not create TSS routine Finalize_Address for concurrent class-wide
4580 -- types. Ignore C, C++, CIL and Java types since it is assumed that the
4581 -- non-Ada side will handle their destruction.
4583 elsif Is_Concurrent_Type (Root)
4584 or else Is_C_Derivation (Root)
4585 or else Convention (Typ) = Convention_CPP
4586 then
4587 return;
4589 -- Do not create TSS routine Finalize_Address when compiling in CodePeer
4590 -- mode since the routine contains an Unchecked_Conversion.
4592 elsif CodePeer_Mode then
4593 return;
4594 end if;
4596 -- Create the body of TSS primitive Finalize_Address. This automatically
4597 -- sets the TSS entry for the class-wide type.
4599 Make_Finalize_Address_Body (Typ);
4600 end Expand_Freeze_Class_Wide_Type;
4602 ------------------------------------
4603 -- Expand_Freeze_Enumeration_Type --
4604 ------------------------------------
4606 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
4607 Typ : constant Entity_Id := Entity (N);
4608 Loc : constant Source_Ptr := Sloc (Typ);
4610 Arr : Entity_Id;
4611 Ent : Entity_Id;
4612 Fent : Entity_Id;
4613 Is_Contiguous : Boolean;
4614 Ityp : Entity_Id;
4615 Last_Repval : Uint;
4616 Lst : List_Id;
4617 Num : Nat;
4618 Pos_Expr : Node_Id;
4620 Func : Entity_Id;
4621 pragma Warnings (Off, Func);
4623 begin
4624 -- Various optimizations possible if given representation is contiguous
4626 Is_Contiguous := True;
4628 Ent := First_Literal (Typ);
4629 Last_Repval := Enumeration_Rep (Ent);
4631 Next_Literal (Ent);
4632 while Present (Ent) loop
4633 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
4634 Is_Contiguous := False;
4635 exit;
4636 else
4637 Last_Repval := Enumeration_Rep (Ent);
4638 end if;
4640 Next_Literal (Ent);
4641 end loop;
4643 if Is_Contiguous then
4644 Set_Has_Contiguous_Rep (Typ);
4645 Ent := First_Literal (Typ);
4646 Num := 1;
4647 Lst := New_List (New_Occurrence_Of (Ent, Sloc (Ent)));
4649 else
4650 -- Build list of literal references
4652 Lst := New_List;
4653 Num := 0;
4655 Ent := First_Literal (Typ);
4656 while Present (Ent) loop
4657 Append_To (Lst, New_Occurrence_Of (Ent, Sloc (Ent)));
4658 Num := Num + 1;
4659 Next_Literal (Ent);
4660 end loop;
4661 end if;
4663 -- Now build an array declaration
4665 -- typA : array (Natural range 0 .. num - 1) of ctype :=
4666 -- (v, v, v, v, v, ....)
4668 -- where ctype is the corresponding integer type. If the representation
4669 -- is contiguous, we only keep the first literal, which provides the
4670 -- offset for Pos_To_Rep computations.
4672 Arr :=
4673 Make_Defining_Identifier (Loc,
4674 Chars => New_External_Name (Chars (Typ), 'A'));
4676 Append_Freeze_Action (Typ,
4677 Make_Object_Declaration (Loc,
4678 Defining_Identifier => Arr,
4679 Constant_Present => True,
4681 Object_Definition =>
4682 Make_Constrained_Array_Definition (Loc,
4683 Discrete_Subtype_Definitions => New_List (
4684 Make_Subtype_Indication (Loc,
4685 Subtype_Mark => New_Occurrence_Of (Standard_Natural, Loc),
4686 Constraint =>
4687 Make_Range_Constraint (Loc,
4688 Range_Expression =>
4689 Make_Range (Loc,
4690 Low_Bound =>
4691 Make_Integer_Literal (Loc, 0),
4692 High_Bound =>
4693 Make_Integer_Literal (Loc, Num - 1))))),
4695 Component_Definition =>
4696 Make_Component_Definition (Loc,
4697 Aliased_Present => False,
4698 Subtype_Indication => New_Occurrence_Of (Typ, Loc))),
4700 Expression =>
4701 Make_Aggregate (Loc,
4702 Expressions => Lst)));
4704 Set_Enum_Pos_To_Rep (Typ, Arr);
4706 -- Now we build the function that converts representation values to
4707 -- position values. This function has the form:
4709 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4710 -- begin
4711 -- case ityp!(A) is
4712 -- when enum-lit'Enum_Rep => return posval;
4713 -- when enum-lit'Enum_Rep => return posval;
4714 -- ...
4715 -- when others =>
4716 -- [raise Constraint_Error when F "invalid data"]
4717 -- return -1;
4718 -- end case;
4719 -- end;
4721 -- Note: the F parameter determines whether the others case (no valid
4722 -- representation) raises Constraint_Error or returns a unique value
4723 -- of minus one. The latter case is used, e.g. in 'Valid code.
4725 -- Note: the reason we use Enum_Rep values in the case here is to avoid
4726 -- the code generator making inappropriate assumptions about the range
4727 -- of the values in the case where the value is invalid. ityp is a
4728 -- signed or unsigned integer type of appropriate width.
4730 -- Note: if exceptions are not supported, then we suppress the raise
4731 -- and return -1 unconditionally (this is an erroneous program in any
4732 -- case and there is no obligation to raise Constraint_Error here). We
4733 -- also do this if pragma Restrictions (No_Exceptions) is active.
4735 -- Is this right??? What about No_Exception_Propagation???
4737 -- Representations are signed
4739 if Enumeration_Rep (First_Literal (Typ)) < 0 then
4741 -- The underlying type is signed. Reset the Is_Unsigned_Type
4742 -- explicitly, because it might have been inherited from
4743 -- parent type.
4745 Set_Is_Unsigned_Type (Typ, False);
4747 if Esize (Typ) <= Standard_Integer_Size then
4748 Ityp := Standard_Integer;
4749 else
4750 Ityp := Universal_Integer;
4751 end if;
4753 -- Representations are unsigned
4755 else
4756 if Esize (Typ) <= Standard_Integer_Size then
4757 Ityp := RTE (RE_Unsigned);
4758 else
4759 Ityp := RTE (RE_Long_Long_Unsigned);
4760 end if;
4761 end if;
4763 -- The body of the function is a case statement. First collect case
4764 -- alternatives, or optimize the contiguous case.
4766 Lst := New_List;
4768 -- If representation is contiguous, Pos is computed by subtracting
4769 -- the representation of the first literal.
4771 if Is_Contiguous then
4772 Ent := First_Literal (Typ);
4774 if Enumeration_Rep (Ent) = Last_Repval then
4776 -- Another special case: for a single literal, Pos is zero
4778 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4780 else
4781 Pos_Expr :=
4782 Convert_To (Standard_Integer,
4783 Make_Op_Subtract (Loc,
4784 Left_Opnd =>
4785 Unchecked_Convert_To
4786 (Ityp, Make_Identifier (Loc, Name_uA)),
4787 Right_Opnd =>
4788 Make_Integer_Literal (Loc,
4789 Intval => Enumeration_Rep (First_Literal (Typ)))));
4790 end if;
4792 Append_To (Lst,
4793 Make_Case_Statement_Alternative (Loc,
4794 Discrete_Choices => New_List (
4795 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4796 Low_Bound =>
4797 Make_Integer_Literal (Loc,
4798 Intval => Enumeration_Rep (Ent)),
4799 High_Bound =>
4800 Make_Integer_Literal (Loc, Intval => Last_Repval))),
4802 Statements => New_List (
4803 Make_Simple_Return_Statement (Loc,
4804 Expression => Pos_Expr))));
4806 else
4807 Ent := First_Literal (Typ);
4808 while Present (Ent) loop
4809 Append_To (Lst,
4810 Make_Case_Statement_Alternative (Loc,
4811 Discrete_Choices => New_List (
4812 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4813 Intval => Enumeration_Rep (Ent))),
4815 Statements => New_List (
4816 Make_Simple_Return_Statement (Loc,
4817 Expression =>
4818 Make_Integer_Literal (Loc,
4819 Intval => Enumeration_Pos (Ent))))));
4821 Next_Literal (Ent);
4822 end loop;
4823 end if;
4825 -- In normal mode, add the others clause with the test.
4826 -- If Predicates_Ignored is True, validity checks do not apply to
4827 -- the subtype.
4829 if not No_Exception_Handlers_Set
4830 and then not Predicates_Ignored (Typ)
4831 then
4832 Append_To (Lst,
4833 Make_Case_Statement_Alternative (Loc,
4834 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4835 Statements => New_List (
4836 Make_Raise_Constraint_Error (Loc,
4837 Condition => Make_Identifier (Loc, Name_uF),
4838 Reason => CE_Invalid_Data),
4839 Make_Simple_Return_Statement (Loc,
4840 Expression => Make_Integer_Literal (Loc, -1)))));
4842 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
4843 -- active then return -1 (we cannot usefully raise Constraint_Error in
4844 -- this case). See description above for further details.
4846 else
4847 Append_To (Lst,
4848 Make_Case_Statement_Alternative (Loc,
4849 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4850 Statements => New_List (
4851 Make_Simple_Return_Statement (Loc,
4852 Expression => Make_Integer_Literal (Loc, -1)))));
4853 end if;
4855 -- Now we can build the function body
4857 Fent :=
4858 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
4860 Func :=
4861 Make_Subprogram_Body (Loc,
4862 Specification =>
4863 Make_Function_Specification (Loc,
4864 Defining_Unit_Name => Fent,
4865 Parameter_Specifications => New_List (
4866 Make_Parameter_Specification (Loc,
4867 Defining_Identifier =>
4868 Make_Defining_Identifier (Loc, Name_uA),
4869 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
4870 Make_Parameter_Specification (Loc,
4871 Defining_Identifier =>
4872 Make_Defining_Identifier (Loc, Name_uF),
4873 Parameter_Type =>
4874 New_Occurrence_Of (Standard_Boolean, Loc))),
4876 Result_Definition => New_Occurrence_Of (Standard_Integer, Loc)),
4878 Declarations => Empty_List,
4880 Handled_Statement_Sequence =>
4881 Make_Handled_Sequence_Of_Statements (Loc,
4882 Statements => New_List (
4883 Make_Case_Statement (Loc,
4884 Expression =>
4885 Unchecked_Convert_To
4886 (Ityp, Make_Identifier (Loc, Name_uA)),
4887 Alternatives => Lst))));
4889 Set_TSS (Typ, Fent);
4891 -- Set Pure flag (it will be reset if the current context is not Pure).
4892 -- We also pretend there was a pragma Pure_Function so that for purposes
4893 -- of optimization and constant-folding, we will consider the function
4894 -- Pure even if we are not in a Pure context).
4896 Set_Is_Pure (Fent);
4897 Set_Has_Pragma_Pure_Function (Fent);
4899 -- Unless we are in -gnatD mode, where we are debugging generated code,
4900 -- this is an internal entity for which we don't need debug info.
4902 if not Debug_Generated_Code then
4903 Set_Debug_Info_Off (Fent);
4904 end if;
4906 Set_Is_Inlined (Fent);
4908 exception
4909 when RE_Not_Available =>
4910 return;
4911 end Expand_Freeze_Enumeration_Type;
4913 -------------------------------
4914 -- Expand_Freeze_Record_Type --
4915 -------------------------------
4917 procedure Expand_Freeze_Record_Type (N : Node_Id) is
4918 Typ : constant Node_Id := Entity (N);
4919 Typ_Decl : constant Node_Id := Parent (Typ);
4921 Comp : Entity_Id;
4922 Comp_Typ : Entity_Id;
4923 Predef_List : List_Id;
4925 Wrapper_Decl_List : List_Id := No_List;
4926 Wrapper_Body_List : List_Id := No_List;
4928 Renamed_Eq : Node_Id := Empty;
4929 -- Defining unit name for the predefined equality function in the case
4930 -- where the type has a primitive operation that is a renaming of
4931 -- predefined equality (but only if there is also an overriding
4932 -- user-defined equality function). Used to pass this entity from
4933 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
4935 -- Start of processing for Expand_Freeze_Record_Type
4937 begin
4938 -- Build discriminant checking functions if not a derived type (for
4939 -- derived types that are not tagged types, always use the discriminant
4940 -- checking functions of the parent type). However, for untagged types
4941 -- the derivation may have taken place before the parent was frozen, so
4942 -- we copy explicitly the discriminant checking functions from the
4943 -- parent into the components of the derived type.
4945 if not Is_Derived_Type (Typ)
4946 or else Has_New_Non_Standard_Rep (Typ)
4947 or else Is_Tagged_Type (Typ)
4948 then
4949 Build_Discr_Checking_Funcs (Typ_Decl);
4951 elsif Is_Derived_Type (Typ)
4952 and then not Is_Tagged_Type (Typ)
4954 -- If we have a derived Unchecked_Union, we do not inherit the
4955 -- discriminant checking functions from the parent type since the
4956 -- discriminants are non existent.
4958 and then not Is_Unchecked_Union (Typ)
4959 and then Has_Discriminants (Typ)
4960 then
4961 declare
4962 Old_Comp : Entity_Id;
4964 begin
4965 Old_Comp :=
4966 First_Component (Base_Type (Underlying_Type (Etype (Typ))));
4967 Comp := First_Component (Typ);
4968 while Present (Comp) loop
4969 if Ekind (Comp) = E_Component
4970 and then Chars (Comp) = Chars (Old_Comp)
4971 then
4972 Set_Discriminant_Checking_Func
4973 (Comp, Discriminant_Checking_Func (Old_Comp));
4974 end if;
4976 Next_Component (Old_Comp);
4977 Next_Component (Comp);
4978 end loop;
4979 end;
4980 end if;
4982 if Is_Derived_Type (Typ)
4983 and then Is_Limited_Type (Typ)
4984 and then Is_Tagged_Type (Typ)
4985 then
4986 Check_Stream_Attributes (Typ);
4987 end if;
4989 -- Update task, protected, and controlled component flags, because some
4990 -- of the component types may have been private at the point of the
4991 -- record declaration. Detect anonymous access-to-controlled components.
4993 Comp := First_Component (Typ);
4994 while Present (Comp) loop
4995 Comp_Typ := Etype (Comp);
4997 Propagate_Concurrent_Flags (Typ, Comp_Typ);
4999 -- Do not set Has_Controlled_Component on a class-wide equivalent
5000 -- type. See Make_CW_Equivalent_Type.
5002 if not Is_Class_Wide_Equivalent_Type (Typ)
5003 and then
5004 (Has_Controlled_Component (Comp_Typ)
5005 or else (Chars (Comp) /= Name_uParent
5006 and then Is_Controlled (Comp_Typ)))
5007 then
5008 Set_Has_Controlled_Component (Typ);
5009 end if;
5011 Next_Component (Comp);
5012 end loop;
5014 -- Handle constructors of untagged CPP_Class types
5016 if not Is_Tagged_Type (Typ) and then Is_CPP_Class (Typ) then
5017 Set_CPP_Constructors (Typ);
5018 end if;
5020 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
5021 -- for regular tagged types as well as for Ada types deriving from a C++
5022 -- Class, but not for tagged types directly corresponding to C++ classes
5023 -- In the later case we assume that it is created in the C++ side and we
5024 -- just use it.
5026 if Is_Tagged_Type (Typ) then
5028 -- Add the _Tag component
5030 if Underlying_Type (Etype (Typ)) = Typ then
5031 Expand_Tagged_Root (Typ);
5032 end if;
5034 if Is_CPP_Class (Typ) then
5035 Set_All_DT_Position (Typ);
5037 -- Create the tag entities with a minimum decoration
5039 if Tagged_Type_Expansion then
5040 Append_Freeze_Actions (Typ, Make_Tags (Typ));
5041 end if;
5043 Set_CPP_Constructors (Typ);
5045 else
5046 if not Building_Static_DT (Typ) then
5048 -- Usually inherited primitives are not delayed but the first
5049 -- Ada extension of a CPP_Class is an exception since the
5050 -- address of the inherited subprogram has to be inserted in
5051 -- the new Ada Dispatch Table and this is a freezing action.
5053 -- Similarly, if this is an inherited operation whose parent is
5054 -- not frozen yet, it is not in the DT of the parent, and we
5055 -- generate an explicit freeze node for the inherited operation
5056 -- so it is properly inserted in the DT of the current type.
5058 declare
5059 Elmt : Elmt_Id;
5060 Subp : Entity_Id;
5062 begin
5063 Elmt := First_Elmt (Primitive_Operations (Typ));
5064 while Present (Elmt) loop
5065 Subp := Node (Elmt);
5067 if Present (Alias (Subp)) then
5068 if Is_CPP_Class (Etype (Typ)) then
5069 Set_Has_Delayed_Freeze (Subp);
5071 elsif Has_Delayed_Freeze (Alias (Subp))
5072 and then not Is_Frozen (Alias (Subp))
5073 then
5074 Set_Is_Frozen (Subp, False);
5075 Set_Has_Delayed_Freeze (Subp);
5076 end if;
5077 end if;
5079 Next_Elmt (Elmt);
5080 end loop;
5081 end;
5082 end if;
5084 -- Unfreeze momentarily the type to add the predefined primitives
5085 -- operations. The reason we unfreeze is so that these predefined
5086 -- operations will indeed end up as primitive operations (which
5087 -- must be before the freeze point).
5089 Set_Is_Frozen (Typ, False);
5091 -- Do not add the spec of predefined primitives in case of
5092 -- CPP tagged type derivations that have convention CPP.
5094 if Is_CPP_Class (Root_Type (Typ))
5095 and then Convention (Typ) = Convention_CPP
5096 then
5097 null;
5099 -- Do not add the spec of the predefined primitives if we are
5100 -- compiling under restriction No_Dispatching_Calls.
5102 elsif not Restriction_Active (No_Dispatching_Calls) then
5103 Make_Predefined_Primitive_Specs (Typ, Predef_List, Renamed_Eq);
5104 Insert_List_Before_And_Analyze (N, Predef_List);
5105 end if;
5107 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5108 -- wrapper functions for each nonoverridden inherited function
5109 -- with a controlling result of the type. The wrapper for such
5110 -- a function returns an extension aggregate that invokes the
5111 -- parent function.
5113 if Ada_Version >= Ada_2005
5114 and then not Is_Abstract_Type (Typ)
5115 and then Is_Null_Extension (Typ)
5116 then
5117 Make_Controlling_Function_Wrappers
5118 (Typ, Wrapper_Decl_List, Wrapper_Body_List);
5119 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5120 end if;
5122 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5123 -- null procedure declarations for each set of homographic null
5124 -- procedures that are inherited from interface types but not
5125 -- overridden. This is done to ensure that the dispatch table
5126 -- entry associated with such null primitives are properly filled.
5128 if Ada_Version >= Ada_2005
5129 and then Etype (Typ) /= Typ
5130 and then not Is_Abstract_Type (Typ)
5131 and then Has_Interfaces (Typ)
5132 then
5133 Insert_Actions (N, Make_Null_Procedure_Specs (Typ));
5134 end if;
5136 Set_Is_Frozen (Typ);
5138 if not Is_Derived_Type (Typ)
5139 or else Is_Tagged_Type (Etype (Typ))
5140 then
5141 Set_All_DT_Position (Typ);
5143 -- If this is a type derived from an untagged private type whose
5144 -- full view is tagged, the type is marked tagged for layout
5145 -- reasons, but it has no dispatch table.
5147 elsif Is_Derived_Type (Typ)
5148 and then Is_Private_Type (Etype (Typ))
5149 and then not Is_Tagged_Type (Etype (Typ))
5150 then
5151 return;
5152 end if;
5154 -- Create and decorate the tags. Suppress their creation when
5155 -- not Tagged_Type_Expansion because the dispatching mechanism is
5156 -- handled internally by the virtual target.
5158 if Tagged_Type_Expansion then
5159 Append_Freeze_Actions (Typ, Make_Tags (Typ));
5161 -- Generate dispatch table of locally defined tagged type.
5162 -- Dispatch tables of library level tagged types are built
5163 -- later (see Analyze_Declarations).
5165 if not Building_Static_DT (Typ) then
5166 Append_Freeze_Actions (Typ, Make_DT (Typ));
5167 end if;
5168 end if;
5170 -- If the type has unknown discriminants, propagate dispatching
5171 -- information to its underlying record view, which does not get
5172 -- its own dispatch table.
5174 if Is_Derived_Type (Typ)
5175 and then Has_Unknown_Discriminants (Typ)
5176 and then Present (Underlying_Record_View (Typ))
5177 then
5178 declare
5179 Rep : constant Entity_Id := Underlying_Record_View (Typ);
5180 begin
5181 Set_Access_Disp_Table
5182 (Rep, Access_Disp_Table (Typ));
5183 Set_Dispatch_Table_Wrappers
5184 (Rep, Dispatch_Table_Wrappers (Typ));
5185 Set_Direct_Primitive_Operations
5186 (Rep, Direct_Primitive_Operations (Typ));
5187 end;
5188 end if;
5190 -- Make sure that the primitives Initialize, Adjust and Finalize
5191 -- are Frozen before other TSS subprograms. We don't want them
5192 -- Frozen inside.
5194 if Is_Controlled (Typ) then
5195 if not Is_Limited_Type (Typ) then
5196 Append_Freeze_Actions (Typ,
5197 Freeze_Entity (Find_Prim_Op (Typ, Name_Adjust), Typ));
5198 end if;
5200 Append_Freeze_Actions (Typ,
5201 Freeze_Entity (Find_Prim_Op (Typ, Name_Initialize), Typ));
5203 Append_Freeze_Actions (Typ,
5204 Freeze_Entity (Find_Prim_Op (Typ, Name_Finalize), Typ));
5205 end if;
5207 -- Freeze rest of primitive operations. There is no need to handle
5208 -- the predefined primitives if we are compiling under restriction
5209 -- No_Dispatching_Calls.
5211 if not Restriction_Active (No_Dispatching_Calls) then
5212 Append_Freeze_Actions (Typ, Predefined_Primitive_Freeze (Typ));
5213 end if;
5214 end if;
5216 -- In the untagged case, ever since Ada 83 an equality function must
5217 -- be provided for variant records that are not unchecked unions.
5218 -- In Ada 2012 the equality function composes, and thus must be built
5219 -- explicitly just as for tagged records.
5221 elsif Has_Discriminants (Typ)
5222 and then not Is_Limited_Type (Typ)
5223 then
5224 declare
5225 Comps : constant Node_Id :=
5226 Component_List (Type_Definition (Typ_Decl));
5227 begin
5228 if Present (Comps)
5229 and then Present (Variant_Part (Comps))
5230 then
5231 Build_Variant_Record_Equality (Typ);
5232 end if;
5233 end;
5235 -- Otherwise create primitive equality operation (AI05-0123)
5237 -- This is done unconditionally to ensure that tools can be linked
5238 -- properly with user programs compiled with older language versions.
5239 -- In addition, this is needed because "=" composes for bounded strings
5240 -- in all language versions (see Exp_Ch4.Expand_Composite_Equality).
5242 elsif Comes_From_Source (Typ)
5243 and then Convention (Typ) = Convention_Ada
5244 and then not Is_Limited_Type (Typ)
5245 then
5246 Build_Untagged_Equality (Typ);
5247 end if;
5249 -- Before building the record initialization procedure, if we are
5250 -- dealing with a concurrent record value type, then we must go through
5251 -- the discriminants, exchanging discriminals between the concurrent
5252 -- type and the concurrent record value type. See the section "Handling
5253 -- of Discriminants" in the Einfo spec for details.
5255 if Is_Concurrent_Record_Type (Typ)
5256 and then Has_Discriminants (Typ)
5257 then
5258 declare
5259 Ctyp : constant Entity_Id :=
5260 Corresponding_Concurrent_Type (Typ);
5261 Conc_Discr : Entity_Id;
5262 Rec_Discr : Entity_Id;
5263 Temp : Entity_Id;
5265 begin
5266 Conc_Discr := First_Discriminant (Ctyp);
5267 Rec_Discr := First_Discriminant (Typ);
5268 while Present (Conc_Discr) loop
5269 Temp := Discriminal (Conc_Discr);
5270 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5271 Set_Discriminal (Rec_Discr, Temp);
5273 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5274 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5276 Next_Discriminant (Conc_Discr);
5277 Next_Discriminant (Rec_Discr);
5278 end loop;
5279 end;
5280 end if;
5282 if Has_Controlled_Component (Typ) then
5283 Build_Controlling_Procs (Typ);
5284 end if;
5286 Adjust_Discriminants (Typ);
5288 -- Do not need init for interfaces on virtual targets since they're
5289 -- abstract.
5291 if Tagged_Type_Expansion or else not Is_Interface (Typ) then
5292 Build_Record_Init_Proc (Typ_Decl, Typ);
5293 end if;
5295 -- For tagged type that are not interfaces, build bodies of primitive
5296 -- operations. Note: do this after building the record initialization
5297 -- procedure, since the primitive operations may need the initialization
5298 -- routine. There is no need to add predefined primitives of interfaces
5299 -- because all their predefined primitives are abstract.
5301 if Is_Tagged_Type (Typ) and then not Is_Interface (Typ) then
5303 -- Do not add the body of predefined primitives in case of CPP tagged
5304 -- type derivations that have convention CPP.
5306 if Is_CPP_Class (Root_Type (Typ))
5307 and then Convention (Typ) = Convention_CPP
5308 then
5309 null;
5311 -- Do not add the body of the predefined primitives if we are
5312 -- compiling under restriction No_Dispatching_Calls or if we are
5313 -- compiling a CPP tagged type.
5315 elsif not Restriction_Active (No_Dispatching_Calls) then
5317 -- Create the body of TSS primitive Finalize_Address. This must
5318 -- be done before the bodies of all predefined primitives are
5319 -- created. If Typ is limited, Stream_Input and Stream_Read may
5320 -- produce build-in-place allocations and for those the expander
5321 -- needs Finalize_Address.
5323 Make_Finalize_Address_Body (Typ);
5324 Predef_List := Predefined_Primitive_Bodies (Typ, Renamed_Eq);
5325 Append_Freeze_Actions (Typ, Predef_List);
5326 end if;
5328 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5329 -- inherited functions, then add their bodies to the freeze actions.
5331 if Present (Wrapper_Body_List) then
5332 Append_Freeze_Actions (Typ, Wrapper_Body_List);
5333 end if;
5335 -- Create extra formals for the primitive operations of the type.
5336 -- This must be done before analyzing the body of the initialization
5337 -- procedure, because a self-referential type might call one of these
5338 -- primitives in the body of the init_proc itself.
5340 declare
5341 Elmt : Elmt_Id;
5342 Subp : Entity_Id;
5344 begin
5345 Elmt := First_Elmt (Primitive_Operations (Typ));
5346 while Present (Elmt) loop
5347 Subp := Node (Elmt);
5348 if not Has_Foreign_Convention (Subp)
5349 and then not Is_Predefined_Dispatching_Operation (Subp)
5350 then
5351 Create_Extra_Formals (Subp);
5352 end if;
5354 Next_Elmt (Elmt);
5355 end loop;
5356 end;
5357 end if;
5358 end Expand_Freeze_Record_Type;
5360 ------------------------------------
5361 -- Expand_N_Full_Type_Declaration --
5362 ------------------------------------
5364 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
5365 procedure Build_Master (Ptr_Typ : Entity_Id);
5366 -- Create the master associated with Ptr_Typ
5368 ------------------
5369 -- Build_Master --
5370 ------------------
5372 procedure Build_Master (Ptr_Typ : Entity_Id) is
5373 Desig_Typ : Entity_Id := Designated_Type (Ptr_Typ);
5375 begin
5376 -- If the designated type is an incomplete view coming from a
5377 -- limited-with'ed package, we need to use the nonlimited view in
5378 -- case it has tasks.
5380 if Ekind (Desig_Typ) in Incomplete_Kind
5381 and then Present (Non_Limited_View (Desig_Typ))
5382 then
5383 Desig_Typ := Non_Limited_View (Desig_Typ);
5384 end if;
5386 -- Anonymous access types are created for the components of the
5387 -- record parameter for an entry declaration. No master is created
5388 -- for such a type.
5390 if Comes_From_Source (N) and then Has_Task (Desig_Typ) then
5391 Build_Master_Entity (Ptr_Typ);
5392 Build_Master_Renaming (Ptr_Typ);
5394 -- Create a class-wide master because a Master_Id must be generated
5395 -- for access-to-limited-class-wide types whose root may be extended
5396 -- with task components.
5398 -- Note: This code covers access-to-limited-interfaces because they
5399 -- can be used to reference tasks implementing them.
5401 elsif Is_Limited_Class_Wide_Type (Desig_Typ)
5402 and then Tasking_Allowed
5403 then
5404 Build_Class_Wide_Master (Ptr_Typ);
5405 end if;
5406 end Build_Master;
5408 -- Local declarations
5410 Def_Id : constant Entity_Id := Defining_Identifier (N);
5411 B_Id : constant Entity_Id := Base_Type (Def_Id);
5412 FN : Node_Id;
5413 Par_Id : Entity_Id;
5415 -- Start of processing for Expand_N_Full_Type_Declaration
5417 begin
5418 if Is_Access_Type (Def_Id) then
5419 Build_Master (Def_Id);
5421 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
5422 Expand_Access_Protected_Subprogram_Type (N);
5423 end if;
5425 -- Array of anonymous access-to-task pointers
5427 elsif Ada_Version >= Ada_2005
5428 and then Is_Array_Type (Def_Id)
5429 and then Is_Access_Type (Component_Type (Def_Id))
5430 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
5431 then
5432 Build_Master (Component_Type (Def_Id));
5434 elsif Has_Task (Def_Id) then
5435 Expand_Previous_Access_Type (Def_Id);
5437 -- Check the components of a record type or array of records for
5438 -- anonymous access-to-task pointers.
5440 elsif Ada_Version >= Ada_2005
5441 and then (Is_Record_Type (Def_Id)
5442 or else
5443 (Is_Array_Type (Def_Id)
5444 and then Is_Record_Type (Component_Type (Def_Id))))
5445 then
5446 declare
5447 Comp : Entity_Id;
5448 First : Boolean;
5449 M_Id : Entity_Id;
5450 Typ : Entity_Id;
5452 begin
5453 if Is_Array_Type (Def_Id) then
5454 Comp := First_Entity (Component_Type (Def_Id));
5455 else
5456 Comp := First_Entity (Def_Id);
5457 end if;
5459 -- Examine all components looking for anonymous access-to-task
5460 -- types.
5462 First := True;
5463 while Present (Comp) loop
5464 Typ := Etype (Comp);
5466 if Ekind (Typ) = E_Anonymous_Access_Type
5467 and then Has_Task (Available_View (Designated_Type (Typ)))
5468 and then No (Master_Id (Typ))
5469 then
5470 -- Ensure that the record or array type have a _master
5472 if First then
5473 Build_Master_Entity (Def_Id);
5474 Build_Master_Renaming (Typ);
5475 M_Id := Master_Id (Typ);
5477 First := False;
5479 -- Reuse the same master to service any additional types
5481 else
5482 Set_Master_Id (Typ, M_Id);
5483 end if;
5484 end if;
5486 Next_Entity (Comp);
5487 end loop;
5488 end;
5489 end if;
5491 Par_Id := Etype (B_Id);
5493 -- The parent type is private then we need to inherit any TSS operations
5494 -- from the full view.
5496 if Ekind (Par_Id) in Private_Kind
5497 and then Present (Full_View (Par_Id))
5498 then
5499 Par_Id := Base_Type (Full_View (Par_Id));
5500 end if;
5502 if Nkind (Type_Definition (Original_Node (N))) =
5503 N_Derived_Type_Definition
5504 and then not Is_Tagged_Type (Def_Id)
5505 and then Present (Freeze_Node (Par_Id))
5506 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
5507 then
5508 Ensure_Freeze_Node (B_Id);
5509 FN := Freeze_Node (B_Id);
5511 if No (TSS_Elist (FN)) then
5512 Set_TSS_Elist (FN, New_Elmt_List);
5513 end if;
5515 declare
5516 T_E : constant Elist_Id := TSS_Elist (FN);
5517 Elmt : Elmt_Id;
5519 begin
5520 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
5521 while Present (Elmt) loop
5522 if Chars (Node (Elmt)) /= Name_uInit then
5523 Append_Elmt (Node (Elmt), T_E);
5524 end if;
5526 Next_Elmt (Elmt);
5527 end loop;
5529 -- If the derived type itself is private with a full view, then
5530 -- associate the full view with the inherited TSS_Elist as well.
5532 if Ekind (B_Id) in Private_Kind
5533 and then Present (Full_View (B_Id))
5534 then
5535 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
5536 Set_TSS_Elist
5537 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
5538 end if;
5539 end;
5540 end if;
5541 end Expand_N_Full_Type_Declaration;
5543 ---------------------------------
5544 -- Expand_N_Object_Declaration --
5545 ---------------------------------
5547 procedure Expand_N_Object_Declaration (N : Node_Id) is
5548 Loc : constant Source_Ptr := Sloc (N);
5549 Def_Id : constant Entity_Id := Defining_Identifier (N);
5550 Expr : constant Node_Id := Expression (N);
5551 Obj_Def : constant Node_Id := Object_Definition (N);
5552 Typ : constant Entity_Id := Etype (Def_Id);
5553 Base_Typ : constant Entity_Id := Base_Type (Typ);
5554 Expr_Q : Node_Id;
5556 function Build_Equivalent_Aggregate return Boolean;
5557 -- If the object has a constrained discriminated type and no initial
5558 -- value, it may be possible to build an equivalent aggregate instead,
5559 -- and prevent an actual call to the initialization procedure.
5561 procedure Check_Large_Modular_Array;
5562 -- Check that the size of the array can be computed without overflow,
5563 -- and generate a Storage_Error otherwise. This is only relevant for
5564 -- array types whose index in a (mod 2**64) type, where wrap-around
5565 -- arithmetic might yield a meaningless value for the length of the
5566 -- array, or its corresponding attribute.
5568 procedure Default_Initialize_Object (After : Node_Id);
5569 -- Generate all default initialization actions for object Def_Id. Any
5570 -- new code is inserted after node After.
5572 function Rewrite_As_Renaming return Boolean;
5573 -- Indicate whether to rewrite a declaration with initialization into an
5574 -- object renaming declaration (see below).
5576 --------------------------------
5577 -- Build_Equivalent_Aggregate --
5578 --------------------------------
5580 function Build_Equivalent_Aggregate return Boolean is
5581 Aggr : Node_Id;
5582 Comp : Entity_Id;
5583 Discr : Elmt_Id;
5584 Full_Type : Entity_Id;
5586 begin
5587 Full_Type := Typ;
5589 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
5590 Full_Type := Full_View (Typ);
5591 end if;
5593 -- Only perform this transformation if Elaboration_Code is forbidden
5594 -- or undesirable, and if this is a global entity of a constrained
5595 -- record type.
5597 -- If Initialize_Scalars might be active this transformation cannot
5598 -- be performed either, because it will lead to different semantics
5599 -- or because elaboration code will in fact be created.
5601 if Ekind (Full_Type) /= E_Record_Subtype
5602 or else not Has_Discriminants (Full_Type)
5603 or else not Is_Constrained (Full_Type)
5604 or else Is_Controlled (Full_Type)
5605 or else Is_Limited_Type (Full_Type)
5606 or else not Restriction_Active (No_Initialize_Scalars)
5607 then
5608 return False;
5609 end if;
5611 if Ekind (Current_Scope) = E_Package
5612 and then
5613 (Restriction_Active (No_Elaboration_Code)
5614 or else Is_Preelaborated (Current_Scope))
5615 then
5616 -- Building a static aggregate is possible if the discriminants
5617 -- have static values and the other components have static
5618 -- defaults or none.
5620 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5621 while Present (Discr) loop
5622 if not Is_OK_Static_Expression (Node (Discr)) then
5623 return False;
5624 end if;
5626 Next_Elmt (Discr);
5627 end loop;
5629 -- Check that initialized components are OK, and that non-
5630 -- initialized components do not require a call to their own
5631 -- initialization procedure.
5633 Comp := First_Component (Full_Type);
5634 while Present (Comp) loop
5635 if Ekind (Comp) = E_Component
5636 and then Present (Expression (Parent (Comp)))
5637 and then
5638 not Is_OK_Static_Expression (Expression (Parent (Comp)))
5639 then
5640 return False;
5642 elsif Has_Non_Null_Base_Init_Proc (Etype (Comp)) then
5643 return False;
5645 end if;
5647 Next_Component (Comp);
5648 end loop;
5650 -- Everything is static, assemble the aggregate, discriminant
5651 -- values first.
5653 Aggr :=
5654 Make_Aggregate (Loc,
5655 Expressions => New_List,
5656 Component_Associations => New_List);
5658 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5659 while Present (Discr) loop
5660 Append_To (Expressions (Aggr), New_Copy (Node (Discr)));
5661 Next_Elmt (Discr);
5662 end loop;
5664 -- Now collect values of initialized components
5666 Comp := First_Component (Full_Type);
5667 while Present (Comp) loop
5668 if Ekind (Comp) = E_Component
5669 and then Present (Expression (Parent (Comp)))
5670 then
5671 Append_To (Component_Associations (Aggr),
5672 Make_Component_Association (Loc,
5673 Choices => New_List (New_Occurrence_Of (Comp, Loc)),
5674 Expression => New_Copy_Tree
5675 (Expression (Parent (Comp)))));
5676 end if;
5678 Next_Component (Comp);
5679 end loop;
5681 -- Finally, box-initialize remaining components
5683 Append_To (Component_Associations (Aggr),
5684 Make_Component_Association (Loc,
5685 Choices => New_List (Make_Others_Choice (Loc)),
5686 Expression => Empty));
5687 Set_Box_Present (Last (Component_Associations (Aggr)));
5688 Set_Expression (N, Aggr);
5690 if Typ /= Full_Type then
5691 Analyze_And_Resolve (Aggr, Full_View (Base_Type (Full_Type)));
5692 Rewrite (Aggr, Unchecked_Convert_To (Typ, Aggr));
5693 Analyze_And_Resolve (Aggr, Typ);
5694 else
5695 Analyze_And_Resolve (Aggr, Full_Type);
5696 end if;
5698 return True;
5700 else
5701 return False;
5702 end if;
5703 end Build_Equivalent_Aggregate;
5705 -------------------------------
5706 -- Check_Large_Modular_Array --
5707 -------------------------------
5709 procedure Check_Large_Modular_Array is
5710 Index_Typ : Entity_Id;
5712 begin
5713 if Is_Array_Type (Typ)
5714 and then Is_Modular_Integer_Type (Etype (First_Index (Typ)))
5715 then
5716 -- To prevent arithmetic overflow with large values, we raise
5717 -- Storage_Error under the following guard:
5719 -- (Arr'Last / 2 - Arr'First / 2) > (2 ** 30)
5721 -- This takes care of the boundary case, but it is preferable to
5722 -- use a smaller limit, because even on 64-bit architectures an
5723 -- array of more than 2 ** 30 bytes is likely to raise
5724 -- Storage_Error.
5726 Index_Typ := Etype (First_Index (Typ));
5728 if RM_Size (Index_Typ) = RM_Size (Standard_Long_Long_Integer) then
5729 Insert_Action (N,
5730 Make_Raise_Storage_Error (Loc,
5731 Condition =>
5732 Make_Op_Ge (Loc,
5733 Left_Opnd =>
5734 Make_Op_Subtract (Loc,
5735 Left_Opnd =>
5736 Make_Op_Divide (Loc,
5737 Left_Opnd =>
5738 Make_Attribute_Reference (Loc,
5739 Prefix =>
5740 New_Occurrence_Of (Typ, Loc),
5741 Attribute_Name => Name_Last),
5742 Right_Opnd =>
5743 Make_Integer_Literal (Loc, Uint_2)),
5744 Right_Opnd =>
5745 Make_Op_Divide (Loc,
5746 Left_Opnd =>
5747 Make_Attribute_Reference (Loc,
5748 Prefix =>
5749 New_Occurrence_Of (Typ, Loc),
5750 Attribute_Name => Name_First),
5751 Right_Opnd =>
5752 Make_Integer_Literal (Loc, Uint_2))),
5753 Right_Opnd =>
5754 Make_Integer_Literal (Loc, (Uint_2 ** 30))),
5755 Reason => SE_Object_Too_Large));
5756 end if;
5757 end if;
5758 end Check_Large_Modular_Array;
5760 -------------------------------
5761 -- Default_Initialize_Object --
5762 -------------------------------
5764 procedure Default_Initialize_Object (After : Node_Id) is
5765 function New_Object_Reference return Node_Id;
5766 -- Return a new reference to Def_Id with attributes Assignment_OK and
5767 -- Must_Not_Freeze already set.
5769 --------------------------
5770 -- New_Object_Reference --
5771 --------------------------
5773 function New_Object_Reference return Node_Id is
5774 Obj_Ref : constant Node_Id := New_Occurrence_Of (Def_Id, Loc);
5776 begin
5777 -- The call to the type init proc or [Deep_]Finalize must not
5778 -- freeze the related object as the call is internally generated.
5779 -- This way legal rep clauses that apply to the object will not be
5780 -- flagged. Note that the initialization call may be removed if
5781 -- pragma Import is encountered or moved to the freeze actions of
5782 -- the object because of an address clause.
5784 Set_Assignment_OK (Obj_Ref);
5785 Set_Must_Not_Freeze (Obj_Ref);
5787 return Obj_Ref;
5788 end New_Object_Reference;
5790 -- Local variables
5792 Exceptions_OK : constant Boolean :=
5793 not Restriction_Active (No_Exception_Propagation);
5795 Aggr_Init : Node_Id;
5796 Comp_Init : List_Id := No_List;
5797 Fin_Call : Node_Id;
5798 Init_Stmts : List_Id := No_List;
5799 Obj_Init : Node_Id := Empty;
5800 Obj_Ref : Node_Id;
5802 -- Start of processing for Default_Initialize_Object
5804 begin
5805 -- Default initialization is suppressed for objects that are already
5806 -- known to be imported (i.e. whose declaration specifies the Import
5807 -- aspect). Note that for objects with a pragma Import, we generate
5808 -- initialization here, and then remove it downstream when processing
5809 -- the pragma. It is also suppressed for variables for which a pragma
5810 -- Suppress_Initialization has been explicitly given
5812 if Is_Imported (Def_Id) or else Suppress_Initialization (Def_Id) then
5813 return;
5815 -- Nothing to do if the object being initialized is of a task type
5816 -- and restriction No_Tasking is in effect, because this is a direct
5817 -- violation of the restriction.
5819 elsif Is_Task_Type (Base_Typ)
5820 and then Restriction_Active (No_Tasking)
5821 then
5822 return;
5823 end if;
5825 -- The expansion performed by this routine is as follows:
5827 -- begin
5828 -- Abort_Defer;
5829 -- Type_Init_Proc (Obj);
5831 -- begin
5832 -- [Deep_]Initialize (Obj);
5834 -- exception
5835 -- when others =>
5836 -- [Deep_]Finalize (Obj, Self => False);
5837 -- raise;
5838 -- end;
5839 -- at end
5840 -- Abort_Undefer_Direct;
5841 -- end;
5843 -- Initialize the components of the object
5845 if Has_Non_Null_Base_Init_Proc (Typ)
5846 and then not No_Initialization (N)
5847 and then not Initialization_Suppressed (Typ)
5848 then
5849 -- Do not initialize the components if No_Default_Initialization
5850 -- applies as the actual restriction check will occur later
5851 -- when the object is frozen as it is not known yet whether the
5852 -- object is imported or not.
5854 if not Restriction_Active (No_Default_Initialization) then
5856 -- If the values of the components are compile-time known, use
5857 -- their prebuilt aggregate form directly.
5859 Aggr_Init := Static_Initialization (Base_Init_Proc (Typ));
5861 if Present (Aggr_Init) then
5862 Set_Expression
5863 (N, New_Copy_Tree (Aggr_Init, New_Scope => Current_Scope));
5865 -- If type has discriminants, try to build an equivalent
5866 -- aggregate using discriminant values from the declaration.
5867 -- This is a useful optimization, in particular if restriction
5868 -- No_Elaboration_Code is active.
5870 elsif Build_Equivalent_Aggregate then
5871 null;
5873 -- Otherwise invoke the type init proc, generate:
5874 -- Type_Init_Proc (Obj);
5876 else
5877 Obj_Ref := New_Object_Reference;
5879 if Comes_From_Source (Def_Id) then
5880 Initialization_Warning (Obj_Ref);
5881 end if;
5883 Comp_Init := Build_Initialization_Call (Loc, Obj_Ref, Typ);
5884 end if;
5885 end if;
5887 -- Provide a default value if the object needs simple initialization
5888 -- and does not already have an initial value. A generated temporary
5889 -- does not require initialization because it will be assigned later.
5891 elsif Needs_Simple_Initialization
5892 (Typ, Initialize_Scalars
5893 and then No (Following_Address_Clause (N)))
5894 and then not Is_Internal (Def_Id)
5895 and then not Has_Init_Expression (N)
5896 then
5897 Set_No_Initialization (N, False);
5898 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
5899 Analyze_And_Resolve (Expression (N), Typ);
5900 end if;
5902 -- Initialize the object, generate:
5903 -- [Deep_]Initialize (Obj);
5905 if Needs_Finalization (Typ) and then not No_Initialization (N) then
5906 Obj_Init :=
5907 Make_Init_Call
5908 (Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5909 Typ => Typ);
5910 end if;
5912 -- Build a special finalization block when both the object and its
5913 -- controlled components are to be initialized. The block finalizes
5914 -- the components if the object initialization fails. Generate:
5916 -- begin
5917 -- <Obj_Init>
5919 -- exception
5920 -- when others =>
5921 -- <Fin_Call>
5922 -- raise;
5923 -- end;
5925 if Has_Controlled_Component (Typ)
5926 and then Present (Comp_Init)
5927 and then Present (Obj_Init)
5928 and then Exceptions_OK
5929 then
5930 Init_Stmts := Comp_Init;
5932 Fin_Call :=
5933 Make_Final_Call
5934 (Obj_Ref => New_Object_Reference,
5935 Typ => Typ,
5936 Skip_Self => True);
5938 if Present (Fin_Call) then
5940 -- Do not emit warnings related to the elaboration order when a
5941 -- controlled object is declared before the body of Finalize is
5942 -- seen.
5944 Set_No_Elaboration_Check (Fin_Call);
5946 Append_To (Init_Stmts,
5947 Make_Block_Statement (Loc,
5948 Declarations => No_List,
5950 Handled_Statement_Sequence =>
5951 Make_Handled_Sequence_Of_Statements (Loc,
5952 Statements => New_List (Obj_Init),
5954 Exception_Handlers => New_List (
5955 Make_Exception_Handler (Loc,
5956 Exception_Choices => New_List (
5957 Make_Others_Choice (Loc)),
5959 Statements => New_List (
5960 Fin_Call,
5961 Make_Raise_Statement (Loc)))))));
5962 end if;
5964 -- Otherwise finalization is not required, the initialization calls
5965 -- are passed to the abort block building circuitry, generate:
5967 -- Type_Init_Proc (Obj);
5968 -- [Deep_]Initialize (Obj);
5970 else
5971 if Present (Comp_Init) then
5972 Init_Stmts := Comp_Init;
5973 end if;
5975 if Present (Obj_Init) then
5976 if No (Init_Stmts) then
5977 Init_Stmts := New_List;
5978 end if;
5980 Append_To (Init_Stmts, Obj_Init);
5981 end if;
5982 end if;
5984 -- Build an abort block to protect the initialization calls
5986 if Abort_Allowed
5987 and then Present (Comp_Init)
5988 and then Present (Obj_Init)
5989 then
5990 -- Generate:
5991 -- Abort_Defer;
5993 Prepend_To (Init_Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
5995 -- When exceptions are propagated, abort deferral must take place
5996 -- in the presence of initialization or finalization exceptions.
5997 -- Generate:
5999 -- begin
6000 -- Abort_Defer;
6001 -- <Init_Stmts>
6002 -- at end
6003 -- Abort_Undefer_Direct;
6004 -- end;
6006 if Exceptions_OK then
6007 Init_Stmts := New_List (
6008 Build_Abort_Undefer_Block (Loc,
6009 Stmts => Init_Stmts,
6010 Context => N));
6012 -- Otherwise exceptions are not propagated. Generate:
6014 -- Abort_Defer;
6015 -- <Init_Stmts>
6016 -- Abort_Undefer;
6018 else
6019 Append_To (Init_Stmts,
6020 Build_Runtime_Call (Loc, RE_Abort_Undefer));
6021 end if;
6022 end if;
6024 -- Insert the whole initialization sequence into the tree. If the
6025 -- object has a delayed freeze, as will be the case when it has
6026 -- aspect specifications, the initialization sequence is part of
6027 -- the freeze actions.
6029 if Present (Init_Stmts) then
6030 if Has_Delayed_Freeze (Def_Id) then
6031 Append_Freeze_Actions (Def_Id, Init_Stmts);
6032 else
6033 Insert_Actions_After (After, Init_Stmts);
6034 end if;
6035 end if;
6036 end Default_Initialize_Object;
6038 -------------------------
6039 -- Rewrite_As_Renaming --
6040 -------------------------
6042 function Rewrite_As_Renaming return Boolean is
6043 begin
6044 -- If the object declaration appears in the form
6046 -- Obj : Ctrl_Typ := Func (...);
6048 -- where Ctrl_Typ is controlled but not immutably limited type, then
6049 -- the expansion of the function call should use a dereference of the
6050 -- result to reference the value on the secondary stack.
6052 -- Obj : Ctrl_Typ renames Func (...).all;
6054 -- As a result, the call avoids an extra copy. This an optimization,
6055 -- but it is required for passing ACATS tests in some cases where it
6056 -- would otherwise make two copies. The RM allows removing redunant
6057 -- Adjust/Finalize calls, but does not allow insertion of extra ones.
6059 -- This part is disabled for now, because it breaks GPS builds
6061 return (False -- ???
6062 and then Nkind (Expr_Q) = N_Explicit_Dereference
6063 and then not Comes_From_Source (Expr_Q)
6064 and then Nkind (Original_Node (Expr_Q)) = N_Function_Call
6065 and then Nkind (Object_Definition (N)) in N_Has_Entity
6066 and then (Needs_Finalization (Entity (Object_Definition (N)))))
6068 -- If the initializing expression is for a variable with attribute
6069 -- OK_To_Rename set, then transform:
6071 -- Obj : Typ := Expr;
6073 -- into
6075 -- Obj : Typ renames Expr;
6077 -- provided that Obj is not aliased. The aliased case has to be
6078 -- excluded in general because Expr will not be aliased in
6079 -- general.
6081 or else
6082 (not Aliased_Present (N)
6083 and then Is_Entity_Name (Expr_Q)
6084 and then Ekind (Entity (Expr_Q)) = E_Variable
6085 and then OK_To_Rename (Entity (Expr_Q))
6086 and then Is_Entity_Name (Obj_Def));
6087 end Rewrite_As_Renaming;
6089 -- Local variables
6091 Next_N : constant Node_Id := Next (N);
6093 Adj_Call : Node_Id;
6094 Id_Ref : Node_Id;
6095 Tag_Assign : Node_Id;
6097 Init_After : Node_Id := N;
6098 -- Node after which the initialization actions are to be inserted. This
6099 -- is normally N, except for the case of a shared passive variable, in
6100 -- which case the init proc call must be inserted only after the bodies
6101 -- of the shared variable procedures have been seen.
6103 -- Start of processing for Expand_N_Object_Declaration
6105 begin
6106 -- Don't do anything for deferred constants. All proper actions will be
6107 -- expanded during the full declaration.
6109 if No (Expr) and Constant_Present (N) then
6110 return;
6111 end if;
6113 -- The type of the object cannot be abstract. This is diagnosed at the
6114 -- point the object is frozen, which happens after the declaration is
6115 -- fully expanded, so simply return now.
6117 if Is_Abstract_Type (Typ) then
6118 return;
6119 end if;
6121 -- First we do special processing for objects of a tagged type where
6122 -- this is the point at which the type is frozen. The creation of the
6123 -- dispatch table and the initialization procedure have to be deferred
6124 -- to this point, since we reference previously declared primitive
6125 -- subprograms.
6127 -- Force construction of dispatch tables of library level tagged types
6129 if Tagged_Type_Expansion
6130 and then Static_Dispatch_Tables
6131 and then Is_Library_Level_Entity (Def_Id)
6132 and then Is_Library_Level_Tagged_Type (Base_Typ)
6133 and then Ekind_In (Base_Typ, E_Record_Type,
6134 E_Protected_Type,
6135 E_Task_Type)
6136 and then not Has_Dispatch_Table (Base_Typ)
6137 then
6138 declare
6139 New_Nodes : List_Id := No_List;
6141 begin
6142 if Is_Concurrent_Type (Base_Typ) then
6143 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
6144 else
6145 New_Nodes := Make_DT (Base_Typ, N);
6146 end if;
6148 if not Is_Empty_List (New_Nodes) then
6149 Insert_List_Before (N, New_Nodes);
6150 end if;
6151 end;
6152 end if;
6154 -- Make shared memory routines for shared passive variable
6156 if Is_Shared_Passive (Def_Id) then
6157 Init_After := Make_Shared_Var_Procs (N);
6158 end if;
6160 -- If tasks being declared, make sure we have an activation chain
6161 -- defined for the tasks (has no effect if we already have one), and
6162 -- also that a Master variable is established and that the appropriate
6163 -- enclosing construct is established as a task master.
6165 if Has_Task (Typ) then
6166 Build_Activation_Chain_Entity (N);
6167 Build_Master_Entity (Def_Id);
6168 end if;
6170 Check_Large_Modular_Array;
6172 -- Default initialization required, and no expression present
6174 if No (Expr) then
6176 -- If we have a type with a variant part, the initialization proc
6177 -- will contain implicit tests of the discriminant values, which
6178 -- counts as a violation of the restriction No_Implicit_Conditionals.
6180 if Has_Variant_Part (Typ) then
6181 declare
6182 Msg : Boolean;
6184 begin
6185 Check_Restriction (Msg, No_Implicit_Conditionals, Obj_Def);
6187 if Msg then
6188 Error_Msg_N
6189 ("\initialization of variant record tests discriminants",
6190 Obj_Def);
6191 return;
6192 end if;
6193 end;
6194 end if;
6196 -- For the default initialization case, if we have a private type
6197 -- with invariants, and invariant checks are enabled, then insert an
6198 -- invariant check after the object declaration. Note that it is OK
6199 -- to clobber the object with an invalid value since if the exception
6200 -- is raised, then the object will go out of scope. In the case where
6201 -- an array object is initialized with an aggregate, the expression
6202 -- is removed. Check flag Has_Init_Expression to avoid generating a
6203 -- junk invariant check and flag No_Initialization to avoid checking
6204 -- an uninitialized object such as a compiler temporary used for an
6205 -- aggregate.
6207 if Has_Invariants (Base_Typ)
6208 and then Present (Invariant_Procedure (Base_Typ))
6209 and then not Has_Init_Expression (N)
6210 and then not No_Initialization (N)
6211 then
6212 -- If entity has an address clause or aspect, make invariant
6213 -- call into a freeze action for the explicit freeze node for
6214 -- object. Otherwise insert invariant check after declaration.
6216 if Present (Following_Address_Clause (N))
6217 or else Has_Aspect (Def_Id, Aspect_Address)
6218 then
6219 Ensure_Freeze_Node (Def_Id);
6220 Set_Has_Delayed_Freeze (Def_Id);
6221 Set_Is_Frozen (Def_Id, False);
6223 if not Partial_View_Has_Unknown_Discr (Typ) then
6224 Append_Freeze_Action (Def_Id,
6225 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
6226 end if;
6228 elsif not Partial_View_Has_Unknown_Discr (Typ) then
6229 Insert_After (N,
6230 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
6231 end if;
6232 end if;
6234 Default_Initialize_Object (Init_After);
6236 -- Generate attribute for Persistent_BSS if needed
6238 if Persistent_BSS_Mode
6239 and then Comes_From_Source (N)
6240 and then Is_Potentially_Persistent_Type (Typ)
6241 and then not Has_Init_Expression (N)
6242 and then Is_Library_Level_Entity (Def_Id)
6243 then
6244 declare
6245 Prag : Node_Id;
6246 begin
6247 Prag :=
6248 Make_Linker_Section_Pragma
6249 (Def_Id, Sloc (N), ".persistent.bss");
6250 Insert_After (N, Prag);
6251 Analyze (Prag);
6252 end;
6253 end if;
6255 -- If access type, then we know it is null if not initialized
6257 if Is_Access_Type (Typ) then
6258 Set_Is_Known_Null (Def_Id);
6259 end if;
6261 -- Explicit initialization present
6263 else
6264 -- Obtain actual expression from qualified expression
6266 if Nkind (Expr) = N_Qualified_Expression then
6267 Expr_Q := Expression (Expr);
6268 else
6269 Expr_Q := Expr;
6270 end if;
6272 -- When we have the appropriate type of aggregate in the expression
6273 -- (it has been determined during analysis of the aggregate by
6274 -- setting the delay flag), let's perform in place assignment and
6275 -- thus avoid creating a temporary.
6277 if Is_Delayed_Aggregate (Expr_Q) then
6278 Convert_Aggr_In_Object_Decl (N);
6280 -- Ada 2005 (AI-318-02): If the initialization expression is a call
6281 -- to a build-in-place function, then access to the declared object
6282 -- must be passed to the function. Currently we limit such functions
6283 -- to those with constrained limited result subtypes, but eventually
6284 -- plan to expand the allowed forms of functions that are treated as
6285 -- build-in-place.
6287 elsif Ada_Version >= Ada_2005
6288 and then Is_Build_In_Place_Function_Call (Expr_Q)
6289 then
6290 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
6292 -- The previous call expands the expression initializing the
6293 -- built-in-place object into further code that will be analyzed
6294 -- later. No further expansion needed here.
6296 return;
6298 -- Ada 2005 (AI-318-02): Specialization of the previous case for
6299 -- expressions containing a build-in-place function call whose
6300 -- returned object covers interface types, and Expr_Q has calls to
6301 -- Ada.Tags.Displace to displace the pointer to the returned build-
6302 -- in-place object to reference the secondary dispatch table of a
6303 -- covered interface type.
6305 elsif Ada_Version >= Ada_2005
6306 and then Present (Unqual_BIP_Iface_Function_Call (Expr_Q))
6307 then
6308 Make_Build_In_Place_Iface_Call_In_Object_Declaration (N, Expr_Q);
6310 -- The previous call expands the expression initializing the
6311 -- built-in-place object into further code that will be analyzed
6312 -- later. No further expansion needed here.
6314 return;
6316 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
6317 -- class-wide interface object to ensure that we copy the full
6318 -- object, unless we are targetting a VM where interfaces are handled
6319 -- by VM itself. Note that if the root type of Typ is an ancestor of
6320 -- Expr's type, both types share the same dispatch table and there is
6321 -- no need to displace the pointer.
6323 elsif Is_Interface (Typ)
6325 -- Avoid never-ending recursion because if Equivalent_Type is set
6326 -- then we've done it already and must not do it again.
6328 and then not
6329 (Nkind (Obj_Def) = N_Identifier
6330 and then Present (Equivalent_Type (Entity (Obj_Def))))
6331 then
6332 pragma Assert (Is_Class_Wide_Type (Typ));
6334 -- If the object is a return object of an inherently limited type,
6335 -- which implies build-in-place treatment, bypass the special
6336 -- treatment of class-wide interface initialization below. In this
6337 -- case, the expansion of the return statement will take care of
6338 -- creating the object (via allocator) and initializing it.
6340 if Is_Return_Object (Def_Id) and then Is_Limited_View (Typ) then
6341 null;
6343 elsif Tagged_Type_Expansion then
6344 declare
6345 Iface : constant Entity_Id := Root_Type (Typ);
6346 Expr_N : Node_Id := Expr;
6347 Expr_Typ : Entity_Id;
6348 New_Expr : Node_Id;
6349 Obj_Id : Entity_Id;
6350 Tag_Comp : Node_Id;
6352 begin
6353 -- If the original node of the expression was a conversion
6354 -- to this specific class-wide interface type then restore
6355 -- the original node because we must copy the object before
6356 -- displacing the pointer to reference the secondary tag
6357 -- component. This code must be kept synchronized with the
6358 -- expansion done by routine Expand_Interface_Conversion
6360 if not Comes_From_Source (Expr_N)
6361 and then Nkind (Expr_N) = N_Explicit_Dereference
6362 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
6363 and then Etype (Original_Node (Expr_N)) = Typ
6364 then
6365 Rewrite (Expr_N, Original_Node (Expression (N)));
6366 end if;
6368 -- Avoid expansion of redundant interface conversion
6370 if Is_Interface (Etype (Expr_N))
6371 and then Nkind (Expr_N) = N_Type_Conversion
6372 and then Etype (Expr_N) = Typ
6373 then
6374 Expr_N := Expression (Expr_N);
6375 Set_Expression (N, Expr_N);
6376 end if;
6378 Obj_Id := Make_Temporary (Loc, 'D', Expr_N);
6379 Expr_Typ := Base_Type (Etype (Expr_N));
6381 if Is_Class_Wide_Type (Expr_Typ) then
6382 Expr_Typ := Root_Type (Expr_Typ);
6383 end if;
6385 -- Replace
6386 -- CW : I'Class := Obj;
6387 -- by
6388 -- Tmp : T := Obj;
6389 -- type Ityp is not null access I'Class;
6390 -- CW : I'Class renames Ityp (Tmp.I_Tag'Address).all;
6392 if Comes_From_Source (Expr_N)
6393 and then Nkind (Expr_N) = N_Identifier
6394 and then not Is_Interface (Expr_Typ)
6395 and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
6396 and then (Expr_Typ = Etype (Expr_Typ)
6397 or else not
6398 Is_Variable_Size_Record (Etype (Expr_Typ)))
6399 then
6400 -- Copy the object
6402 Insert_Action (N,
6403 Make_Object_Declaration (Loc,
6404 Defining_Identifier => Obj_Id,
6405 Object_Definition =>
6406 New_Occurrence_Of (Expr_Typ, Loc),
6407 Expression => Relocate_Node (Expr_N)));
6409 -- Statically reference the tag associated with the
6410 -- interface
6412 Tag_Comp :=
6413 Make_Selected_Component (Loc,
6414 Prefix => New_Occurrence_Of (Obj_Id, Loc),
6415 Selector_Name =>
6416 New_Occurrence_Of
6417 (Find_Interface_Tag (Expr_Typ, Iface), Loc));
6419 -- Replace
6420 -- IW : I'Class := Obj;
6421 -- by
6422 -- type Equiv_Record is record ... end record;
6423 -- implicit subtype CW is <Class_Wide_Subtype>;
6424 -- Tmp : CW := CW!(Obj);
6425 -- type Ityp is not null access I'Class;
6426 -- IW : I'Class renames
6427 -- Ityp!(Displace (Temp'Address, I'Tag)).all;
6429 else
6430 -- Generate the equivalent record type and update the
6431 -- subtype indication to reference it.
6433 Expand_Subtype_From_Expr
6434 (N => N,
6435 Unc_Type => Typ,
6436 Subtype_Indic => Obj_Def,
6437 Exp => Expr_N);
6439 if not Is_Interface (Etype (Expr_N)) then
6440 New_Expr := Relocate_Node (Expr_N);
6442 -- For interface types we use 'Address which displaces
6443 -- the pointer to the base of the object (if required)
6445 else
6446 New_Expr :=
6447 Unchecked_Convert_To (Etype (Obj_Def),
6448 Make_Explicit_Dereference (Loc,
6449 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
6450 Make_Attribute_Reference (Loc,
6451 Prefix => Relocate_Node (Expr_N),
6452 Attribute_Name => Name_Address))));
6453 end if;
6455 -- Copy the object
6457 if not Is_Limited_Record (Expr_Typ) then
6458 Insert_Action (N,
6459 Make_Object_Declaration (Loc,
6460 Defining_Identifier => Obj_Id,
6461 Object_Definition =>
6462 New_Occurrence_Of (Etype (Obj_Def), Loc),
6463 Expression => New_Expr));
6465 -- Rename limited type object since they cannot be copied
6466 -- This case occurs when the initialization expression
6467 -- has been previously expanded into a temporary object.
6469 else pragma Assert (not Comes_From_Source (Expr_Q));
6470 Insert_Action (N,
6471 Make_Object_Renaming_Declaration (Loc,
6472 Defining_Identifier => Obj_Id,
6473 Subtype_Mark =>
6474 New_Occurrence_Of (Etype (Obj_Def), Loc),
6475 Name =>
6476 Unchecked_Convert_To
6477 (Etype (Obj_Def), New_Expr)));
6478 end if;
6480 -- Dynamically reference the tag associated with the
6481 -- interface.
6483 Tag_Comp :=
6484 Make_Function_Call (Loc,
6485 Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
6486 Parameter_Associations => New_List (
6487 Make_Attribute_Reference (Loc,
6488 Prefix => New_Occurrence_Of (Obj_Id, Loc),
6489 Attribute_Name => Name_Address),
6490 New_Occurrence_Of
6491 (Node (First_Elmt (Access_Disp_Table (Iface))),
6492 Loc)));
6493 end if;
6495 Rewrite (N,
6496 Make_Object_Renaming_Declaration (Loc,
6497 Defining_Identifier => Make_Temporary (Loc, 'D'),
6498 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
6499 Name =>
6500 Convert_Tag_To_Interface (Typ, Tag_Comp)));
6502 -- If the original entity comes from source, then mark the
6503 -- new entity as needing debug information, even though it's
6504 -- defined by a generated renaming that does not come from
6505 -- source, so that Materialize_Entity will be set on the
6506 -- entity when Debug_Renaming_Declaration is called during
6507 -- analysis.
6509 if Comes_From_Source (Def_Id) then
6510 Set_Debug_Info_Needed (Defining_Identifier (N));
6511 end if;
6513 Analyze (N, Suppress => All_Checks);
6515 -- Replace internal identifier of rewritten node by the
6516 -- identifier found in the sources. We also have to exchange
6517 -- entities containing their defining identifiers to ensure
6518 -- the correct replacement of the object declaration by this
6519 -- object renaming declaration because these identifiers
6520 -- were previously added by Enter_Name to the current scope.
6521 -- We must preserve the homonym chain of the source entity
6522 -- as well. We must also preserve the kind of the entity,
6523 -- which may be a constant. Preserve entity chain because
6524 -- itypes may have been generated already, and the full
6525 -- chain must be preserved for final freezing. Finally,
6526 -- preserve Comes_From_Source setting, so that debugging
6527 -- and cross-referencing information is properly kept, and
6528 -- preserve source location, to prevent spurious errors when
6529 -- entities are declared (they must have their own Sloc).
6531 declare
6532 New_Id : constant Entity_Id := Defining_Identifier (N);
6533 Next_Temp : constant Entity_Id := Next_Entity (New_Id);
6534 S_Flag : constant Boolean :=
6535 Comes_From_Source (Def_Id);
6537 begin
6538 Set_Next_Entity (New_Id, Next_Entity (Def_Id));
6539 Set_Next_Entity (Def_Id, Next_Temp);
6541 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
6542 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
6543 Set_Ekind (Defining_Identifier (N), Ekind (Def_Id));
6544 Set_Sloc (Defining_Identifier (N), Sloc (Def_Id));
6546 Set_Comes_From_Source (Def_Id, False);
6547 Exchange_Entities (Defining_Identifier (N), Def_Id);
6548 Set_Comes_From_Source (Def_Id, S_Flag);
6549 end;
6550 end;
6551 end if;
6553 return;
6555 -- Common case of explicit object initialization
6557 else
6558 -- In most cases, we must check that the initial value meets any
6559 -- constraint imposed by the declared type. However, there is one
6560 -- very important exception to this rule. If the entity has an
6561 -- unconstrained nominal subtype, then it acquired its constraints
6562 -- from the expression in the first place, and not only does this
6563 -- mean that the constraint check is not needed, but an attempt to
6564 -- perform the constraint check can cause order of elaboration
6565 -- problems.
6567 if not Is_Constr_Subt_For_U_Nominal (Typ) then
6569 -- If this is an allocator for an aggregate that has been
6570 -- allocated in place, delay checks until assignments are
6571 -- made, because the discriminants are not initialized.
6573 if Nkind (Expr) = N_Allocator and then No_Initialization (Expr)
6574 then
6575 null;
6577 -- Otherwise apply a constraint check now if no prev error
6579 elsif Nkind (Expr) /= N_Error then
6580 Apply_Constraint_Check (Expr, Typ);
6582 -- Deal with possible range check
6584 if Do_Range_Check (Expr) then
6586 -- If assignment checks are suppressed, turn off flag
6588 if Suppress_Assignment_Checks (N) then
6589 Set_Do_Range_Check (Expr, False);
6591 -- Otherwise generate the range check
6593 else
6594 Generate_Range_Check
6595 (Expr, Typ, CE_Range_Check_Failed);
6596 end if;
6597 end if;
6598 end if;
6599 end if;
6601 -- If the type is controlled and not inherently limited, then
6602 -- the target is adjusted after the copy and attached to the
6603 -- finalization list. However, no adjustment is done in the case
6604 -- where the object was initialized by a call to a function whose
6605 -- result is built in place, since no copy occurred. (Eventually
6606 -- we plan to support in-place function results for some cases
6607 -- of nonlimited types. ???) Similarly, no adjustment is required
6608 -- if we are going to rewrite the object declaration into a
6609 -- renaming declaration.
6611 if Needs_Finalization (Typ)
6612 and then not Is_Limited_View (Typ)
6613 and then not Rewrite_As_Renaming
6614 then
6615 Adj_Call :=
6616 Make_Adjust_Call (
6617 Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
6618 Typ => Base_Typ);
6620 -- Guard against a missing [Deep_]Adjust when the base type
6621 -- was not properly frozen.
6623 if Present (Adj_Call) then
6624 Insert_Action_After (Init_After, Adj_Call);
6625 end if;
6626 end if;
6628 -- For tagged types, when an init value is given, the tag has to
6629 -- be re-initialized separately in order to avoid the propagation
6630 -- of a wrong tag coming from a view conversion unless the type
6631 -- is class wide (in this case the tag comes from the init value).
6632 -- Suppress the tag assignment when not Tagged_Type_Expansion
6633 -- because tags are represented implicitly in objects. Ditto for
6634 -- types that are CPP_CLASS, and for initializations that are
6635 -- aggregates, because they have to have the right tag.
6637 -- The re-assignment of the tag has to be done even if the object
6638 -- is a constant. The assignment must be analyzed after the
6639 -- declaration. If an address clause follows, this is handled as
6640 -- part of the freeze actions for the object, otherwise insert
6641 -- tag assignment here.
6643 Tag_Assign := Make_Tag_Assignment (N);
6645 if Present (Tag_Assign) then
6646 if Present (Following_Address_Clause (N)) then
6647 Ensure_Freeze_Node (Def_Id);
6649 else
6650 Insert_Action_After (Init_After, Tag_Assign);
6651 end if;
6653 -- Handle C++ constructor calls. Note that we do not check that
6654 -- Typ is a tagged type since the equivalent Ada type of a C++
6655 -- class that has no virtual methods is an untagged limited
6656 -- record type.
6658 elsif Is_CPP_Constructor_Call (Expr) then
6660 -- The call to the initialization procedure does NOT freeze the
6661 -- object being initialized.
6663 Id_Ref := New_Occurrence_Of (Def_Id, Loc);
6664 Set_Must_Not_Freeze (Id_Ref);
6665 Set_Assignment_OK (Id_Ref);
6667 Insert_Actions_After (Init_After,
6668 Build_Initialization_Call (Loc, Id_Ref, Typ,
6669 Constructor_Ref => Expr));
6671 -- We remove here the original call to the constructor
6672 -- to avoid its management in the backend
6674 Set_Expression (N, Empty);
6675 return;
6677 -- Handle initialization of limited tagged types
6679 elsif Is_Tagged_Type (Typ)
6680 and then Is_Class_Wide_Type (Typ)
6681 and then Is_Limited_Record (Typ)
6682 and then not Is_Limited_Interface (Typ)
6683 then
6684 -- Given that the type is limited we cannot perform a copy. If
6685 -- Expr_Q is the reference to a variable we mark the variable
6686 -- as OK_To_Rename to expand this declaration into a renaming
6687 -- declaration (see bellow).
6689 if Is_Entity_Name (Expr_Q) then
6690 Set_OK_To_Rename (Entity (Expr_Q));
6692 -- If we cannot convert the expression into a renaming we must
6693 -- consider it an internal error because the backend does not
6694 -- have support to handle it.
6696 else
6697 pragma Assert (False);
6698 raise Program_Error;
6699 end if;
6701 -- For discrete types, set the Is_Known_Valid flag if the
6702 -- initializing value is known to be valid. Only do this for
6703 -- source assignments, since otherwise we can end up turning
6704 -- on the known valid flag prematurely from inserted code.
6706 elsif Comes_From_Source (N)
6707 and then Is_Discrete_Type (Typ)
6708 and then Expr_Known_Valid (Expr)
6709 then
6710 Set_Is_Known_Valid (Def_Id);
6712 elsif Is_Access_Type (Typ) then
6714 -- For access types set the Is_Known_Non_Null flag if the
6715 -- initializing value is known to be non-null. We can also set
6716 -- Can_Never_Be_Null if this is a constant.
6718 if Known_Non_Null (Expr) then
6719 Set_Is_Known_Non_Null (Def_Id, True);
6721 if Constant_Present (N) then
6722 Set_Can_Never_Be_Null (Def_Id);
6723 end if;
6724 end if;
6725 end if;
6727 -- If validity checking on copies, validate initial expression.
6728 -- But skip this if declaration is for a generic type, since it
6729 -- makes no sense to validate generic types. Not clear if this
6730 -- can happen for legal programs, but it definitely can arise
6731 -- from previous instantiation errors.
6733 if Validity_Checks_On
6734 and then Comes_From_Source (N)
6735 and then Validity_Check_Copies
6736 and then not Is_Generic_Type (Etype (Def_Id))
6737 then
6738 Ensure_Valid (Expr);
6739 Set_Is_Known_Valid (Def_Id);
6740 end if;
6741 end if;
6743 -- Cases where the back end cannot handle the initialization directly
6744 -- In such cases, we expand an assignment that will be appropriately
6745 -- handled by Expand_N_Assignment_Statement.
6747 -- The exclusion of the unconstrained case is wrong, but for now it
6748 -- is too much trouble ???
6750 if (Is_Possibly_Unaligned_Slice (Expr)
6751 or else (Is_Possibly_Unaligned_Object (Expr)
6752 and then not Represented_As_Scalar (Etype (Expr))))
6753 and then not (Is_Array_Type (Etype (Expr))
6754 and then not Is_Constrained (Etype (Expr)))
6755 then
6756 declare
6757 Stat : constant Node_Id :=
6758 Make_Assignment_Statement (Loc,
6759 Name => New_Occurrence_Of (Def_Id, Loc),
6760 Expression => Relocate_Node (Expr));
6761 begin
6762 Set_Expression (N, Empty);
6763 Set_No_Initialization (N);
6764 Set_Assignment_OK (Name (Stat));
6765 Set_No_Ctrl_Actions (Stat);
6766 Insert_After_And_Analyze (Init_After, Stat);
6767 end;
6768 end if;
6769 end if;
6771 if Nkind (Obj_Def) = N_Access_Definition
6772 and then not Is_Local_Anonymous_Access (Etype (Def_Id))
6773 then
6774 -- An Ada 2012 stand-alone object of an anonymous access type
6776 declare
6777 Loc : constant Source_Ptr := Sloc (N);
6779 Level : constant Entity_Id :=
6780 Make_Defining_Identifier (Sloc (N),
6781 Chars =>
6782 New_External_Name (Chars (Def_Id), Suffix => "L"));
6784 Level_Expr : Node_Id;
6785 Level_Decl : Node_Id;
6787 begin
6788 Set_Ekind (Level, Ekind (Def_Id));
6789 Set_Etype (Level, Standard_Natural);
6790 Set_Scope (Level, Scope (Def_Id));
6792 if No (Expr) then
6794 -- Set accessibility level of null
6796 Level_Expr :=
6797 Make_Integer_Literal (Loc, Scope_Depth (Standard_Standard));
6799 else
6800 Level_Expr := Dynamic_Accessibility_Level (Expr);
6801 end if;
6803 Level_Decl :=
6804 Make_Object_Declaration (Loc,
6805 Defining_Identifier => Level,
6806 Object_Definition =>
6807 New_Occurrence_Of (Standard_Natural, Loc),
6808 Expression => Level_Expr,
6809 Constant_Present => Constant_Present (N),
6810 Has_Init_Expression => True);
6812 Insert_Action_After (Init_After, Level_Decl);
6814 Set_Extra_Accessibility (Def_Id, Level);
6815 end;
6816 end if;
6818 -- If the object is default initialized and its type is subject to
6819 -- pragma Default_Initial_Condition, add a runtime check to verify
6820 -- the assumption of the pragma (SPARK RM 7.3.3). Generate:
6822 -- <Base_Typ>DIC (<Base_Typ> (Def_Id));
6824 -- Note that the check is generated for source objects only
6826 if Comes_From_Source (Def_Id)
6827 and then Has_DIC (Typ)
6828 and then Present (DIC_Procedure (Typ))
6829 and then not Has_Init_Expression (N)
6830 then
6831 declare
6832 DIC_Call : constant Node_Id := Build_DIC_Call (Loc, Def_Id, Typ);
6834 begin
6835 if Present (Next_N) then
6836 Insert_Before_And_Analyze (Next_N, DIC_Call);
6838 -- The object declaration is the last node in a declarative or a
6839 -- statement list.
6841 else
6842 Append_To (List_Containing (N), DIC_Call);
6843 Analyze (DIC_Call);
6844 end if;
6845 end;
6846 end if;
6848 -- Final transformation - turn the object declaration into a renaming
6849 -- if appropriate. If this is the completion of a deferred constant
6850 -- declaration, then this transformation generates what would be
6851 -- illegal code if written by hand, but that's OK.
6853 if Present (Expr) then
6854 if Rewrite_As_Renaming then
6855 Rewrite (N,
6856 Make_Object_Renaming_Declaration (Loc,
6857 Defining_Identifier => Defining_Identifier (N),
6858 Subtype_Mark => Obj_Def,
6859 Name => Expr_Q));
6861 -- We do not analyze this renaming declaration, because all its
6862 -- components have already been analyzed, and if we were to go
6863 -- ahead and analyze it, we would in effect be trying to generate
6864 -- another declaration of X, which won't do.
6866 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
6867 Set_Analyzed (N);
6869 -- We do need to deal with debug issues for this renaming
6871 -- First, if entity comes from source, then mark it as needing
6872 -- debug information, even though it is defined by a generated
6873 -- renaming that does not come from source.
6875 if Comes_From_Source (Defining_Identifier (N)) then
6876 Set_Debug_Info_Needed (Defining_Identifier (N));
6877 end if;
6879 -- Now call the routine to generate debug info for the renaming
6881 declare
6882 Decl : constant Node_Id := Debug_Renaming_Declaration (N);
6883 begin
6884 if Present (Decl) then
6885 Insert_Action (N, Decl);
6886 end if;
6887 end;
6888 end if;
6889 end if;
6891 -- Exception on library entity not available
6893 exception
6894 when RE_Not_Available =>
6895 return;
6896 end Expand_N_Object_Declaration;
6898 ---------------------------------
6899 -- Expand_N_Subtype_Indication --
6900 ---------------------------------
6902 -- Add a check on the range of the subtype. The static case is partially
6903 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
6904 -- to check here for the static case in order to avoid generating
6905 -- extraneous expanded code. Also deal with validity checking.
6907 procedure Expand_N_Subtype_Indication (N : Node_Id) is
6908 Ran : constant Node_Id := Range_Expression (Constraint (N));
6909 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6911 begin
6912 if Nkind (Constraint (N)) = N_Range_Constraint then
6913 Validity_Check_Range (Range_Expression (Constraint (N)));
6914 end if;
6916 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
6917 Apply_Range_Check (Ran, Typ);
6918 end if;
6919 end Expand_N_Subtype_Indication;
6921 ---------------------------
6922 -- Expand_N_Variant_Part --
6923 ---------------------------
6925 -- Note: this procedure no longer has any effect. It used to be that we
6926 -- would replace the choices in the last variant by a when others, and
6927 -- also expanded static predicates in variant choices here, but both of
6928 -- those activities were being done too early, since we can't check the
6929 -- choices until the statically predicated subtypes are frozen, which can
6930 -- happen as late as the free point of the record, and we can't change the
6931 -- last choice to an others before checking the choices, which is now done
6932 -- at the freeze point of the record.
6934 procedure Expand_N_Variant_Part (N : Node_Id) is
6935 begin
6936 null;
6937 end Expand_N_Variant_Part;
6939 ---------------------------------
6940 -- Expand_Previous_Access_Type --
6941 ---------------------------------
6943 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
6944 Ptr_Typ : Entity_Id;
6946 begin
6947 -- Find all access types in the current scope whose designated type is
6948 -- Def_Id and build master renamings for them.
6950 Ptr_Typ := First_Entity (Current_Scope);
6951 while Present (Ptr_Typ) loop
6952 if Is_Access_Type (Ptr_Typ)
6953 and then Designated_Type (Ptr_Typ) = Def_Id
6954 and then No (Master_Id (Ptr_Typ))
6955 then
6956 -- Ensure that the designated type has a master
6958 Build_Master_Entity (Def_Id);
6960 -- Private and incomplete types complicate the insertion of master
6961 -- renamings because the access type may precede the full view of
6962 -- the designated type. For this reason, the master renamings are
6963 -- inserted relative to the designated type.
6965 Build_Master_Renaming (Ptr_Typ, Ins_Nod => Parent (Def_Id));
6966 end if;
6968 Next_Entity (Ptr_Typ);
6969 end loop;
6970 end Expand_Previous_Access_Type;
6972 -----------------------------
6973 -- Expand_Record_Extension --
6974 -----------------------------
6976 -- Add a field _parent at the beginning of the record extension. This is
6977 -- used to implement inheritance. Here are some examples of expansion:
6979 -- 1. no discriminants
6980 -- type T2 is new T1 with null record;
6981 -- gives
6982 -- type T2 is new T1 with record
6983 -- _Parent : T1;
6984 -- end record;
6986 -- 2. renamed discriminants
6987 -- type T2 (B, C : Int) is new T1 (A => B) with record
6988 -- _Parent : T1 (A => B);
6989 -- D : Int;
6990 -- end;
6992 -- 3. inherited discriminants
6993 -- type T2 is new T1 with record -- discriminant A inherited
6994 -- _Parent : T1 (A);
6995 -- D : Int;
6996 -- end;
6998 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
6999 Indic : constant Node_Id := Subtype_Indication (Def);
7000 Loc : constant Source_Ptr := Sloc (Def);
7001 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
7002 Par_Subtype : Entity_Id;
7003 Comp_List : Node_Id;
7004 Comp_Decl : Node_Id;
7005 Parent_N : Node_Id;
7006 D : Entity_Id;
7007 List_Constr : constant List_Id := New_List;
7009 begin
7010 -- Expand_Record_Extension is called directly from the semantics, so
7011 -- we must check to see whether expansion is active before proceeding,
7012 -- because this affects the visibility of selected components in bodies
7013 -- of instances.
7015 if not Expander_Active then
7016 return;
7017 end if;
7019 -- This may be a derivation of an untagged private type whose full
7020 -- view is tagged, in which case the Derived_Type_Definition has no
7021 -- extension part. Build an empty one now.
7023 if No (Rec_Ext_Part) then
7024 Rec_Ext_Part :=
7025 Make_Record_Definition (Loc,
7026 End_Label => Empty,
7027 Component_List => Empty,
7028 Null_Present => True);
7030 Set_Record_Extension_Part (Def, Rec_Ext_Part);
7031 Mark_Rewrite_Insertion (Rec_Ext_Part);
7032 end if;
7034 Comp_List := Component_List (Rec_Ext_Part);
7036 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
7038 -- If the derived type inherits its discriminants the type of the
7039 -- _parent field must be constrained by the inherited discriminants
7041 if Has_Discriminants (T)
7042 and then Nkind (Indic) /= N_Subtype_Indication
7043 and then not Is_Constrained (Entity (Indic))
7044 then
7045 D := First_Discriminant (T);
7046 while Present (D) loop
7047 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
7048 Next_Discriminant (D);
7049 end loop;
7051 Par_Subtype :=
7052 Process_Subtype (
7053 Make_Subtype_Indication (Loc,
7054 Subtype_Mark => New_Occurrence_Of (Entity (Indic), Loc),
7055 Constraint =>
7056 Make_Index_Or_Discriminant_Constraint (Loc,
7057 Constraints => List_Constr)),
7058 Def);
7060 -- Otherwise the original subtype_indication is just what is needed
7062 else
7063 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
7064 end if;
7066 Set_Parent_Subtype (T, Par_Subtype);
7068 Comp_Decl :=
7069 Make_Component_Declaration (Loc,
7070 Defining_Identifier => Parent_N,
7071 Component_Definition =>
7072 Make_Component_Definition (Loc,
7073 Aliased_Present => False,
7074 Subtype_Indication => New_Occurrence_Of (Par_Subtype, Loc)));
7076 if Null_Present (Rec_Ext_Part) then
7077 Set_Component_List (Rec_Ext_Part,
7078 Make_Component_List (Loc,
7079 Component_Items => New_List (Comp_Decl),
7080 Variant_Part => Empty,
7081 Null_Present => False));
7082 Set_Null_Present (Rec_Ext_Part, False);
7084 elsif Null_Present (Comp_List)
7085 or else Is_Empty_List (Component_Items (Comp_List))
7086 then
7087 Set_Component_Items (Comp_List, New_List (Comp_Decl));
7088 Set_Null_Present (Comp_List, False);
7090 else
7091 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7092 end if;
7094 Analyze (Comp_Decl);
7095 end Expand_Record_Extension;
7097 ------------------------
7098 -- Expand_Tagged_Root --
7099 ------------------------
7101 procedure Expand_Tagged_Root (T : Entity_Id) is
7102 Def : constant Node_Id := Type_Definition (Parent (T));
7103 Comp_List : Node_Id;
7104 Comp_Decl : Node_Id;
7105 Sloc_N : Source_Ptr;
7107 begin
7108 if Null_Present (Def) then
7109 Set_Component_List (Def,
7110 Make_Component_List (Sloc (Def),
7111 Component_Items => Empty_List,
7112 Variant_Part => Empty,
7113 Null_Present => True));
7114 end if;
7116 Comp_List := Component_List (Def);
7118 if Null_Present (Comp_List)
7119 or else Is_Empty_List (Component_Items (Comp_List))
7120 then
7121 Sloc_N := Sloc (Comp_List);
7122 else
7123 Sloc_N := Sloc (First (Component_Items (Comp_List)));
7124 end if;
7126 Comp_Decl :=
7127 Make_Component_Declaration (Sloc_N,
7128 Defining_Identifier => First_Tag_Component (T),
7129 Component_Definition =>
7130 Make_Component_Definition (Sloc_N,
7131 Aliased_Present => False,
7132 Subtype_Indication => New_Occurrence_Of (RTE (RE_Tag), Sloc_N)));
7134 if Null_Present (Comp_List)
7135 or else Is_Empty_List (Component_Items (Comp_List))
7136 then
7137 Set_Component_Items (Comp_List, New_List (Comp_Decl));
7138 Set_Null_Present (Comp_List, False);
7140 else
7141 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7142 end if;
7144 -- We don't Analyze the whole expansion because the tag component has
7145 -- already been analyzed previously. Here we just insure that the tree
7146 -- is coherent with the semantic decoration
7148 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
7150 exception
7151 when RE_Not_Available =>
7152 return;
7153 end Expand_Tagged_Root;
7155 ------------------------------
7156 -- Freeze_Stream_Operations --
7157 ------------------------------
7159 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
7160 Names : constant array (1 .. 4) of TSS_Name_Type :=
7161 (TSS_Stream_Input,
7162 TSS_Stream_Output,
7163 TSS_Stream_Read,
7164 TSS_Stream_Write);
7165 Stream_Op : Entity_Id;
7167 begin
7168 -- Primitive operations of tagged types are frozen when the dispatch
7169 -- table is constructed.
7171 if not Comes_From_Source (Typ) or else Is_Tagged_Type (Typ) then
7172 return;
7173 end if;
7175 for J in Names'Range loop
7176 Stream_Op := TSS (Typ, Names (J));
7178 if Present (Stream_Op)
7179 and then Is_Subprogram (Stream_Op)
7180 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
7181 N_Subprogram_Declaration
7182 and then not Is_Frozen (Stream_Op)
7183 then
7184 Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
7185 end if;
7186 end loop;
7187 end Freeze_Stream_Operations;
7189 -----------------
7190 -- Freeze_Type --
7191 -----------------
7193 -- Full type declarations are expanded at the point at which the type is
7194 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
7195 -- declarations generated by the freezing (e.g. the procedure generated
7196 -- for initialization) are chained in the Actions field list of the freeze
7197 -- node using Append_Freeze_Actions.
7199 -- WARNING: This routine manages Ghost regions. Return statements must be
7200 -- replaced by gotos which jump to the end of the routine and restore the
7201 -- Ghost mode.
7203 function Freeze_Type (N : Node_Id) return Boolean is
7204 procedure Process_RACW_Types (Typ : Entity_Id);
7205 -- Validate and generate stubs for all RACW types associated with type
7206 -- Typ.
7208 procedure Process_Pending_Access_Types (Typ : Entity_Id);
7209 -- Associate type Typ's Finalize_Address primitive with the finalization
7210 -- masters of pending access-to-Typ types.
7212 ------------------------
7213 -- Process_RACW_Types --
7214 ------------------------
7216 procedure Process_RACW_Types (Typ : Entity_Id) is
7217 List : constant Elist_Id := Access_Types_To_Process (N);
7218 E : Elmt_Id;
7219 Seen : Boolean := False;
7221 begin
7222 if Present (List) then
7223 E := First_Elmt (List);
7224 while Present (E) loop
7225 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
7226 Validate_RACW_Primitives (Node (E));
7227 Seen := True;
7228 end if;
7230 Next_Elmt (E);
7231 end loop;
7232 end if;
7234 -- If there are RACWs designating this type, make stubs now
7236 if Seen then
7237 Remote_Types_Tagged_Full_View_Encountered (Typ);
7238 end if;
7239 end Process_RACW_Types;
7241 ----------------------------------
7242 -- Process_Pending_Access_Types --
7243 ----------------------------------
7245 procedure Process_Pending_Access_Types (Typ : Entity_Id) is
7246 E : Elmt_Id;
7248 begin
7249 -- Finalize_Address is not generated in CodePeer mode because the
7250 -- body contains address arithmetic. This processing is disabled.
7252 if CodePeer_Mode then
7253 null;
7255 -- Certain itypes are generated for contexts that cannot allocate
7256 -- objects and should not set primitive Finalize_Address.
7258 elsif Is_Itype (Typ)
7259 and then Nkind (Associated_Node_For_Itype (Typ)) =
7260 N_Explicit_Dereference
7261 then
7262 null;
7264 -- When an access type is declared after the incomplete view of a
7265 -- Taft-amendment type, the access type is considered pending in
7266 -- case the full view of the Taft-amendment type is controlled. If
7267 -- this is indeed the case, associate the Finalize_Address routine
7268 -- of the full view with the finalization masters of all pending
7269 -- access types. This scenario applies to anonymous access types as
7270 -- well.
7272 elsif Needs_Finalization (Typ)
7273 and then Present (Pending_Access_Types (Typ))
7274 then
7275 E := First_Elmt (Pending_Access_Types (Typ));
7276 while Present (E) loop
7278 -- Generate:
7279 -- Set_Finalize_Address
7280 -- (Ptr_Typ, <Typ>FD'Unrestricted_Access);
7282 Append_Freeze_Action (Typ,
7283 Make_Set_Finalize_Address_Call
7284 (Loc => Sloc (N),
7285 Ptr_Typ => Node (E)));
7287 Next_Elmt (E);
7288 end loop;
7289 end if;
7290 end Process_Pending_Access_Types;
7292 -- Local variables
7294 Def_Id : constant Entity_Id := Entity (N);
7296 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
7297 -- Save the Ghost mode to restore on exit
7299 Result : Boolean := False;
7301 -- Start of processing for Freeze_Type
7303 begin
7304 -- The type being frozen may be subject to pragma Ghost. Set the mode
7305 -- now to ensure that any nodes generated during freezing are properly
7306 -- marked as Ghost.
7308 Set_Ghost_Mode (Def_Id);
7310 -- Process any remote access-to-class-wide types designating the type
7311 -- being frozen.
7313 Process_RACW_Types (Def_Id);
7315 -- Freeze processing for record types
7317 if Is_Record_Type (Def_Id) then
7318 if Ekind (Def_Id) = E_Record_Type then
7319 Expand_Freeze_Record_Type (N);
7320 elsif Is_Class_Wide_Type (Def_Id) then
7321 Expand_Freeze_Class_Wide_Type (N);
7322 end if;
7324 -- Freeze processing for array types
7326 elsif Is_Array_Type (Def_Id) then
7327 Expand_Freeze_Array_Type (N);
7329 -- Freeze processing for access types
7331 -- For pool-specific access types, find out the pool object used for
7332 -- this type, needs actual expansion of it in some cases. Here are the
7333 -- different cases :
7335 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
7336 -- ---> don't use any storage pool
7338 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
7339 -- Expand:
7340 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
7342 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7343 -- ---> Storage Pool is the specified one
7345 -- See GNAT Pool packages in the Run-Time for more details
7347 elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
7348 declare
7349 Loc : constant Source_Ptr := Sloc (N);
7350 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
7352 Freeze_Action_Typ : Entity_Id;
7353 Pool_Object : Entity_Id;
7355 begin
7356 -- Case 1
7358 -- Rep Clause "for Def_Id'Storage_Size use 0;"
7359 -- ---> don't use any storage pool
7361 if No_Pool_Assigned (Def_Id) then
7362 null;
7364 -- Case 2
7366 -- Rep Clause : for Def_Id'Storage_Size use Expr.
7367 -- ---> Expand:
7368 -- Def_Id__Pool : Stack_Bounded_Pool
7369 -- (Expr, DT'Size, DT'Alignment);
7371 elsif Has_Storage_Size_Clause (Def_Id) then
7372 declare
7373 DT_Align : Node_Id;
7374 DT_Size : Node_Id;
7376 begin
7377 -- For unconstrained composite types we give a size of zero
7378 -- so that the pool knows that it needs a special algorithm
7379 -- for variable size object allocation.
7381 if Is_Composite_Type (Desig_Type)
7382 and then not Is_Constrained (Desig_Type)
7383 then
7384 DT_Size := Make_Integer_Literal (Loc, 0);
7385 DT_Align := Make_Integer_Literal (Loc, Maximum_Alignment);
7387 else
7388 DT_Size :=
7389 Make_Attribute_Reference (Loc,
7390 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7391 Attribute_Name => Name_Max_Size_In_Storage_Elements);
7393 DT_Align :=
7394 Make_Attribute_Reference (Loc,
7395 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7396 Attribute_Name => Name_Alignment);
7397 end if;
7399 Pool_Object :=
7400 Make_Defining_Identifier (Loc,
7401 Chars => New_External_Name (Chars (Def_Id), 'P'));
7403 -- We put the code associated with the pools in the entity
7404 -- that has the later freeze node, usually the access type
7405 -- but it can also be the designated_type; because the pool
7406 -- code requires both those types to be frozen
7408 if Is_Frozen (Desig_Type)
7409 and then (No (Freeze_Node (Desig_Type))
7410 or else Analyzed (Freeze_Node (Desig_Type)))
7411 then
7412 Freeze_Action_Typ := Def_Id;
7414 -- A Taft amendment type cannot get the freeze actions
7415 -- since the full view is not there.
7417 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
7418 and then No (Full_View (Desig_Type))
7419 then
7420 Freeze_Action_Typ := Def_Id;
7422 else
7423 Freeze_Action_Typ := Desig_Type;
7424 end if;
7426 Append_Freeze_Action (Freeze_Action_Typ,
7427 Make_Object_Declaration (Loc,
7428 Defining_Identifier => Pool_Object,
7429 Object_Definition =>
7430 Make_Subtype_Indication (Loc,
7431 Subtype_Mark =>
7432 New_Occurrence_Of
7433 (RTE (RE_Stack_Bounded_Pool), Loc),
7435 Constraint =>
7436 Make_Index_Or_Discriminant_Constraint (Loc,
7437 Constraints => New_List (
7439 -- First discriminant is the Pool Size
7441 New_Occurrence_Of (
7442 Storage_Size_Variable (Def_Id), Loc),
7444 -- Second discriminant is the element size
7446 DT_Size,
7448 -- Third discriminant is the alignment
7450 DT_Align)))));
7451 end;
7453 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
7455 -- Case 3
7457 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7458 -- ---> Storage Pool is the specified one
7460 -- When compiling in Ada 2012 mode, ensure that the accessibility
7461 -- level of the subpool access type is not deeper than that of the
7462 -- pool_with_subpools.
7464 elsif Ada_Version >= Ada_2012
7465 and then Present (Associated_Storage_Pool (Def_Id))
7467 -- Omit this check for the case of a configurable run-time that
7468 -- does not provide package System.Storage_Pools.Subpools.
7470 and then RTE_Available (RE_Root_Storage_Pool_With_Subpools)
7471 then
7472 declare
7473 Loc : constant Source_Ptr := Sloc (Def_Id);
7474 Pool : constant Entity_Id :=
7475 Associated_Storage_Pool (Def_Id);
7476 RSPWS : constant Entity_Id :=
7477 RTE (RE_Root_Storage_Pool_With_Subpools);
7479 begin
7480 -- It is known that the accessibility level of the access
7481 -- type is deeper than that of the pool.
7483 if Type_Access_Level (Def_Id) > Object_Access_Level (Pool)
7484 and then not Accessibility_Checks_Suppressed (Def_Id)
7485 and then not Accessibility_Checks_Suppressed (Pool)
7486 then
7487 -- Static case: the pool is known to be a descendant of
7488 -- Root_Storage_Pool_With_Subpools.
7490 if Is_Ancestor (RSPWS, Etype (Pool)) then
7491 Error_Msg_N
7492 ("??subpool access type has deeper accessibility "
7493 & "level than pool", Def_Id);
7495 Append_Freeze_Action (Def_Id,
7496 Make_Raise_Program_Error (Loc,
7497 Reason => PE_Accessibility_Check_Failed));
7499 -- Dynamic case: when the pool is of a class-wide type,
7500 -- it may or may not support subpools depending on the
7501 -- path of derivation. Generate:
7503 -- if Def_Id in RSPWS'Class then
7504 -- raise Program_Error;
7505 -- end if;
7507 elsif Is_Class_Wide_Type (Etype (Pool)) then
7508 Append_Freeze_Action (Def_Id,
7509 Make_If_Statement (Loc,
7510 Condition =>
7511 Make_In (Loc,
7512 Left_Opnd => New_Occurrence_Of (Pool, Loc),
7513 Right_Opnd =>
7514 New_Occurrence_Of
7515 (Class_Wide_Type (RSPWS), Loc)),
7517 Then_Statements => New_List (
7518 Make_Raise_Program_Error (Loc,
7519 Reason => PE_Accessibility_Check_Failed))));
7520 end if;
7521 end if;
7522 end;
7523 end if;
7525 -- For access-to-controlled types (including class-wide types and
7526 -- Taft-amendment types, which potentially have controlled
7527 -- components), expand the list controller object that will store
7528 -- the dynamically allocated objects. Don't do this transformation
7529 -- for expander-generated access types, but do it for types that
7530 -- are the full view of types derived from other private types.
7531 -- Also suppress the list controller in the case of a designated
7532 -- type with convention Java, since this is used when binding to
7533 -- Java API specs, where there's no equivalent of a finalization
7534 -- list and we don't want to pull in the finalization support if
7535 -- not needed.
7537 if not Comes_From_Source (Def_Id)
7538 and then not Has_Private_Declaration (Def_Id)
7539 then
7540 null;
7542 -- An exception is made for types defined in the run-time because
7543 -- Ada.Tags.Tag itself is such a type and cannot afford this
7544 -- unnecessary overhead that would generates a loop in the
7545 -- expansion scheme. Another exception is if Restrictions
7546 -- (No_Finalization) is active, since then we know nothing is
7547 -- controlled.
7549 elsif Restriction_Active (No_Finalization)
7550 or else In_Runtime (Def_Id)
7551 then
7552 null;
7554 -- Create a finalization master for an access-to-controlled type
7555 -- or an access-to-incomplete type. It is assumed that the full
7556 -- view will be controlled.
7558 elsif Needs_Finalization (Desig_Type)
7559 or else (Is_Incomplete_Type (Desig_Type)
7560 and then No (Full_View (Desig_Type)))
7561 then
7562 Build_Finalization_Master (Def_Id);
7564 -- Create a finalization master when the designated type contains
7565 -- a private component. It is assumed that the full view will be
7566 -- controlled.
7568 elsif Has_Private_Component (Desig_Type) then
7569 Build_Finalization_Master
7570 (Typ => Def_Id,
7571 For_Private => True,
7572 Context_Scope => Scope (Def_Id),
7573 Insertion_Node => Declaration_Node (Desig_Type));
7574 end if;
7575 end;
7577 -- Freeze processing for enumeration types
7579 elsif Ekind (Def_Id) = E_Enumeration_Type then
7581 -- We only have something to do if we have a non-standard
7582 -- representation (i.e. at least one literal whose pos value
7583 -- is not the same as its representation)
7585 if Has_Non_Standard_Rep (Def_Id) then
7586 Expand_Freeze_Enumeration_Type (N);
7587 end if;
7589 -- Private types that are completed by a derivation from a private
7590 -- type have an internally generated full view, that needs to be
7591 -- frozen. This must be done explicitly because the two views share
7592 -- the freeze node, and the underlying full view is not visible when
7593 -- the freeze node is analyzed.
7595 elsif Is_Private_Type (Def_Id)
7596 and then Is_Derived_Type (Def_Id)
7597 and then Present (Full_View (Def_Id))
7598 and then Is_Itype (Full_View (Def_Id))
7599 and then Has_Private_Declaration (Full_View (Def_Id))
7600 and then Freeze_Node (Full_View (Def_Id)) = N
7601 then
7602 Set_Entity (N, Full_View (Def_Id));
7603 Result := Freeze_Type (N);
7604 Set_Entity (N, Def_Id);
7606 -- All other types require no expander action. There are such cases
7607 -- (e.g. task types and protected types). In such cases, the freeze
7608 -- nodes are there for use by Gigi.
7610 end if;
7612 -- Complete the initialization of all pending access types' finalization
7613 -- masters now that the designated type has been is frozen and primitive
7614 -- Finalize_Address generated.
7616 Process_Pending_Access_Types (Def_Id);
7617 Freeze_Stream_Operations (N, Def_Id);
7619 -- Generate the [spec and] body of the procedure tasked with the runtime
7620 -- verification of pragma Default_Initial_Condition's expression.
7622 if Has_DIC (Def_Id) then
7623 Build_DIC_Procedure_Body (Def_Id, For_Freeze => True);
7624 end if;
7626 -- Generate the [spec and] body of the invariant procedure tasked with
7627 -- the runtime verification of all invariants that pertain to the type.
7628 -- This includes invariants on the partial and full view, inherited
7629 -- class-wide invariants from parent types or interfaces, and invariants
7630 -- on array elements or record components.
7632 if Is_Interface (Def_Id) then
7634 -- Interfaces are treated as the partial view of a private type in
7635 -- order to achieve uniformity with the general case. As a result, an
7636 -- interface receives only a "partial" invariant procedure which is
7637 -- never called.
7639 if Has_Own_Invariants (Def_Id) then
7640 Build_Invariant_Procedure_Body
7641 (Typ => Def_Id,
7642 Partial_Invariant => Is_Interface (Def_Id));
7643 end if;
7645 -- Non-interface types
7647 -- Do not generate invariant procedure within other assertion
7648 -- subprograms, which may involve local declarations of local
7649 -- subtypes to which these checks do not apply.
7651 elsif Has_Invariants (Def_Id) then
7652 if Within_Internal_Subprogram
7653 or else (Ekind (Current_Scope) = E_Function
7654 and then Is_Predicate_Function (Current_Scope))
7655 then
7656 null;
7657 else
7658 Build_Invariant_Procedure_Body (Def_Id);
7659 end if;
7660 end if;
7662 Restore_Ghost_Mode (Saved_GM);
7664 return Result;
7666 exception
7667 when RE_Not_Available =>
7668 Restore_Ghost_Mode (Saved_GM);
7670 return False;
7671 end Freeze_Type;
7673 -------------------------
7674 -- Get_Simple_Init_Val --
7675 -------------------------
7677 function Get_Simple_Init_Val
7678 (T : Entity_Id;
7679 N : Node_Id;
7680 Size : Uint := No_Uint) return Node_Id
7682 Loc : constant Source_Ptr := Sloc (N);
7683 Val : Node_Id;
7684 Result : Node_Id;
7685 Val_RE : RE_Id;
7687 Size_To_Use : Uint;
7688 -- This is the size to be used for computation of the appropriate
7689 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
7691 IV_Attribute : constant Boolean :=
7692 Nkind (N) = N_Attribute_Reference
7693 and then Attribute_Name (N) = Name_Invalid_Value;
7695 Lo_Bound : Uint;
7696 Hi_Bound : Uint;
7697 -- These are the values computed by the procedure Check_Subtype_Bounds
7699 procedure Check_Subtype_Bounds;
7700 -- This procedure examines the subtype T, and its ancestor subtypes and
7701 -- derived types to determine the best known information about the
7702 -- bounds of the subtype. After the call Lo_Bound is set either to
7703 -- No_Uint if no information can be determined, or to a value which
7704 -- represents a known low bound, i.e. a valid value of the subtype can
7705 -- not be less than this value. Hi_Bound is similarly set to a known
7706 -- high bound (valid value cannot be greater than this).
7708 --------------------------
7709 -- Check_Subtype_Bounds --
7710 --------------------------
7712 procedure Check_Subtype_Bounds is
7713 ST1 : Entity_Id;
7714 ST2 : Entity_Id;
7715 Lo : Node_Id;
7716 Hi : Node_Id;
7717 Loval : Uint;
7718 Hival : Uint;
7720 begin
7721 Lo_Bound := No_Uint;
7722 Hi_Bound := No_Uint;
7724 -- Loop to climb ancestor subtypes and derived types
7726 ST1 := T;
7727 loop
7728 if not Is_Discrete_Type (ST1) then
7729 return;
7730 end if;
7732 Lo := Type_Low_Bound (ST1);
7733 Hi := Type_High_Bound (ST1);
7735 if Compile_Time_Known_Value (Lo) then
7736 Loval := Expr_Value (Lo);
7738 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
7739 Lo_Bound := Loval;
7740 end if;
7741 end if;
7743 if Compile_Time_Known_Value (Hi) then
7744 Hival := Expr_Value (Hi);
7746 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
7747 Hi_Bound := Hival;
7748 end if;
7749 end if;
7751 ST2 := Ancestor_Subtype (ST1);
7753 if No (ST2) then
7754 ST2 := Etype (ST1);
7755 end if;
7757 exit when ST1 = ST2;
7758 ST1 := ST2;
7759 end loop;
7760 end Check_Subtype_Bounds;
7762 -- Start of processing for Get_Simple_Init_Val
7764 begin
7765 -- For a private type, we should always have an underlying type (because
7766 -- this was already checked in Needs_Simple_Initialization). What we do
7767 -- is to get the value for the underlying type and then do an unchecked
7768 -- conversion to the private type.
7770 if Is_Private_Type (T) then
7771 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
7773 -- A special case, if the underlying value is null, then qualify it
7774 -- with the underlying type, so that the null is properly typed.
7775 -- Similarly, if it is an aggregate it must be qualified, because an
7776 -- unchecked conversion does not provide a context for it.
7778 if Nkind_In (Val, N_Null, N_Aggregate) then
7779 Val :=
7780 Make_Qualified_Expression (Loc,
7781 Subtype_Mark =>
7782 New_Occurrence_Of (Underlying_Type (T), Loc),
7783 Expression => Val);
7784 end if;
7786 Result := Unchecked_Convert_To (T, Val);
7788 -- Don't truncate result (important for Initialize/Normalize_Scalars)
7790 if Nkind (Result) = N_Unchecked_Type_Conversion
7791 and then Is_Scalar_Type (Underlying_Type (T))
7792 then
7793 Set_No_Truncation (Result);
7794 end if;
7796 return Result;
7798 -- Scalars with Default_Value aspect. The first subtype may now be
7799 -- private, so retrieve value from underlying type.
7801 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
7802 if Is_Private_Type (First_Subtype (T)) then
7803 return Unchecked_Convert_To (T,
7804 Default_Aspect_Value (Full_View (First_Subtype (T))));
7805 else
7806 return
7807 Convert_To (T, Default_Aspect_Value (First_Subtype (T)));
7808 end if;
7810 -- Otherwise, for scalars, we must have normalize/initialize scalars
7811 -- case, or if the node N is an 'Invalid_Value attribute node.
7813 elsif Is_Scalar_Type (T) then
7814 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
7816 -- Compute size of object. If it is given by the caller, we can use
7817 -- it directly, otherwise we use Esize (T) as an estimate. As far as
7818 -- we know this covers all cases correctly.
7820 if Size = No_Uint or else Size <= Uint_0 then
7821 Size_To_Use := UI_Max (Uint_1, Esize (T));
7822 else
7823 Size_To_Use := Size;
7824 end if;
7826 -- Maximum size to use is 64 bits, since we will create values of
7827 -- type Unsigned_64 and the range must fit this type.
7829 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
7830 Size_To_Use := Uint_64;
7831 end if;
7833 -- Check known bounds of subtype
7835 Check_Subtype_Bounds;
7837 -- Processing for Normalize_Scalars case
7839 if Normalize_Scalars and then not IV_Attribute then
7841 -- If zero is invalid, it is a convenient value to use that is
7842 -- for sure an appropriate invalid value in all situations.
7844 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7845 Val := Make_Integer_Literal (Loc, 0);
7847 -- Cases where all one bits is the appropriate invalid value
7849 -- For modular types, all 1 bits is either invalid or valid. If
7850 -- it is valid, then there is nothing that can be done since there
7851 -- are no invalid values (we ruled out zero already).
7853 -- For signed integer types that have no negative values, either
7854 -- there is room for negative values, or there is not. If there
7855 -- is, then all 1-bits may be interpreted as minus one, which is
7856 -- certainly invalid. Alternatively it is treated as the largest
7857 -- positive value, in which case the observation for modular types
7858 -- still applies.
7860 -- For float types, all 1-bits is a NaN (not a number), which is
7861 -- certainly an appropriately invalid value.
7863 elsif Is_Unsigned_Type (T)
7864 or else Is_Floating_Point_Type (T)
7865 or else Is_Enumeration_Type (T)
7866 then
7867 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
7869 -- Resolve as Unsigned_64, because the largest number we can
7870 -- generate is out of range of universal integer.
7872 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
7874 -- Case of signed types
7876 else
7877 declare
7878 Signed_Size : constant Uint :=
7879 UI_Min (Uint_63, Size_To_Use - 1);
7881 begin
7882 -- Normally we like to use the most negative number. The one
7883 -- exception is when this number is in the known subtype
7884 -- range and the largest positive number is not in the known
7885 -- subtype range.
7887 -- For this exceptional case, use largest positive value
7889 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
7890 and then Lo_Bound <= (-(2 ** Signed_Size))
7891 and then Hi_Bound < 2 ** Signed_Size
7892 then
7893 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
7895 -- Normal case of largest negative value
7897 else
7898 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
7899 end if;
7900 end;
7901 end if;
7903 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
7905 else
7906 -- For float types, use float values from System.Scalar_Values
7908 if Is_Floating_Point_Type (T) then
7909 if Root_Type (T) = Standard_Short_Float then
7910 Val_RE := RE_IS_Isf;
7911 elsif Root_Type (T) = Standard_Float then
7912 Val_RE := RE_IS_Ifl;
7913 elsif Root_Type (T) = Standard_Long_Float then
7914 Val_RE := RE_IS_Ilf;
7915 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
7916 Val_RE := RE_IS_Ill;
7917 end if;
7919 -- If zero is invalid, use zero values from System.Scalar_Values
7921 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7922 if Size_To_Use <= 8 then
7923 Val_RE := RE_IS_Iz1;
7924 elsif Size_To_Use <= 16 then
7925 Val_RE := RE_IS_Iz2;
7926 elsif Size_To_Use <= 32 then
7927 Val_RE := RE_IS_Iz4;
7928 else
7929 Val_RE := RE_IS_Iz8;
7930 end if;
7932 -- For unsigned, use unsigned values from System.Scalar_Values
7934 elsif Is_Unsigned_Type (T) then
7935 if Size_To_Use <= 8 then
7936 Val_RE := RE_IS_Iu1;
7937 elsif Size_To_Use <= 16 then
7938 Val_RE := RE_IS_Iu2;
7939 elsif Size_To_Use <= 32 then
7940 Val_RE := RE_IS_Iu4;
7941 else
7942 Val_RE := RE_IS_Iu8;
7943 end if;
7945 -- For signed, use signed values from System.Scalar_Values
7947 else
7948 if Size_To_Use <= 8 then
7949 Val_RE := RE_IS_Is1;
7950 elsif Size_To_Use <= 16 then
7951 Val_RE := RE_IS_Is2;
7952 elsif Size_To_Use <= 32 then
7953 Val_RE := RE_IS_Is4;
7954 else
7955 Val_RE := RE_IS_Is8;
7956 end if;
7957 end if;
7959 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
7960 end if;
7962 -- The final expression is obtained by doing an unchecked conversion
7963 -- of this result to the base type of the required subtype. Use the
7964 -- base type to prevent the unchecked conversion from chopping bits,
7965 -- and then we set Kill_Range_Check to preserve the "bad" value.
7967 Result := Unchecked_Convert_To (Base_Type (T), Val);
7969 -- Ensure result is not truncated, since we want the "bad" bits, and
7970 -- also kill range check on result.
7972 if Nkind (Result) = N_Unchecked_Type_Conversion then
7973 Set_No_Truncation (Result);
7974 Set_Kill_Range_Check (Result, True);
7975 end if;
7977 return Result;
7979 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
7981 elsif Is_Standard_String_Type (T) then
7982 pragma Assert (Init_Or_Norm_Scalars);
7984 return
7985 Make_Aggregate (Loc,
7986 Component_Associations => New_List (
7987 Make_Component_Association (Loc,
7988 Choices => New_List (
7989 Make_Others_Choice (Loc)),
7990 Expression =>
7991 Get_Simple_Init_Val
7992 (Component_Type (T), N, Esize (Root_Type (T))))));
7994 -- Access type is initialized to null
7996 elsif Is_Access_Type (T) then
7997 return Make_Null (Loc);
7999 -- No other possibilities should arise, since we should only be calling
8000 -- Get_Simple_Init_Val if Needs_Simple_Initialization returned True,
8001 -- indicating one of the above cases held.
8003 else
8004 raise Program_Error;
8005 end if;
8007 exception
8008 when RE_Not_Available =>
8009 return Empty;
8010 end Get_Simple_Init_Val;
8012 ------------------------------
8013 -- Has_New_Non_Standard_Rep --
8014 ------------------------------
8016 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
8017 begin
8018 if not Is_Derived_Type (T) then
8019 return Has_Non_Standard_Rep (T)
8020 or else Has_Non_Standard_Rep (Root_Type (T));
8022 -- If Has_Non_Standard_Rep is not set on the derived type, the
8023 -- representation is fully inherited.
8025 elsif not Has_Non_Standard_Rep (T) then
8026 return False;
8028 else
8029 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
8031 -- May need a more precise check here: the First_Rep_Item may be a
8032 -- stream attribute, which does not affect the representation of the
8033 -- type ???
8035 end if;
8036 end Has_New_Non_Standard_Rep;
8038 ----------------------
8039 -- Inline_Init_Proc --
8040 ----------------------
8042 function Inline_Init_Proc (Typ : Entity_Id) return Boolean is
8043 begin
8044 -- The initialization proc of protected records is not worth inlining.
8045 -- In addition, when compiled for another unit for inlining purposes,
8046 -- it may make reference to entities that have not been elaborated yet.
8047 -- The initialization proc of records that need finalization contains
8048 -- a nested clean-up procedure that makes it impractical to inline as
8049 -- well, except for simple controlled types themselves. And similar
8050 -- considerations apply to task types.
8052 if Is_Concurrent_Type (Typ) then
8053 return False;
8055 elsif Needs_Finalization (Typ) and then not Is_Controlled (Typ) then
8056 return False;
8058 elsif Has_Task (Typ) then
8059 return False;
8061 else
8062 return True;
8063 end if;
8064 end Inline_Init_Proc;
8066 ----------------
8067 -- In_Runtime --
8068 ----------------
8070 function In_Runtime (E : Entity_Id) return Boolean is
8071 S1 : Entity_Id;
8073 begin
8074 S1 := Scope (E);
8075 while Scope (S1) /= Standard_Standard loop
8076 S1 := Scope (S1);
8077 end loop;
8079 return Is_RTU (S1, System) or else Is_RTU (S1, Ada);
8080 end In_Runtime;
8082 ----------------------------
8083 -- Initialization_Warning --
8084 ----------------------------
8086 procedure Initialization_Warning (E : Entity_Id) is
8087 Warning_Needed : Boolean;
8089 begin
8090 Warning_Needed := False;
8092 if Ekind (Current_Scope) = E_Package
8093 and then Static_Elaboration_Desired (Current_Scope)
8094 then
8095 if Is_Type (E) then
8096 if Is_Record_Type (E) then
8097 if Has_Discriminants (E)
8098 or else Is_Limited_Type (E)
8099 or else Has_Non_Standard_Rep (E)
8100 then
8101 Warning_Needed := True;
8103 else
8104 -- Verify that at least one component has an initialization
8105 -- expression. No need for a warning on a type if all its
8106 -- components have no initialization.
8108 declare
8109 Comp : Entity_Id;
8111 begin
8112 Comp := First_Component (E);
8113 while Present (Comp) loop
8114 if Ekind (Comp) = E_Discriminant
8115 or else
8116 (Nkind (Parent (Comp)) = N_Component_Declaration
8117 and then Present (Expression (Parent (Comp))))
8118 then
8119 Warning_Needed := True;
8120 exit;
8121 end if;
8123 Next_Component (Comp);
8124 end loop;
8125 end;
8126 end if;
8128 if Warning_Needed then
8129 Error_Msg_N
8130 ("Objects of the type cannot be initialized statically "
8131 & "by default??", Parent (E));
8132 end if;
8133 end if;
8135 else
8136 Error_Msg_N ("Object cannot be initialized statically??", E);
8137 end if;
8138 end if;
8139 end Initialization_Warning;
8141 ------------------
8142 -- Init_Formals --
8143 ------------------
8145 function Init_Formals (Typ : Entity_Id) return List_Id is
8146 Loc : constant Source_Ptr := Sloc (Typ);
8147 Formals : List_Id;
8149 begin
8150 -- First parameter is always _Init : in out typ. Note that we need this
8151 -- to be in/out because in the case of the task record value, there
8152 -- are default record fields (_Priority, _Size, -Task_Info) that may
8153 -- be referenced in the generated initialization routine.
8155 Formals := New_List (
8156 Make_Parameter_Specification (Loc,
8157 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uInit),
8158 In_Present => True,
8159 Out_Present => True,
8160 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
8162 -- For task record value, or type that contains tasks, add two more
8163 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
8164 -- We also add these parameters for the task record type case.
8166 if Has_Task (Typ)
8167 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
8168 then
8169 Append_To (Formals,
8170 Make_Parameter_Specification (Loc,
8171 Defining_Identifier =>
8172 Make_Defining_Identifier (Loc, Name_uMaster),
8173 Parameter_Type =>
8174 New_Occurrence_Of (RTE (RE_Master_Id), Loc)));
8176 -- Add _Chain (not done for sequential elaboration policy, see
8177 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
8179 if Partition_Elaboration_Policy /= 'S' then
8180 Append_To (Formals,
8181 Make_Parameter_Specification (Loc,
8182 Defining_Identifier =>
8183 Make_Defining_Identifier (Loc, Name_uChain),
8184 In_Present => True,
8185 Out_Present => True,
8186 Parameter_Type =>
8187 New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)));
8188 end if;
8190 Append_To (Formals,
8191 Make_Parameter_Specification (Loc,
8192 Defining_Identifier =>
8193 Make_Defining_Identifier (Loc, Name_uTask_Name),
8194 In_Present => True,
8195 Parameter_Type => New_Occurrence_Of (Standard_String, Loc)));
8196 end if;
8198 return Formals;
8200 exception
8201 when RE_Not_Available =>
8202 return Empty_List;
8203 end Init_Formals;
8205 -------------------------
8206 -- Init_Secondary_Tags --
8207 -------------------------
8209 procedure Init_Secondary_Tags
8210 (Typ : Entity_Id;
8211 Target : Node_Id;
8212 Init_Tags_List : List_Id;
8213 Stmts_List : List_Id;
8214 Fixed_Comps : Boolean := True;
8215 Variable_Comps : Boolean := True)
8217 Loc : constant Source_Ptr := Sloc (Target);
8219 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
8220 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8222 procedure Initialize_Tag
8223 (Typ : Entity_Id;
8224 Iface : Entity_Id;
8225 Tag_Comp : Entity_Id;
8226 Iface_Tag : Node_Id);
8227 -- Initialize the tag of the secondary dispatch table of Typ associated
8228 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8229 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
8230 -- of Typ CPP tagged type we generate code to inherit the contents of
8231 -- the dispatch table directly from the ancestor.
8233 --------------------
8234 -- Initialize_Tag --
8235 --------------------
8237 procedure Initialize_Tag
8238 (Typ : Entity_Id;
8239 Iface : Entity_Id;
8240 Tag_Comp : Entity_Id;
8241 Iface_Tag : Node_Id)
8243 Comp_Typ : Entity_Id;
8244 Offset_To_Top_Comp : Entity_Id := Empty;
8246 begin
8247 -- Initialize pointer to secondary DT associated with the interface
8249 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8250 Append_To (Init_Tags_List,
8251 Make_Assignment_Statement (Loc,
8252 Name =>
8253 Make_Selected_Component (Loc,
8254 Prefix => New_Copy_Tree (Target),
8255 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8256 Expression =>
8257 New_Occurrence_Of (Iface_Tag, Loc)));
8258 end if;
8260 Comp_Typ := Scope (Tag_Comp);
8262 -- Initialize the entries of the table of interfaces. We generate a
8263 -- different call when the parent of the type has variable size
8264 -- components.
8266 if Comp_Typ /= Etype (Comp_Typ)
8267 and then Is_Variable_Size_Record (Etype (Comp_Typ))
8268 and then Chars (Tag_Comp) /= Name_uTag
8269 then
8270 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
8272 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
8273 -- configurable run-time environment.
8275 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
8276 Error_Msg_CRT
8277 ("variable size record with interface types", Typ);
8278 return;
8279 end if;
8281 -- Generate:
8282 -- Set_Dynamic_Offset_To_Top
8283 -- (This => Init,
8284 -- Prim_T => Typ'Tag,
8285 -- Interface_T => Iface'Tag,
8286 -- Offset_Value => n,
8287 -- Offset_Func => Fn'Address)
8289 Append_To (Stmts_List,
8290 Make_Procedure_Call_Statement (Loc,
8291 Name =>
8292 New_Occurrence_Of (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
8293 Parameter_Associations => New_List (
8294 Make_Attribute_Reference (Loc,
8295 Prefix => New_Copy_Tree (Target),
8296 Attribute_Name => Name_Address),
8298 Unchecked_Convert_To (RTE (RE_Tag),
8299 New_Occurrence_Of
8300 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc)),
8302 Unchecked_Convert_To (RTE (RE_Tag),
8303 New_Occurrence_Of
8304 (Node (First_Elmt (Access_Disp_Table (Iface))),
8305 Loc)),
8307 Unchecked_Convert_To
8308 (RTE (RE_Storage_Offset),
8309 Make_Attribute_Reference (Loc,
8310 Prefix =>
8311 Make_Selected_Component (Loc,
8312 Prefix => New_Copy_Tree (Target),
8313 Selector_Name =>
8314 New_Occurrence_Of (Tag_Comp, Loc)),
8315 Attribute_Name => Name_Position)),
8317 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
8318 Make_Attribute_Reference (Loc,
8319 Prefix => New_Occurrence_Of
8320 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
8321 Attribute_Name => Name_Address)))));
8323 -- In this case the next component stores the value of the offset
8324 -- to the top.
8326 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
8327 pragma Assert (Present (Offset_To_Top_Comp));
8329 Append_To (Init_Tags_List,
8330 Make_Assignment_Statement (Loc,
8331 Name =>
8332 Make_Selected_Component (Loc,
8333 Prefix => New_Copy_Tree (Target),
8334 Selector_Name =>
8335 New_Occurrence_Of (Offset_To_Top_Comp, Loc)),
8337 Expression =>
8338 Make_Attribute_Reference (Loc,
8339 Prefix =>
8340 Make_Selected_Component (Loc,
8341 Prefix => New_Copy_Tree (Target),
8342 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8343 Attribute_Name => Name_Position)));
8345 -- Normal case: No discriminants in the parent type
8347 else
8348 -- Don't need to set any value if this interface shares the
8349 -- primary dispatch table.
8351 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8352 Append_To (Stmts_List,
8353 Build_Set_Static_Offset_To_Top (Loc,
8354 Iface_Tag => New_Occurrence_Of (Iface_Tag, Loc),
8355 Offset_Value =>
8356 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8357 Make_Attribute_Reference (Loc,
8358 Prefix =>
8359 Make_Selected_Component (Loc,
8360 Prefix => New_Copy_Tree (Target),
8361 Selector_Name =>
8362 New_Occurrence_Of (Tag_Comp, Loc)),
8363 Attribute_Name => Name_Position))));
8364 end if;
8366 -- Generate:
8367 -- Register_Interface_Offset
8368 -- (Prim_T => Typ'Tag,
8369 -- Interface_T => Iface'Tag,
8370 -- Is_Constant => True,
8371 -- Offset_Value => n,
8372 -- Offset_Func => null);
8374 if RTE_Available (RE_Register_Interface_Offset) then
8375 Append_To (Stmts_List,
8376 Make_Procedure_Call_Statement (Loc,
8377 Name =>
8378 New_Occurrence_Of
8379 (RTE (RE_Register_Interface_Offset), Loc),
8380 Parameter_Associations => New_List (
8381 Unchecked_Convert_To (RTE (RE_Tag),
8382 New_Occurrence_Of
8383 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc)),
8385 Unchecked_Convert_To (RTE (RE_Tag),
8386 New_Occurrence_Of
8387 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
8389 New_Occurrence_Of (Standard_True, Loc),
8391 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8392 Make_Attribute_Reference (Loc,
8393 Prefix =>
8394 Make_Selected_Component (Loc,
8395 Prefix => New_Copy_Tree (Target),
8396 Selector_Name =>
8397 New_Occurrence_Of (Tag_Comp, Loc)),
8398 Attribute_Name => Name_Position)),
8400 Make_Null (Loc))));
8401 end if;
8402 end if;
8403 end Initialize_Tag;
8405 -- Local variables
8407 Full_Typ : Entity_Id;
8408 Ifaces_List : Elist_Id;
8409 Ifaces_Comp_List : Elist_Id;
8410 Ifaces_Tag_List : Elist_Id;
8411 Iface_Elmt : Elmt_Id;
8412 Iface_Comp_Elmt : Elmt_Id;
8413 Iface_Tag_Elmt : Elmt_Id;
8414 Tag_Comp : Node_Id;
8415 In_Variable_Pos : Boolean;
8417 -- Start of processing for Init_Secondary_Tags
8419 begin
8420 -- Handle private types
8422 if Present (Full_View (Typ)) then
8423 Full_Typ := Full_View (Typ);
8424 else
8425 Full_Typ := Typ;
8426 end if;
8428 Collect_Interfaces_Info
8429 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
8431 Iface_Elmt := First_Elmt (Ifaces_List);
8432 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
8433 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
8434 while Present (Iface_Elmt) loop
8435 Tag_Comp := Node (Iface_Comp_Elmt);
8437 -- Check if parent of record type has variable size components
8439 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
8440 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
8442 -- If we are compiling under the CPP full ABI compatibility mode and
8443 -- the ancestor is a CPP_Pragma tagged type then we generate code to
8444 -- initialize the secondary tag components from tags that reference
8445 -- secondary tables filled with copy of parent slots.
8447 if Is_CPP_Class (Root_Type (Full_Typ)) then
8449 -- Reject interface components located at variable offset in
8450 -- C++ derivations. This is currently unsupported.
8452 if not Fixed_Comps and then In_Variable_Pos then
8454 -- Locate the first dynamic component of the record. Done to
8455 -- improve the text of the warning.
8457 declare
8458 Comp : Entity_Id;
8459 Comp_Typ : Entity_Id;
8461 begin
8462 Comp := First_Entity (Typ);
8463 while Present (Comp) loop
8464 Comp_Typ := Etype (Comp);
8466 if Ekind (Comp) /= E_Discriminant
8467 and then not Is_Tag (Comp)
8468 then
8469 exit when
8470 (Is_Record_Type (Comp_Typ)
8471 and then
8472 Is_Variable_Size_Record (Base_Type (Comp_Typ)))
8473 or else
8474 (Is_Array_Type (Comp_Typ)
8475 and then Is_Variable_Size_Array (Comp_Typ));
8476 end if;
8478 Next_Entity (Comp);
8479 end loop;
8481 pragma Assert (Present (Comp));
8482 Error_Msg_Node_2 := Comp;
8483 Error_Msg_NE
8484 ("parent type & with dynamic component & cannot be parent"
8485 & " of 'C'P'P derivation if new interfaces are present",
8486 Typ, Scope (Original_Record_Component (Comp)));
8488 Error_Msg_Sloc :=
8489 Sloc (Scope (Original_Record_Component (Comp)));
8490 Error_Msg_NE
8491 ("type derived from 'C'P'P type & defined #",
8492 Typ, Scope (Original_Record_Component (Comp)));
8494 -- Avoid duplicated warnings
8496 exit;
8497 end;
8499 -- Initialize secondary tags
8501 else
8502 Append_To (Init_Tags_List,
8503 Make_Assignment_Statement (Loc,
8504 Name =>
8505 Make_Selected_Component (Loc,
8506 Prefix => New_Copy_Tree (Target),
8507 Selector_Name =>
8508 New_Occurrence_Of (Node (Iface_Comp_Elmt), Loc)),
8509 Expression =>
8510 New_Occurrence_Of (Node (Iface_Tag_Elmt), Loc)));
8511 end if;
8513 -- Otherwise generate code to initialize the tag
8515 else
8516 if (In_Variable_Pos and then Variable_Comps)
8517 or else (not In_Variable_Pos and then Fixed_Comps)
8518 then
8519 Initialize_Tag (Full_Typ,
8520 Iface => Node (Iface_Elmt),
8521 Tag_Comp => Tag_Comp,
8522 Iface_Tag => Node (Iface_Tag_Elmt));
8523 end if;
8524 end if;
8526 Next_Elmt (Iface_Elmt);
8527 Next_Elmt (Iface_Comp_Elmt);
8528 Next_Elmt (Iface_Tag_Elmt);
8529 end loop;
8530 end Init_Secondary_Tags;
8532 ------------------------
8533 -- Is_User_Defined_Eq --
8534 ------------------------
8536 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean is
8537 begin
8538 return Chars (Prim) = Name_Op_Eq
8539 and then Etype (First_Formal (Prim)) =
8540 Etype (Next_Formal (First_Formal (Prim)))
8541 and then Base_Type (Etype (Prim)) = Standard_Boolean;
8542 end Is_User_Defined_Equality;
8544 ----------------------------------------
8545 -- Make_Controlling_Function_Wrappers --
8546 ----------------------------------------
8548 procedure Make_Controlling_Function_Wrappers
8549 (Tag_Typ : Entity_Id;
8550 Decl_List : out List_Id;
8551 Body_List : out List_Id)
8553 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8554 Prim_Elmt : Elmt_Id;
8555 Subp : Entity_Id;
8556 Actual_List : List_Id;
8557 Formal_List : List_Id;
8558 Formal : Entity_Id;
8559 Par_Formal : Entity_Id;
8560 Formal_Node : Node_Id;
8561 Func_Body : Node_Id;
8562 Func_Decl : Node_Id;
8563 Func_Spec : Node_Id;
8564 Return_Stmt : Node_Id;
8566 begin
8567 Decl_List := New_List;
8568 Body_List := New_List;
8570 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
8571 while Present (Prim_Elmt) loop
8572 Subp := Node (Prim_Elmt);
8574 -- If a primitive function with a controlling result of the type has
8575 -- not been overridden by the user, then we must create a wrapper
8576 -- function here that effectively overrides it and invokes the
8577 -- (non-abstract) parent function. This can only occur for a null
8578 -- extension. Note that functions with anonymous controlling access
8579 -- results don't qualify and must be overridden. We also exclude
8580 -- Input attributes, since each type will have its own version of
8581 -- Input constructed by the expander. The test for Comes_From_Source
8582 -- is needed to distinguish inherited operations from renamings
8583 -- (which also have Alias set). We exclude internal entities with
8584 -- Interface_Alias to avoid generating duplicated wrappers since
8585 -- the primitive which covers the interface is also available in
8586 -- the list of primitive operations.
8588 -- The function may be abstract, or require_Overriding may be set
8589 -- for it, because tests for null extensions may already have reset
8590 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
8591 -- set, functions that need wrappers are recognized by having an
8592 -- alias that returns the parent type.
8594 if Comes_From_Source (Subp)
8595 or else No (Alias (Subp))
8596 or else Present (Interface_Alias (Subp))
8597 or else Ekind (Subp) /= E_Function
8598 or else not Has_Controlling_Result (Subp)
8599 or else Is_Access_Type (Etype (Subp))
8600 or else Is_Abstract_Subprogram (Alias (Subp))
8601 or else Is_TSS (Subp, TSS_Stream_Input)
8602 then
8603 goto Next_Prim;
8605 elsif Is_Abstract_Subprogram (Subp)
8606 or else Requires_Overriding (Subp)
8607 or else
8608 (Is_Null_Extension (Etype (Subp))
8609 and then Etype (Alias (Subp)) /= Etype (Subp))
8610 then
8611 Formal_List := No_List;
8612 Formal := First_Formal (Subp);
8614 if Present (Formal) then
8615 Formal_List := New_List;
8617 while Present (Formal) loop
8618 Append
8619 (Make_Parameter_Specification
8620 (Loc,
8621 Defining_Identifier =>
8622 Make_Defining_Identifier (Sloc (Formal),
8623 Chars => Chars (Formal)),
8624 In_Present => In_Present (Parent (Formal)),
8625 Out_Present => Out_Present (Parent (Formal)),
8626 Null_Exclusion_Present =>
8627 Null_Exclusion_Present (Parent (Formal)),
8628 Parameter_Type =>
8629 New_Occurrence_Of (Etype (Formal), Loc),
8630 Expression =>
8631 New_Copy_Tree (Expression (Parent (Formal)))),
8632 Formal_List);
8634 Next_Formal (Formal);
8635 end loop;
8636 end if;
8638 Func_Spec :=
8639 Make_Function_Specification (Loc,
8640 Defining_Unit_Name =>
8641 Make_Defining_Identifier (Loc,
8642 Chars => Chars (Subp)),
8643 Parameter_Specifications => Formal_List,
8644 Result_Definition =>
8645 New_Occurrence_Of (Etype (Subp), Loc));
8647 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
8648 Append_To (Decl_List, Func_Decl);
8650 -- Build a wrapper body that calls the parent function. The body
8651 -- contains a single return statement that returns an extension
8652 -- aggregate whose ancestor part is a call to the parent function,
8653 -- passing the formals as actuals (with any controlling arguments
8654 -- converted to the types of the corresponding formals of the
8655 -- parent function, which might be anonymous access types), and
8656 -- having a null extension.
8658 Formal := First_Formal (Subp);
8659 Par_Formal := First_Formal (Alias (Subp));
8660 Formal_Node := First (Formal_List);
8662 if Present (Formal) then
8663 Actual_List := New_List;
8664 else
8665 Actual_List := No_List;
8666 end if;
8668 while Present (Formal) loop
8669 if Is_Controlling_Formal (Formal) then
8670 Append_To (Actual_List,
8671 Make_Type_Conversion (Loc,
8672 Subtype_Mark =>
8673 New_Occurrence_Of (Etype (Par_Formal), Loc),
8674 Expression =>
8675 New_Occurrence_Of
8676 (Defining_Identifier (Formal_Node), Loc)));
8677 else
8678 Append_To
8679 (Actual_List,
8680 New_Occurrence_Of
8681 (Defining_Identifier (Formal_Node), Loc));
8682 end if;
8684 Next_Formal (Formal);
8685 Next_Formal (Par_Formal);
8686 Next (Formal_Node);
8687 end loop;
8689 Return_Stmt :=
8690 Make_Simple_Return_Statement (Loc,
8691 Expression =>
8692 Make_Extension_Aggregate (Loc,
8693 Ancestor_Part =>
8694 Make_Function_Call (Loc,
8695 Name =>
8696 New_Occurrence_Of (Alias (Subp), Loc),
8697 Parameter_Associations => Actual_List),
8698 Null_Record_Present => True));
8700 Func_Body :=
8701 Make_Subprogram_Body (Loc,
8702 Specification => New_Copy_Tree (Func_Spec),
8703 Declarations => Empty_List,
8704 Handled_Statement_Sequence =>
8705 Make_Handled_Sequence_Of_Statements (Loc,
8706 Statements => New_List (Return_Stmt)));
8708 Set_Defining_Unit_Name
8709 (Specification (Func_Body),
8710 Make_Defining_Identifier (Loc, Chars (Subp)));
8712 Append_To (Body_List, Func_Body);
8714 -- Replace the inherited function with the wrapper function in the
8715 -- primitive operations list. We add the minimum decoration needed
8716 -- to override interface primitives.
8718 Set_Ekind (Defining_Unit_Name (Func_Spec), E_Function);
8720 Override_Dispatching_Operation
8721 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec),
8722 Is_Wrapper => True);
8723 end if;
8725 <<Next_Prim>>
8726 Next_Elmt (Prim_Elmt);
8727 end loop;
8728 end Make_Controlling_Function_Wrappers;
8730 -------------------
8731 -- Make_Eq_Body --
8732 -------------------
8734 function Make_Eq_Body
8735 (Typ : Entity_Id;
8736 Eq_Name : Name_Id) return Node_Id
8738 Loc : constant Source_Ptr := Sloc (Parent (Typ));
8739 Decl : Node_Id;
8740 Def : constant Node_Id := Parent (Typ);
8741 Stmts : constant List_Id := New_List;
8742 Variant_Case : Boolean := Has_Discriminants (Typ);
8743 Comps : Node_Id := Empty;
8744 Typ_Def : Node_Id := Type_Definition (Def);
8746 begin
8747 Decl :=
8748 Predef_Spec_Or_Body (Loc,
8749 Tag_Typ => Typ,
8750 Name => Eq_Name,
8751 Profile => New_List (
8752 Make_Parameter_Specification (Loc,
8753 Defining_Identifier =>
8754 Make_Defining_Identifier (Loc, Name_X),
8755 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
8757 Make_Parameter_Specification (Loc,
8758 Defining_Identifier =>
8759 Make_Defining_Identifier (Loc, Name_Y),
8760 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
8762 Ret_Type => Standard_Boolean,
8763 For_Body => True);
8765 if Variant_Case then
8766 if Nkind (Typ_Def) = N_Derived_Type_Definition then
8767 Typ_Def := Record_Extension_Part (Typ_Def);
8768 end if;
8770 if Present (Typ_Def) then
8771 Comps := Component_List (Typ_Def);
8772 end if;
8774 Variant_Case :=
8775 Present (Comps) and then Present (Variant_Part (Comps));
8776 end if;
8778 if Variant_Case then
8779 Append_To (Stmts,
8780 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
8781 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
8782 Append_To (Stmts,
8783 Make_Simple_Return_Statement (Loc,
8784 Expression => New_Occurrence_Of (Standard_True, Loc)));
8786 else
8787 Append_To (Stmts,
8788 Make_Simple_Return_Statement (Loc,
8789 Expression =>
8790 Expand_Record_Equality
8791 (Typ,
8792 Typ => Typ,
8793 Lhs => Make_Identifier (Loc, Name_X),
8794 Rhs => Make_Identifier (Loc, Name_Y),
8795 Bodies => Declarations (Decl))));
8796 end if;
8798 Set_Handled_Statement_Sequence
8799 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8800 return Decl;
8801 end Make_Eq_Body;
8803 ------------------
8804 -- Make_Eq_Case --
8805 ------------------
8807 -- <Make_Eq_If shared components>
8809 -- case X.D1 is
8810 -- when V1 => <Make_Eq_Case> on subcomponents
8811 -- ...
8812 -- when Vn => <Make_Eq_Case> on subcomponents
8813 -- end case;
8815 function Make_Eq_Case
8816 (E : Entity_Id;
8817 CL : Node_Id;
8818 Discrs : Elist_Id := New_Elmt_List) return List_Id
8820 Loc : constant Source_Ptr := Sloc (E);
8821 Result : constant List_Id := New_List;
8822 Variant : Node_Id;
8823 Alt_List : List_Id;
8825 function Corresponding_Formal (C : Node_Id) return Entity_Id;
8826 -- Given the discriminant that controls a given variant of an unchecked
8827 -- union, find the formal of the equality function that carries the
8828 -- inferred value of the discriminant.
8830 function External_Name (E : Entity_Id) return Name_Id;
8831 -- The value of a given discriminant is conveyed in the corresponding
8832 -- formal parameter of the equality routine. The name of this formal
8833 -- parameter carries a one-character suffix which is removed here.
8835 --------------------------
8836 -- Corresponding_Formal --
8837 --------------------------
8839 function Corresponding_Formal (C : Node_Id) return Entity_Id is
8840 Discr : constant Entity_Id := Entity (Name (Variant_Part (C)));
8841 Elm : Elmt_Id;
8843 begin
8844 Elm := First_Elmt (Discrs);
8845 while Present (Elm) loop
8846 if Chars (Discr) = External_Name (Node (Elm)) then
8847 return Node (Elm);
8848 end if;
8850 Next_Elmt (Elm);
8851 end loop;
8853 -- A formal of the proper name must be found
8855 raise Program_Error;
8856 end Corresponding_Formal;
8858 -------------------
8859 -- External_Name --
8860 -------------------
8862 function External_Name (E : Entity_Id) return Name_Id is
8863 begin
8864 Get_Name_String (Chars (E));
8865 Name_Len := Name_Len - 1;
8866 return Name_Find;
8867 end External_Name;
8869 -- Start of processing for Make_Eq_Case
8871 begin
8872 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
8874 if No (Variant_Part (CL)) then
8875 return Result;
8876 end if;
8878 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
8880 if No (Variant) then
8881 return Result;
8882 end if;
8884 Alt_List := New_List;
8885 while Present (Variant) loop
8886 Append_To (Alt_List,
8887 Make_Case_Statement_Alternative (Loc,
8888 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
8889 Statements =>
8890 Make_Eq_Case (E, Component_List (Variant), Discrs)));
8891 Next_Non_Pragma (Variant);
8892 end loop;
8894 -- If we have an Unchecked_Union, use one of the parameters of the
8895 -- enclosing equality routine that captures the discriminant, to use
8896 -- as the expression in the generated case statement.
8898 if Is_Unchecked_Union (E) then
8899 Append_To (Result,
8900 Make_Case_Statement (Loc,
8901 Expression =>
8902 New_Occurrence_Of (Corresponding_Formal (CL), Loc),
8903 Alternatives => Alt_List));
8905 else
8906 Append_To (Result,
8907 Make_Case_Statement (Loc,
8908 Expression =>
8909 Make_Selected_Component (Loc,
8910 Prefix => Make_Identifier (Loc, Name_X),
8911 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
8912 Alternatives => Alt_List));
8913 end if;
8915 return Result;
8916 end Make_Eq_Case;
8918 ----------------
8919 -- Make_Eq_If --
8920 ----------------
8922 -- Generates:
8924 -- if
8925 -- X.C1 /= Y.C1
8926 -- or else
8927 -- X.C2 /= Y.C2
8928 -- ...
8929 -- then
8930 -- return False;
8931 -- end if;
8933 -- or a null statement if the list L is empty
8935 function Make_Eq_If
8936 (E : Entity_Id;
8937 L : List_Id) return Node_Id
8939 Loc : constant Source_Ptr := Sloc (E);
8940 C : Node_Id;
8941 Field_Name : Name_Id;
8942 Cond : Node_Id;
8944 begin
8945 if No (L) then
8946 return Make_Null_Statement (Loc);
8948 else
8949 Cond := Empty;
8951 C := First_Non_Pragma (L);
8952 while Present (C) loop
8953 Field_Name := Chars (Defining_Identifier (C));
8955 -- The tags must not be compared: they are not part of the value.
8956 -- Ditto for parent interfaces because their equality operator is
8957 -- abstract.
8959 -- Note also that in the following, we use Make_Identifier for
8960 -- the component names. Use of New_Occurrence_Of to identify the
8961 -- components would be incorrect because the wrong entities for
8962 -- discriminants could be picked up in the private type case.
8964 if Field_Name = Name_uParent
8965 and then Is_Interface (Etype (Defining_Identifier (C)))
8966 then
8967 null;
8969 elsif Field_Name /= Name_uTag then
8970 Evolve_Or_Else (Cond,
8971 Make_Op_Ne (Loc,
8972 Left_Opnd =>
8973 Make_Selected_Component (Loc,
8974 Prefix => Make_Identifier (Loc, Name_X),
8975 Selector_Name => Make_Identifier (Loc, Field_Name)),
8977 Right_Opnd =>
8978 Make_Selected_Component (Loc,
8979 Prefix => Make_Identifier (Loc, Name_Y),
8980 Selector_Name => Make_Identifier (Loc, Field_Name))));
8981 end if;
8983 Next_Non_Pragma (C);
8984 end loop;
8986 if No (Cond) then
8987 return Make_Null_Statement (Loc);
8989 else
8990 return
8991 Make_Implicit_If_Statement (E,
8992 Condition => Cond,
8993 Then_Statements => New_List (
8994 Make_Simple_Return_Statement (Loc,
8995 Expression => New_Occurrence_Of (Standard_False, Loc))));
8996 end if;
8997 end if;
8998 end Make_Eq_If;
9000 -------------------
9001 -- Make_Neq_Body --
9002 -------------------
9004 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id is
9006 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean;
9007 -- Returns true if Prim is a renaming of an unresolved predefined
9008 -- inequality operation.
9010 --------------------------------
9011 -- Is_Predefined_Neq_Renaming --
9012 --------------------------------
9014 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean is
9015 begin
9016 return Chars (Prim) /= Name_Op_Ne
9017 and then Present (Alias (Prim))
9018 and then Comes_From_Source (Prim)
9019 and then Is_Intrinsic_Subprogram (Alias (Prim))
9020 and then Chars (Alias (Prim)) = Name_Op_Ne;
9021 end Is_Predefined_Neq_Renaming;
9023 -- Local variables
9025 Loc : constant Source_Ptr := Sloc (Parent (Tag_Typ));
9026 Stmts : constant List_Id := New_List;
9027 Decl : Node_Id;
9028 Eq_Prim : Entity_Id;
9029 Left_Op : Entity_Id;
9030 Renaming_Prim : Entity_Id;
9031 Right_Op : Entity_Id;
9032 Target : Entity_Id;
9034 -- Start of processing for Make_Neq_Body
9036 begin
9037 -- For a call on a renaming of a dispatching subprogram that is
9038 -- overridden, if the overriding occurred before the renaming, then
9039 -- the body executed is that of the overriding declaration, even if the
9040 -- overriding declaration is not visible at the place of the renaming;
9041 -- otherwise, the inherited or predefined subprogram is called, see
9042 -- (RM 8.5.4(8))
9044 -- Stage 1: Search for a renaming of the inequality primitive and also
9045 -- search for an overriding of the equality primitive located before the
9046 -- renaming declaration.
9048 declare
9049 Elmt : Elmt_Id;
9050 Prim : Node_Id;
9052 begin
9053 Eq_Prim := Empty;
9054 Renaming_Prim := Empty;
9056 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9057 while Present (Elmt) loop
9058 Prim := Node (Elmt);
9060 if Is_User_Defined_Equality (Prim) and then No (Alias (Prim)) then
9061 if No (Renaming_Prim) then
9062 pragma Assert (No (Eq_Prim));
9063 Eq_Prim := Prim;
9064 end if;
9066 elsif Is_Predefined_Neq_Renaming (Prim) then
9067 Renaming_Prim := Prim;
9068 end if;
9070 Next_Elmt (Elmt);
9071 end loop;
9072 end;
9074 -- No further action needed if no renaming was found
9076 if No (Renaming_Prim) then
9077 return Empty;
9078 end if;
9080 -- Stage 2: Replace the renaming declaration by a subprogram declaration
9081 -- (required to add its body)
9083 Decl := Parent (Parent (Renaming_Prim));
9084 Rewrite (Decl,
9085 Make_Subprogram_Declaration (Loc,
9086 Specification => Specification (Decl)));
9087 Set_Analyzed (Decl);
9089 -- Remove the decoration of intrinsic renaming subprogram
9091 Set_Is_Intrinsic_Subprogram (Renaming_Prim, False);
9092 Set_Convention (Renaming_Prim, Convention_Ada);
9093 Set_Alias (Renaming_Prim, Empty);
9094 Set_Has_Completion (Renaming_Prim, False);
9096 -- Stage 3: Build the corresponding body
9098 Left_Op := First_Formal (Renaming_Prim);
9099 Right_Op := Next_Formal (Left_Op);
9101 Decl :=
9102 Predef_Spec_Or_Body (Loc,
9103 Tag_Typ => Tag_Typ,
9104 Name => Chars (Renaming_Prim),
9105 Profile => New_List (
9106 Make_Parameter_Specification (Loc,
9107 Defining_Identifier =>
9108 Make_Defining_Identifier (Loc, Chars (Left_Op)),
9109 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9111 Make_Parameter_Specification (Loc,
9112 Defining_Identifier =>
9113 Make_Defining_Identifier (Loc, Chars (Right_Op)),
9114 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9116 Ret_Type => Standard_Boolean,
9117 For_Body => True);
9119 -- If the overriding of the equality primitive occurred before the
9120 -- renaming, then generate:
9122 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9123 -- begin
9124 -- return not Oeq (X, Y);
9125 -- end;
9127 if Present (Eq_Prim) then
9128 Target := Eq_Prim;
9130 -- Otherwise build a nested subprogram which performs the predefined
9131 -- evaluation of the equality operator. That is, generate:
9133 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9134 -- function Oeq (X : Y) return Boolean is
9135 -- begin
9136 -- <<body of default implementation>>
9137 -- end;
9138 -- begin
9139 -- return not Oeq (X, Y);
9140 -- end;
9142 else
9143 declare
9144 Local_Subp : Node_Id;
9145 begin
9146 Local_Subp := Make_Eq_Body (Tag_Typ, Name_Op_Eq);
9147 Set_Declarations (Decl, New_List (Local_Subp));
9148 Target := Defining_Entity (Local_Subp);
9149 end;
9150 end if;
9152 Append_To (Stmts,
9153 Make_Simple_Return_Statement (Loc,
9154 Expression =>
9155 Make_Op_Not (Loc,
9156 Make_Function_Call (Loc,
9157 Name => New_Occurrence_Of (Target, Loc),
9158 Parameter_Associations => New_List (
9159 Make_Identifier (Loc, Chars (Left_Op)),
9160 Make_Identifier (Loc, Chars (Right_Op)))))));
9162 Set_Handled_Statement_Sequence
9163 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
9164 return Decl;
9165 end Make_Neq_Body;
9167 -------------------------------
9168 -- Make_Null_Procedure_Specs --
9169 -------------------------------
9171 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
9172 Decl_List : constant List_Id := New_List;
9173 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9174 Formal : Entity_Id;
9175 Formal_List : List_Id;
9176 New_Param_Spec : Node_Id;
9177 Parent_Subp : Entity_Id;
9178 Prim_Elmt : Elmt_Id;
9179 Subp : Entity_Id;
9181 begin
9182 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9183 while Present (Prim_Elmt) loop
9184 Subp := Node (Prim_Elmt);
9186 -- If a null procedure inherited from an interface has not been
9187 -- overridden, then we build a null procedure declaration to
9188 -- override the inherited procedure.
9190 Parent_Subp := Alias (Subp);
9192 if Present (Parent_Subp)
9193 and then Is_Null_Interface_Primitive (Parent_Subp)
9194 then
9195 Formal_List := No_List;
9196 Formal := First_Formal (Subp);
9198 if Present (Formal) then
9199 Formal_List := New_List;
9201 while Present (Formal) loop
9203 -- Copy the parameter spec including default expressions
9205 New_Param_Spec :=
9206 New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
9208 -- Generate a new defining identifier for the new formal.
9209 -- required because New_Copy_Tree does not duplicate
9210 -- semantic fields (except itypes).
9212 Set_Defining_Identifier (New_Param_Spec,
9213 Make_Defining_Identifier (Sloc (Formal),
9214 Chars => Chars (Formal)));
9216 -- For controlling arguments we must change their
9217 -- parameter type to reference the tagged type (instead
9218 -- of the interface type)
9220 if Is_Controlling_Formal (Formal) then
9221 if Nkind (Parameter_Type (Parent (Formal))) = N_Identifier
9222 then
9223 Set_Parameter_Type (New_Param_Spec,
9224 New_Occurrence_Of (Tag_Typ, Loc));
9226 else pragma Assert
9227 (Nkind (Parameter_Type (Parent (Formal))) =
9228 N_Access_Definition);
9229 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
9230 New_Occurrence_Of (Tag_Typ, Loc));
9231 end if;
9232 end if;
9234 Append (New_Param_Spec, Formal_List);
9236 Next_Formal (Formal);
9237 end loop;
9238 end if;
9240 Append_To (Decl_List,
9241 Make_Subprogram_Declaration (Loc,
9242 Make_Procedure_Specification (Loc,
9243 Defining_Unit_Name =>
9244 Make_Defining_Identifier (Loc, Chars (Subp)),
9245 Parameter_Specifications => Formal_List,
9246 Null_Present => True)));
9247 end if;
9249 Next_Elmt (Prim_Elmt);
9250 end loop;
9252 return Decl_List;
9253 end Make_Null_Procedure_Specs;
9255 -------------------------------------
9256 -- Make_Predefined_Primitive_Specs --
9257 -------------------------------------
9259 procedure Make_Predefined_Primitive_Specs
9260 (Tag_Typ : Entity_Id;
9261 Predef_List : out List_Id;
9262 Renamed_Eq : out Entity_Id)
9264 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
9265 -- Returns true if Prim is a renaming of an unresolved predefined
9266 -- equality operation.
9268 -------------------------------
9269 -- Is_Predefined_Eq_Renaming --
9270 -------------------------------
9272 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
9273 begin
9274 return Chars (Prim) /= Name_Op_Eq
9275 and then Present (Alias (Prim))
9276 and then Comes_From_Source (Prim)
9277 and then Is_Intrinsic_Subprogram (Alias (Prim))
9278 and then Chars (Alias (Prim)) = Name_Op_Eq;
9279 end Is_Predefined_Eq_Renaming;
9281 -- Local variables
9283 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9284 Res : constant List_Id := New_List;
9285 Eq_Name : Name_Id := Name_Op_Eq;
9286 Eq_Needed : Boolean;
9287 Eq_Spec : Node_Id;
9288 Prim : Elmt_Id;
9290 Has_Predef_Eq_Renaming : Boolean := False;
9291 -- Set to True if Tag_Typ has a primitive that renames the predefined
9292 -- equality operator. Used to implement (RM 8-5-4(8)).
9294 -- Start of processing for Make_Predefined_Primitive_Specs
9296 begin
9297 Renamed_Eq := Empty;
9299 -- Spec of _Size
9301 Append_To (Res, Predef_Spec_Or_Body (Loc,
9302 Tag_Typ => Tag_Typ,
9303 Name => Name_uSize,
9304 Profile => New_List (
9305 Make_Parameter_Specification (Loc,
9306 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9307 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9309 Ret_Type => Standard_Long_Long_Integer));
9311 -- Specs for dispatching stream attributes
9313 declare
9314 Stream_Op_TSS_Names :
9315 constant array (Positive range <>) of TSS_Name_Type :=
9316 (TSS_Stream_Read,
9317 TSS_Stream_Write,
9318 TSS_Stream_Input,
9319 TSS_Stream_Output);
9321 begin
9322 for Op in Stream_Op_TSS_Names'Range loop
9323 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
9324 Append_To (Res,
9325 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
9326 Stream_Op_TSS_Names (Op)));
9327 end if;
9328 end loop;
9329 end;
9331 -- Spec of "=" is expanded if the type is not limited and if a user
9332 -- defined "=" was not already declared for the non-full view of a
9333 -- private extension
9335 if not Is_Limited_Type (Tag_Typ) then
9336 Eq_Needed := True;
9337 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9338 while Present (Prim) loop
9340 -- If a primitive is encountered that renames the predefined
9341 -- equality operator before reaching any explicit equality
9342 -- primitive, then we still need to create a predefined equality
9343 -- function, because calls to it can occur via the renaming. A
9344 -- new name is created for the equality to avoid conflicting with
9345 -- any user-defined equality. (Note that this doesn't account for
9346 -- renamings of equality nested within subpackages???)
9348 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9349 Has_Predef_Eq_Renaming := True;
9350 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
9352 -- User-defined equality
9354 elsif Is_User_Defined_Equality (Node (Prim)) then
9355 if No (Alias (Node (Prim)))
9356 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
9357 N_Subprogram_Renaming_Declaration
9358 then
9359 Eq_Needed := False;
9360 exit;
9362 -- If the parent is not an interface type and has an abstract
9363 -- equality function explicitly defined in the sources, then
9364 -- the inherited equality is abstract as well, and no body can
9365 -- be created for it.
9367 elsif not Is_Interface (Etype (Tag_Typ))
9368 and then Present (Alias (Node (Prim)))
9369 and then Comes_From_Source (Alias (Node (Prim)))
9370 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
9371 then
9372 Eq_Needed := False;
9373 exit;
9375 -- If the type has an equality function corresponding with
9376 -- a primitive defined in an interface type, the inherited
9377 -- equality is abstract as well, and no body can be created
9378 -- for it.
9380 elsif Present (Alias (Node (Prim)))
9381 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
9382 and then
9383 Is_Interface
9384 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
9385 then
9386 Eq_Needed := False;
9387 exit;
9388 end if;
9389 end if;
9391 Next_Elmt (Prim);
9392 end loop;
9394 -- If a renaming of predefined equality was found but there was no
9395 -- user-defined equality (so Eq_Needed is still true), then set the
9396 -- name back to Name_Op_Eq. But in the case where a user-defined
9397 -- equality was located after such a renaming, then the predefined
9398 -- equality function is still needed, so Eq_Needed must be set back
9399 -- to True.
9401 if Eq_Name /= Name_Op_Eq then
9402 if Eq_Needed then
9403 Eq_Name := Name_Op_Eq;
9404 else
9405 Eq_Needed := True;
9406 end if;
9407 end if;
9409 if Eq_Needed then
9410 Eq_Spec := Predef_Spec_Or_Body (Loc,
9411 Tag_Typ => Tag_Typ,
9412 Name => Eq_Name,
9413 Profile => New_List (
9414 Make_Parameter_Specification (Loc,
9415 Defining_Identifier =>
9416 Make_Defining_Identifier (Loc, Name_X),
9417 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9419 Make_Parameter_Specification (Loc,
9420 Defining_Identifier =>
9421 Make_Defining_Identifier (Loc, Name_Y),
9422 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9423 Ret_Type => Standard_Boolean);
9424 Append_To (Res, Eq_Spec);
9426 if Has_Predef_Eq_Renaming then
9427 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
9429 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9430 while Present (Prim) loop
9432 -- Any renamings of equality that appeared before an
9433 -- overriding equality must be updated to refer to the
9434 -- entity for the predefined equality, otherwise calls via
9435 -- the renaming would get incorrectly resolved to call the
9436 -- user-defined equality function.
9438 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9439 Set_Alias (Node (Prim), Renamed_Eq);
9441 -- Exit upon encountering a user-defined equality
9443 elsif Chars (Node (Prim)) = Name_Op_Eq
9444 and then No (Alias (Node (Prim)))
9445 then
9446 exit;
9447 end if;
9449 Next_Elmt (Prim);
9450 end loop;
9451 end if;
9452 end if;
9454 -- Spec for dispatching assignment
9456 Append_To (Res, Predef_Spec_Or_Body (Loc,
9457 Tag_Typ => Tag_Typ,
9458 Name => Name_uAssign,
9459 Profile => New_List (
9460 Make_Parameter_Specification (Loc,
9461 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9462 Out_Present => True,
9463 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9465 Make_Parameter_Specification (Loc,
9466 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
9467 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)))));
9468 end if;
9470 -- Ada 2005: Generate declarations for the following primitive
9471 -- operations for limited interfaces and synchronized types that
9472 -- implement a limited interface.
9474 -- Disp_Asynchronous_Select
9475 -- Disp_Conditional_Select
9476 -- Disp_Get_Prim_Op_Kind
9477 -- Disp_Get_Task_Id
9478 -- Disp_Requeue
9479 -- Disp_Timed_Select
9481 -- Disable the generation of these bodies if No_Dispatching_Calls,
9482 -- Ravenscar or ZFP is active.
9484 if Ada_Version >= Ada_2005
9485 and then not Restriction_Active (No_Dispatching_Calls)
9486 and then not Restriction_Active (No_Select_Statements)
9487 and then RTE_Available (RE_Select_Specific_Data)
9488 then
9489 -- These primitives are defined abstract in interface types
9491 if Is_Interface (Tag_Typ)
9492 and then Is_Limited_Record (Tag_Typ)
9493 then
9494 Append_To (Res,
9495 Make_Abstract_Subprogram_Declaration (Loc,
9496 Specification =>
9497 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9499 Append_To (Res,
9500 Make_Abstract_Subprogram_Declaration (Loc,
9501 Specification =>
9502 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9504 Append_To (Res,
9505 Make_Abstract_Subprogram_Declaration (Loc,
9506 Specification =>
9507 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9509 Append_To (Res,
9510 Make_Abstract_Subprogram_Declaration (Loc,
9511 Specification =>
9512 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9514 Append_To (Res,
9515 Make_Abstract_Subprogram_Declaration (Loc,
9516 Specification =>
9517 Make_Disp_Requeue_Spec (Tag_Typ)));
9519 Append_To (Res,
9520 Make_Abstract_Subprogram_Declaration (Loc,
9521 Specification =>
9522 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9524 -- If ancestor is an interface type, declare non-abstract primitives
9525 -- to override the abstract primitives of the interface type.
9527 -- In VM targets we define these primitives in all root tagged types
9528 -- that are not interface types. Done because in VM targets we don't
9529 -- have secondary dispatch tables and any derivation of Tag_Typ may
9530 -- cover limited interfaces (which always have these primitives since
9531 -- they may be ancestors of synchronized interface types).
9533 elsif (not Is_Interface (Tag_Typ)
9534 and then Is_Interface (Etype (Tag_Typ))
9535 and then Is_Limited_Record (Etype (Tag_Typ)))
9536 or else
9537 (Is_Concurrent_Record_Type (Tag_Typ)
9538 and then Has_Interfaces (Tag_Typ))
9539 or else
9540 (not Tagged_Type_Expansion
9541 and then not Is_Interface (Tag_Typ)
9542 and then Tag_Typ = Root_Type (Tag_Typ))
9543 then
9544 Append_To (Res,
9545 Make_Subprogram_Declaration (Loc,
9546 Specification =>
9547 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9549 Append_To (Res,
9550 Make_Subprogram_Declaration (Loc,
9551 Specification =>
9552 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9554 Append_To (Res,
9555 Make_Subprogram_Declaration (Loc,
9556 Specification =>
9557 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9559 Append_To (Res,
9560 Make_Subprogram_Declaration (Loc,
9561 Specification =>
9562 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9564 Append_To (Res,
9565 Make_Subprogram_Declaration (Loc,
9566 Specification =>
9567 Make_Disp_Requeue_Spec (Tag_Typ)));
9569 Append_To (Res,
9570 Make_Subprogram_Declaration (Loc,
9571 Specification =>
9572 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9573 end if;
9574 end if;
9576 -- All tagged types receive their own Deep_Adjust and Deep_Finalize
9577 -- regardless of whether they are controlled or may contain controlled
9578 -- components.
9580 -- Do not generate the routines if finalization is disabled
9582 if Restriction_Active (No_Finalization) then
9583 null;
9585 else
9586 if not Is_Limited_Type (Tag_Typ) then
9587 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
9588 end if;
9590 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
9591 end if;
9593 Predef_List := Res;
9594 end Make_Predefined_Primitive_Specs;
9596 -------------------------
9597 -- Make_Tag_Assignment --
9598 -------------------------
9600 function Make_Tag_Assignment (N : Node_Id) return Node_Id is
9601 Loc : constant Source_Ptr := Sloc (N);
9602 Def_If : constant Entity_Id := Defining_Identifier (N);
9603 Expr : constant Node_Id := Expression (N);
9604 Typ : constant Entity_Id := Etype (Def_If);
9605 Full_Typ : constant Entity_Id := Underlying_Type (Typ);
9606 New_Ref : Node_Id;
9608 begin
9609 -- This expansion activity is called during analysis, but cannot
9610 -- be applied in ASIS mode when other expansion is disabled.
9612 if Is_Tagged_Type (Typ)
9613 and then not Is_Class_Wide_Type (Typ)
9614 and then not Is_CPP_Class (Typ)
9615 and then Tagged_Type_Expansion
9616 and then Nkind (Expr) /= N_Aggregate
9617 and then not ASIS_Mode
9618 and then (Nkind (Expr) /= N_Qualified_Expression
9619 or else Nkind (Expression (Expr)) /= N_Aggregate)
9620 then
9621 New_Ref :=
9622 Make_Selected_Component (Loc,
9623 Prefix => New_Occurrence_Of (Def_If, Loc),
9624 Selector_Name =>
9625 New_Occurrence_Of (First_Tag_Component (Full_Typ), Loc));
9626 Set_Assignment_OK (New_Ref);
9628 return
9629 Make_Assignment_Statement (Loc,
9630 Name => New_Ref,
9631 Expression =>
9632 Unchecked_Convert_To (RTE (RE_Tag),
9633 New_Occurrence_Of (Node
9634 (First_Elmt (Access_Disp_Table (Full_Typ))), Loc)));
9635 else
9636 return Empty;
9637 end if;
9638 end Make_Tag_Assignment;
9640 ---------------------------------
9641 -- Needs_Simple_Initialization --
9642 ---------------------------------
9644 function Needs_Simple_Initialization
9645 (T : Entity_Id;
9646 Consider_IS : Boolean := True) return Boolean
9648 Consider_IS_NS : constant Boolean :=
9649 Normalize_Scalars or (Initialize_Scalars and Consider_IS);
9651 begin
9652 -- Never need initialization if it is suppressed
9654 if Initialization_Suppressed (T) then
9655 return False;
9656 end if;
9658 -- Check for private type, in which case test applies to the underlying
9659 -- type of the private type.
9661 if Is_Private_Type (T) then
9662 declare
9663 RT : constant Entity_Id := Underlying_Type (T);
9664 begin
9665 if Present (RT) then
9666 return Needs_Simple_Initialization (RT);
9667 else
9668 return False;
9669 end if;
9670 end;
9672 -- Scalar type with Default_Value aspect requires initialization
9674 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
9675 return True;
9677 -- Cases needing simple initialization are access types, and, if pragma
9678 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
9679 -- types.
9681 elsif Is_Access_Type (T)
9682 or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
9683 then
9684 return True;
9686 -- If Initialize/Normalize_Scalars is in effect, string objects also
9687 -- need initialization, unless they are created in the course of
9688 -- expanding an aggregate (since in the latter case they will be
9689 -- filled with appropriate initializing values before they are used).
9691 elsif Consider_IS_NS
9692 and then Is_Standard_String_Type (T)
9693 and then
9694 (not Is_Itype (T)
9695 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
9696 then
9697 return True;
9699 else
9700 return False;
9701 end if;
9702 end Needs_Simple_Initialization;
9704 ----------------------
9705 -- Predef_Deep_Spec --
9706 ----------------------
9708 function Predef_Deep_Spec
9709 (Loc : Source_Ptr;
9710 Tag_Typ : Entity_Id;
9711 Name : TSS_Name_Type;
9712 For_Body : Boolean := False) return Node_Id
9714 Formals : List_Id;
9716 begin
9717 -- V : in out Tag_Typ
9719 Formals := New_List (
9720 Make_Parameter_Specification (Loc,
9721 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
9722 In_Present => True,
9723 Out_Present => True,
9724 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)));
9726 -- F : Boolean := True
9728 if Name = TSS_Deep_Adjust
9729 or else Name = TSS_Deep_Finalize
9730 then
9731 Append_To (Formals,
9732 Make_Parameter_Specification (Loc,
9733 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
9734 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
9735 Expression => New_Occurrence_Of (Standard_True, Loc)));
9736 end if;
9738 return
9739 Predef_Spec_Or_Body (Loc,
9740 Name => Make_TSS_Name (Tag_Typ, Name),
9741 Tag_Typ => Tag_Typ,
9742 Profile => Formals,
9743 For_Body => For_Body);
9745 exception
9746 when RE_Not_Available =>
9747 return Empty;
9748 end Predef_Deep_Spec;
9750 -------------------------
9751 -- Predef_Spec_Or_Body --
9752 -------------------------
9754 function Predef_Spec_Or_Body
9755 (Loc : Source_Ptr;
9756 Tag_Typ : Entity_Id;
9757 Name : Name_Id;
9758 Profile : List_Id;
9759 Ret_Type : Entity_Id := Empty;
9760 For_Body : Boolean := False) return Node_Id
9762 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
9763 Spec : Node_Id;
9765 begin
9766 Set_Is_Public (Id, Is_Public (Tag_Typ));
9768 -- The internal flag is set to mark these declarations because they have
9769 -- specific properties. First, they are primitives even if they are not
9770 -- defined in the type scope (the freezing point is not necessarily in
9771 -- the same scope). Second, the predefined equality can be overridden by
9772 -- a user-defined equality, no body will be generated in this case.
9774 Set_Is_Internal (Id);
9776 if not Debug_Generated_Code then
9777 Set_Debug_Info_Off (Id);
9778 end if;
9780 if No (Ret_Type) then
9781 Spec :=
9782 Make_Procedure_Specification (Loc,
9783 Defining_Unit_Name => Id,
9784 Parameter_Specifications => Profile);
9785 else
9786 Spec :=
9787 Make_Function_Specification (Loc,
9788 Defining_Unit_Name => Id,
9789 Parameter_Specifications => Profile,
9790 Result_Definition => New_Occurrence_Of (Ret_Type, Loc));
9791 end if;
9793 if Is_Interface (Tag_Typ) then
9794 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9796 -- If body case, return empty subprogram body. Note that this is ill-
9797 -- formed, because there is not even a null statement, and certainly not
9798 -- a return in the function case. The caller is expected to do surgery
9799 -- on the body to add the appropriate stuff.
9801 elsif For_Body then
9802 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
9804 -- For the case of an Input attribute predefined for an abstract type,
9805 -- generate an abstract specification. This will never be called, but we
9806 -- need the slot allocated in the dispatching table so that attributes
9807 -- typ'Class'Input and typ'Class'Output will work properly.
9809 elsif Is_TSS (Name, TSS_Stream_Input)
9810 and then Is_Abstract_Type (Tag_Typ)
9811 then
9812 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9814 -- Normal spec case, where we return a subprogram declaration
9816 else
9817 return Make_Subprogram_Declaration (Loc, Spec);
9818 end if;
9819 end Predef_Spec_Or_Body;
9821 -----------------------------
9822 -- Predef_Stream_Attr_Spec --
9823 -----------------------------
9825 function Predef_Stream_Attr_Spec
9826 (Loc : Source_Ptr;
9827 Tag_Typ : Entity_Id;
9828 Name : TSS_Name_Type;
9829 For_Body : Boolean := False) return Node_Id
9831 Ret_Type : Entity_Id;
9833 begin
9834 if Name = TSS_Stream_Input then
9835 Ret_Type := Tag_Typ;
9836 else
9837 Ret_Type := Empty;
9838 end if;
9840 return
9841 Predef_Spec_Or_Body
9842 (Loc,
9843 Name => Make_TSS_Name (Tag_Typ, Name),
9844 Tag_Typ => Tag_Typ,
9845 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
9846 Ret_Type => Ret_Type,
9847 For_Body => For_Body);
9848 end Predef_Stream_Attr_Spec;
9850 ---------------------------------
9851 -- Predefined_Primitive_Bodies --
9852 ---------------------------------
9854 function Predefined_Primitive_Bodies
9855 (Tag_Typ : Entity_Id;
9856 Renamed_Eq : Entity_Id) return List_Id
9858 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9859 Res : constant List_Id := New_List;
9860 Adj_Call : Node_Id;
9861 Decl : Node_Id;
9862 Fin_Call : Node_Id;
9863 Prim : Elmt_Id;
9864 Eq_Needed : Boolean;
9865 Eq_Name : Name_Id;
9866 Ent : Entity_Id;
9868 pragma Warnings (Off, Ent);
9870 begin
9871 pragma Assert (not Is_Interface (Tag_Typ));
9873 -- See if we have a predefined "=" operator
9875 if Present (Renamed_Eq) then
9876 Eq_Needed := True;
9877 Eq_Name := Chars (Renamed_Eq);
9879 -- If the parent is an interface type then it has defined all the
9880 -- predefined primitives abstract and we need to check if the type
9881 -- has some user defined "=" function which matches the profile of
9882 -- the Ada predefined equality operator to avoid generating it.
9884 elsif Is_Interface (Etype (Tag_Typ)) then
9885 Eq_Needed := True;
9886 Eq_Name := Name_Op_Eq;
9888 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9889 while Present (Prim) loop
9890 if Chars (Node (Prim)) = Name_Op_Eq
9891 and then not Is_Internal (Node (Prim))
9892 and then Present (First_Entity (Node (Prim)))
9894 -- The predefined equality primitive must have exactly two
9895 -- formals whose type is this tagged type
9897 and then Present (Last_Entity (Node (Prim)))
9898 and then Next_Entity (First_Entity (Node (Prim)))
9899 = Last_Entity (Node (Prim))
9900 and then Etype (First_Entity (Node (Prim))) = Tag_Typ
9901 and then Etype (Last_Entity (Node (Prim))) = Tag_Typ
9902 then
9903 Eq_Needed := False;
9904 Eq_Name := No_Name;
9905 exit;
9906 end if;
9908 Next_Elmt (Prim);
9909 end loop;
9911 else
9912 Eq_Needed := False;
9913 Eq_Name := No_Name;
9915 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9916 while Present (Prim) loop
9917 if Chars (Node (Prim)) = Name_Op_Eq
9918 and then Is_Internal (Node (Prim))
9919 then
9920 Eq_Needed := True;
9921 Eq_Name := Name_Op_Eq;
9922 exit;
9923 end if;
9925 Next_Elmt (Prim);
9926 end loop;
9927 end if;
9929 -- Body of _Size
9931 Decl := Predef_Spec_Or_Body (Loc,
9932 Tag_Typ => Tag_Typ,
9933 Name => Name_uSize,
9934 Profile => New_List (
9935 Make_Parameter_Specification (Loc,
9936 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9937 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9939 Ret_Type => Standard_Long_Long_Integer,
9940 For_Body => True);
9942 Set_Handled_Statement_Sequence (Decl,
9943 Make_Handled_Sequence_Of_Statements (Loc, New_List (
9944 Make_Simple_Return_Statement (Loc,
9945 Expression =>
9946 Make_Attribute_Reference (Loc,
9947 Prefix => Make_Identifier (Loc, Name_X),
9948 Attribute_Name => Name_Size)))));
9950 Append_To (Res, Decl);
9952 -- Bodies for Dispatching stream IO routines. We need these only for
9953 -- non-limited types (in the limited case there is no dispatching).
9954 -- We also skip them if dispatching or finalization are not available
9955 -- or if stream operations are prohibited by restriction No_Streams or
9956 -- from use of pragma/aspect No_Tagged_Streams.
9958 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
9959 and then No (TSS (Tag_Typ, TSS_Stream_Read))
9960 then
9961 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
9962 Append_To (Res, Decl);
9963 end if;
9965 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
9966 and then No (TSS (Tag_Typ, TSS_Stream_Write))
9967 then
9968 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
9969 Append_To (Res, Decl);
9970 end if;
9972 -- Skip body of _Input for the abstract case, since the corresponding
9973 -- spec is abstract (see Predef_Spec_Or_Body).
9975 if not Is_Abstract_Type (Tag_Typ)
9976 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
9977 and then No (TSS (Tag_Typ, TSS_Stream_Input))
9978 then
9979 Build_Record_Or_Elementary_Input_Function
9980 (Loc, Tag_Typ, Decl, Ent);
9981 Append_To (Res, Decl);
9982 end if;
9984 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
9985 and then No (TSS (Tag_Typ, TSS_Stream_Output))
9986 then
9987 Build_Record_Or_Elementary_Output_Procedure (Loc, Tag_Typ, Decl, Ent);
9988 Append_To (Res, Decl);
9989 end if;
9991 -- Ada 2005: Generate bodies for the following primitive operations for
9992 -- limited interfaces and synchronized types that implement a limited
9993 -- interface.
9995 -- disp_asynchronous_select
9996 -- disp_conditional_select
9997 -- disp_get_prim_op_kind
9998 -- disp_get_task_id
9999 -- disp_timed_select
10001 -- The interface versions will have null bodies
10003 -- Disable the generation of these bodies if No_Dispatching_Calls,
10004 -- Ravenscar or ZFP is active.
10006 -- In VM targets we define these primitives in all root tagged types
10007 -- that are not interface types. Done because in VM targets we don't
10008 -- have secondary dispatch tables and any derivation of Tag_Typ may
10009 -- cover limited interfaces (which always have these primitives since
10010 -- they may be ancestors of synchronized interface types).
10012 if Ada_Version >= Ada_2005
10013 and then not Is_Interface (Tag_Typ)
10014 and then
10015 ((Is_Interface (Etype (Tag_Typ))
10016 and then Is_Limited_Record (Etype (Tag_Typ)))
10017 or else
10018 (Is_Concurrent_Record_Type (Tag_Typ)
10019 and then Has_Interfaces (Tag_Typ))
10020 or else
10021 (not Tagged_Type_Expansion
10022 and then Tag_Typ = Root_Type (Tag_Typ)))
10023 and then not Restriction_Active (No_Dispatching_Calls)
10024 and then not Restriction_Active (No_Select_Statements)
10025 and then RTE_Available (RE_Select_Specific_Data)
10026 then
10027 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
10028 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
10029 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
10030 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
10031 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
10032 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
10033 end if;
10035 if not Is_Limited_Type (Tag_Typ) and then not Is_Interface (Tag_Typ) then
10037 -- Body for equality
10039 if Eq_Needed then
10040 Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
10041 Append_To (Res, Decl);
10042 end if;
10044 -- Body for inequality (if required)
10046 Decl := Make_Neq_Body (Tag_Typ);
10048 if Present (Decl) then
10049 Append_To (Res, Decl);
10050 end if;
10052 -- Body for dispatching assignment
10054 Decl :=
10055 Predef_Spec_Or_Body (Loc,
10056 Tag_Typ => Tag_Typ,
10057 Name => Name_uAssign,
10058 Profile => New_List (
10059 Make_Parameter_Specification (Loc,
10060 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10061 Out_Present => True,
10062 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10064 Make_Parameter_Specification (Loc,
10065 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
10066 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10067 For_Body => True);
10069 Set_Handled_Statement_Sequence (Decl,
10070 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10071 Make_Assignment_Statement (Loc,
10072 Name => Make_Identifier (Loc, Name_X),
10073 Expression => Make_Identifier (Loc, Name_Y)))));
10075 Append_To (Res, Decl);
10076 end if;
10078 -- Generate empty bodies of routines Deep_Adjust and Deep_Finalize for
10079 -- tagged types which do not contain controlled components.
10081 -- Do not generate the routines if finalization is disabled
10083 if Restriction_Active (No_Finalization) then
10084 null;
10086 elsif not Has_Controlled_Component (Tag_Typ) then
10087 if not Is_Limited_Type (Tag_Typ) then
10088 Adj_Call := Empty;
10089 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
10091 if Is_Controlled (Tag_Typ) then
10092 Adj_Call :=
10093 Make_Adjust_Call (
10094 Obj_Ref => Make_Identifier (Loc, Name_V),
10095 Typ => Tag_Typ);
10096 end if;
10098 if No (Adj_Call) then
10099 Adj_Call := Make_Null_Statement (Loc);
10100 end if;
10102 Set_Handled_Statement_Sequence (Decl,
10103 Make_Handled_Sequence_Of_Statements (Loc,
10104 Statements => New_List (Adj_Call)));
10106 Append_To (Res, Decl);
10107 end if;
10109 Fin_Call := Empty;
10110 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
10112 if Is_Controlled (Tag_Typ) then
10113 Fin_Call :=
10114 Make_Final_Call
10115 (Obj_Ref => Make_Identifier (Loc, Name_V),
10116 Typ => Tag_Typ);
10117 end if;
10119 if No (Fin_Call) then
10120 Fin_Call := Make_Null_Statement (Loc);
10121 end if;
10123 Set_Handled_Statement_Sequence (Decl,
10124 Make_Handled_Sequence_Of_Statements (Loc,
10125 Statements => New_List (Fin_Call)));
10127 Append_To (Res, Decl);
10128 end if;
10130 return Res;
10131 end Predefined_Primitive_Bodies;
10133 ---------------------------------
10134 -- Predefined_Primitive_Freeze --
10135 ---------------------------------
10137 function Predefined_Primitive_Freeze
10138 (Tag_Typ : Entity_Id) return List_Id
10140 Res : constant List_Id := New_List;
10141 Prim : Elmt_Id;
10142 Frnodes : List_Id;
10144 begin
10145 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10146 while Present (Prim) loop
10147 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
10148 Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
10150 if Present (Frnodes) then
10151 Append_List_To (Res, Frnodes);
10152 end if;
10153 end if;
10155 Next_Elmt (Prim);
10156 end loop;
10158 return Res;
10159 end Predefined_Primitive_Freeze;
10161 -------------------------
10162 -- Stream_Operation_OK --
10163 -------------------------
10165 function Stream_Operation_OK
10166 (Typ : Entity_Id;
10167 Operation : TSS_Name_Type) return Boolean
10169 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
10171 begin
10172 -- Special case of a limited type extension: a default implementation
10173 -- of the stream attributes Read or Write exists if that attribute
10174 -- has been specified or is available for an ancestor type; a default
10175 -- implementation of the attribute Output (resp. Input) exists if the
10176 -- attribute has been specified or Write (resp. Read) is available for
10177 -- an ancestor type. The last condition only applies under Ada 2005.
10179 if Is_Limited_Type (Typ) and then Is_Tagged_Type (Typ) then
10180 if Operation = TSS_Stream_Read then
10181 Has_Predefined_Or_Specified_Stream_Attribute :=
10182 Has_Specified_Stream_Read (Typ);
10184 elsif Operation = TSS_Stream_Write then
10185 Has_Predefined_Or_Specified_Stream_Attribute :=
10186 Has_Specified_Stream_Write (Typ);
10188 elsif Operation = TSS_Stream_Input then
10189 Has_Predefined_Or_Specified_Stream_Attribute :=
10190 Has_Specified_Stream_Input (Typ)
10191 or else
10192 (Ada_Version >= Ada_2005
10193 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
10195 elsif Operation = TSS_Stream_Output then
10196 Has_Predefined_Or_Specified_Stream_Attribute :=
10197 Has_Specified_Stream_Output (Typ)
10198 or else
10199 (Ada_Version >= Ada_2005
10200 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
10201 end if;
10203 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
10205 if not Has_Predefined_Or_Specified_Stream_Attribute
10206 and then Is_Derived_Type (Typ)
10207 and then (Operation = TSS_Stream_Read
10208 or else Operation = TSS_Stream_Write)
10209 then
10210 Has_Predefined_Or_Specified_Stream_Attribute :=
10211 Present
10212 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
10213 end if;
10214 end if;
10216 -- If the type is not limited, or else is limited but the attribute is
10217 -- explicitly specified or is predefined for the type, then return True,
10218 -- unless other conditions prevail, such as restrictions prohibiting
10219 -- streams or dispatching operations. We also return True for limited
10220 -- interfaces, because they may be extended by nonlimited types and
10221 -- permit inheritance in this case (addresses cases where an abstract
10222 -- extension doesn't get 'Input declared, as per comments below, but
10223 -- 'Class'Input must still be allowed). Note that attempts to apply
10224 -- stream attributes to a limited interface or its class-wide type
10225 -- (or limited extensions thereof) will still get properly rejected
10226 -- by Check_Stream_Attribute.
10228 -- We exclude the Input operation from being a predefined subprogram in
10229 -- the case where the associated type is an abstract extension, because
10230 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
10231 -- we don't want an abstract version created because types derived from
10232 -- the abstract type may not even have Input available (for example if
10233 -- derived from a private view of the abstract type that doesn't have
10234 -- a visible Input).
10236 -- Do not generate stream routines for type Finalization_Master because
10237 -- a master may never appear in types and therefore cannot be read or
10238 -- written.
10240 return
10241 (not Is_Limited_Type (Typ)
10242 or else Is_Interface (Typ)
10243 or else Has_Predefined_Or_Specified_Stream_Attribute)
10244 and then
10245 (Operation /= TSS_Stream_Input
10246 or else not Is_Abstract_Type (Typ)
10247 or else not Is_Derived_Type (Typ))
10248 and then not Has_Unknown_Discriminants (Typ)
10249 and then not
10250 (Is_Interface (Typ)
10251 and then
10252 (Is_Task_Interface (Typ)
10253 or else Is_Protected_Interface (Typ)
10254 or else Is_Synchronized_Interface (Typ)))
10255 and then not Restriction_Active (No_Streams)
10256 and then not Restriction_Active (No_Dispatch)
10257 and then No (No_Tagged_Streams_Pragma (Typ))
10258 and then not No_Run_Time_Mode
10259 and then RTE_Available (RE_Tag)
10260 and then No (Type_Without_Stream_Operation (Typ))
10261 and then RTE_Available (RE_Root_Stream_Type)
10262 and then not Is_RTE (Typ, RE_Finalization_Master);
10263 end Stream_Operation_OK;
10265 end Exp_Ch3;