[gcc/testsuite]
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob9ed8ea0ae1656523f25029261b353a6d6df1626a
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 begin
1786 Lhs :=
1787 Make_Selected_Component (N_Loc,
1788 Prefix => Make_Identifier (Loc, Name_uInit),
1789 Selector_Name => New_Occurrence_Of (Id, N_Loc));
1790 Set_Assignment_OK (Lhs);
1792 -- Case of an access attribute applied to the current instance.
1793 -- Replace the reference to the type by a reference to the actual
1794 -- object. (Note that this handles the case of the top level of
1795 -- the expression being given by such an attribute, but does not
1796 -- cover uses nested within an initial value expression. Nested
1797 -- uses are unlikely to occur in practice, but are theoretically
1798 -- possible.) It is not clear how to handle them without fully
1799 -- traversing the expression. ???
1801 if Kind = N_Attribute_Reference
1802 and then Nam_In (Attribute_Name (N), Name_Unchecked_Access,
1803 Name_Unrestricted_Access)
1804 and then Is_Entity_Name (Prefix (N))
1805 and then Is_Type (Entity (Prefix (N)))
1806 and then Entity (Prefix (N)) = Rec_Type
1807 then
1808 Exp :=
1809 Make_Attribute_Reference (N_Loc,
1810 Prefix =>
1811 Make_Identifier (N_Loc, Name_uInit),
1812 Attribute_Name => Name_Unrestricted_Access);
1813 end if;
1815 -- Take a copy of Exp to ensure that later copies of this component
1816 -- declaration in derived types see the original tree, not a node
1817 -- rewritten during expansion of the init_proc. If the copy contains
1818 -- itypes, the scope of the new itypes is the init_proc being built.
1820 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id);
1822 Res := New_List (
1823 Make_Assignment_Statement (Loc,
1824 Name => Lhs,
1825 Expression => Exp));
1827 Set_No_Ctrl_Actions (First (Res));
1829 -- Adjust the tag if tagged (because of possible view conversions).
1830 -- Suppress the tag adjustment when not Tagged_Type_Expansion because
1831 -- tags are represented implicitly in objects.
1833 if Is_Tagged_Type (Typ) and then Tagged_Type_Expansion then
1834 Append_To (Res,
1835 Make_Assignment_Statement (N_Loc,
1836 Name =>
1837 Make_Selected_Component (N_Loc,
1838 Prefix =>
1839 New_Copy_Tree (Lhs, New_Scope => Proc_Id),
1840 Selector_Name =>
1841 New_Occurrence_Of (First_Tag_Component (Typ), N_Loc)),
1843 Expression =>
1844 Unchecked_Convert_To (RTE (RE_Tag),
1845 New_Occurrence_Of
1846 (Node
1847 (First_Elmt
1848 (Access_Disp_Table (Underlying_Type (Typ)))),
1849 N_Loc))));
1850 end if;
1852 -- Adjust the component if controlled except if it is an aggregate
1853 -- that will be expanded inline.
1855 if Kind = N_Qualified_Expression then
1856 Kind := Nkind (Expression (N));
1857 end if;
1859 if Needs_Finalization (Typ)
1860 and then not (Nkind_In (Kind, N_Aggregate, N_Extension_Aggregate))
1861 and then not Is_Limited_View (Typ)
1862 then
1863 Adj_Call :=
1864 Make_Adjust_Call
1865 (Obj_Ref => New_Copy_Tree (Lhs),
1866 Typ => Etype (Id));
1868 -- Guard against a missing [Deep_]Adjust when the component type
1869 -- was not properly frozen.
1871 if Present (Adj_Call) then
1872 Append_To (Res, Adj_Call);
1873 end if;
1874 end if;
1876 -- If a component type has a predicate, add check to the component
1877 -- assignment. Discriminants are handled at the point of the call,
1878 -- which provides for a better error message.
1880 if Comes_From_Source (Exp)
1881 and then Has_Predicates (Typ)
1882 and then not Predicate_Checks_Suppressed (Empty)
1883 and then not Predicates_Ignored (Typ)
1884 then
1885 Append (Make_Predicate_Check (Typ, Exp), Res);
1886 end if;
1888 return Res;
1890 exception
1891 when RE_Not_Available =>
1892 return Empty_List;
1893 end Build_Assignment;
1895 ------------------------------------
1896 -- Build_Discriminant_Assignments --
1897 ------------------------------------
1899 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1900 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1901 D : Entity_Id;
1902 D_Loc : Source_Ptr;
1904 begin
1905 if Has_Discriminants (Rec_Type)
1906 and then not Is_Unchecked_Union (Rec_Type)
1907 then
1908 D := First_Discriminant (Rec_Type);
1909 while Present (D) loop
1911 -- Don't generate the assignment for discriminants in derived
1912 -- tagged types if the discriminant is a renaming of some
1913 -- ancestor discriminant. This initialization will be done
1914 -- when initializing the _parent field of the derived record.
1916 if Is_Tagged
1917 and then Present (Corresponding_Discriminant (D))
1918 then
1919 null;
1921 else
1922 D_Loc := Sloc (D);
1923 Append_List_To (Statement_List,
1924 Build_Assignment (D,
1925 New_Occurrence_Of (Discriminal (D), D_Loc)));
1926 end if;
1928 Next_Discriminant (D);
1929 end loop;
1930 end if;
1931 end Build_Discriminant_Assignments;
1933 --------------------------
1934 -- Build_Init_Call_Thru --
1935 --------------------------
1937 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1938 Parent_Proc : constant Entity_Id :=
1939 Base_Init_Proc (Etype (Rec_Type));
1941 Parent_Type : constant Entity_Id :=
1942 Etype (First_Formal (Parent_Proc));
1944 Uparent_Type : constant Entity_Id :=
1945 Underlying_Type (Parent_Type);
1947 First_Discr_Param : Node_Id;
1949 Arg : Node_Id;
1950 Args : List_Id;
1951 First_Arg : Node_Id;
1952 Parent_Discr : Entity_Id;
1953 Res : List_Id;
1955 begin
1956 -- First argument (_Init) is the object to be initialized.
1957 -- ??? not sure where to get a reasonable Loc for First_Arg
1959 First_Arg :=
1960 OK_Convert_To (Parent_Type,
1961 New_Occurrence_Of
1962 (Defining_Identifier (First (Parameters)), Loc));
1964 Set_Etype (First_Arg, Parent_Type);
1966 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1968 -- In the tasks case,
1969 -- add _Master as the value of the _Master parameter
1970 -- add _Chain as the value of the _Chain parameter.
1971 -- add _Task_Name as the value of the _Task_Name parameter.
1972 -- At the outer level, these will be variables holding the
1973 -- corresponding values obtained from GNARL or the expander.
1975 -- At inner levels, they will be the parameters passed down through
1976 -- the outer routines.
1978 First_Discr_Param := Next (First (Parameters));
1980 if Has_Task (Rec_Type) then
1981 if Restriction_Active (No_Task_Hierarchy) then
1982 Append_To (Args,
1983 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
1984 else
1985 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1986 end if;
1988 -- Add _Chain (not done for sequential elaboration policy, see
1989 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
1991 if Partition_Elaboration_Policy /= 'S' then
1992 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1993 end if;
1995 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1996 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1997 end if;
1999 -- Append discriminant values
2001 if Has_Discriminants (Uparent_Type) then
2002 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2004 Parent_Discr := First_Discriminant (Uparent_Type);
2005 while Present (Parent_Discr) loop
2007 -- Get the initial value for this discriminant
2008 -- ??? needs to be cleaned up to use parent_Discr_Constr
2009 -- directly.
2011 declare
2012 Discr : Entity_Id :=
2013 First_Stored_Discriminant (Uparent_Type);
2015 Discr_Value : Elmt_Id :=
2016 First_Elmt (Stored_Constraint (Rec_Type));
2018 begin
2019 while Original_Record_Component (Parent_Discr) /= Discr loop
2020 Next_Stored_Discriminant (Discr);
2021 Next_Elmt (Discr_Value);
2022 end loop;
2024 Arg := Node (Discr_Value);
2025 end;
2027 -- Append it to the list
2029 if Nkind (Arg) = N_Identifier
2030 and then Ekind (Entity (Arg)) = E_Discriminant
2031 then
2032 Append_To (Args,
2033 New_Occurrence_Of (Discriminal (Entity (Arg)), Loc));
2035 -- Case of access discriminants. We replace the reference
2036 -- to the type by a reference to the actual object.
2038 -- Is above comment right??? Use of New_Copy below seems mighty
2039 -- suspicious ???
2041 else
2042 Append_To (Args, New_Copy (Arg));
2043 end if;
2045 Next_Discriminant (Parent_Discr);
2046 end loop;
2047 end if;
2049 Res :=
2050 New_List (
2051 Make_Procedure_Call_Statement (Loc,
2052 Name =>
2053 New_Occurrence_Of (Parent_Proc, Loc),
2054 Parameter_Associations => Args));
2056 return Res;
2057 end Build_Init_Call_Thru;
2059 -----------------------------------
2060 -- Build_Offset_To_Top_Functions --
2061 -----------------------------------
2063 procedure Build_Offset_To_Top_Functions is
2065 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2066 -- Generate:
2067 -- function Fxx (O : Address) return Storage_Offset is
2068 -- type Acc is access all <Typ>;
2069 -- begin
2070 -- return Acc!(O).Iface_Comp'Position;
2071 -- end Fxx;
2073 ----------------------------------
2074 -- Build_Offset_To_Top_Function --
2075 ----------------------------------
2077 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2078 Body_Node : Node_Id;
2079 Func_Id : Entity_Id;
2080 Spec_Node : Node_Id;
2081 Acc_Type : Entity_Id;
2083 begin
2084 Func_Id := Make_Temporary (Loc, 'F');
2085 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2087 -- Generate
2088 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2090 Spec_Node := New_Node (N_Function_Specification, Loc);
2091 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2092 Set_Parameter_Specifications (Spec_Node, New_List (
2093 Make_Parameter_Specification (Loc,
2094 Defining_Identifier =>
2095 Make_Defining_Identifier (Loc, Name_uO),
2096 In_Present => True,
2097 Parameter_Type =>
2098 New_Occurrence_Of (RTE (RE_Address), Loc))));
2099 Set_Result_Definition (Spec_Node,
2100 New_Occurrence_Of (RTE (RE_Storage_Offset), Loc));
2102 -- Generate
2103 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2104 -- begin
2105 -- return O.Iface_Comp'Position;
2106 -- end Fxx;
2108 Body_Node := New_Node (N_Subprogram_Body, Loc);
2109 Set_Specification (Body_Node, Spec_Node);
2111 Acc_Type := Make_Temporary (Loc, 'T');
2112 Set_Declarations (Body_Node, New_List (
2113 Make_Full_Type_Declaration (Loc,
2114 Defining_Identifier => Acc_Type,
2115 Type_Definition =>
2116 Make_Access_To_Object_Definition (Loc,
2117 All_Present => True,
2118 Null_Exclusion_Present => False,
2119 Constant_Present => False,
2120 Subtype_Indication =>
2121 New_Occurrence_Of (Rec_Type, Loc)))));
2123 Set_Handled_Statement_Sequence (Body_Node,
2124 Make_Handled_Sequence_Of_Statements (Loc,
2125 Statements => New_List (
2126 Make_Simple_Return_Statement (Loc,
2127 Expression =>
2128 Make_Attribute_Reference (Loc,
2129 Prefix =>
2130 Make_Selected_Component (Loc,
2131 Prefix =>
2132 Unchecked_Convert_To (Acc_Type,
2133 Make_Identifier (Loc, Name_uO)),
2134 Selector_Name =>
2135 New_Occurrence_Of (Iface_Comp, Loc)),
2136 Attribute_Name => Name_Position)))));
2138 Set_Ekind (Func_Id, E_Function);
2139 Set_Mechanism (Func_Id, Default_Mechanism);
2140 Set_Is_Internal (Func_Id, True);
2142 if not Debug_Generated_Code then
2143 Set_Debug_Info_Off (Func_Id);
2144 end if;
2146 Analyze (Body_Node);
2148 Append_Freeze_Action (Rec_Type, Body_Node);
2149 end Build_Offset_To_Top_Function;
2151 -- Local variables
2153 Iface_Comp : Node_Id;
2154 Iface_Comp_Elmt : Elmt_Id;
2155 Ifaces_Comp_List : Elist_Id;
2157 -- Start of processing for Build_Offset_To_Top_Functions
2159 begin
2160 -- Offset_To_Top_Functions are built only for derivations of types
2161 -- with discriminants that cover interface types.
2162 -- Nothing is needed either in case of virtual targets, since
2163 -- interfaces are handled directly by the target.
2165 if not Is_Tagged_Type (Rec_Type)
2166 or else Etype (Rec_Type) = Rec_Type
2167 or else not Has_Discriminants (Etype (Rec_Type))
2168 or else not Tagged_Type_Expansion
2169 then
2170 return;
2171 end if;
2173 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2175 -- For each interface type with secondary dispatch table we generate
2176 -- the Offset_To_Top_Functions (required to displace the pointer in
2177 -- interface conversions)
2179 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2180 while Present (Iface_Comp_Elmt) loop
2181 Iface_Comp := Node (Iface_Comp_Elmt);
2182 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2184 -- If the interface is a parent of Rec_Type it shares the primary
2185 -- dispatch table and hence there is no need to build the function
2187 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type,
2188 Use_Full_View => True)
2189 then
2190 Build_Offset_To_Top_Function (Iface_Comp);
2191 end if;
2193 Next_Elmt (Iface_Comp_Elmt);
2194 end loop;
2195 end Build_Offset_To_Top_Functions;
2197 ------------------------------
2198 -- Build_CPP_Init_Procedure --
2199 ------------------------------
2201 procedure Build_CPP_Init_Procedure is
2202 Body_Node : Node_Id;
2203 Body_Stmts : List_Id;
2204 Flag_Id : Entity_Id;
2205 Handled_Stmt_Node : Node_Id;
2206 Init_Tags_List : List_Id;
2207 Proc_Id : Entity_Id;
2208 Proc_Spec_Node : Node_Id;
2210 begin
2211 -- Check cases requiring no IC routine
2213 if not Is_CPP_Class (Root_Type (Rec_Type))
2214 or else Is_CPP_Class (Rec_Type)
2215 or else CPP_Num_Prims (Rec_Type) = 0
2216 or else not Tagged_Type_Expansion
2217 or else No_Run_Time_Mode
2218 then
2219 return;
2220 end if;
2222 -- Generate:
2224 -- Flag : Boolean := False;
2226 -- procedure Typ_IC is
2227 -- begin
2228 -- if not Flag then
2229 -- Copy C++ dispatch table slots from parent
2230 -- Update C++ slots of overridden primitives
2231 -- end if;
2232 -- end;
2234 Flag_Id := Make_Temporary (Loc, 'F');
2236 Append_Freeze_Action (Rec_Type,
2237 Make_Object_Declaration (Loc,
2238 Defining_Identifier => Flag_Id,
2239 Object_Definition =>
2240 New_Occurrence_Of (Standard_Boolean, Loc),
2241 Expression =>
2242 New_Occurrence_Of (Standard_True, Loc)));
2244 Body_Stmts := New_List;
2245 Body_Node := New_Node (N_Subprogram_Body, Loc);
2247 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2249 Proc_Id :=
2250 Make_Defining_Identifier (Loc,
2251 Chars => Make_TSS_Name (Rec_Type, TSS_CPP_Init_Proc));
2253 Set_Ekind (Proc_Id, E_Procedure);
2254 Set_Is_Internal (Proc_Id);
2256 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2258 Set_Parameter_Specifications (Proc_Spec_Node, New_List);
2259 Set_Specification (Body_Node, Proc_Spec_Node);
2260 Set_Declarations (Body_Node, New_List);
2262 Init_Tags_List := Build_Inherit_CPP_Prims (Rec_Type);
2264 Append_To (Init_Tags_List,
2265 Make_Assignment_Statement (Loc,
2266 Name =>
2267 New_Occurrence_Of (Flag_Id, Loc),
2268 Expression =>
2269 New_Occurrence_Of (Standard_False, Loc)));
2271 Append_To (Body_Stmts,
2272 Make_If_Statement (Loc,
2273 Condition => New_Occurrence_Of (Flag_Id, Loc),
2274 Then_Statements => Init_Tags_List));
2276 Handled_Stmt_Node :=
2277 New_Node (N_Handled_Sequence_Of_Statements, Loc);
2278 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2279 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2280 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2282 if not Debug_Generated_Code then
2283 Set_Debug_Info_Off (Proc_Id);
2284 end if;
2286 -- Associate CPP_Init_Proc with type
2288 Set_Init_Proc (Rec_Type, Proc_Id);
2289 end Build_CPP_Init_Procedure;
2291 --------------------------
2292 -- Build_Init_Procedure --
2293 --------------------------
2295 procedure Build_Init_Procedure is
2296 Body_Stmts : List_Id;
2297 Body_Node : Node_Id;
2298 Handled_Stmt_Node : Node_Id;
2299 Init_Tags_List : List_Id;
2300 Parameters : List_Id;
2301 Proc_Spec_Node : Node_Id;
2302 Record_Extension_Node : Node_Id;
2304 begin
2305 Body_Stmts := New_List;
2306 Body_Node := New_Node (N_Subprogram_Body, Loc);
2307 Set_Ekind (Proc_Id, E_Procedure);
2309 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2310 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2312 Parameters := Init_Formals (Rec_Type);
2313 Append_List_To (Parameters,
2314 Build_Discriminant_Formals (Rec_Type, True));
2316 -- For tagged types, we add a flag to indicate whether the routine
2317 -- is called to initialize a parent component in the init_proc of
2318 -- a type extension. If the flag is false, we do not set the tag
2319 -- because it has been set already in the extension.
2321 if Is_Tagged_Type (Rec_Type) then
2322 Set_Tag := Make_Temporary (Loc, 'P');
2324 Append_To (Parameters,
2325 Make_Parameter_Specification (Loc,
2326 Defining_Identifier => Set_Tag,
2327 Parameter_Type =>
2328 New_Occurrence_Of (Standard_Boolean, Loc),
2329 Expression =>
2330 New_Occurrence_Of (Standard_True, Loc)));
2331 end if;
2333 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2334 Set_Specification (Body_Node, Proc_Spec_Node);
2335 Set_Declarations (Body_Node, Decls);
2337 -- N is a Derived_Type_Definition that renames the parameters of the
2338 -- ancestor type. We initialize it by expanding our discriminants and
2339 -- call the ancestor _init_proc with a type-converted object.
2341 if Parent_Subtype_Renaming_Discrims then
2342 Append_List_To (Body_Stmts, Build_Init_Call_Thru (Parameters));
2344 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2345 Build_Discriminant_Assignments (Body_Stmts);
2347 if not Null_Present (Type_Definition (N)) then
2348 Append_List_To (Body_Stmts,
2349 Build_Init_Statements (Component_List (Type_Definition (N))));
2350 end if;
2352 -- N is a Derived_Type_Definition with a possible non-empty
2353 -- extension. The initialization of a type extension consists in the
2354 -- initialization of the components in the extension.
2356 else
2357 Build_Discriminant_Assignments (Body_Stmts);
2359 Record_Extension_Node :=
2360 Record_Extension_Part (Type_Definition (N));
2362 if not Null_Present (Record_Extension_Node) then
2363 declare
2364 Stmts : constant List_Id :=
2365 Build_Init_Statements (
2366 Component_List (Record_Extension_Node));
2368 begin
2369 -- The parent field must be initialized first because the
2370 -- offset of the new discriminants may depend on it. This is
2371 -- not needed if the parent is an interface type because in
2372 -- such case the initialization of the _parent field was not
2373 -- generated.
2375 if not Is_Interface (Etype (Rec_Ent)) then
2376 declare
2377 Parent_IP : constant Name_Id :=
2378 Make_Init_Proc_Name (Etype (Rec_Ent));
2379 Stmt : Node_Id;
2380 IP_Call : Node_Id;
2381 IP_Stmts : List_Id;
2383 begin
2384 -- Look for a call to the parent IP at the beginning
2385 -- of Stmts associated with the record extension
2387 Stmt := First (Stmts);
2388 IP_Call := Empty;
2389 while Present (Stmt) loop
2390 if Nkind (Stmt) = N_Procedure_Call_Statement
2391 and then Chars (Name (Stmt)) = Parent_IP
2392 then
2393 IP_Call := Stmt;
2394 exit;
2395 end if;
2397 Next (Stmt);
2398 end loop;
2400 -- If found then move it to the beginning of the
2401 -- statements of this IP routine
2403 if Present (IP_Call) then
2404 IP_Stmts := New_List;
2405 loop
2406 Stmt := Remove_Head (Stmts);
2407 Append_To (IP_Stmts, Stmt);
2408 exit when Stmt = IP_Call;
2409 end loop;
2411 Prepend_List_To (Body_Stmts, IP_Stmts);
2412 end if;
2413 end;
2414 end if;
2416 Append_List_To (Body_Stmts, Stmts);
2417 end;
2418 end if;
2419 end if;
2421 -- Add here the assignment to instantiate the Tag
2423 -- The assignment corresponds to the code:
2425 -- _Init._Tag := Typ'Tag;
2427 -- Suppress the tag assignment when not Tagged_Type_Expansion because
2428 -- tags are represented implicitly in objects. It is also suppressed
2429 -- in case of CPP_Class types because in this case the tag is
2430 -- initialized in the C++ side.
2432 if Is_Tagged_Type (Rec_Type)
2433 and then Tagged_Type_Expansion
2434 and then not No_Run_Time_Mode
2435 then
2436 -- Case 1: Ada tagged types with no CPP ancestor. Set the tags of
2437 -- the actual object and invoke the IP of the parent (in this
2438 -- order). The tag must be initialized before the call to the IP
2439 -- of the parent and the assignments to other components because
2440 -- the initial value of the components may depend on the tag (eg.
2441 -- through a dispatching operation on an access to the current
2442 -- type). The tag assignment is not done when initializing the
2443 -- parent component of a type extension, because in that case the
2444 -- tag is set in the extension.
2446 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2448 -- Initialize the primary tag component
2450 Init_Tags_List := New_List (
2451 Make_Assignment_Statement (Loc,
2452 Name =>
2453 Make_Selected_Component (Loc,
2454 Prefix => Make_Identifier (Loc, Name_uInit),
2455 Selector_Name =>
2456 New_Occurrence_Of
2457 (First_Tag_Component (Rec_Type), Loc)),
2458 Expression =>
2459 New_Occurrence_Of
2460 (Node
2461 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2463 -- Ada 2005 (AI-251): Initialize the secondary tags components
2464 -- located at fixed positions (tags whose position depends on
2465 -- variable size components are initialized later ---see below)
2467 if Ada_Version >= Ada_2005
2468 and then not Is_Interface (Rec_Type)
2469 and then Has_Interfaces (Rec_Type)
2470 then
2471 declare
2472 Elab_Sec_DT_Stmts_List : constant List_Id := New_List;
2474 begin
2475 Init_Secondary_Tags
2476 (Typ => Rec_Type,
2477 Target => Make_Identifier (Loc, Name_uInit),
2478 Init_Tags_List => Init_Tags_List,
2479 Stmts_List => Elab_Sec_DT_Stmts_List,
2480 Fixed_Comps => True,
2481 Variable_Comps => False);
2483 Append_To (Elab_Sec_DT_Stmts_List,
2484 Make_Assignment_Statement (Loc,
2485 Name =>
2486 New_Occurrence_Of
2487 (Access_Disp_Table_Elab_Flag (Rec_Type), Loc),
2488 Expression =>
2489 New_Occurrence_Of (Standard_False, Loc)));
2491 Prepend_List_To (Body_Stmts, New_List (
2492 Make_If_Statement (Loc,
2493 Condition => New_Occurrence_Of (Set_Tag, Loc),
2494 Then_Statements => Init_Tags_List),
2496 Make_If_Statement (Loc,
2497 Condition =>
2498 New_Occurrence_Of
2499 (Access_Disp_Table_Elab_Flag (Rec_Type), Loc),
2500 Then_Statements => Elab_Sec_DT_Stmts_List)));
2501 end;
2502 else
2503 Prepend_To (Body_Stmts,
2504 Make_If_Statement (Loc,
2505 Condition => New_Occurrence_Of (Set_Tag, Loc),
2506 Then_Statements => Init_Tags_List));
2507 end if;
2509 -- Case 2: CPP type. The imported C++ constructor takes care of
2510 -- tags initialization. No action needed here because the IP
2511 -- is built by Set_CPP_Constructors; in this case the IP is a
2512 -- wrapper that invokes the C++ constructor and copies the C++
2513 -- tags locally. Done to inherit the C++ slots in Ada derivations
2514 -- (see case 3).
2516 elsif Is_CPP_Class (Rec_Type) then
2517 pragma Assert (False);
2518 null;
2520 -- Case 3: Combined hierarchy containing C++ types and Ada tagged
2521 -- type derivations. Derivations of imported C++ classes add a
2522 -- complication, because we cannot inhibit tag setting in the
2523 -- constructor for the parent. Hence we initialize the tag after
2524 -- the call to the parent IP (that is, in reverse order compared
2525 -- with pure Ada hierarchies ---see comment on case 1).
2527 else
2528 -- Initialize the primary tag
2530 Init_Tags_List := New_List (
2531 Make_Assignment_Statement (Loc,
2532 Name =>
2533 Make_Selected_Component (Loc,
2534 Prefix => Make_Identifier (Loc, Name_uInit),
2535 Selector_Name =>
2536 New_Occurrence_Of
2537 (First_Tag_Component (Rec_Type), Loc)),
2538 Expression =>
2539 New_Occurrence_Of
2540 (Node
2541 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2543 -- Ada 2005 (AI-251): Initialize the secondary tags components
2544 -- located at fixed positions (tags whose position depends on
2545 -- variable size components are initialized later ---see below)
2547 if Ada_Version >= Ada_2005
2548 and then not Is_Interface (Rec_Type)
2549 and then Has_Interfaces (Rec_Type)
2550 then
2551 Init_Secondary_Tags
2552 (Typ => Rec_Type,
2553 Target => Make_Identifier (Loc, Name_uInit),
2554 Init_Tags_List => Init_Tags_List,
2555 Stmts_List => Init_Tags_List,
2556 Fixed_Comps => True,
2557 Variable_Comps => False);
2558 end if;
2560 -- Initialize the tag component after invocation of parent IP.
2562 -- Generate:
2563 -- parent_IP(_init.parent); // Invokes the C++ constructor
2564 -- [ typIC; ] // Inherit C++ slots from parent
2565 -- init_tags
2567 declare
2568 Ins_Nod : Node_Id;
2570 begin
2571 -- Search for the call to the IP of the parent. We assume
2572 -- that the first init_proc call is for the parent.
2574 Ins_Nod := First (Body_Stmts);
2575 while Present (Next (Ins_Nod))
2576 and then (Nkind (Ins_Nod) /= N_Procedure_Call_Statement
2577 or else not Is_Init_Proc (Name (Ins_Nod)))
2578 loop
2579 Next (Ins_Nod);
2580 end loop;
2582 -- The IC routine copies the inherited slots of the C+ part
2583 -- of the dispatch table from the parent and updates the
2584 -- overridden C++ slots.
2586 if CPP_Num_Prims (Rec_Type) > 0 then
2587 declare
2588 Init_DT : Entity_Id;
2589 New_Nod : Node_Id;
2591 begin
2592 Init_DT := CPP_Init_Proc (Rec_Type);
2593 pragma Assert (Present (Init_DT));
2595 New_Nod :=
2596 Make_Procedure_Call_Statement (Loc,
2597 New_Occurrence_Of (Init_DT, Loc));
2598 Insert_After (Ins_Nod, New_Nod);
2600 -- Update location of init tag statements
2602 Ins_Nod := New_Nod;
2603 end;
2604 end if;
2606 Insert_List_After (Ins_Nod, Init_Tags_List);
2607 end;
2608 end if;
2610 -- Ada 2005 (AI-251): Initialize the secondary tag components
2611 -- located at variable positions. We delay the generation of this
2612 -- code until here because the value of the attribute 'Position
2613 -- applied to variable size components of the parent type that
2614 -- depend on discriminants is only safely read at runtime after
2615 -- the parent components have been initialized.
2617 if Ada_Version >= Ada_2005
2618 and then not Is_Interface (Rec_Type)
2619 and then Has_Interfaces (Rec_Type)
2620 and then Has_Discriminants (Etype (Rec_Type))
2621 and then Is_Variable_Size_Record (Etype (Rec_Type))
2622 then
2623 Init_Tags_List := New_List;
2625 Init_Secondary_Tags
2626 (Typ => Rec_Type,
2627 Target => Make_Identifier (Loc, Name_uInit),
2628 Init_Tags_List => Init_Tags_List,
2629 Stmts_List => Init_Tags_List,
2630 Fixed_Comps => False,
2631 Variable_Comps => True);
2633 if Is_Non_Empty_List (Init_Tags_List) then
2634 Append_List_To (Body_Stmts, Init_Tags_List);
2635 end if;
2636 end if;
2637 end if;
2639 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2640 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2642 -- Generate:
2643 -- Deep_Finalize (_init, C1, ..., CN);
2644 -- raise;
2646 if Counter > 0
2647 and then Needs_Finalization (Rec_Type)
2648 and then not Is_Abstract_Type (Rec_Type)
2649 and then not Restriction_Active (No_Exception_Propagation)
2650 then
2651 declare
2652 DF_Call : Node_Id;
2653 DF_Id : Entity_Id;
2655 begin
2656 -- Create a local version of Deep_Finalize which has indication
2657 -- of partial initialization state.
2659 DF_Id := Make_Temporary (Loc, 'F');
2661 Append_To (Decls, Make_Local_Deep_Finalize (Rec_Type, DF_Id));
2663 DF_Call :=
2664 Make_Procedure_Call_Statement (Loc,
2665 Name => New_Occurrence_Of (DF_Id, Loc),
2666 Parameter_Associations => New_List (
2667 Make_Identifier (Loc, Name_uInit),
2668 New_Occurrence_Of (Standard_False, Loc)));
2670 -- Do not emit warnings related to the elaboration order when a
2671 -- controlled object is declared before the body of Finalize is
2672 -- seen.
2674 Set_No_Elaboration_Check (DF_Call);
2676 Set_Exception_Handlers (Handled_Stmt_Node, New_List (
2677 Make_Exception_Handler (Loc,
2678 Exception_Choices => New_List (
2679 Make_Others_Choice (Loc)),
2680 Statements => New_List (
2681 DF_Call,
2682 Make_Raise_Statement (Loc)))));
2683 end;
2684 else
2685 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2686 end if;
2688 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2690 if not Debug_Generated_Code then
2691 Set_Debug_Info_Off (Proc_Id);
2692 end if;
2694 -- Associate Init_Proc with type, and determine if the procedure
2695 -- is null (happens because of the Initialize_Scalars pragma case,
2696 -- where we have to generate a null procedure in case it is called
2697 -- by a client with Initialize_Scalars set). Such procedures have
2698 -- to be generated, but do not have to be called, so we mark them
2699 -- as null to suppress the call.
2701 Set_Init_Proc (Rec_Type, Proc_Id);
2703 if List_Length (Body_Stmts) = 1
2705 -- We must skip SCIL nodes because they may have been added to this
2706 -- list by Insert_Actions.
2708 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
2709 then
2710 Set_Is_Null_Init_Proc (Proc_Id);
2711 end if;
2712 end Build_Init_Procedure;
2714 ---------------------------
2715 -- Build_Init_Statements --
2716 ---------------------------
2718 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2719 Checks : constant List_Id := New_List;
2720 Actions : List_Id := No_List;
2721 Counter_Id : Entity_Id := Empty;
2722 Comp_Loc : Source_Ptr;
2723 Decl : Node_Id;
2724 Has_POC : Boolean;
2725 Id : Entity_Id;
2726 Parent_Stmts : List_Id;
2727 Stmts : List_Id;
2728 Typ : Entity_Id;
2730 procedure Increment_Counter (Loc : Source_Ptr);
2731 -- Generate an "increment by one" statement for the current counter
2732 -- and append it to the list Stmts.
2734 procedure Make_Counter (Loc : Source_Ptr);
2735 -- Create a new counter for the current component list. The routine
2736 -- creates a new defining Id, adds an object declaration and sets
2737 -- the Id generator for the next variant.
2739 -----------------------
2740 -- Increment_Counter --
2741 -----------------------
2743 procedure Increment_Counter (Loc : Source_Ptr) is
2744 begin
2745 -- Generate:
2746 -- Counter := Counter + 1;
2748 Append_To (Stmts,
2749 Make_Assignment_Statement (Loc,
2750 Name => New_Occurrence_Of (Counter_Id, Loc),
2751 Expression =>
2752 Make_Op_Add (Loc,
2753 Left_Opnd => New_Occurrence_Of (Counter_Id, Loc),
2754 Right_Opnd => Make_Integer_Literal (Loc, 1))));
2755 end Increment_Counter;
2757 ------------------
2758 -- Make_Counter --
2759 ------------------
2761 procedure Make_Counter (Loc : Source_Ptr) is
2762 begin
2763 -- Increment the Id generator
2765 Counter := Counter + 1;
2767 -- Create the entity and declaration
2769 Counter_Id :=
2770 Make_Defining_Identifier (Loc,
2771 Chars => New_External_Name ('C', Counter));
2773 -- Generate:
2774 -- Cnn : Integer := 0;
2776 Append_To (Decls,
2777 Make_Object_Declaration (Loc,
2778 Defining_Identifier => Counter_Id,
2779 Object_Definition =>
2780 New_Occurrence_Of (Standard_Integer, Loc),
2781 Expression =>
2782 Make_Integer_Literal (Loc, 0)));
2783 end Make_Counter;
2785 -- Start of processing for Build_Init_Statements
2787 begin
2788 if Null_Present (Comp_List) then
2789 return New_List (Make_Null_Statement (Loc));
2790 end if;
2792 Parent_Stmts := New_List;
2793 Stmts := New_List;
2795 -- Loop through visible declarations of task types and protected
2796 -- types moving any expanded code from the spec to the body of the
2797 -- init procedure.
2799 if Is_Task_Record_Type (Rec_Type)
2800 or else Is_Protected_Record_Type (Rec_Type)
2801 then
2802 declare
2803 Decl : constant Node_Id :=
2804 Parent (Corresponding_Concurrent_Type (Rec_Type));
2805 Def : Node_Id;
2806 N1 : Node_Id;
2807 N2 : Node_Id;
2809 begin
2810 if Is_Task_Record_Type (Rec_Type) then
2811 Def := Task_Definition (Decl);
2812 else
2813 Def := Protected_Definition (Decl);
2814 end if;
2816 if Present (Def) then
2817 N1 := First (Visible_Declarations (Def));
2818 while Present (N1) loop
2819 N2 := N1;
2820 N1 := Next (N1);
2822 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2823 or else Nkind (N2) in N_Raise_xxx_Error
2824 or else Nkind (N2) = N_Procedure_Call_Statement
2825 then
2826 Append_To (Stmts,
2827 New_Copy_Tree (N2, New_Scope => Proc_Id));
2828 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2829 Analyze (N2);
2830 end if;
2831 end loop;
2832 end if;
2833 end;
2834 end if;
2836 -- Loop through components, skipping pragmas, in 2 steps. The first
2837 -- step deals with regular components. The second step deals with
2838 -- components that have per object constraints and no explicit
2839 -- initialization.
2841 Has_POC := False;
2843 -- First pass : regular components
2845 Decl := First_Non_Pragma (Component_Items (Comp_List));
2846 while Present (Decl) loop
2847 Comp_Loc := Sloc (Decl);
2848 Build_Record_Checks
2849 (Subtype_Indication (Component_Definition (Decl)), Checks);
2851 Id := Defining_Identifier (Decl);
2852 Typ := Etype (Id);
2854 -- Leave any processing of per-object constrained component for
2855 -- the second pass.
2857 if Has_Access_Constraint (Id) and then No (Expression (Decl)) then
2858 Has_POC := True;
2860 -- Regular component cases
2862 else
2863 -- In the context of the init proc, references to discriminants
2864 -- resolve to denote the discriminals: this is where we can
2865 -- freeze discriminant dependent component subtypes.
2867 if not Is_Frozen (Typ) then
2868 Append_List_To (Stmts, Freeze_Entity (Typ, N));
2869 end if;
2871 -- Explicit initialization
2873 if Present (Expression (Decl)) then
2874 if Is_CPP_Constructor_Call (Expression (Decl)) then
2875 Actions :=
2876 Build_Initialization_Call
2877 (Comp_Loc,
2878 Id_Ref =>
2879 Make_Selected_Component (Comp_Loc,
2880 Prefix =>
2881 Make_Identifier (Comp_Loc, Name_uInit),
2882 Selector_Name =>
2883 New_Occurrence_Of (Id, Comp_Loc)),
2884 Typ => Typ,
2885 In_Init_Proc => True,
2886 Enclos_Type => Rec_Type,
2887 Discr_Map => Discr_Map,
2888 Constructor_Ref => Expression (Decl));
2889 else
2890 Actions := Build_Assignment (Id, Expression (Decl));
2891 end if;
2893 -- CPU, Dispatching_Domain, Priority, and Secondary_Stack_Size
2894 -- components are filled in with the corresponding rep-item
2895 -- expression of the concurrent type (if any).
2897 elsif Ekind (Scope (Id)) = E_Record_Type
2898 and then Present (Corresponding_Concurrent_Type (Scope (Id)))
2899 and then Nam_In (Chars (Id), Name_uCPU,
2900 Name_uDispatching_Domain,
2901 Name_uPriority,
2902 Name_uSecondary_Stack_Size)
2903 then
2904 declare
2905 Exp : Node_Id;
2906 Nam : Name_Id;
2907 pragma Warnings (Off, Nam);
2908 Ritem : Node_Id;
2910 begin
2911 if Chars (Id) = Name_uCPU then
2912 Nam := Name_CPU;
2914 elsif Chars (Id) = Name_uDispatching_Domain then
2915 Nam := Name_Dispatching_Domain;
2917 elsif Chars (Id) = Name_uPriority then
2918 Nam := Name_Priority;
2920 elsif Chars (Id) = Name_uSecondary_Stack_Size then
2921 Nam := Name_Secondary_Stack_Size;
2922 end if;
2924 -- Get the Rep Item (aspect specification, attribute
2925 -- definition clause or pragma) of the corresponding
2926 -- concurrent type.
2928 Ritem :=
2929 Get_Rep_Item
2930 (Corresponding_Concurrent_Type (Scope (Id)),
2931 Nam,
2932 Check_Parents => False);
2934 if Present (Ritem) then
2936 -- Pragma case
2938 if Nkind (Ritem) = N_Pragma then
2939 Exp := First (Pragma_Argument_Associations (Ritem));
2941 if Nkind (Exp) = N_Pragma_Argument_Association then
2942 Exp := Expression (Exp);
2943 end if;
2945 -- Conversion for Priority expression
2947 if Nam = Name_Priority then
2948 if Pragma_Name (Ritem) = Name_Priority
2949 and then not GNAT_Mode
2950 then
2951 Exp := Convert_To (RTE (RE_Priority), Exp);
2952 else
2953 Exp :=
2954 Convert_To (RTE (RE_Any_Priority), Exp);
2955 end if;
2956 end if;
2958 -- Aspect/Attribute definition clause case
2960 else
2961 Exp := Expression (Ritem);
2963 -- Conversion for Priority expression
2965 if Nam = Name_Priority then
2966 if Chars (Ritem) = Name_Priority
2967 and then not GNAT_Mode
2968 then
2969 Exp := Convert_To (RTE (RE_Priority), Exp);
2970 else
2971 Exp :=
2972 Convert_To (RTE (RE_Any_Priority), Exp);
2973 end if;
2974 end if;
2975 end if;
2977 -- Conversion for Dispatching_Domain value
2979 if Nam = Name_Dispatching_Domain then
2980 Exp :=
2981 Unchecked_Convert_To
2982 (RTE (RE_Dispatching_Domain_Access), Exp);
2984 -- Conversion for Secondary_Stack_Size value
2986 elsif Nam = Name_Secondary_Stack_Size then
2987 Exp := Convert_To (RTE (RE_Size_Type), Exp);
2988 end if;
2990 Actions := Build_Assignment (Id, Exp);
2992 -- Nothing needed if no Rep Item
2994 else
2995 Actions := No_List;
2996 end if;
2997 end;
2999 -- Composite component with its own Init_Proc
3001 elsif not Is_Interface (Typ)
3002 and then Has_Non_Null_Base_Init_Proc (Typ)
3003 then
3004 Actions :=
3005 Build_Initialization_Call
3006 (Comp_Loc,
3007 Make_Selected_Component (Comp_Loc,
3008 Prefix =>
3009 Make_Identifier (Comp_Loc, Name_uInit),
3010 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3011 Typ,
3012 In_Init_Proc => True,
3013 Enclos_Type => Rec_Type,
3014 Discr_Map => Discr_Map);
3016 Clean_Task_Names (Typ, Proc_Id);
3018 -- Simple initialization
3020 elsif Component_Needs_Simple_Initialization (Typ) then
3021 Actions :=
3022 Build_Assignment
3023 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
3025 -- Nothing needed for this case
3027 else
3028 Actions := No_List;
3029 end if;
3031 if Present (Checks) then
3032 if Chars (Id) = Name_uParent then
3033 Append_List_To (Parent_Stmts, Checks);
3034 else
3035 Append_List_To (Stmts, Checks);
3036 end if;
3037 end if;
3039 if Present (Actions) then
3040 if Chars (Id) = Name_uParent then
3041 Append_List_To (Parent_Stmts, Actions);
3043 else
3044 Append_List_To (Stmts, Actions);
3046 -- Preserve initialization state in the current counter
3048 if Needs_Finalization (Typ) then
3049 if No (Counter_Id) then
3050 Make_Counter (Comp_Loc);
3051 end if;
3053 Increment_Counter (Comp_Loc);
3054 end if;
3055 end if;
3056 end if;
3057 end if;
3059 Next_Non_Pragma (Decl);
3060 end loop;
3062 -- The parent field must be initialized first because variable
3063 -- size components of the parent affect the location of all the
3064 -- new components.
3066 Prepend_List_To (Stmts, Parent_Stmts);
3068 -- Set up tasks and protected object support. This needs to be done
3069 -- before any component with a per-object access discriminant
3070 -- constraint, or any variant part (which may contain such
3071 -- components) is initialized, because the initialization of these
3072 -- components may reference the enclosing concurrent object.
3074 -- For a task record type, add the task create call and calls to bind
3075 -- any interrupt (signal) entries.
3077 if Is_Task_Record_Type (Rec_Type) then
3079 -- In the case of the restricted run time the ATCB has already
3080 -- been preallocated.
3082 if Restricted_Profile then
3083 Append_To (Stmts,
3084 Make_Assignment_Statement (Loc,
3085 Name =>
3086 Make_Selected_Component (Loc,
3087 Prefix => Make_Identifier (Loc, Name_uInit),
3088 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
3089 Expression =>
3090 Make_Attribute_Reference (Loc,
3091 Prefix =>
3092 Make_Selected_Component (Loc,
3093 Prefix => Make_Identifier (Loc, Name_uInit),
3094 Selector_Name => Make_Identifier (Loc, Name_uATCB)),
3095 Attribute_Name => Name_Unchecked_Access)));
3096 end if;
3098 Append_To (Stmts, Make_Task_Create_Call (Rec_Type));
3100 declare
3101 Task_Type : constant Entity_Id :=
3102 Corresponding_Concurrent_Type (Rec_Type);
3103 Task_Decl : constant Node_Id := Parent (Task_Type);
3104 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
3105 Decl_Loc : Source_Ptr;
3106 Ent : Entity_Id;
3107 Vis_Decl : Node_Id;
3109 begin
3110 if Present (Task_Def) then
3111 Vis_Decl := First (Visible_Declarations (Task_Def));
3112 while Present (Vis_Decl) loop
3113 Decl_Loc := Sloc (Vis_Decl);
3115 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
3116 if Get_Attribute_Id (Chars (Vis_Decl)) =
3117 Attribute_Address
3118 then
3119 Ent := Entity (Name (Vis_Decl));
3121 if Ekind (Ent) = E_Entry then
3122 Append_To (Stmts,
3123 Make_Procedure_Call_Statement (Decl_Loc,
3124 Name =>
3125 New_Occurrence_Of (RTE (
3126 RE_Bind_Interrupt_To_Entry), Decl_Loc),
3127 Parameter_Associations => New_List (
3128 Make_Selected_Component (Decl_Loc,
3129 Prefix =>
3130 Make_Identifier (Decl_Loc, Name_uInit),
3131 Selector_Name =>
3132 Make_Identifier
3133 (Decl_Loc, Name_uTask_Id)),
3134 Entry_Index_Expression
3135 (Decl_Loc, Ent, Empty, Task_Type),
3136 Expression (Vis_Decl))));
3137 end if;
3138 end if;
3139 end if;
3141 Next (Vis_Decl);
3142 end loop;
3143 end if;
3144 end;
3145 end if;
3147 -- For a protected type, add statements generated by
3148 -- Make_Initialize_Protection.
3150 if Is_Protected_Record_Type (Rec_Type) then
3151 Append_List_To (Stmts,
3152 Make_Initialize_Protection (Rec_Type));
3153 end if;
3155 -- Second pass: components with per-object constraints
3157 if Has_POC then
3158 Decl := First_Non_Pragma (Component_Items (Comp_List));
3159 while Present (Decl) loop
3160 Comp_Loc := Sloc (Decl);
3161 Id := Defining_Identifier (Decl);
3162 Typ := Etype (Id);
3164 if Has_Access_Constraint (Id)
3165 and then No (Expression (Decl))
3166 then
3167 if Has_Non_Null_Base_Init_Proc (Typ) then
3168 Append_List_To (Stmts,
3169 Build_Initialization_Call (Comp_Loc,
3170 Make_Selected_Component (Comp_Loc,
3171 Prefix =>
3172 Make_Identifier (Comp_Loc, Name_uInit),
3173 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3174 Typ,
3175 In_Init_Proc => True,
3176 Enclos_Type => Rec_Type,
3177 Discr_Map => Discr_Map));
3179 Clean_Task_Names (Typ, Proc_Id);
3181 -- Preserve initialization state in the current counter
3183 if Needs_Finalization (Typ) then
3184 if No (Counter_Id) then
3185 Make_Counter (Comp_Loc);
3186 end if;
3188 Increment_Counter (Comp_Loc);
3189 end if;
3191 elsif Component_Needs_Simple_Initialization (Typ) then
3192 Append_List_To (Stmts,
3193 Build_Assignment
3194 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
3195 end if;
3196 end if;
3198 Next_Non_Pragma (Decl);
3199 end loop;
3200 end if;
3202 -- Process the variant part
3204 if Present (Variant_Part (Comp_List)) then
3205 declare
3206 Variant_Alts : constant List_Id := New_List;
3207 Var_Loc : Source_Ptr := No_Location;
3208 Variant : Node_Id;
3210 begin
3211 Variant :=
3212 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3213 while Present (Variant) loop
3214 Var_Loc := Sloc (Variant);
3215 Append_To (Variant_Alts,
3216 Make_Case_Statement_Alternative (Var_Loc,
3217 Discrete_Choices =>
3218 New_Copy_List (Discrete_Choices (Variant)),
3219 Statements =>
3220 Build_Init_Statements (Component_List (Variant))));
3221 Next_Non_Pragma (Variant);
3222 end loop;
3224 -- The expression of the case statement which is a reference
3225 -- to one of the discriminants is replaced by the appropriate
3226 -- formal parameter of the initialization procedure.
3228 Append_To (Stmts,
3229 Make_Case_Statement (Var_Loc,
3230 Expression =>
3231 New_Occurrence_Of (Discriminal (
3232 Entity (Name (Variant_Part (Comp_List)))), Var_Loc),
3233 Alternatives => Variant_Alts));
3234 end;
3235 end if;
3237 -- If no initializations when generated for component declarations
3238 -- corresponding to this Stmts, append a null statement to Stmts to
3239 -- to make it a valid Ada tree.
3241 if Is_Empty_List (Stmts) then
3242 Append (Make_Null_Statement (Loc), Stmts);
3243 end if;
3245 return Stmts;
3247 exception
3248 when RE_Not_Available =>
3249 return Empty_List;
3250 end Build_Init_Statements;
3252 -------------------------
3253 -- Build_Record_Checks --
3254 -------------------------
3256 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
3257 Subtype_Mark_Id : Entity_Id;
3259 procedure Constrain_Array
3260 (SI : Node_Id;
3261 Check_List : List_Id);
3262 -- Apply a list of index constraints to an unconstrained array type.
3263 -- The first parameter is the entity for the resulting subtype.
3264 -- Check_List is a list to which the check actions are appended.
3266 ---------------------
3267 -- Constrain_Array --
3268 ---------------------
3270 procedure Constrain_Array
3271 (SI : Node_Id;
3272 Check_List : List_Id)
3274 C : constant Node_Id := Constraint (SI);
3275 Number_Of_Constraints : Nat := 0;
3276 Index : Node_Id;
3277 S, T : Entity_Id;
3279 procedure Constrain_Index
3280 (Index : Node_Id;
3281 S : Node_Id;
3282 Check_List : List_Id);
3283 -- Process an index constraint in a constrained array declaration.
3284 -- The constraint can be either a subtype name or a range with or
3285 -- without an explicit subtype mark. Index is the corresponding
3286 -- index of the unconstrained array. S is the range expression.
3287 -- Check_List is a list to which the check actions are appended.
3289 ---------------------
3290 -- Constrain_Index --
3291 ---------------------
3293 procedure Constrain_Index
3294 (Index : Node_Id;
3295 S : Node_Id;
3296 Check_List : List_Id)
3298 T : constant Entity_Id := Etype (Index);
3300 begin
3301 if Nkind (S) = N_Range then
3302 Process_Range_Expr_In_Decl (S, T, Check_List => Check_List);
3303 end if;
3304 end Constrain_Index;
3306 -- Start of processing for Constrain_Array
3308 begin
3309 T := Entity (Subtype_Mark (SI));
3311 if Is_Access_Type (T) then
3312 T := Designated_Type (T);
3313 end if;
3315 S := First (Constraints (C));
3316 while Present (S) loop
3317 Number_Of_Constraints := Number_Of_Constraints + 1;
3318 Next (S);
3319 end loop;
3321 -- In either case, the index constraint must provide a discrete
3322 -- range for each index of the array type and the type of each
3323 -- discrete range must be the same as that of the corresponding
3324 -- index. (RM 3.6.1)
3326 S := First (Constraints (C));
3327 Index := First_Index (T);
3328 Analyze (Index);
3330 -- Apply constraints to each index type
3332 for J in 1 .. Number_Of_Constraints loop
3333 Constrain_Index (Index, S, Check_List);
3334 Next (Index);
3335 Next (S);
3336 end loop;
3337 end Constrain_Array;
3339 -- Start of processing for Build_Record_Checks
3341 begin
3342 if Nkind (S) = N_Subtype_Indication then
3343 Find_Type (Subtype_Mark (S));
3344 Subtype_Mark_Id := Entity (Subtype_Mark (S));
3346 -- Remaining processing depends on type
3348 case Ekind (Subtype_Mark_Id) is
3349 when Array_Kind =>
3350 Constrain_Array (S, Check_List);
3352 when others =>
3353 null;
3354 end case;
3355 end if;
3356 end Build_Record_Checks;
3358 -------------------------------------------
3359 -- Component_Needs_Simple_Initialization --
3360 -------------------------------------------
3362 function Component_Needs_Simple_Initialization
3363 (T : Entity_Id) return Boolean
3365 begin
3366 return
3367 Needs_Simple_Initialization (T)
3368 and then not Is_RTE (T, RE_Tag)
3370 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
3372 and then not Is_RTE (T, RE_Interface_Tag);
3373 end Component_Needs_Simple_Initialization;
3375 --------------------------------------
3376 -- Parent_Subtype_Renaming_Discrims --
3377 --------------------------------------
3379 function Parent_Subtype_Renaming_Discrims return Boolean is
3380 De : Entity_Id;
3381 Dp : Entity_Id;
3383 begin
3384 if Base_Type (Rec_Ent) /= Rec_Ent then
3385 return False;
3386 end if;
3388 if Etype (Rec_Ent) = Rec_Ent
3389 or else not Has_Discriminants (Rec_Ent)
3390 or else Is_Constrained (Rec_Ent)
3391 or else Is_Tagged_Type (Rec_Ent)
3392 then
3393 return False;
3394 end if;
3396 -- If there are no explicit stored discriminants we have inherited
3397 -- the root type discriminants so far, so no renamings occurred.
3399 if First_Discriminant (Rec_Ent) =
3400 First_Stored_Discriminant (Rec_Ent)
3401 then
3402 return False;
3403 end if;
3405 -- Check if we have done some trivial renaming of the parent
3406 -- discriminants, i.e. something like
3408 -- type DT (X1, X2: int) is new PT (X1, X2);
3410 De := First_Discriminant (Rec_Ent);
3411 Dp := First_Discriminant (Etype (Rec_Ent));
3412 while Present (De) loop
3413 pragma Assert (Present (Dp));
3415 if Corresponding_Discriminant (De) /= Dp then
3416 return True;
3417 end if;
3419 Next_Discriminant (De);
3420 Next_Discriminant (Dp);
3421 end loop;
3423 return Present (Dp);
3424 end Parent_Subtype_Renaming_Discrims;
3426 ------------------------
3427 -- Requires_Init_Proc --
3428 ------------------------
3430 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3431 Comp_Decl : Node_Id;
3432 Id : Entity_Id;
3433 Typ : Entity_Id;
3435 begin
3436 -- Definitely do not need one if specifically suppressed
3438 if Initialization_Suppressed (Rec_Id) then
3439 return False;
3440 end if;
3442 -- If it is a type derived from a type with unknown discriminants,
3443 -- we cannot build an initialization procedure for it.
3445 if Has_Unknown_Discriminants (Rec_Id)
3446 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3447 then
3448 return False;
3449 end if;
3451 -- Otherwise we need to generate an initialization procedure if
3452 -- Is_CPP_Class is False and at least one of the following applies:
3454 -- 1. Discriminants are present, since they need to be initialized
3455 -- with the appropriate discriminant constraint expressions.
3456 -- However, the discriminant of an unchecked union does not
3457 -- count, since the discriminant is not present.
3459 -- 2. The type is a tagged type, since the implicit Tag component
3460 -- needs to be initialized with a pointer to the dispatch table.
3462 -- 3. The type contains tasks
3464 -- 4. One or more components has an initial value
3466 -- 5. One or more components is for a type which itself requires
3467 -- an initialization procedure.
3469 -- 6. One or more components is a type that requires simple
3470 -- initialization (see Needs_Simple_Initialization), except
3471 -- that types Tag and Interface_Tag are excluded, since fields
3472 -- of these types are initialized by other means.
3474 -- 7. The type is the record type built for a task type (since at
3475 -- the very least, Create_Task must be called)
3477 -- 8. The type is the record type built for a protected type (since
3478 -- at least Initialize_Protection must be called)
3480 -- 9. The type is marked as a public entity. The reason we add this
3481 -- case (even if none of the above apply) is to properly handle
3482 -- Initialize_Scalars. If a package is compiled without an IS
3483 -- pragma, and the client is compiled with an IS pragma, then
3484 -- the client will think an initialization procedure is present
3485 -- and call it, when in fact no such procedure is required, but
3486 -- since the call is generated, there had better be a routine
3487 -- at the other end of the call, even if it does nothing).
3489 -- Note: the reason we exclude the CPP_Class case is because in this
3490 -- case the initialization is performed by the C++ constructors, and
3491 -- the IP is built by Set_CPP_Constructors.
3493 if Is_CPP_Class (Rec_Id) then
3494 return False;
3496 elsif Is_Interface (Rec_Id) then
3497 return False;
3499 elsif (Has_Discriminants (Rec_Id)
3500 and then not Is_Unchecked_Union (Rec_Id))
3501 or else Is_Tagged_Type (Rec_Id)
3502 or else Is_Concurrent_Record_Type (Rec_Id)
3503 or else Has_Task (Rec_Id)
3504 then
3505 return True;
3506 end if;
3508 Id := First_Component (Rec_Id);
3509 while Present (Id) loop
3510 Comp_Decl := Parent (Id);
3511 Typ := Etype (Id);
3513 if Present (Expression (Comp_Decl))
3514 or else Has_Non_Null_Base_Init_Proc (Typ)
3515 or else Component_Needs_Simple_Initialization (Typ)
3516 then
3517 return True;
3518 end if;
3520 Next_Component (Id);
3521 end loop;
3523 -- As explained above, a record initialization procedure is needed
3524 -- for public types in case Initialize_Scalars applies to a client.
3525 -- However, such a procedure is not needed in the case where either
3526 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3527 -- applies. No_Initialize_Scalars excludes the possibility of using
3528 -- Initialize_Scalars in any partition, and No_Default_Initialization
3529 -- implies that no initialization should ever be done for objects of
3530 -- the type, so is incompatible with Initialize_Scalars.
3532 if not Restriction_Active (No_Initialize_Scalars)
3533 and then not Restriction_Active (No_Default_Initialization)
3534 and then Is_Public (Rec_Id)
3535 then
3536 return True;
3537 end if;
3539 return False;
3540 end Requires_Init_Proc;
3542 -- Start of processing for Build_Record_Init_Proc
3544 begin
3545 Rec_Type := Defining_Identifier (N);
3547 -- This may be full declaration of a private type, in which case
3548 -- the visible entity is a record, and the private entity has been
3549 -- exchanged with it in the private part of the current package.
3550 -- The initialization procedure is built for the record type, which
3551 -- is retrievable from the private entity.
3553 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3554 Rec_Type := Underlying_Type (Rec_Type);
3555 end if;
3557 -- If we have a variant record with restriction No_Implicit_Conditionals
3558 -- in effect, then we skip building the procedure. This is safe because
3559 -- if we can see the restriction, so can any caller, calls to initialize
3560 -- such records are not allowed for variant records if this restriction
3561 -- is active.
3563 if Has_Variant_Part (Rec_Type)
3564 and then Restriction_Active (No_Implicit_Conditionals)
3565 then
3566 return;
3567 end if;
3569 -- If there are discriminants, build the discriminant map to replace
3570 -- discriminants by their discriminals in complex bound expressions.
3571 -- These only arise for the corresponding records of synchronized types.
3573 if Is_Concurrent_Record_Type (Rec_Type)
3574 and then Has_Discriminants (Rec_Type)
3575 then
3576 declare
3577 Disc : Entity_Id;
3578 begin
3579 Disc := First_Discriminant (Rec_Type);
3580 while Present (Disc) loop
3581 Append_Elmt (Disc, Discr_Map);
3582 Append_Elmt (Discriminal (Disc), Discr_Map);
3583 Next_Discriminant (Disc);
3584 end loop;
3585 end;
3586 end if;
3588 -- Derived types that have no type extension can use the initialization
3589 -- procedure of their parent and do not need a procedure of their own.
3590 -- This is only correct if there are no representation clauses for the
3591 -- type or its parent, and if the parent has in fact been frozen so
3592 -- that its initialization procedure exists.
3594 if Is_Derived_Type (Rec_Type)
3595 and then not Is_Tagged_Type (Rec_Type)
3596 and then not Is_Unchecked_Union (Rec_Type)
3597 and then not Has_New_Non_Standard_Rep (Rec_Type)
3598 and then not Parent_Subtype_Renaming_Discrims
3599 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3600 then
3601 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3603 -- Otherwise if we need an initialization procedure, then build one,
3604 -- mark it as public and inlinable and as having a completion.
3606 elsif Requires_Init_Proc (Rec_Type)
3607 or else Is_Unchecked_Union (Rec_Type)
3608 then
3609 Proc_Id :=
3610 Make_Defining_Identifier (Loc,
3611 Chars => Make_Init_Proc_Name (Rec_Type));
3613 -- If No_Default_Initialization restriction is active, then we don't
3614 -- want to build an init_proc, but we need to mark that an init_proc
3615 -- would be needed if this restriction was not active (so that we can
3616 -- detect attempts to call it), so set a dummy init_proc in place.
3618 if Restriction_Active (No_Default_Initialization) then
3619 Set_Init_Proc (Rec_Type, Proc_Id);
3620 return;
3621 end if;
3623 Build_Offset_To_Top_Functions;
3624 Build_CPP_Init_Procedure;
3625 Build_Init_Procedure;
3627 Set_Is_Public (Proc_Id, Is_Public (Rec_Ent));
3628 Set_Is_Internal (Proc_Id);
3629 Set_Has_Completion (Proc_Id);
3631 if not Debug_Generated_Code then
3632 Set_Debug_Info_Off (Proc_Id);
3633 end if;
3635 Set_Is_Inlined (Proc_Id, Inline_Init_Proc (Rec_Type));
3637 -- Do not build an aggregate if Modify_Tree_For_C, this isn't
3638 -- needed and may generate early references to non frozen types
3639 -- since we expand aggregate much more systematically.
3641 if Modify_Tree_For_C then
3642 return;
3643 end if;
3645 declare
3646 Agg : constant Node_Id :=
3647 Build_Equivalent_Record_Aggregate (Rec_Type);
3649 procedure Collect_Itypes (Comp : Node_Id);
3650 -- Generate references to itypes in the aggregate, because
3651 -- the first use of the aggregate may be in a nested scope.
3653 --------------------
3654 -- Collect_Itypes --
3655 --------------------
3657 procedure Collect_Itypes (Comp : Node_Id) is
3658 Ref : Node_Id;
3659 Sub_Aggr : Node_Id;
3660 Typ : constant Entity_Id := Etype (Comp);
3662 begin
3663 if Is_Array_Type (Typ) and then Is_Itype (Typ) then
3664 Ref := Make_Itype_Reference (Loc);
3665 Set_Itype (Ref, Typ);
3666 Append_Freeze_Action (Rec_Type, Ref);
3668 Ref := Make_Itype_Reference (Loc);
3669 Set_Itype (Ref, Etype (First_Index (Typ)));
3670 Append_Freeze_Action (Rec_Type, Ref);
3672 -- Recurse on nested arrays
3674 Sub_Aggr := First (Expressions (Comp));
3675 while Present (Sub_Aggr) loop
3676 Collect_Itypes (Sub_Aggr);
3677 Next (Sub_Aggr);
3678 end loop;
3679 end if;
3680 end Collect_Itypes;
3682 begin
3683 -- If there is a static initialization aggregate for the type,
3684 -- generate itype references for the types of its (sub)components,
3685 -- to prevent out-of-scope errors in the resulting tree.
3686 -- The aggregate may have been rewritten as a Raise node, in which
3687 -- case there are no relevant itypes.
3689 if Present (Agg) and then Nkind (Agg) = N_Aggregate then
3690 Set_Static_Initialization (Proc_Id, Agg);
3692 declare
3693 Comp : Node_Id;
3694 begin
3695 Comp := First (Component_Associations (Agg));
3696 while Present (Comp) loop
3697 Collect_Itypes (Expression (Comp));
3698 Next (Comp);
3699 end loop;
3700 end;
3701 end if;
3702 end;
3703 end if;
3704 end Build_Record_Init_Proc;
3706 ----------------------------
3707 -- Build_Slice_Assignment --
3708 ----------------------------
3710 -- Generates the following subprogram:
3712 -- procedure Assign
3713 -- (Source, Target : Array_Type,
3714 -- Left_Lo, Left_Hi : Index;
3715 -- Right_Lo, Right_Hi : Index;
3716 -- Rev : Boolean)
3717 -- is
3718 -- Li1 : Index;
3719 -- Ri1 : Index;
3721 -- begin
3723 -- if Left_Hi < Left_Lo then
3724 -- return;
3725 -- end if;
3727 -- if Rev then
3728 -- Li1 := Left_Hi;
3729 -- Ri1 := Right_Hi;
3730 -- else
3731 -- Li1 := Left_Lo;
3732 -- Ri1 := Right_Lo;
3733 -- end if;
3735 -- loop
3736 -- Target (Li1) := Source (Ri1);
3738 -- if Rev then
3739 -- exit when Li1 = Left_Lo;
3740 -- Li1 := Index'pred (Li1);
3741 -- Ri1 := Index'pred (Ri1);
3742 -- else
3743 -- exit when Li1 = Left_Hi;
3744 -- Li1 := Index'succ (Li1);
3745 -- Ri1 := Index'succ (Ri1);
3746 -- end if;
3747 -- end loop;
3748 -- end Assign;
3750 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3751 Loc : constant Source_Ptr := Sloc (Typ);
3752 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3754 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
3755 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
3756 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
3757 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
3758 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
3759 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
3760 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
3761 -- Formal parameters of procedure
3763 Proc_Name : constant Entity_Id :=
3764 Make_Defining_Identifier (Loc,
3765 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3767 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3768 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3769 -- Subscripts for left and right sides
3771 Decls : List_Id;
3772 Loops : Node_Id;
3773 Stats : List_Id;
3775 begin
3776 -- Build declarations for indexes
3778 Decls := New_List;
3780 Append_To (Decls,
3781 Make_Object_Declaration (Loc,
3782 Defining_Identifier => Lnn,
3783 Object_Definition =>
3784 New_Occurrence_Of (Index, Loc)));
3786 Append_To (Decls,
3787 Make_Object_Declaration (Loc,
3788 Defining_Identifier => Rnn,
3789 Object_Definition =>
3790 New_Occurrence_Of (Index, Loc)));
3792 Stats := New_List;
3794 -- Build test for empty slice case
3796 Append_To (Stats,
3797 Make_If_Statement (Loc,
3798 Condition =>
3799 Make_Op_Lt (Loc,
3800 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
3801 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3802 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
3804 -- Build initializations for indexes
3806 declare
3807 F_Init : constant List_Id := New_List;
3808 B_Init : constant List_Id := New_List;
3810 begin
3811 Append_To (F_Init,
3812 Make_Assignment_Statement (Loc,
3813 Name => New_Occurrence_Of (Lnn, Loc),
3814 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3816 Append_To (F_Init,
3817 Make_Assignment_Statement (Loc,
3818 Name => New_Occurrence_Of (Rnn, Loc),
3819 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3821 Append_To (B_Init,
3822 Make_Assignment_Statement (Loc,
3823 Name => New_Occurrence_Of (Lnn, Loc),
3824 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3826 Append_To (B_Init,
3827 Make_Assignment_Statement (Loc,
3828 Name => New_Occurrence_Of (Rnn, Loc),
3829 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3831 Append_To (Stats,
3832 Make_If_Statement (Loc,
3833 Condition => New_Occurrence_Of (Rev, Loc),
3834 Then_Statements => B_Init,
3835 Else_Statements => F_Init));
3836 end;
3838 -- Now construct the assignment statement
3840 Loops :=
3841 Make_Loop_Statement (Loc,
3842 Statements => New_List (
3843 Make_Assignment_Statement (Loc,
3844 Name =>
3845 Make_Indexed_Component (Loc,
3846 Prefix => New_Occurrence_Of (Larray, Loc),
3847 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3848 Expression =>
3849 Make_Indexed_Component (Loc,
3850 Prefix => New_Occurrence_Of (Rarray, Loc),
3851 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3852 End_Label => Empty);
3854 -- Build the exit condition and increment/decrement statements
3856 declare
3857 F_Ass : constant List_Id := New_List;
3858 B_Ass : constant List_Id := New_List;
3860 begin
3861 Append_To (F_Ass,
3862 Make_Exit_Statement (Loc,
3863 Condition =>
3864 Make_Op_Eq (Loc,
3865 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3866 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3868 Append_To (F_Ass,
3869 Make_Assignment_Statement (Loc,
3870 Name => New_Occurrence_Of (Lnn, Loc),
3871 Expression =>
3872 Make_Attribute_Reference (Loc,
3873 Prefix =>
3874 New_Occurrence_Of (Index, Loc),
3875 Attribute_Name => Name_Succ,
3876 Expressions => New_List (
3877 New_Occurrence_Of (Lnn, Loc)))));
3879 Append_To (F_Ass,
3880 Make_Assignment_Statement (Loc,
3881 Name => New_Occurrence_Of (Rnn, Loc),
3882 Expression =>
3883 Make_Attribute_Reference (Loc,
3884 Prefix =>
3885 New_Occurrence_Of (Index, Loc),
3886 Attribute_Name => Name_Succ,
3887 Expressions => New_List (
3888 New_Occurrence_Of (Rnn, Loc)))));
3890 Append_To (B_Ass,
3891 Make_Exit_Statement (Loc,
3892 Condition =>
3893 Make_Op_Eq (Loc,
3894 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3895 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3897 Append_To (B_Ass,
3898 Make_Assignment_Statement (Loc,
3899 Name => New_Occurrence_Of (Lnn, Loc),
3900 Expression =>
3901 Make_Attribute_Reference (Loc,
3902 Prefix =>
3903 New_Occurrence_Of (Index, Loc),
3904 Attribute_Name => Name_Pred,
3905 Expressions => New_List (
3906 New_Occurrence_Of (Lnn, Loc)))));
3908 Append_To (B_Ass,
3909 Make_Assignment_Statement (Loc,
3910 Name => New_Occurrence_Of (Rnn, Loc),
3911 Expression =>
3912 Make_Attribute_Reference (Loc,
3913 Prefix =>
3914 New_Occurrence_Of (Index, Loc),
3915 Attribute_Name => Name_Pred,
3916 Expressions => New_List (
3917 New_Occurrence_Of (Rnn, Loc)))));
3919 Append_To (Statements (Loops),
3920 Make_If_Statement (Loc,
3921 Condition => New_Occurrence_Of (Rev, Loc),
3922 Then_Statements => B_Ass,
3923 Else_Statements => F_Ass));
3924 end;
3926 Append_To (Stats, Loops);
3928 declare
3929 Spec : Node_Id;
3930 Formals : List_Id := New_List;
3932 begin
3933 Formals := New_List (
3934 Make_Parameter_Specification (Loc,
3935 Defining_Identifier => Larray,
3936 Out_Present => True,
3937 Parameter_Type =>
3938 New_Occurrence_Of (Base_Type (Typ), Loc)),
3940 Make_Parameter_Specification (Loc,
3941 Defining_Identifier => Rarray,
3942 Parameter_Type =>
3943 New_Occurrence_Of (Base_Type (Typ), Loc)),
3945 Make_Parameter_Specification (Loc,
3946 Defining_Identifier => Left_Lo,
3947 Parameter_Type =>
3948 New_Occurrence_Of (Index, Loc)),
3950 Make_Parameter_Specification (Loc,
3951 Defining_Identifier => Left_Hi,
3952 Parameter_Type =>
3953 New_Occurrence_Of (Index, Loc)),
3955 Make_Parameter_Specification (Loc,
3956 Defining_Identifier => Right_Lo,
3957 Parameter_Type =>
3958 New_Occurrence_Of (Index, Loc)),
3960 Make_Parameter_Specification (Loc,
3961 Defining_Identifier => Right_Hi,
3962 Parameter_Type =>
3963 New_Occurrence_Of (Index, Loc)));
3965 Append_To (Formals,
3966 Make_Parameter_Specification (Loc,
3967 Defining_Identifier => Rev,
3968 Parameter_Type =>
3969 New_Occurrence_Of (Standard_Boolean, Loc)));
3971 Spec :=
3972 Make_Procedure_Specification (Loc,
3973 Defining_Unit_Name => Proc_Name,
3974 Parameter_Specifications => Formals);
3976 Discard_Node (
3977 Make_Subprogram_Body (Loc,
3978 Specification => Spec,
3979 Declarations => Decls,
3980 Handled_Statement_Sequence =>
3981 Make_Handled_Sequence_Of_Statements (Loc,
3982 Statements => Stats)));
3983 end;
3985 Set_TSS (Typ, Proc_Name);
3986 Set_Is_Pure (Proc_Name);
3987 end Build_Slice_Assignment;
3989 -----------------------------
3990 -- Build_Untagged_Equality --
3991 -----------------------------
3993 procedure Build_Untagged_Equality (Typ : Entity_Id) is
3994 Build_Eq : Boolean;
3995 Comp : Entity_Id;
3996 Decl : Node_Id;
3997 Op : Entity_Id;
3998 Prim : Elmt_Id;
3999 Eq_Op : Entity_Id;
4001 function User_Defined_Eq (T : Entity_Id) return Entity_Id;
4002 -- Check whether the type T has a user-defined primitive equality. If so
4003 -- return it, else return Empty. If true for a component of Typ, we have
4004 -- to build the primitive equality for it.
4006 ---------------------
4007 -- User_Defined_Eq --
4008 ---------------------
4010 function User_Defined_Eq (T : Entity_Id) return Entity_Id is
4011 Prim : Elmt_Id;
4012 Op : Entity_Id;
4014 begin
4015 Op := TSS (T, TSS_Composite_Equality);
4017 if Present (Op) then
4018 return Op;
4019 end if;
4021 Prim := First_Elmt (Collect_Primitive_Operations (T));
4022 while Present (Prim) loop
4023 Op := Node (Prim);
4025 if Chars (Op) = Name_Op_Eq
4026 and then Etype (Op) = Standard_Boolean
4027 and then Etype (First_Formal (Op)) = T
4028 and then Etype (Next_Formal (First_Formal (Op))) = T
4029 then
4030 return Op;
4031 end if;
4033 Next_Elmt (Prim);
4034 end loop;
4036 return Empty;
4037 end User_Defined_Eq;
4039 -- Start of processing for Build_Untagged_Equality
4041 begin
4042 -- If a record component has a primitive equality operation, we must
4043 -- build the corresponding one for the current type.
4045 Build_Eq := False;
4046 Comp := First_Component (Typ);
4047 while Present (Comp) loop
4048 if Is_Record_Type (Etype (Comp))
4049 and then Present (User_Defined_Eq (Etype (Comp)))
4050 then
4051 Build_Eq := True;
4052 end if;
4054 Next_Component (Comp);
4055 end loop;
4057 -- If there is a user-defined equality for the type, we do not create
4058 -- the implicit one.
4060 Prim := First_Elmt (Collect_Primitive_Operations (Typ));
4061 Eq_Op := Empty;
4062 while Present (Prim) loop
4063 if Chars (Node (Prim)) = Name_Op_Eq
4064 and then Comes_From_Source (Node (Prim))
4066 -- Don't we also need to check formal types and return type as in
4067 -- User_Defined_Eq above???
4069 then
4070 Eq_Op := Node (Prim);
4071 Build_Eq := False;
4072 exit;
4073 end if;
4075 Next_Elmt (Prim);
4076 end loop;
4078 -- If the type is derived, inherit the operation, if present, from the
4079 -- parent type. It may have been declared after the type derivation. If
4080 -- the parent type itself is derived, it may have inherited an operation
4081 -- that has itself been overridden, so update its alias and related
4082 -- flags. Ditto for inequality.
4084 if No (Eq_Op) and then Is_Derived_Type (Typ) then
4085 Prim := First_Elmt (Collect_Primitive_Operations (Etype (Typ)));
4086 while Present (Prim) loop
4087 if Chars (Node (Prim)) = Name_Op_Eq then
4088 Copy_TSS (Node (Prim), Typ);
4089 Build_Eq := False;
4091 declare
4092 Op : constant Entity_Id := User_Defined_Eq (Typ);
4093 Eq_Op : constant Entity_Id := Node (Prim);
4094 NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
4096 begin
4097 if Present (Op) then
4098 Set_Alias (Op, Eq_Op);
4099 Set_Is_Abstract_Subprogram
4100 (Op, Is_Abstract_Subprogram (Eq_Op));
4102 if Chars (Next_Entity (Op)) = Name_Op_Ne then
4103 Set_Is_Abstract_Subprogram
4104 (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
4105 end if;
4106 end if;
4107 end;
4109 exit;
4110 end if;
4112 Next_Elmt (Prim);
4113 end loop;
4114 end if;
4116 -- If not inherited and not user-defined, build body as for a type with
4117 -- tagged components.
4119 if Build_Eq then
4120 Decl :=
4121 Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
4122 Op := Defining_Entity (Decl);
4123 Set_TSS (Typ, Op);
4124 Set_Is_Pure (Op);
4126 if Is_Library_Level_Entity (Typ) then
4127 Set_Is_Public (Op);
4128 end if;
4129 end if;
4130 end Build_Untagged_Equality;
4132 -----------------------------------
4133 -- Build_Variant_Record_Equality --
4134 -----------------------------------
4136 -- Generates:
4138 -- function _Equality (X, Y : T) return Boolean is
4139 -- begin
4140 -- -- Compare discriminants
4142 -- if X.D1 /= Y.D1 or else X.D2 /= Y.D2 or else ... then
4143 -- return False;
4144 -- end if;
4146 -- -- Compare components
4148 -- if X.C1 /= Y.C1 or else X.C2 /= Y.C2 or else ... then
4149 -- return False;
4150 -- end if;
4152 -- -- Compare variant part
4154 -- case X.D1 is
4155 -- when V1 =>
4156 -- if X.C2 /= Y.C2 or else X.C3 /= Y.C3 or else ... then
4157 -- return False;
4158 -- end if;
4159 -- ...
4160 -- when Vn =>
4161 -- if X.Cn /= Y.Cn or else ... then
4162 -- return False;
4163 -- end if;
4164 -- end case;
4166 -- return True;
4167 -- end _Equality;
4169 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
4170 Loc : constant Source_Ptr := Sloc (Typ);
4172 F : constant Entity_Id :=
4173 Make_Defining_Identifier (Loc,
4174 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
4176 X : constant Entity_Id := Make_Defining_Identifier (Loc, Name_X);
4177 Y : constant Entity_Id := Make_Defining_Identifier (Loc, Name_Y);
4179 Def : constant Node_Id := Parent (Typ);
4180 Comps : constant Node_Id := Component_List (Type_Definition (Def));
4181 Stmts : constant List_Id := New_List;
4182 Pspecs : constant List_Id := New_List;
4184 begin
4185 -- If we have a variant record with restriction No_Implicit_Conditionals
4186 -- in effect, then we skip building the procedure. This is safe because
4187 -- if we can see the restriction, so can any caller, calls to equality
4188 -- test routines are not allowed for variant records if this restriction
4189 -- is active.
4191 if Restriction_Active (No_Implicit_Conditionals) then
4192 return;
4193 end if;
4195 -- Derived Unchecked_Union types no longer inherit the equality function
4196 -- of their parent.
4198 if Is_Derived_Type (Typ)
4199 and then not Is_Unchecked_Union (Typ)
4200 and then not Has_New_Non_Standard_Rep (Typ)
4201 then
4202 declare
4203 Parent_Eq : constant Entity_Id :=
4204 TSS (Root_Type (Typ), TSS_Composite_Equality);
4205 begin
4206 if Present (Parent_Eq) then
4207 Copy_TSS (Parent_Eq, Typ);
4208 return;
4209 end if;
4210 end;
4211 end if;
4213 Discard_Node (
4214 Make_Subprogram_Body (Loc,
4215 Specification =>
4216 Make_Function_Specification (Loc,
4217 Defining_Unit_Name => F,
4218 Parameter_Specifications => Pspecs,
4219 Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
4220 Declarations => New_List,
4221 Handled_Statement_Sequence =>
4222 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
4224 Append_To (Pspecs,
4225 Make_Parameter_Specification (Loc,
4226 Defining_Identifier => X,
4227 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4229 Append_To (Pspecs,
4230 Make_Parameter_Specification (Loc,
4231 Defining_Identifier => Y,
4232 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4234 -- Unchecked_Unions require additional machinery to support equality.
4235 -- Two extra parameters (A and B) are added to the equality function
4236 -- parameter list for each discriminant of the type, in order to
4237 -- capture the inferred values of the discriminants in equality calls.
4238 -- The names of the parameters match the names of the corresponding
4239 -- discriminant, with an added suffix.
4241 if Is_Unchecked_Union (Typ) then
4242 declare
4243 Discr : Entity_Id;
4244 Discr_Type : Entity_Id;
4245 A, B : Entity_Id;
4246 New_Discrs : Elist_Id;
4248 begin
4249 New_Discrs := New_Elmt_List;
4251 Discr := First_Discriminant (Typ);
4252 while Present (Discr) loop
4253 Discr_Type := Etype (Discr);
4254 A := Make_Defining_Identifier (Loc,
4255 Chars => New_External_Name (Chars (Discr), 'A'));
4257 B := Make_Defining_Identifier (Loc,
4258 Chars => New_External_Name (Chars (Discr), 'B'));
4260 -- Add new parameters to the parameter list
4262 Append_To (Pspecs,
4263 Make_Parameter_Specification (Loc,
4264 Defining_Identifier => A,
4265 Parameter_Type =>
4266 New_Occurrence_Of (Discr_Type, Loc)));
4268 Append_To (Pspecs,
4269 Make_Parameter_Specification (Loc,
4270 Defining_Identifier => B,
4271 Parameter_Type =>
4272 New_Occurrence_Of (Discr_Type, Loc)));
4274 Append_Elmt (A, New_Discrs);
4276 -- Generate the following code to compare each of the inferred
4277 -- discriminants:
4279 -- if a /= b then
4280 -- return False;
4281 -- end if;
4283 Append_To (Stmts,
4284 Make_If_Statement (Loc,
4285 Condition =>
4286 Make_Op_Ne (Loc,
4287 Left_Opnd => New_Occurrence_Of (A, Loc),
4288 Right_Opnd => New_Occurrence_Of (B, Loc)),
4289 Then_Statements => New_List (
4290 Make_Simple_Return_Statement (Loc,
4291 Expression =>
4292 New_Occurrence_Of (Standard_False, Loc)))));
4293 Next_Discriminant (Discr);
4294 end loop;
4296 -- Generate component-by-component comparison. Note that we must
4297 -- propagate the inferred discriminants formals to act as
4298 -- the case statement switch. Their value is added when an
4299 -- equality call on unchecked unions is expanded.
4301 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps, New_Discrs));
4302 end;
4304 -- Normal case (not unchecked union)
4306 else
4307 Append_To (Stmts,
4308 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
4309 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
4310 end if;
4312 Append_To (Stmts,
4313 Make_Simple_Return_Statement (Loc,
4314 Expression => New_Occurrence_Of (Standard_True, Loc)));
4316 Set_TSS (Typ, F);
4317 Set_Is_Pure (F);
4319 if not Debug_Generated_Code then
4320 Set_Debug_Info_Off (F);
4321 end if;
4322 end Build_Variant_Record_Equality;
4324 -----------------------------
4325 -- Check_Stream_Attributes --
4326 -----------------------------
4328 procedure Check_Stream_Attributes (Typ : Entity_Id) is
4329 Comp : Entity_Id;
4330 Par_Read : constant Boolean :=
4331 Stream_Attribute_Available (Typ, TSS_Stream_Read)
4332 and then not Has_Specified_Stream_Read (Typ);
4333 Par_Write : constant Boolean :=
4334 Stream_Attribute_Available (Typ, TSS_Stream_Write)
4335 and then not Has_Specified_Stream_Write (Typ);
4337 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4338 -- Check that Comp has a user-specified Nam stream attribute
4340 ----------------
4341 -- Check_Attr --
4342 ----------------
4344 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4345 begin
4346 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4347 Error_Msg_Name_1 := Nam;
4348 Error_Msg_N
4349 ("|component& in limited extension must have% attribute", Comp);
4350 end if;
4351 end Check_Attr;
4353 -- Start of processing for Check_Stream_Attributes
4355 begin
4356 if Par_Read or else Par_Write then
4357 Comp := First_Component (Typ);
4358 while Present (Comp) loop
4359 if Comes_From_Source (Comp)
4360 and then Original_Record_Component (Comp) = Comp
4361 and then Is_Limited_Type (Etype (Comp))
4362 then
4363 if Par_Read then
4364 Check_Attr (Name_Read, TSS_Stream_Read);
4365 end if;
4367 if Par_Write then
4368 Check_Attr (Name_Write, TSS_Stream_Write);
4369 end if;
4370 end if;
4372 Next_Component (Comp);
4373 end loop;
4374 end if;
4375 end Check_Stream_Attributes;
4377 ----------------------
4378 -- Clean_Task_Names --
4379 ----------------------
4381 procedure Clean_Task_Names
4382 (Typ : Entity_Id;
4383 Proc_Id : Entity_Id)
4385 begin
4386 if Has_Task (Typ)
4387 and then not Restriction_Active (No_Implicit_Heap_Allocations)
4388 and then not Global_Discard_Names
4389 and then Tagged_Type_Expansion
4390 then
4391 Set_Uses_Sec_Stack (Proc_Id);
4392 end if;
4393 end Clean_Task_Names;
4395 ------------------------------
4396 -- Expand_Freeze_Array_Type --
4397 ------------------------------
4399 procedure Expand_Freeze_Array_Type (N : Node_Id) is
4400 Typ : constant Entity_Id := Entity (N);
4401 Base : constant Entity_Id := Base_Type (Typ);
4402 Comp_Typ : constant Entity_Id := Component_Type (Typ);
4404 begin
4405 if not Is_Bit_Packed_Array (Typ) then
4407 -- If the component contains tasks, so does the array type. This may
4408 -- not be indicated in the array type because the component may have
4409 -- been a private type at the point of definition. Same if component
4410 -- type is controlled or contains protected objects.
4412 Propagate_Concurrent_Flags (Base, Comp_Typ);
4413 Set_Has_Controlled_Component
4414 (Base, Has_Controlled_Component (Comp_Typ)
4415 or else Is_Controlled (Comp_Typ));
4417 if No (Init_Proc (Base)) then
4419 -- If this is an anonymous array created for a declaration with
4420 -- an initial value, its init_proc will never be called. The
4421 -- initial value itself may have been expanded into assignments,
4422 -- in which case the object declaration is carries the
4423 -- No_Initialization flag.
4425 if Is_Itype (Base)
4426 and then Nkind (Associated_Node_For_Itype (Base)) =
4427 N_Object_Declaration
4428 and then
4429 (Present (Expression (Associated_Node_For_Itype (Base)))
4430 or else No_Initialization (Associated_Node_For_Itype (Base)))
4431 then
4432 null;
4434 -- We do not need an init proc for string or wide [wide] string,
4435 -- since the only time these need initialization in normalize or
4436 -- initialize scalars mode, and these types are treated specially
4437 -- and do not need initialization procedures.
4439 elsif Is_Standard_String_Type (Base) then
4440 null;
4442 -- Otherwise we have to build an init proc for the subtype
4444 else
4445 Build_Array_Init_Proc (Base, N);
4446 end if;
4447 end if;
4449 if Typ = Base and then Has_Controlled_Component (Base) then
4450 Build_Controlling_Procs (Base);
4452 if not Is_Limited_Type (Comp_Typ)
4453 and then Number_Dimensions (Typ) = 1
4454 then
4455 Build_Slice_Assignment (Typ);
4456 end if;
4457 end if;
4459 -- For packed case, default initialization, except if the component type
4460 -- is itself a packed structure with an initialization procedure, or
4461 -- initialize/normalize scalars active, and we have a base type, or the
4462 -- type is public, because in that case a client might specify
4463 -- Normalize_Scalars and there better be a public Init_Proc for it.
4465 elsif (Present (Init_Proc (Component_Type (Base)))
4466 and then No (Base_Init_Proc (Base)))
4467 or else (Init_Or_Norm_Scalars and then Base = Typ)
4468 or else Is_Public (Typ)
4469 then
4470 Build_Array_Init_Proc (Base, N);
4471 end if;
4472 end Expand_Freeze_Array_Type;
4474 -----------------------------------
4475 -- Expand_Freeze_Class_Wide_Type --
4476 -----------------------------------
4478 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id) is
4479 function Is_C_Derivation (Typ : Entity_Id) return Boolean;
4480 -- Given a type, determine whether it is derived from a C or C++ root
4482 ---------------------
4483 -- Is_C_Derivation --
4484 ---------------------
4486 function Is_C_Derivation (Typ : Entity_Id) return Boolean is
4487 T : Entity_Id;
4489 begin
4490 T := Typ;
4491 loop
4492 if Is_CPP_Class (T)
4493 or else Convention (T) = Convention_C
4494 or else Convention (T) = Convention_CPP
4495 then
4496 return True;
4497 end if;
4499 exit when T = Etype (T);
4501 T := Etype (T);
4502 end loop;
4504 return False;
4505 end Is_C_Derivation;
4507 -- Local variables
4509 Typ : constant Entity_Id := Entity (N);
4510 Root : constant Entity_Id := Root_Type (Typ);
4512 -- Start of processing for Expand_Freeze_Class_Wide_Type
4514 begin
4515 -- Certain run-time configurations and targets do not provide support
4516 -- for controlled types.
4518 if Restriction_Active (No_Finalization) then
4519 return;
4521 -- Do not create TSS routine Finalize_Address when dispatching calls are
4522 -- disabled since the core of the routine is a dispatching call.
4524 elsif Restriction_Active (No_Dispatching_Calls) then
4525 return;
4527 -- Do not create TSS routine Finalize_Address for concurrent class-wide
4528 -- types. Ignore C, C++, CIL and Java types since it is assumed that the
4529 -- non-Ada side will handle their destruction.
4531 elsif Is_Concurrent_Type (Root)
4532 or else Is_C_Derivation (Root)
4533 or else Convention (Typ) = Convention_CPP
4534 then
4535 return;
4537 -- Do not create TSS routine Finalize_Address when compiling in CodePeer
4538 -- mode since the routine contains an Unchecked_Conversion.
4540 elsif CodePeer_Mode then
4541 return;
4542 end if;
4544 -- Create the body of TSS primitive Finalize_Address. This automatically
4545 -- sets the TSS entry for the class-wide type.
4547 Make_Finalize_Address_Body (Typ);
4548 end Expand_Freeze_Class_Wide_Type;
4550 ------------------------------------
4551 -- Expand_Freeze_Enumeration_Type --
4552 ------------------------------------
4554 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
4555 Typ : constant Entity_Id := Entity (N);
4556 Loc : constant Source_Ptr := Sloc (Typ);
4558 Arr : Entity_Id;
4559 Ent : Entity_Id;
4560 Fent : Entity_Id;
4561 Is_Contiguous : Boolean;
4562 Ityp : Entity_Id;
4563 Last_Repval : Uint;
4564 Lst : List_Id;
4565 Num : Nat;
4566 Pos_Expr : Node_Id;
4568 Func : Entity_Id;
4569 pragma Warnings (Off, Func);
4571 begin
4572 -- Various optimizations possible if given representation is contiguous
4574 Is_Contiguous := True;
4576 Ent := First_Literal (Typ);
4577 Last_Repval := Enumeration_Rep (Ent);
4579 Next_Literal (Ent);
4580 while Present (Ent) loop
4581 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
4582 Is_Contiguous := False;
4583 exit;
4584 else
4585 Last_Repval := Enumeration_Rep (Ent);
4586 end if;
4588 Next_Literal (Ent);
4589 end loop;
4591 if Is_Contiguous then
4592 Set_Has_Contiguous_Rep (Typ);
4593 Ent := First_Literal (Typ);
4594 Num := 1;
4595 Lst := New_List (New_Occurrence_Of (Ent, Sloc (Ent)));
4597 else
4598 -- Build list of literal references
4600 Lst := New_List;
4601 Num := 0;
4603 Ent := First_Literal (Typ);
4604 while Present (Ent) loop
4605 Append_To (Lst, New_Occurrence_Of (Ent, Sloc (Ent)));
4606 Num := Num + 1;
4607 Next_Literal (Ent);
4608 end loop;
4609 end if;
4611 -- Now build an array declaration
4613 -- typA : array (Natural range 0 .. num - 1) of ctype :=
4614 -- (v, v, v, v, v, ....)
4616 -- where ctype is the corresponding integer type. If the representation
4617 -- is contiguous, we only keep the first literal, which provides the
4618 -- offset for Pos_To_Rep computations.
4620 Arr :=
4621 Make_Defining_Identifier (Loc,
4622 Chars => New_External_Name (Chars (Typ), 'A'));
4624 Append_Freeze_Action (Typ,
4625 Make_Object_Declaration (Loc,
4626 Defining_Identifier => Arr,
4627 Constant_Present => True,
4629 Object_Definition =>
4630 Make_Constrained_Array_Definition (Loc,
4631 Discrete_Subtype_Definitions => New_List (
4632 Make_Subtype_Indication (Loc,
4633 Subtype_Mark => New_Occurrence_Of (Standard_Natural, Loc),
4634 Constraint =>
4635 Make_Range_Constraint (Loc,
4636 Range_Expression =>
4637 Make_Range (Loc,
4638 Low_Bound =>
4639 Make_Integer_Literal (Loc, 0),
4640 High_Bound =>
4641 Make_Integer_Literal (Loc, Num - 1))))),
4643 Component_Definition =>
4644 Make_Component_Definition (Loc,
4645 Aliased_Present => False,
4646 Subtype_Indication => New_Occurrence_Of (Typ, Loc))),
4648 Expression =>
4649 Make_Aggregate (Loc,
4650 Expressions => Lst)));
4652 Set_Enum_Pos_To_Rep (Typ, Arr);
4654 -- Now we build the function that converts representation values to
4655 -- position values. This function has the form:
4657 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
4658 -- begin
4659 -- case ityp!(A) is
4660 -- when enum-lit'Enum_Rep => return posval;
4661 -- when enum-lit'Enum_Rep => return posval;
4662 -- ...
4663 -- when others =>
4664 -- [raise Constraint_Error when F "invalid data"]
4665 -- return -1;
4666 -- end case;
4667 -- end;
4669 -- Note: the F parameter determines whether the others case (no valid
4670 -- representation) raises Constraint_Error or returns a unique value
4671 -- of minus one. The latter case is used, e.g. in 'Valid code.
4673 -- Note: the reason we use Enum_Rep values in the case here is to avoid
4674 -- the code generator making inappropriate assumptions about the range
4675 -- of the values in the case where the value is invalid. ityp is a
4676 -- signed or unsigned integer type of appropriate width.
4678 -- Note: if exceptions are not supported, then we suppress the raise
4679 -- and return -1 unconditionally (this is an erroneous program in any
4680 -- case and there is no obligation to raise Constraint_Error here). We
4681 -- also do this if pragma Restrictions (No_Exceptions) is active.
4683 -- Is this right??? What about No_Exception_Propagation???
4685 -- Representations are signed
4687 if Enumeration_Rep (First_Literal (Typ)) < 0 then
4689 -- The underlying type is signed. Reset the Is_Unsigned_Type
4690 -- explicitly, because it might have been inherited from
4691 -- parent type.
4693 Set_Is_Unsigned_Type (Typ, False);
4695 if Esize (Typ) <= Standard_Integer_Size then
4696 Ityp := Standard_Integer;
4697 else
4698 Ityp := Universal_Integer;
4699 end if;
4701 -- Representations are unsigned
4703 else
4704 if Esize (Typ) <= Standard_Integer_Size then
4705 Ityp := RTE (RE_Unsigned);
4706 else
4707 Ityp := RTE (RE_Long_Long_Unsigned);
4708 end if;
4709 end if;
4711 -- The body of the function is a case statement. First collect case
4712 -- alternatives, or optimize the contiguous case.
4714 Lst := New_List;
4716 -- If representation is contiguous, Pos is computed by subtracting
4717 -- the representation of the first literal.
4719 if Is_Contiguous then
4720 Ent := First_Literal (Typ);
4722 if Enumeration_Rep (Ent) = Last_Repval then
4724 -- Another special case: for a single literal, Pos is zero
4726 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
4728 else
4729 Pos_Expr :=
4730 Convert_To (Standard_Integer,
4731 Make_Op_Subtract (Loc,
4732 Left_Opnd =>
4733 Unchecked_Convert_To
4734 (Ityp, Make_Identifier (Loc, Name_uA)),
4735 Right_Opnd =>
4736 Make_Integer_Literal (Loc,
4737 Intval => Enumeration_Rep (First_Literal (Typ)))));
4738 end if;
4740 Append_To (Lst,
4741 Make_Case_Statement_Alternative (Loc,
4742 Discrete_Choices => New_List (
4743 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
4744 Low_Bound =>
4745 Make_Integer_Literal (Loc,
4746 Intval => Enumeration_Rep (Ent)),
4747 High_Bound =>
4748 Make_Integer_Literal (Loc, Intval => Last_Repval))),
4750 Statements => New_List (
4751 Make_Simple_Return_Statement (Loc,
4752 Expression => Pos_Expr))));
4754 else
4755 Ent := First_Literal (Typ);
4756 while Present (Ent) loop
4757 Append_To (Lst,
4758 Make_Case_Statement_Alternative (Loc,
4759 Discrete_Choices => New_List (
4760 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
4761 Intval => Enumeration_Rep (Ent))),
4763 Statements => New_List (
4764 Make_Simple_Return_Statement (Loc,
4765 Expression =>
4766 Make_Integer_Literal (Loc,
4767 Intval => Enumeration_Pos (Ent))))));
4769 Next_Literal (Ent);
4770 end loop;
4771 end if;
4773 -- In normal mode, add the others clause with the test.
4774 -- If Predicates_Ignored is True, validity checks do not apply to
4775 -- the subtype.
4777 if not No_Exception_Handlers_Set
4778 and then not Predicates_Ignored (Typ)
4779 then
4780 Append_To (Lst,
4781 Make_Case_Statement_Alternative (Loc,
4782 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4783 Statements => New_List (
4784 Make_Raise_Constraint_Error (Loc,
4785 Condition => Make_Identifier (Loc, Name_uF),
4786 Reason => CE_Invalid_Data),
4787 Make_Simple_Return_Statement (Loc,
4788 Expression => Make_Integer_Literal (Loc, -1)))));
4790 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
4791 -- active then return -1 (we cannot usefully raise Constraint_Error in
4792 -- this case). See description above for further details.
4794 else
4795 Append_To (Lst,
4796 Make_Case_Statement_Alternative (Loc,
4797 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
4798 Statements => New_List (
4799 Make_Simple_Return_Statement (Loc,
4800 Expression => Make_Integer_Literal (Loc, -1)))));
4801 end if;
4803 -- Now we can build the function body
4805 Fent :=
4806 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
4808 Func :=
4809 Make_Subprogram_Body (Loc,
4810 Specification =>
4811 Make_Function_Specification (Loc,
4812 Defining_Unit_Name => Fent,
4813 Parameter_Specifications => New_List (
4814 Make_Parameter_Specification (Loc,
4815 Defining_Identifier =>
4816 Make_Defining_Identifier (Loc, Name_uA),
4817 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
4818 Make_Parameter_Specification (Loc,
4819 Defining_Identifier =>
4820 Make_Defining_Identifier (Loc, Name_uF),
4821 Parameter_Type =>
4822 New_Occurrence_Of (Standard_Boolean, Loc))),
4824 Result_Definition => New_Occurrence_Of (Standard_Integer, Loc)),
4826 Declarations => Empty_List,
4828 Handled_Statement_Sequence =>
4829 Make_Handled_Sequence_Of_Statements (Loc,
4830 Statements => New_List (
4831 Make_Case_Statement (Loc,
4832 Expression =>
4833 Unchecked_Convert_To
4834 (Ityp, Make_Identifier (Loc, Name_uA)),
4835 Alternatives => Lst))));
4837 Set_TSS (Typ, Fent);
4839 -- Set Pure flag (it will be reset if the current context is not Pure).
4840 -- We also pretend there was a pragma Pure_Function so that for purposes
4841 -- of optimization and constant-folding, we will consider the function
4842 -- Pure even if we are not in a Pure context).
4844 Set_Is_Pure (Fent);
4845 Set_Has_Pragma_Pure_Function (Fent);
4847 -- Unless we are in -gnatD mode, where we are debugging generated code,
4848 -- this is an internal entity for which we don't need debug info.
4850 if not Debug_Generated_Code then
4851 Set_Debug_Info_Off (Fent);
4852 end if;
4854 Set_Is_Inlined (Fent);
4856 exception
4857 when RE_Not_Available =>
4858 return;
4859 end Expand_Freeze_Enumeration_Type;
4861 -------------------------------
4862 -- Expand_Freeze_Record_Type --
4863 -------------------------------
4865 procedure Expand_Freeze_Record_Type (N : Node_Id) is
4866 Typ : constant Node_Id := Entity (N);
4867 Typ_Decl : constant Node_Id := Parent (Typ);
4869 Comp : Entity_Id;
4870 Comp_Typ : Entity_Id;
4871 Predef_List : List_Id;
4873 Wrapper_Decl_List : List_Id := No_List;
4874 Wrapper_Body_List : List_Id := No_List;
4876 Renamed_Eq : Node_Id := Empty;
4877 -- Defining unit name for the predefined equality function in the case
4878 -- where the type has a primitive operation that is a renaming of
4879 -- predefined equality (but only if there is also an overriding
4880 -- user-defined equality function). Used to pass this entity from
4881 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
4883 -- Start of processing for Expand_Freeze_Record_Type
4885 begin
4886 -- Build discriminant checking functions if not a derived type (for
4887 -- derived types that are not tagged types, always use the discriminant
4888 -- checking functions of the parent type). However, for untagged types
4889 -- the derivation may have taken place before the parent was frozen, so
4890 -- we copy explicitly the discriminant checking functions from the
4891 -- parent into the components of the derived type.
4893 if not Is_Derived_Type (Typ)
4894 or else Has_New_Non_Standard_Rep (Typ)
4895 or else Is_Tagged_Type (Typ)
4896 then
4897 Build_Discr_Checking_Funcs (Typ_Decl);
4899 elsif Is_Derived_Type (Typ)
4900 and then not Is_Tagged_Type (Typ)
4902 -- If we have a derived Unchecked_Union, we do not inherit the
4903 -- discriminant checking functions from the parent type since the
4904 -- discriminants are non existent.
4906 and then not Is_Unchecked_Union (Typ)
4907 and then Has_Discriminants (Typ)
4908 then
4909 declare
4910 Old_Comp : Entity_Id;
4912 begin
4913 Old_Comp :=
4914 First_Component (Base_Type (Underlying_Type (Etype (Typ))));
4915 Comp := First_Component (Typ);
4916 while Present (Comp) loop
4917 if Ekind (Comp) = E_Component
4918 and then Chars (Comp) = Chars (Old_Comp)
4919 then
4920 Set_Discriminant_Checking_Func
4921 (Comp, Discriminant_Checking_Func (Old_Comp));
4922 end if;
4924 Next_Component (Old_Comp);
4925 Next_Component (Comp);
4926 end loop;
4927 end;
4928 end if;
4930 if Is_Derived_Type (Typ)
4931 and then Is_Limited_Type (Typ)
4932 and then Is_Tagged_Type (Typ)
4933 then
4934 Check_Stream_Attributes (Typ);
4935 end if;
4937 -- Update task, protected, and controlled component flags, because some
4938 -- of the component types may have been private at the point of the
4939 -- record declaration. Detect anonymous access-to-controlled components.
4941 Comp := First_Component (Typ);
4942 while Present (Comp) loop
4943 Comp_Typ := Etype (Comp);
4945 Propagate_Concurrent_Flags (Typ, Comp_Typ);
4947 -- Do not set Has_Controlled_Component on a class-wide equivalent
4948 -- type. See Make_CW_Equivalent_Type.
4950 if not Is_Class_Wide_Equivalent_Type (Typ)
4951 and then
4952 (Has_Controlled_Component (Comp_Typ)
4953 or else (Chars (Comp) /= Name_uParent
4954 and then Is_Controlled (Comp_Typ)))
4955 then
4956 Set_Has_Controlled_Component (Typ);
4957 end if;
4959 Next_Component (Comp);
4960 end loop;
4962 -- Handle constructors of untagged CPP_Class types
4964 if not Is_Tagged_Type (Typ) and then Is_CPP_Class (Typ) then
4965 Set_CPP_Constructors (Typ);
4966 end if;
4968 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
4969 -- for regular tagged types as well as for Ada types deriving from a C++
4970 -- Class, but not for tagged types directly corresponding to C++ classes
4971 -- In the later case we assume that it is created in the C++ side and we
4972 -- just use it.
4974 if Is_Tagged_Type (Typ) then
4976 -- Add the _Tag component
4978 if Underlying_Type (Etype (Typ)) = Typ then
4979 Expand_Tagged_Root (Typ);
4980 end if;
4982 if Is_CPP_Class (Typ) then
4983 Set_All_DT_Position (Typ);
4985 -- Create the tag entities with a minimum decoration
4987 if Tagged_Type_Expansion then
4988 Append_Freeze_Actions (Typ, Make_Tags (Typ));
4989 end if;
4991 Set_CPP_Constructors (Typ);
4993 else
4994 if not Building_Static_DT (Typ) then
4996 -- Usually inherited primitives are not delayed but the first
4997 -- Ada extension of a CPP_Class is an exception since the
4998 -- address of the inherited subprogram has to be inserted in
4999 -- the new Ada Dispatch Table and this is a freezing action.
5001 -- Similarly, if this is an inherited operation whose parent is
5002 -- not frozen yet, it is not in the DT of the parent, and we
5003 -- generate an explicit freeze node for the inherited operation
5004 -- so it is properly inserted in the DT of the current type.
5006 declare
5007 Elmt : Elmt_Id;
5008 Subp : Entity_Id;
5010 begin
5011 Elmt := First_Elmt (Primitive_Operations (Typ));
5012 while Present (Elmt) loop
5013 Subp := Node (Elmt);
5015 if Present (Alias (Subp)) then
5016 if Is_CPP_Class (Etype (Typ)) then
5017 Set_Has_Delayed_Freeze (Subp);
5019 elsif Has_Delayed_Freeze (Alias (Subp))
5020 and then not Is_Frozen (Alias (Subp))
5021 then
5022 Set_Is_Frozen (Subp, False);
5023 Set_Has_Delayed_Freeze (Subp);
5024 end if;
5025 end if;
5027 Next_Elmt (Elmt);
5028 end loop;
5029 end;
5030 end if;
5032 -- Unfreeze momentarily the type to add the predefined primitives
5033 -- operations. The reason we unfreeze is so that these predefined
5034 -- operations will indeed end up as primitive operations (which
5035 -- must be before the freeze point).
5037 Set_Is_Frozen (Typ, False);
5039 -- Do not add the spec of predefined primitives in case of
5040 -- CPP tagged type derivations that have convention CPP.
5042 if Is_CPP_Class (Root_Type (Typ))
5043 and then Convention (Typ) = Convention_CPP
5044 then
5045 null;
5047 -- Do not add the spec of the predefined primitives if we are
5048 -- compiling under restriction No_Dispatching_Calls.
5050 elsif not Restriction_Active (No_Dispatching_Calls) then
5051 Make_Predefined_Primitive_Specs (Typ, Predef_List, Renamed_Eq);
5052 Insert_List_Before_And_Analyze (N, Predef_List);
5053 end if;
5055 -- Ada 2005 (AI-391): For a nonabstract null extension, create
5056 -- wrapper functions for each nonoverridden inherited function
5057 -- with a controlling result of the type. The wrapper for such
5058 -- a function returns an extension aggregate that invokes the
5059 -- parent function.
5061 if Ada_Version >= Ada_2005
5062 and then not Is_Abstract_Type (Typ)
5063 and then Is_Null_Extension (Typ)
5064 then
5065 Make_Controlling_Function_Wrappers
5066 (Typ, Wrapper_Decl_List, Wrapper_Body_List);
5067 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
5068 end if;
5070 -- Ada 2005 (AI-251): For a nonabstract type extension, build
5071 -- null procedure declarations for each set of homographic null
5072 -- procedures that are inherited from interface types but not
5073 -- overridden. This is done to ensure that the dispatch table
5074 -- entry associated with such null primitives are properly filled.
5076 if Ada_Version >= Ada_2005
5077 and then Etype (Typ) /= Typ
5078 and then not Is_Abstract_Type (Typ)
5079 and then Has_Interfaces (Typ)
5080 then
5081 Insert_Actions (N, Make_Null_Procedure_Specs (Typ));
5082 end if;
5084 Set_Is_Frozen (Typ);
5086 if not Is_Derived_Type (Typ)
5087 or else Is_Tagged_Type (Etype (Typ))
5088 then
5089 Set_All_DT_Position (Typ);
5091 -- If this is a type derived from an untagged private type whose
5092 -- full view is tagged, the type is marked tagged for layout
5093 -- reasons, but it has no dispatch table.
5095 elsif Is_Derived_Type (Typ)
5096 and then Is_Private_Type (Etype (Typ))
5097 and then not Is_Tagged_Type (Etype (Typ))
5098 then
5099 return;
5100 end if;
5102 -- Create and decorate the tags. Suppress their creation when
5103 -- not Tagged_Type_Expansion because the dispatching mechanism is
5104 -- handled internally by the virtual target.
5106 if Tagged_Type_Expansion then
5107 Append_Freeze_Actions (Typ, Make_Tags (Typ));
5109 -- Generate dispatch table of locally defined tagged type.
5110 -- Dispatch tables of library level tagged types are built
5111 -- later (see Analyze_Declarations).
5113 if not Building_Static_DT (Typ) then
5114 Append_Freeze_Actions (Typ, Make_DT (Typ));
5115 end if;
5116 end if;
5118 -- If the type has unknown discriminants, propagate dispatching
5119 -- information to its underlying record view, which does not get
5120 -- its own dispatch table.
5122 if Is_Derived_Type (Typ)
5123 and then Has_Unknown_Discriminants (Typ)
5124 and then Present (Underlying_Record_View (Typ))
5125 then
5126 declare
5127 Rep : constant Entity_Id := Underlying_Record_View (Typ);
5128 begin
5129 Set_Access_Disp_Table
5130 (Rep, Access_Disp_Table (Typ));
5131 Set_Dispatch_Table_Wrappers
5132 (Rep, Dispatch_Table_Wrappers (Typ));
5133 Set_Direct_Primitive_Operations
5134 (Rep, Direct_Primitive_Operations (Typ));
5135 end;
5136 end if;
5138 -- Make sure that the primitives Initialize, Adjust and Finalize
5139 -- are Frozen before other TSS subprograms. We don't want them
5140 -- Frozen inside.
5142 if Is_Controlled (Typ) then
5143 if not Is_Limited_Type (Typ) then
5144 Append_Freeze_Actions (Typ,
5145 Freeze_Entity (Find_Prim_Op (Typ, Name_Adjust), Typ));
5146 end if;
5148 Append_Freeze_Actions (Typ,
5149 Freeze_Entity (Find_Prim_Op (Typ, Name_Initialize), Typ));
5151 Append_Freeze_Actions (Typ,
5152 Freeze_Entity (Find_Prim_Op (Typ, Name_Finalize), Typ));
5153 end if;
5155 -- Freeze rest of primitive operations. There is no need to handle
5156 -- the predefined primitives if we are compiling under restriction
5157 -- No_Dispatching_Calls.
5159 if not Restriction_Active (No_Dispatching_Calls) then
5160 Append_Freeze_Actions (Typ, Predefined_Primitive_Freeze (Typ));
5161 end if;
5162 end if;
5164 -- In the untagged case, ever since Ada 83 an equality function must
5165 -- be provided for variant records that are not unchecked unions.
5166 -- In Ada 2012 the equality function composes, and thus must be built
5167 -- explicitly just as for tagged records.
5169 elsif Has_Discriminants (Typ)
5170 and then not Is_Limited_Type (Typ)
5171 then
5172 declare
5173 Comps : constant Node_Id :=
5174 Component_List (Type_Definition (Typ_Decl));
5175 begin
5176 if Present (Comps)
5177 and then Present (Variant_Part (Comps))
5178 then
5179 Build_Variant_Record_Equality (Typ);
5180 end if;
5181 end;
5183 -- Otherwise create primitive equality operation (AI05-0123)
5185 -- This is done unconditionally to ensure that tools can be linked
5186 -- properly with user programs compiled with older language versions.
5187 -- In addition, this is needed because "=" composes for bounded strings
5188 -- in all language versions (see Exp_Ch4.Expand_Composite_Equality).
5190 elsif Comes_From_Source (Typ)
5191 and then Convention (Typ) = Convention_Ada
5192 and then not Is_Limited_Type (Typ)
5193 then
5194 Build_Untagged_Equality (Typ);
5195 end if;
5197 -- Before building the record initialization procedure, if we are
5198 -- dealing with a concurrent record value type, then we must go through
5199 -- the discriminants, exchanging discriminals between the concurrent
5200 -- type and the concurrent record value type. See the section "Handling
5201 -- of Discriminants" in the Einfo spec for details.
5203 if Is_Concurrent_Record_Type (Typ)
5204 and then Has_Discriminants (Typ)
5205 then
5206 declare
5207 Ctyp : constant Entity_Id :=
5208 Corresponding_Concurrent_Type (Typ);
5209 Conc_Discr : Entity_Id;
5210 Rec_Discr : Entity_Id;
5211 Temp : Entity_Id;
5213 begin
5214 Conc_Discr := First_Discriminant (Ctyp);
5215 Rec_Discr := First_Discriminant (Typ);
5216 while Present (Conc_Discr) loop
5217 Temp := Discriminal (Conc_Discr);
5218 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
5219 Set_Discriminal (Rec_Discr, Temp);
5221 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
5222 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
5224 Next_Discriminant (Conc_Discr);
5225 Next_Discriminant (Rec_Discr);
5226 end loop;
5227 end;
5228 end if;
5230 if Has_Controlled_Component (Typ) then
5231 Build_Controlling_Procs (Typ);
5232 end if;
5234 Adjust_Discriminants (Typ);
5236 -- Do not need init for interfaces on virtual targets since they're
5237 -- abstract.
5239 if Tagged_Type_Expansion or else not Is_Interface (Typ) then
5240 Build_Record_Init_Proc (Typ_Decl, Typ);
5241 end if;
5243 -- For tagged type that are not interfaces, build bodies of primitive
5244 -- operations. Note: do this after building the record initialization
5245 -- procedure, since the primitive operations may need the initialization
5246 -- routine. There is no need to add predefined primitives of interfaces
5247 -- because all their predefined primitives are abstract.
5249 if Is_Tagged_Type (Typ) and then not Is_Interface (Typ) then
5251 -- Do not add the body of predefined primitives in case of CPP tagged
5252 -- type derivations that have convention CPP.
5254 if Is_CPP_Class (Root_Type (Typ))
5255 and then Convention (Typ) = Convention_CPP
5256 then
5257 null;
5259 -- Do not add the body of the predefined primitives if we are
5260 -- compiling under restriction No_Dispatching_Calls or if we are
5261 -- compiling a CPP tagged type.
5263 elsif not Restriction_Active (No_Dispatching_Calls) then
5265 -- Create the body of TSS primitive Finalize_Address. This must
5266 -- be done before the bodies of all predefined primitives are
5267 -- created. If Typ is limited, Stream_Input and Stream_Read may
5268 -- produce build-in-place allocations and for those the expander
5269 -- needs Finalize_Address.
5271 Make_Finalize_Address_Body (Typ);
5272 Predef_List := Predefined_Primitive_Bodies (Typ, Renamed_Eq);
5273 Append_Freeze_Actions (Typ, Predef_List);
5274 end if;
5276 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
5277 -- inherited functions, then add their bodies to the freeze actions.
5279 if Present (Wrapper_Body_List) then
5280 Append_Freeze_Actions (Typ, Wrapper_Body_List);
5281 end if;
5283 -- Create extra formals for the primitive operations of the type.
5284 -- This must be done before analyzing the body of the initialization
5285 -- procedure, because a self-referential type might call one of these
5286 -- primitives in the body of the init_proc itself.
5288 declare
5289 Elmt : Elmt_Id;
5290 Subp : Entity_Id;
5292 begin
5293 Elmt := First_Elmt (Primitive_Operations (Typ));
5294 while Present (Elmt) loop
5295 Subp := Node (Elmt);
5296 if not Has_Foreign_Convention (Subp)
5297 and then not Is_Predefined_Dispatching_Operation (Subp)
5298 then
5299 Create_Extra_Formals (Subp);
5300 end if;
5302 Next_Elmt (Elmt);
5303 end loop;
5304 end;
5305 end if;
5306 end Expand_Freeze_Record_Type;
5308 ------------------------------------
5309 -- Expand_N_Full_Type_Declaration --
5310 ------------------------------------
5312 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
5313 procedure Build_Master (Ptr_Typ : Entity_Id);
5314 -- Create the master associated with Ptr_Typ
5316 ------------------
5317 -- Build_Master --
5318 ------------------
5320 procedure Build_Master (Ptr_Typ : Entity_Id) is
5321 Desig_Typ : Entity_Id := Designated_Type (Ptr_Typ);
5323 begin
5324 -- If the designated type is an incomplete view coming from a
5325 -- limited-with'ed package, we need to use the nonlimited view in
5326 -- case it has tasks.
5328 if Ekind (Desig_Typ) in Incomplete_Kind
5329 and then Present (Non_Limited_View (Desig_Typ))
5330 then
5331 Desig_Typ := Non_Limited_View (Desig_Typ);
5332 end if;
5334 -- Anonymous access types are created for the components of the
5335 -- record parameter for an entry declaration. No master is created
5336 -- for such a type.
5338 if Comes_From_Source (N) and then Has_Task (Desig_Typ) then
5339 Build_Master_Entity (Ptr_Typ);
5340 Build_Master_Renaming (Ptr_Typ);
5342 -- Create a class-wide master because a Master_Id must be generated
5343 -- for access-to-limited-class-wide types whose root may be extended
5344 -- with task components.
5346 -- Note: This code covers access-to-limited-interfaces because they
5347 -- can be used to reference tasks implementing them.
5349 elsif Is_Limited_Class_Wide_Type (Desig_Typ)
5350 and then Tasking_Allowed
5351 then
5352 Build_Class_Wide_Master (Ptr_Typ);
5353 end if;
5354 end Build_Master;
5356 -- Local declarations
5358 Def_Id : constant Entity_Id := Defining_Identifier (N);
5359 B_Id : constant Entity_Id := Base_Type (Def_Id);
5360 FN : Node_Id;
5361 Par_Id : Entity_Id;
5363 -- Start of processing for Expand_N_Full_Type_Declaration
5365 begin
5366 if Is_Access_Type (Def_Id) then
5367 Build_Master (Def_Id);
5369 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
5370 Expand_Access_Protected_Subprogram_Type (N);
5371 end if;
5373 -- Array of anonymous access-to-task pointers
5375 elsif Ada_Version >= Ada_2005
5376 and then Is_Array_Type (Def_Id)
5377 and then Is_Access_Type (Component_Type (Def_Id))
5378 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
5379 then
5380 Build_Master (Component_Type (Def_Id));
5382 elsif Has_Task (Def_Id) then
5383 Expand_Previous_Access_Type (Def_Id);
5385 -- Check the components of a record type or array of records for
5386 -- anonymous access-to-task pointers.
5388 elsif Ada_Version >= Ada_2005
5389 and then (Is_Record_Type (Def_Id)
5390 or else
5391 (Is_Array_Type (Def_Id)
5392 and then Is_Record_Type (Component_Type (Def_Id))))
5393 then
5394 declare
5395 Comp : Entity_Id;
5396 First : Boolean;
5397 M_Id : Entity_Id;
5398 Typ : Entity_Id;
5400 begin
5401 if Is_Array_Type (Def_Id) then
5402 Comp := First_Entity (Component_Type (Def_Id));
5403 else
5404 Comp := First_Entity (Def_Id);
5405 end if;
5407 -- Examine all components looking for anonymous access-to-task
5408 -- types.
5410 First := True;
5411 while Present (Comp) loop
5412 Typ := Etype (Comp);
5414 if Ekind (Typ) = E_Anonymous_Access_Type
5415 and then Has_Task (Available_View (Designated_Type (Typ)))
5416 and then No (Master_Id (Typ))
5417 then
5418 -- Ensure that the record or array type have a _master
5420 if First then
5421 Build_Master_Entity (Def_Id);
5422 Build_Master_Renaming (Typ);
5423 M_Id := Master_Id (Typ);
5425 First := False;
5427 -- Reuse the same master to service any additional types
5429 else
5430 Set_Master_Id (Typ, M_Id);
5431 end if;
5432 end if;
5434 Next_Entity (Comp);
5435 end loop;
5436 end;
5437 end if;
5439 Par_Id := Etype (B_Id);
5441 -- The parent type is private then we need to inherit any TSS operations
5442 -- from the full view.
5444 if Ekind (Par_Id) in Private_Kind
5445 and then Present (Full_View (Par_Id))
5446 then
5447 Par_Id := Base_Type (Full_View (Par_Id));
5448 end if;
5450 if Nkind (Type_Definition (Original_Node (N))) =
5451 N_Derived_Type_Definition
5452 and then not Is_Tagged_Type (Def_Id)
5453 and then Present (Freeze_Node (Par_Id))
5454 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
5455 then
5456 Ensure_Freeze_Node (B_Id);
5457 FN := Freeze_Node (B_Id);
5459 if No (TSS_Elist (FN)) then
5460 Set_TSS_Elist (FN, New_Elmt_List);
5461 end if;
5463 declare
5464 T_E : constant Elist_Id := TSS_Elist (FN);
5465 Elmt : Elmt_Id;
5467 begin
5468 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
5469 while Present (Elmt) loop
5470 if Chars (Node (Elmt)) /= Name_uInit then
5471 Append_Elmt (Node (Elmt), T_E);
5472 end if;
5474 Next_Elmt (Elmt);
5475 end loop;
5477 -- If the derived type itself is private with a full view, then
5478 -- associate the full view with the inherited TSS_Elist as well.
5480 if Ekind (B_Id) in Private_Kind
5481 and then Present (Full_View (B_Id))
5482 then
5483 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
5484 Set_TSS_Elist
5485 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
5486 end if;
5487 end;
5488 end if;
5489 end Expand_N_Full_Type_Declaration;
5491 ---------------------------------
5492 -- Expand_N_Object_Declaration --
5493 ---------------------------------
5495 procedure Expand_N_Object_Declaration (N : Node_Id) is
5496 Loc : constant Source_Ptr := Sloc (N);
5497 Def_Id : constant Entity_Id := Defining_Identifier (N);
5498 Expr : constant Node_Id := Expression (N);
5499 Obj_Def : constant Node_Id := Object_Definition (N);
5500 Typ : constant Entity_Id := Etype (Def_Id);
5501 Base_Typ : constant Entity_Id := Base_Type (Typ);
5502 Expr_Q : Node_Id;
5504 function Build_Equivalent_Aggregate return Boolean;
5505 -- If the object has a constrained discriminated type and no initial
5506 -- value, it may be possible to build an equivalent aggregate instead,
5507 -- and prevent an actual call to the initialization procedure.
5509 procedure Check_Large_Modular_Array;
5510 -- Check that the size of the array can be computed without overflow,
5511 -- and generate a Storage_Error otherwise. This is only relevant for
5512 -- array types whose index in a (mod 2**64) type, where wrap-around
5513 -- arithmetic might yield a meaningless value for the length of the
5514 -- array, or its corresponding attribute.
5516 procedure Default_Initialize_Object (After : Node_Id);
5517 -- Generate all default initialization actions for object Def_Id. Any
5518 -- new code is inserted after node After.
5520 function Rewrite_As_Renaming return Boolean;
5521 -- Indicate whether to rewrite a declaration with initialization into an
5522 -- object renaming declaration (see below).
5524 --------------------------------
5525 -- Build_Equivalent_Aggregate --
5526 --------------------------------
5528 function Build_Equivalent_Aggregate return Boolean is
5529 Aggr : Node_Id;
5530 Comp : Entity_Id;
5531 Discr : Elmt_Id;
5532 Full_Type : Entity_Id;
5534 begin
5535 Full_Type := Typ;
5537 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
5538 Full_Type := Full_View (Typ);
5539 end if;
5541 -- Only perform this transformation if Elaboration_Code is forbidden
5542 -- or undesirable, and if this is a global entity of a constrained
5543 -- record type.
5545 -- If Initialize_Scalars might be active this transformation cannot
5546 -- be performed either, because it will lead to different semantics
5547 -- or because elaboration code will in fact be created.
5549 if Ekind (Full_Type) /= E_Record_Subtype
5550 or else not Has_Discriminants (Full_Type)
5551 or else not Is_Constrained (Full_Type)
5552 or else Is_Controlled (Full_Type)
5553 or else Is_Limited_Type (Full_Type)
5554 or else not Restriction_Active (No_Initialize_Scalars)
5555 then
5556 return False;
5557 end if;
5559 if Ekind (Current_Scope) = E_Package
5560 and then
5561 (Restriction_Active (No_Elaboration_Code)
5562 or else Is_Preelaborated (Current_Scope))
5563 then
5564 -- Building a static aggregate is possible if the discriminants
5565 -- have static values and the other components have static
5566 -- defaults or none.
5568 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5569 while Present (Discr) loop
5570 if not Is_OK_Static_Expression (Node (Discr)) then
5571 return False;
5572 end if;
5574 Next_Elmt (Discr);
5575 end loop;
5577 -- Check that initialized components are OK, and that non-
5578 -- initialized components do not require a call to their own
5579 -- initialization procedure.
5581 Comp := First_Component (Full_Type);
5582 while Present (Comp) loop
5583 if Ekind (Comp) = E_Component
5584 and then Present (Expression (Parent (Comp)))
5585 and then
5586 not Is_OK_Static_Expression (Expression (Parent (Comp)))
5587 then
5588 return False;
5590 elsif Has_Non_Null_Base_Init_Proc (Etype (Comp)) then
5591 return False;
5593 end if;
5595 Next_Component (Comp);
5596 end loop;
5598 -- Everything is static, assemble the aggregate, discriminant
5599 -- values first.
5601 Aggr :=
5602 Make_Aggregate (Loc,
5603 Expressions => New_List,
5604 Component_Associations => New_List);
5606 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5607 while Present (Discr) loop
5608 Append_To (Expressions (Aggr), New_Copy (Node (Discr)));
5609 Next_Elmt (Discr);
5610 end loop;
5612 -- Now collect values of initialized components
5614 Comp := First_Component (Full_Type);
5615 while Present (Comp) loop
5616 if Ekind (Comp) = E_Component
5617 and then Present (Expression (Parent (Comp)))
5618 then
5619 Append_To (Component_Associations (Aggr),
5620 Make_Component_Association (Loc,
5621 Choices => New_List (New_Occurrence_Of (Comp, Loc)),
5622 Expression => New_Copy_Tree
5623 (Expression (Parent (Comp)))));
5624 end if;
5626 Next_Component (Comp);
5627 end loop;
5629 -- Finally, box-initialize remaining components
5631 Append_To (Component_Associations (Aggr),
5632 Make_Component_Association (Loc,
5633 Choices => New_List (Make_Others_Choice (Loc)),
5634 Expression => Empty));
5635 Set_Box_Present (Last (Component_Associations (Aggr)));
5636 Set_Expression (N, Aggr);
5638 if Typ /= Full_Type then
5639 Analyze_And_Resolve (Aggr, Full_View (Base_Type (Full_Type)));
5640 Rewrite (Aggr, Unchecked_Convert_To (Typ, Aggr));
5641 Analyze_And_Resolve (Aggr, Typ);
5642 else
5643 Analyze_And_Resolve (Aggr, Full_Type);
5644 end if;
5646 return True;
5648 else
5649 return False;
5650 end if;
5651 end Build_Equivalent_Aggregate;
5653 -------------------------------
5654 -- Check_Large_Modular_Array --
5655 -------------------------------
5657 procedure Check_Large_Modular_Array is
5658 Index_Typ : Entity_Id;
5660 begin
5661 if Is_Array_Type (Typ)
5662 and then Is_Modular_Integer_Type (Etype (First_Index (Typ)))
5663 then
5664 -- To prevent arithmetic overflow with large values, we raise
5665 -- Storage_Error under the following guard:
5667 -- (Arr'Last / 2 - Arr'First / 2) > (2 ** 30)
5669 -- This takes care of the boundary case, but it is preferable to
5670 -- use a smaller limit, because even on 64-bit architectures an
5671 -- array of more than 2 ** 30 bytes is likely to raise
5672 -- Storage_Error.
5674 Index_Typ := Etype (First_Index (Typ));
5676 if RM_Size (Index_Typ) = RM_Size (Standard_Long_Long_Integer) then
5677 Insert_Action (N,
5678 Make_Raise_Storage_Error (Loc,
5679 Condition =>
5680 Make_Op_Ge (Loc,
5681 Left_Opnd =>
5682 Make_Op_Subtract (Loc,
5683 Left_Opnd =>
5684 Make_Op_Divide (Loc,
5685 Left_Opnd =>
5686 Make_Attribute_Reference (Loc,
5687 Prefix =>
5688 New_Occurrence_Of (Typ, Loc),
5689 Attribute_Name => Name_Last),
5690 Right_Opnd =>
5691 Make_Integer_Literal (Loc, Uint_2)),
5692 Right_Opnd =>
5693 Make_Op_Divide (Loc,
5694 Left_Opnd =>
5695 Make_Attribute_Reference (Loc,
5696 Prefix =>
5697 New_Occurrence_Of (Typ, Loc),
5698 Attribute_Name => Name_First),
5699 Right_Opnd =>
5700 Make_Integer_Literal (Loc, Uint_2))),
5701 Right_Opnd =>
5702 Make_Integer_Literal (Loc, (Uint_2 ** 30))),
5703 Reason => SE_Object_Too_Large));
5704 end if;
5705 end if;
5706 end Check_Large_Modular_Array;
5708 -------------------------------
5709 -- Default_Initialize_Object --
5710 -------------------------------
5712 procedure Default_Initialize_Object (After : Node_Id) is
5713 function New_Object_Reference return Node_Id;
5714 -- Return a new reference to Def_Id with attributes Assignment_OK and
5715 -- Must_Not_Freeze already set.
5717 --------------------------
5718 -- New_Object_Reference --
5719 --------------------------
5721 function New_Object_Reference return Node_Id is
5722 Obj_Ref : constant Node_Id := New_Occurrence_Of (Def_Id, Loc);
5724 begin
5725 -- The call to the type init proc or [Deep_]Finalize must not
5726 -- freeze the related object as the call is internally generated.
5727 -- This way legal rep clauses that apply to the object will not be
5728 -- flagged. Note that the initialization call may be removed if
5729 -- pragma Import is encountered or moved to the freeze actions of
5730 -- the object because of an address clause.
5732 Set_Assignment_OK (Obj_Ref);
5733 Set_Must_Not_Freeze (Obj_Ref);
5735 return Obj_Ref;
5736 end New_Object_Reference;
5738 -- Local variables
5740 Exceptions_OK : constant Boolean :=
5741 not Restriction_Active (No_Exception_Propagation);
5743 Aggr_Init : Node_Id;
5744 Comp_Init : List_Id := No_List;
5745 Fin_Call : Node_Id;
5746 Init_Stmts : List_Id := No_List;
5747 Obj_Init : Node_Id := Empty;
5748 Obj_Ref : Node_Id;
5750 -- Start of processing for Default_Initialize_Object
5752 begin
5753 -- Default initialization is suppressed for objects that are already
5754 -- known to be imported (i.e. whose declaration specifies the Import
5755 -- aspect). Note that for objects with a pragma Import, we generate
5756 -- initialization here, and then remove it downstream when processing
5757 -- the pragma. It is also suppressed for variables for which a pragma
5758 -- Suppress_Initialization has been explicitly given
5760 if Is_Imported (Def_Id) or else Suppress_Initialization (Def_Id) then
5761 return;
5763 -- Nothing to do if the object being initialized is of a task type
5764 -- and restriction No_Tasking is in effect, because this is a direct
5765 -- violation of the restriction.
5767 elsif Is_Task_Type (Base_Typ)
5768 and then Restriction_Active (No_Tasking)
5769 then
5770 return;
5771 end if;
5773 -- The expansion performed by this routine is as follows:
5775 -- begin
5776 -- Abort_Defer;
5777 -- Type_Init_Proc (Obj);
5779 -- begin
5780 -- [Deep_]Initialize (Obj);
5782 -- exception
5783 -- when others =>
5784 -- [Deep_]Finalize (Obj, Self => False);
5785 -- raise;
5786 -- end;
5787 -- at end
5788 -- Abort_Undefer_Direct;
5789 -- end;
5791 -- Initialize the components of the object
5793 if Has_Non_Null_Base_Init_Proc (Typ)
5794 and then not No_Initialization (N)
5795 and then not Initialization_Suppressed (Typ)
5796 then
5797 -- Do not initialize the components if No_Default_Initialization
5798 -- applies as the actual restriction check will occur later
5799 -- when the object is frozen as it is not known yet whether the
5800 -- object is imported or not.
5802 if not Restriction_Active (No_Default_Initialization) then
5804 -- If the values of the components are compile-time known, use
5805 -- their prebuilt aggregate form directly.
5807 Aggr_Init := Static_Initialization (Base_Init_Proc (Typ));
5809 if Present (Aggr_Init) then
5810 Set_Expression
5811 (N, New_Copy_Tree (Aggr_Init, New_Scope => Current_Scope));
5813 -- If type has discriminants, try to build an equivalent
5814 -- aggregate using discriminant values from the declaration.
5815 -- This is a useful optimization, in particular if restriction
5816 -- No_Elaboration_Code is active.
5818 elsif Build_Equivalent_Aggregate then
5819 null;
5821 -- Otherwise invoke the type init proc, generate:
5822 -- Type_Init_Proc (Obj);
5824 else
5825 Obj_Ref := New_Object_Reference;
5827 if Comes_From_Source (Def_Id) then
5828 Initialization_Warning (Obj_Ref);
5829 end if;
5831 Comp_Init := Build_Initialization_Call (Loc, Obj_Ref, Typ);
5832 end if;
5833 end if;
5835 -- Provide a default value if the object needs simple initialization
5836 -- and does not already have an initial value. A generated temporary
5837 -- does not require initialization because it will be assigned later.
5839 elsif Needs_Simple_Initialization
5840 (Typ, Initialize_Scalars
5841 and then No (Following_Address_Clause (N)))
5842 and then not Is_Internal (Def_Id)
5843 and then not Has_Init_Expression (N)
5844 then
5845 Set_No_Initialization (N, False);
5846 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
5847 Analyze_And_Resolve (Expression (N), Typ);
5848 end if;
5850 -- Initialize the object, generate:
5851 -- [Deep_]Initialize (Obj);
5853 if Needs_Finalization (Typ) and then not No_Initialization (N) then
5854 Obj_Init :=
5855 Make_Init_Call
5856 (Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5857 Typ => Typ);
5858 end if;
5860 -- Build a special finalization block when both the object and its
5861 -- controlled components are to be initialized. The block finalizes
5862 -- the components if the object initialization fails. Generate:
5864 -- begin
5865 -- <Obj_Init>
5867 -- exception
5868 -- when others =>
5869 -- <Fin_Call>
5870 -- raise;
5871 -- end;
5873 if Has_Controlled_Component (Typ)
5874 and then Present (Comp_Init)
5875 and then Present (Obj_Init)
5876 and then Exceptions_OK
5877 then
5878 Init_Stmts := Comp_Init;
5880 Fin_Call :=
5881 Make_Final_Call
5882 (Obj_Ref => New_Object_Reference,
5883 Typ => Typ,
5884 Skip_Self => True);
5886 if Present (Fin_Call) then
5888 -- Do not emit warnings related to the elaboration order when a
5889 -- controlled object is declared before the body of Finalize is
5890 -- seen.
5892 Set_No_Elaboration_Check (Fin_Call);
5894 Append_To (Init_Stmts,
5895 Make_Block_Statement (Loc,
5896 Declarations => No_List,
5898 Handled_Statement_Sequence =>
5899 Make_Handled_Sequence_Of_Statements (Loc,
5900 Statements => New_List (Obj_Init),
5902 Exception_Handlers => New_List (
5903 Make_Exception_Handler (Loc,
5904 Exception_Choices => New_List (
5905 Make_Others_Choice (Loc)),
5907 Statements => New_List (
5908 Fin_Call,
5909 Make_Raise_Statement (Loc)))))));
5910 end if;
5912 -- Otherwise finalization is not required, the initialization calls
5913 -- are passed to the abort block building circuitry, generate:
5915 -- Type_Init_Proc (Obj);
5916 -- [Deep_]Initialize (Obj);
5918 else
5919 if Present (Comp_Init) then
5920 Init_Stmts := Comp_Init;
5921 end if;
5923 if Present (Obj_Init) then
5924 if No (Init_Stmts) then
5925 Init_Stmts := New_List;
5926 end if;
5928 Append_To (Init_Stmts, Obj_Init);
5929 end if;
5930 end if;
5932 -- Build an abort block to protect the initialization calls
5934 if Abort_Allowed
5935 and then Present (Comp_Init)
5936 and then Present (Obj_Init)
5937 then
5938 -- Generate:
5939 -- Abort_Defer;
5941 Prepend_To (Init_Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
5943 -- When exceptions are propagated, abort deferral must take place
5944 -- in the presence of initialization or finalization exceptions.
5945 -- Generate:
5947 -- begin
5948 -- Abort_Defer;
5949 -- <Init_Stmts>
5950 -- at end
5951 -- Abort_Undefer_Direct;
5952 -- end;
5954 if Exceptions_OK then
5955 Init_Stmts := New_List (
5956 Build_Abort_Undefer_Block (Loc,
5957 Stmts => Init_Stmts,
5958 Context => N));
5960 -- Otherwise exceptions are not propagated. Generate:
5962 -- Abort_Defer;
5963 -- <Init_Stmts>
5964 -- Abort_Undefer;
5966 else
5967 Append_To (Init_Stmts,
5968 Build_Runtime_Call (Loc, RE_Abort_Undefer));
5969 end if;
5970 end if;
5972 -- Insert the whole initialization sequence into the tree. If the
5973 -- object has a delayed freeze, as will be the case when it has
5974 -- aspect specifications, the initialization sequence is part of
5975 -- the freeze actions.
5977 if Present (Init_Stmts) then
5978 if Has_Delayed_Freeze (Def_Id) then
5979 Append_Freeze_Actions (Def_Id, Init_Stmts);
5980 else
5981 Insert_Actions_After (After, Init_Stmts);
5982 end if;
5983 end if;
5984 end Default_Initialize_Object;
5986 -------------------------
5987 -- Rewrite_As_Renaming --
5988 -------------------------
5990 function Rewrite_As_Renaming return Boolean is
5991 begin
5992 -- If the object declaration appears in the form
5994 -- Obj : Ctrl_Typ := Func (...);
5996 -- where Ctrl_Typ is controlled but not immutably limited type, then
5997 -- the expansion of the function call should use a dereference of the
5998 -- result to reference the value on the secondary stack.
6000 -- Obj : Ctrl_Typ renames Func (...).all;
6002 -- As a result, the call avoids an extra copy. This an optimization,
6003 -- but it is required for passing ACATS tests in some cases where it
6004 -- would otherwise make two copies. The RM allows removing redunant
6005 -- Adjust/Finalize calls, but does not allow insertion of extra ones.
6007 -- This part is disabled for now, because it breaks GPS builds
6009 return (False -- ???
6010 and then Nkind (Expr_Q) = N_Explicit_Dereference
6011 and then not Comes_From_Source (Expr_Q)
6012 and then Nkind (Original_Node (Expr_Q)) = N_Function_Call
6013 and then Nkind (Object_Definition (N)) in N_Has_Entity
6014 and then (Needs_Finalization (Entity (Object_Definition (N)))))
6016 -- If the initializing expression is for a variable with attribute
6017 -- OK_To_Rename set, then transform:
6019 -- Obj : Typ := Expr;
6021 -- into
6023 -- Obj : Typ renames Expr;
6025 -- provided that Obj is not aliased. The aliased case has to be
6026 -- excluded in general because Expr will not be aliased in
6027 -- general.
6029 or else
6030 (not Aliased_Present (N)
6031 and then Is_Entity_Name (Expr_Q)
6032 and then Ekind (Entity (Expr_Q)) = E_Variable
6033 and then OK_To_Rename (Entity (Expr_Q))
6034 and then Is_Entity_Name (Obj_Def));
6035 end Rewrite_As_Renaming;
6037 -- Local variables
6039 Next_N : constant Node_Id := Next (N);
6041 Adj_Call : Node_Id;
6042 Id_Ref : Node_Id;
6043 Tag_Assign : Node_Id;
6045 Init_After : Node_Id := N;
6046 -- Node after which the initialization actions are to be inserted. This
6047 -- is normally N, except for the case of a shared passive variable, in
6048 -- which case the init proc call must be inserted only after the bodies
6049 -- of the shared variable procedures have been seen.
6051 -- Start of processing for Expand_N_Object_Declaration
6053 begin
6054 -- Don't do anything for deferred constants. All proper actions will be
6055 -- expanded during the full declaration.
6057 if No (Expr) and Constant_Present (N) then
6058 return;
6059 end if;
6061 -- The type of the object cannot be abstract. This is diagnosed at the
6062 -- point the object is frozen, which happens after the declaration is
6063 -- fully expanded, so simply return now.
6065 if Is_Abstract_Type (Typ) then
6066 return;
6067 end if;
6069 -- First we do special processing for objects of a tagged type where
6070 -- this is the point at which the type is frozen. The creation of the
6071 -- dispatch table and the initialization procedure have to be deferred
6072 -- to this point, since we reference previously declared primitive
6073 -- subprograms.
6075 -- Force construction of dispatch tables of library level tagged types
6077 if Tagged_Type_Expansion
6078 and then Static_Dispatch_Tables
6079 and then Is_Library_Level_Entity (Def_Id)
6080 and then Is_Library_Level_Tagged_Type (Base_Typ)
6081 and then Ekind_In (Base_Typ, E_Record_Type,
6082 E_Protected_Type,
6083 E_Task_Type)
6084 and then not Has_Dispatch_Table (Base_Typ)
6085 then
6086 declare
6087 New_Nodes : List_Id := No_List;
6089 begin
6090 if Is_Concurrent_Type (Base_Typ) then
6091 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
6092 else
6093 New_Nodes := Make_DT (Base_Typ, N);
6094 end if;
6096 if not Is_Empty_List (New_Nodes) then
6097 Insert_List_Before (N, New_Nodes);
6098 end if;
6099 end;
6100 end if;
6102 -- Make shared memory routines for shared passive variable
6104 if Is_Shared_Passive (Def_Id) then
6105 Init_After := Make_Shared_Var_Procs (N);
6106 end if;
6108 -- If tasks being declared, make sure we have an activation chain
6109 -- defined for the tasks (has no effect if we already have one), and
6110 -- also that a Master variable is established and that the appropriate
6111 -- enclosing construct is established as a task master.
6113 if Has_Task (Typ) then
6114 Build_Activation_Chain_Entity (N);
6115 Build_Master_Entity (Def_Id);
6116 end if;
6118 Check_Large_Modular_Array;
6120 -- Default initialization required, and no expression present
6122 if No (Expr) then
6124 -- If we have a type with a variant part, the initialization proc
6125 -- will contain implicit tests of the discriminant values, which
6126 -- counts as a violation of the restriction No_Implicit_Conditionals.
6128 if Has_Variant_Part (Typ) then
6129 declare
6130 Msg : Boolean;
6132 begin
6133 Check_Restriction (Msg, No_Implicit_Conditionals, Obj_Def);
6135 if Msg then
6136 Error_Msg_N
6137 ("\initialization of variant record tests discriminants",
6138 Obj_Def);
6139 return;
6140 end if;
6141 end;
6142 end if;
6144 -- For the default initialization case, if we have a private type
6145 -- with invariants, and invariant checks are enabled, then insert an
6146 -- invariant check after the object declaration. Note that it is OK
6147 -- to clobber the object with an invalid value since if the exception
6148 -- is raised, then the object will go out of scope. In the case where
6149 -- an array object is initialized with an aggregate, the expression
6150 -- is removed. Check flag Has_Init_Expression to avoid generating a
6151 -- junk invariant check and flag No_Initialization to avoid checking
6152 -- an uninitialized object such as a compiler temporary used for an
6153 -- aggregate.
6155 if Has_Invariants (Base_Typ)
6156 and then Present (Invariant_Procedure (Base_Typ))
6157 and then not Has_Init_Expression (N)
6158 and then not No_Initialization (N)
6159 then
6160 -- If entity has an address clause or aspect, make invariant
6161 -- call into a freeze action for the explicit freeze node for
6162 -- object. Otherwise insert invariant check after declaration.
6164 if Present (Following_Address_Clause (N))
6165 or else Has_Aspect (Def_Id, Aspect_Address)
6166 then
6167 Ensure_Freeze_Node (Def_Id);
6168 Set_Has_Delayed_Freeze (Def_Id);
6169 Set_Is_Frozen (Def_Id, False);
6171 if not Partial_View_Has_Unknown_Discr (Typ) then
6172 Append_Freeze_Action (Def_Id,
6173 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
6174 end if;
6176 elsif not Partial_View_Has_Unknown_Discr (Typ) then
6177 Insert_After (N,
6178 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
6179 end if;
6180 end if;
6182 Default_Initialize_Object (Init_After);
6184 -- Generate attribute for Persistent_BSS if needed
6186 if Persistent_BSS_Mode
6187 and then Comes_From_Source (N)
6188 and then Is_Potentially_Persistent_Type (Typ)
6189 and then not Has_Init_Expression (N)
6190 and then Is_Library_Level_Entity (Def_Id)
6191 then
6192 declare
6193 Prag : Node_Id;
6194 begin
6195 Prag :=
6196 Make_Linker_Section_Pragma
6197 (Def_Id, Sloc (N), ".persistent.bss");
6198 Insert_After (N, Prag);
6199 Analyze (Prag);
6200 end;
6201 end if;
6203 -- If access type, then we know it is null if not initialized
6205 if Is_Access_Type (Typ) then
6206 Set_Is_Known_Null (Def_Id);
6207 end if;
6209 -- Explicit initialization present
6211 else
6212 -- Obtain actual expression from qualified expression
6214 if Nkind (Expr) = N_Qualified_Expression then
6215 Expr_Q := Expression (Expr);
6216 else
6217 Expr_Q := Expr;
6218 end if;
6220 -- When we have the appropriate type of aggregate in the expression
6221 -- (it has been determined during analysis of the aggregate by
6222 -- setting the delay flag), let's perform in place assignment and
6223 -- thus avoid creating a temporary.
6225 if Is_Delayed_Aggregate (Expr_Q) then
6226 Convert_Aggr_In_Object_Decl (N);
6228 -- Ada 2005 (AI-318-02): If the initialization expression is a call
6229 -- to a build-in-place function, then access to the declared object
6230 -- must be passed to the function. Currently we limit such functions
6231 -- to those with constrained limited result subtypes, but eventually
6232 -- plan to expand the allowed forms of functions that are treated as
6233 -- build-in-place.
6235 elsif Ada_Version >= Ada_2005
6236 and then Is_Build_In_Place_Function_Call (Expr_Q)
6237 then
6238 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
6240 -- The previous call expands the expression initializing the
6241 -- built-in-place object into further code that will be analyzed
6242 -- later. No further expansion needed here.
6244 return;
6246 -- Ada 2005 (AI-318-02): Specialization of the previous case for
6247 -- expressions containing a build-in-place function call whose
6248 -- returned object covers interface types, and Expr_Q has calls to
6249 -- Ada.Tags.Displace to displace the pointer to the returned build-
6250 -- in-place object to reference the secondary dispatch table of a
6251 -- covered interface type.
6253 elsif Ada_Version >= Ada_2005
6254 and then Present (Unqual_BIP_Iface_Function_Call (Expr_Q))
6255 then
6256 Make_Build_In_Place_Iface_Call_In_Object_Declaration (N, Expr_Q);
6258 -- The previous call expands the expression initializing the
6259 -- built-in-place object into further code that will be analyzed
6260 -- later. No further expansion needed here.
6262 return;
6264 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
6265 -- class-wide interface object to ensure that we copy the full
6266 -- object, unless we are targetting a VM where interfaces are handled
6267 -- by VM itself. Note that if the root type of Typ is an ancestor of
6268 -- Expr's type, both types share the same dispatch table and there is
6269 -- no need to displace the pointer.
6271 elsif Is_Interface (Typ)
6273 -- Avoid never-ending recursion because if Equivalent_Type is set
6274 -- then we've done it already and must not do it again.
6276 and then not
6277 (Nkind (Obj_Def) = N_Identifier
6278 and then Present (Equivalent_Type (Entity (Obj_Def))))
6279 then
6280 pragma Assert (Is_Class_Wide_Type (Typ));
6282 -- If the object is a return object of an inherently limited type,
6283 -- which implies build-in-place treatment, bypass the special
6284 -- treatment of class-wide interface initialization below. In this
6285 -- case, the expansion of the return statement will take care of
6286 -- creating the object (via allocator) and initializing it.
6288 if Is_Return_Object (Def_Id) and then Is_Limited_View (Typ) then
6289 null;
6291 elsif Tagged_Type_Expansion then
6292 declare
6293 Iface : constant Entity_Id := Root_Type (Typ);
6294 Expr_N : Node_Id := Expr;
6295 Expr_Typ : Entity_Id;
6296 New_Expr : Node_Id;
6297 Obj_Id : Entity_Id;
6298 Tag_Comp : Node_Id;
6300 begin
6301 -- If the original node of the expression was a conversion
6302 -- to this specific class-wide interface type then restore
6303 -- the original node because we must copy the object before
6304 -- displacing the pointer to reference the secondary tag
6305 -- component. This code must be kept synchronized with the
6306 -- expansion done by routine Expand_Interface_Conversion
6308 if not Comes_From_Source (Expr_N)
6309 and then Nkind (Expr_N) = N_Explicit_Dereference
6310 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
6311 and then Etype (Original_Node (Expr_N)) = Typ
6312 then
6313 Rewrite (Expr_N, Original_Node (Expression (N)));
6314 end if;
6316 -- Avoid expansion of redundant interface conversion
6318 if Is_Interface (Etype (Expr_N))
6319 and then Nkind (Expr_N) = N_Type_Conversion
6320 and then Etype (Expr_N) = Typ
6321 then
6322 Expr_N := Expression (Expr_N);
6323 Set_Expression (N, Expr_N);
6324 end if;
6326 Obj_Id := Make_Temporary (Loc, 'D', Expr_N);
6327 Expr_Typ := Base_Type (Etype (Expr_N));
6329 if Is_Class_Wide_Type (Expr_Typ) then
6330 Expr_Typ := Root_Type (Expr_Typ);
6331 end if;
6333 -- Replace
6334 -- CW : I'Class := Obj;
6335 -- by
6336 -- Tmp : T := Obj;
6337 -- type Ityp is not null access I'Class;
6338 -- CW : I'Class renames Ityp (Tmp.I_Tag'Address).all;
6340 if Comes_From_Source (Expr_N)
6341 and then Nkind (Expr_N) = N_Identifier
6342 and then not Is_Interface (Expr_Typ)
6343 and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
6344 and then (Expr_Typ = Etype (Expr_Typ)
6345 or else not
6346 Is_Variable_Size_Record (Etype (Expr_Typ)))
6347 then
6348 -- Copy the object
6350 Insert_Action (N,
6351 Make_Object_Declaration (Loc,
6352 Defining_Identifier => Obj_Id,
6353 Object_Definition =>
6354 New_Occurrence_Of (Expr_Typ, Loc),
6355 Expression => Relocate_Node (Expr_N)));
6357 -- Statically reference the tag associated with the
6358 -- interface
6360 Tag_Comp :=
6361 Make_Selected_Component (Loc,
6362 Prefix => New_Occurrence_Of (Obj_Id, Loc),
6363 Selector_Name =>
6364 New_Occurrence_Of
6365 (Find_Interface_Tag (Expr_Typ, Iface), Loc));
6367 -- Replace
6368 -- IW : I'Class := Obj;
6369 -- by
6370 -- type Equiv_Record is record ... end record;
6371 -- implicit subtype CW is <Class_Wide_Subtype>;
6372 -- Tmp : CW := CW!(Obj);
6373 -- type Ityp is not null access I'Class;
6374 -- IW : I'Class renames
6375 -- Ityp!(Displace (Temp'Address, I'Tag)).all;
6377 else
6378 -- Generate the equivalent record type and update the
6379 -- subtype indication to reference it.
6381 Expand_Subtype_From_Expr
6382 (N => N,
6383 Unc_Type => Typ,
6384 Subtype_Indic => Obj_Def,
6385 Exp => Expr_N);
6387 if not Is_Interface (Etype (Expr_N)) then
6388 New_Expr := Relocate_Node (Expr_N);
6390 -- For interface types we use 'Address which displaces
6391 -- the pointer to the base of the object (if required)
6393 else
6394 New_Expr :=
6395 Unchecked_Convert_To (Etype (Obj_Def),
6396 Make_Explicit_Dereference (Loc,
6397 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
6398 Make_Attribute_Reference (Loc,
6399 Prefix => Relocate_Node (Expr_N),
6400 Attribute_Name => Name_Address))));
6401 end if;
6403 -- Copy the object
6405 if not Is_Limited_Record (Expr_Typ) then
6406 Insert_Action (N,
6407 Make_Object_Declaration (Loc,
6408 Defining_Identifier => Obj_Id,
6409 Object_Definition =>
6410 New_Occurrence_Of (Etype (Obj_Def), Loc),
6411 Expression => New_Expr));
6413 -- Rename limited type object since they cannot be copied
6414 -- This case occurs when the initialization expression
6415 -- has been previously expanded into a temporary object.
6417 else pragma Assert (not Comes_From_Source (Expr_Q));
6418 Insert_Action (N,
6419 Make_Object_Renaming_Declaration (Loc,
6420 Defining_Identifier => Obj_Id,
6421 Subtype_Mark =>
6422 New_Occurrence_Of (Etype (Obj_Def), Loc),
6423 Name =>
6424 Unchecked_Convert_To
6425 (Etype (Obj_Def), New_Expr)));
6426 end if;
6428 -- Dynamically reference the tag associated with the
6429 -- interface.
6431 Tag_Comp :=
6432 Make_Function_Call (Loc,
6433 Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
6434 Parameter_Associations => New_List (
6435 Make_Attribute_Reference (Loc,
6436 Prefix => New_Occurrence_Of (Obj_Id, Loc),
6437 Attribute_Name => Name_Address),
6438 New_Occurrence_Of
6439 (Node (First_Elmt (Access_Disp_Table (Iface))),
6440 Loc)));
6441 end if;
6443 Rewrite (N,
6444 Make_Object_Renaming_Declaration (Loc,
6445 Defining_Identifier => Make_Temporary (Loc, 'D'),
6446 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
6447 Name =>
6448 Convert_Tag_To_Interface (Typ, Tag_Comp)));
6450 -- If the original entity comes from source, then mark the
6451 -- new entity as needing debug information, even though it's
6452 -- defined by a generated renaming that does not come from
6453 -- source, so that Materialize_Entity will be set on the
6454 -- entity when Debug_Renaming_Declaration is called during
6455 -- analysis.
6457 if Comes_From_Source (Def_Id) then
6458 Set_Debug_Info_Needed (Defining_Identifier (N));
6459 end if;
6461 Analyze (N, Suppress => All_Checks);
6463 -- Replace internal identifier of rewritten node by the
6464 -- identifier found in the sources. We also have to exchange
6465 -- entities containing their defining identifiers to ensure
6466 -- the correct replacement of the object declaration by this
6467 -- object renaming declaration because these identifiers
6468 -- were previously added by Enter_Name to the current scope.
6469 -- We must preserve the homonym chain of the source entity
6470 -- as well. We must also preserve the kind of the entity,
6471 -- which may be a constant. Preserve entity chain because
6472 -- itypes may have been generated already, and the full
6473 -- chain must be preserved for final freezing. Finally,
6474 -- preserve Comes_From_Source setting, so that debugging
6475 -- and cross-referencing information is properly kept, and
6476 -- preserve source location, to prevent spurious errors when
6477 -- entities are declared (they must have their own Sloc).
6479 declare
6480 New_Id : constant Entity_Id := Defining_Identifier (N);
6481 Next_Temp : constant Entity_Id := Next_Entity (New_Id);
6482 S_Flag : constant Boolean :=
6483 Comes_From_Source (Def_Id);
6485 begin
6486 Set_Next_Entity (New_Id, Next_Entity (Def_Id));
6487 Set_Next_Entity (Def_Id, Next_Temp);
6489 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
6490 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
6491 Set_Ekind (Defining_Identifier (N), Ekind (Def_Id));
6492 Set_Sloc (Defining_Identifier (N), Sloc (Def_Id));
6494 Set_Comes_From_Source (Def_Id, False);
6495 Exchange_Entities (Defining_Identifier (N), Def_Id);
6496 Set_Comes_From_Source (Def_Id, S_Flag);
6497 end;
6498 end;
6499 end if;
6501 return;
6503 -- Common case of explicit object initialization
6505 else
6506 -- In most cases, we must check that the initial value meets any
6507 -- constraint imposed by the declared type. However, there is one
6508 -- very important exception to this rule. If the entity has an
6509 -- unconstrained nominal subtype, then it acquired its constraints
6510 -- from the expression in the first place, and not only does this
6511 -- mean that the constraint check is not needed, but an attempt to
6512 -- perform the constraint check can cause order of elaboration
6513 -- problems.
6515 if not Is_Constr_Subt_For_U_Nominal (Typ) then
6517 -- If this is an allocator for an aggregate that has been
6518 -- allocated in place, delay checks until assignments are
6519 -- made, because the discriminants are not initialized.
6521 if Nkind (Expr) = N_Allocator and then No_Initialization (Expr)
6522 then
6523 null;
6525 -- Otherwise apply a constraint check now if no prev error
6527 elsif Nkind (Expr) /= N_Error then
6528 Apply_Constraint_Check (Expr, Typ);
6530 -- Deal with possible range check
6532 if Do_Range_Check (Expr) then
6534 -- If assignment checks are suppressed, turn off flag
6536 if Suppress_Assignment_Checks (N) then
6537 Set_Do_Range_Check (Expr, False);
6539 -- Otherwise generate the range check
6541 else
6542 Generate_Range_Check
6543 (Expr, Typ, CE_Range_Check_Failed);
6544 end if;
6545 end if;
6546 end if;
6547 end if;
6549 -- If the type is controlled and not inherently limited, then
6550 -- the target is adjusted after the copy and attached to the
6551 -- finalization list. However, no adjustment is done in the case
6552 -- where the object was initialized by a call to a function whose
6553 -- result is built in place, since no copy occurred. (Eventually
6554 -- we plan to support in-place function results for some cases
6555 -- of nonlimited types. ???) Similarly, no adjustment is required
6556 -- if we are going to rewrite the object declaration into a
6557 -- renaming declaration.
6559 if Needs_Finalization (Typ)
6560 and then not Is_Limited_View (Typ)
6561 and then not Rewrite_As_Renaming
6562 then
6563 Adj_Call :=
6564 Make_Adjust_Call (
6565 Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
6566 Typ => Base_Typ);
6568 -- Guard against a missing [Deep_]Adjust when the base type
6569 -- was not properly frozen.
6571 if Present (Adj_Call) then
6572 Insert_Action_After (Init_After, Adj_Call);
6573 end if;
6574 end if;
6576 -- For tagged types, when an init value is given, the tag has to
6577 -- be re-initialized separately in order to avoid the propagation
6578 -- of a wrong tag coming from a view conversion unless the type
6579 -- is class wide (in this case the tag comes from the init value).
6580 -- Suppress the tag assignment when not Tagged_Type_Expansion
6581 -- because tags are represented implicitly in objects. Ditto for
6582 -- types that are CPP_CLASS, and for initializations that are
6583 -- aggregates, because they have to have the right tag.
6585 -- The re-assignment of the tag has to be done even if the object
6586 -- is a constant. The assignment must be analyzed after the
6587 -- declaration. If an address clause follows, this is handled as
6588 -- part of the freeze actions for the object, otherwise insert
6589 -- tag assignment here.
6591 Tag_Assign := Make_Tag_Assignment (N);
6593 if Present (Tag_Assign) then
6594 if Present (Following_Address_Clause (N)) then
6595 Ensure_Freeze_Node (Def_Id);
6597 else
6598 Insert_Action_After (Init_After, Tag_Assign);
6599 end if;
6601 -- Handle C++ constructor calls. Note that we do not check that
6602 -- Typ is a tagged type since the equivalent Ada type of a C++
6603 -- class that has no virtual methods is an untagged limited
6604 -- record type.
6606 elsif Is_CPP_Constructor_Call (Expr) then
6608 -- The call to the initialization procedure does NOT freeze the
6609 -- object being initialized.
6611 Id_Ref := New_Occurrence_Of (Def_Id, Loc);
6612 Set_Must_Not_Freeze (Id_Ref);
6613 Set_Assignment_OK (Id_Ref);
6615 Insert_Actions_After (Init_After,
6616 Build_Initialization_Call (Loc, Id_Ref, Typ,
6617 Constructor_Ref => Expr));
6619 -- We remove here the original call to the constructor
6620 -- to avoid its management in the backend
6622 Set_Expression (N, Empty);
6623 return;
6625 -- Handle initialization of limited tagged types
6627 elsif Is_Tagged_Type (Typ)
6628 and then Is_Class_Wide_Type (Typ)
6629 and then Is_Limited_Record (Typ)
6630 and then not Is_Limited_Interface (Typ)
6631 then
6632 -- Given that the type is limited we cannot perform a copy. If
6633 -- Expr_Q is the reference to a variable we mark the variable
6634 -- as OK_To_Rename to expand this declaration into a renaming
6635 -- declaration (see bellow).
6637 if Is_Entity_Name (Expr_Q) then
6638 Set_OK_To_Rename (Entity (Expr_Q));
6640 -- If we cannot convert the expression into a renaming we must
6641 -- consider it an internal error because the backend does not
6642 -- have support to handle it.
6644 else
6645 pragma Assert (False);
6646 raise Program_Error;
6647 end if;
6649 -- For discrete types, set the Is_Known_Valid flag if the
6650 -- initializing value is known to be valid. Only do this for
6651 -- source assignments, since otherwise we can end up turning
6652 -- on the known valid flag prematurely from inserted code.
6654 elsif Comes_From_Source (N)
6655 and then Is_Discrete_Type (Typ)
6656 and then Expr_Known_Valid (Expr)
6657 then
6658 Set_Is_Known_Valid (Def_Id);
6660 elsif Is_Access_Type (Typ) then
6662 -- For access types set the Is_Known_Non_Null flag if the
6663 -- initializing value is known to be non-null. We can also set
6664 -- Can_Never_Be_Null if this is a constant.
6666 if Known_Non_Null (Expr) then
6667 Set_Is_Known_Non_Null (Def_Id, True);
6669 if Constant_Present (N) then
6670 Set_Can_Never_Be_Null (Def_Id);
6671 end if;
6672 end if;
6673 end if;
6675 -- If validity checking on copies, validate initial expression.
6676 -- But skip this if declaration is for a generic type, since it
6677 -- makes no sense to validate generic types. Not clear if this
6678 -- can happen for legal programs, but it definitely can arise
6679 -- from previous instantiation errors.
6681 if Validity_Checks_On
6682 and then Comes_From_Source (N)
6683 and then Validity_Check_Copies
6684 and then not Is_Generic_Type (Etype (Def_Id))
6685 then
6686 Ensure_Valid (Expr);
6687 Set_Is_Known_Valid (Def_Id);
6688 end if;
6689 end if;
6691 -- Cases where the back end cannot handle the initialization directly
6692 -- In such cases, we expand an assignment that will be appropriately
6693 -- handled by Expand_N_Assignment_Statement.
6695 -- The exclusion of the unconstrained case is wrong, but for now it
6696 -- is too much trouble ???
6698 if (Is_Possibly_Unaligned_Slice (Expr)
6699 or else (Is_Possibly_Unaligned_Object (Expr)
6700 and then not Represented_As_Scalar (Etype (Expr))))
6701 and then not (Is_Array_Type (Etype (Expr))
6702 and then not Is_Constrained (Etype (Expr)))
6703 then
6704 declare
6705 Stat : constant Node_Id :=
6706 Make_Assignment_Statement (Loc,
6707 Name => New_Occurrence_Of (Def_Id, Loc),
6708 Expression => Relocate_Node (Expr));
6709 begin
6710 Set_Expression (N, Empty);
6711 Set_No_Initialization (N);
6712 Set_Assignment_OK (Name (Stat));
6713 Set_No_Ctrl_Actions (Stat);
6714 Insert_After_And_Analyze (Init_After, Stat);
6715 end;
6716 end if;
6717 end if;
6719 if Nkind (Obj_Def) = N_Access_Definition
6720 and then not Is_Local_Anonymous_Access (Etype (Def_Id))
6721 then
6722 -- An Ada 2012 stand-alone object of an anonymous access type
6724 declare
6725 Loc : constant Source_Ptr := Sloc (N);
6727 Level : constant Entity_Id :=
6728 Make_Defining_Identifier (Sloc (N),
6729 Chars =>
6730 New_External_Name (Chars (Def_Id), Suffix => "L"));
6732 Level_Expr : Node_Id;
6733 Level_Decl : Node_Id;
6735 begin
6736 Set_Ekind (Level, Ekind (Def_Id));
6737 Set_Etype (Level, Standard_Natural);
6738 Set_Scope (Level, Scope (Def_Id));
6740 if No (Expr) then
6742 -- Set accessibility level of null
6744 Level_Expr :=
6745 Make_Integer_Literal (Loc, Scope_Depth (Standard_Standard));
6747 else
6748 Level_Expr := Dynamic_Accessibility_Level (Expr);
6749 end if;
6751 Level_Decl :=
6752 Make_Object_Declaration (Loc,
6753 Defining_Identifier => Level,
6754 Object_Definition =>
6755 New_Occurrence_Of (Standard_Natural, Loc),
6756 Expression => Level_Expr,
6757 Constant_Present => Constant_Present (N),
6758 Has_Init_Expression => True);
6760 Insert_Action_After (Init_After, Level_Decl);
6762 Set_Extra_Accessibility (Def_Id, Level);
6763 end;
6764 end if;
6766 -- If the object is default initialized and its type is subject to
6767 -- pragma Default_Initial_Condition, add a runtime check to verify
6768 -- the assumption of the pragma (SPARK RM 7.3.3). Generate:
6770 -- <Base_Typ>DIC (<Base_Typ> (Def_Id));
6772 -- Note that the check is generated for source objects only
6774 if Comes_From_Source (Def_Id)
6775 and then Has_DIC (Typ)
6776 and then Present (DIC_Procedure (Typ))
6777 and then not Has_Init_Expression (N)
6778 then
6779 declare
6780 DIC_Call : constant Node_Id := Build_DIC_Call (Loc, Def_Id, Typ);
6782 begin
6783 if Present (Next_N) then
6784 Insert_Before_And_Analyze (Next_N, DIC_Call);
6786 -- The object declaration is the last node in a declarative or a
6787 -- statement list.
6789 else
6790 Append_To (List_Containing (N), DIC_Call);
6791 Analyze (DIC_Call);
6792 end if;
6793 end;
6794 end if;
6796 -- Final transformation - turn the object declaration into a renaming
6797 -- if appropriate. If this is the completion of a deferred constant
6798 -- declaration, then this transformation generates what would be
6799 -- illegal code if written by hand, but that's OK.
6801 if Present (Expr) then
6802 if Rewrite_As_Renaming then
6803 Rewrite (N,
6804 Make_Object_Renaming_Declaration (Loc,
6805 Defining_Identifier => Defining_Identifier (N),
6806 Subtype_Mark => Obj_Def,
6807 Name => Expr_Q));
6809 -- We do not analyze this renaming declaration, because all its
6810 -- components have already been analyzed, and if we were to go
6811 -- ahead and analyze it, we would in effect be trying to generate
6812 -- another declaration of X, which won't do.
6814 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
6815 Set_Analyzed (N);
6817 -- We do need to deal with debug issues for this renaming
6819 -- First, if entity comes from source, then mark it as needing
6820 -- debug information, even though it is defined by a generated
6821 -- renaming that does not come from source.
6823 if Comes_From_Source (Defining_Identifier (N)) then
6824 Set_Debug_Info_Needed (Defining_Identifier (N));
6825 end if;
6827 -- Now call the routine to generate debug info for the renaming
6829 declare
6830 Decl : constant Node_Id := Debug_Renaming_Declaration (N);
6831 begin
6832 if Present (Decl) then
6833 Insert_Action (N, Decl);
6834 end if;
6835 end;
6836 end if;
6837 end if;
6839 -- Exception on library entity not available
6841 exception
6842 when RE_Not_Available =>
6843 return;
6844 end Expand_N_Object_Declaration;
6846 ---------------------------------
6847 -- Expand_N_Subtype_Indication --
6848 ---------------------------------
6850 -- Add a check on the range of the subtype. The static case is partially
6851 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
6852 -- to check here for the static case in order to avoid generating
6853 -- extraneous expanded code. Also deal with validity checking.
6855 procedure Expand_N_Subtype_Indication (N : Node_Id) is
6856 Ran : constant Node_Id := Range_Expression (Constraint (N));
6857 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6859 begin
6860 if Nkind (Constraint (N)) = N_Range_Constraint then
6861 Validity_Check_Range (Range_Expression (Constraint (N)));
6862 end if;
6864 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
6865 Apply_Range_Check (Ran, Typ);
6866 end if;
6867 end Expand_N_Subtype_Indication;
6869 ---------------------------
6870 -- Expand_N_Variant_Part --
6871 ---------------------------
6873 -- Note: this procedure no longer has any effect. It used to be that we
6874 -- would replace the choices in the last variant by a when others, and
6875 -- also expanded static predicates in variant choices here, but both of
6876 -- those activities were being done too early, since we can't check the
6877 -- choices until the statically predicated subtypes are frozen, which can
6878 -- happen as late as the free point of the record, and we can't change the
6879 -- last choice to an others before checking the choices, which is now done
6880 -- at the freeze point of the record.
6882 procedure Expand_N_Variant_Part (N : Node_Id) is
6883 begin
6884 null;
6885 end Expand_N_Variant_Part;
6887 ---------------------------------
6888 -- Expand_Previous_Access_Type --
6889 ---------------------------------
6891 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
6892 Ptr_Typ : Entity_Id;
6894 begin
6895 -- Find all access types in the current scope whose designated type is
6896 -- Def_Id and build master renamings for them.
6898 Ptr_Typ := First_Entity (Current_Scope);
6899 while Present (Ptr_Typ) loop
6900 if Is_Access_Type (Ptr_Typ)
6901 and then Designated_Type (Ptr_Typ) = Def_Id
6902 and then No (Master_Id (Ptr_Typ))
6903 then
6904 -- Ensure that the designated type has a master
6906 Build_Master_Entity (Def_Id);
6908 -- Private and incomplete types complicate the insertion of master
6909 -- renamings because the access type may precede the full view of
6910 -- the designated type. For this reason, the master renamings are
6911 -- inserted relative to the designated type.
6913 Build_Master_Renaming (Ptr_Typ, Ins_Nod => Parent (Def_Id));
6914 end if;
6916 Next_Entity (Ptr_Typ);
6917 end loop;
6918 end Expand_Previous_Access_Type;
6920 -----------------------------
6921 -- Expand_Record_Extension --
6922 -----------------------------
6924 -- Add a field _parent at the beginning of the record extension. This is
6925 -- used to implement inheritance. Here are some examples of expansion:
6927 -- 1. no discriminants
6928 -- type T2 is new T1 with null record;
6929 -- gives
6930 -- type T2 is new T1 with record
6931 -- _Parent : T1;
6932 -- end record;
6934 -- 2. renamed discriminants
6935 -- type T2 (B, C : Int) is new T1 (A => B) with record
6936 -- _Parent : T1 (A => B);
6937 -- D : Int;
6938 -- end;
6940 -- 3. inherited discriminants
6941 -- type T2 is new T1 with record -- discriminant A inherited
6942 -- _Parent : T1 (A);
6943 -- D : Int;
6944 -- end;
6946 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
6947 Indic : constant Node_Id := Subtype_Indication (Def);
6948 Loc : constant Source_Ptr := Sloc (Def);
6949 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
6950 Par_Subtype : Entity_Id;
6951 Comp_List : Node_Id;
6952 Comp_Decl : Node_Id;
6953 Parent_N : Node_Id;
6954 D : Entity_Id;
6955 List_Constr : constant List_Id := New_List;
6957 begin
6958 -- Expand_Record_Extension is called directly from the semantics, so
6959 -- we must check to see whether expansion is active before proceeding,
6960 -- because this affects the visibility of selected components in bodies
6961 -- of instances.
6963 if not Expander_Active then
6964 return;
6965 end if;
6967 -- This may be a derivation of an untagged private type whose full
6968 -- view is tagged, in which case the Derived_Type_Definition has no
6969 -- extension part. Build an empty one now.
6971 if No (Rec_Ext_Part) then
6972 Rec_Ext_Part :=
6973 Make_Record_Definition (Loc,
6974 End_Label => Empty,
6975 Component_List => Empty,
6976 Null_Present => True);
6978 Set_Record_Extension_Part (Def, Rec_Ext_Part);
6979 Mark_Rewrite_Insertion (Rec_Ext_Part);
6980 end if;
6982 Comp_List := Component_List (Rec_Ext_Part);
6984 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
6986 -- If the derived type inherits its discriminants the type of the
6987 -- _parent field must be constrained by the inherited discriminants
6989 if Has_Discriminants (T)
6990 and then Nkind (Indic) /= N_Subtype_Indication
6991 and then not Is_Constrained (Entity (Indic))
6992 then
6993 D := First_Discriminant (T);
6994 while Present (D) loop
6995 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
6996 Next_Discriminant (D);
6997 end loop;
6999 Par_Subtype :=
7000 Process_Subtype (
7001 Make_Subtype_Indication (Loc,
7002 Subtype_Mark => New_Occurrence_Of (Entity (Indic), Loc),
7003 Constraint =>
7004 Make_Index_Or_Discriminant_Constraint (Loc,
7005 Constraints => List_Constr)),
7006 Def);
7008 -- Otherwise the original subtype_indication is just what is needed
7010 else
7011 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
7012 end if;
7014 Set_Parent_Subtype (T, Par_Subtype);
7016 Comp_Decl :=
7017 Make_Component_Declaration (Loc,
7018 Defining_Identifier => Parent_N,
7019 Component_Definition =>
7020 Make_Component_Definition (Loc,
7021 Aliased_Present => False,
7022 Subtype_Indication => New_Occurrence_Of (Par_Subtype, Loc)));
7024 if Null_Present (Rec_Ext_Part) then
7025 Set_Component_List (Rec_Ext_Part,
7026 Make_Component_List (Loc,
7027 Component_Items => New_List (Comp_Decl),
7028 Variant_Part => Empty,
7029 Null_Present => False));
7030 Set_Null_Present (Rec_Ext_Part, False);
7032 elsif Null_Present (Comp_List)
7033 or else Is_Empty_List (Component_Items (Comp_List))
7034 then
7035 Set_Component_Items (Comp_List, New_List (Comp_Decl));
7036 Set_Null_Present (Comp_List, False);
7038 else
7039 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7040 end if;
7042 Analyze (Comp_Decl);
7043 end Expand_Record_Extension;
7045 ------------------------
7046 -- Expand_Tagged_Root --
7047 ------------------------
7049 procedure Expand_Tagged_Root (T : Entity_Id) is
7050 Def : constant Node_Id := Type_Definition (Parent (T));
7051 Comp_List : Node_Id;
7052 Comp_Decl : Node_Id;
7053 Sloc_N : Source_Ptr;
7055 begin
7056 if Null_Present (Def) then
7057 Set_Component_List (Def,
7058 Make_Component_List (Sloc (Def),
7059 Component_Items => Empty_List,
7060 Variant_Part => Empty,
7061 Null_Present => True));
7062 end if;
7064 Comp_List := Component_List (Def);
7066 if Null_Present (Comp_List)
7067 or else Is_Empty_List (Component_Items (Comp_List))
7068 then
7069 Sloc_N := Sloc (Comp_List);
7070 else
7071 Sloc_N := Sloc (First (Component_Items (Comp_List)));
7072 end if;
7074 Comp_Decl :=
7075 Make_Component_Declaration (Sloc_N,
7076 Defining_Identifier => First_Tag_Component (T),
7077 Component_Definition =>
7078 Make_Component_Definition (Sloc_N,
7079 Aliased_Present => False,
7080 Subtype_Indication => New_Occurrence_Of (RTE (RE_Tag), Sloc_N)));
7082 if Null_Present (Comp_List)
7083 or else Is_Empty_List (Component_Items (Comp_List))
7084 then
7085 Set_Component_Items (Comp_List, New_List (Comp_Decl));
7086 Set_Null_Present (Comp_List, False);
7088 else
7089 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
7090 end if;
7092 -- We don't Analyze the whole expansion because the tag component has
7093 -- already been analyzed previously. Here we just insure that the tree
7094 -- is coherent with the semantic decoration
7096 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
7098 exception
7099 when RE_Not_Available =>
7100 return;
7101 end Expand_Tagged_Root;
7103 ------------------------------
7104 -- Freeze_Stream_Operations --
7105 ------------------------------
7107 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
7108 Names : constant array (1 .. 4) of TSS_Name_Type :=
7109 (TSS_Stream_Input,
7110 TSS_Stream_Output,
7111 TSS_Stream_Read,
7112 TSS_Stream_Write);
7113 Stream_Op : Entity_Id;
7115 begin
7116 -- Primitive operations of tagged types are frozen when the dispatch
7117 -- table is constructed.
7119 if not Comes_From_Source (Typ) or else Is_Tagged_Type (Typ) then
7120 return;
7121 end if;
7123 for J in Names'Range loop
7124 Stream_Op := TSS (Typ, Names (J));
7126 if Present (Stream_Op)
7127 and then Is_Subprogram (Stream_Op)
7128 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
7129 N_Subprogram_Declaration
7130 and then not Is_Frozen (Stream_Op)
7131 then
7132 Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
7133 end if;
7134 end loop;
7135 end Freeze_Stream_Operations;
7137 -----------------
7138 -- Freeze_Type --
7139 -----------------
7141 -- Full type declarations are expanded at the point at which the type is
7142 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
7143 -- declarations generated by the freezing (e.g. the procedure generated
7144 -- for initialization) are chained in the Actions field list of the freeze
7145 -- node using Append_Freeze_Actions.
7147 -- WARNING: This routine manages Ghost regions. Return statements must be
7148 -- replaced by gotos which jump to the end of the routine and restore the
7149 -- Ghost mode.
7151 function Freeze_Type (N : Node_Id) return Boolean is
7152 procedure Process_RACW_Types (Typ : Entity_Id);
7153 -- Validate and generate stubs for all RACW types associated with type
7154 -- Typ.
7156 procedure Process_Pending_Access_Types (Typ : Entity_Id);
7157 -- Associate type Typ's Finalize_Address primitive with the finalization
7158 -- masters of pending access-to-Typ types.
7160 ------------------------
7161 -- Process_RACW_Types --
7162 ------------------------
7164 procedure Process_RACW_Types (Typ : Entity_Id) is
7165 List : constant Elist_Id := Access_Types_To_Process (N);
7166 E : Elmt_Id;
7167 Seen : Boolean := False;
7169 begin
7170 if Present (List) then
7171 E := First_Elmt (List);
7172 while Present (E) loop
7173 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
7174 Validate_RACW_Primitives (Node (E));
7175 Seen := True;
7176 end if;
7178 Next_Elmt (E);
7179 end loop;
7180 end if;
7182 -- If there are RACWs designating this type, make stubs now
7184 if Seen then
7185 Remote_Types_Tagged_Full_View_Encountered (Typ);
7186 end if;
7187 end Process_RACW_Types;
7189 ----------------------------------
7190 -- Process_Pending_Access_Types --
7191 ----------------------------------
7193 procedure Process_Pending_Access_Types (Typ : Entity_Id) is
7194 E : Elmt_Id;
7196 begin
7197 -- Finalize_Address is not generated in CodePeer mode because the
7198 -- body contains address arithmetic. This processing is disabled.
7200 if CodePeer_Mode then
7201 null;
7203 -- Certain itypes are generated for contexts that cannot allocate
7204 -- objects and should not set primitive Finalize_Address.
7206 elsif Is_Itype (Typ)
7207 and then Nkind (Associated_Node_For_Itype (Typ)) =
7208 N_Explicit_Dereference
7209 then
7210 null;
7212 -- When an access type is declared after the incomplete view of a
7213 -- Taft-amendment type, the access type is considered pending in
7214 -- case the full view of the Taft-amendment type is controlled. If
7215 -- this is indeed the case, associate the Finalize_Address routine
7216 -- of the full view with the finalization masters of all pending
7217 -- access types. This scenario applies to anonymous access types as
7218 -- well.
7220 elsif Needs_Finalization (Typ)
7221 and then Present (Pending_Access_Types (Typ))
7222 then
7223 E := First_Elmt (Pending_Access_Types (Typ));
7224 while Present (E) loop
7226 -- Generate:
7227 -- Set_Finalize_Address
7228 -- (Ptr_Typ, <Typ>FD'Unrestricted_Access);
7230 Append_Freeze_Action (Typ,
7231 Make_Set_Finalize_Address_Call
7232 (Loc => Sloc (N),
7233 Ptr_Typ => Node (E)));
7235 Next_Elmt (E);
7236 end loop;
7237 end if;
7238 end Process_Pending_Access_Types;
7240 -- Local variables
7242 Def_Id : constant Entity_Id := Entity (N);
7244 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
7245 -- Save the Ghost mode to restore on exit
7247 Result : Boolean := False;
7249 -- Start of processing for Freeze_Type
7251 begin
7252 -- The type being frozen may be subject to pragma Ghost. Set the mode
7253 -- now to ensure that any nodes generated during freezing are properly
7254 -- marked as Ghost.
7256 Set_Ghost_Mode (Def_Id);
7258 -- Process any remote access-to-class-wide types designating the type
7259 -- being frozen.
7261 Process_RACW_Types (Def_Id);
7263 -- Freeze processing for record types
7265 if Is_Record_Type (Def_Id) then
7266 if Ekind (Def_Id) = E_Record_Type then
7267 Expand_Freeze_Record_Type (N);
7268 elsif Is_Class_Wide_Type (Def_Id) then
7269 Expand_Freeze_Class_Wide_Type (N);
7270 end if;
7272 -- Freeze processing for array types
7274 elsif Is_Array_Type (Def_Id) then
7275 Expand_Freeze_Array_Type (N);
7277 -- Freeze processing for access types
7279 -- For pool-specific access types, find out the pool object used for
7280 -- this type, needs actual expansion of it in some cases. Here are the
7281 -- different cases :
7283 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
7284 -- ---> don't use any storage pool
7286 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
7287 -- Expand:
7288 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
7290 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7291 -- ---> Storage Pool is the specified one
7293 -- See GNAT Pool packages in the Run-Time for more details
7295 elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
7296 declare
7297 Loc : constant Source_Ptr := Sloc (N);
7298 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
7300 Freeze_Action_Typ : Entity_Id;
7301 Pool_Object : Entity_Id;
7303 begin
7304 -- Case 1
7306 -- Rep Clause "for Def_Id'Storage_Size use 0;"
7307 -- ---> don't use any storage pool
7309 if No_Pool_Assigned (Def_Id) then
7310 null;
7312 -- Case 2
7314 -- Rep Clause : for Def_Id'Storage_Size use Expr.
7315 -- ---> Expand:
7316 -- Def_Id__Pool : Stack_Bounded_Pool
7317 -- (Expr, DT'Size, DT'Alignment);
7319 elsif Has_Storage_Size_Clause (Def_Id) then
7320 declare
7321 DT_Align : Node_Id;
7322 DT_Size : Node_Id;
7324 begin
7325 -- For unconstrained composite types we give a size of zero
7326 -- so that the pool knows that it needs a special algorithm
7327 -- for variable size object allocation.
7329 if Is_Composite_Type (Desig_Type)
7330 and then not Is_Constrained (Desig_Type)
7331 then
7332 DT_Size := Make_Integer_Literal (Loc, 0);
7333 DT_Align := Make_Integer_Literal (Loc, Maximum_Alignment);
7335 else
7336 DT_Size :=
7337 Make_Attribute_Reference (Loc,
7338 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7339 Attribute_Name => Name_Max_Size_In_Storage_Elements);
7341 DT_Align :=
7342 Make_Attribute_Reference (Loc,
7343 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7344 Attribute_Name => Name_Alignment);
7345 end if;
7347 Pool_Object :=
7348 Make_Defining_Identifier (Loc,
7349 Chars => New_External_Name (Chars (Def_Id), 'P'));
7351 -- We put the code associated with the pools in the entity
7352 -- that has the later freeze node, usually the access type
7353 -- but it can also be the designated_type; because the pool
7354 -- code requires both those types to be frozen
7356 if Is_Frozen (Desig_Type)
7357 and then (No (Freeze_Node (Desig_Type))
7358 or else Analyzed (Freeze_Node (Desig_Type)))
7359 then
7360 Freeze_Action_Typ := Def_Id;
7362 -- A Taft amendment type cannot get the freeze actions
7363 -- since the full view is not there.
7365 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
7366 and then No (Full_View (Desig_Type))
7367 then
7368 Freeze_Action_Typ := Def_Id;
7370 else
7371 Freeze_Action_Typ := Desig_Type;
7372 end if;
7374 Append_Freeze_Action (Freeze_Action_Typ,
7375 Make_Object_Declaration (Loc,
7376 Defining_Identifier => Pool_Object,
7377 Object_Definition =>
7378 Make_Subtype_Indication (Loc,
7379 Subtype_Mark =>
7380 New_Occurrence_Of
7381 (RTE (RE_Stack_Bounded_Pool), Loc),
7383 Constraint =>
7384 Make_Index_Or_Discriminant_Constraint (Loc,
7385 Constraints => New_List (
7387 -- First discriminant is the Pool Size
7389 New_Occurrence_Of (
7390 Storage_Size_Variable (Def_Id), Loc),
7392 -- Second discriminant is the element size
7394 DT_Size,
7396 -- Third discriminant is the alignment
7398 DT_Align)))));
7399 end;
7401 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
7403 -- Case 3
7405 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7406 -- ---> Storage Pool is the specified one
7408 -- When compiling in Ada 2012 mode, ensure that the accessibility
7409 -- level of the subpool access type is not deeper than that of the
7410 -- pool_with_subpools.
7412 elsif Ada_Version >= Ada_2012
7413 and then Present (Associated_Storage_Pool (Def_Id))
7415 -- Omit this check for the case of a configurable run-time that
7416 -- does not provide package System.Storage_Pools.Subpools.
7418 and then RTE_Available (RE_Root_Storage_Pool_With_Subpools)
7419 then
7420 declare
7421 Loc : constant Source_Ptr := Sloc (Def_Id);
7422 Pool : constant Entity_Id :=
7423 Associated_Storage_Pool (Def_Id);
7424 RSPWS : constant Entity_Id :=
7425 RTE (RE_Root_Storage_Pool_With_Subpools);
7427 begin
7428 -- It is known that the accessibility level of the access
7429 -- type is deeper than that of the pool.
7431 if Type_Access_Level (Def_Id) > Object_Access_Level (Pool)
7432 and then not Accessibility_Checks_Suppressed (Def_Id)
7433 and then not Accessibility_Checks_Suppressed (Pool)
7434 then
7435 -- Static case: the pool is known to be a descendant of
7436 -- Root_Storage_Pool_With_Subpools.
7438 if Is_Ancestor (RSPWS, Etype (Pool)) then
7439 Error_Msg_N
7440 ("??subpool access type has deeper accessibility "
7441 & "level than pool", Def_Id);
7443 Append_Freeze_Action (Def_Id,
7444 Make_Raise_Program_Error (Loc,
7445 Reason => PE_Accessibility_Check_Failed));
7447 -- Dynamic case: when the pool is of a class-wide type,
7448 -- it may or may not support subpools depending on the
7449 -- path of derivation. Generate:
7451 -- if Def_Id in RSPWS'Class then
7452 -- raise Program_Error;
7453 -- end if;
7455 elsif Is_Class_Wide_Type (Etype (Pool)) then
7456 Append_Freeze_Action (Def_Id,
7457 Make_If_Statement (Loc,
7458 Condition =>
7459 Make_In (Loc,
7460 Left_Opnd => New_Occurrence_Of (Pool, Loc),
7461 Right_Opnd =>
7462 New_Occurrence_Of
7463 (Class_Wide_Type (RSPWS), Loc)),
7465 Then_Statements => New_List (
7466 Make_Raise_Program_Error (Loc,
7467 Reason => PE_Accessibility_Check_Failed))));
7468 end if;
7469 end if;
7470 end;
7471 end if;
7473 -- For access-to-controlled types (including class-wide types and
7474 -- Taft-amendment types, which potentially have controlled
7475 -- components), expand the list controller object that will store
7476 -- the dynamically allocated objects. Don't do this transformation
7477 -- for expander-generated access types, but do it for types that
7478 -- are the full view of types derived from other private types.
7479 -- Also suppress the list controller in the case of a designated
7480 -- type with convention Java, since this is used when binding to
7481 -- Java API specs, where there's no equivalent of a finalization
7482 -- list and we don't want to pull in the finalization support if
7483 -- not needed.
7485 if not Comes_From_Source (Def_Id)
7486 and then not Has_Private_Declaration (Def_Id)
7487 then
7488 null;
7490 -- An exception is made for types defined in the run-time because
7491 -- Ada.Tags.Tag itself is such a type and cannot afford this
7492 -- unnecessary overhead that would generates a loop in the
7493 -- expansion scheme. Another exception is if Restrictions
7494 -- (No_Finalization) is active, since then we know nothing is
7495 -- controlled.
7497 elsif Restriction_Active (No_Finalization)
7498 or else In_Runtime (Def_Id)
7499 then
7500 null;
7502 -- Create a finalization master for an access-to-controlled type
7503 -- or an access-to-incomplete type. It is assumed that the full
7504 -- view will be controlled.
7506 elsif Needs_Finalization (Desig_Type)
7507 or else (Is_Incomplete_Type (Desig_Type)
7508 and then No (Full_View (Desig_Type)))
7509 then
7510 Build_Finalization_Master (Def_Id);
7512 -- Create a finalization master when the designated type contains
7513 -- a private component. It is assumed that the full view will be
7514 -- controlled.
7516 elsif Has_Private_Component (Desig_Type) then
7517 Build_Finalization_Master
7518 (Typ => Def_Id,
7519 For_Private => True,
7520 Context_Scope => Scope (Def_Id),
7521 Insertion_Node => Declaration_Node (Desig_Type));
7522 end if;
7523 end;
7525 -- Freeze processing for enumeration types
7527 elsif Ekind (Def_Id) = E_Enumeration_Type then
7529 -- We only have something to do if we have a non-standard
7530 -- representation (i.e. at least one literal whose pos value
7531 -- is not the same as its representation)
7533 if Has_Non_Standard_Rep (Def_Id) then
7534 Expand_Freeze_Enumeration_Type (N);
7535 end if;
7537 -- Private types that are completed by a derivation from a private
7538 -- type have an internally generated full view, that needs to be
7539 -- frozen. This must be done explicitly because the two views share
7540 -- the freeze node, and the underlying full view is not visible when
7541 -- the freeze node is analyzed.
7543 elsif Is_Private_Type (Def_Id)
7544 and then Is_Derived_Type (Def_Id)
7545 and then Present (Full_View (Def_Id))
7546 and then Is_Itype (Full_View (Def_Id))
7547 and then Has_Private_Declaration (Full_View (Def_Id))
7548 and then Freeze_Node (Full_View (Def_Id)) = N
7549 then
7550 Set_Entity (N, Full_View (Def_Id));
7551 Result := Freeze_Type (N);
7552 Set_Entity (N, Def_Id);
7554 -- All other types require no expander action. There are such cases
7555 -- (e.g. task types and protected types). In such cases, the freeze
7556 -- nodes are there for use by Gigi.
7558 end if;
7560 -- Complete the initialization of all pending access types' finalization
7561 -- masters now that the designated type has been is frozen and primitive
7562 -- Finalize_Address generated.
7564 Process_Pending_Access_Types (Def_Id);
7565 Freeze_Stream_Operations (N, Def_Id);
7567 -- Generate the [spec and] body of the procedure tasked with the runtime
7568 -- verification of pragma Default_Initial_Condition's expression.
7570 if Has_DIC (Def_Id) then
7571 Build_DIC_Procedure_Body (Def_Id, For_Freeze => True);
7572 end if;
7574 -- Generate the [spec and] body of the invariant procedure tasked with
7575 -- the runtime verification of all invariants that pertain to the type.
7576 -- This includes invariants on the partial and full view, inherited
7577 -- class-wide invariants from parent types or interfaces, and invariants
7578 -- on array elements or record components.
7580 if Is_Interface (Def_Id) then
7582 -- Interfaces are treated as the partial view of a private type in
7583 -- order to achieve uniformity with the general case. As a result, an
7584 -- interface receives only a "partial" invariant procedure which is
7585 -- never called.
7587 if Has_Own_Invariants (Def_Id) then
7588 Build_Invariant_Procedure_Body
7589 (Typ => Def_Id,
7590 Partial_Invariant => Is_Interface (Def_Id));
7591 end if;
7593 -- Non-interface types
7595 -- Do not generate invariant procedure within other assertion
7596 -- subprograms, which may involve local declarations of local
7597 -- subtypes to which these checks do not apply.
7599 elsif Has_Invariants (Def_Id) then
7600 if Within_Internal_Subprogram
7601 or else (Ekind (Current_Scope) = E_Function
7602 and then Is_Predicate_Function (Current_Scope))
7603 then
7604 null;
7605 else
7606 Build_Invariant_Procedure_Body (Def_Id);
7607 end if;
7608 end if;
7610 Restore_Ghost_Mode (Saved_GM);
7612 return Result;
7614 exception
7615 when RE_Not_Available =>
7616 Restore_Ghost_Mode (Saved_GM);
7618 return False;
7619 end Freeze_Type;
7621 -------------------------
7622 -- Get_Simple_Init_Val --
7623 -------------------------
7625 function Get_Simple_Init_Val
7626 (T : Entity_Id;
7627 N : Node_Id;
7628 Size : Uint := No_Uint) return Node_Id
7630 Loc : constant Source_Ptr := Sloc (N);
7631 Val : Node_Id;
7632 Result : Node_Id;
7633 Val_RE : RE_Id;
7635 Size_To_Use : Uint;
7636 -- This is the size to be used for computation of the appropriate
7637 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
7639 IV_Attribute : constant Boolean :=
7640 Nkind (N) = N_Attribute_Reference
7641 and then Attribute_Name (N) = Name_Invalid_Value;
7643 Lo_Bound : Uint;
7644 Hi_Bound : Uint;
7645 -- These are the values computed by the procedure Check_Subtype_Bounds
7647 procedure Check_Subtype_Bounds;
7648 -- This procedure examines the subtype T, and its ancestor subtypes and
7649 -- derived types to determine the best known information about the
7650 -- bounds of the subtype. After the call Lo_Bound is set either to
7651 -- No_Uint if no information can be determined, or to a value which
7652 -- represents a known low bound, i.e. a valid value of the subtype can
7653 -- not be less than this value. Hi_Bound is similarly set to a known
7654 -- high bound (valid value cannot be greater than this).
7656 --------------------------
7657 -- Check_Subtype_Bounds --
7658 --------------------------
7660 procedure Check_Subtype_Bounds is
7661 ST1 : Entity_Id;
7662 ST2 : Entity_Id;
7663 Lo : Node_Id;
7664 Hi : Node_Id;
7665 Loval : Uint;
7666 Hival : Uint;
7668 begin
7669 Lo_Bound := No_Uint;
7670 Hi_Bound := No_Uint;
7672 -- Loop to climb ancestor subtypes and derived types
7674 ST1 := T;
7675 loop
7676 if not Is_Discrete_Type (ST1) then
7677 return;
7678 end if;
7680 Lo := Type_Low_Bound (ST1);
7681 Hi := Type_High_Bound (ST1);
7683 if Compile_Time_Known_Value (Lo) then
7684 Loval := Expr_Value (Lo);
7686 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
7687 Lo_Bound := Loval;
7688 end if;
7689 end if;
7691 if Compile_Time_Known_Value (Hi) then
7692 Hival := Expr_Value (Hi);
7694 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
7695 Hi_Bound := Hival;
7696 end if;
7697 end if;
7699 ST2 := Ancestor_Subtype (ST1);
7701 if No (ST2) then
7702 ST2 := Etype (ST1);
7703 end if;
7705 exit when ST1 = ST2;
7706 ST1 := ST2;
7707 end loop;
7708 end Check_Subtype_Bounds;
7710 -- Start of processing for Get_Simple_Init_Val
7712 begin
7713 -- For a private type, we should always have an underlying type (because
7714 -- this was already checked in Needs_Simple_Initialization). What we do
7715 -- is to get the value for the underlying type and then do an unchecked
7716 -- conversion to the private type.
7718 if Is_Private_Type (T) then
7719 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
7721 -- A special case, if the underlying value is null, then qualify it
7722 -- with the underlying type, so that the null is properly typed.
7723 -- Similarly, if it is an aggregate it must be qualified, because an
7724 -- unchecked conversion does not provide a context for it.
7726 if Nkind_In (Val, N_Null, N_Aggregate) then
7727 Val :=
7728 Make_Qualified_Expression (Loc,
7729 Subtype_Mark =>
7730 New_Occurrence_Of (Underlying_Type (T), Loc),
7731 Expression => Val);
7732 end if;
7734 Result := Unchecked_Convert_To (T, Val);
7736 -- Don't truncate result (important for Initialize/Normalize_Scalars)
7738 if Nkind (Result) = N_Unchecked_Type_Conversion
7739 and then Is_Scalar_Type (Underlying_Type (T))
7740 then
7741 Set_No_Truncation (Result);
7742 end if;
7744 return Result;
7746 -- Scalars with Default_Value aspect. The first subtype may now be
7747 -- private, so retrieve value from underlying type.
7749 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
7750 if Is_Private_Type (First_Subtype (T)) then
7751 return Unchecked_Convert_To (T,
7752 Default_Aspect_Value (Full_View (First_Subtype (T))));
7753 else
7754 return
7755 Convert_To (T, Default_Aspect_Value (First_Subtype (T)));
7756 end if;
7758 -- Otherwise, for scalars, we must have normalize/initialize scalars
7759 -- case, or if the node N is an 'Invalid_Value attribute node.
7761 elsif Is_Scalar_Type (T) then
7762 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
7764 -- Compute size of object. If it is given by the caller, we can use
7765 -- it directly, otherwise we use Esize (T) as an estimate. As far as
7766 -- we know this covers all cases correctly.
7768 if Size = No_Uint or else Size <= Uint_0 then
7769 Size_To_Use := UI_Max (Uint_1, Esize (T));
7770 else
7771 Size_To_Use := Size;
7772 end if;
7774 -- Maximum size to use is 64 bits, since we will create values of
7775 -- type Unsigned_64 and the range must fit this type.
7777 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
7778 Size_To_Use := Uint_64;
7779 end if;
7781 -- Check known bounds of subtype
7783 Check_Subtype_Bounds;
7785 -- Processing for Normalize_Scalars case
7787 if Normalize_Scalars and then not IV_Attribute then
7789 -- If zero is invalid, it is a convenient value to use that is
7790 -- for sure an appropriate invalid value in all situations.
7792 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7793 Val := Make_Integer_Literal (Loc, 0);
7795 -- Cases where all one bits is the appropriate invalid value
7797 -- For modular types, all 1 bits is either invalid or valid. If
7798 -- it is valid, then there is nothing that can be done since there
7799 -- are no invalid values (we ruled out zero already).
7801 -- For signed integer types that have no negative values, either
7802 -- there is room for negative values, or there is not. If there
7803 -- is, then all 1-bits may be interpreted as minus one, which is
7804 -- certainly invalid. Alternatively it is treated as the largest
7805 -- positive value, in which case the observation for modular types
7806 -- still applies.
7808 -- For float types, all 1-bits is a NaN (not a number), which is
7809 -- certainly an appropriately invalid value.
7811 elsif Is_Unsigned_Type (T)
7812 or else Is_Floating_Point_Type (T)
7813 or else Is_Enumeration_Type (T)
7814 then
7815 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
7817 -- Resolve as Unsigned_64, because the largest number we can
7818 -- generate is out of range of universal integer.
7820 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
7822 -- Case of signed types
7824 else
7825 declare
7826 Signed_Size : constant Uint :=
7827 UI_Min (Uint_63, Size_To_Use - 1);
7829 begin
7830 -- Normally we like to use the most negative number. The one
7831 -- exception is when this number is in the known subtype
7832 -- range and the largest positive number is not in the known
7833 -- subtype range.
7835 -- For this exceptional case, use largest positive value
7837 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
7838 and then Lo_Bound <= (-(2 ** Signed_Size))
7839 and then Hi_Bound < 2 ** Signed_Size
7840 then
7841 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
7843 -- Normal case of largest negative value
7845 else
7846 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
7847 end if;
7848 end;
7849 end if;
7851 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
7853 else
7854 -- For float types, use float values from System.Scalar_Values
7856 if Is_Floating_Point_Type (T) then
7857 if Root_Type (T) = Standard_Short_Float then
7858 Val_RE := RE_IS_Isf;
7859 elsif Root_Type (T) = Standard_Float then
7860 Val_RE := RE_IS_Ifl;
7861 elsif Root_Type (T) = Standard_Long_Float then
7862 Val_RE := RE_IS_Ilf;
7863 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
7864 Val_RE := RE_IS_Ill;
7865 end if;
7867 -- If zero is invalid, use zero values from System.Scalar_Values
7869 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7870 if Size_To_Use <= 8 then
7871 Val_RE := RE_IS_Iz1;
7872 elsif Size_To_Use <= 16 then
7873 Val_RE := RE_IS_Iz2;
7874 elsif Size_To_Use <= 32 then
7875 Val_RE := RE_IS_Iz4;
7876 else
7877 Val_RE := RE_IS_Iz8;
7878 end if;
7880 -- For unsigned, use unsigned values from System.Scalar_Values
7882 elsif Is_Unsigned_Type (T) then
7883 if Size_To_Use <= 8 then
7884 Val_RE := RE_IS_Iu1;
7885 elsif Size_To_Use <= 16 then
7886 Val_RE := RE_IS_Iu2;
7887 elsif Size_To_Use <= 32 then
7888 Val_RE := RE_IS_Iu4;
7889 else
7890 Val_RE := RE_IS_Iu8;
7891 end if;
7893 -- For signed, use signed values from System.Scalar_Values
7895 else
7896 if Size_To_Use <= 8 then
7897 Val_RE := RE_IS_Is1;
7898 elsif Size_To_Use <= 16 then
7899 Val_RE := RE_IS_Is2;
7900 elsif Size_To_Use <= 32 then
7901 Val_RE := RE_IS_Is4;
7902 else
7903 Val_RE := RE_IS_Is8;
7904 end if;
7905 end if;
7907 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
7908 end if;
7910 -- The final expression is obtained by doing an unchecked conversion
7911 -- of this result to the base type of the required subtype. Use the
7912 -- base type to prevent the unchecked conversion from chopping bits,
7913 -- and then we set Kill_Range_Check to preserve the "bad" value.
7915 Result := Unchecked_Convert_To (Base_Type (T), Val);
7917 -- Ensure result is not truncated, since we want the "bad" bits, and
7918 -- also kill range check on result.
7920 if Nkind (Result) = N_Unchecked_Type_Conversion then
7921 Set_No_Truncation (Result);
7922 Set_Kill_Range_Check (Result, True);
7923 end if;
7925 return Result;
7927 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
7929 elsif Is_Standard_String_Type (T) then
7930 pragma Assert (Init_Or_Norm_Scalars);
7932 return
7933 Make_Aggregate (Loc,
7934 Component_Associations => New_List (
7935 Make_Component_Association (Loc,
7936 Choices => New_List (
7937 Make_Others_Choice (Loc)),
7938 Expression =>
7939 Get_Simple_Init_Val
7940 (Component_Type (T), N, Esize (Root_Type (T))))));
7942 -- Access type is initialized to null
7944 elsif Is_Access_Type (T) then
7945 return Make_Null (Loc);
7947 -- No other possibilities should arise, since we should only be calling
7948 -- Get_Simple_Init_Val if Needs_Simple_Initialization returned True,
7949 -- indicating one of the above cases held.
7951 else
7952 raise Program_Error;
7953 end if;
7955 exception
7956 when RE_Not_Available =>
7957 return Empty;
7958 end Get_Simple_Init_Val;
7960 ------------------------------
7961 -- Has_New_Non_Standard_Rep --
7962 ------------------------------
7964 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
7965 begin
7966 if not Is_Derived_Type (T) then
7967 return Has_Non_Standard_Rep (T)
7968 or else Has_Non_Standard_Rep (Root_Type (T));
7970 -- If Has_Non_Standard_Rep is not set on the derived type, the
7971 -- representation is fully inherited.
7973 elsif not Has_Non_Standard_Rep (T) then
7974 return False;
7976 else
7977 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
7979 -- May need a more precise check here: the First_Rep_Item may be a
7980 -- stream attribute, which does not affect the representation of the
7981 -- type ???
7983 end if;
7984 end Has_New_Non_Standard_Rep;
7986 ----------------------
7987 -- Inline_Init_Proc --
7988 ----------------------
7990 function Inline_Init_Proc (Typ : Entity_Id) return Boolean is
7991 begin
7992 -- The initialization proc of protected records is not worth inlining.
7993 -- In addition, when compiled for another unit for inlining purposes,
7994 -- it may make reference to entities that have not been elaborated yet.
7995 -- The initialization proc of records that need finalization contains
7996 -- a nested clean-up procedure that makes it impractical to inline as
7997 -- well, except for simple controlled types themselves. And similar
7998 -- considerations apply to task types.
8000 if Is_Concurrent_Type (Typ) then
8001 return False;
8003 elsif Needs_Finalization (Typ) and then not Is_Controlled (Typ) then
8004 return False;
8006 elsif Has_Task (Typ) then
8007 return False;
8009 else
8010 return True;
8011 end if;
8012 end Inline_Init_Proc;
8014 ----------------
8015 -- In_Runtime --
8016 ----------------
8018 function In_Runtime (E : Entity_Id) return Boolean is
8019 S1 : Entity_Id;
8021 begin
8022 S1 := Scope (E);
8023 while Scope (S1) /= Standard_Standard loop
8024 S1 := Scope (S1);
8025 end loop;
8027 return Is_RTU (S1, System) or else Is_RTU (S1, Ada);
8028 end In_Runtime;
8030 ----------------------------
8031 -- Initialization_Warning --
8032 ----------------------------
8034 procedure Initialization_Warning (E : Entity_Id) is
8035 Warning_Needed : Boolean;
8037 begin
8038 Warning_Needed := False;
8040 if Ekind (Current_Scope) = E_Package
8041 and then Static_Elaboration_Desired (Current_Scope)
8042 then
8043 if Is_Type (E) then
8044 if Is_Record_Type (E) then
8045 if Has_Discriminants (E)
8046 or else Is_Limited_Type (E)
8047 or else Has_Non_Standard_Rep (E)
8048 then
8049 Warning_Needed := True;
8051 else
8052 -- Verify that at least one component has an initialization
8053 -- expression. No need for a warning on a type if all its
8054 -- components have no initialization.
8056 declare
8057 Comp : Entity_Id;
8059 begin
8060 Comp := First_Component (E);
8061 while Present (Comp) loop
8062 if Ekind (Comp) = E_Discriminant
8063 or else
8064 (Nkind (Parent (Comp)) = N_Component_Declaration
8065 and then Present (Expression (Parent (Comp))))
8066 then
8067 Warning_Needed := True;
8068 exit;
8069 end if;
8071 Next_Component (Comp);
8072 end loop;
8073 end;
8074 end if;
8076 if Warning_Needed then
8077 Error_Msg_N
8078 ("Objects of the type cannot be initialized statically "
8079 & "by default??", Parent (E));
8080 end if;
8081 end if;
8083 else
8084 Error_Msg_N ("Object cannot be initialized statically??", E);
8085 end if;
8086 end if;
8087 end Initialization_Warning;
8089 ------------------
8090 -- Init_Formals --
8091 ------------------
8093 function Init_Formals (Typ : Entity_Id) return List_Id is
8094 Loc : constant Source_Ptr := Sloc (Typ);
8095 Formals : List_Id;
8097 begin
8098 -- First parameter is always _Init : in out typ. Note that we need this
8099 -- to be in/out because in the case of the task record value, there
8100 -- are default record fields (_Priority, _Size, -Task_Info) that may
8101 -- be referenced in the generated initialization routine.
8103 Formals := New_List (
8104 Make_Parameter_Specification (Loc,
8105 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uInit),
8106 In_Present => True,
8107 Out_Present => True,
8108 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
8110 -- For task record value, or type that contains tasks, add two more
8111 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
8112 -- We also add these parameters for the task record type case.
8114 if Has_Task (Typ)
8115 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
8116 then
8117 Append_To (Formals,
8118 Make_Parameter_Specification (Loc,
8119 Defining_Identifier =>
8120 Make_Defining_Identifier (Loc, Name_uMaster),
8121 Parameter_Type =>
8122 New_Occurrence_Of (RTE (RE_Master_Id), Loc)));
8124 -- Add _Chain (not done for sequential elaboration policy, see
8125 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
8127 if Partition_Elaboration_Policy /= 'S' then
8128 Append_To (Formals,
8129 Make_Parameter_Specification (Loc,
8130 Defining_Identifier =>
8131 Make_Defining_Identifier (Loc, Name_uChain),
8132 In_Present => True,
8133 Out_Present => True,
8134 Parameter_Type =>
8135 New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)));
8136 end if;
8138 Append_To (Formals,
8139 Make_Parameter_Specification (Loc,
8140 Defining_Identifier =>
8141 Make_Defining_Identifier (Loc, Name_uTask_Name),
8142 In_Present => True,
8143 Parameter_Type => New_Occurrence_Of (Standard_String, Loc)));
8144 end if;
8146 return Formals;
8148 exception
8149 when RE_Not_Available =>
8150 return Empty_List;
8151 end Init_Formals;
8153 -------------------------
8154 -- Init_Secondary_Tags --
8155 -------------------------
8157 procedure Init_Secondary_Tags
8158 (Typ : Entity_Id;
8159 Target : Node_Id;
8160 Init_Tags_List : List_Id;
8161 Stmts_List : List_Id;
8162 Fixed_Comps : Boolean := True;
8163 Variable_Comps : Boolean := True)
8165 Loc : constant Source_Ptr := Sloc (Target);
8167 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
8168 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8170 procedure Initialize_Tag
8171 (Typ : Entity_Id;
8172 Iface : Entity_Id;
8173 Tag_Comp : Entity_Id;
8174 Iface_Tag : Node_Id);
8175 -- Initialize the tag of the secondary dispatch table of Typ associated
8176 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8177 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
8178 -- of Typ CPP tagged type we generate code to inherit the contents of
8179 -- the dispatch table directly from the ancestor.
8181 --------------------
8182 -- Initialize_Tag --
8183 --------------------
8185 procedure Initialize_Tag
8186 (Typ : Entity_Id;
8187 Iface : Entity_Id;
8188 Tag_Comp : Entity_Id;
8189 Iface_Tag : Node_Id)
8191 Comp_Typ : Entity_Id;
8192 Offset_To_Top_Comp : Entity_Id := Empty;
8194 begin
8195 -- Initialize pointer to secondary DT associated with the interface
8197 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8198 Append_To (Init_Tags_List,
8199 Make_Assignment_Statement (Loc,
8200 Name =>
8201 Make_Selected_Component (Loc,
8202 Prefix => New_Copy_Tree (Target),
8203 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8204 Expression =>
8205 New_Occurrence_Of (Iface_Tag, Loc)));
8206 end if;
8208 Comp_Typ := Scope (Tag_Comp);
8210 -- Initialize the entries of the table of interfaces. We generate a
8211 -- different call when the parent of the type has variable size
8212 -- components.
8214 if Comp_Typ /= Etype (Comp_Typ)
8215 and then Is_Variable_Size_Record (Etype (Comp_Typ))
8216 and then Chars (Tag_Comp) /= Name_uTag
8217 then
8218 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
8220 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
8221 -- configurable run-time environment.
8223 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
8224 Error_Msg_CRT
8225 ("variable size record with interface types", Typ);
8226 return;
8227 end if;
8229 -- Generate:
8230 -- Set_Dynamic_Offset_To_Top
8231 -- (This => Init,
8232 -- Prim_T => Typ'Tag,
8233 -- Interface_T => Iface'Tag,
8234 -- Offset_Value => n,
8235 -- Offset_Func => Fn'Address)
8237 Append_To (Stmts_List,
8238 Make_Procedure_Call_Statement (Loc,
8239 Name =>
8240 New_Occurrence_Of (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
8241 Parameter_Associations => New_List (
8242 Make_Attribute_Reference (Loc,
8243 Prefix => New_Copy_Tree (Target),
8244 Attribute_Name => Name_Address),
8246 Unchecked_Convert_To (RTE (RE_Tag),
8247 New_Occurrence_Of
8248 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc)),
8250 Unchecked_Convert_To (RTE (RE_Tag),
8251 New_Occurrence_Of
8252 (Node (First_Elmt (Access_Disp_Table (Iface))),
8253 Loc)),
8255 Unchecked_Convert_To
8256 (RTE (RE_Storage_Offset),
8257 Make_Attribute_Reference (Loc,
8258 Prefix =>
8259 Make_Selected_Component (Loc,
8260 Prefix => New_Copy_Tree (Target),
8261 Selector_Name =>
8262 New_Occurrence_Of (Tag_Comp, Loc)),
8263 Attribute_Name => Name_Position)),
8265 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
8266 Make_Attribute_Reference (Loc,
8267 Prefix => New_Occurrence_Of
8268 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
8269 Attribute_Name => Name_Address)))));
8271 -- In this case the next component stores the value of the offset
8272 -- to the top.
8274 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
8275 pragma Assert (Present (Offset_To_Top_Comp));
8277 Append_To (Init_Tags_List,
8278 Make_Assignment_Statement (Loc,
8279 Name =>
8280 Make_Selected_Component (Loc,
8281 Prefix => New_Copy_Tree (Target),
8282 Selector_Name =>
8283 New_Occurrence_Of (Offset_To_Top_Comp, Loc)),
8285 Expression =>
8286 Make_Attribute_Reference (Loc,
8287 Prefix =>
8288 Make_Selected_Component (Loc,
8289 Prefix => New_Copy_Tree (Target),
8290 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8291 Attribute_Name => Name_Position)));
8293 -- Normal case: No discriminants in the parent type
8295 else
8296 -- Don't need to set any value if this interface shares the
8297 -- primary dispatch table.
8299 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8300 Append_To (Stmts_List,
8301 Build_Set_Static_Offset_To_Top (Loc,
8302 Iface_Tag => New_Occurrence_Of (Iface_Tag, Loc),
8303 Offset_Value =>
8304 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8305 Make_Attribute_Reference (Loc,
8306 Prefix =>
8307 Make_Selected_Component (Loc,
8308 Prefix => New_Copy_Tree (Target),
8309 Selector_Name =>
8310 New_Occurrence_Of (Tag_Comp, Loc)),
8311 Attribute_Name => Name_Position))));
8312 end if;
8314 -- Generate:
8315 -- Register_Interface_Offset
8316 -- (Prim_T => Typ'Tag,
8317 -- Interface_T => Iface'Tag,
8318 -- Is_Constant => True,
8319 -- Offset_Value => n,
8320 -- Offset_Func => null);
8322 if RTE_Available (RE_Register_Interface_Offset) then
8323 Append_To (Stmts_List,
8324 Make_Procedure_Call_Statement (Loc,
8325 Name =>
8326 New_Occurrence_Of
8327 (RTE (RE_Register_Interface_Offset), Loc),
8328 Parameter_Associations => New_List (
8329 Unchecked_Convert_To (RTE (RE_Tag),
8330 New_Occurrence_Of
8331 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc)),
8333 Unchecked_Convert_To (RTE (RE_Tag),
8334 New_Occurrence_Of
8335 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
8337 New_Occurrence_Of (Standard_True, Loc),
8339 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8340 Make_Attribute_Reference (Loc,
8341 Prefix =>
8342 Make_Selected_Component (Loc,
8343 Prefix => New_Copy_Tree (Target),
8344 Selector_Name =>
8345 New_Occurrence_Of (Tag_Comp, Loc)),
8346 Attribute_Name => Name_Position)),
8348 Make_Null (Loc))));
8349 end if;
8350 end if;
8351 end Initialize_Tag;
8353 -- Local variables
8355 Full_Typ : Entity_Id;
8356 Ifaces_List : Elist_Id;
8357 Ifaces_Comp_List : Elist_Id;
8358 Ifaces_Tag_List : Elist_Id;
8359 Iface_Elmt : Elmt_Id;
8360 Iface_Comp_Elmt : Elmt_Id;
8361 Iface_Tag_Elmt : Elmt_Id;
8362 Tag_Comp : Node_Id;
8363 In_Variable_Pos : Boolean;
8365 -- Start of processing for Init_Secondary_Tags
8367 begin
8368 -- Handle private types
8370 if Present (Full_View (Typ)) then
8371 Full_Typ := Full_View (Typ);
8372 else
8373 Full_Typ := Typ;
8374 end if;
8376 Collect_Interfaces_Info
8377 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
8379 Iface_Elmt := First_Elmt (Ifaces_List);
8380 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
8381 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
8382 while Present (Iface_Elmt) loop
8383 Tag_Comp := Node (Iface_Comp_Elmt);
8385 -- Check if parent of record type has variable size components
8387 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
8388 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
8390 -- If we are compiling under the CPP full ABI compatibility mode and
8391 -- the ancestor is a CPP_Pragma tagged type then we generate code to
8392 -- initialize the secondary tag components from tags that reference
8393 -- secondary tables filled with copy of parent slots.
8395 if Is_CPP_Class (Root_Type (Full_Typ)) then
8397 -- Reject interface components located at variable offset in
8398 -- C++ derivations. This is currently unsupported.
8400 if not Fixed_Comps and then In_Variable_Pos then
8402 -- Locate the first dynamic component of the record. Done to
8403 -- improve the text of the warning.
8405 declare
8406 Comp : Entity_Id;
8407 Comp_Typ : Entity_Id;
8409 begin
8410 Comp := First_Entity (Typ);
8411 while Present (Comp) loop
8412 Comp_Typ := Etype (Comp);
8414 if Ekind (Comp) /= E_Discriminant
8415 and then not Is_Tag (Comp)
8416 then
8417 exit when
8418 (Is_Record_Type (Comp_Typ)
8419 and then
8420 Is_Variable_Size_Record (Base_Type (Comp_Typ)))
8421 or else
8422 (Is_Array_Type (Comp_Typ)
8423 and then Is_Variable_Size_Array (Comp_Typ));
8424 end if;
8426 Next_Entity (Comp);
8427 end loop;
8429 pragma Assert (Present (Comp));
8430 Error_Msg_Node_2 := Comp;
8431 Error_Msg_NE
8432 ("parent type & with dynamic component & cannot be parent"
8433 & " of 'C'P'P derivation if new interfaces are present",
8434 Typ, Scope (Original_Record_Component (Comp)));
8436 Error_Msg_Sloc :=
8437 Sloc (Scope (Original_Record_Component (Comp)));
8438 Error_Msg_NE
8439 ("type derived from 'C'P'P type & defined #",
8440 Typ, Scope (Original_Record_Component (Comp)));
8442 -- Avoid duplicated warnings
8444 exit;
8445 end;
8447 -- Initialize secondary tags
8449 else
8450 Append_To (Init_Tags_List,
8451 Make_Assignment_Statement (Loc,
8452 Name =>
8453 Make_Selected_Component (Loc,
8454 Prefix => New_Copy_Tree (Target),
8455 Selector_Name =>
8456 New_Occurrence_Of (Node (Iface_Comp_Elmt), Loc)),
8457 Expression =>
8458 New_Occurrence_Of (Node (Iface_Tag_Elmt), Loc)));
8459 end if;
8461 -- Otherwise generate code to initialize the tag
8463 else
8464 if (In_Variable_Pos and then Variable_Comps)
8465 or else (not In_Variable_Pos and then Fixed_Comps)
8466 then
8467 Initialize_Tag (Full_Typ,
8468 Iface => Node (Iface_Elmt),
8469 Tag_Comp => Tag_Comp,
8470 Iface_Tag => Node (Iface_Tag_Elmt));
8471 end if;
8472 end if;
8474 Next_Elmt (Iface_Elmt);
8475 Next_Elmt (Iface_Comp_Elmt);
8476 Next_Elmt (Iface_Tag_Elmt);
8477 end loop;
8478 end Init_Secondary_Tags;
8480 ------------------------
8481 -- Is_User_Defined_Eq --
8482 ------------------------
8484 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean is
8485 begin
8486 return Chars (Prim) = Name_Op_Eq
8487 and then Etype (First_Formal (Prim)) =
8488 Etype (Next_Formal (First_Formal (Prim)))
8489 and then Base_Type (Etype (Prim)) = Standard_Boolean;
8490 end Is_User_Defined_Equality;
8492 ----------------------------------------
8493 -- Make_Controlling_Function_Wrappers --
8494 ----------------------------------------
8496 procedure Make_Controlling_Function_Wrappers
8497 (Tag_Typ : Entity_Id;
8498 Decl_List : out List_Id;
8499 Body_List : out List_Id)
8501 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8502 Prim_Elmt : Elmt_Id;
8503 Subp : Entity_Id;
8504 Actual_List : List_Id;
8505 Formal_List : List_Id;
8506 Formal : Entity_Id;
8507 Par_Formal : Entity_Id;
8508 Formal_Node : Node_Id;
8509 Func_Body : Node_Id;
8510 Func_Decl : Node_Id;
8511 Func_Spec : Node_Id;
8512 Return_Stmt : Node_Id;
8514 begin
8515 Decl_List := New_List;
8516 Body_List := New_List;
8518 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
8519 while Present (Prim_Elmt) loop
8520 Subp := Node (Prim_Elmt);
8522 -- If a primitive function with a controlling result of the type has
8523 -- not been overridden by the user, then we must create a wrapper
8524 -- function here that effectively overrides it and invokes the
8525 -- (non-abstract) parent function. This can only occur for a null
8526 -- extension. Note that functions with anonymous controlling access
8527 -- results don't qualify and must be overridden. We also exclude
8528 -- Input attributes, since each type will have its own version of
8529 -- Input constructed by the expander. The test for Comes_From_Source
8530 -- is needed to distinguish inherited operations from renamings
8531 -- (which also have Alias set). We exclude internal entities with
8532 -- Interface_Alias to avoid generating duplicated wrappers since
8533 -- the primitive which covers the interface is also available in
8534 -- the list of primitive operations.
8536 -- The function may be abstract, or require_Overriding may be set
8537 -- for it, because tests for null extensions may already have reset
8538 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
8539 -- set, functions that need wrappers are recognized by having an
8540 -- alias that returns the parent type.
8542 if Comes_From_Source (Subp)
8543 or else No (Alias (Subp))
8544 or else Present (Interface_Alias (Subp))
8545 or else Ekind (Subp) /= E_Function
8546 or else not Has_Controlling_Result (Subp)
8547 or else Is_Access_Type (Etype (Subp))
8548 or else Is_Abstract_Subprogram (Alias (Subp))
8549 or else Is_TSS (Subp, TSS_Stream_Input)
8550 then
8551 goto Next_Prim;
8553 elsif Is_Abstract_Subprogram (Subp)
8554 or else Requires_Overriding (Subp)
8555 or else
8556 (Is_Null_Extension (Etype (Subp))
8557 and then Etype (Alias (Subp)) /= Etype (Subp))
8558 then
8559 Formal_List := No_List;
8560 Formal := First_Formal (Subp);
8562 if Present (Formal) then
8563 Formal_List := New_List;
8565 while Present (Formal) loop
8566 Append
8567 (Make_Parameter_Specification
8568 (Loc,
8569 Defining_Identifier =>
8570 Make_Defining_Identifier (Sloc (Formal),
8571 Chars => Chars (Formal)),
8572 In_Present => In_Present (Parent (Formal)),
8573 Out_Present => Out_Present (Parent (Formal)),
8574 Null_Exclusion_Present =>
8575 Null_Exclusion_Present (Parent (Formal)),
8576 Parameter_Type =>
8577 New_Occurrence_Of (Etype (Formal), Loc),
8578 Expression =>
8579 New_Copy_Tree (Expression (Parent (Formal)))),
8580 Formal_List);
8582 Next_Formal (Formal);
8583 end loop;
8584 end if;
8586 Func_Spec :=
8587 Make_Function_Specification (Loc,
8588 Defining_Unit_Name =>
8589 Make_Defining_Identifier (Loc,
8590 Chars => Chars (Subp)),
8591 Parameter_Specifications => Formal_List,
8592 Result_Definition =>
8593 New_Occurrence_Of (Etype (Subp), Loc));
8595 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
8596 Append_To (Decl_List, Func_Decl);
8598 -- Build a wrapper body that calls the parent function. The body
8599 -- contains a single return statement that returns an extension
8600 -- aggregate whose ancestor part is a call to the parent function,
8601 -- passing the formals as actuals (with any controlling arguments
8602 -- converted to the types of the corresponding formals of the
8603 -- parent function, which might be anonymous access types), and
8604 -- having a null extension.
8606 Formal := First_Formal (Subp);
8607 Par_Formal := First_Formal (Alias (Subp));
8608 Formal_Node := First (Formal_List);
8610 if Present (Formal) then
8611 Actual_List := New_List;
8612 else
8613 Actual_List := No_List;
8614 end if;
8616 while Present (Formal) loop
8617 if Is_Controlling_Formal (Formal) then
8618 Append_To (Actual_List,
8619 Make_Type_Conversion (Loc,
8620 Subtype_Mark =>
8621 New_Occurrence_Of (Etype (Par_Formal), Loc),
8622 Expression =>
8623 New_Occurrence_Of
8624 (Defining_Identifier (Formal_Node), Loc)));
8625 else
8626 Append_To
8627 (Actual_List,
8628 New_Occurrence_Of
8629 (Defining_Identifier (Formal_Node), Loc));
8630 end if;
8632 Next_Formal (Formal);
8633 Next_Formal (Par_Formal);
8634 Next (Formal_Node);
8635 end loop;
8637 Return_Stmt :=
8638 Make_Simple_Return_Statement (Loc,
8639 Expression =>
8640 Make_Extension_Aggregate (Loc,
8641 Ancestor_Part =>
8642 Make_Function_Call (Loc,
8643 Name =>
8644 New_Occurrence_Of (Alias (Subp), Loc),
8645 Parameter_Associations => Actual_List),
8646 Null_Record_Present => True));
8648 Func_Body :=
8649 Make_Subprogram_Body (Loc,
8650 Specification => New_Copy_Tree (Func_Spec),
8651 Declarations => Empty_List,
8652 Handled_Statement_Sequence =>
8653 Make_Handled_Sequence_Of_Statements (Loc,
8654 Statements => New_List (Return_Stmt)));
8656 Set_Defining_Unit_Name
8657 (Specification (Func_Body),
8658 Make_Defining_Identifier (Loc, Chars (Subp)));
8660 Append_To (Body_List, Func_Body);
8662 -- Replace the inherited function with the wrapper function in the
8663 -- primitive operations list. We add the minimum decoration needed
8664 -- to override interface primitives.
8666 Set_Ekind (Defining_Unit_Name (Func_Spec), E_Function);
8668 Override_Dispatching_Operation
8669 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec),
8670 Is_Wrapper => True);
8671 end if;
8673 <<Next_Prim>>
8674 Next_Elmt (Prim_Elmt);
8675 end loop;
8676 end Make_Controlling_Function_Wrappers;
8678 -------------------
8679 -- Make_Eq_Body --
8680 -------------------
8682 function Make_Eq_Body
8683 (Typ : Entity_Id;
8684 Eq_Name : Name_Id) return Node_Id
8686 Loc : constant Source_Ptr := Sloc (Parent (Typ));
8687 Decl : Node_Id;
8688 Def : constant Node_Id := Parent (Typ);
8689 Stmts : constant List_Id := New_List;
8690 Variant_Case : Boolean := Has_Discriminants (Typ);
8691 Comps : Node_Id := Empty;
8692 Typ_Def : Node_Id := Type_Definition (Def);
8694 begin
8695 Decl :=
8696 Predef_Spec_Or_Body (Loc,
8697 Tag_Typ => Typ,
8698 Name => Eq_Name,
8699 Profile => New_List (
8700 Make_Parameter_Specification (Loc,
8701 Defining_Identifier =>
8702 Make_Defining_Identifier (Loc, Name_X),
8703 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
8705 Make_Parameter_Specification (Loc,
8706 Defining_Identifier =>
8707 Make_Defining_Identifier (Loc, Name_Y),
8708 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
8710 Ret_Type => Standard_Boolean,
8711 For_Body => True);
8713 if Variant_Case then
8714 if Nkind (Typ_Def) = N_Derived_Type_Definition then
8715 Typ_Def := Record_Extension_Part (Typ_Def);
8716 end if;
8718 if Present (Typ_Def) then
8719 Comps := Component_List (Typ_Def);
8720 end if;
8722 Variant_Case :=
8723 Present (Comps) and then Present (Variant_Part (Comps));
8724 end if;
8726 if Variant_Case then
8727 Append_To (Stmts,
8728 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
8729 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
8730 Append_To (Stmts,
8731 Make_Simple_Return_Statement (Loc,
8732 Expression => New_Occurrence_Of (Standard_True, Loc)));
8734 else
8735 Append_To (Stmts,
8736 Make_Simple_Return_Statement (Loc,
8737 Expression =>
8738 Expand_Record_Equality
8739 (Typ,
8740 Typ => Typ,
8741 Lhs => Make_Identifier (Loc, Name_X),
8742 Rhs => Make_Identifier (Loc, Name_Y),
8743 Bodies => Declarations (Decl))));
8744 end if;
8746 Set_Handled_Statement_Sequence
8747 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8748 return Decl;
8749 end Make_Eq_Body;
8751 ------------------
8752 -- Make_Eq_Case --
8753 ------------------
8755 -- <Make_Eq_If shared components>
8757 -- case X.D1 is
8758 -- when V1 => <Make_Eq_Case> on subcomponents
8759 -- ...
8760 -- when Vn => <Make_Eq_Case> on subcomponents
8761 -- end case;
8763 function Make_Eq_Case
8764 (E : Entity_Id;
8765 CL : Node_Id;
8766 Discrs : Elist_Id := New_Elmt_List) return List_Id
8768 Loc : constant Source_Ptr := Sloc (E);
8769 Result : constant List_Id := New_List;
8770 Variant : Node_Id;
8771 Alt_List : List_Id;
8773 function Corresponding_Formal (C : Node_Id) return Entity_Id;
8774 -- Given the discriminant that controls a given variant of an unchecked
8775 -- union, find the formal of the equality function that carries the
8776 -- inferred value of the discriminant.
8778 function External_Name (E : Entity_Id) return Name_Id;
8779 -- The value of a given discriminant is conveyed in the corresponding
8780 -- formal parameter of the equality routine. The name of this formal
8781 -- parameter carries a one-character suffix which is removed here.
8783 --------------------------
8784 -- Corresponding_Formal --
8785 --------------------------
8787 function Corresponding_Formal (C : Node_Id) return Entity_Id is
8788 Discr : constant Entity_Id := Entity (Name (Variant_Part (C)));
8789 Elm : Elmt_Id;
8791 begin
8792 Elm := First_Elmt (Discrs);
8793 while Present (Elm) loop
8794 if Chars (Discr) = External_Name (Node (Elm)) then
8795 return Node (Elm);
8796 end if;
8798 Next_Elmt (Elm);
8799 end loop;
8801 -- A formal of the proper name must be found
8803 raise Program_Error;
8804 end Corresponding_Formal;
8806 -------------------
8807 -- External_Name --
8808 -------------------
8810 function External_Name (E : Entity_Id) return Name_Id is
8811 begin
8812 Get_Name_String (Chars (E));
8813 Name_Len := Name_Len - 1;
8814 return Name_Find;
8815 end External_Name;
8817 -- Start of processing for Make_Eq_Case
8819 begin
8820 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
8822 if No (Variant_Part (CL)) then
8823 return Result;
8824 end if;
8826 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
8828 if No (Variant) then
8829 return Result;
8830 end if;
8832 Alt_List := New_List;
8833 while Present (Variant) loop
8834 Append_To (Alt_List,
8835 Make_Case_Statement_Alternative (Loc,
8836 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
8837 Statements =>
8838 Make_Eq_Case (E, Component_List (Variant), Discrs)));
8839 Next_Non_Pragma (Variant);
8840 end loop;
8842 -- If we have an Unchecked_Union, use one of the parameters of the
8843 -- enclosing equality routine that captures the discriminant, to use
8844 -- as the expression in the generated case statement.
8846 if Is_Unchecked_Union (E) then
8847 Append_To (Result,
8848 Make_Case_Statement (Loc,
8849 Expression =>
8850 New_Occurrence_Of (Corresponding_Formal (CL), Loc),
8851 Alternatives => Alt_List));
8853 else
8854 Append_To (Result,
8855 Make_Case_Statement (Loc,
8856 Expression =>
8857 Make_Selected_Component (Loc,
8858 Prefix => Make_Identifier (Loc, Name_X),
8859 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
8860 Alternatives => Alt_List));
8861 end if;
8863 return Result;
8864 end Make_Eq_Case;
8866 ----------------
8867 -- Make_Eq_If --
8868 ----------------
8870 -- Generates:
8872 -- if
8873 -- X.C1 /= Y.C1
8874 -- or else
8875 -- X.C2 /= Y.C2
8876 -- ...
8877 -- then
8878 -- return False;
8879 -- end if;
8881 -- or a null statement if the list L is empty
8883 function Make_Eq_If
8884 (E : Entity_Id;
8885 L : List_Id) return Node_Id
8887 Loc : constant Source_Ptr := Sloc (E);
8888 C : Node_Id;
8889 Field_Name : Name_Id;
8890 Cond : Node_Id;
8892 begin
8893 if No (L) then
8894 return Make_Null_Statement (Loc);
8896 else
8897 Cond := Empty;
8899 C := First_Non_Pragma (L);
8900 while Present (C) loop
8901 Field_Name := Chars (Defining_Identifier (C));
8903 -- The tags must not be compared: they are not part of the value.
8904 -- Ditto for parent interfaces because their equality operator is
8905 -- abstract.
8907 -- Note also that in the following, we use Make_Identifier for
8908 -- the component names. Use of New_Occurrence_Of to identify the
8909 -- components would be incorrect because the wrong entities for
8910 -- discriminants could be picked up in the private type case.
8912 if Field_Name = Name_uParent
8913 and then Is_Interface (Etype (Defining_Identifier (C)))
8914 then
8915 null;
8917 elsif Field_Name /= Name_uTag then
8918 Evolve_Or_Else (Cond,
8919 Make_Op_Ne (Loc,
8920 Left_Opnd =>
8921 Make_Selected_Component (Loc,
8922 Prefix => Make_Identifier (Loc, Name_X),
8923 Selector_Name => Make_Identifier (Loc, Field_Name)),
8925 Right_Opnd =>
8926 Make_Selected_Component (Loc,
8927 Prefix => Make_Identifier (Loc, Name_Y),
8928 Selector_Name => Make_Identifier (Loc, Field_Name))));
8929 end if;
8931 Next_Non_Pragma (C);
8932 end loop;
8934 if No (Cond) then
8935 return Make_Null_Statement (Loc);
8937 else
8938 return
8939 Make_Implicit_If_Statement (E,
8940 Condition => Cond,
8941 Then_Statements => New_List (
8942 Make_Simple_Return_Statement (Loc,
8943 Expression => New_Occurrence_Of (Standard_False, Loc))));
8944 end if;
8945 end if;
8946 end Make_Eq_If;
8948 -------------------
8949 -- Make_Neq_Body --
8950 -------------------
8952 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id is
8954 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean;
8955 -- Returns true if Prim is a renaming of an unresolved predefined
8956 -- inequality operation.
8958 --------------------------------
8959 -- Is_Predefined_Neq_Renaming --
8960 --------------------------------
8962 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean is
8963 begin
8964 return Chars (Prim) /= Name_Op_Ne
8965 and then Present (Alias (Prim))
8966 and then Comes_From_Source (Prim)
8967 and then Is_Intrinsic_Subprogram (Alias (Prim))
8968 and then Chars (Alias (Prim)) = Name_Op_Ne;
8969 end Is_Predefined_Neq_Renaming;
8971 -- Local variables
8973 Loc : constant Source_Ptr := Sloc (Parent (Tag_Typ));
8974 Stmts : constant List_Id := New_List;
8975 Decl : Node_Id;
8976 Eq_Prim : Entity_Id;
8977 Left_Op : Entity_Id;
8978 Renaming_Prim : Entity_Id;
8979 Right_Op : Entity_Id;
8980 Target : Entity_Id;
8982 -- Start of processing for Make_Neq_Body
8984 begin
8985 -- For a call on a renaming of a dispatching subprogram that is
8986 -- overridden, if the overriding occurred before the renaming, then
8987 -- the body executed is that of the overriding declaration, even if the
8988 -- overriding declaration is not visible at the place of the renaming;
8989 -- otherwise, the inherited or predefined subprogram is called, see
8990 -- (RM 8.5.4(8))
8992 -- Stage 1: Search for a renaming of the inequality primitive and also
8993 -- search for an overriding of the equality primitive located before the
8994 -- renaming declaration.
8996 declare
8997 Elmt : Elmt_Id;
8998 Prim : Node_Id;
9000 begin
9001 Eq_Prim := Empty;
9002 Renaming_Prim := Empty;
9004 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9005 while Present (Elmt) loop
9006 Prim := Node (Elmt);
9008 if Is_User_Defined_Equality (Prim) and then No (Alias (Prim)) then
9009 if No (Renaming_Prim) then
9010 pragma Assert (No (Eq_Prim));
9011 Eq_Prim := Prim;
9012 end if;
9014 elsif Is_Predefined_Neq_Renaming (Prim) then
9015 Renaming_Prim := Prim;
9016 end if;
9018 Next_Elmt (Elmt);
9019 end loop;
9020 end;
9022 -- No further action needed if no renaming was found
9024 if No (Renaming_Prim) then
9025 return Empty;
9026 end if;
9028 -- Stage 2: Replace the renaming declaration by a subprogram declaration
9029 -- (required to add its body)
9031 Decl := Parent (Parent (Renaming_Prim));
9032 Rewrite (Decl,
9033 Make_Subprogram_Declaration (Loc,
9034 Specification => Specification (Decl)));
9035 Set_Analyzed (Decl);
9037 -- Remove the decoration of intrinsic renaming subprogram
9039 Set_Is_Intrinsic_Subprogram (Renaming_Prim, False);
9040 Set_Convention (Renaming_Prim, Convention_Ada);
9041 Set_Alias (Renaming_Prim, Empty);
9042 Set_Has_Completion (Renaming_Prim, False);
9044 -- Stage 3: Build the corresponding body
9046 Left_Op := First_Formal (Renaming_Prim);
9047 Right_Op := Next_Formal (Left_Op);
9049 Decl :=
9050 Predef_Spec_Or_Body (Loc,
9051 Tag_Typ => Tag_Typ,
9052 Name => Chars (Renaming_Prim),
9053 Profile => New_List (
9054 Make_Parameter_Specification (Loc,
9055 Defining_Identifier =>
9056 Make_Defining_Identifier (Loc, Chars (Left_Op)),
9057 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9059 Make_Parameter_Specification (Loc,
9060 Defining_Identifier =>
9061 Make_Defining_Identifier (Loc, Chars (Right_Op)),
9062 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9064 Ret_Type => Standard_Boolean,
9065 For_Body => True);
9067 -- If the overriding of the equality primitive occurred before the
9068 -- renaming, then generate:
9070 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9071 -- begin
9072 -- return not Oeq (X, Y);
9073 -- end;
9075 if Present (Eq_Prim) then
9076 Target := Eq_Prim;
9078 -- Otherwise build a nested subprogram which performs the predefined
9079 -- evaluation of the equality operator. That is, generate:
9081 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9082 -- function Oeq (X : Y) return Boolean is
9083 -- begin
9084 -- <<body of default implementation>>
9085 -- end;
9086 -- begin
9087 -- return not Oeq (X, Y);
9088 -- end;
9090 else
9091 declare
9092 Local_Subp : Node_Id;
9093 begin
9094 Local_Subp := Make_Eq_Body (Tag_Typ, Name_Op_Eq);
9095 Set_Declarations (Decl, New_List (Local_Subp));
9096 Target := Defining_Entity (Local_Subp);
9097 end;
9098 end if;
9100 Append_To (Stmts,
9101 Make_Simple_Return_Statement (Loc,
9102 Expression =>
9103 Make_Op_Not (Loc,
9104 Make_Function_Call (Loc,
9105 Name => New_Occurrence_Of (Target, Loc),
9106 Parameter_Associations => New_List (
9107 Make_Identifier (Loc, Chars (Left_Op)),
9108 Make_Identifier (Loc, Chars (Right_Op)))))));
9110 Set_Handled_Statement_Sequence
9111 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
9112 return Decl;
9113 end Make_Neq_Body;
9115 -------------------------------
9116 -- Make_Null_Procedure_Specs --
9117 -------------------------------
9119 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
9120 Decl_List : constant List_Id := New_List;
9121 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9122 Formal : Entity_Id;
9123 Formal_List : List_Id;
9124 New_Param_Spec : Node_Id;
9125 Parent_Subp : Entity_Id;
9126 Prim_Elmt : Elmt_Id;
9127 Subp : Entity_Id;
9129 begin
9130 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9131 while Present (Prim_Elmt) loop
9132 Subp := Node (Prim_Elmt);
9134 -- If a null procedure inherited from an interface has not been
9135 -- overridden, then we build a null procedure declaration to
9136 -- override the inherited procedure.
9138 Parent_Subp := Alias (Subp);
9140 if Present (Parent_Subp)
9141 and then Is_Null_Interface_Primitive (Parent_Subp)
9142 then
9143 Formal_List := No_List;
9144 Formal := First_Formal (Subp);
9146 if Present (Formal) then
9147 Formal_List := New_List;
9149 while Present (Formal) loop
9151 -- Copy the parameter spec including default expressions
9153 New_Param_Spec :=
9154 New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
9156 -- Generate a new defining identifier for the new formal.
9157 -- required because New_Copy_Tree does not duplicate
9158 -- semantic fields (except itypes).
9160 Set_Defining_Identifier (New_Param_Spec,
9161 Make_Defining_Identifier (Sloc (Formal),
9162 Chars => Chars (Formal)));
9164 -- For controlling arguments we must change their
9165 -- parameter type to reference the tagged type (instead
9166 -- of the interface type)
9168 if Is_Controlling_Formal (Formal) then
9169 if Nkind (Parameter_Type (Parent (Formal))) = N_Identifier
9170 then
9171 Set_Parameter_Type (New_Param_Spec,
9172 New_Occurrence_Of (Tag_Typ, Loc));
9174 else pragma Assert
9175 (Nkind (Parameter_Type (Parent (Formal))) =
9176 N_Access_Definition);
9177 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
9178 New_Occurrence_Of (Tag_Typ, Loc));
9179 end if;
9180 end if;
9182 Append (New_Param_Spec, Formal_List);
9184 Next_Formal (Formal);
9185 end loop;
9186 end if;
9188 Append_To (Decl_List,
9189 Make_Subprogram_Declaration (Loc,
9190 Make_Procedure_Specification (Loc,
9191 Defining_Unit_Name =>
9192 Make_Defining_Identifier (Loc, Chars (Subp)),
9193 Parameter_Specifications => Formal_List,
9194 Null_Present => True)));
9195 end if;
9197 Next_Elmt (Prim_Elmt);
9198 end loop;
9200 return Decl_List;
9201 end Make_Null_Procedure_Specs;
9203 -------------------------------------
9204 -- Make_Predefined_Primitive_Specs --
9205 -------------------------------------
9207 procedure Make_Predefined_Primitive_Specs
9208 (Tag_Typ : Entity_Id;
9209 Predef_List : out List_Id;
9210 Renamed_Eq : out Entity_Id)
9212 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
9213 -- Returns true if Prim is a renaming of an unresolved predefined
9214 -- equality operation.
9216 -------------------------------
9217 -- Is_Predefined_Eq_Renaming --
9218 -------------------------------
9220 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
9221 begin
9222 return Chars (Prim) /= Name_Op_Eq
9223 and then Present (Alias (Prim))
9224 and then Comes_From_Source (Prim)
9225 and then Is_Intrinsic_Subprogram (Alias (Prim))
9226 and then Chars (Alias (Prim)) = Name_Op_Eq;
9227 end Is_Predefined_Eq_Renaming;
9229 -- Local variables
9231 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9232 Res : constant List_Id := New_List;
9233 Eq_Name : Name_Id := Name_Op_Eq;
9234 Eq_Needed : Boolean;
9235 Eq_Spec : Node_Id;
9236 Prim : Elmt_Id;
9238 Has_Predef_Eq_Renaming : Boolean := False;
9239 -- Set to True if Tag_Typ has a primitive that renames the predefined
9240 -- equality operator. Used to implement (RM 8-5-4(8)).
9242 -- Start of processing for Make_Predefined_Primitive_Specs
9244 begin
9245 Renamed_Eq := Empty;
9247 -- Spec of _Size
9249 Append_To (Res, Predef_Spec_Or_Body (Loc,
9250 Tag_Typ => Tag_Typ,
9251 Name => Name_uSize,
9252 Profile => New_List (
9253 Make_Parameter_Specification (Loc,
9254 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9255 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9257 Ret_Type => Standard_Long_Long_Integer));
9259 -- Specs for dispatching stream attributes
9261 declare
9262 Stream_Op_TSS_Names :
9263 constant array (Positive range <>) of TSS_Name_Type :=
9264 (TSS_Stream_Read,
9265 TSS_Stream_Write,
9266 TSS_Stream_Input,
9267 TSS_Stream_Output);
9269 begin
9270 for Op in Stream_Op_TSS_Names'Range loop
9271 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
9272 Append_To (Res,
9273 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
9274 Stream_Op_TSS_Names (Op)));
9275 end if;
9276 end loop;
9277 end;
9279 -- Spec of "=" is expanded if the type is not limited and if a user
9280 -- defined "=" was not already declared for the non-full view of a
9281 -- private extension
9283 if not Is_Limited_Type (Tag_Typ) then
9284 Eq_Needed := True;
9285 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9286 while Present (Prim) loop
9288 -- If a primitive is encountered that renames the predefined
9289 -- equality operator before reaching any explicit equality
9290 -- primitive, then we still need to create a predefined equality
9291 -- function, because calls to it can occur via the renaming. A
9292 -- new name is created for the equality to avoid conflicting with
9293 -- any user-defined equality. (Note that this doesn't account for
9294 -- renamings of equality nested within subpackages???)
9296 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9297 Has_Predef_Eq_Renaming := True;
9298 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
9300 -- User-defined equality
9302 elsif Is_User_Defined_Equality (Node (Prim)) then
9303 if No (Alias (Node (Prim)))
9304 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
9305 N_Subprogram_Renaming_Declaration
9306 then
9307 Eq_Needed := False;
9308 exit;
9310 -- If the parent is not an interface type and has an abstract
9311 -- equality function explicitly defined in the sources, then
9312 -- the inherited equality is abstract as well, and no body can
9313 -- be created for it.
9315 elsif not Is_Interface (Etype (Tag_Typ))
9316 and then Present (Alias (Node (Prim)))
9317 and then Comes_From_Source (Alias (Node (Prim)))
9318 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
9319 then
9320 Eq_Needed := False;
9321 exit;
9323 -- If the type has an equality function corresponding with
9324 -- a primitive defined in an interface type, the inherited
9325 -- equality is abstract as well, and no body can be created
9326 -- for it.
9328 elsif Present (Alias (Node (Prim)))
9329 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
9330 and then
9331 Is_Interface
9332 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
9333 then
9334 Eq_Needed := False;
9335 exit;
9336 end if;
9337 end if;
9339 Next_Elmt (Prim);
9340 end loop;
9342 -- If a renaming of predefined equality was found but there was no
9343 -- user-defined equality (so Eq_Needed is still true), then set the
9344 -- name back to Name_Op_Eq. But in the case where a user-defined
9345 -- equality was located after such a renaming, then the predefined
9346 -- equality function is still needed, so Eq_Needed must be set back
9347 -- to True.
9349 if Eq_Name /= Name_Op_Eq then
9350 if Eq_Needed then
9351 Eq_Name := Name_Op_Eq;
9352 else
9353 Eq_Needed := True;
9354 end if;
9355 end if;
9357 if Eq_Needed then
9358 Eq_Spec := Predef_Spec_Or_Body (Loc,
9359 Tag_Typ => Tag_Typ,
9360 Name => Eq_Name,
9361 Profile => New_List (
9362 Make_Parameter_Specification (Loc,
9363 Defining_Identifier =>
9364 Make_Defining_Identifier (Loc, Name_X),
9365 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9367 Make_Parameter_Specification (Loc,
9368 Defining_Identifier =>
9369 Make_Defining_Identifier (Loc, Name_Y),
9370 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9371 Ret_Type => Standard_Boolean);
9372 Append_To (Res, Eq_Spec);
9374 if Has_Predef_Eq_Renaming then
9375 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
9377 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9378 while Present (Prim) loop
9380 -- Any renamings of equality that appeared before an
9381 -- overriding equality must be updated to refer to the
9382 -- entity for the predefined equality, otherwise calls via
9383 -- the renaming would get incorrectly resolved to call the
9384 -- user-defined equality function.
9386 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9387 Set_Alias (Node (Prim), Renamed_Eq);
9389 -- Exit upon encountering a user-defined equality
9391 elsif Chars (Node (Prim)) = Name_Op_Eq
9392 and then No (Alias (Node (Prim)))
9393 then
9394 exit;
9395 end if;
9397 Next_Elmt (Prim);
9398 end loop;
9399 end if;
9400 end if;
9402 -- Spec for dispatching assignment
9404 Append_To (Res, Predef_Spec_Or_Body (Loc,
9405 Tag_Typ => Tag_Typ,
9406 Name => Name_uAssign,
9407 Profile => New_List (
9408 Make_Parameter_Specification (Loc,
9409 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9410 Out_Present => True,
9411 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9413 Make_Parameter_Specification (Loc,
9414 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
9415 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)))));
9416 end if;
9418 -- Ada 2005: Generate declarations for the following primitive
9419 -- operations for limited interfaces and synchronized types that
9420 -- implement a limited interface.
9422 -- Disp_Asynchronous_Select
9423 -- Disp_Conditional_Select
9424 -- Disp_Get_Prim_Op_Kind
9425 -- Disp_Get_Task_Id
9426 -- Disp_Requeue
9427 -- Disp_Timed_Select
9429 -- Disable the generation of these bodies if No_Dispatching_Calls,
9430 -- Ravenscar or ZFP is active.
9432 if Ada_Version >= Ada_2005
9433 and then not Restriction_Active (No_Dispatching_Calls)
9434 and then not Restriction_Active (No_Select_Statements)
9435 and then RTE_Available (RE_Select_Specific_Data)
9436 then
9437 -- These primitives are defined abstract in interface types
9439 if Is_Interface (Tag_Typ)
9440 and then Is_Limited_Record (Tag_Typ)
9441 then
9442 Append_To (Res,
9443 Make_Abstract_Subprogram_Declaration (Loc,
9444 Specification =>
9445 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9447 Append_To (Res,
9448 Make_Abstract_Subprogram_Declaration (Loc,
9449 Specification =>
9450 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9452 Append_To (Res,
9453 Make_Abstract_Subprogram_Declaration (Loc,
9454 Specification =>
9455 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9457 Append_To (Res,
9458 Make_Abstract_Subprogram_Declaration (Loc,
9459 Specification =>
9460 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9462 Append_To (Res,
9463 Make_Abstract_Subprogram_Declaration (Loc,
9464 Specification =>
9465 Make_Disp_Requeue_Spec (Tag_Typ)));
9467 Append_To (Res,
9468 Make_Abstract_Subprogram_Declaration (Loc,
9469 Specification =>
9470 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9472 -- If ancestor is an interface type, declare non-abstract primitives
9473 -- to override the abstract primitives of the interface type.
9475 -- In VM targets we define these primitives in all root tagged types
9476 -- that are not interface types. Done because in VM targets we don't
9477 -- have secondary dispatch tables and any derivation of Tag_Typ may
9478 -- cover limited interfaces (which always have these primitives since
9479 -- they may be ancestors of synchronized interface types).
9481 elsif (not Is_Interface (Tag_Typ)
9482 and then Is_Interface (Etype (Tag_Typ))
9483 and then Is_Limited_Record (Etype (Tag_Typ)))
9484 or else
9485 (Is_Concurrent_Record_Type (Tag_Typ)
9486 and then Has_Interfaces (Tag_Typ))
9487 or else
9488 (not Tagged_Type_Expansion
9489 and then not Is_Interface (Tag_Typ)
9490 and then Tag_Typ = Root_Type (Tag_Typ))
9491 then
9492 Append_To (Res,
9493 Make_Subprogram_Declaration (Loc,
9494 Specification =>
9495 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9497 Append_To (Res,
9498 Make_Subprogram_Declaration (Loc,
9499 Specification =>
9500 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9502 Append_To (Res,
9503 Make_Subprogram_Declaration (Loc,
9504 Specification =>
9505 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9507 Append_To (Res,
9508 Make_Subprogram_Declaration (Loc,
9509 Specification =>
9510 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9512 Append_To (Res,
9513 Make_Subprogram_Declaration (Loc,
9514 Specification =>
9515 Make_Disp_Requeue_Spec (Tag_Typ)));
9517 Append_To (Res,
9518 Make_Subprogram_Declaration (Loc,
9519 Specification =>
9520 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9521 end if;
9522 end if;
9524 -- All tagged types receive their own Deep_Adjust and Deep_Finalize
9525 -- regardless of whether they are controlled or may contain controlled
9526 -- components.
9528 -- Do not generate the routines if finalization is disabled
9530 if Restriction_Active (No_Finalization) then
9531 null;
9533 else
9534 if not Is_Limited_Type (Tag_Typ) then
9535 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
9536 end if;
9538 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
9539 end if;
9541 Predef_List := Res;
9542 end Make_Predefined_Primitive_Specs;
9544 -------------------------
9545 -- Make_Tag_Assignment --
9546 -------------------------
9548 function Make_Tag_Assignment (N : Node_Id) return Node_Id is
9549 Loc : constant Source_Ptr := Sloc (N);
9550 Def_If : constant Entity_Id := Defining_Identifier (N);
9551 Expr : constant Node_Id := Expression (N);
9552 Typ : constant Entity_Id := Etype (Def_If);
9553 Full_Typ : constant Entity_Id := Underlying_Type (Typ);
9554 New_Ref : Node_Id;
9556 begin
9557 -- This expansion activity is called during analysis, but cannot
9558 -- be applied in ASIS mode when other expansion is disabled.
9560 if Is_Tagged_Type (Typ)
9561 and then not Is_Class_Wide_Type (Typ)
9562 and then not Is_CPP_Class (Typ)
9563 and then Tagged_Type_Expansion
9564 and then Nkind (Expr) /= N_Aggregate
9565 and then not ASIS_Mode
9566 and then (Nkind (Expr) /= N_Qualified_Expression
9567 or else Nkind (Expression (Expr)) /= N_Aggregate)
9568 then
9569 New_Ref :=
9570 Make_Selected_Component (Loc,
9571 Prefix => New_Occurrence_Of (Def_If, Loc),
9572 Selector_Name =>
9573 New_Occurrence_Of (First_Tag_Component (Full_Typ), Loc));
9574 Set_Assignment_OK (New_Ref);
9576 return
9577 Make_Assignment_Statement (Loc,
9578 Name => New_Ref,
9579 Expression =>
9580 Unchecked_Convert_To (RTE (RE_Tag),
9581 New_Occurrence_Of (Node
9582 (First_Elmt (Access_Disp_Table (Full_Typ))), Loc)));
9583 else
9584 return Empty;
9585 end if;
9586 end Make_Tag_Assignment;
9588 ---------------------------------
9589 -- Needs_Simple_Initialization --
9590 ---------------------------------
9592 function Needs_Simple_Initialization
9593 (T : Entity_Id;
9594 Consider_IS : Boolean := True) return Boolean
9596 Consider_IS_NS : constant Boolean :=
9597 Normalize_Scalars or (Initialize_Scalars and Consider_IS);
9599 begin
9600 -- Never need initialization if it is suppressed
9602 if Initialization_Suppressed (T) then
9603 return False;
9604 end if;
9606 -- Check for private type, in which case test applies to the underlying
9607 -- type of the private type.
9609 if Is_Private_Type (T) then
9610 declare
9611 RT : constant Entity_Id := Underlying_Type (T);
9612 begin
9613 if Present (RT) then
9614 return Needs_Simple_Initialization (RT);
9615 else
9616 return False;
9617 end if;
9618 end;
9620 -- Scalar type with Default_Value aspect requires initialization
9622 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
9623 return True;
9625 -- Cases needing simple initialization are access types, and, if pragma
9626 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
9627 -- types.
9629 elsif Is_Access_Type (T)
9630 or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
9631 then
9632 return True;
9634 -- If Initialize/Normalize_Scalars is in effect, string objects also
9635 -- need initialization, unless they are created in the course of
9636 -- expanding an aggregate (since in the latter case they will be
9637 -- filled with appropriate initializing values before they are used).
9639 elsif Consider_IS_NS
9640 and then Is_Standard_String_Type (T)
9641 and then
9642 (not Is_Itype (T)
9643 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
9644 then
9645 return True;
9647 else
9648 return False;
9649 end if;
9650 end Needs_Simple_Initialization;
9652 ----------------------
9653 -- Predef_Deep_Spec --
9654 ----------------------
9656 function Predef_Deep_Spec
9657 (Loc : Source_Ptr;
9658 Tag_Typ : Entity_Id;
9659 Name : TSS_Name_Type;
9660 For_Body : Boolean := False) return Node_Id
9662 Formals : List_Id;
9664 begin
9665 -- V : in out Tag_Typ
9667 Formals := New_List (
9668 Make_Parameter_Specification (Loc,
9669 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
9670 In_Present => True,
9671 Out_Present => True,
9672 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)));
9674 -- F : Boolean := True
9676 if Name = TSS_Deep_Adjust
9677 or else Name = TSS_Deep_Finalize
9678 then
9679 Append_To (Formals,
9680 Make_Parameter_Specification (Loc,
9681 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
9682 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
9683 Expression => New_Occurrence_Of (Standard_True, Loc)));
9684 end if;
9686 return
9687 Predef_Spec_Or_Body (Loc,
9688 Name => Make_TSS_Name (Tag_Typ, Name),
9689 Tag_Typ => Tag_Typ,
9690 Profile => Formals,
9691 For_Body => For_Body);
9693 exception
9694 when RE_Not_Available =>
9695 return Empty;
9696 end Predef_Deep_Spec;
9698 -------------------------
9699 -- Predef_Spec_Or_Body --
9700 -------------------------
9702 function Predef_Spec_Or_Body
9703 (Loc : Source_Ptr;
9704 Tag_Typ : Entity_Id;
9705 Name : Name_Id;
9706 Profile : List_Id;
9707 Ret_Type : Entity_Id := Empty;
9708 For_Body : Boolean := False) return Node_Id
9710 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
9711 Spec : Node_Id;
9713 begin
9714 Set_Is_Public (Id, Is_Public (Tag_Typ));
9716 -- The internal flag is set to mark these declarations because they have
9717 -- specific properties. First, they are primitives even if they are not
9718 -- defined in the type scope (the freezing point is not necessarily in
9719 -- the same scope). Second, the predefined equality can be overridden by
9720 -- a user-defined equality, no body will be generated in this case.
9722 Set_Is_Internal (Id);
9724 if not Debug_Generated_Code then
9725 Set_Debug_Info_Off (Id);
9726 end if;
9728 if No (Ret_Type) then
9729 Spec :=
9730 Make_Procedure_Specification (Loc,
9731 Defining_Unit_Name => Id,
9732 Parameter_Specifications => Profile);
9733 else
9734 Spec :=
9735 Make_Function_Specification (Loc,
9736 Defining_Unit_Name => Id,
9737 Parameter_Specifications => Profile,
9738 Result_Definition => New_Occurrence_Of (Ret_Type, Loc));
9739 end if;
9741 if Is_Interface (Tag_Typ) then
9742 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9744 -- If body case, return empty subprogram body. Note that this is ill-
9745 -- formed, because there is not even a null statement, and certainly not
9746 -- a return in the function case. The caller is expected to do surgery
9747 -- on the body to add the appropriate stuff.
9749 elsif For_Body then
9750 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
9752 -- For the case of an Input attribute predefined for an abstract type,
9753 -- generate an abstract specification. This will never be called, but we
9754 -- need the slot allocated in the dispatching table so that attributes
9755 -- typ'Class'Input and typ'Class'Output will work properly.
9757 elsif Is_TSS (Name, TSS_Stream_Input)
9758 and then Is_Abstract_Type (Tag_Typ)
9759 then
9760 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9762 -- Normal spec case, where we return a subprogram declaration
9764 else
9765 return Make_Subprogram_Declaration (Loc, Spec);
9766 end if;
9767 end Predef_Spec_Or_Body;
9769 -----------------------------
9770 -- Predef_Stream_Attr_Spec --
9771 -----------------------------
9773 function Predef_Stream_Attr_Spec
9774 (Loc : Source_Ptr;
9775 Tag_Typ : Entity_Id;
9776 Name : TSS_Name_Type;
9777 For_Body : Boolean := False) return Node_Id
9779 Ret_Type : Entity_Id;
9781 begin
9782 if Name = TSS_Stream_Input then
9783 Ret_Type := Tag_Typ;
9784 else
9785 Ret_Type := Empty;
9786 end if;
9788 return
9789 Predef_Spec_Or_Body
9790 (Loc,
9791 Name => Make_TSS_Name (Tag_Typ, Name),
9792 Tag_Typ => Tag_Typ,
9793 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
9794 Ret_Type => Ret_Type,
9795 For_Body => For_Body);
9796 end Predef_Stream_Attr_Spec;
9798 ---------------------------------
9799 -- Predefined_Primitive_Bodies --
9800 ---------------------------------
9802 function Predefined_Primitive_Bodies
9803 (Tag_Typ : Entity_Id;
9804 Renamed_Eq : Entity_Id) return List_Id
9806 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9807 Res : constant List_Id := New_List;
9808 Adj_Call : Node_Id;
9809 Decl : Node_Id;
9810 Fin_Call : Node_Id;
9811 Prim : Elmt_Id;
9812 Eq_Needed : Boolean;
9813 Eq_Name : Name_Id;
9814 Ent : Entity_Id;
9816 pragma Warnings (Off, Ent);
9818 begin
9819 pragma Assert (not Is_Interface (Tag_Typ));
9821 -- See if we have a predefined "=" operator
9823 if Present (Renamed_Eq) then
9824 Eq_Needed := True;
9825 Eq_Name := Chars (Renamed_Eq);
9827 -- If the parent is an interface type then it has defined all the
9828 -- predefined primitives abstract and we need to check if the type
9829 -- has some user defined "=" function which matches the profile of
9830 -- the Ada predefined equality operator to avoid generating it.
9832 elsif Is_Interface (Etype (Tag_Typ)) then
9833 Eq_Needed := True;
9834 Eq_Name := Name_Op_Eq;
9836 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9837 while Present (Prim) loop
9838 if Chars (Node (Prim)) = Name_Op_Eq
9839 and then not Is_Internal (Node (Prim))
9840 and then Present (First_Entity (Node (Prim)))
9842 -- The predefined equality primitive must have exactly two
9843 -- formals whose type is this tagged type
9845 and then Present (Last_Entity (Node (Prim)))
9846 and then Next_Entity (First_Entity (Node (Prim)))
9847 = Last_Entity (Node (Prim))
9848 and then Etype (First_Entity (Node (Prim))) = Tag_Typ
9849 and then Etype (Last_Entity (Node (Prim))) = Tag_Typ
9850 then
9851 Eq_Needed := False;
9852 Eq_Name := No_Name;
9853 exit;
9854 end if;
9856 Next_Elmt (Prim);
9857 end loop;
9859 else
9860 Eq_Needed := False;
9861 Eq_Name := No_Name;
9863 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9864 while Present (Prim) loop
9865 if Chars (Node (Prim)) = Name_Op_Eq
9866 and then Is_Internal (Node (Prim))
9867 then
9868 Eq_Needed := True;
9869 Eq_Name := Name_Op_Eq;
9870 exit;
9871 end if;
9873 Next_Elmt (Prim);
9874 end loop;
9875 end if;
9877 -- Body of _Size
9879 Decl := Predef_Spec_Or_Body (Loc,
9880 Tag_Typ => Tag_Typ,
9881 Name => Name_uSize,
9882 Profile => New_List (
9883 Make_Parameter_Specification (Loc,
9884 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9885 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9887 Ret_Type => Standard_Long_Long_Integer,
9888 For_Body => True);
9890 Set_Handled_Statement_Sequence (Decl,
9891 Make_Handled_Sequence_Of_Statements (Loc, New_List (
9892 Make_Simple_Return_Statement (Loc,
9893 Expression =>
9894 Make_Attribute_Reference (Loc,
9895 Prefix => Make_Identifier (Loc, Name_X),
9896 Attribute_Name => Name_Size)))));
9898 Append_To (Res, Decl);
9900 -- Bodies for Dispatching stream IO routines. We need these only for
9901 -- non-limited types (in the limited case there is no dispatching).
9902 -- We also skip them if dispatching or finalization are not available
9903 -- or if stream operations are prohibited by restriction No_Streams or
9904 -- from use of pragma/aspect No_Tagged_Streams.
9906 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
9907 and then No (TSS (Tag_Typ, TSS_Stream_Read))
9908 then
9909 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
9910 Append_To (Res, Decl);
9911 end if;
9913 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
9914 and then No (TSS (Tag_Typ, TSS_Stream_Write))
9915 then
9916 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
9917 Append_To (Res, Decl);
9918 end if;
9920 -- Skip body of _Input for the abstract case, since the corresponding
9921 -- spec is abstract (see Predef_Spec_Or_Body).
9923 if not Is_Abstract_Type (Tag_Typ)
9924 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
9925 and then No (TSS (Tag_Typ, TSS_Stream_Input))
9926 then
9927 Build_Record_Or_Elementary_Input_Function
9928 (Loc, Tag_Typ, Decl, Ent);
9929 Append_To (Res, Decl);
9930 end if;
9932 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
9933 and then No (TSS (Tag_Typ, TSS_Stream_Output))
9934 then
9935 Build_Record_Or_Elementary_Output_Procedure (Loc, Tag_Typ, Decl, Ent);
9936 Append_To (Res, Decl);
9937 end if;
9939 -- Ada 2005: Generate bodies for the following primitive operations for
9940 -- limited interfaces and synchronized types that implement a limited
9941 -- interface.
9943 -- disp_asynchronous_select
9944 -- disp_conditional_select
9945 -- disp_get_prim_op_kind
9946 -- disp_get_task_id
9947 -- disp_timed_select
9949 -- The interface versions will have null bodies
9951 -- Disable the generation of these bodies if No_Dispatching_Calls,
9952 -- Ravenscar or ZFP is active.
9954 -- In VM targets we define these primitives in all root tagged types
9955 -- that are not interface types. Done because in VM targets we don't
9956 -- have secondary dispatch tables and any derivation of Tag_Typ may
9957 -- cover limited interfaces (which always have these primitives since
9958 -- they may be ancestors of synchronized interface types).
9960 if Ada_Version >= Ada_2005
9961 and then not Is_Interface (Tag_Typ)
9962 and then
9963 ((Is_Interface (Etype (Tag_Typ))
9964 and then Is_Limited_Record (Etype (Tag_Typ)))
9965 or else
9966 (Is_Concurrent_Record_Type (Tag_Typ)
9967 and then Has_Interfaces (Tag_Typ))
9968 or else
9969 (not Tagged_Type_Expansion
9970 and then Tag_Typ = Root_Type (Tag_Typ)))
9971 and then not Restriction_Active (No_Dispatching_Calls)
9972 and then not Restriction_Active (No_Select_Statements)
9973 and then RTE_Available (RE_Select_Specific_Data)
9974 then
9975 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
9976 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
9977 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
9978 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
9979 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
9980 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
9981 end if;
9983 if not Is_Limited_Type (Tag_Typ) and then not Is_Interface (Tag_Typ) then
9985 -- Body for equality
9987 if Eq_Needed then
9988 Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
9989 Append_To (Res, Decl);
9990 end if;
9992 -- Body for inequality (if required)
9994 Decl := Make_Neq_Body (Tag_Typ);
9996 if Present (Decl) then
9997 Append_To (Res, Decl);
9998 end if;
10000 -- Body for dispatching assignment
10002 Decl :=
10003 Predef_Spec_Or_Body (Loc,
10004 Tag_Typ => Tag_Typ,
10005 Name => Name_uAssign,
10006 Profile => New_List (
10007 Make_Parameter_Specification (Loc,
10008 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10009 Out_Present => True,
10010 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10012 Make_Parameter_Specification (Loc,
10013 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
10014 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10015 For_Body => True);
10017 Set_Handled_Statement_Sequence (Decl,
10018 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10019 Make_Assignment_Statement (Loc,
10020 Name => Make_Identifier (Loc, Name_X),
10021 Expression => Make_Identifier (Loc, Name_Y)))));
10023 Append_To (Res, Decl);
10024 end if;
10026 -- Generate empty bodies of routines Deep_Adjust and Deep_Finalize for
10027 -- tagged types which do not contain controlled components.
10029 -- Do not generate the routines if finalization is disabled
10031 if Restriction_Active (No_Finalization) then
10032 null;
10034 elsif not Has_Controlled_Component (Tag_Typ) then
10035 if not Is_Limited_Type (Tag_Typ) then
10036 Adj_Call := Empty;
10037 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
10039 if Is_Controlled (Tag_Typ) then
10040 Adj_Call :=
10041 Make_Adjust_Call (
10042 Obj_Ref => Make_Identifier (Loc, Name_V),
10043 Typ => Tag_Typ);
10044 end if;
10046 if No (Adj_Call) then
10047 Adj_Call := Make_Null_Statement (Loc);
10048 end if;
10050 Set_Handled_Statement_Sequence (Decl,
10051 Make_Handled_Sequence_Of_Statements (Loc,
10052 Statements => New_List (Adj_Call)));
10054 Append_To (Res, Decl);
10055 end if;
10057 Fin_Call := Empty;
10058 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
10060 if Is_Controlled (Tag_Typ) then
10061 Fin_Call :=
10062 Make_Final_Call
10063 (Obj_Ref => Make_Identifier (Loc, Name_V),
10064 Typ => Tag_Typ);
10065 end if;
10067 if No (Fin_Call) then
10068 Fin_Call := Make_Null_Statement (Loc);
10069 end if;
10071 Set_Handled_Statement_Sequence (Decl,
10072 Make_Handled_Sequence_Of_Statements (Loc,
10073 Statements => New_List (Fin_Call)));
10075 Append_To (Res, Decl);
10076 end if;
10078 return Res;
10079 end Predefined_Primitive_Bodies;
10081 ---------------------------------
10082 -- Predefined_Primitive_Freeze --
10083 ---------------------------------
10085 function Predefined_Primitive_Freeze
10086 (Tag_Typ : Entity_Id) return List_Id
10088 Res : constant List_Id := New_List;
10089 Prim : Elmt_Id;
10090 Frnodes : List_Id;
10092 begin
10093 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10094 while Present (Prim) loop
10095 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
10096 Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
10098 if Present (Frnodes) then
10099 Append_List_To (Res, Frnodes);
10100 end if;
10101 end if;
10103 Next_Elmt (Prim);
10104 end loop;
10106 return Res;
10107 end Predefined_Primitive_Freeze;
10109 -------------------------
10110 -- Stream_Operation_OK --
10111 -------------------------
10113 function Stream_Operation_OK
10114 (Typ : Entity_Id;
10115 Operation : TSS_Name_Type) return Boolean
10117 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
10119 begin
10120 -- Special case of a limited type extension: a default implementation
10121 -- of the stream attributes Read or Write exists if that attribute
10122 -- has been specified or is available for an ancestor type; a default
10123 -- implementation of the attribute Output (resp. Input) exists if the
10124 -- attribute has been specified or Write (resp. Read) is available for
10125 -- an ancestor type. The last condition only applies under Ada 2005.
10127 if Is_Limited_Type (Typ) and then Is_Tagged_Type (Typ) then
10128 if Operation = TSS_Stream_Read then
10129 Has_Predefined_Or_Specified_Stream_Attribute :=
10130 Has_Specified_Stream_Read (Typ);
10132 elsif Operation = TSS_Stream_Write then
10133 Has_Predefined_Or_Specified_Stream_Attribute :=
10134 Has_Specified_Stream_Write (Typ);
10136 elsif Operation = TSS_Stream_Input then
10137 Has_Predefined_Or_Specified_Stream_Attribute :=
10138 Has_Specified_Stream_Input (Typ)
10139 or else
10140 (Ada_Version >= Ada_2005
10141 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
10143 elsif Operation = TSS_Stream_Output then
10144 Has_Predefined_Or_Specified_Stream_Attribute :=
10145 Has_Specified_Stream_Output (Typ)
10146 or else
10147 (Ada_Version >= Ada_2005
10148 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
10149 end if;
10151 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
10153 if not Has_Predefined_Or_Specified_Stream_Attribute
10154 and then Is_Derived_Type (Typ)
10155 and then (Operation = TSS_Stream_Read
10156 or else Operation = TSS_Stream_Write)
10157 then
10158 Has_Predefined_Or_Specified_Stream_Attribute :=
10159 Present
10160 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
10161 end if;
10162 end if;
10164 -- If the type is not limited, or else is limited but the attribute is
10165 -- explicitly specified or is predefined for the type, then return True,
10166 -- unless other conditions prevail, such as restrictions prohibiting
10167 -- streams or dispatching operations. We also return True for limited
10168 -- interfaces, because they may be extended by nonlimited types and
10169 -- permit inheritance in this case (addresses cases where an abstract
10170 -- extension doesn't get 'Input declared, as per comments below, but
10171 -- 'Class'Input must still be allowed). Note that attempts to apply
10172 -- stream attributes to a limited interface or its class-wide type
10173 -- (or limited extensions thereof) will still get properly rejected
10174 -- by Check_Stream_Attribute.
10176 -- We exclude the Input operation from being a predefined subprogram in
10177 -- the case where the associated type is an abstract extension, because
10178 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
10179 -- we don't want an abstract version created because types derived from
10180 -- the abstract type may not even have Input available (for example if
10181 -- derived from a private view of the abstract type that doesn't have
10182 -- a visible Input).
10184 -- Do not generate stream routines for type Finalization_Master because
10185 -- a master may never appear in types and therefore cannot be read or
10186 -- written.
10188 return
10189 (not Is_Limited_Type (Typ)
10190 or else Is_Interface (Typ)
10191 or else Has_Predefined_Or_Specified_Stream_Attribute)
10192 and then
10193 (Operation /= TSS_Stream_Input
10194 or else not Is_Abstract_Type (Typ)
10195 or else not Is_Derived_Type (Typ))
10196 and then not Has_Unknown_Discriminants (Typ)
10197 and then not
10198 (Is_Interface (Typ)
10199 and then
10200 (Is_Task_Interface (Typ)
10201 or else Is_Protected_Interface (Typ)
10202 or else Is_Synchronized_Interface (Typ)))
10203 and then not Restriction_Active (No_Streams)
10204 and then not Restriction_Active (No_Dispatch)
10205 and then No (No_Tagged_Streams_Pragma (Typ))
10206 and then not No_Run_Time_Mode
10207 and then RTE_Available (RE_Tag)
10208 and then No (Type_Without_Stream_Operation (Typ))
10209 and then RTE_Available (RE_Root_Stream_Type)
10210 and then not Is_RTE (Typ, RE_Finalization_Master);
10211 end Stream_Operation_OK;
10213 end Exp_Ch3;