Rebase.
[official-gcc.git] / gcc / ada / exp_ch3.adb
blobbd4886da51261faf1df4017c3897cfb175356f5b
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-2014, 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 Atree; use Atree;
27 with Checks; use Checks;
28 with Einfo; use Einfo;
29 with Errout; use Errout;
30 with Exp_Aggr; use Exp_Aggr;
31 with Exp_Atag; use Exp_Atag;
32 with Exp_Ch4; use Exp_Ch4;
33 with Exp_Ch6; use Exp_Ch6;
34 with Exp_Ch7; use Exp_Ch7;
35 with Exp_Ch9; use Exp_Ch9;
36 with Exp_Ch11; use Exp_Ch11;
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 Namet; use Namet;
46 with Nlists; use Nlists;
47 with Nmake; use Nmake;
48 with Opt; use Opt;
49 with Restrict; use Restrict;
50 with Rident; use Rident;
51 with Rtsfind; use Rtsfind;
52 with Sem; use Sem;
53 with Sem_Aux; use Sem_Aux;
54 with Sem_Attr; use Sem_Attr;
55 with Sem_Cat; use Sem_Cat;
56 with Sem_Ch3; use Sem_Ch3;
57 with Sem_Ch6; use Sem_Ch6;
58 with Sem_Ch8; use Sem_Ch8;
59 with Sem_Ch13; use Sem_Ch13;
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 Targparm; use Targparm;
71 with Tbuild; use Tbuild;
72 with Ttypes; use Ttypes;
73 with Validsw; use Validsw;
75 package body Exp_Ch3 is
77 -----------------------
78 -- Local Subprograms --
79 -----------------------
81 procedure Adjust_Discriminants (Rtype : Entity_Id);
82 -- This is used when freezing a record type. It attempts to construct
83 -- more restrictive subtypes for discriminants so that the max size of
84 -- the record can be calculated more accurately. See the body of this
85 -- procedure for details.
87 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
88 -- Build initialization procedure for given array type. Nod is a node
89 -- used for attachment of any actions required in its construction.
90 -- It also supplies the source location used for the procedure.
92 function Build_Array_Invariant_Proc
93 (A_Type : Entity_Id;
94 Nod : Node_Id) return Node_Id;
95 -- If the component of type of array type has invariants, build procedure
96 -- that checks invariant on all components of the array. Ada 2012 specifies
97 -- that an invariant on some type T must be applied to in-out parameters
98 -- and return values that include a part of type T. If the array type has
99 -- an otherwise specified invariant, the component check procedure is
100 -- called from within the user-specified invariant. Otherwise this becomes
101 -- the invariant procedure for the array type.
103 function Build_Record_Invariant_Proc
104 (R_Type : Entity_Id;
105 Nod : Node_Id) return Node_Id;
106 -- Ditto for record types.
108 function Build_Discriminant_Formals
109 (Rec_Id : Entity_Id;
110 Use_Dl : Boolean) return List_Id;
111 -- This function uses the discriminants of a type to build a list of
112 -- formal parameters, used in Build_Init_Procedure among other places.
113 -- If the flag Use_Dl is set, the list is built using the already
114 -- defined discriminals of the type, as is the case for concurrent
115 -- types with discriminants. Otherwise new identifiers are created,
116 -- with the source names of the discriminants.
118 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
119 -- This function builds a static aggregate that can serve as the initial
120 -- value for an array type whose bounds are static, and whose component
121 -- type is a composite type that has a static equivalent aggregate.
122 -- The equivalent array aggregate is used both for object initialization
123 -- and for component initialization, when used in the following function.
125 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
126 -- This function builds a static aggregate that can serve as the initial
127 -- value for a record type whose components are scalar and initialized
128 -- with compile-time values, or arrays with similar initialization or
129 -- defaults. When possible, initialization of an object of the type can
130 -- be achieved by using a copy of the aggregate as an initial value, thus
131 -- removing the implicit call that would otherwise constitute elaboration
132 -- code.
134 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id);
135 -- Build record initialization procedure. N is the type declaration
136 -- node, and Rec_Ent is the corresponding entity for the record type.
138 procedure Build_Slice_Assignment (Typ : Entity_Id);
139 -- Build assignment procedure for one-dimensional arrays of controlled
140 -- types. Other array and slice assignments are expanded in-line, but
141 -- the code expansion for controlled components (when control actions
142 -- are active) can lead to very large blocks that GCC3 handles poorly.
144 procedure Build_Untagged_Equality (Typ : Entity_Id);
145 -- AI05-0123: Equality on untagged records composes. This procedure
146 -- builds the equality routine for an untagged record that has components
147 -- of a record type that has user-defined primitive equality operations.
148 -- The resulting operation is a TSS subprogram.
150 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
151 -- Create An Equality function for the untagged variant record Typ and
152 -- attach it to the TSS list
154 procedure Check_Stream_Attributes (Typ : Entity_Id);
155 -- Check that if a limited extension has a parent with user-defined stream
156 -- attributes, and does not itself have user-defined stream-attributes,
157 -- then any limited component of the extension also has the corresponding
158 -- user-defined stream attributes.
160 procedure Clean_Task_Names
161 (Typ : Entity_Id;
162 Proc_Id : Entity_Id);
163 -- If an initialization procedure includes calls to generate names
164 -- for task subcomponents, indicate that secondary stack cleanup is
165 -- needed after an initialization. Typ is the component type, and Proc_Id
166 -- the initialization procedure for the enclosing composite type.
168 procedure Expand_Freeze_Array_Type (N : Node_Id);
169 -- Freeze an array type. Deals with building the initialization procedure,
170 -- creating the packed array type for a packed array and also with the
171 -- creation of the controlling procedures for the controlled case. The
172 -- argument N is the N_Freeze_Entity node for the type.
174 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id);
175 -- Freeze a class-wide type. Build routine Finalize_Address for the purpose
176 -- of finalizing controlled derivations from the class-wide's root type.
178 procedure Expand_Freeze_Enumeration_Type (N : Node_Id);
179 -- Freeze enumeration type with non-standard representation. Builds the
180 -- array and function needed to convert between enumeration pos and
181 -- enumeration representation values. N is the N_Freeze_Entity node
182 -- for the type.
184 procedure Expand_Freeze_Record_Type (N : Node_Id);
185 -- Freeze record type. Builds all necessary discriminant checking
186 -- and other ancillary functions, and builds dispatch tables where
187 -- needed. The argument N is the N_Freeze_Entity node. This processing
188 -- applies only to E_Record_Type entities, not to class wide types,
189 -- record subtypes, or private types.
191 procedure Expand_Tagged_Root (T : Entity_Id);
192 -- Add a field _Tag at the beginning of the record. This field carries
193 -- the value of the access to the Dispatch table. This procedure is only
194 -- called on root type, the _Tag field being inherited by the descendants.
196 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
197 -- Treat user-defined stream operations as renaming_as_body if the
198 -- subprogram they rename is not frozen when the type is frozen.
200 procedure Insert_Component_Invariant_Checks
201 (N : Node_Id;
202 Typ : Entity_Id;
203 Proc : Node_Id);
204 -- If a composite type has invariants and also has components with defined
205 -- invariants. the component invariant procedure is inserted into the user-
206 -- defined invariant procedure and added to the checks to be performed.
208 procedure Initialization_Warning (E : Entity_Id);
209 -- If static elaboration of the package is requested, indicate
210 -- when a type does meet the conditions for static initialization. If
211 -- E is a type, it has components that have no static initialization.
212 -- if E is an entity, its initial expression is not compile-time known.
214 function Init_Formals (Typ : Entity_Id) return List_Id;
215 -- This function builds the list of formals for an initialization routine.
216 -- The first formal is always _Init with the given type. For task value
217 -- record types and types containing tasks, three additional formals are
218 -- added:
220 -- _Master : Master_Id
221 -- _Chain : in out Activation_Chain
222 -- _Task_Name : String
224 -- The caller must append additional entries for discriminants if required.
226 function In_Runtime (E : Entity_Id) return Boolean;
227 -- Check if E is defined in the RTL (in a child of Ada or System). Used
228 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
230 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean;
231 -- Returns true if Prim is a user defined equality function
233 function Make_Eq_Body
234 (Typ : Entity_Id;
235 Eq_Name : Name_Id) return Node_Id;
236 -- Build the body of a primitive equality operation for a tagged record
237 -- type, or in Ada 2012 for any record type that has components with a
238 -- user-defined equality. Factored out of Predefined_Primitive_Bodies.
240 function Make_Eq_Case
241 (E : Entity_Id;
242 CL : Node_Id;
243 Discrs : Elist_Id := New_Elmt_List) return List_Id;
244 -- Building block for variant record equality. Defined to share the code
245 -- between the tagged and untagged case. Given a Component_List node CL,
246 -- it generates an 'if' followed by a 'case' statement that compares all
247 -- components of local temporaries named X and Y (that are declared as
248 -- formals at some upper level). E provides the Sloc to be used for the
249 -- generated code.
251 -- IF E is an unchecked_union, Discrs is the list of formals created for
252 -- the inferred discriminants of one operand. These formals are used in
253 -- the generated case statements for each variant of the unchecked union.
255 function Make_Eq_If
256 (E : Entity_Id;
257 L : List_Id) return Node_Id;
258 -- Building block for variant record equality. Defined to share the code
259 -- between the tagged and untagged case. Given the list of components
260 -- (or discriminants) L, it generates a return statement that compares all
261 -- components of local temporaries named X and Y (that are declared as
262 -- formals at some upper level). E provides the Sloc to be used for the
263 -- generated code.
265 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id;
266 -- Search for a renaming of the inequality dispatching primitive of
267 -- this tagged type. If found then build and return the corresponding
268 -- rename-as-body inequality subprogram; otherwise return Empty.
270 procedure Make_Predefined_Primitive_Specs
271 (Tag_Typ : Entity_Id;
272 Predef_List : out List_Id;
273 Renamed_Eq : out Entity_Id);
274 -- Create a list with the specs of the predefined primitive operations.
275 -- For tagged types that are interfaces all these primitives are defined
276 -- abstract.
278 -- The following entries are present for all tagged types, and provide
279 -- the results of the corresponding attribute applied to the object.
280 -- Dispatching is required in general, since the result of the attribute
281 -- will vary with the actual object subtype.
283 -- _size provides result of 'Size attribute
284 -- typSR provides result of 'Read attribute
285 -- typSW provides result of 'Write attribute
286 -- typSI provides result of 'Input attribute
287 -- typSO provides result of 'Output attribute
289 -- The following entries are additionally present for non-limited tagged
290 -- types, and implement additional dispatching operations for predefined
291 -- operations:
293 -- _equality implements "=" operator
294 -- _assign implements assignment operation
295 -- typDF implements deep finalization
296 -- typDA implements deep adjust
298 -- The latter two are empty procedures unless the type contains some
299 -- controlled components that require finalization actions (the deep
300 -- in the name refers to the fact that the action applies to components).
302 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
303 -- returns the value Empty, or else the defining unit name for the
304 -- predefined equality function in the case where the type has a primitive
305 -- operation that is a renaming of predefined equality (but only if there
306 -- is also an overriding user-defined equality function). The returned
307 -- Renamed_Eq will be passed to the corresponding parameter of
308 -- Predefined_Primitive_Bodies.
310 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
311 -- returns True if there are representation clauses for type T that are not
312 -- inherited. If the result is false, the init_proc and the discriminant
313 -- checking functions of the parent can be reused by a derived type.
315 procedure Make_Controlling_Function_Wrappers
316 (Tag_Typ : Entity_Id;
317 Decl_List : out List_Id;
318 Body_List : out List_Id);
319 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
320 -- associated with inherited functions with controlling results which
321 -- are not overridden. The body of each wrapper function consists solely
322 -- of a return statement whose expression is an extension aggregate
323 -- invoking the inherited subprogram's parent subprogram and extended
324 -- with a null association list.
326 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id;
327 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
328 -- null procedures inherited from an interface type that have not been
329 -- overridden. Only one null procedure will be created for a given set of
330 -- inherited null procedures with homographic profiles.
332 function Predef_Spec_Or_Body
333 (Loc : Source_Ptr;
334 Tag_Typ : Entity_Id;
335 Name : Name_Id;
336 Profile : List_Id;
337 Ret_Type : Entity_Id := Empty;
338 For_Body : Boolean := False) return Node_Id;
339 -- This function generates the appropriate expansion for a predefined
340 -- primitive operation specified by its name, parameter profile and
341 -- return type (Empty means this is a procedure). If For_Body is false,
342 -- then the returned node is a subprogram declaration. If For_Body is
343 -- true, then the returned node is a empty subprogram body containing
344 -- no declarations and no statements.
346 function Predef_Stream_Attr_Spec
347 (Loc : Source_Ptr;
348 Tag_Typ : Entity_Id;
349 Name : TSS_Name_Type;
350 For_Body : Boolean := False) return Node_Id;
351 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
352 -- input and output attribute whose specs are constructed in Exp_Strm.
354 function Predef_Deep_Spec
355 (Loc : Source_Ptr;
356 Tag_Typ : Entity_Id;
357 Name : TSS_Name_Type;
358 For_Body : Boolean := False) return Node_Id;
359 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
360 -- and _deep_finalize
362 function Predefined_Primitive_Bodies
363 (Tag_Typ : Entity_Id;
364 Renamed_Eq : Entity_Id) return List_Id;
365 -- Create the bodies of the predefined primitives that are described in
366 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
367 -- the defining unit name of the type's predefined equality as returned
368 -- by Make_Predefined_Primitive_Specs.
370 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
371 -- Freeze entities of all predefined primitive operations. This is needed
372 -- because the bodies of these operations do not normally do any freezing.
374 function Stream_Operation_OK
375 (Typ : Entity_Id;
376 Operation : TSS_Name_Type) return Boolean;
377 -- Check whether the named stream operation must be emitted for a given
378 -- type. The rules for inheritance of stream attributes by type extensions
379 -- are enforced by this function. Furthermore, various restrictions prevent
380 -- the generation of these operations, as a useful optimization or for
381 -- certification purposes.
383 --------------------------
384 -- Adjust_Discriminants --
385 --------------------------
387 -- This procedure attempts to define subtypes for discriminants that are
388 -- more restrictive than those declared. Such a replacement is possible if
389 -- we can demonstrate that values outside the restricted range would cause
390 -- constraint errors in any case. The advantage of restricting the
391 -- discriminant types in this way is that the maximum size of the variant
392 -- record can be calculated more conservatively.
394 -- An example of a situation in which we can perform this type of
395 -- restriction is the following:
397 -- subtype B is range 1 .. 10;
398 -- type Q is array (B range <>) of Integer;
400 -- type V (N : Natural) is record
401 -- C : Q (1 .. N);
402 -- end record;
404 -- In this situation, we can restrict the upper bound of N to 10, since
405 -- any larger value would cause a constraint error in any case.
407 -- There are many situations in which such restriction is possible, but
408 -- for now, we just look for cases like the above, where the component
409 -- in question is a one dimensional array whose upper bound is one of
410 -- the record discriminants. Also the component must not be part of
411 -- any variant part, since then the component does not always exist.
413 procedure Adjust_Discriminants (Rtype : Entity_Id) is
414 Loc : constant Source_Ptr := Sloc (Rtype);
415 Comp : Entity_Id;
416 Ctyp : Entity_Id;
417 Ityp : Entity_Id;
418 Lo : Node_Id;
419 Hi : Node_Id;
420 P : Node_Id;
421 Loval : Uint;
422 Discr : Entity_Id;
423 Dtyp : Entity_Id;
424 Dhi : Node_Id;
425 Dhiv : Uint;
426 Ahi : Node_Id;
427 Ahiv : Uint;
428 Tnn : Entity_Id;
430 begin
431 Comp := First_Component (Rtype);
432 while Present (Comp) loop
434 -- If our parent is a variant, quit, we do not look at components
435 -- that are in variant parts, because they may not always exist.
437 P := Parent (Comp); -- component declaration
438 P := Parent (P); -- component list
440 exit when Nkind (Parent (P)) = N_Variant;
442 -- We are looking for a one dimensional array type
444 Ctyp := Etype (Comp);
446 if not Is_Array_Type (Ctyp) or else Number_Dimensions (Ctyp) > 1 then
447 goto Continue;
448 end if;
450 -- The lower bound must be constant, and the upper bound is a
451 -- discriminant (which is a discriminant of the current record).
453 Ityp := Etype (First_Index (Ctyp));
454 Lo := Type_Low_Bound (Ityp);
455 Hi := Type_High_Bound (Ityp);
457 if not Compile_Time_Known_Value (Lo)
458 or else Nkind (Hi) /= N_Identifier
459 or else No (Entity (Hi))
460 or else Ekind (Entity (Hi)) /= E_Discriminant
461 then
462 goto Continue;
463 end if;
465 -- We have an array with appropriate bounds
467 Loval := Expr_Value (Lo);
468 Discr := Entity (Hi);
469 Dtyp := Etype (Discr);
471 -- See if the discriminant has a known upper bound
473 Dhi := Type_High_Bound (Dtyp);
475 if not Compile_Time_Known_Value (Dhi) then
476 goto Continue;
477 end if;
479 Dhiv := Expr_Value (Dhi);
481 -- See if base type of component array has known upper bound
483 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
485 if not Compile_Time_Known_Value (Ahi) then
486 goto Continue;
487 end if;
489 Ahiv := Expr_Value (Ahi);
491 -- The condition for doing the restriction is that the high bound
492 -- of the discriminant is greater than the low bound of the array,
493 -- and is also greater than the high bound of the base type index.
495 if Dhiv > Loval and then Dhiv > Ahiv then
497 -- We can reset the upper bound of the discriminant type to
498 -- whichever is larger, the low bound of the component, or
499 -- the high bound of the base type array index.
501 -- We build a subtype that is declared as
503 -- subtype Tnn is discr_type range discr_type'First .. max;
505 -- And insert this declaration into the tree. The type of the
506 -- discriminant is then reset to this more restricted subtype.
508 Tnn := Make_Temporary (Loc, 'T');
510 Insert_Action (Declaration_Node (Rtype),
511 Make_Subtype_Declaration (Loc,
512 Defining_Identifier => Tnn,
513 Subtype_Indication =>
514 Make_Subtype_Indication (Loc,
515 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
516 Constraint =>
517 Make_Range_Constraint (Loc,
518 Range_Expression =>
519 Make_Range (Loc,
520 Low_Bound =>
521 Make_Attribute_Reference (Loc,
522 Attribute_Name => Name_First,
523 Prefix => New_Occurrence_Of (Dtyp, Loc)),
524 High_Bound =>
525 Make_Integer_Literal (Loc,
526 Intval => UI_Max (Loval, Ahiv)))))));
528 Set_Etype (Discr, Tnn);
529 end if;
531 <<Continue>>
532 Next_Component (Comp);
533 end loop;
534 end Adjust_Discriminants;
536 ---------------------------
537 -- Build_Array_Init_Proc --
538 ---------------------------
540 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
541 Comp_Type : constant Entity_Id := Component_Type (A_Type);
542 Body_Stmts : List_Id;
543 Has_Default_Init : Boolean;
544 Index_List : List_Id;
545 Loc : Source_Ptr;
546 Proc_Id : Entity_Id;
548 function Init_Component return List_Id;
549 -- Create one statement to initialize one array component, designated
550 -- by a full set of indexes.
552 function Init_One_Dimension (N : Int) return List_Id;
553 -- Create loop to initialize one dimension of the array. The single
554 -- statement in the loop body initializes the inner dimensions if any,
555 -- or else the single component. Note that this procedure is called
556 -- recursively, with N being the dimension to be initialized. A call
557 -- with N greater than the number of dimensions simply generates the
558 -- component initialization, terminating the recursion.
560 --------------------
561 -- Init_Component --
562 --------------------
564 function Init_Component return List_Id is
565 Comp : Node_Id;
567 begin
568 Comp :=
569 Make_Indexed_Component (Loc,
570 Prefix => Make_Identifier (Loc, Name_uInit),
571 Expressions => Index_List);
573 if Has_Default_Aspect (A_Type) then
574 Set_Assignment_OK (Comp);
575 return New_List (
576 Make_Assignment_Statement (Loc,
577 Name => Comp,
578 Expression =>
579 Convert_To (Comp_Type,
580 Default_Aspect_Component_Value (First_Subtype (A_Type)))));
582 elsif Needs_Simple_Initialization (Comp_Type) then
583 Set_Assignment_OK (Comp);
584 return New_List (
585 Make_Assignment_Statement (Loc,
586 Name => Comp,
587 Expression =>
588 Get_Simple_Init_Val
589 (Comp_Type, Nod, Component_Size (A_Type))));
591 else
592 Clean_Task_Names (Comp_Type, Proc_Id);
593 return
594 Build_Initialization_Call
595 (Loc, Comp, Comp_Type,
596 In_Init_Proc => True,
597 Enclos_Type => A_Type);
598 end if;
599 end Init_Component;
601 ------------------------
602 -- Init_One_Dimension --
603 ------------------------
605 function Init_One_Dimension (N : Int) return List_Id is
606 Index : Entity_Id;
608 begin
609 -- If the component does not need initializing, then there is nothing
610 -- to do here, so we return a null body. This occurs when generating
611 -- the dummy Init_Proc needed for Initialize_Scalars processing.
613 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
614 and then not Needs_Simple_Initialization (Comp_Type)
615 and then not Has_Task (Comp_Type)
616 and then not Has_Default_Aspect (A_Type)
617 then
618 return New_List (Make_Null_Statement (Loc));
620 -- If all dimensions dealt with, we simply initialize the component
622 elsif N > Number_Dimensions (A_Type) then
623 return Init_Component;
625 -- Here we generate the required loop
627 else
628 Index :=
629 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
631 Append (New_Occurrence_Of (Index, Loc), Index_List);
633 return New_List (
634 Make_Implicit_Loop_Statement (Nod,
635 Identifier => Empty,
636 Iteration_Scheme =>
637 Make_Iteration_Scheme (Loc,
638 Loop_Parameter_Specification =>
639 Make_Loop_Parameter_Specification (Loc,
640 Defining_Identifier => Index,
641 Discrete_Subtype_Definition =>
642 Make_Attribute_Reference (Loc,
643 Prefix =>
644 Make_Identifier (Loc, Name_uInit),
645 Attribute_Name => Name_Range,
646 Expressions => New_List (
647 Make_Integer_Literal (Loc, N))))),
648 Statements => Init_One_Dimension (N + 1)));
649 end if;
650 end Init_One_Dimension;
652 -- Start of processing for Build_Array_Init_Proc
654 begin
655 -- The init proc is created when analyzing the freeze node for the type,
656 -- but it properly belongs with the array type declaration. However, if
657 -- the freeze node is for a subtype of a type declared in another unit
658 -- it seems preferable to use the freeze node as the source location of
659 -- the init proc. In any case this is preferable for gcov usage, and
660 -- the Sloc is not otherwise used by the compiler.
662 if In_Open_Scopes (Scope (A_Type)) then
663 Loc := Sloc (A_Type);
664 else
665 Loc := Sloc (Nod);
666 end if;
668 -- Nothing to generate in the following cases:
670 -- 1. Initialization is suppressed for the type
671 -- 2. The type is a value type, in the CIL sense.
672 -- 3. The type has CIL/JVM convention.
673 -- 4. An initialization already exists for the base type
675 if Initialization_Suppressed (A_Type)
676 or else Is_Value_Type (Comp_Type)
677 or else Convention (A_Type) = Convention_CIL
678 or else Convention (A_Type) = Convention_Java
679 or else Present (Base_Init_Proc (A_Type))
680 then
681 return;
682 end if;
684 Index_List := New_List;
686 -- We need an initialization procedure if any of the following is true:
688 -- 1. The component type has an initialization procedure
689 -- 2. The component type needs simple initialization
690 -- 3. Tasks are present
691 -- 4. The type is marked as a public entity
692 -- 5. The array type has a Default_Component_Value aspect
694 -- The reason for the public entity test is to deal properly with the
695 -- Initialize_Scalars pragma. This pragma can be set in the client and
696 -- not in the declaring package, this means the client will make a call
697 -- to the initialization procedure (because one of conditions 1-3 must
698 -- apply in this case), and we must generate a procedure (even if it is
699 -- null) to satisfy the call in this case.
701 -- Exception: do not build an array init_proc for a type whose root
702 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
703 -- is no place to put the code, and in any case we handle initialization
704 -- of such types (in the Initialize_Scalars case, that's the only time
705 -- the issue arises) in a special manner anyway which does not need an
706 -- init_proc.
708 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
709 or else Needs_Simple_Initialization (Comp_Type)
710 or else Has_Task (Comp_Type)
711 or else Has_Default_Aspect (A_Type);
713 if Has_Default_Init
714 or else (not Restriction_Active (No_Initialize_Scalars)
715 and then Is_Public (A_Type)
716 and then not Is_Standard_String_Type (A_Type))
717 then
718 Proc_Id :=
719 Make_Defining_Identifier (Loc,
720 Chars => Make_Init_Proc_Name (A_Type));
722 -- If No_Default_Initialization restriction is active, then we don't
723 -- want to build an init_proc, but we need to mark that an init_proc
724 -- would be needed if this restriction was not active (so that we can
725 -- detect attempts to call it), so set a dummy init_proc in place.
726 -- This is only done though when actual default initialization is
727 -- needed (and not done when only Is_Public is True), since otherwise
728 -- objects such as arrays of scalars could be wrongly flagged as
729 -- violating the restriction.
731 if Restriction_Active (No_Default_Initialization) then
732 if Has_Default_Init then
733 Set_Init_Proc (A_Type, Proc_Id);
734 end if;
736 return;
737 end if;
739 Body_Stmts := Init_One_Dimension (1);
741 Discard_Node (
742 Make_Subprogram_Body (Loc,
743 Specification =>
744 Make_Procedure_Specification (Loc,
745 Defining_Unit_Name => Proc_Id,
746 Parameter_Specifications => Init_Formals (A_Type)),
747 Declarations => New_List,
748 Handled_Statement_Sequence =>
749 Make_Handled_Sequence_Of_Statements (Loc,
750 Statements => Body_Stmts)));
752 Set_Ekind (Proc_Id, E_Procedure);
753 Set_Is_Public (Proc_Id, Is_Public (A_Type));
754 Set_Is_Internal (Proc_Id);
755 Set_Has_Completion (Proc_Id);
757 if not Debug_Generated_Code then
758 Set_Debug_Info_Off (Proc_Id);
759 end if;
761 -- Set inlined unless controlled stuff or tasks around, in which
762 -- case we do not want to inline, because nested stuff may cause
763 -- difficulties in inter-unit inlining, and furthermore there is
764 -- in any case no point in inlining such complex init procs.
766 if not Has_Task (Proc_Id)
767 and then not Needs_Finalization (Proc_Id)
768 then
769 Set_Is_Inlined (Proc_Id);
770 end if;
772 -- Associate Init_Proc with type, and determine if the procedure
773 -- is null (happens because of the Initialize_Scalars pragma case,
774 -- where we have to generate a null procedure in case it is called
775 -- by a client with Initialize_Scalars set). Such procedures have
776 -- to be generated, but do not have to be called, so we mark them
777 -- as null to suppress the call.
779 Set_Init_Proc (A_Type, Proc_Id);
781 if List_Length (Body_Stmts) = 1
783 -- We must skip SCIL nodes because they may have been added to this
784 -- list by Insert_Actions.
786 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
787 then
788 Set_Is_Null_Init_Proc (Proc_Id);
790 else
791 -- Try to build a static aggregate to statically initialize
792 -- objects of the type. This can only be done for constrained
793 -- one-dimensional arrays with static bounds.
795 Set_Static_Initialization
796 (Proc_Id,
797 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
798 end if;
799 end if;
800 end Build_Array_Init_Proc;
802 --------------------------------
803 -- Build_Array_Invariant_Proc --
804 --------------------------------
806 function Build_Array_Invariant_Proc
807 (A_Type : Entity_Id;
808 Nod : Node_Id) return Node_Id
810 Loc : constant Source_Ptr := Sloc (Nod);
812 Object_Name : constant Name_Id := New_Internal_Name ('I');
813 -- Name for argument of invariant procedure
815 Object_Entity : constant Node_Id :=
816 Make_Defining_Identifier (Loc, Object_Name);
817 -- The procedure declaration entity for the argument
819 Body_Stmts : List_Id;
820 Index_List : List_Id;
821 Proc_Id : Entity_Id;
822 Proc_Body : Node_Id;
824 function Build_Component_Invariant_Call return Node_Id;
825 -- Create one statement to verify invariant on one array component,
826 -- designated by a full set of indexes.
828 function Check_One_Dimension (N : Int) return List_Id;
829 -- Create loop to check on one dimension of the array. The single
830 -- statement in the loop body checks the inner dimensions if any, or
831 -- else a single component. This procedure is called recursively, with
832 -- N being the dimension to be initialized. A call with N greater than
833 -- the number of dimensions generates the component initialization
834 -- and terminates the recursion.
836 ------------------------------------
837 -- Build_Component_Invariant_Call --
838 ------------------------------------
840 function Build_Component_Invariant_Call return Node_Id is
841 Comp : Node_Id;
842 begin
843 Comp :=
844 Make_Indexed_Component (Loc,
845 Prefix => New_Occurrence_Of (Object_Entity, Loc),
846 Expressions => Index_List);
847 return
848 Make_Procedure_Call_Statement (Loc,
849 Name =>
850 New_Occurrence_Of
851 (Invariant_Procedure (Component_Type (A_Type)), Loc),
852 Parameter_Associations => New_List (Comp));
853 end Build_Component_Invariant_Call;
855 -------------------------
856 -- Check_One_Dimension --
857 -------------------------
859 function Check_One_Dimension (N : Int) return List_Id is
860 Index : Entity_Id;
862 begin
863 -- If all dimensions dealt with, we simply check invariant of the
864 -- component.
866 if N > Number_Dimensions (A_Type) then
867 return New_List (Build_Component_Invariant_Call);
869 -- Else generate one loop and recurse
871 else
872 Index :=
873 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
875 Append (New_Occurrence_Of (Index, Loc), Index_List);
877 return New_List (
878 Make_Implicit_Loop_Statement (Nod,
879 Identifier => Empty,
880 Iteration_Scheme =>
881 Make_Iteration_Scheme (Loc,
882 Loop_Parameter_Specification =>
883 Make_Loop_Parameter_Specification (Loc,
884 Defining_Identifier => Index,
885 Discrete_Subtype_Definition =>
886 Make_Attribute_Reference (Loc,
887 Prefix =>
888 New_Occurrence_Of (Object_Entity, Loc),
889 Attribute_Name => Name_Range,
890 Expressions => New_List (
891 Make_Integer_Literal (Loc, N))))),
892 Statements => Check_One_Dimension (N + 1)));
893 end if;
894 end Check_One_Dimension;
896 -- Start of processing for Build_Array_Invariant_Proc
898 begin
899 Index_List := New_List;
901 Proc_Id :=
902 Make_Defining_Identifier (Loc,
903 Chars => New_External_Name (Chars (A_Type), "CInvariant"));
905 Body_Stmts := Check_One_Dimension (1);
907 Proc_Body :=
908 Make_Subprogram_Body (Loc,
909 Specification =>
910 Make_Procedure_Specification (Loc,
911 Defining_Unit_Name => Proc_Id,
912 Parameter_Specifications => New_List (
913 Make_Parameter_Specification (Loc,
914 Defining_Identifier => Object_Entity,
915 Parameter_Type => New_Occurrence_Of (A_Type, Loc)))),
917 Declarations => Empty_List,
918 Handled_Statement_Sequence =>
919 Make_Handled_Sequence_Of_Statements (Loc,
920 Statements => Body_Stmts));
922 Set_Ekind (Proc_Id, E_Procedure);
923 Set_Is_Public (Proc_Id, Is_Public (A_Type));
924 Set_Is_Internal (Proc_Id);
925 Set_Has_Completion (Proc_Id);
927 if not Debug_Generated_Code then
928 Set_Debug_Info_Off (Proc_Id);
929 end if;
931 return Proc_Body;
932 end Build_Array_Invariant_Proc;
934 --------------------------------
935 -- Build_Discr_Checking_Funcs --
936 --------------------------------
938 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
939 Rec_Id : Entity_Id;
940 Loc : Source_Ptr;
941 Enclosing_Func_Id : Entity_Id;
942 Sequence : Nat := 1;
943 Type_Def : Node_Id;
944 V : Node_Id;
946 function Build_Case_Statement
947 (Case_Id : Entity_Id;
948 Variant : Node_Id) return Node_Id;
949 -- Build a case statement containing only two alternatives. The first
950 -- alternative corresponds exactly to the discrete choices given on the
951 -- variant with contains the components that we are generating the
952 -- checks for. If the discriminant is one of these return False. The
953 -- second alternative is an OTHERS choice that will return True
954 -- indicating the discriminant did not match.
956 function Build_Dcheck_Function
957 (Case_Id : Entity_Id;
958 Variant : Node_Id) return Entity_Id;
959 -- Build the discriminant checking function for a given variant
961 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
962 -- Builds the discriminant checking function for each variant of the
963 -- given variant part of the record type.
965 --------------------------
966 -- Build_Case_Statement --
967 --------------------------
969 function Build_Case_Statement
970 (Case_Id : Entity_Id;
971 Variant : Node_Id) return Node_Id
973 Alt_List : constant List_Id := New_List;
974 Actuals_List : List_Id;
975 Case_Node : Node_Id;
976 Case_Alt_Node : Node_Id;
977 Choice : Node_Id;
978 Choice_List : List_Id;
979 D : Entity_Id;
980 Return_Node : Node_Id;
982 begin
983 Case_Node := New_Node (N_Case_Statement, Loc);
985 -- Replace the discriminant which controls the variant with the name
986 -- of the formal of the checking function.
988 Set_Expression (Case_Node, Make_Identifier (Loc, Chars (Case_Id)));
990 Choice := First (Discrete_Choices (Variant));
992 if Nkind (Choice) = N_Others_Choice then
993 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
994 else
995 Choice_List := New_Copy_List (Discrete_Choices (Variant));
996 end if;
998 if not Is_Empty_List (Choice_List) then
999 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1000 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1002 -- In case this is a nested variant, we need to return the result
1003 -- of the discriminant checking function for the immediately
1004 -- enclosing variant.
1006 if Present (Enclosing_Func_Id) then
1007 Actuals_List := New_List;
1009 D := First_Discriminant (Rec_Id);
1010 while Present (D) loop
1011 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
1012 Next_Discriminant (D);
1013 end loop;
1015 Return_Node :=
1016 Make_Simple_Return_Statement (Loc,
1017 Expression =>
1018 Make_Function_Call (Loc,
1019 Name =>
1020 New_Occurrence_Of (Enclosing_Func_Id, Loc),
1021 Parameter_Associations =>
1022 Actuals_List));
1024 else
1025 Return_Node :=
1026 Make_Simple_Return_Statement (Loc,
1027 Expression =>
1028 New_Occurrence_Of (Standard_False, Loc));
1029 end if;
1031 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1032 Append (Case_Alt_Node, Alt_List);
1033 end if;
1035 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1036 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
1037 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1039 Return_Node :=
1040 Make_Simple_Return_Statement (Loc,
1041 Expression =>
1042 New_Occurrence_Of (Standard_True, Loc));
1044 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1045 Append (Case_Alt_Node, Alt_List);
1047 Set_Alternatives (Case_Node, Alt_List);
1048 return Case_Node;
1049 end Build_Case_Statement;
1051 ---------------------------
1052 -- Build_Dcheck_Function --
1053 ---------------------------
1055 function Build_Dcheck_Function
1056 (Case_Id : Entity_Id;
1057 Variant : Node_Id) return Entity_Id
1059 Body_Node : Node_Id;
1060 Func_Id : Entity_Id;
1061 Parameter_List : List_Id;
1062 Spec_Node : Node_Id;
1064 begin
1065 Body_Node := New_Node (N_Subprogram_Body, Loc);
1066 Sequence := Sequence + 1;
1068 Func_Id :=
1069 Make_Defining_Identifier (Loc,
1070 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
1071 Set_Is_Discriminant_Check_Function (Func_Id);
1073 Spec_Node := New_Node (N_Function_Specification, Loc);
1074 Set_Defining_Unit_Name (Spec_Node, Func_Id);
1076 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
1078 Set_Parameter_Specifications (Spec_Node, Parameter_List);
1079 Set_Result_Definition (Spec_Node,
1080 New_Occurrence_Of (Standard_Boolean, Loc));
1081 Set_Specification (Body_Node, Spec_Node);
1082 Set_Declarations (Body_Node, New_List);
1084 Set_Handled_Statement_Sequence (Body_Node,
1085 Make_Handled_Sequence_Of_Statements (Loc,
1086 Statements => New_List (
1087 Build_Case_Statement (Case_Id, Variant))));
1089 Set_Ekind (Func_Id, E_Function);
1090 Set_Mechanism (Func_Id, Default_Mechanism);
1091 Set_Is_Inlined (Func_Id, True);
1092 Set_Is_Pure (Func_Id, True);
1093 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
1094 Set_Is_Internal (Func_Id, True);
1096 if not Debug_Generated_Code then
1097 Set_Debug_Info_Off (Func_Id);
1098 end if;
1100 Analyze (Body_Node);
1102 Append_Freeze_Action (Rec_Id, Body_Node);
1103 Set_Dcheck_Function (Variant, Func_Id);
1104 return Func_Id;
1105 end Build_Dcheck_Function;
1107 ----------------------------
1108 -- Build_Dcheck_Functions --
1109 ----------------------------
1111 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1112 Component_List_Node : Node_Id;
1113 Decl : Entity_Id;
1114 Discr_Name : Entity_Id;
1115 Func_Id : Entity_Id;
1116 Variant : Node_Id;
1117 Saved_Enclosing_Func_Id : Entity_Id;
1119 begin
1120 -- Build the discriminant-checking function for each variant, and
1121 -- label all components of that variant with the function's name.
1122 -- We only Generate a discriminant-checking function when the
1123 -- variant is not empty, to prevent the creation of dead code.
1124 -- The exception to that is when Frontend_Layout_On_Target is set,
1125 -- because the variant record size function generated in package
1126 -- Layout needs to generate calls to all discriminant-checking
1127 -- functions, including those for empty variants.
1129 Discr_Name := Entity (Name (Variant_Part_Node));
1130 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1132 while Present (Variant) loop
1133 Component_List_Node := Component_List (Variant);
1135 if not Null_Present (Component_List_Node)
1136 or else Frontend_Layout_On_Target
1137 then
1138 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1139 Decl :=
1140 First_Non_Pragma (Component_Items (Component_List_Node));
1142 while Present (Decl) loop
1143 Set_Discriminant_Checking_Func
1144 (Defining_Identifier (Decl), Func_Id);
1146 Next_Non_Pragma (Decl);
1147 end loop;
1149 if Present (Variant_Part (Component_List_Node)) then
1150 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1151 Enclosing_Func_Id := Func_Id;
1152 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1153 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1154 end if;
1155 end if;
1157 Next_Non_Pragma (Variant);
1158 end loop;
1159 end Build_Dcheck_Functions;
1161 -- Start of processing for Build_Discr_Checking_Funcs
1163 begin
1164 -- Only build if not done already
1166 if not Discr_Check_Funcs_Built (N) then
1167 Type_Def := Type_Definition (N);
1169 if Nkind (Type_Def) = N_Record_Definition then
1170 if No (Component_List (Type_Def)) then -- null record.
1171 return;
1172 else
1173 V := Variant_Part (Component_List (Type_Def));
1174 end if;
1176 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1177 if No (Component_List (Record_Extension_Part (Type_Def))) then
1178 return;
1179 else
1180 V := Variant_Part
1181 (Component_List (Record_Extension_Part (Type_Def)));
1182 end if;
1183 end if;
1185 Rec_Id := Defining_Identifier (N);
1187 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1188 Loc := Sloc (N);
1189 Enclosing_Func_Id := Empty;
1190 Build_Dcheck_Functions (V);
1191 end if;
1193 Set_Discr_Check_Funcs_Built (N);
1194 end if;
1195 end Build_Discr_Checking_Funcs;
1197 --------------------------------
1198 -- Build_Discriminant_Formals --
1199 --------------------------------
1201 function Build_Discriminant_Formals
1202 (Rec_Id : Entity_Id;
1203 Use_Dl : Boolean) return List_Id
1205 Loc : Source_Ptr := Sloc (Rec_Id);
1206 Parameter_List : constant List_Id := New_List;
1207 D : Entity_Id;
1208 Formal : Entity_Id;
1209 Formal_Type : Entity_Id;
1210 Param_Spec_Node : Node_Id;
1212 begin
1213 if Has_Discriminants (Rec_Id) then
1214 D := First_Discriminant (Rec_Id);
1215 while Present (D) loop
1216 Loc := Sloc (D);
1218 if Use_Dl then
1219 Formal := Discriminal (D);
1220 Formal_Type := Etype (Formal);
1221 else
1222 Formal := Make_Defining_Identifier (Loc, Chars (D));
1223 Formal_Type := Etype (D);
1224 end if;
1226 Param_Spec_Node :=
1227 Make_Parameter_Specification (Loc,
1228 Defining_Identifier => Formal,
1229 Parameter_Type =>
1230 New_Occurrence_Of (Formal_Type, Loc));
1231 Append (Param_Spec_Node, Parameter_List);
1232 Next_Discriminant (D);
1233 end loop;
1234 end if;
1236 return Parameter_List;
1237 end Build_Discriminant_Formals;
1239 --------------------------------------
1240 -- Build_Equivalent_Array_Aggregate --
1241 --------------------------------------
1243 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1244 Loc : constant Source_Ptr := Sloc (T);
1245 Comp_Type : constant Entity_Id := Component_Type (T);
1246 Index_Type : constant Entity_Id := Etype (First_Index (T));
1247 Proc : constant Entity_Id := Base_Init_Proc (T);
1248 Lo, Hi : Node_Id;
1249 Aggr : Node_Id;
1250 Expr : Node_Id;
1252 begin
1253 if not Is_Constrained (T)
1254 or else Number_Dimensions (T) > 1
1255 or else No (Proc)
1256 then
1257 Initialization_Warning (T);
1258 return Empty;
1259 end if;
1261 Lo := Type_Low_Bound (Index_Type);
1262 Hi := Type_High_Bound (Index_Type);
1264 if not Compile_Time_Known_Value (Lo)
1265 or else not Compile_Time_Known_Value (Hi)
1266 then
1267 Initialization_Warning (T);
1268 return Empty;
1269 end if;
1271 if Is_Record_Type (Comp_Type)
1272 and then Present (Base_Init_Proc (Comp_Type))
1273 then
1274 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1276 if No (Expr) then
1277 Initialization_Warning (T);
1278 return Empty;
1279 end if;
1281 else
1282 Initialization_Warning (T);
1283 return Empty;
1284 end if;
1286 Aggr := Make_Aggregate (Loc, No_List, New_List);
1287 Set_Etype (Aggr, T);
1288 Set_Aggregate_Bounds (Aggr,
1289 Make_Range (Loc,
1290 Low_Bound => New_Copy (Lo),
1291 High_Bound => New_Copy (Hi)));
1292 Set_Parent (Aggr, Parent (Proc));
1294 Append_To (Component_Associations (Aggr),
1295 Make_Component_Association (Loc,
1296 Choices =>
1297 New_List (
1298 Make_Range (Loc,
1299 Low_Bound => New_Copy (Lo),
1300 High_Bound => New_Copy (Hi))),
1301 Expression => Expr));
1303 if Static_Array_Aggregate (Aggr) then
1304 return Aggr;
1305 else
1306 Initialization_Warning (T);
1307 return Empty;
1308 end if;
1309 end Build_Equivalent_Array_Aggregate;
1311 ---------------------------------------
1312 -- Build_Equivalent_Record_Aggregate --
1313 ---------------------------------------
1315 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1316 Agg : Node_Id;
1317 Comp : Entity_Id;
1318 Comp_Type : Entity_Id;
1320 -- Start of processing for Build_Equivalent_Record_Aggregate
1322 begin
1323 if not Is_Record_Type (T)
1324 or else Has_Discriminants (T)
1325 or else Is_Limited_Type (T)
1326 or else Has_Non_Standard_Rep (T)
1327 then
1328 Initialization_Warning (T);
1329 return Empty;
1330 end if;
1332 Comp := First_Component (T);
1334 -- A null record needs no warning
1336 if No (Comp) then
1337 return Empty;
1338 end if;
1340 while Present (Comp) loop
1342 -- Array components are acceptable if initialized by a positional
1343 -- aggregate with static components.
1345 if Is_Array_Type (Etype (Comp)) then
1346 Comp_Type := Component_Type (Etype (Comp));
1348 if Nkind (Parent (Comp)) /= N_Component_Declaration
1349 or else No (Expression (Parent (Comp)))
1350 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1351 then
1352 Initialization_Warning (T);
1353 return Empty;
1355 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1356 and then
1357 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1358 or else
1359 not Compile_Time_Known_Value (Type_High_Bound (Comp_Type)))
1360 then
1361 Initialization_Warning (T);
1362 return Empty;
1364 elsif
1365 not Static_Array_Aggregate (Expression (Parent (Comp)))
1366 then
1367 Initialization_Warning (T);
1368 return Empty;
1369 end if;
1371 elsif Is_Scalar_Type (Etype (Comp)) then
1372 Comp_Type := Etype (Comp);
1374 if Nkind (Parent (Comp)) /= N_Component_Declaration
1375 or else No (Expression (Parent (Comp)))
1376 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1377 or else not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1378 or else not
1379 Compile_Time_Known_Value (Type_High_Bound (Comp_Type))
1380 then
1381 Initialization_Warning (T);
1382 return Empty;
1383 end if;
1385 -- For now, other types are excluded
1387 else
1388 Initialization_Warning (T);
1389 return Empty;
1390 end if;
1392 Next_Component (Comp);
1393 end loop;
1395 -- All components have static initialization. Build positional aggregate
1396 -- from the given expressions or defaults.
1398 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1399 Set_Parent (Agg, Parent (T));
1401 Comp := First_Component (T);
1402 while Present (Comp) loop
1403 Append
1404 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1405 Next_Component (Comp);
1406 end loop;
1408 Analyze_And_Resolve (Agg, T);
1409 return Agg;
1410 end Build_Equivalent_Record_Aggregate;
1412 -------------------------------
1413 -- Build_Initialization_Call --
1414 -------------------------------
1416 -- References to a discriminant inside the record type declaration can
1417 -- appear either in the subtype_indication to constrain a record or an
1418 -- array, or as part of a larger expression given for the initial value
1419 -- of a component. In both of these cases N appears in the record
1420 -- initialization procedure and needs to be replaced by the formal
1421 -- parameter of the initialization procedure which corresponds to that
1422 -- discriminant.
1424 -- In the example below, references to discriminants D1 and D2 in proc_1
1425 -- are replaced by references to formals with the same name
1426 -- (discriminals)
1428 -- A similar replacement is done for calls to any record initialization
1429 -- procedure for any components that are themselves of a record type.
1431 -- type R (D1, D2 : Integer) is record
1432 -- X : Integer := F * D1;
1433 -- Y : Integer := F * D2;
1434 -- end record;
1436 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1437 -- begin
1438 -- Out_2.D1 := D1;
1439 -- Out_2.D2 := D2;
1440 -- Out_2.X := F * D1;
1441 -- Out_2.Y := F * D2;
1442 -- end;
1444 function Build_Initialization_Call
1445 (Loc : Source_Ptr;
1446 Id_Ref : Node_Id;
1447 Typ : Entity_Id;
1448 In_Init_Proc : Boolean := False;
1449 Enclos_Type : Entity_Id := Empty;
1450 Discr_Map : Elist_Id := New_Elmt_List;
1451 With_Default_Init : Boolean := False;
1452 Constructor_Ref : Node_Id := Empty) return List_Id
1454 Res : constant List_Id := New_List;
1455 Arg : Node_Id;
1456 Args : List_Id;
1457 Decls : List_Id;
1458 Decl : Node_Id;
1459 Discr : Entity_Id;
1460 First_Arg : Node_Id;
1461 Full_Init_Type : Entity_Id;
1462 Full_Type : Entity_Id := Typ;
1463 Init_Type : Entity_Id;
1464 Proc : Entity_Id;
1466 begin
1467 pragma Assert (Constructor_Ref = Empty
1468 or else Is_CPP_Constructor_Call (Constructor_Ref));
1470 if No (Constructor_Ref) then
1471 Proc := Base_Init_Proc (Typ);
1472 else
1473 Proc := Base_Init_Proc (Typ, Entity (Name (Constructor_Ref)));
1474 end if;
1476 pragma Assert (Present (Proc));
1477 Init_Type := Etype (First_Formal (Proc));
1478 Full_Init_Type := Underlying_Type (Init_Type);
1480 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1481 -- is active (in which case we make the call anyway, since in the
1482 -- actual compiled client it may be non null).
1483 -- Also nothing to do for value types.
1485 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1486 or else Is_Value_Type (Typ)
1487 or else
1488 (Is_Array_Type (Typ) and then Is_Value_Type (Component_Type (Typ)))
1489 then
1490 return Empty_List;
1491 end if;
1493 -- Go to full view or underlying full view if private type. In the case
1494 -- of successive private derivations, this can require two steps.
1496 if Is_Private_Type (Full_Type)
1497 and then Present (Full_View (Full_Type))
1498 then
1499 Full_Type := Full_View (Full_Type);
1500 end if;
1502 if Is_Private_Type (Full_Type)
1503 and then Present (Underlying_Full_View (Full_Type))
1504 then
1505 Full_Type := Underlying_Full_View (Full_Type);
1506 end if;
1508 -- If Typ is derived, the procedure is the initialization procedure for
1509 -- the root type. Wrap the argument in an conversion to make it type
1510 -- honest. Actually it isn't quite type honest, because there can be
1511 -- conflicts of views in the private type case. That is why we set
1512 -- Conversion_OK in the conversion node.
1514 if (Is_Record_Type (Typ)
1515 or else Is_Array_Type (Typ)
1516 or else Is_Private_Type (Typ))
1517 and then Init_Type /= Base_Type (Typ)
1518 then
1519 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1520 Set_Etype (First_Arg, Init_Type);
1522 else
1523 First_Arg := Id_Ref;
1524 end if;
1526 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1528 -- In the tasks case, add _Master as the value of the _Master parameter
1529 -- and _Chain as the value of the _Chain parameter. At the outer level,
1530 -- these will be variables holding the corresponding values obtained
1531 -- from GNARL. At inner levels, they will be the parameters passed down
1532 -- through the outer routines.
1534 if Has_Task (Full_Type) then
1535 if Restriction_Active (No_Task_Hierarchy) then
1536 Append_To (Args,
1537 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
1538 else
1539 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1540 end if;
1542 -- Add _Chain (not done for sequential elaboration policy, see
1543 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
1545 if Partition_Elaboration_Policy /= 'S' then
1546 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1547 end if;
1549 -- Ada 2005 (AI-287): In case of default initialized components
1550 -- with tasks, we generate a null string actual parameter.
1551 -- This is just a workaround that must be improved later???
1553 if With_Default_Init then
1554 Append_To (Args,
1555 Make_String_Literal (Loc,
1556 Strval => ""));
1558 else
1559 Decls :=
1560 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1561 Decl := Last (Decls);
1563 Append_To (Args,
1564 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1565 Append_List (Decls, Res);
1566 end if;
1568 else
1569 Decls := No_List;
1570 Decl := Empty;
1571 end if;
1573 -- Add discriminant values if discriminants are present
1575 if Has_Discriminants (Full_Init_Type) then
1576 Discr := First_Discriminant (Full_Init_Type);
1578 while Present (Discr) loop
1580 -- If this is a discriminated concurrent type, the init_proc
1581 -- for the corresponding record is being called. Use that type
1582 -- directly to find the discriminant value, to handle properly
1583 -- intervening renamed discriminants.
1585 declare
1586 T : Entity_Id := Full_Type;
1588 begin
1589 if Is_Protected_Type (T) then
1590 T := Corresponding_Record_Type (T);
1591 end if;
1593 Arg :=
1594 Get_Discriminant_Value (
1595 Discr,
1597 Discriminant_Constraint (Full_Type));
1598 end;
1600 -- If the target has access discriminants, and is constrained by
1601 -- an access to the enclosing construct, i.e. a current instance,
1602 -- replace the reference to the type by a reference to the object.
1604 if Nkind (Arg) = N_Attribute_Reference
1605 and then Is_Access_Type (Etype (Arg))
1606 and then Is_Entity_Name (Prefix (Arg))
1607 and then Is_Type (Entity (Prefix (Arg)))
1608 then
1609 Arg :=
1610 Make_Attribute_Reference (Loc,
1611 Prefix => New_Copy (Prefix (Id_Ref)),
1612 Attribute_Name => Name_Unrestricted_Access);
1614 elsif In_Init_Proc then
1616 -- Replace any possible references to the discriminant in the
1617 -- call to the record initialization procedure with references
1618 -- to the appropriate formal parameter.
1620 if Nkind (Arg) = N_Identifier
1621 and then Ekind (Entity (Arg)) = E_Discriminant
1622 then
1623 Arg := New_Occurrence_Of (Discriminal (Entity (Arg)), Loc);
1625 -- Otherwise make a copy of the default expression. Note that
1626 -- we use the current Sloc for this, because we do not want the
1627 -- call to appear to be at the declaration point. Within the
1628 -- expression, replace discriminants with their discriminals.
1630 else
1631 Arg :=
1632 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1633 end if;
1635 else
1636 if Is_Constrained (Full_Type) then
1637 Arg := Duplicate_Subexpr_No_Checks (Arg);
1638 else
1639 -- The constraints come from the discriminant default exps,
1640 -- they must be reevaluated, so we use New_Copy_Tree but we
1641 -- ensure the proper Sloc (for any embedded calls).
1643 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1644 end if;
1645 end if;
1647 -- Ada 2005 (AI-287): In case of default initialized components,
1648 -- if the component is constrained with a discriminant of the
1649 -- enclosing type, we need to generate the corresponding selected
1650 -- component node to access the discriminant value. In other cases
1651 -- this is not required, either because we are inside the init
1652 -- proc and we use the corresponding formal, or else because the
1653 -- component is constrained by an expression.
1655 if With_Default_Init
1656 and then Nkind (Id_Ref) = N_Selected_Component
1657 and then Nkind (Arg) = N_Identifier
1658 and then Ekind (Entity (Arg)) = E_Discriminant
1659 then
1660 Append_To (Args,
1661 Make_Selected_Component (Loc,
1662 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1663 Selector_Name => Arg));
1664 else
1665 Append_To (Args, Arg);
1666 end if;
1668 Next_Discriminant (Discr);
1669 end loop;
1670 end if;
1672 -- If this is a call to initialize the parent component of a derived
1673 -- tagged type, indicate that the tag should not be set in the parent.
1675 if Is_Tagged_Type (Full_Init_Type)
1676 and then not Is_CPP_Class (Full_Init_Type)
1677 and then Nkind (Id_Ref) = N_Selected_Component
1678 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1679 then
1680 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1682 elsif Present (Constructor_Ref) then
1683 Append_List_To (Args,
1684 New_Copy_List (Parameter_Associations (Constructor_Ref)));
1685 end if;
1687 Append_To (Res,
1688 Make_Procedure_Call_Statement (Loc,
1689 Name => New_Occurrence_Of (Proc, Loc),
1690 Parameter_Associations => Args));
1692 if Needs_Finalization (Typ)
1693 and then Nkind (Id_Ref) = N_Selected_Component
1694 then
1695 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1696 Append_To (Res,
1697 Make_Init_Call
1698 (Obj_Ref => New_Copy_Tree (First_Arg),
1699 Typ => Typ));
1700 end if;
1701 end if;
1703 return Res;
1705 exception
1706 when RE_Not_Available =>
1707 return Empty_List;
1708 end Build_Initialization_Call;
1710 ----------------------------
1711 -- Build_Record_Init_Proc --
1712 ----------------------------
1714 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id) is
1715 Decls : constant List_Id := New_List;
1716 Discr_Map : constant Elist_Id := New_Elmt_List;
1717 Loc : constant Source_Ptr := Sloc (Rec_Ent);
1718 Counter : Int := 0;
1719 Proc_Id : Entity_Id;
1720 Rec_Type : Entity_Id;
1721 Set_Tag : Entity_Id := Empty;
1723 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1724 -- Build an assignment statement which assigns the default expression
1725 -- to its corresponding record component if defined. The left hand side
1726 -- of the assignment is marked Assignment_OK so that initialization of
1727 -- limited private records works correctly. This routine may also build
1728 -- an adjustment call if the component is controlled.
1730 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1731 -- If the record has discriminants, add assignment statements to
1732 -- Statement_List to initialize the discriminant values from the
1733 -- arguments of the initialization procedure.
1735 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1736 -- Build a list representing a sequence of statements which initialize
1737 -- components of the given component list. This may involve building
1738 -- case statements for the variant parts. Append any locally declared
1739 -- objects on list Decls.
1741 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1742 -- Given an untagged type-derivation that declares discriminants, e.g.
1744 -- type R (R1, R2 : Integer) is record ... end record;
1745 -- type D (D1 : Integer) is new R (1, D1);
1747 -- we make the _init_proc of D be
1749 -- procedure _init_proc (X : D; D1 : Integer) is
1750 -- begin
1751 -- _init_proc (R (X), 1, D1);
1752 -- end _init_proc;
1754 -- This function builds the call statement in this _init_proc.
1756 procedure Build_CPP_Init_Procedure;
1757 -- Build the tree corresponding to the procedure specification and body
1758 -- of the IC procedure that initializes the C++ part of the dispatch
1759 -- table of an Ada tagged type that is a derivation of a CPP type.
1760 -- Install it as the CPP_Init TSS.
1762 procedure Build_Init_Procedure;
1763 -- Build the tree corresponding to the procedure specification and body
1764 -- of the initialization procedure and install it as the _init TSS.
1766 procedure Build_Offset_To_Top_Functions;
1767 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1768 -- and body of Offset_To_Top, a function used in conjuction with types
1769 -- having secondary dispatch tables.
1771 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1772 -- Add range checks to components of discriminated records. S is a
1773 -- subtype indication of a record component. Check_List is a list
1774 -- to which the check actions are appended.
1776 function Component_Needs_Simple_Initialization
1777 (T : Entity_Id) return Boolean;
1778 -- Determine if a component needs simple initialization, given its type
1779 -- T. This routine is the same as Needs_Simple_Initialization except for
1780 -- components of type Tag and Interface_Tag. These two access types do
1781 -- not require initialization since they are explicitly initialized by
1782 -- other means.
1784 function Parent_Subtype_Renaming_Discrims return Boolean;
1785 -- Returns True for base types N that rename discriminants, else False
1787 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1788 -- Determine whether a record initialization procedure needs to be
1789 -- generated for the given record type.
1791 ----------------------
1792 -- Build_Assignment --
1793 ----------------------
1795 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1796 N_Loc : constant Source_Ptr := Sloc (N);
1797 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1798 Exp : Node_Id := N;
1799 Kind : Node_Kind := Nkind (N);
1800 Lhs : Node_Id;
1801 Res : List_Id;
1803 begin
1804 Lhs :=
1805 Make_Selected_Component (N_Loc,
1806 Prefix => Make_Identifier (Loc, Name_uInit),
1807 Selector_Name => New_Occurrence_Of (Id, N_Loc));
1808 Set_Assignment_OK (Lhs);
1810 -- Case of an access attribute applied to the current instance.
1811 -- Replace the reference to the type by a reference to the actual
1812 -- object. (Note that this handles the case of the top level of
1813 -- the expression being given by such an attribute, but does not
1814 -- cover uses nested within an initial value expression. Nested
1815 -- uses are unlikely to occur in practice, but are theoretically
1816 -- possible.) It is not clear how to handle them without fully
1817 -- traversing the expression. ???
1819 if Kind = N_Attribute_Reference
1820 and then Nam_In (Attribute_Name (N), Name_Unchecked_Access,
1821 Name_Unrestricted_Access)
1822 and then Is_Entity_Name (Prefix (N))
1823 and then Is_Type (Entity (Prefix (N)))
1824 and then Entity (Prefix (N)) = Rec_Type
1825 then
1826 Exp :=
1827 Make_Attribute_Reference (N_Loc,
1828 Prefix =>
1829 Make_Identifier (N_Loc, Name_uInit),
1830 Attribute_Name => Name_Unrestricted_Access);
1831 end if;
1833 -- Take a copy of Exp to ensure that later copies of this component
1834 -- declaration in derived types see the original tree, not a node
1835 -- rewritten during expansion of the init_proc. If the copy contains
1836 -- itypes, the scope of the new itypes is the init_proc being built.
1838 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id);
1840 Res := New_List (
1841 Make_Assignment_Statement (Loc,
1842 Name => Lhs,
1843 Expression => Exp));
1845 Set_No_Ctrl_Actions (First (Res));
1847 -- Adjust the tag if tagged (because of possible view conversions).
1848 -- Suppress the tag adjustment when VM_Target because VM tags are
1849 -- represented implicitly in objects.
1851 if Is_Tagged_Type (Typ) and then Tagged_Type_Expansion then
1852 Append_To (Res,
1853 Make_Assignment_Statement (N_Loc,
1854 Name =>
1855 Make_Selected_Component (N_Loc,
1856 Prefix =>
1857 New_Copy_Tree (Lhs, New_Scope => Proc_Id),
1858 Selector_Name =>
1859 New_Occurrence_Of (First_Tag_Component (Typ), N_Loc)),
1861 Expression =>
1862 Unchecked_Convert_To (RTE (RE_Tag),
1863 New_Occurrence_Of
1864 (Node
1865 (First_Elmt
1866 (Access_Disp_Table (Underlying_Type (Typ)))),
1867 N_Loc))));
1868 end if;
1870 -- Adjust the component if controlled except if it is an aggregate
1871 -- that will be expanded inline.
1873 if Kind = N_Qualified_Expression then
1874 Kind := Nkind (Expression (N));
1875 end if;
1877 if Needs_Finalization (Typ)
1878 and then not (Nkind_In (Kind, N_Aggregate, N_Extension_Aggregate))
1879 and then not Is_Limited_View (Typ)
1880 then
1881 Append_To (Res,
1882 Make_Adjust_Call
1883 (Obj_Ref => New_Copy_Tree (Lhs),
1884 Typ => Etype (Id)));
1885 end if;
1887 return Res;
1889 exception
1890 when RE_Not_Available =>
1891 return Empty_List;
1892 end Build_Assignment;
1894 ------------------------------------
1895 -- Build_Discriminant_Assignments --
1896 ------------------------------------
1898 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1899 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1900 D : Entity_Id;
1901 D_Loc : Source_Ptr;
1903 begin
1904 if Has_Discriminants (Rec_Type)
1905 and then not Is_Unchecked_Union (Rec_Type)
1906 then
1907 D := First_Discriminant (Rec_Type);
1908 while Present (D) loop
1910 -- Don't generate the assignment for discriminants in derived
1911 -- tagged types if the discriminant is a renaming of some
1912 -- ancestor discriminant. This initialization will be done
1913 -- when initializing the _parent field of the derived record.
1915 if Is_Tagged
1916 and then Present (Corresponding_Discriminant (D))
1917 then
1918 null;
1920 else
1921 D_Loc := Sloc (D);
1922 Append_List_To (Statement_List,
1923 Build_Assignment (D,
1924 New_Occurrence_Of (Discriminal (D), D_Loc)));
1925 end if;
1927 Next_Discriminant (D);
1928 end loop;
1929 end if;
1930 end Build_Discriminant_Assignments;
1932 --------------------------
1933 -- Build_Init_Call_Thru --
1934 --------------------------
1936 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1937 Parent_Proc : constant Entity_Id :=
1938 Base_Init_Proc (Etype (Rec_Type));
1940 Parent_Type : constant Entity_Id :=
1941 Etype (First_Formal (Parent_Proc));
1943 Uparent_Type : constant Entity_Id :=
1944 Underlying_Type (Parent_Type);
1946 First_Discr_Param : Node_Id;
1948 Arg : Node_Id;
1949 Args : List_Id;
1950 First_Arg : Node_Id;
1951 Parent_Discr : Entity_Id;
1952 Res : List_Id;
1954 begin
1955 -- First argument (_Init) is the object to be initialized.
1956 -- ??? not sure where to get a reasonable Loc for First_Arg
1958 First_Arg :=
1959 OK_Convert_To (Parent_Type,
1960 New_Occurrence_Of
1961 (Defining_Identifier (First (Parameters)), Loc));
1963 Set_Etype (First_Arg, Parent_Type);
1965 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1967 -- In the tasks case,
1968 -- add _Master as the value of the _Master parameter
1969 -- add _Chain as the value of the _Chain parameter.
1970 -- add _Task_Name as the value of the _Task_Name parameter.
1971 -- At the outer level, these will be variables holding the
1972 -- corresponding values obtained from GNARL or the expander.
1974 -- At inner levels, they will be the parameters passed down through
1975 -- the outer routines.
1977 First_Discr_Param := Next (First (Parameters));
1979 if Has_Task (Rec_Type) then
1980 if Restriction_Active (No_Task_Hierarchy) then
1981 Append_To (Args,
1982 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
1983 else
1984 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1985 end if;
1987 -- Add _Chain (not done for sequential elaboration policy, see
1988 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
1990 if Partition_Elaboration_Policy /= 'S' then
1991 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1992 end if;
1994 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
1995 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
1996 end if;
1998 -- Append discriminant values
2000 if Has_Discriminants (Uparent_Type) then
2001 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2003 Parent_Discr := First_Discriminant (Uparent_Type);
2004 while Present (Parent_Discr) loop
2006 -- Get the initial value for this discriminant
2007 -- ??? needs to be cleaned up to use parent_Discr_Constr
2008 -- directly.
2010 declare
2011 Discr : Entity_Id :=
2012 First_Stored_Discriminant (Uparent_Type);
2014 Discr_Value : Elmt_Id :=
2015 First_Elmt (Stored_Constraint (Rec_Type));
2017 begin
2018 while Original_Record_Component (Parent_Discr) /= Discr loop
2019 Next_Stored_Discriminant (Discr);
2020 Next_Elmt (Discr_Value);
2021 end loop;
2023 Arg := Node (Discr_Value);
2024 end;
2026 -- Append it to the list
2028 if Nkind (Arg) = N_Identifier
2029 and then Ekind (Entity (Arg)) = E_Discriminant
2030 then
2031 Append_To (Args,
2032 New_Occurrence_Of (Discriminal (Entity (Arg)), Loc));
2034 -- Case of access discriminants. We replace the reference
2035 -- to the type by a reference to the actual object.
2037 -- Is above comment right??? Use of New_Copy below seems mighty
2038 -- suspicious ???
2040 else
2041 Append_To (Args, New_Copy (Arg));
2042 end if;
2044 Next_Discriminant (Parent_Discr);
2045 end loop;
2046 end if;
2048 Res :=
2049 New_List (
2050 Make_Procedure_Call_Statement (Loc,
2051 Name =>
2052 New_Occurrence_Of (Parent_Proc, Loc),
2053 Parameter_Associations => Args));
2055 return Res;
2056 end Build_Init_Call_Thru;
2058 -----------------------------------
2059 -- Build_Offset_To_Top_Functions --
2060 -----------------------------------
2062 procedure Build_Offset_To_Top_Functions is
2064 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2065 -- Generate:
2066 -- function Fxx (O : Address) return Storage_Offset is
2067 -- type Acc is access all <Typ>;
2068 -- begin
2069 -- return Acc!(O).Iface_Comp'Position;
2070 -- end Fxx;
2072 ----------------------------------
2073 -- Build_Offset_To_Top_Function --
2074 ----------------------------------
2076 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2077 Body_Node : Node_Id;
2078 Func_Id : Entity_Id;
2079 Spec_Node : Node_Id;
2080 Acc_Type : Entity_Id;
2082 begin
2083 Func_Id := Make_Temporary (Loc, 'F');
2084 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2086 -- Generate
2087 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2089 Spec_Node := New_Node (N_Function_Specification, Loc);
2090 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2091 Set_Parameter_Specifications (Spec_Node, New_List (
2092 Make_Parameter_Specification (Loc,
2093 Defining_Identifier =>
2094 Make_Defining_Identifier (Loc, Name_uO),
2095 In_Present => True,
2096 Parameter_Type =>
2097 New_Occurrence_Of (RTE (RE_Address), Loc))));
2098 Set_Result_Definition (Spec_Node,
2099 New_Occurrence_Of (RTE (RE_Storage_Offset), Loc));
2101 -- Generate
2102 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2103 -- begin
2104 -- return O.Iface_Comp'Position;
2105 -- end Fxx;
2107 Body_Node := New_Node (N_Subprogram_Body, Loc);
2108 Set_Specification (Body_Node, Spec_Node);
2110 Acc_Type := Make_Temporary (Loc, 'T');
2111 Set_Declarations (Body_Node, New_List (
2112 Make_Full_Type_Declaration (Loc,
2113 Defining_Identifier => Acc_Type,
2114 Type_Definition =>
2115 Make_Access_To_Object_Definition (Loc,
2116 All_Present => True,
2117 Null_Exclusion_Present => False,
2118 Constant_Present => False,
2119 Subtype_Indication =>
2120 New_Occurrence_Of (Rec_Type, Loc)))));
2122 Set_Handled_Statement_Sequence (Body_Node,
2123 Make_Handled_Sequence_Of_Statements (Loc,
2124 Statements => New_List (
2125 Make_Simple_Return_Statement (Loc,
2126 Expression =>
2127 Make_Attribute_Reference (Loc,
2128 Prefix =>
2129 Make_Selected_Component (Loc,
2130 Prefix =>
2131 Unchecked_Convert_To (Acc_Type,
2132 Make_Identifier (Loc, Name_uO)),
2133 Selector_Name =>
2134 New_Occurrence_Of (Iface_Comp, Loc)),
2135 Attribute_Name => Name_Position)))));
2137 Set_Ekind (Func_Id, E_Function);
2138 Set_Mechanism (Func_Id, Default_Mechanism);
2139 Set_Is_Internal (Func_Id, True);
2141 if not Debug_Generated_Code then
2142 Set_Debug_Info_Off (Func_Id);
2143 end if;
2145 Analyze (Body_Node);
2147 Append_Freeze_Action (Rec_Type, Body_Node);
2148 end Build_Offset_To_Top_Function;
2150 -- Local variables
2152 Iface_Comp : Node_Id;
2153 Iface_Comp_Elmt : Elmt_Id;
2154 Ifaces_Comp_List : Elist_Id;
2156 -- Start of processing for Build_Offset_To_Top_Functions
2158 begin
2159 -- Offset_To_Top_Functions are built only for derivations of types
2160 -- with discriminants that cover interface types.
2161 -- Nothing is needed either in case of virtual machines, since
2162 -- interfaces are handled directly by the VM.
2164 if not Is_Tagged_Type (Rec_Type)
2165 or else Etype (Rec_Type) = Rec_Type
2166 or else not Has_Discriminants (Etype (Rec_Type))
2167 or else not Tagged_Type_Expansion
2168 then
2169 return;
2170 end if;
2172 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2174 -- For each interface type with secondary dispatch table we generate
2175 -- the Offset_To_Top_Functions (required to displace the pointer in
2176 -- interface conversions)
2178 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2179 while Present (Iface_Comp_Elmt) loop
2180 Iface_Comp := Node (Iface_Comp_Elmt);
2181 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2183 -- If the interface is a parent of Rec_Type it shares the primary
2184 -- dispatch table and hence there is no need to build the function
2186 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type,
2187 Use_Full_View => True)
2188 then
2189 Build_Offset_To_Top_Function (Iface_Comp);
2190 end if;
2192 Next_Elmt (Iface_Comp_Elmt);
2193 end loop;
2194 end Build_Offset_To_Top_Functions;
2196 ------------------------------
2197 -- Build_CPP_Init_Procedure --
2198 ------------------------------
2200 procedure Build_CPP_Init_Procedure is
2201 Body_Node : Node_Id;
2202 Body_Stmts : List_Id;
2203 Flag_Id : Entity_Id;
2204 Handled_Stmt_Node : Node_Id;
2205 Init_Tags_List : List_Id;
2206 Proc_Id : Entity_Id;
2207 Proc_Spec_Node : Node_Id;
2209 begin
2210 -- Check cases requiring no IC routine
2212 if not Is_CPP_Class (Root_Type (Rec_Type))
2213 or else Is_CPP_Class (Rec_Type)
2214 or else CPP_Num_Prims (Rec_Type) = 0
2215 or else not Tagged_Type_Expansion
2216 or else No_Run_Time_Mode
2217 then
2218 return;
2219 end if;
2221 -- Generate:
2223 -- Flag : Boolean := False;
2225 -- procedure Typ_IC is
2226 -- begin
2227 -- if not Flag then
2228 -- Copy C++ dispatch table slots from parent
2229 -- Update C++ slots of overridden primitives
2230 -- end if;
2231 -- end;
2233 Flag_Id := Make_Temporary (Loc, 'F');
2235 Append_Freeze_Action (Rec_Type,
2236 Make_Object_Declaration (Loc,
2237 Defining_Identifier => Flag_Id,
2238 Object_Definition =>
2239 New_Occurrence_Of (Standard_Boolean, Loc),
2240 Expression =>
2241 New_Occurrence_Of (Standard_True, Loc)));
2243 Body_Stmts := New_List;
2244 Body_Node := New_Node (N_Subprogram_Body, Loc);
2246 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2248 Proc_Id :=
2249 Make_Defining_Identifier (Loc,
2250 Chars => Make_TSS_Name (Rec_Type, TSS_CPP_Init_Proc));
2252 Set_Ekind (Proc_Id, E_Procedure);
2253 Set_Is_Internal (Proc_Id);
2255 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2257 Set_Parameter_Specifications (Proc_Spec_Node, New_List);
2258 Set_Specification (Body_Node, Proc_Spec_Node);
2259 Set_Declarations (Body_Node, New_List);
2261 Init_Tags_List := Build_Inherit_CPP_Prims (Rec_Type);
2263 Append_To (Init_Tags_List,
2264 Make_Assignment_Statement (Loc,
2265 Name =>
2266 New_Occurrence_Of (Flag_Id, Loc),
2267 Expression =>
2268 New_Occurrence_Of (Standard_False, Loc)));
2270 Append_To (Body_Stmts,
2271 Make_If_Statement (Loc,
2272 Condition => New_Occurrence_Of (Flag_Id, Loc),
2273 Then_Statements => Init_Tags_List));
2275 Handled_Stmt_Node :=
2276 New_Node (N_Handled_Sequence_Of_Statements, Loc);
2277 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2278 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2279 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2281 if not Debug_Generated_Code then
2282 Set_Debug_Info_Off (Proc_Id);
2283 end if;
2285 -- Associate CPP_Init_Proc with type
2287 Set_Init_Proc (Rec_Type, Proc_Id);
2288 end Build_CPP_Init_Procedure;
2290 --------------------------
2291 -- Build_Init_Procedure --
2292 --------------------------
2294 procedure Build_Init_Procedure is
2295 Body_Stmts : List_Id;
2296 Body_Node : Node_Id;
2297 Handled_Stmt_Node : Node_Id;
2298 Init_Tags_List : List_Id;
2299 Parameters : List_Id;
2300 Proc_Spec_Node : Node_Id;
2301 Record_Extension_Node : Node_Id;
2303 begin
2304 Body_Stmts := New_List;
2305 Body_Node := New_Node (N_Subprogram_Body, Loc);
2306 Set_Ekind (Proc_Id, E_Procedure);
2308 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2309 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2311 Parameters := Init_Formals (Rec_Type);
2312 Append_List_To (Parameters,
2313 Build_Discriminant_Formals (Rec_Type, True));
2315 -- For tagged types, we add a flag to indicate whether the routine
2316 -- is called to initialize a parent component in the init_proc of
2317 -- a type extension. If the flag is false, we do not set the tag
2318 -- because it has been set already in the extension.
2320 if Is_Tagged_Type (Rec_Type) then
2321 Set_Tag := Make_Temporary (Loc, 'P');
2323 Append_To (Parameters,
2324 Make_Parameter_Specification (Loc,
2325 Defining_Identifier => Set_Tag,
2326 Parameter_Type =>
2327 New_Occurrence_Of (Standard_Boolean, Loc),
2328 Expression =>
2329 New_Occurrence_Of (Standard_True, Loc)));
2330 end if;
2332 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2333 Set_Specification (Body_Node, Proc_Spec_Node);
2334 Set_Declarations (Body_Node, Decls);
2336 -- N is a Derived_Type_Definition that renames the parameters of the
2337 -- ancestor type. We initialize it by expanding our discriminants and
2338 -- call the ancestor _init_proc with a type-converted object.
2340 if Parent_Subtype_Renaming_Discrims then
2341 Append_List_To (Body_Stmts, Build_Init_Call_Thru (Parameters));
2343 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2344 Build_Discriminant_Assignments (Body_Stmts);
2346 if not Null_Present (Type_Definition (N)) then
2347 Append_List_To (Body_Stmts,
2348 Build_Init_Statements (Component_List (Type_Definition (N))));
2349 end if;
2351 -- N is a Derived_Type_Definition with a possible non-empty
2352 -- extension. The initialization of a type extension consists in the
2353 -- initialization of the components in the extension.
2355 else
2356 Build_Discriminant_Assignments (Body_Stmts);
2358 Record_Extension_Node :=
2359 Record_Extension_Part (Type_Definition (N));
2361 if not Null_Present (Record_Extension_Node) then
2362 declare
2363 Stmts : constant List_Id :=
2364 Build_Init_Statements (
2365 Component_List (Record_Extension_Node));
2367 begin
2368 -- The parent field must be initialized first because the
2369 -- offset of the new discriminants may depend on it. This is
2370 -- not needed if the parent is an interface type because in
2371 -- such case the initialization of the _parent field was not
2372 -- generated.
2374 if not Is_Interface (Etype (Rec_Ent)) then
2375 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2376 end if;
2378 Append_List_To (Body_Stmts, Stmts);
2379 end;
2380 end if;
2381 end if;
2383 -- Add here the assignment to instantiate the Tag
2385 -- The assignment corresponds to the code:
2387 -- _Init._Tag := Typ'Tag;
2389 -- Suppress the tag assignment when VM_Target because VM tags are
2390 -- represented implicitly in objects. It is also suppressed in case
2391 -- of CPP_Class types because in this case the tag is initialized in
2392 -- the C++ side.
2394 if Is_Tagged_Type (Rec_Type)
2395 and then Tagged_Type_Expansion
2396 and then not No_Run_Time_Mode
2397 then
2398 -- Case 1: Ada tagged types with no CPP ancestor. Set the tags of
2399 -- the actual object and invoke the IP of the parent (in this
2400 -- order). The tag must be initialized before the call to the IP
2401 -- of the parent and the assignments to other components because
2402 -- the initial value of the components may depend on the tag (eg.
2403 -- through a dispatching operation on an access to the current
2404 -- type). The tag assignment is not done when initializing the
2405 -- parent component of a type extension, because in that case the
2406 -- tag is set in the extension.
2408 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2410 -- Initialize the primary tag component
2412 Init_Tags_List := New_List (
2413 Make_Assignment_Statement (Loc,
2414 Name =>
2415 Make_Selected_Component (Loc,
2416 Prefix => Make_Identifier (Loc, Name_uInit),
2417 Selector_Name =>
2418 New_Occurrence_Of
2419 (First_Tag_Component (Rec_Type), Loc)),
2420 Expression =>
2421 New_Occurrence_Of
2422 (Node
2423 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2425 -- Ada 2005 (AI-251): Initialize the secondary tags components
2426 -- located at fixed positions (tags whose position depends on
2427 -- variable size components are initialized later ---see below)
2429 if Ada_Version >= Ada_2005
2430 and then not Is_Interface (Rec_Type)
2431 and then Has_Interfaces (Rec_Type)
2432 then
2433 Init_Secondary_Tags
2434 (Typ => Rec_Type,
2435 Target => Make_Identifier (Loc, Name_uInit),
2436 Stmts_List => Init_Tags_List,
2437 Fixed_Comps => True,
2438 Variable_Comps => False);
2439 end if;
2441 Prepend_To (Body_Stmts,
2442 Make_If_Statement (Loc,
2443 Condition => New_Occurrence_Of (Set_Tag, Loc),
2444 Then_Statements => Init_Tags_List));
2446 -- Case 2: CPP type. The imported C++ constructor takes care of
2447 -- tags initialization. No action needed here because the IP
2448 -- is built by Set_CPP_Constructors; in this case the IP is a
2449 -- wrapper that invokes the C++ constructor and copies the C++
2450 -- tags locally. Done to inherit the C++ slots in Ada derivations
2451 -- (see case 3).
2453 elsif Is_CPP_Class (Rec_Type) then
2454 pragma Assert (False);
2455 null;
2457 -- Case 3: Combined hierarchy containing C++ types and Ada tagged
2458 -- type derivations. Derivations of imported C++ classes add a
2459 -- complication, because we cannot inhibit tag setting in the
2460 -- constructor for the parent. Hence we initialize the tag after
2461 -- the call to the parent IP (that is, in reverse order compared
2462 -- with pure Ada hierarchies ---see comment on case 1).
2464 else
2465 -- Initialize the primary tag
2467 Init_Tags_List := New_List (
2468 Make_Assignment_Statement (Loc,
2469 Name =>
2470 Make_Selected_Component (Loc,
2471 Prefix => Make_Identifier (Loc, Name_uInit),
2472 Selector_Name =>
2473 New_Occurrence_Of
2474 (First_Tag_Component (Rec_Type), Loc)),
2475 Expression =>
2476 New_Occurrence_Of
2477 (Node
2478 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2480 -- Ada 2005 (AI-251): Initialize the secondary tags components
2481 -- located at fixed positions (tags whose position depends on
2482 -- variable size components are initialized later ---see below)
2484 if Ada_Version >= Ada_2005
2485 and then not Is_Interface (Rec_Type)
2486 and then Has_Interfaces (Rec_Type)
2487 then
2488 Init_Secondary_Tags
2489 (Typ => Rec_Type,
2490 Target => Make_Identifier (Loc, Name_uInit),
2491 Stmts_List => Init_Tags_List,
2492 Fixed_Comps => True,
2493 Variable_Comps => False);
2494 end if;
2496 -- Initialize the tag component after invocation of parent IP.
2498 -- Generate:
2499 -- parent_IP(_init.parent); // Invokes the C++ constructor
2500 -- [ typIC; ] // Inherit C++ slots from parent
2501 -- init_tags
2503 declare
2504 Ins_Nod : Node_Id;
2506 begin
2507 -- Search for the call to the IP of the parent. We assume
2508 -- that the first init_proc call is for the parent.
2510 Ins_Nod := First (Body_Stmts);
2511 while Present (Next (Ins_Nod))
2512 and then (Nkind (Ins_Nod) /= N_Procedure_Call_Statement
2513 or else not Is_Init_Proc (Name (Ins_Nod)))
2514 loop
2515 Next (Ins_Nod);
2516 end loop;
2518 -- The IC routine copies the inherited slots of the C+ part
2519 -- of the dispatch table from the parent and updates the
2520 -- overridden C++ slots.
2522 if CPP_Num_Prims (Rec_Type) > 0 then
2523 declare
2524 Init_DT : Entity_Id;
2525 New_Nod : Node_Id;
2527 begin
2528 Init_DT := CPP_Init_Proc (Rec_Type);
2529 pragma Assert (Present (Init_DT));
2531 New_Nod :=
2532 Make_Procedure_Call_Statement (Loc,
2533 New_Occurrence_Of (Init_DT, Loc));
2534 Insert_After (Ins_Nod, New_Nod);
2536 -- Update location of init tag statements
2538 Ins_Nod := New_Nod;
2539 end;
2540 end if;
2542 Insert_List_After (Ins_Nod, Init_Tags_List);
2543 end;
2544 end if;
2546 -- Ada 2005 (AI-251): Initialize the secondary tag components
2547 -- located at variable positions. We delay the generation of this
2548 -- code until here because the value of the attribute 'Position
2549 -- applied to variable size components of the parent type that
2550 -- depend on discriminants is only safely read at runtime after
2551 -- the parent components have been initialized.
2553 if Ada_Version >= Ada_2005
2554 and then not Is_Interface (Rec_Type)
2555 and then Has_Interfaces (Rec_Type)
2556 and then Has_Discriminants (Etype (Rec_Type))
2557 and then Is_Variable_Size_Record (Etype (Rec_Type))
2558 then
2559 Init_Tags_List := New_List;
2561 Init_Secondary_Tags
2562 (Typ => Rec_Type,
2563 Target => Make_Identifier (Loc, Name_uInit),
2564 Stmts_List => Init_Tags_List,
2565 Fixed_Comps => False,
2566 Variable_Comps => True);
2568 if Is_Non_Empty_List (Init_Tags_List) then
2569 Append_List_To (Body_Stmts, Init_Tags_List);
2570 end if;
2571 end if;
2572 end if;
2574 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2575 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2577 -- Generate:
2578 -- Deep_Finalize (_init, C1, ..., CN);
2579 -- raise;
2581 if Counter > 0
2582 and then Needs_Finalization (Rec_Type)
2583 and then not Is_Abstract_Type (Rec_Type)
2584 and then not Restriction_Active (No_Exception_Propagation)
2585 then
2586 declare
2587 DF_Call : Node_Id;
2588 DF_Id : Entity_Id;
2590 begin
2591 -- Create a local version of Deep_Finalize which has indication
2592 -- of partial initialization state.
2594 DF_Id := Make_Temporary (Loc, 'F');
2596 Append_To (Decls, Make_Local_Deep_Finalize (Rec_Type, DF_Id));
2598 DF_Call :=
2599 Make_Procedure_Call_Statement (Loc,
2600 Name => New_Occurrence_Of (DF_Id, Loc),
2601 Parameter_Associations => New_List (
2602 Make_Identifier (Loc, Name_uInit),
2603 New_Occurrence_Of (Standard_False, Loc)));
2605 -- Do not emit warnings related to the elaboration order when a
2606 -- controlled object is declared before the body of Finalize is
2607 -- seen.
2609 Set_No_Elaboration_Check (DF_Call);
2611 Set_Exception_Handlers (Handled_Stmt_Node, New_List (
2612 Make_Exception_Handler (Loc,
2613 Exception_Choices => New_List (
2614 Make_Others_Choice (Loc)),
2615 Statements => New_List (
2616 DF_Call,
2617 Make_Raise_Statement (Loc)))));
2618 end;
2619 else
2620 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2621 end if;
2623 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2625 if not Debug_Generated_Code then
2626 Set_Debug_Info_Off (Proc_Id);
2627 end if;
2629 -- Associate Init_Proc with type, and determine if the procedure
2630 -- is null (happens because of the Initialize_Scalars pragma case,
2631 -- where we have to generate a null procedure in case it is called
2632 -- by a client with Initialize_Scalars set). Such procedures have
2633 -- to be generated, but do not have to be called, so we mark them
2634 -- as null to suppress the call.
2636 Set_Init_Proc (Rec_Type, Proc_Id);
2638 if List_Length (Body_Stmts) = 1
2640 -- We must skip SCIL nodes because they may have been added to this
2641 -- list by Insert_Actions.
2643 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
2644 and then VM_Target = No_VM
2645 then
2646 -- Even though the init proc may be null at this time it might get
2647 -- some stuff added to it later by the VM backend.
2649 Set_Is_Null_Init_Proc (Proc_Id);
2650 end if;
2651 end Build_Init_Procedure;
2653 ---------------------------
2654 -- Build_Init_Statements --
2655 ---------------------------
2657 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2658 Checks : constant List_Id := New_List;
2659 Actions : List_Id := No_List;
2660 Comp_Loc : Source_Ptr;
2661 Counter_Id : Entity_Id := Empty;
2662 Decl : Node_Id;
2663 Has_POC : Boolean;
2664 Id : Entity_Id;
2665 Stmts : List_Id;
2666 Typ : Entity_Id;
2668 procedure Increment_Counter (Loc : Source_Ptr);
2669 -- Generate an "increment by one" statement for the current counter
2670 -- and append it to the list Stmts.
2672 procedure Make_Counter (Loc : Source_Ptr);
2673 -- Create a new counter for the current component list. The routine
2674 -- creates a new defining Id, adds an object declaration and sets
2675 -- the Id generator for the next variant.
2677 -----------------------
2678 -- Increment_Counter --
2679 -----------------------
2681 procedure Increment_Counter (Loc : Source_Ptr) is
2682 begin
2683 -- Generate:
2684 -- Counter := Counter + 1;
2686 Append_To (Stmts,
2687 Make_Assignment_Statement (Loc,
2688 Name => New_Occurrence_Of (Counter_Id, Loc),
2689 Expression =>
2690 Make_Op_Add (Loc,
2691 Left_Opnd => New_Occurrence_Of (Counter_Id, Loc),
2692 Right_Opnd => Make_Integer_Literal (Loc, 1))));
2693 end Increment_Counter;
2695 ------------------
2696 -- Make_Counter --
2697 ------------------
2699 procedure Make_Counter (Loc : Source_Ptr) is
2700 begin
2701 -- Increment the Id generator
2703 Counter := Counter + 1;
2705 -- Create the entity and declaration
2707 Counter_Id :=
2708 Make_Defining_Identifier (Loc,
2709 Chars => New_External_Name ('C', Counter));
2711 -- Generate:
2712 -- Cnn : Integer := 0;
2714 Append_To (Decls,
2715 Make_Object_Declaration (Loc,
2716 Defining_Identifier => Counter_Id,
2717 Object_Definition =>
2718 New_Occurrence_Of (Standard_Integer, Loc),
2719 Expression =>
2720 Make_Integer_Literal (Loc, 0)));
2721 end Make_Counter;
2723 -- Start of processing for Build_Init_Statements
2725 begin
2726 if Null_Present (Comp_List) then
2727 return New_List (Make_Null_Statement (Loc));
2728 end if;
2730 Stmts := New_List;
2732 -- Loop through visible declarations of task types and protected
2733 -- types moving any expanded code from the spec to the body of the
2734 -- init procedure.
2736 if Is_Task_Record_Type (Rec_Type)
2737 or else Is_Protected_Record_Type (Rec_Type)
2738 then
2739 declare
2740 Decl : constant Node_Id :=
2741 Parent (Corresponding_Concurrent_Type (Rec_Type));
2742 Def : Node_Id;
2743 N1 : Node_Id;
2744 N2 : Node_Id;
2746 begin
2747 if Is_Task_Record_Type (Rec_Type) then
2748 Def := Task_Definition (Decl);
2749 else
2750 Def := Protected_Definition (Decl);
2751 end if;
2753 if Present (Def) then
2754 N1 := First (Visible_Declarations (Def));
2755 while Present (N1) loop
2756 N2 := N1;
2757 N1 := Next (N1);
2759 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2760 or else Nkind (N2) in N_Raise_xxx_Error
2761 or else Nkind (N2) = N_Procedure_Call_Statement
2762 then
2763 Append_To (Stmts,
2764 New_Copy_Tree (N2, New_Scope => Proc_Id));
2765 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2766 Analyze (N2);
2767 end if;
2768 end loop;
2769 end if;
2770 end;
2771 end if;
2773 -- Loop through components, skipping pragmas, in 2 steps. The first
2774 -- step deals with regular components. The second step deals with
2775 -- components that have per object constraints and no explicit
2776 -- initialization.
2778 Has_POC := False;
2780 -- First pass : regular components
2782 Decl := First_Non_Pragma (Component_Items (Comp_List));
2783 while Present (Decl) loop
2784 Comp_Loc := Sloc (Decl);
2785 Build_Record_Checks
2786 (Subtype_Indication (Component_Definition (Decl)), Checks);
2788 Id := Defining_Identifier (Decl);
2789 Typ := Etype (Id);
2791 -- Leave any processing of per-object constrained component for
2792 -- the second pass.
2794 if Has_Access_Constraint (Id) and then No (Expression (Decl)) then
2795 Has_POC := True;
2797 -- Regular component cases
2799 else
2800 -- In the context of the init proc, references to discriminants
2801 -- resolve to denote the discriminals: this is where we can
2802 -- freeze discriminant dependent component subtypes.
2804 if not Is_Frozen (Typ) then
2805 Append_List_To (Stmts, Freeze_Entity (Typ, N));
2806 end if;
2808 -- Explicit initialization
2810 if Present (Expression (Decl)) then
2811 if Is_CPP_Constructor_Call (Expression (Decl)) then
2812 Actions :=
2813 Build_Initialization_Call
2814 (Comp_Loc,
2815 Id_Ref =>
2816 Make_Selected_Component (Comp_Loc,
2817 Prefix =>
2818 Make_Identifier (Comp_Loc, Name_uInit),
2819 Selector_Name =>
2820 New_Occurrence_Of (Id, Comp_Loc)),
2821 Typ => Typ,
2822 In_Init_Proc => True,
2823 Enclos_Type => Rec_Type,
2824 Discr_Map => Discr_Map,
2825 Constructor_Ref => Expression (Decl));
2826 else
2827 Actions := Build_Assignment (Id, Expression (Decl));
2828 end if;
2830 -- CPU, Dispatching_Domain, Priority and Size components are
2831 -- filled with the corresponding rep item expression of the
2832 -- concurrent type (if any).
2834 elsif Ekind (Scope (Id)) = E_Record_Type
2835 and then Present (Corresponding_Concurrent_Type (Scope (Id)))
2836 and then Nam_In (Chars (Id), Name_uCPU,
2837 Name_uDispatching_Domain,
2838 Name_uPriority)
2839 then
2840 declare
2841 Exp : Node_Id;
2842 Nam : Name_Id;
2843 Ritem : Node_Id;
2845 begin
2846 if Chars (Id) = Name_uCPU then
2847 Nam := Name_CPU;
2849 elsif Chars (Id) = Name_uDispatching_Domain then
2850 Nam := Name_Dispatching_Domain;
2852 elsif Chars (Id) = Name_uPriority then
2853 Nam := Name_Priority;
2854 end if;
2856 -- Get the Rep Item (aspect specification, attribute
2857 -- definition clause or pragma) of the corresponding
2858 -- concurrent type.
2860 Ritem :=
2861 Get_Rep_Item
2862 (Corresponding_Concurrent_Type (Scope (Id)),
2863 Nam,
2864 Check_Parents => False);
2866 if Present (Ritem) then
2868 -- Pragma case
2870 if Nkind (Ritem) = N_Pragma then
2871 Exp := First (Pragma_Argument_Associations (Ritem));
2873 if Nkind (Exp) = N_Pragma_Argument_Association then
2874 Exp := Expression (Exp);
2875 end if;
2877 -- Conversion for Priority expression
2879 if Nam = Name_Priority then
2880 if Pragma_Name (Ritem) = Name_Priority
2881 and then not GNAT_Mode
2882 then
2883 Exp := Convert_To (RTE (RE_Priority), Exp);
2884 else
2885 Exp :=
2886 Convert_To (RTE (RE_Any_Priority), Exp);
2887 end if;
2888 end if;
2890 -- Aspect/Attribute definition clause case
2892 else
2893 Exp := Expression (Ritem);
2895 -- Conversion for Priority expression
2897 if Nam = Name_Priority then
2898 if Chars (Ritem) = Name_Priority
2899 and then not GNAT_Mode
2900 then
2901 Exp := Convert_To (RTE (RE_Priority), Exp);
2902 else
2903 Exp :=
2904 Convert_To (RTE (RE_Any_Priority), Exp);
2905 end if;
2906 end if;
2907 end if;
2909 -- Conversion for Dispatching_Domain value
2911 if Nam = Name_Dispatching_Domain then
2912 Exp :=
2913 Unchecked_Convert_To
2914 (RTE (RE_Dispatching_Domain_Access), Exp);
2915 end if;
2917 Actions := Build_Assignment (Id, Exp);
2919 -- Nothing needed if no Rep Item
2921 else
2922 Actions := No_List;
2923 end if;
2924 end;
2926 -- Composite component with its own Init_Proc
2928 elsif not Is_Interface (Typ)
2929 and then Has_Non_Null_Base_Init_Proc (Typ)
2930 then
2931 Actions :=
2932 Build_Initialization_Call
2933 (Comp_Loc,
2934 Make_Selected_Component (Comp_Loc,
2935 Prefix =>
2936 Make_Identifier (Comp_Loc, Name_uInit),
2937 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
2938 Typ,
2939 In_Init_Proc => True,
2940 Enclos_Type => Rec_Type,
2941 Discr_Map => Discr_Map);
2943 Clean_Task_Names (Typ, Proc_Id);
2945 -- Simple initialization
2947 elsif Component_Needs_Simple_Initialization (Typ) then
2948 Actions :=
2949 Build_Assignment
2950 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
2952 -- Nothing needed for this case
2954 else
2955 Actions := No_List;
2956 end if;
2958 if Present (Checks) then
2959 Append_List_To (Stmts, Checks);
2960 end if;
2962 if Present (Actions) then
2963 Append_List_To (Stmts, Actions);
2965 -- Preserve the initialization state in the current counter
2967 if Chars (Id) /= Name_uParent
2968 and then Needs_Finalization (Typ)
2969 then
2970 if No (Counter_Id) then
2971 Make_Counter (Comp_Loc);
2972 end if;
2974 Increment_Counter (Comp_Loc);
2975 end if;
2976 end if;
2977 end if;
2979 Next_Non_Pragma (Decl);
2980 end loop;
2982 -- Set up tasks and protected object support. This needs to be done
2983 -- before any component with a per-object access discriminant
2984 -- constraint, or any variant part (which may contain such
2985 -- components) is initialized, because the initialization of these
2986 -- components may reference the enclosing concurrent object.
2988 -- For a task record type, add the task create call and calls to bind
2989 -- any interrupt (signal) entries.
2991 if Is_Task_Record_Type (Rec_Type) then
2993 -- In the case of the restricted run time the ATCB has already
2994 -- been preallocated.
2996 if Restricted_Profile then
2997 Append_To (Stmts,
2998 Make_Assignment_Statement (Loc,
2999 Name =>
3000 Make_Selected_Component (Loc,
3001 Prefix => Make_Identifier (Loc, Name_uInit),
3002 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
3003 Expression =>
3004 Make_Attribute_Reference (Loc,
3005 Prefix =>
3006 Make_Selected_Component (Loc,
3007 Prefix => Make_Identifier (Loc, Name_uInit),
3008 Selector_Name => Make_Identifier (Loc, Name_uATCB)),
3009 Attribute_Name => Name_Unchecked_Access)));
3010 end if;
3012 Append_To (Stmts, Make_Task_Create_Call (Rec_Type));
3014 declare
3015 Task_Type : constant Entity_Id :=
3016 Corresponding_Concurrent_Type (Rec_Type);
3017 Task_Decl : constant Node_Id := Parent (Task_Type);
3018 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
3019 Decl_Loc : Source_Ptr;
3020 Ent : Entity_Id;
3021 Vis_Decl : Node_Id;
3023 begin
3024 if Present (Task_Def) then
3025 Vis_Decl := First (Visible_Declarations (Task_Def));
3026 while Present (Vis_Decl) loop
3027 Decl_Loc := Sloc (Vis_Decl);
3029 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
3030 if Get_Attribute_Id (Chars (Vis_Decl)) =
3031 Attribute_Address
3032 then
3033 Ent := Entity (Name (Vis_Decl));
3035 if Ekind (Ent) = E_Entry then
3036 Append_To (Stmts,
3037 Make_Procedure_Call_Statement (Decl_Loc,
3038 Name =>
3039 New_Occurrence_Of (RTE (
3040 RE_Bind_Interrupt_To_Entry), Decl_Loc),
3041 Parameter_Associations => New_List (
3042 Make_Selected_Component (Decl_Loc,
3043 Prefix =>
3044 Make_Identifier (Decl_Loc, Name_uInit),
3045 Selector_Name =>
3046 Make_Identifier
3047 (Decl_Loc, Name_uTask_Id)),
3048 Entry_Index_Expression
3049 (Decl_Loc, Ent, Empty, Task_Type),
3050 Expression (Vis_Decl))));
3051 end if;
3052 end if;
3053 end if;
3055 Next (Vis_Decl);
3056 end loop;
3057 end if;
3058 end;
3059 end if;
3061 -- For a protected type, add statements generated by
3062 -- Make_Initialize_Protection.
3064 if Is_Protected_Record_Type (Rec_Type) then
3065 Append_List_To (Stmts,
3066 Make_Initialize_Protection (Rec_Type));
3067 end if;
3069 -- Second pass: components with per-object constraints
3071 if Has_POC then
3072 Decl := First_Non_Pragma (Component_Items (Comp_List));
3073 while Present (Decl) loop
3074 Comp_Loc := Sloc (Decl);
3075 Id := Defining_Identifier (Decl);
3076 Typ := Etype (Id);
3078 if Has_Access_Constraint (Id)
3079 and then No (Expression (Decl))
3080 then
3081 if Has_Non_Null_Base_Init_Proc (Typ) then
3082 Append_List_To (Stmts,
3083 Build_Initialization_Call (Comp_Loc,
3084 Make_Selected_Component (Comp_Loc,
3085 Prefix =>
3086 Make_Identifier (Comp_Loc, Name_uInit),
3087 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3088 Typ,
3089 In_Init_Proc => True,
3090 Enclos_Type => Rec_Type,
3091 Discr_Map => Discr_Map));
3093 Clean_Task_Names (Typ, Proc_Id);
3095 -- Preserve initialization state in the current counter
3097 if Needs_Finalization (Typ) then
3098 if No (Counter_Id) then
3099 Make_Counter (Comp_Loc);
3100 end if;
3102 Increment_Counter (Comp_Loc);
3103 end if;
3105 elsif Component_Needs_Simple_Initialization (Typ) then
3106 Append_List_To (Stmts,
3107 Build_Assignment
3108 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
3109 end if;
3110 end if;
3112 Next_Non_Pragma (Decl);
3113 end loop;
3114 end if;
3116 -- Process the variant part
3118 if Present (Variant_Part (Comp_List)) then
3119 declare
3120 Variant_Alts : constant List_Id := New_List;
3121 Var_Loc : Source_Ptr;
3122 Variant : Node_Id;
3124 begin
3125 Variant :=
3126 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3127 while Present (Variant) loop
3128 Var_Loc := Sloc (Variant);
3129 Append_To (Variant_Alts,
3130 Make_Case_Statement_Alternative (Var_Loc,
3131 Discrete_Choices =>
3132 New_Copy_List (Discrete_Choices (Variant)),
3133 Statements =>
3134 Build_Init_Statements (Component_List (Variant))));
3135 Next_Non_Pragma (Variant);
3136 end loop;
3138 -- The expression of the case statement which is a reference
3139 -- to one of the discriminants is replaced by the appropriate
3140 -- formal parameter of the initialization procedure.
3142 Append_To (Stmts,
3143 Make_Case_Statement (Var_Loc,
3144 Expression =>
3145 New_Occurrence_Of (Discriminal (
3146 Entity (Name (Variant_Part (Comp_List)))), Var_Loc),
3147 Alternatives => Variant_Alts));
3148 end;
3149 end if;
3151 -- If no initializations when generated for component declarations
3152 -- corresponding to this Stmts, append a null statement to Stmts to
3153 -- to make it a valid Ada tree.
3155 if Is_Empty_List (Stmts) then
3156 Append (Make_Null_Statement (Loc), Stmts);
3157 end if;
3159 return Stmts;
3161 exception
3162 when RE_Not_Available =>
3163 return Empty_List;
3164 end Build_Init_Statements;
3166 -------------------------
3167 -- Build_Record_Checks --
3168 -------------------------
3170 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
3171 Subtype_Mark_Id : Entity_Id;
3173 procedure Constrain_Array
3174 (SI : Node_Id;
3175 Check_List : List_Id);
3176 -- Apply a list of index constraints to an unconstrained array type.
3177 -- The first parameter is the entity for the resulting subtype.
3178 -- Check_List is a list to which the check actions are appended.
3180 ---------------------
3181 -- Constrain_Array --
3182 ---------------------
3184 procedure Constrain_Array
3185 (SI : Node_Id;
3186 Check_List : List_Id)
3188 C : constant Node_Id := Constraint (SI);
3189 Number_Of_Constraints : Nat := 0;
3190 Index : Node_Id;
3191 S, T : Entity_Id;
3193 procedure Constrain_Index
3194 (Index : Node_Id;
3195 S : Node_Id;
3196 Check_List : List_Id);
3197 -- Process an index constraint in a constrained array declaration.
3198 -- The constraint can be either a subtype name or a range with or
3199 -- without an explicit subtype mark. Index is the corresponding
3200 -- index of the unconstrained array. S is the range expression.
3201 -- Check_List is a list to which the check actions are appended.
3203 ---------------------
3204 -- Constrain_Index --
3205 ---------------------
3207 procedure Constrain_Index
3208 (Index : Node_Id;
3209 S : Node_Id;
3210 Check_List : List_Id)
3212 T : constant Entity_Id := Etype (Index);
3214 begin
3215 if Nkind (S) = N_Range then
3216 Process_Range_Expr_In_Decl (S, T, Check_List => Check_List);
3217 end if;
3218 end Constrain_Index;
3220 -- Start of processing for Constrain_Array
3222 begin
3223 T := Entity (Subtype_Mark (SI));
3225 if Is_Access_Type (T) then
3226 T := Designated_Type (T);
3227 end if;
3229 S := First (Constraints (C));
3231 while Present (S) loop
3232 Number_Of_Constraints := Number_Of_Constraints + 1;
3233 Next (S);
3234 end loop;
3236 -- In either case, the index constraint must provide a discrete
3237 -- range for each index of the array type and the type of each
3238 -- discrete range must be the same as that of the corresponding
3239 -- index. (RM 3.6.1)
3241 S := First (Constraints (C));
3242 Index := First_Index (T);
3243 Analyze (Index);
3245 -- Apply constraints to each index type
3247 for J in 1 .. Number_Of_Constraints loop
3248 Constrain_Index (Index, S, Check_List);
3249 Next (Index);
3250 Next (S);
3251 end loop;
3252 end Constrain_Array;
3254 -- Start of processing for Build_Record_Checks
3256 begin
3257 if Nkind (S) = N_Subtype_Indication then
3258 Find_Type (Subtype_Mark (S));
3259 Subtype_Mark_Id := Entity (Subtype_Mark (S));
3261 -- Remaining processing depends on type
3263 case Ekind (Subtype_Mark_Id) is
3265 when Array_Kind =>
3266 Constrain_Array (S, Check_List);
3268 when others =>
3269 null;
3270 end case;
3271 end if;
3272 end Build_Record_Checks;
3274 -------------------------------------------
3275 -- Component_Needs_Simple_Initialization --
3276 -------------------------------------------
3278 function Component_Needs_Simple_Initialization
3279 (T : Entity_Id) return Boolean
3281 begin
3282 return
3283 Needs_Simple_Initialization (T)
3284 and then not Is_RTE (T, RE_Tag)
3286 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
3288 and then not Is_RTE (T, RE_Interface_Tag);
3289 end Component_Needs_Simple_Initialization;
3291 --------------------------------------
3292 -- Parent_Subtype_Renaming_Discrims --
3293 --------------------------------------
3295 function Parent_Subtype_Renaming_Discrims return Boolean is
3296 De : Entity_Id;
3297 Dp : Entity_Id;
3299 begin
3300 if Base_Type (Rec_Ent) /= Rec_Ent then
3301 return False;
3302 end if;
3304 if Etype (Rec_Ent) = Rec_Ent
3305 or else not Has_Discriminants (Rec_Ent)
3306 or else Is_Constrained (Rec_Ent)
3307 or else Is_Tagged_Type (Rec_Ent)
3308 then
3309 return False;
3310 end if;
3312 -- If there are no explicit stored discriminants we have inherited
3313 -- the root type discriminants so far, so no renamings occurred.
3315 if First_Discriminant (Rec_Ent) =
3316 First_Stored_Discriminant (Rec_Ent)
3317 then
3318 return False;
3319 end if;
3321 -- Check if we have done some trivial renaming of the parent
3322 -- discriminants, i.e. something like
3324 -- type DT (X1, X2: int) is new PT (X1, X2);
3326 De := First_Discriminant (Rec_Ent);
3327 Dp := First_Discriminant (Etype (Rec_Ent));
3328 while Present (De) loop
3329 pragma Assert (Present (Dp));
3331 if Corresponding_Discriminant (De) /= Dp then
3332 return True;
3333 end if;
3335 Next_Discriminant (De);
3336 Next_Discriminant (Dp);
3337 end loop;
3339 return Present (Dp);
3340 end Parent_Subtype_Renaming_Discrims;
3342 ------------------------
3343 -- Requires_Init_Proc --
3344 ------------------------
3346 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3347 Comp_Decl : Node_Id;
3348 Id : Entity_Id;
3349 Typ : Entity_Id;
3351 begin
3352 -- Definitely do not need one if specifically suppressed
3354 if Initialization_Suppressed (Rec_Id) then
3355 return False;
3356 end if;
3358 -- If it is a type derived from a type with unknown discriminants,
3359 -- we cannot build an initialization procedure for it.
3361 if Has_Unknown_Discriminants (Rec_Id)
3362 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3363 then
3364 return False;
3365 end if;
3367 -- Otherwise we need to generate an initialization procedure if
3368 -- Is_CPP_Class is False and at least one of the following applies:
3370 -- 1. Discriminants are present, since they need to be initialized
3371 -- with the appropriate discriminant constraint expressions.
3372 -- However, the discriminant of an unchecked union does not
3373 -- count, since the discriminant is not present.
3375 -- 2. The type is a tagged type, since the implicit Tag component
3376 -- needs to be initialized with a pointer to the dispatch table.
3378 -- 3. The type contains tasks
3380 -- 4. One or more components has an initial value
3382 -- 5. One or more components is for a type which itself requires
3383 -- an initialization procedure.
3385 -- 6. One or more components is a type that requires simple
3386 -- initialization (see Needs_Simple_Initialization), except
3387 -- that types Tag and Interface_Tag are excluded, since fields
3388 -- of these types are initialized by other means.
3390 -- 7. The type is the record type built for a task type (since at
3391 -- the very least, Create_Task must be called)
3393 -- 8. The type is the record type built for a protected type (since
3394 -- at least Initialize_Protection must be called)
3396 -- 9. The type is marked as a public entity. The reason we add this
3397 -- case (even if none of the above apply) is to properly handle
3398 -- Initialize_Scalars. If a package is compiled without an IS
3399 -- pragma, and the client is compiled with an IS pragma, then
3400 -- the client will think an initialization procedure is present
3401 -- and call it, when in fact no such procedure is required, but
3402 -- since the call is generated, there had better be a routine
3403 -- at the other end of the call, even if it does nothing).
3405 -- Note: the reason we exclude the CPP_Class case is because in this
3406 -- case the initialization is performed by the C++ constructors, and
3407 -- the IP is built by Set_CPP_Constructors.
3409 if Is_CPP_Class (Rec_Id) then
3410 return False;
3412 elsif Is_Interface (Rec_Id) then
3413 return False;
3415 elsif (Has_Discriminants (Rec_Id)
3416 and then not Is_Unchecked_Union (Rec_Id))
3417 or else Is_Tagged_Type (Rec_Id)
3418 or else Is_Concurrent_Record_Type (Rec_Id)
3419 or else Has_Task (Rec_Id)
3420 then
3421 return True;
3422 end if;
3424 Id := First_Component (Rec_Id);
3425 while Present (Id) loop
3426 Comp_Decl := Parent (Id);
3427 Typ := Etype (Id);
3429 if Present (Expression (Comp_Decl))
3430 or else Has_Non_Null_Base_Init_Proc (Typ)
3431 or else Component_Needs_Simple_Initialization (Typ)
3432 then
3433 return True;
3434 end if;
3436 Next_Component (Id);
3437 end loop;
3439 -- As explained above, a record initialization procedure is needed
3440 -- for public types in case Initialize_Scalars applies to a client.
3441 -- However, such a procedure is not needed in the case where either
3442 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3443 -- applies. No_Initialize_Scalars excludes the possibility of using
3444 -- Initialize_Scalars in any partition, and No_Default_Initialization
3445 -- implies that no initialization should ever be done for objects of
3446 -- the type, so is incompatible with Initialize_Scalars.
3448 if not Restriction_Active (No_Initialize_Scalars)
3449 and then not Restriction_Active (No_Default_Initialization)
3450 and then Is_Public (Rec_Id)
3451 then
3452 return True;
3453 end if;
3455 return False;
3456 end Requires_Init_Proc;
3458 -- Start of processing for Build_Record_Init_Proc
3460 begin
3461 -- Check for value type, which means no initialization required
3463 Rec_Type := Defining_Identifier (N);
3465 if Is_Value_Type (Rec_Type) then
3466 return;
3467 end if;
3469 -- This may be full declaration of a private type, in which case
3470 -- the visible entity is a record, and the private entity has been
3471 -- exchanged with it in the private part of the current package.
3472 -- The initialization procedure is built for the record type, which
3473 -- is retrievable from the private entity.
3475 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3476 Rec_Type := Underlying_Type (Rec_Type);
3477 end if;
3479 -- If we have a variant record with restriction No_Implicit_Conditionals
3480 -- in effect, then we skip building the procedure. This is safe because
3481 -- if we can see the restriction, so can any caller, calls to initialize
3482 -- such records are not allowed for variant records if this restriction
3483 -- is active.
3485 if Has_Variant_Part (Rec_Type)
3486 and then Restriction_Active (No_Implicit_Conditionals)
3487 then
3488 return;
3489 end if;
3491 -- If there are discriminants, build the discriminant map to replace
3492 -- discriminants by their discriminals in complex bound expressions.
3493 -- These only arise for the corresponding records of synchronized types.
3495 if Is_Concurrent_Record_Type (Rec_Type)
3496 and then Has_Discriminants (Rec_Type)
3497 then
3498 declare
3499 Disc : Entity_Id;
3500 begin
3501 Disc := First_Discriminant (Rec_Type);
3502 while Present (Disc) loop
3503 Append_Elmt (Disc, Discr_Map);
3504 Append_Elmt (Discriminal (Disc), Discr_Map);
3505 Next_Discriminant (Disc);
3506 end loop;
3507 end;
3508 end if;
3510 -- Derived types that have no type extension can use the initialization
3511 -- procedure of their parent and do not need a procedure of their own.
3512 -- This is only correct if there are no representation clauses for the
3513 -- type or its parent, and if the parent has in fact been frozen so
3514 -- that its initialization procedure exists.
3516 if Is_Derived_Type (Rec_Type)
3517 and then not Is_Tagged_Type (Rec_Type)
3518 and then not Is_Unchecked_Union (Rec_Type)
3519 and then not Has_New_Non_Standard_Rep (Rec_Type)
3520 and then not Parent_Subtype_Renaming_Discrims
3521 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3522 then
3523 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3525 -- Otherwise if we need an initialization procedure, then build one,
3526 -- mark it as public and inlinable and as having a completion.
3528 elsif Requires_Init_Proc (Rec_Type)
3529 or else Is_Unchecked_Union (Rec_Type)
3530 then
3531 Proc_Id :=
3532 Make_Defining_Identifier (Loc,
3533 Chars => Make_Init_Proc_Name (Rec_Type));
3535 -- If No_Default_Initialization restriction is active, then we don't
3536 -- want to build an init_proc, but we need to mark that an init_proc
3537 -- would be needed if this restriction was not active (so that we can
3538 -- detect attempts to call it), so set a dummy init_proc in place.
3540 if Restriction_Active (No_Default_Initialization) then
3541 Set_Init_Proc (Rec_Type, Proc_Id);
3542 return;
3543 end if;
3545 Build_Offset_To_Top_Functions;
3546 Build_CPP_Init_Procedure;
3547 Build_Init_Procedure;
3548 Set_Is_Public (Proc_Id, Is_Public (Rec_Ent));
3550 -- The initialization of protected records is not worth inlining.
3551 -- In addition, when compiled for another unit for inlining purposes,
3552 -- it may make reference to entities that have not been elaborated
3553 -- yet. The initialization of controlled records contains a nested
3554 -- clean-up procedure that makes it impractical to inline as well,
3555 -- and leads to undefined symbols if inlined in a different unit.
3556 -- Similar considerations apply to task types.
3558 if not Is_Concurrent_Type (Rec_Type)
3559 and then not Has_Task (Rec_Type)
3560 and then not Needs_Finalization (Rec_Type)
3561 then
3562 Set_Is_Inlined (Proc_Id);
3563 end if;
3565 Set_Is_Internal (Proc_Id);
3566 Set_Has_Completion (Proc_Id);
3568 if not Debug_Generated_Code then
3569 Set_Debug_Info_Off (Proc_Id);
3570 end if;
3572 declare
3573 Agg : constant Node_Id :=
3574 Build_Equivalent_Record_Aggregate (Rec_Type);
3576 procedure Collect_Itypes (Comp : Node_Id);
3577 -- Generate references to itypes in the aggregate, because
3578 -- the first use of the aggregate may be in a nested scope.
3580 --------------------
3581 -- Collect_Itypes --
3582 --------------------
3584 procedure Collect_Itypes (Comp : Node_Id) is
3585 Ref : Node_Id;
3586 Sub_Aggr : Node_Id;
3587 Typ : constant Entity_Id := Etype (Comp);
3589 begin
3590 if Is_Array_Type (Typ) and then Is_Itype (Typ) then
3591 Ref := Make_Itype_Reference (Loc);
3592 Set_Itype (Ref, Typ);
3593 Append_Freeze_Action (Rec_Type, Ref);
3595 Ref := Make_Itype_Reference (Loc);
3596 Set_Itype (Ref, Etype (First_Index (Typ)));
3597 Append_Freeze_Action (Rec_Type, Ref);
3599 Sub_Aggr := First (Expressions (Comp));
3601 -- Recurse on nested arrays
3603 while Present (Sub_Aggr) loop
3604 Collect_Itypes (Sub_Aggr);
3605 Next (Sub_Aggr);
3606 end loop;
3607 end if;
3608 end Collect_Itypes;
3610 begin
3611 -- If there is a static initialization aggregate for the type,
3612 -- generate itype references for the types of its (sub)components,
3613 -- to prevent out-of-scope errors in the resulting tree.
3614 -- The aggregate may have been rewritten as a Raise node, in which
3615 -- case there are no relevant itypes.
3617 if Present (Agg) and then Nkind (Agg) = N_Aggregate then
3618 Set_Static_Initialization (Proc_Id, Agg);
3620 declare
3621 Comp : Node_Id;
3622 begin
3623 Comp := First (Component_Associations (Agg));
3624 while Present (Comp) loop
3625 Collect_Itypes (Expression (Comp));
3626 Next (Comp);
3627 end loop;
3628 end;
3629 end if;
3630 end;
3631 end if;
3632 end Build_Record_Init_Proc;
3634 --------------------------------
3635 -- Build_Record_Invariant_Proc --
3636 --------------------------------
3638 function Build_Record_Invariant_Proc
3639 (R_Type : Entity_Id;
3640 Nod : Node_Id) return Node_Id
3642 Loc : constant Source_Ptr := Sloc (Nod);
3644 Object_Name : constant Name_Id := New_Internal_Name ('I');
3645 -- Name for argument of invariant procedure
3647 Object_Entity : constant Node_Id :=
3648 Make_Defining_Identifier (Loc, Object_Name);
3649 -- The procedure declaration entity for the argument
3651 Invariant_Found : Boolean;
3652 -- Set if any component needs an invariant check.
3654 Proc_Id : Entity_Id;
3655 Proc_Body : Node_Id;
3656 Stmts : List_Id;
3657 Type_Def : Node_Id;
3659 function Build_Invariant_Checks (Comp_List : Node_Id) return List_Id;
3660 -- Recursive procedure that generates a list of checks for components
3661 -- that need it, and recurses through variant parts when present.
3663 function Build_Component_Invariant_Call (Comp : Entity_Id)
3664 return Node_Id;
3665 -- Build call to invariant procedure for a record component.
3667 ------------------------------------
3668 -- Build_Component_Invariant_Call --
3669 ------------------------------------
3671 function Build_Component_Invariant_Call (Comp : Entity_Id)
3672 return Node_Id
3674 Sel_Comp : Node_Id;
3675 Typ : Entity_Id;
3676 Call : Node_Id;
3678 begin
3679 Invariant_Found := True;
3680 Typ := Etype (Comp);
3682 Sel_Comp :=
3683 Make_Selected_Component (Loc,
3684 Prefix => New_Occurrence_Of (Object_Entity, Loc),
3685 Selector_Name => New_Occurrence_Of (Comp, Loc));
3687 if Is_Access_Type (Typ) then
3689 -- If the access component designates a type with an invariant,
3690 -- the check applies to the designated object. The access type
3691 -- itself may have an invariant, in which case it applies to the
3692 -- access value directly.
3694 -- Note: we are assuming that invariants will not occur on both
3695 -- the access type and the type that it designates. This is not
3696 -- really justified but it is hard to imagine that this case will
3697 -- ever cause trouble ???
3699 if not (Has_Invariants (Typ)) then
3700 Sel_Comp := Make_Explicit_Dereference (Loc, Sel_Comp);
3701 Typ := Designated_Type (Typ);
3702 end if;
3703 end if;
3705 Call :=
3706 Make_Procedure_Call_Statement (Loc,
3707 Name =>
3708 New_Occurrence_Of (Invariant_Procedure (Typ), Loc),
3709 Parameter_Associations => New_List (Sel_Comp));
3711 if Is_Access_Type (Etype (Comp)) then
3712 Call :=
3713 Make_If_Statement (Loc,
3714 Condition =>
3715 Make_Op_Ne (Loc,
3716 Left_Opnd => Make_Null (Loc),
3717 Right_Opnd =>
3718 Make_Selected_Component (Loc,
3719 Prefix => New_Occurrence_Of (Object_Entity, Loc),
3720 Selector_Name => New_Occurrence_Of (Comp, Loc))),
3721 Then_Statements => New_List (Call));
3722 end if;
3724 return Call;
3725 end Build_Component_Invariant_Call;
3727 ----------------------------
3728 -- Build_Invariant_Checks --
3729 ----------------------------
3731 function Build_Invariant_Checks (Comp_List : Node_Id) return List_Id is
3732 Decl : Node_Id;
3733 Id : Entity_Id;
3734 Stmts : List_Id;
3736 begin
3737 Stmts := New_List;
3738 Decl := First_Non_Pragma (Component_Items (Comp_List));
3739 while Present (Decl) loop
3740 if Nkind (Decl) = N_Component_Declaration then
3741 Id := Defining_Identifier (Decl);
3743 if Has_Invariants (Etype (Id))
3744 and then In_Open_Scopes (Scope (R_Type))
3745 then
3746 if Has_Unchecked_Union (R_Type) then
3747 Error_Msg_NE
3748 ("invariants cannot be checked on components of "
3749 & "unchecked_union type&?", Decl, R_Type);
3750 return Empty_List;
3752 else
3753 Append_To (Stmts, Build_Component_Invariant_Call (Id));
3754 end if;
3756 elsif Is_Access_Type (Etype (Id))
3757 and then not Is_Access_Constant (Etype (Id))
3758 and then Has_Invariants (Designated_Type (Etype (Id)))
3759 and then In_Open_Scopes (Scope (Designated_Type (Etype (Id))))
3760 then
3761 Append_To (Stmts, Build_Component_Invariant_Call (Id));
3762 end if;
3763 end if;
3765 Next (Decl);
3766 end loop;
3768 if Present (Variant_Part (Comp_List)) then
3769 declare
3770 Variant_Alts : constant List_Id := New_List;
3771 Var_Loc : Source_Ptr;
3772 Variant : Node_Id;
3773 Variant_Stmts : List_Id;
3775 begin
3776 Variant :=
3777 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3778 while Present (Variant) loop
3779 Variant_Stmts :=
3780 Build_Invariant_Checks (Component_List (Variant));
3781 Var_Loc := Sloc (Variant);
3782 Append_To (Variant_Alts,
3783 Make_Case_Statement_Alternative (Var_Loc,
3784 Discrete_Choices =>
3785 New_Copy_List (Discrete_Choices (Variant)),
3786 Statements => Variant_Stmts));
3788 Next_Non_Pragma (Variant);
3789 end loop;
3791 -- The expression in the case statement is the reference to
3792 -- the discriminant of the target object.
3794 Append_To (Stmts,
3795 Make_Case_Statement (Var_Loc,
3796 Expression =>
3797 Make_Selected_Component (Var_Loc,
3798 Prefix => New_Occurrence_Of (Object_Entity, Var_Loc),
3799 Selector_Name => New_Occurrence_Of
3800 (Entity
3801 (Name (Variant_Part (Comp_List))), Var_Loc)),
3802 Alternatives => Variant_Alts));
3803 end;
3804 end if;
3806 return Stmts;
3807 end Build_Invariant_Checks;
3809 -- Start of processing for Build_Record_Invariant_Proc
3811 begin
3812 Invariant_Found := False;
3813 Type_Def := Type_Definition (Parent (R_Type));
3815 if Nkind (Type_Def) = N_Record_Definition
3816 and then not Null_Present (Type_Def)
3817 then
3818 Stmts := Build_Invariant_Checks (Component_List (Type_Def));
3819 else
3820 return Empty;
3821 end if;
3823 if not Invariant_Found then
3824 return Empty;
3825 end if;
3827 -- The name of the invariant procedure reflects the fact that the
3828 -- checks correspond to invariants on the component types. The
3829 -- record type itself may have invariants that will create a separate
3830 -- procedure whose name carries the Invariant suffix.
3832 Proc_Id :=
3833 Make_Defining_Identifier (Loc,
3834 Chars => New_External_Name (Chars (R_Type), "CInvariant"));
3836 Proc_Body :=
3837 Make_Subprogram_Body (Loc,
3838 Specification =>
3839 Make_Procedure_Specification (Loc,
3840 Defining_Unit_Name => Proc_Id,
3841 Parameter_Specifications => New_List (
3842 Make_Parameter_Specification (Loc,
3843 Defining_Identifier => Object_Entity,
3844 Parameter_Type => New_Occurrence_Of (R_Type, Loc)))),
3846 Declarations => Empty_List,
3847 Handled_Statement_Sequence =>
3848 Make_Handled_Sequence_Of_Statements (Loc,
3849 Statements => Stmts));
3851 Set_Ekind (Proc_Id, E_Procedure);
3852 Set_Is_Public (Proc_Id, Is_Public (R_Type));
3853 Set_Is_Internal (Proc_Id);
3854 Set_Has_Completion (Proc_Id);
3856 return Proc_Body;
3857 -- Insert_After (Nod, Proc_Body);
3858 -- Analyze (Proc_Body);
3859 end Build_Record_Invariant_Proc;
3861 ----------------------------
3862 -- Build_Slice_Assignment --
3863 ----------------------------
3865 -- Generates the following subprogram:
3867 -- procedure Assign
3868 -- (Source, Target : Array_Type,
3869 -- Left_Lo, Left_Hi : Index;
3870 -- Right_Lo, Right_Hi : Index;
3871 -- Rev : Boolean)
3872 -- is
3873 -- Li1 : Index;
3874 -- Ri1 : Index;
3876 -- begin
3878 -- if Left_Hi < Left_Lo then
3879 -- return;
3880 -- end if;
3882 -- if Rev then
3883 -- Li1 := Left_Hi;
3884 -- Ri1 := Right_Hi;
3885 -- else
3886 -- Li1 := Left_Lo;
3887 -- Ri1 := Right_Lo;
3888 -- end if;
3890 -- loop
3891 -- Target (Li1) := Source (Ri1);
3893 -- if Rev then
3894 -- exit when Li1 = Left_Lo;
3895 -- Li1 := Index'pred (Li1);
3896 -- Ri1 := Index'pred (Ri1);
3897 -- else
3898 -- exit when Li1 = Left_Hi;
3899 -- Li1 := Index'succ (Li1);
3900 -- Ri1 := Index'succ (Ri1);
3901 -- end if;
3902 -- end loop;
3903 -- end Assign;
3905 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3906 Loc : constant Source_Ptr := Sloc (Typ);
3907 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3909 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
3910 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
3911 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
3912 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
3913 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
3914 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
3915 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
3916 -- Formal parameters of procedure
3918 Proc_Name : constant Entity_Id :=
3919 Make_Defining_Identifier (Loc,
3920 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3922 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3923 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3924 -- Subscripts for left and right sides
3926 Decls : List_Id;
3927 Loops : Node_Id;
3928 Stats : List_Id;
3930 begin
3931 -- Build declarations for indexes
3933 Decls := New_List;
3935 Append_To (Decls,
3936 Make_Object_Declaration (Loc,
3937 Defining_Identifier => Lnn,
3938 Object_Definition =>
3939 New_Occurrence_Of (Index, Loc)));
3941 Append_To (Decls,
3942 Make_Object_Declaration (Loc,
3943 Defining_Identifier => Rnn,
3944 Object_Definition =>
3945 New_Occurrence_Of (Index, Loc)));
3947 Stats := New_List;
3949 -- Build test for empty slice case
3951 Append_To (Stats,
3952 Make_If_Statement (Loc,
3953 Condition =>
3954 Make_Op_Lt (Loc,
3955 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
3956 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3957 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
3959 -- Build initializations for indexes
3961 declare
3962 F_Init : constant List_Id := New_List;
3963 B_Init : constant List_Id := New_List;
3965 begin
3966 Append_To (F_Init,
3967 Make_Assignment_Statement (Loc,
3968 Name => New_Occurrence_Of (Lnn, Loc),
3969 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3971 Append_To (F_Init,
3972 Make_Assignment_Statement (Loc,
3973 Name => New_Occurrence_Of (Rnn, Loc),
3974 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3976 Append_To (B_Init,
3977 Make_Assignment_Statement (Loc,
3978 Name => New_Occurrence_Of (Lnn, Loc),
3979 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3981 Append_To (B_Init,
3982 Make_Assignment_Statement (Loc,
3983 Name => New_Occurrence_Of (Rnn, Loc),
3984 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3986 Append_To (Stats,
3987 Make_If_Statement (Loc,
3988 Condition => New_Occurrence_Of (Rev, Loc),
3989 Then_Statements => B_Init,
3990 Else_Statements => F_Init));
3991 end;
3993 -- Now construct the assignment statement
3995 Loops :=
3996 Make_Loop_Statement (Loc,
3997 Statements => New_List (
3998 Make_Assignment_Statement (Loc,
3999 Name =>
4000 Make_Indexed_Component (Loc,
4001 Prefix => New_Occurrence_Of (Larray, Loc),
4002 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
4003 Expression =>
4004 Make_Indexed_Component (Loc,
4005 Prefix => New_Occurrence_Of (Rarray, Loc),
4006 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
4007 End_Label => Empty);
4009 -- Build the exit condition and increment/decrement statements
4011 declare
4012 F_Ass : constant List_Id := New_List;
4013 B_Ass : constant List_Id := New_List;
4015 begin
4016 Append_To (F_Ass,
4017 Make_Exit_Statement (Loc,
4018 Condition =>
4019 Make_Op_Eq (Loc,
4020 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4021 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
4023 Append_To (F_Ass,
4024 Make_Assignment_Statement (Loc,
4025 Name => New_Occurrence_Of (Lnn, Loc),
4026 Expression =>
4027 Make_Attribute_Reference (Loc,
4028 Prefix =>
4029 New_Occurrence_Of (Index, Loc),
4030 Attribute_Name => Name_Succ,
4031 Expressions => New_List (
4032 New_Occurrence_Of (Lnn, Loc)))));
4034 Append_To (F_Ass,
4035 Make_Assignment_Statement (Loc,
4036 Name => New_Occurrence_Of (Rnn, Loc),
4037 Expression =>
4038 Make_Attribute_Reference (Loc,
4039 Prefix =>
4040 New_Occurrence_Of (Index, Loc),
4041 Attribute_Name => Name_Succ,
4042 Expressions => New_List (
4043 New_Occurrence_Of (Rnn, Loc)))));
4045 Append_To (B_Ass,
4046 Make_Exit_Statement (Loc,
4047 Condition =>
4048 Make_Op_Eq (Loc,
4049 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4050 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
4052 Append_To (B_Ass,
4053 Make_Assignment_Statement (Loc,
4054 Name => New_Occurrence_Of (Lnn, Loc),
4055 Expression =>
4056 Make_Attribute_Reference (Loc,
4057 Prefix =>
4058 New_Occurrence_Of (Index, Loc),
4059 Attribute_Name => Name_Pred,
4060 Expressions => New_List (
4061 New_Occurrence_Of (Lnn, Loc)))));
4063 Append_To (B_Ass,
4064 Make_Assignment_Statement (Loc,
4065 Name => New_Occurrence_Of (Rnn, Loc),
4066 Expression =>
4067 Make_Attribute_Reference (Loc,
4068 Prefix =>
4069 New_Occurrence_Of (Index, Loc),
4070 Attribute_Name => Name_Pred,
4071 Expressions => New_List (
4072 New_Occurrence_Of (Rnn, Loc)))));
4074 Append_To (Statements (Loops),
4075 Make_If_Statement (Loc,
4076 Condition => New_Occurrence_Of (Rev, Loc),
4077 Then_Statements => B_Ass,
4078 Else_Statements => F_Ass));
4079 end;
4081 Append_To (Stats, Loops);
4083 declare
4084 Spec : Node_Id;
4085 Formals : List_Id := New_List;
4087 begin
4088 Formals := New_List (
4089 Make_Parameter_Specification (Loc,
4090 Defining_Identifier => Larray,
4091 Out_Present => True,
4092 Parameter_Type =>
4093 New_Occurrence_Of (Base_Type (Typ), Loc)),
4095 Make_Parameter_Specification (Loc,
4096 Defining_Identifier => Rarray,
4097 Parameter_Type =>
4098 New_Occurrence_Of (Base_Type (Typ), Loc)),
4100 Make_Parameter_Specification (Loc,
4101 Defining_Identifier => Left_Lo,
4102 Parameter_Type =>
4103 New_Occurrence_Of (Index, Loc)),
4105 Make_Parameter_Specification (Loc,
4106 Defining_Identifier => Left_Hi,
4107 Parameter_Type =>
4108 New_Occurrence_Of (Index, Loc)),
4110 Make_Parameter_Specification (Loc,
4111 Defining_Identifier => Right_Lo,
4112 Parameter_Type =>
4113 New_Occurrence_Of (Index, Loc)),
4115 Make_Parameter_Specification (Loc,
4116 Defining_Identifier => Right_Hi,
4117 Parameter_Type =>
4118 New_Occurrence_Of (Index, Loc)));
4120 Append_To (Formals,
4121 Make_Parameter_Specification (Loc,
4122 Defining_Identifier => Rev,
4123 Parameter_Type =>
4124 New_Occurrence_Of (Standard_Boolean, Loc)));
4126 Spec :=
4127 Make_Procedure_Specification (Loc,
4128 Defining_Unit_Name => Proc_Name,
4129 Parameter_Specifications => Formals);
4131 Discard_Node (
4132 Make_Subprogram_Body (Loc,
4133 Specification => Spec,
4134 Declarations => Decls,
4135 Handled_Statement_Sequence =>
4136 Make_Handled_Sequence_Of_Statements (Loc,
4137 Statements => Stats)));
4138 end;
4140 Set_TSS (Typ, Proc_Name);
4141 Set_Is_Pure (Proc_Name);
4142 end Build_Slice_Assignment;
4144 -----------------------------
4145 -- Build_Untagged_Equality --
4146 -----------------------------
4148 procedure Build_Untagged_Equality (Typ : Entity_Id) is
4149 Build_Eq : Boolean;
4150 Comp : Entity_Id;
4151 Decl : Node_Id;
4152 Op : Entity_Id;
4153 Prim : Elmt_Id;
4154 Eq_Op : Entity_Id;
4156 function User_Defined_Eq (T : Entity_Id) return Entity_Id;
4157 -- Check whether the type T has a user-defined primitive equality. If so
4158 -- return it, else return Empty. If true for a component of Typ, we have
4159 -- to build the primitive equality for it.
4161 ---------------------
4162 -- User_Defined_Eq --
4163 ---------------------
4165 function User_Defined_Eq (T : Entity_Id) return Entity_Id is
4166 Prim : Elmt_Id;
4167 Op : Entity_Id;
4169 begin
4170 Op := TSS (T, TSS_Composite_Equality);
4172 if Present (Op) then
4173 return Op;
4174 end if;
4176 Prim := First_Elmt (Collect_Primitive_Operations (T));
4177 while Present (Prim) loop
4178 Op := Node (Prim);
4180 if Chars (Op) = Name_Op_Eq
4181 and then Etype (Op) = Standard_Boolean
4182 and then Etype (First_Formal (Op)) = T
4183 and then Etype (Next_Formal (First_Formal (Op))) = T
4184 then
4185 return Op;
4186 end if;
4188 Next_Elmt (Prim);
4189 end loop;
4191 return Empty;
4192 end User_Defined_Eq;
4194 -- Start of processing for Build_Untagged_Equality
4196 begin
4197 -- If a record component has a primitive equality operation, we must
4198 -- build the corresponding one for the current type.
4200 Build_Eq := False;
4201 Comp := First_Component (Typ);
4202 while Present (Comp) loop
4203 if Is_Record_Type (Etype (Comp))
4204 and then Present (User_Defined_Eq (Etype (Comp)))
4205 then
4206 Build_Eq := True;
4207 end if;
4209 Next_Component (Comp);
4210 end loop;
4212 -- If there is a user-defined equality for the type, we do not create
4213 -- the implicit one.
4215 Prim := First_Elmt (Collect_Primitive_Operations (Typ));
4216 Eq_Op := Empty;
4217 while Present (Prim) loop
4218 if Chars (Node (Prim)) = Name_Op_Eq
4219 and then Comes_From_Source (Node (Prim))
4221 -- Don't we also need to check formal types and return type as in
4222 -- User_Defined_Eq above???
4224 then
4225 Eq_Op := Node (Prim);
4226 Build_Eq := False;
4227 exit;
4228 end if;
4230 Next_Elmt (Prim);
4231 end loop;
4233 -- If the type is derived, inherit the operation, if present, from the
4234 -- parent type. It may have been declared after the type derivation. If
4235 -- the parent type itself is derived, it may have inherited an operation
4236 -- that has itself been overridden, so update its alias and related
4237 -- flags. Ditto for inequality.
4239 if No (Eq_Op) and then Is_Derived_Type (Typ) then
4240 Prim := First_Elmt (Collect_Primitive_Operations (Etype (Typ)));
4241 while Present (Prim) loop
4242 if Chars (Node (Prim)) = Name_Op_Eq then
4243 Copy_TSS (Node (Prim), Typ);
4244 Build_Eq := False;
4246 declare
4247 Op : constant Entity_Id := User_Defined_Eq (Typ);
4248 Eq_Op : constant Entity_Id := Node (Prim);
4249 NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
4251 begin
4252 if Present (Op) then
4253 Set_Alias (Op, Eq_Op);
4254 Set_Is_Abstract_Subprogram
4255 (Op, Is_Abstract_Subprogram (Eq_Op));
4257 if Chars (Next_Entity (Op)) = Name_Op_Ne then
4258 Set_Is_Abstract_Subprogram
4259 (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
4260 end if;
4261 end if;
4262 end;
4264 exit;
4265 end if;
4267 Next_Elmt (Prim);
4268 end loop;
4269 end if;
4271 -- If not inherited and not user-defined, build body as for a type with
4272 -- tagged components.
4274 if Build_Eq then
4275 Decl :=
4276 Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
4277 Op := Defining_Entity (Decl);
4278 Set_TSS (Typ, Op);
4279 Set_Is_Pure (Op);
4281 if Is_Library_Level_Entity (Typ) then
4282 Set_Is_Public (Op);
4283 end if;
4284 end if;
4285 end Build_Untagged_Equality;
4287 -----------------------------------
4288 -- Build_Variant_Record_Equality --
4289 -----------------------------------
4291 -- Generates:
4293 -- function _Equality (X, Y : T) return Boolean is
4294 -- begin
4295 -- -- Compare discriminants
4297 -- if X.D1 /= Y.D1 or else X.D2 /= Y.D2 or else ... then
4298 -- return False;
4299 -- end if;
4301 -- -- Compare components
4303 -- if X.C1 /= Y.C1 or else X.C2 /= Y.C2 or else ... then
4304 -- return False;
4305 -- end if;
4307 -- -- Compare variant part
4309 -- case X.D1 is
4310 -- when V1 =>
4311 -- if X.C2 /= Y.C2 or else X.C3 /= Y.C3 or else ... then
4312 -- return False;
4313 -- end if;
4314 -- ...
4315 -- when Vn =>
4316 -- if X.Cn /= Y.Cn or else ... then
4317 -- return False;
4318 -- end if;
4319 -- end case;
4321 -- return True;
4322 -- end _Equality;
4324 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
4325 Loc : constant Source_Ptr := Sloc (Typ);
4327 F : constant Entity_Id :=
4328 Make_Defining_Identifier (Loc,
4329 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
4331 X : constant Entity_Id := Make_Defining_Identifier (Loc, Name_X);
4332 Y : constant Entity_Id := Make_Defining_Identifier (Loc, Name_Y);
4334 Def : constant Node_Id := Parent (Typ);
4335 Comps : constant Node_Id := Component_List (Type_Definition (Def));
4336 Stmts : constant List_Id := New_List;
4337 Pspecs : constant List_Id := New_List;
4339 begin
4340 -- If we have a variant record with restriction No_Implicit_Conditionals
4341 -- in effect, then we skip building the procedure. This is safe because
4342 -- if we can see the restriction, so can any caller, calls to equality
4343 -- test routines are not allowed for variant records if this restriction
4344 -- is active.
4346 if Restriction_Active (No_Implicit_Conditionals) then
4347 return;
4348 end if;
4350 -- Derived Unchecked_Union types no longer inherit the equality function
4351 -- of their parent.
4353 if Is_Derived_Type (Typ)
4354 and then not Is_Unchecked_Union (Typ)
4355 and then not Has_New_Non_Standard_Rep (Typ)
4356 then
4357 declare
4358 Parent_Eq : constant Entity_Id :=
4359 TSS (Root_Type (Typ), TSS_Composite_Equality);
4360 begin
4361 if Present (Parent_Eq) then
4362 Copy_TSS (Parent_Eq, Typ);
4363 return;
4364 end if;
4365 end;
4366 end if;
4368 Discard_Node (
4369 Make_Subprogram_Body (Loc,
4370 Specification =>
4371 Make_Function_Specification (Loc,
4372 Defining_Unit_Name => F,
4373 Parameter_Specifications => Pspecs,
4374 Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
4375 Declarations => New_List,
4376 Handled_Statement_Sequence =>
4377 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
4379 Append_To (Pspecs,
4380 Make_Parameter_Specification (Loc,
4381 Defining_Identifier => X,
4382 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4384 Append_To (Pspecs,
4385 Make_Parameter_Specification (Loc,
4386 Defining_Identifier => Y,
4387 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4389 -- Unchecked_Unions require additional machinery to support equality.
4390 -- Two extra parameters (A and B) are added to the equality function
4391 -- parameter list for each discriminant of the type, in order to
4392 -- capture the inferred values of the discriminants in equality calls.
4393 -- The names of the parameters match the names of the corresponding
4394 -- discriminant, with an added suffix.
4396 if Is_Unchecked_Union (Typ) then
4397 declare
4398 Discr : Entity_Id;
4399 Discr_Type : Entity_Id;
4400 A, B : Entity_Id;
4401 New_Discrs : Elist_Id;
4403 begin
4404 New_Discrs := New_Elmt_List;
4406 Discr := First_Discriminant (Typ);
4407 while Present (Discr) loop
4408 Discr_Type := Etype (Discr);
4409 A := Make_Defining_Identifier (Loc,
4410 Chars => New_External_Name (Chars (Discr), 'A'));
4412 B := Make_Defining_Identifier (Loc,
4413 Chars => New_External_Name (Chars (Discr), 'B'));
4415 -- Add new parameters to the parameter list
4417 Append_To (Pspecs,
4418 Make_Parameter_Specification (Loc,
4419 Defining_Identifier => A,
4420 Parameter_Type =>
4421 New_Occurrence_Of (Discr_Type, Loc)));
4423 Append_To (Pspecs,
4424 Make_Parameter_Specification (Loc,
4425 Defining_Identifier => B,
4426 Parameter_Type =>
4427 New_Occurrence_Of (Discr_Type, Loc)));
4429 Append_Elmt (A, New_Discrs);
4431 -- Generate the following code to compare each of the inferred
4432 -- discriminants:
4434 -- if a /= b then
4435 -- return False;
4436 -- end if;
4438 Append_To (Stmts,
4439 Make_If_Statement (Loc,
4440 Condition =>
4441 Make_Op_Ne (Loc,
4442 Left_Opnd => New_Occurrence_Of (A, Loc),
4443 Right_Opnd => New_Occurrence_Of (B, Loc)),
4444 Then_Statements => New_List (
4445 Make_Simple_Return_Statement (Loc,
4446 Expression =>
4447 New_Occurrence_Of (Standard_False, Loc)))));
4448 Next_Discriminant (Discr);
4449 end loop;
4451 -- Generate component-by-component comparison. Note that we must
4452 -- propagate the inferred discriminants formals to act as
4453 -- the case statement switch. Their value is added when an
4454 -- equality call on unchecked unions is expanded.
4456 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps, New_Discrs));
4457 end;
4459 -- Normal case (not unchecked union)
4461 else
4462 Append_To (Stmts,
4463 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
4464 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
4465 end if;
4467 Append_To (Stmts,
4468 Make_Simple_Return_Statement (Loc,
4469 Expression => New_Occurrence_Of (Standard_True, Loc)));
4471 Set_TSS (Typ, F);
4472 Set_Is_Pure (F);
4474 if not Debug_Generated_Code then
4475 Set_Debug_Info_Off (F);
4476 end if;
4477 end Build_Variant_Record_Equality;
4479 -----------------------------
4480 -- Check_Stream_Attributes --
4481 -----------------------------
4483 procedure Check_Stream_Attributes (Typ : Entity_Id) is
4484 Comp : Entity_Id;
4485 Par_Read : constant Boolean :=
4486 Stream_Attribute_Available (Typ, TSS_Stream_Read)
4487 and then not Has_Specified_Stream_Read (Typ);
4488 Par_Write : constant Boolean :=
4489 Stream_Attribute_Available (Typ, TSS_Stream_Write)
4490 and then not Has_Specified_Stream_Write (Typ);
4492 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4493 -- Check that Comp has a user-specified Nam stream attribute
4495 ----------------
4496 -- Check_Attr --
4497 ----------------
4499 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4500 begin
4501 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4502 Error_Msg_Name_1 := Nam;
4503 Error_Msg_N
4504 ("|component& in limited extension must have% attribute", Comp);
4505 end if;
4506 end Check_Attr;
4508 -- Start of processing for Check_Stream_Attributes
4510 begin
4511 if Par_Read or else Par_Write then
4512 Comp := First_Component (Typ);
4513 while Present (Comp) loop
4514 if Comes_From_Source (Comp)
4515 and then Original_Record_Component (Comp) = Comp
4516 and then Is_Limited_Type (Etype (Comp))
4517 then
4518 if Par_Read then
4519 Check_Attr (Name_Read, TSS_Stream_Read);
4520 end if;
4522 if Par_Write then
4523 Check_Attr (Name_Write, TSS_Stream_Write);
4524 end if;
4525 end if;
4527 Next_Component (Comp);
4528 end loop;
4529 end if;
4530 end Check_Stream_Attributes;
4532 -----------------------------
4533 -- Expand_Record_Extension --
4534 -----------------------------
4536 -- Add a field _parent at the beginning of the record extension. This is
4537 -- used to implement inheritance. Here are some examples of expansion:
4539 -- 1. no discriminants
4540 -- type T2 is new T1 with null record;
4541 -- gives
4542 -- type T2 is new T1 with record
4543 -- _Parent : T1;
4544 -- end record;
4546 -- 2. renamed discriminants
4547 -- type T2 (B, C : Int) is new T1 (A => B) with record
4548 -- _Parent : T1 (A => B);
4549 -- D : Int;
4550 -- end;
4552 -- 3. inherited discriminants
4553 -- type T2 is new T1 with record -- discriminant A inherited
4554 -- _Parent : T1 (A);
4555 -- D : Int;
4556 -- end;
4558 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
4559 Indic : constant Node_Id := Subtype_Indication (Def);
4560 Loc : constant Source_Ptr := Sloc (Def);
4561 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
4562 Par_Subtype : Entity_Id;
4563 Comp_List : Node_Id;
4564 Comp_Decl : Node_Id;
4565 Parent_N : Node_Id;
4566 D : Entity_Id;
4567 List_Constr : constant List_Id := New_List;
4569 begin
4570 -- Expand_Record_Extension is called directly from the semantics, so
4571 -- we must check to see whether expansion is active before proceeding,
4572 -- because this affects the visibility of selected components in bodies
4573 -- of instances.
4575 if not Expander_Active then
4576 return;
4577 end if;
4579 -- This may be a derivation of an untagged private type whose full
4580 -- view is tagged, in which case the Derived_Type_Definition has no
4581 -- extension part. Build an empty one now.
4583 if No (Rec_Ext_Part) then
4584 Rec_Ext_Part :=
4585 Make_Record_Definition (Loc,
4586 End_Label => Empty,
4587 Component_List => Empty,
4588 Null_Present => True);
4590 Set_Record_Extension_Part (Def, Rec_Ext_Part);
4591 Mark_Rewrite_Insertion (Rec_Ext_Part);
4592 end if;
4594 Comp_List := Component_List (Rec_Ext_Part);
4596 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
4598 -- If the derived type inherits its discriminants the type of the
4599 -- _parent field must be constrained by the inherited discriminants
4601 if Has_Discriminants (T)
4602 and then Nkind (Indic) /= N_Subtype_Indication
4603 and then not Is_Constrained (Entity (Indic))
4604 then
4605 D := First_Discriminant (T);
4606 while Present (D) loop
4607 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
4608 Next_Discriminant (D);
4609 end loop;
4611 Par_Subtype :=
4612 Process_Subtype (
4613 Make_Subtype_Indication (Loc,
4614 Subtype_Mark => New_Occurrence_Of (Entity (Indic), Loc),
4615 Constraint =>
4616 Make_Index_Or_Discriminant_Constraint (Loc,
4617 Constraints => List_Constr)),
4618 Def);
4620 -- Otherwise the original subtype_indication is just what is needed
4622 else
4623 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
4624 end if;
4626 Set_Parent_Subtype (T, Par_Subtype);
4628 Comp_Decl :=
4629 Make_Component_Declaration (Loc,
4630 Defining_Identifier => Parent_N,
4631 Component_Definition =>
4632 Make_Component_Definition (Loc,
4633 Aliased_Present => False,
4634 Subtype_Indication => New_Occurrence_Of (Par_Subtype, Loc)));
4636 if Null_Present (Rec_Ext_Part) then
4637 Set_Component_List (Rec_Ext_Part,
4638 Make_Component_List (Loc,
4639 Component_Items => New_List (Comp_Decl),
4640 Variant_Part => Empty,
4641 Null_Present => False));
4642 Set_Null_Present (Rec_Ext_Part, False);
4644 elsif Null_Present (Comp_List)
4645 or else Is_Empty_List (Component_Items (Comp_List))
4646 then
4647 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4648 Set_Null_Present (Comp_List, False);
4650 else
4651 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4652 end if;
4654 Analyze (Comp_Decl);
4655 end Expand_Record_Extension;
4657 ------------------------------------
4658 -- Expand_N_Full_Type_Declaration --
4659 ------------------------------------
4661 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
4662 procedure Build_Master (Ptr_Typ : Entity_Id);
4663 -- Create the master associated with Ptr_Typ
4665 ------------------
4666 -- Build_Master --
4667 ------------------
4669 procedure Build_Master (Ptr_Typ : Entity_Id) is
4670 Desig_Typ : Entity_Id := Designated_Type (Ptr_Typ);
4672 begin
4673 -- If the designated type is an incomplete view coming from a
4674 -- limited-with'ed package, we need to use the nonlimited view in
4675 -- case it has tasks.
4677 if Ekind (Desig_Typ) in Incomplete_Kind
4678 and then Present (Non_Limited_View (Desig_Typ))
4679 then
4680 Desig_Typ := Non_Limited_View (Desig_Typ);
4681 end if;
4683 -- Anonymous access types are created for the components of the
4684 -- record parameter for an entry declaration. No master is created
4685 -- for such a type.
4687 if Comes_From_Source (N) and then Has_Task (Desig_Typ) then
4688 Build_Master_Entity (Ptr_Typ);
4689 Build_Master_Renaming (Ptr_Typ);
4691 -- Create a class-wide master because a Master_Id must be generated
4692 -- for access-to-limited-class-wide types whose root may be extended
4693 -- with task components.
4695 -- Note: This code covers access-to-limited-interfaces because they
4696 -- can be used to reference tasks implementing them.
4698 elsif Is_Limited_Class_Wide_Type (Desig_Typ)
4699 and then Tasking_Allowed
4701 -- Do not create a class-wide master for types whose convention is
4702 -- Java since these types cannot embed Ada tasks anyway. Note that
4703 -- the following test cannot catch the following case:
4705 -- package java.lang.Object is
4706 -- type Typ is tagged limited private;
4707 -- type Ref is access all Typ'Class;
4708 -- private
4709 -- type Typ is tagged limited ...;
4710 -- pragma Convention (Typ, Java)
4711 -- end;
4713 -- Because the convention appears after we have done the
4714 -- processing for type Ref.
4716 and then Convention (Desig_Typ) /= Convention_Java
4717 and then Convention (Desig_Typ) /= Convention_CIL
4718 then
4719 Build_Class_Wide_Master (Ptr_Typ);
4720 end if;
4721 end Build_Master;
4723 -- Local declarations
4725 Def_Id : constant Entity_Id := Defining_Identifier (N);
4726 B_Id : constant Entity_Id := Base_Type (Def_Id);
4727 FN : Node_Id;
4728 Par_Id : Entity_Id;
4730 -- Start of processing for Expand_N_Full_Type_Declaration
4732 begin
4733 if Is_Access_Type (Def_Id) then
4734 Build_Master (Def_Id);
4736 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
4737 Expand_Access_Protected_Subprogram_Type (N);
4738 end if;
4740 -- Array of anonymous access-to-task pointers
4742 elsif Ada_Version >= Ada_2005
4743 and then Is_Array_Type (Def_Id)
4744 and then Is_Access_Type (Component_Type (Def_Id))
4745 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
4746 then
4747 Build_Master (Component_Type (Def_Id));
4749 elsif Has_Task (Def_Id) then
4750 Expand_Previous_Access_Type (Def_Id);
4752 -- Check the components of a record type or array of records for
4753 -- anonymous access-to-task pointers.
4755 elsif Ada_Version >= Ada_2005
4756 and then (Is_Record_Type (Def_Id)
4757 or else
4758 (Is_Array_Type (Def_Id)
4759 and then Is_Record_Type (Component_Type (Def_Id))))
4760 then
4761 declare
4762 Comp : Entity_Id;
4763 First : Boolean;
4764 M_Id : Entity_Id;
4765 Typ : Entity_Id;
4767 begin
4768 if Is_Array_Type (Def_Id) then
4769 Comp := First_Entity (Component_Type (Def_Id));
4770 else
4771 Comp := First_Entity (Def_Id);
4772 end if;
4774 -- Examine all components looking for anonymous access-to-task
4775 -- types.
4777 First := True;
4778 while Present (Comp) loop
4779 Typ := Etype (Comp);
4781 if Ekind (Typ) = E_Anonymous_Access_Type
4782 and then Has_Task (Available_View (Designated_Type (Typ)))
4783 and then No (Master_Id (Typ))
4784 then
4785 -- Ensure that the record or array type have a _master
4787 if First then
4788 Build_Master_Entity (Def_Id);
4789 Build_Master_Renaming (Typ);
4790 M_Id := Master_Id (Typ);
4792 First := False;
4794 -- Reuse the same master to service any additional types
4796 else
4797 Set_Master_Id (Typ, M_Id);
4798 end if;
4799 end if;
4801 Next_Entity (Comp);
4802 end loop;
4803 end;
4804 end if;
4806 Par_Id := Etype (B_Id);
4808 -- The parent type is private then we need to inherit any TSS operations
4809 -- from the full view.
4811 if Ekind (Par_Id) in Private_Kind
4812 and then Present (Full_View (Par_Id))
4813 then
4814 Par_Id := Base_Type (Full_View (Par_Id));
4815 end if;
4817 if Nkind (Type_Definition (Original_Node (N))) =
4818 N_Derived_Type_Definition
4819 and then not Is_Tagged_Type (Def_Id)
4820 and then Present (Freeze_Node (Par_Id))
4821 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
4822 then
4823 Ensure_Freeze_Node (B_Id);
4824 FN := Freeze_Node (B_Id);
4826 if No (TSS_Elist (FN)) then
4827 Set_TSS_Elist (FN, New_Elmt_List);
4828 end if;
4830 declare
4831 T_E : constant Elist_Id := TSS_Elist (FN);
4832 Elmt : Elmt_Id;
4834 begin
4835 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4836 while Present (Elmt) loop
4837 if Chars (Node (Elmt)) /= Name_uInit then
4838 Append_Elmt (Node (Elmt), T_E);
4839 end if;
4841 Next_Elmt (Elmt);
4842 end loop;
4844 -- If the derived type itself is private with a full view, then
4845 -- associate the full view with the inherited TSS_Elist as well.
4847 if Ekind (B_Id) in Private_Kind
4848 and then Present (Full_View (B_Id))
4849 then
4850 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4851 Set_TSS_Elist
4852 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4853 end if;
4854 end;
4855 end if;
4856 end Expand_N_Full_Type_Declaration;
4858 ---------------------------------
4859 -- Expand_N_Object_Declaration --
4860 ---------------------------------
4862 procedure Expand_N_Object_Declaration (N : Node_Id) is
4863 Def_Id : constant Entity_Id := Defining_Identifier (N);
4864 Expr : constant Node_Id := Expression (N);
4865 Loc : constant Source_Ptr := Sloc (N);
4866 Obj_Def : constant Node_Id := Object_Definition (N);
4867 Typ : constant Entity_Id := Etype (Def_Id);
4868 Base_Typ : constant Entity_Id := Base_Type (Typ);
4869 Expr_Q : Node_Id;
4871 function Build_Equivalent_Aggregate return Boolean;
4872 -- If the object has a constrained discriminated type and no initial
4873 -- value, it may be possible to build an equivalent aggregate instead,
4874 -- and prevent an actual call to the initialization procedure.
4876 procedure Default_Initialize_Object (After : Node_Id);
4877 -- Generate all default initialization actions for object Def_Id. Any
4878 -- new code is inserted after node After.
4880 function Rewrite_As_Renaming return Boolean;
4881 -- Indicate whether to rewrite a declaration with initialization into an
4882 -- object renaming declaration (see below).
4884 --------------------------------
4885 -- Build_Equivalent_Aggregate --
4886 --------------------------------
4888 function Build_Equivalent_Aggregate return Boolean is
4889 Aggr : Node_Id;
4890 Comp : Entity_Id;
4891 Discr : Elmt_Id;
4892 Full_Type : Entity_Id;
4894 begin
4895 Full_Type := Typ;
4897 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
4898 Full_Type := Full_View (Typ);
4899 end if;
4901 -- Only perform this transformation if Elaboration_Code is forbidden
4902 -- or undesirable, and if this is a global entity of a constrained
4903 -- record type.
4905 -- If Initialize_Scalars might be active this transformation cannot
4906 -- be performed either, because it will lead to different semantics
4907 -- or because elaboration code will in fact be created.
4909 if Ekind (Full_Type) /= E_Record_Subtype
4910 or else not Has_Discriminants (Full_Type)
4911 or else not Is_Constrained (Full_Type)
4912 or else Is_Controlled (Full_Type)
4913 or else Is_Limited_Type (Full_Type)
4914 or else not Restriction_Active (No_Initialize_Scalars)
4915 then
4916 return False;
4917 end if;
4919 if Ekind (Current_Scope) = E_Package
4920 and then
4921 (Restriction_Active (No_Elaboration_Code)
4922 or else Is_Preelaborated (Current_Scope))
4923 then
4924 -- Building a static aggregate is possible if the discriminants
4925 -- have static values and the other components have static
4926 -- defaults or none.
4928 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
4929 while Present (Discr) loop
4930 if not Is_OK_Static_Expression (Node (Discr)) then
4931 return False;
4932 end if;
4934 Next_Elmt (Discr);
4935 end loop;
4937 -- Check that initialized components are OK, and that non-
4938 -- initialized components do not require a call to their own
4939 -- initialization procedure.
4941 Comp := First_Component (Full_Type);
4942 while Present (Comp) loop
4943 if Ekind (Comp) = E_Component
4944 and then Present (Expression (Parent (Comp)))
4945 and then
4946 not Is_OK_Static_Expression (Expression (Parent (Comp)))
4947 then
4948 return False;
4950 elsif Has_Non_Null_Base_Init_Proc (Etype (Comp)) then
4951 return False;
4953 end if;
4955 Next_Component (Comp);
4956 end loop;
4958 -- Everything is static, assemble the aggregate, discriminant
4959 -- values first.
4961 Aggr :=
4962 Make_Aggregate (Loc,
4963 Expressions => New_List,
4964 Component_Associations => New_List);
4966 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
4967 while Present (Discr) loop
4968 Append_To (Expressions (Aggr), New_Copy (Node (Discr)));
4969 Next_Elmt (Discr);
4970 end loop;
4972 -- Now collect values of initialized components
4974 Comp := First_Component (Full_Type);
4975 while Present (Comp) loop
4976 if Ekind (Comp) = E_Component
4977 and then Present (Expression (Parent (Comp)))
4978 then
4979 Append_To (Component_Associations (Aggr),
4980 Make_Component_Association (Loc,
4981 Choices => New_List (New_Occurrence_Of (Comp, Loc)),
4982 Expression => New_Copy_Tree
4983 (Expression (Parent (Comp)))));
4984 end if;
4986 Next_Component (Comp);
4987 end loop;
4989 -- Finally, box-initialize remaining components
4991 Append_To (Component_Associations (Aggr),
4992 Make_Component_Association (Loc,
4993 Choices => New_List (Make_Others_Choice (Loc)),
4994 Expression => Empty));
4995 Set_Box_Present (Last (Component_Associations (Aggr)));
4996 Set_Expression (N, Aggr);
4998 if Typ /= Full_Type then
4999 Analyze_And_Resolve (Aggr, Full_View (Base_Type (Full_Type)));
5000 Rewrite (Aggr, Unchecked_Convert_To (Typ, Aggr));
5001 Analyze_And_Resolve (Aggr, Typ);
5002 else
5003 Analyze_And_Resolve (Aggr, Full_Type);
5004 end if;
5006 return True;
5008 else
5009 return False;
5010 end if;
5011 end Build_Equivalent_Aggregate;
5013 -------------------------------
5014 -- Default_Initialize_Object --
5015 -------------------------------
5017 procedure Default_Initialize_Object (After : Node_Id) is
5018 function New_Object_Reference return Node_Id;
5019 -- Return a new reference to Def_Id with attributes Assignment_OK and
5020 -- Must_Not_Freeze already set.
5022 --------------------------
5023 -- New_Object_Reference --
5024 --------------------------
5026 function New_Object_Reference return Node_Id is
5027 Obj_Ref : constant Node_Id := New_Occurrence_Of (Def_Id, Loc);
5029 begin
5030 -- The call to the type init proc or [Deep_]Finalize must not
5031 -- freeze the related object as the call is internally generated.
5032 -- This way legal rep clauses that apply to the object will not be
5033 -- flagged. Note that the initialization call may be removed if
5034 -- pragma Import is encountered or moved to the freeze actions of
5035 -- the object because of an address clause.
5037 Set_Assignment_OK (Obj_Ref);
5038 Set_Must_Not_Freeze (Obj_Ref);
5040 return Obj_Ref;
5041 end New_Object_Reference;
5043 -- Local variables
5045 Abrt_Blk : Node_Id;
5046 Abrt_HSS : Node_Id;
5047 Abrt_Id : Entity_Id;
5048 Abrt_Stmts : List_Id;
5049 Aggr_Init : Node_Id;
5050 Comp_Init : List_Id := No_List;
5051 Fin_Call : Node_Id;
5052 Fin_Stmts : List_Id := No_List;
5053 Obj_Init : Node_Id := Empty;
5054 Obj_Ref : Node_Id;
5056 Dummy : Entity_Id;
5057 -- This variable captures a dummy internal entity, see the comment
5058 -- associated with its use.
5060 -- Start of processing for Default_Initialize_Object
5062 begin
5063 -- Default initialization is suppressed for objects that are already
5064 -- known to be imported (i.e. whose declaration specifies the Import
5065 -- aspect). Note that for objects with a pragma Import, we generate
5066 -- initialization here, and then remove it downstream when processing
5067 -- the pragma.
5069 if Is_Imported (Def_Id) then
5070 return;
5071 end if;
5073 -- Step 1: Initialize the object
5075 if Needs_Finalization (Typ) and then not No_Initialization (N) then
5076 Obj_Init :=
5077 Make_Init_Call
5078 (Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5079 Typ => Typ);
5080 end if;
5082 -- Step 2: Initialize the components of the object
5084 -- Do not initialize the components if their initialization is
5085 -- prohibited or the type represents a value type in a .NET VM.
5087 if Has_Non_Null_Base_Init_Proc (Typ)
5088 and then not No_Initialization (N)
5089 and then not Initialization_Suppressed (Typ)
5090 and then not Is_Value_Type (Typ)
5091 then
5092 -- Do not initialize the components if No_Default_Initialization
5093 -- applies as the the actual restriction check will occur later
5094 -- when the object is frozen as it is not known yet whether the
5095 -- object is imported or not.
5097 if not Restriction_Active (No_Default_Initialization) then
5099 -- If the values of the components are compile-time known, use
5100 -- their prebuilt aggregate form directly.
5102 Aggr_Init := Static_Initialization (Base_Init_Proc (Typ));
5104 if Present (Aggr_Init) then
5105 Set_Expression
5106 (N, New_Copy_Tree (Aggr_Init, New_Scope => Current_Scope));
5108 -- If type has discriminants, try to build an equivalent
5109 -- aggregate using discriminant values from the declaration.
5110 -- This is a useful optimization, in particular if restriction
5111 -- No_Elaboration_Code is active.
5113 elsif Build_Equivalent_Aggregate then
5114 null;
5116 -- Otherwise invoke the type init proc
5118 else
5119 Obj_Ref := New_Object_Reference;
5121 if Comes_From_Source (Def_Id) then
5122 Initialization_Warning (Obj_Ref);
5123 end if;
5125 Comp_Init := Build_Initialization_Call (Loc, Obj_Ref, Typ);
5126 end if;
5127 end if;
5129 -- Provide a default value if the object needs simple initialization
5130 -- and does not already have an initial value. A generated temporary
5131 -- do not require initialization because it will be assigned later.
5133 elsif Needs_Simple_Initialization
5134 (Typ, Initialize_Scalars
5135 and then not Has_Following_Address_Clause (N))
5136 and then not Is_Internal (Def_Id)
5137 and then not Has_Init_Expression (N)
5138 then
5139 Set_No_Initialization (N, False);
5140 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
5141 Analyze_And_Resolve (Expression (N), Typ);
5142 end if;
5144 -- Step 3: Add partial finalization and abort actions, generate:
5146 -- Type_Init_Proc (Obj);
5147 -- begin
5148 -- Deep_Initialize (Obj);
5149 -- exception
5150 -- when others =>
5151 -- Deep_Finalize (Obj, Self => False);
5152 -- raise;
5153 -- end;
5155 -- Step 3a: Build the finalization block (if applicable)
5157 -- The finalization block is required when both the object and its
5158 -- controlled components are to be initialized. The block finalizes
5159 -- the components if the object initialization fails.
5161 if Has_Controlled_Component (Typ)
5162 and then Present (Comp_Init)
5163 and then Present (Obj_Init)
5164 and then not Restriction_Active (No_Exception_Propagation)
5165 then
5166 -- Generate:
5167 -- Type_Init_Proc (Obj);
5169 Fin_Stmts := Comp_Init;
5171 -- Generate:
5172 -- begin
5173 -- Deep_Initialize (Obj);
5174 -- exception
5175 -- when others =>
5176 -- Deep_Finalize (Obj, Self => False);
5177 -- raise;
5178 -- end;
5180 Fin_Call :=
5181 Make_Final_Call
5182 (Obj_Ref => New_Object_Reference,
5183 Typ => Typ,
5184 Skip_Self => True);
5186 if Present (Fin_Call) then
5188 -- Do not emit warnings related to the elaboration order when a
5189 -- controlled object is declared before the body of Finalize is
5190 -- seen.
5192 Set_No_Elaboration_Check (Fin_Call);
5194 Append_To (Fin_Stmts,
5195 Make_Block_Statement (Loc,
5196 Declarations => No_List,
5198 Handled_Statement_Sequence =>
5199 Make_Handled_Sequence_Of_Statements (Loc,
5200 Statements => New_List (Obj_Init),
5202 Exception_Handlers => New_List (
5203 Make_Exception_Handler (Loc,
5204 Exception_Choices => New_List (
5205 Make_Others_Choice (Loc)),
5207 Statements => New_List (
5208 Fin_Call,
5209 Make_Raise_Statement (Loc)))))));
5210 end if;
5212 -- Finalization is not required, the initialization calls are passed
5213 -- to the abort block building circuitry, generate:
5215 -- Type_Init_Proc (Obj);
5216 -- Deep_Initialize (Obj);
5218 else
5219 if Present (Comp_Init) then
5220 Fin_Stmts := Comp_Init;
5221 end if;
5223 if Present (Obj_Init) then
5224 if No (Fin_Stmts) then
5225 Fin_Stmts := New_List;
5226 end if;
5228 Append_To (Fin_Stmts, Obj_Init);
5229 end if;
5230 end if;
5232 -- Step 3b: Build the abort block (if applicable)
5234 -- The abort block is required when aborts are allowed in order to
5235 -- protect both initialization calls.
5237 if Present (Comp_Init) and then Present (Obj_Init) then
5238 if Abort_Allowed then
5240 -- Generate:
5241 -- Abort_Defer;
5243 Prepend_To
5244 (Fin_Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
5246 -- Generate:
5247 -- begin
5248 -- Abort_Defer;
5249 -- <finalization statements>
5250 -- at end
5251 -- Abort_Undefer_Direct;
5252 -- end;
5254 Abrt_HSS :=
5255 Make_Handled_Sequence_Of_Statements (Loc,
5256 Statements => Fin_Stmts,
5257 At_End_Proc =>
5258 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
5260 Abrt_Blk :=
5261 Make_Block_Statement (Loc,
5262 Declarations => No_List,
5263 Handled_Statement_Sequence => Abrt_HSS);
5265 Add_Block_Identifier (Abrt_Blk, Abrt_Id);
5266 Expand_At_End_Handler (Abrt_HSS, Abrt_Id);
5268 Abrt_Stmts := New_List (Abrt_Blk);
5270 -- Abort is not required
5272 else
5273 -- Generate a dummy entity to ensure that the internal symbols
5274 -- are in sync when a unit is compiled with and without aborts.
5275 -- The entity is a block with proper scope and type.
5277 Dummy := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
5278 Set_Etype (Dummy, Standard_Void_Type);
5279 Abrt_Stmts := Fin_Stmts;
5280 end if;
5282 -- No initialization calls present
5284 else
5285 Abrt_Stmts := Fin_Stmts;
5286 end if;
5288 -- Step 4: Insert the whole initialization sequence into the tree
5290 Insert_Actions_After (After, Abrt_Stmts);
5291 end Default_Initialize_Object;
5293 -------------------------
5294 -- Rewrite_As_Renaming --
5295 -------------------------
5297 function Rewrite_As_Renaming return Boolean is
5298 begin
5299 return not Aliased_Present (N)
5300 and then Is_Entity_Name (Expr_Q)
5301 and then Ekind (Entity (Expr_Q)) = E_Variable
5302 and then OK_To_Rename (Entity (Expr_Q))
5303 and then Is_Entity_Name (Obj_Def);
5304 end Rewrite_As_Renaming;
5306 -- Local variables
5308 Next_N : constant Node_Id := Next (N);
5309 Id_Ref : Node_Id;
5310 New_Ref : Node_Id;
5312 Init_After : Node_Id := N;
5313 -- Node after which the initialization actions are to be inserted. This
5314 -- is normally N, except for the case of a shared passive variable, in
5315 -- which case the init proc call must be inserted only after the bodies
5316 -- of the shared variable procedures have been seen.
5318 -- Start of processing for Expand_N_Object_Declaration
5320 begin
5321 -- Don't do anything for deferred constants. All proper actions will be
5322 -- expanded during the full declaration.
5324 if No (Expr) and Constant_Present (N) then
5325 return;
5326 end if;
5328 -- First we do special processing for objects of a tagged type where
5329 -- this is the point at which the type is frozen. The creation of the
5330 -- dispatch table and the initialization procedure have to be deferred
5331 -- to this point, since we reference previously declared primitive
5332 -- subprograms.
5334 -- Force construction of dispatch tables of library level tagged types
5336 if Tagged_Type_Expansion
5337 and then Static_Dispatch_Tables
5338 and then Is_Library_Level_Entity (Def_Id)
5339 and then Is_Library_Level_Tagged_Type (Base_Typ)
5340 and then (Ekind (Base_Typ) = E_Record_Type
5341 or else Ekind (Base_Typ) = E_Protected_Type
5342 or else Ekind (Base_Typ) = E_Task_Type)
5343 and then not Has_Dispatch_Table (Base_Typ)
5344 then
5345 declare
5346 New_Nodes : List_Id := No_List;
5348 begin
5349 if Is_Concurrent_Type (Base_Typ) then
5350 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
5351 else
5352 New_Nodes := Make_DT (Base_Typ, N);
5353 end if;
5355 if not Is_Empty_List (New_Nodes) then
5356 Insert_List_Before (N, New_Nodes);
5357 end if;
5358 end;
5359 end if;
5361 -- Make shared memory routines for shared passive variable
5363 if Is_Shared_Passive (Def_Id) then
5364 Init_After := Make_Shared_Var_Procs (N);
5365 end if;
5367 -- If tasks being declared, make sure we have an activation chain
5368 -- defined for the tasks (has no effect if we already have one), and
5369 -- also that a Master variable is established and that the appropriate
5370 -- enclosing construct is established as a task master.
5372 if Has_Task (Typ) then
5373 Build_Activation_Chain_Entity (N);
5374 Build_Master_Entity (Def_Id);
5375 end if;
5377 -- Default initialization required, and no expression present
5379 if No (Expr) then
5381 -- If we have a type with a variant part, the initialization proc
5382 -- will contain implicit tests of the discriminant values, which
5383 -- counts as a violation of the restriction No_Implicit_Conditionals.
5385 if Has_Variant_Part (Typ) then
5386 declare
5387 Msg : Boolean;
5389 begin
5390 Check_Restriction (Msg, No_Implicit_Conditionals, Obj_Def);
5392 if Msg then
5393 Error_Msg_N
5394 ("\initialization of variant record tests discriminants",
5395 Obj_Def);
5396 return;
5397 end if;
5398 end;
5399 end if;
5401 -- For the default initialization case, if we have a private type
5402 -- with invariants, and invariant checks are enabled, then insert an
5403 -- invariant check after the object declaration. Note that it is OK
5404 -- to clobber the object with an invalid value since if the exception
5405 -- is raised, then the object will go out of scope. In the case where
5406 -- an array object is initialized with an aggregate, the expression
5407 -- is removed. Check flag Has_Init_Expression to avoid generating a
5408 -- junk invariant check and flag No_Initialization to avoid checking
5409 -- an uninitialized object such as a compiler temporary used for an
5410 -- aggregate.
5412 if Has_Invariants (Base_Typ)
5413 and then Present (Invariant_Procedure (Base_Typ))
5414 and then not Has_Init_Expression (N)
5415 and then not No_Initialization (N)
5416 then
5417 Insert_After (N,
5418 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
5419 end if;
5421 Default_Initialize_Object (Init_After);
5423 -- Generate attribute for Persistent_BSS if needed
5425 if Persistent_BSS_Mode
5426 and then Comes_From_Source (N)
5427 and then Is_Potentially_Persistent_Type (Typ)
5428 and then not Has_Init_Expression (N)
5429 and then Is_Library_Level_Entity (Def_Id)
5430 then
5431 declare
5432 Prag : Node_Id;
5433 begin
5434 Prag :=
5435 Make_Linker_Section_Pragma
5436 (Def_Id, Sloc (N), ".persistent.bss");
5437 Insert_After (N, Prag);
5438 Analyze (Prag);
5439 end;
5440 end if;
5442 -- If access type, then we know it is null if not initialized
5444 if Is_Access_Type (Typ) then
5445 Set_Is_Known_Null (Def_Id);
5446 end if;
5448 -- Explicit initialization present
5450 else
5451 -- Obtain actual expression from qualified expression
5453 if Nkind (Expr) = N_Qualified_Expression then
5454 Expr_Q := Expression (Expr);
5455 else
5456 Expr_Q := Expr;
5457 end if;
5459 -- When we have the appropriate type of aggregate in the expression
5460 -- (it has been determined during analysis of the aggregate by
5461 -- setting the delay flag), let's perform in place assignment and
5462 -- thus avoid creating a temporary.
5464 if Is_Delayed_Aggregate (Expr_Q) then
5465 Convert_Aggr_In_Object_Decl (N);
5467 -- Ada 2005 (AI-318-02): If the initialization expression is a call
5468 -- to a build-in-place function, then access to the declared object
5469 -- must be passed to the function. Currently we limit such functions
5470 -- to those with constrained limited result subtypes, but eventually
5471 -- plan to expand the allowed forms of functions that are treated as
5472 -- build-in-place.
5474 elsif Ada_Version >= Ada_2005
5475 and then Is_Build_In_Place_Function_Call (Expr_Q)
5476 then
5477 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
5479 -- The previous call expands the expression initializing the
5480 -- built-in-place object into further code that will be analyzed
5481 -- later. No further expansion needed here.
5483 return;
5485 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
5486 -- class-wide interface object to ensure that we copy the full
5487 -- object, unless we are targetting a VM where interfaces are handled
5488 -- by VM itself. Note that if the root type of Typ is an ancestor of
5489 -- Expr's type, both types share the same dispatch table and there is
5490 -- no need to displace the pointer.
5492 elsif Is_Interface (Typ)
5494 -- Avoid never-ending recursion because if Equivalent_Type is set
5495 -- then we've done it already and must not do it again.
5497 and then not
5498 (Nkind (Obj_Def) = N_Identifier
5499 and then Present (Equivalent_Type (Entity (Obj_Def))))
5500 then
5501 pragma Assert (Is_Class_Wide_Type (Typ));
5503 -- If the object is a return object of an inherently limited type,
5504 -- which implies build-in-place treatment, bypass the special
5505 -- treatment of class-wide interface initialization below. In this
5506 -- case, the expansion of the return statement will take care of
5507 -- creating the object (via allocator) and initializing it.
5509 if Is_Return_Object (Def_Id) and then Is_Limited_View (Typ) then
5510 null;
5512 elsif Tagged_Type_Expansion then
5513 declare
5514 Iface : constant Entity_Id := Root_Type (Typ);
5515 Expr_N : Node_Id := Expr;
5516 Expr_Typ : Entity_Id;
5517 New_Expr : Node_Id;
5518 Obj_Id : Entity_Id;
5519 Tag_Comp : Node_Id;
5521 begin
5522 -- If the original node of the expression was a conversion
5523 -- to this specific class-wide interface type then restore
5524 -- the original node because we must copy the object before
5525 -- displacing the pointer to reference the secondary tag
5526 -- component. This code must be kept synchronized with the
5527 -- expansion done by routine Expand_Interface_Conversion
5529 if not Comes_From_Source (Expr_N)
5530 and then Nkind (Expr_N) = N_Explicit_Dereference
5531 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
5532 and then Etype (Original_Node (Expr_N)) = Typ
5533 then
5534 Rewrite (Expr_N, Original_Node (Expression (N)));
5535 end if;
5537 -- Avoid expansion of redundant interface conversion
5539 if Is_Interface (Etype (Expr_N))
5540 and then Nkind (Expr_N) = N_Type_Conversion
5541 and then Etype (Expr_N) = Typ
5542 then
5543 Expr_N := Expression (Expr_N);
5544 Set_Expression (N, Expr_N);
5545 end if;
5547 Obj_Id := Make_Temporary (Loc, 'D', Expr_N);
5548 Expr_Typ := Base_Type (Etype (Expr_N));
5550 if Is_Class_Wide_Type (Expr_Typ) then
5551 Expr_Typ := Root_Type (Expr_Typ);
5552 end if;
5554 -- Replace
5555 -- CW : I'Class := Obj;
5556 -- by
5557 -- Tmp : T := Obj;
5558 -- type Ityp is not null access I'Class;
5559 -- CW : I'Class renames Ityp (Tmp.I_Tag'Address).all;
5561 if Comes_From_Source (Expr_N)
5562 and then Nkind (Expr_N) = N_Identifier
5563 and then not Is_Interface (Expr_Typ)
5564 and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
5565 and then (Expr_Typ = Etype (Expr_Typ)
5566 or else not
5567 Is_Variable_Size_Record (Etype (Expr_Typ)))
5568 then
5569 -- Copy the object
5571 Insert_Action (N,
5572 Make_Object_Declaration (Loc,
5573 Defining_Identifier => Obj_Id,
5574 Object_Definition =>
5575 New_Occurrence_Of (Expr_Typ, Loc),
5576 Expression => Relocate_Node (Expr_N)));
5578 -- Statically reference the tag associated with the
5579 -- interface
5581 Tag_Comp :=
5582 Make_Selected_Component (Loc,
5583 Prefix => New_Occurrence_Of (Obj_Id, Loc),
5584 Selector_Name =>
5585 New_Occurrence_Of
5586 (Find_Interface_Tag (Expr_Typ, Iface), Loc));
5588 -- Replace
5589 -- IW : I'Class := Obj;
5590 -- by
5591 -- type Equiv_Record is record ... end record;
5592 -- implicit subtype CW is <Class_Wide_Subtype>;
5593 -- Tmp : CW := CW!(Obj);
5594 -- type Ityp is not null access I'Class;
5595 -- IW : I'Class renames
5596 -- Ityp!(Displace (Temp'Address, I'Tag)).all;
5598 else
5599 -- Generate the equivalent record type and update the
5600 -- subtype indication to reference it.
5602 Expand_Subtype_From_Expr
5603 (N => N,
5604 Unc_Type => Typ,
5605 Subtype_Indic => Obj_Def,
5606 Exp => Expr_N);
5608 if not Is_Interface (Etype (Expr_N)) then
5609 New_Expr := Relocate_Node (Expr_N);
5611 -- For interface types we use 'Address which displaces
5612 -- the pointer to the base of the object (if required)
5614 else
5615 New_Expr :=
5616 Unchecked_Convert_To (Etype (Obj_Def),
5617 Make_Explicit_Dereference (Loc,
5618 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
5619 Make_Attribute_Reference (Loc,
5620 Prefix => Relocate_Node (Expr_N),
5621 Attribute_Name => Name_Address))));
5622 end if;
5624 -- Copy the object
5626 if not Is_Limited_Record (Expr_Typ) then
5627 Insert_Action (N,
5628 Make_Object_Declaration (Loc,
5629 Defining_Identifier => Obj_Id,
5630 Object_Definition =>
5631 New_Occurrence_Of (Etype (Obj_Def), Loc),
5632 Expression => New_Expr));
5634 -- Rename limited type object since they cannot be copied
5635 -- This case occurs when the initialization expression
5636 -- has been previously expanded into a temporary object.
5638 else pragma Assert (not Comes_From_Source (Expr_Q));
5639 Insert_Action (N,
5640 Make_Object_Renaming_Declaration (Loc,
5641 Defining_Identifier => Obj_Id,
5642 Subtype_Mark =>
5643 New_Occurrence_Of (Etype (Obj_Def), Loc),
5644 Name =>
5645 Unchecked_Convert_To
5646 (Etype (Obj_Def), New_Expr)));
5647 end if;
5649 -- Dynamically reference the tag associated with the
5650 -- interface.
5652 Tag_Comp :=
5653 Make_Function_Call (Loc,
5654 Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
5655 Parameter_Associations => New_List (
5656 Make_Attribute_Reference (Loc,
5657 Prefix => New_Occurrence_Of (Obj_Id, Loc),
5658 Attribute_Name => Name_Address),
5659 New_Occurrence_Of
5660 (Node (First_Elmt (Access_Disp_Table (Iface))),
5661 Loc)));
5662 end if;
5664 Rewrite (N,
5665 Make_Object_Renaming_Declaration (Loc,
5666 Defining_Identifier => Make_Temporary (Loc, 'D'),
5667 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
5668 Name =>
5669 Convert_Tag_To_Interface (Typ, Tag_Comp)));
5671 -- If the original entity comes from source, then mark the
5672 -- new entity as needing debug information, even though it's
5673 -- defined by a generated renaming that does not come from
5674 -- source, so that Materialize_Entity will be set on the
5675 -- entity when Debug_Renaming_Declaration is called during
5676 -- analysis.
5678 if Comes_From_Source (Def_Id) then
5679 Set_Debug_Info_Needed (Defining_Identifier (N));
5680 end if;
5682 Analyze (N, Suppress => All_Checks);
5684 -- Replace internal identifier of rewritten node by the
5685 -- identifier found in the sources. We also have to exchange
5686 -- entities containing their defining identifiers to ensure
5687 -- the correct replacement of the object declaration by this
5688 -- object renaming declaration because these identifiers
5689 -- were previously added by Enter_Name to the current scope.
5690 -- We must preserve the homonym chain of the source entity
5691 -- as well. We must also preserve the kind of the entity,
5692 -- which may be a constant. Preserve entity chain because
5693 -- itypes may have been generated already, and the full
5694 -- chain must be preserved for final freezing. Finally,
5695 -- preserve Comes_From_Source setting, so that debugging
5696 -- and cross-referencing information is properly kept, and
5697 -- preserve source location, to prevent spurious errors when
5698 -- entities are declared (they must have their own Sloc).
5700 declare
5701 New_Id : constant Entity_Id := Defining_Identifier (N);
5702 Next_Temp : constant Entity_Id := Next_Entity (New_Id);
5703 S_Flag : constant Boolean :=
5704 Comes_From_Source (Def_Id);
5706 begin
5707 Set_Next_Entity (New_Id, Next_Entity (Def_Id));
5708 Set_Next_Entity (Def_Id, Next_Temp);
5710 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
5711 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
5712 Set_Ekind (Defining_Identifier (N), Ekind (Def_Id));
5713 Set_Sloc (Defining_Identifier (N), Sloc (Def_Id));
5715 Set_Comes_From_Source (Def_Id, False);
5716 Exchange_Entities (Defining_Identifier (N), Def_Id);
5717 Set_Comes_From_Source (Def_Id, S_Flag);
5718 end;
5719 end;
5720 end if;
5722 return;
5724 -- Common case of explicit object initialization
5726 else
5727 -- In most cases, we must check that the initial value meets any
5728 -- constraint imposed by the declared type. However, there is one
5729 -- very important exception to this rule. If the entity has an
5730 -- unconstrained nominal subtype, then it acquired its constraints
5731 -- from the expression in the first place, and not only does this
5732 -- mean that the constraint check is not needed, but an attempt to
5733 -- perform the constraint check can cause order of elaboration
5734 -- problems.
5736 if not Is_Constr_Subt_For_U_Nominal (Typ) then
5738 -- If this is an allocator for an aggregate that has been
5739 -- allocated in place, delay checks until assignments are
5740 -- made, because the discriminants are not initialized.
5742 if Nkind (Expr) = N_Allocator and then No_Initialization (Expr)
5743 then
5744 null;
5746 -- Otherwise apply a constraint check now if no prev error
5748 elsif Nkind (Expr) /= N_Error then
5749 Apply_Constraint_Check (Expr, Typ);
5751 -- Deal with possible range check
5753 if Do_Range_Check (Expr) then
5755 -- If assignment checks are suppressed, turn off flag
5757 if Suppress_Assignment_Checks (N) then
5758 Set_Do_Range_Check (Expr, False);
5760 -- Otherwise generate the range check
5762 else
5763 Generate_Range_Check
5764 (Expr, Typ, CE_Range_Check_Failed);
5765 end if;
5766 end if;
5767 end if;
5768 end if;
5770 -- If the type is controlled and not inherently limited, then
5771 -- the target is adjusted after the copy and attached to the
5772 -- finalization list. However, no adjustment is done in the case
5773 -- where the object was initialized by a call to a function whose
5774 -- result is built in place, since no copy occurred. (Eventually
5775 -- we plan to support in-place function results for some cases
5776 -- of nonlimited types. ???) Similarly, no adjustment is required
5777 -- if we are going to rewrite the object declaration into a
5778 -- renaming declaration.
5780 if Needs_Finalization (Typ)
5781 and then not Is_Limited_View (Typ)
5782 and then not Rewrite_As_Renaming
5783 then
5784 Insert_Action_After (Init_After,
5785 Make_Adjust_Call (
5786 Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5787 Typ => Base_Typ));
5788 end if;
5790 -- For tagged types, when an init value is given, the tag has to
5791 -- be re-initialized separately in order to avoid the propagation
5792 -- of a wrong tag coming from a view conversion unless the type
5793 -- is class wide (in this case the tag comes from the init value).
5794 -- Suppress the tag assignment when VM_Target because VM tags are
5795 -- represented implicitly in objects. Ditto for types that are
5796 -- CPP_CLASS, and for initializations that are aggregates, because
5797 -- they have to have the right tag.
5799 if Is_Tagged_Type (Typ)
5800 and then not Is_Class_Wide_Type (Typ)
5801 and then not Is_CPP_Class (Typ)
5802 and then Tagged_Type_Expansion
5803 and then Nkind (Expr) /= N_Aggregate
5804 and then (Nkind (Expr) /= N_Qualified_Expression
5805 or else Nkind (Expression (Expr)) /= N_Aggregate)
5806 then
5807 declare
5808 Full_Typ : constant Entity_Id := Underlying_Type (Typ);
5810 begin
5811 -- The re-assignment of the tag has to be done even if the
5812 -- object is a constant. The assignment must be analyzed
5813 -- after the declaration.
5815 New_Ref :=
5816 Make_Selected_Component (Loc,
5817 Prefix => New_Occurrence_Of (Def_Id, Loc),
5818 Selector_Name =>
5819 New_Occurrence_Of (First_Tag_Component (Full_Typ),
5820 Loc));
5821 Set_Assignment_OK (New_Ref);
5823 Insert_Action_After (Init_After,
5824 Make_Assignment_Statement (Loc,
5825 Name => New_Ref,
5826 Expression =>
5827 Unchecked_Convert_To (RTE (RE_Tag),
5828 New_Occurrence_Of
5829 (Node (First_Elmt (Access_Disp_Table (Full_Typ))),
5830 Loc))));
5831 end;
5833 -- Handle C++ constructor calls. Note that we do not check that
5834 -- Typ is a tagged type since the equivalent Ada type of a C++
5835 -- class that has no virtual methods is an untagged limited
5836 -- record type.
5838 elsif Is_CPP_Constructor_Call (Expr) then
5840 -- The call to the initialization procedure does NOT freeze the
5841 -- object being initialized.
5843 Id_Ref := New_Occurrence_Of (Def_Id, Loc);
5844 Set_Must_Not_Freeze (Id_Ref);
5845 Set_Assignment_OK (Id_Ref);
5847 Insert_Actions_After (Init_After,
5848 Build_Initialization_Call (Loc, Id_Ref, Typ,
5849 Constructor_Ref => Expr));
5851 -- We remove here the original call to the constructor
5852 -- to avoid its management in the backend
5854 Set_Expression (N, Empty);
5855 return;
5857 -- For discrete types, set the Is_Known_Valid flag if the
5858 -- initializing value is known to be valid. Only do this for
5859 -- source assignments, since otherwise we can end up turning
5860 -- on the known valid flag prematurely from inserted code.
5862 elsif Comes_From_Source (N)
5863 and then Is_Discrete_Type (Typ)
5864 and then Expr_Known_Valid (Expr)
5865 then
5866 Set_Is_Known_Valid (Def_Id);
5868 elsif Is_Access_Type (Typ) then
5870 -- For access types set the Is_Known_Non_Null flag if the
5871 -- initializing value is known to be non-null. We can also set
5872 -- Can_Never_Be_Null if this is a constant.
5874 if Known_Non_Null (Expr) then
5875 Set_Is_Known_Non_Null (Def_Id, True);
5877 if Constant_Present (N) then
5878 Set_Can_Never_Be_Null (Def_Id);
5879 end if;
5880 end if;
5881 end if;
5883 -- If validity checking on copies, validate initial expression.
5884 -- But skip this if declaration is for a generic type, since it
5885 -- makes no sense to validate generic types. Not clear if this
5886 -- can happen for legal programs, but it definitely can arise
5887 -- from previous instantiation errors.
5889 if Validity_Checks_On
5890 and then Validity_Check_Copies
5891 and then not Is_Generic_Type (Etype (Def_Id))
5892 then
5893 Ensure_Valid (Expr);
5894 Set_Is_Known_Valid (Def_Id);
5895 end if;
5896 end if;
5898 -- Cases where the back end cannot handle the initialization directly
5899 -- In such cases, we expand an assignment that will be appropriately
5900 -- handled by Expand_N_Assignment_Statement.
5902 -- The exclusion of the unconstrained case is wrong, but for now it
5903 -- is too much trouble ???
5905 if (Is_Possibly_Unaligned_Slice (Expr)
5906 or else (Is_Possibly_Unaligned_Object (Expr)
5907 and then not Represented_As_Scalar (Etype (Expr))))
5908 and then not (Is_Array_Type (Etype (Expr))
5909 and then not Is_Constrained (Etype (Expr)))
5910 then
5911 declare
5912 Stat : constant Node_Id :=
5913 Make_Assignment_Statement (Loc,
5914 Name => New_Occurrence_Of (Def_Id, Loc),
5915 Expression => Relocate_Node (Expr));
5916 begin
5917 Set_Expression (N, Empty);
5918 Set_No_Initialization (N);
5919 Set_Assignment_OK (Name (Stat));
5920 Set_No_Ctrl_Actions (Stat);
5921 Insert_After_And_Analyze (Init_After, Stat);
5922 end;
5923 end if;
5925 -- Final transformation, if the initializing expression is an entity
5926 -- for a variable with OK_To_Rename set, then we transform:
5928 -- X : typ := expr;
5930 -- into
5932 -- X : typ renames expr
5934 -- provided that X is not aliased. The aliased case has to be
5935 -- excluded in general because Expr will not be aliased in general.
5937 if Rewrite_As_Renaming then
5938 Rewrite (N,
5939 Make_Object_Renaming_Declaration (Loc,
5940 Defining_Identifier => Defining_Identifier (N),
5941 Subtype_Mark => Obj_Def,
5942 Name => Expr_Q));
5944 -- We do not analyze this renaming declaration, because all its
5945 -- components have already been analyzed, and if we were to go
5946 -- ahead and analyze it, we would in effect be trying to generate
5947 -- another declaration of X, which won't do.
5949 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
5950 Set_Analyzed (N);
5952 -- We do need to deal with debug issues for this renaming
5954 -- First, if entity comes from source, then mark it as needing
5955 -- debug information, even though it is defined by a generated
5956 -- renaming that does not come from source.
5958 if Comes_From_Source (Defining_Identifier (N)) then
5959 Set_Debug_Info_Needed (Defining_Identifier (N));
5960 end if;
5962 -- Now call the routine to generate debug info for the renaming
5964 declare
5965 Decl : constant Node_Id := Debug_Renaming_Declaration (N);
5966 begin
5967 if Present (Decl) then
5968 Insert_Action (N, Decl);
5969 end if;
5970 end;
5971 end if;
5972 end if;
5974 if Nkind (N) = N_Object_Declaration
5975 and then Nkind (Obj_Def) = N_Access_Definition
5976 and then not Is_Local_Anonymous_Access (Etype (Def_Id))
5977 then
5978 -- An Ada 2012 stand-alone object of an anonymous access type
5980 declare
5981 Loc : constant Source_Ptr := Sloc (N);
5983 Level : constant Entity_Id :=
5984 Make_Defining_Identifier (Sloc (N),
5985 Chars =>
5986 New_External_Name (Chars (Def_Id), Suffix => "L"));
5988 Level_Expr : Node_Id;
5989 Level_Decl : Node_Id;
5991 begin
5992 Set_Ekind (Level, Ekind (Def_Id));
5993 Set_Etype (Level, Standard_Natural);
5994 Set_Scope (Level, Scope (Def_Id));
5996 if No (Expr) then
5998 -- Set accessibility level of null
6000 Level_Expr :=
6001 Make_Integer_Literal (Loc, Scope_Depth (Standard_Standard));
6003 else
6004 Level_Expr := Dynamic_Accessibility_Level (Expr);
6005 end if;
6007 Level_Decl :=
6008 Make_Object_Declaration (Loc,
6009 Defining_Identifier => Level,
6010 Object_Definition =>
6011 New_Occurrence_Of (Standard_Natural, Loc),
6012 Expression => Level_Expr,
6013 Constant_Present => Constant_Present (N),
6014 Has_Init_Expression => True);
6016 Insert_Action_After (Init_After, Level_Decl);
6018 Set_Extra_Accessibility (Def_Id, Level);
6019 end;
6020 end if;
6022 -- At this point the object is fully initialized by either invoking the
6023 -- related type init proc, routine [Deep_]Initialize or performing in-
6024 -- place assingments for an array object. If the related type is subject
6025 -- to pragma Default_Initial_Condition, add a runtime check to verify
6026 -- the assumption of the pragma. Generate:
6028 -- <Base_Typ>Default_Init_Cond (<Base_Typ> (Def_Id));
6030 -- Note that the check is generated for source objects only
6032 if Comes_From_Source (Def_Id)
6033 and then (Has_Default_Init_Cond (Base_Typ)
6034 or else
6035 Has_Inherited_Default_Init_Cond (Base_Typ))
6036 then
6037 declare
6038 DIC_Call : constant Node_Id :=
6039 Build_Default_Init_Cond_Call (Loc, Def_Id, Base_Typ);
6040 begin
6041 if Present (Next_N) then
6042 Insert_Before_And_Analyze (Next_N, DIC_Call);
6044 -- The object declaration is the last node in a declarative or a
6045 -- statement list.
6047 else
6048 Append_To (List_Containing (N), DIC_Call);
6049 Analyze (DIC_Call);
6050 end if;
6051 end;
6052 end if;
6054 -- Exception on library entity not available
6056 exception
6057 when RE_Not_Available =>
6058 return;
6059 end Expand_N_Object_Declaration;
6061 ---------------------------------
6062 -- Expand_N_Subtype_Indication --
6063 ---------------------------------
6065 -- Add a check on the range of the subtype. The static case is partially
6066 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
6067 -- to check here for the static case in order to avoid generating
6068 -- extraneous expanded code. Also deal with validity checking.
6070 procedure Expand_N_Subtype_Indication (N : Node_Id) is
6071 Ran : constant Node_Id := Range_Expression (Constraint (N));
6072 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6074 begin
6075 if Nkind (Constraint (N)) = N_Range_Constraint then
6076 Validity_Check_Range (Range_Expression (Constraint (N)));
6077 end if;
6079 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
6080 Apply_Range_Check (Ran, Typ);
6081 end if;
6082 end Expand_N_Subtype_Indication;
6084 ---------------------------
6085 -- Expand_N_Variant_Part --
6086 ---------------------------
6088 -- Note: this procedure no longer has any effect. It used to be that we
6089 -- would replace the choices in the last variant by a when others, and
6090 -- also expanded static predicates in variant choices here, but both of
6091 -- those activities were being done too early, since we can't check the
6092 -- choices until the statically predicated subtypes are frozen, which can
6093 -- happen as late as the free point of the record, and we can't change the
6094 -- last choice to an others before checking the choices, which is now done
6095 -- at the freeze point of the record.
6097 procedure Expand_N_Variant_Part (N : Node_Id) is
6098 begin
6099 null;
6100 end Expand_N_Variant_Part;
6102 ---------------------------------
6103 -- Expand_Previous_Access_Type --
6104 ---------------------------------
6106 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
6107 Ptr_Typ : Entity_Id;
6109 begin
6110 -- Find all access types in the current scope whose designated type is
6111 -- Def_Id and build master renamings for them.
6113 Ptr_Typ := First_Entity (Current_Scope);
6114 while Present (Ptr_Typ) loop
6115 if Is_Access_Type (Ptr_Typ)
6116 and then Designated_Type (Ptr_Typ) = Def_Id
6117 and then No (Master_Id (Ptr_Typ))
6118 then
6119 -- Ensure that the designated type has a master
6121 Build_Master_Entity (Def_Id);
6123 -- Private and incomplete types complicate the insertion of master
6124 -- renamings because the access type may precede the full view of
6125 -- the designated type. For this reason, the master renamings are
6126 -- inserted relative to the designated type.
6128 Build_Master_Renaming (Ptr_Typ, Ins_Nod => Parent (Def_Id));
6129 end if;
6131 Next_Entity (Ptr_Typ);
6132 end loop;
6133 end Expand_Previous_Access_Type;
6135 ------------------------
6136 -- Expand_Tagged_Root --
6137 ------------------------
6139 procedure Expand_Tagged_Root (T : Entity_Id) is
6140 Def : constant Node_Id := Type_Definition (Parent (T));
6141 Comp_List : Node_Id;
6142 Comp_Decl : Node_Id;
6143 Sloc_N : Source_Ptr;
6145 begin
6146 if Null_Present (Def) then
6147 Set_Component_List (Def,
6148 Make_Component_List (Sloc (Def),
6149 Component_Items => Empty_List,
6150 Variant_Part => Empty,
6151 Null_Present => True));
6152 end if;
6154 Comp_List := Component_List (Def);
6156 if Null_Present (Comp_List)
6157 or else Is_Empty_List (Component_Items (Comp_List))
6158 then
6159 Sloc_N := Sloc (Comp_List);
6160 else
6161 Sloc_N := Sloc (First (Component_Items (Comp_List)));
6162 end if;
6164 Comp_Decl :=
6165 Make_Component_Declaration (Sloc_N,
6166 Defining_Identifier => First_Tag_Component (T),
6167 Component_Definition =>
6168 Make_Component_Definition (Sloc_N,
6169 Aliased_Present => False,
6170 Subtype_Indication => New_Occurrence_Of (RTE (RE_Tag), Sloc_N)));
6172 if Null_Present (Comp_List)
6173 or else Is_Empty_List (Component_Items (Comp_List))
6174 then
6175 Set_Component_Items (Comp_List, New_List (Comp_Decl));
6176 Set_Null_Present (Comp_List, False);
6178 else
6179 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
6180 end if;
6182 -- We don't Analyze the whole expansion because the tag component has
6183 -- already been analyzed previously. Here we just insure that the tree
6184 -- is coherent with the semantic decoration
6186 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
6188 exception
6189 when RE_Not_Available =>
6190 return;
6191 end Expand_Tagged_Root;
6193 ----------------------
6194 -- Clean_Task_Names --
6195 ----------------------
6197 procedure Clean_Task_Names
6198 (Typ : Entity_Id;
6199 Proc_Id : Entity_Id)
6201 begin
6202 if Has_Task (Typ)
6203 and then not Restriction_Active (No_Implicit_Heap_Allocations)
6204 and then not Global_Discard_Names
6205 and then Tagged_Type_Expansion
6206 then
6207 Set_Uses_Sec_Stack (Proc_Id);
6208 end if;
6209 end Clean_Task_Names;
6211 ------------------------------
6212 -- Expand_Freeze_Array_Type --
6213 ------------------------------
6215 procedure Expand_Freeze_Array_Type (N : Node_Id) is
6216 Typ : constant Entity_Id := Entity (N);
6217 Comp_Typ : constant Entity_Id := Component_Type (Typ);
6218 Base : constant Entity_Id := Base_Type (Typ);
6220 begin
6221 if not Is_Bit_Packed_Array (Typ) then
6223 -- If the component contains tasks, so does the array type. This may
6224 -- not be indicated in the array type because the component may have
6225 -- been a private type at the point of definition. Same if component
6226 -- type is controlled or contains protected objects.
6228 Set_Has_Task (Base, Has_Task (Comp_Typ));
6229 Set_Has_Protected (Base, Has_Protected (Comp_Typ));
6230 Set_Has_Controlled_Component
6231 (Base, Has_Controlled_Component
6232 (Comp_Typ)
6233 or else
6234 Is_Controlled (Comp_Typ));
6236 if No (Init_Proc (Base)) then
6238 -- If this is an anonymous array created for a declaration with
6239 -- an initial value, its init_proc will never be called. The
6240 -- initial value itself may have been expanded into assignments,
6241 -- in which case the object declaration is carries the
6242 -- No_Initialization flag.
6244 if Is_Itype (Base)
6245 and then Nkind (Associated_Node_For_Itype (Base)) =
6246 N_Object_Declaration
6247 and then
6248 (Present (Expression (Associated_Node_For_Itype (Base)))
6249 or else No_Initialization (Associated_Node_For_Itype (Base)))
6250 then
6251 null;
6253 -- We do not need an init proc for string or wide [wide] string,
6254 -- since the only time these need initialization in normalize or
6255 -- initialize scalars mode, and these types are treated specially
6256 -- and do not need initialization procedures.
6258 elsif Is_Standard_String_Type (Base) then
6259 null;
6261 -- Otherwise we have to build an init proc for the subtype
6263 else
6264 Build_Array_Init_Proc (Base, N);
6265 end if;
6266 end if;
6268 if Typ = Base then
6269 if Has_Controlled_Component (Base) then
6270 Build_Controlling_Procs (Base);
6272 if not Is_Limited_Type (Comp_Typ)
6273 and then Number_Dimensions (Typ) = 1
6274 then
6275 Build_Slice_Assignment (Typ);
6276 end if;
6277 end if;
6279 -- Create a finalization master to service the anonymous access
6280 -- components of the array.
6282 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
6283 and then Needs_Finalization (Designated_Type (Comp_Typ))
6284 then
6285 Build_Finalization_Master
6286 (Typ => Comp_Typ,
6287 Ins_Node => Parent (Typ),
6288 Encl_Scope => Scope (Typ));
6289 end if;
6290 end if;
6292 -- For packed case, default initialization, except if the component type
6293 -- is itself a packed structure with an initialization procedure, or
6294 -- initialize/normalize scalars active, and we have a base type, or the
6295 -- type is public, because in that case a client might specify
6296 -- Normalize_Scalars and there better be a public Init_Proc for it.
6298 elsif (Present (Init_Proc (Component_Type (Base)))
6299 and then No (Base_Init_Proc (Base)))
6300 or else (Init_Or_Norm_Scalars and then Base = Typ)
6301 or else Is_Public (Typ)
6302 then
6303 Build_Array_Init_Proc (Base, N);
6304 end if;
6306 if Has_Invariants (Component_Type (Base))
6307 and then Typ = Base
6308 and then In_Open_Scopes (Scope (Component_Type (Base)))
6309 then
6310 -- Generate component invariant checking procedure. This is only
6311 -- relevant if the array type is within the scope of the component
6312 -- type. Otherwise an array object can only be built using the public
6313 -- subprograms for the component type, and calls to those will have
6314 -- invariant checks. The invariant procedure is only generated for
6315 -- a base type, not a subtype.
6317 Insert_Component_Invariant_Checks
6318 (N, Base, Build_Array_Invariant_Proc (Base, N));
6319 end if;
6320 end Expand_Freeze_Array_Type;
6322 -----------------------------------
6323 -- Expand_Freeze_Class_Wide_Type --
6324 -----------------------------------
6326 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id) is
6327 Typ : constant Entity_Id := Entity (N);
6328 Root : constant Entity_Id := Root_Type (Typ);
6330 function Is_C_Derivation (Typ : Entity_Id) return Boolean;
6331 -- Given a type, determine whether it is derived from a C or C++ root
6333 ---------------------
6334 -- Is_C_Derivation --
6335 ---------------------
6337 function Is_C_Derivation (Typ : Entity_Id) return Boolean is
6338 T : Entity_Id := Typ;
6340 begin
6341 loop
6342 if Is_CPP_Class (T)
6343 or else Convention (T) = Convention_C
6344 or else Convention (T) = Convention_CPP
6345 then
6346 return True;
6347 end if;
6349 exit when T = Etype (T);
6351 T := Etype (T);
6352 end loop;
6354 return False;
6355 end Is_C_Derivation;
6357 -- Start of processing for Expand_Freeze_Class_Wide_Type
6359 begin
6360 -- Certain run-time configurations and targets do not provide support
6361 -- for controlled types.
6363 if Restriction_Active (No_Finalization) then
6364 return;
6366 -- Do not create TSS routine Finalize_Address when dispatching calls are
6367 -- disabled since the core of the routine is a dispatching call.
6369 elsif Restriction_Active (No_Dispatching_Calls) then
6370 return;
6372 -- Do not create TSS routine Finalize_Address for concurrent class-wide
6373 -- types. Ignore C, C++, CIL and Java types since it is assumed that the
6374 -- non-Ada side will handle their destruction.
6376 elsif Is_Concurrent_Type (Root)
6377 or else Is_C_Derivation (Root)
6378 or else Convention (Typ) = Convention_CIL
6379 or else Convention (Typ) = Convention_CPP
6380 or else Convention (Typ) = Convention_Java
6381 then
6382 return;
6384 -- Do not create TSS routine Finalize_Address for .NET/JVM because these
6385 -- targets do not support address arithmetic and unchecked conversions.
6387 elsif VM_Target /= No_VM then
6388 return;
6390 -- Do not create TSS routine Finalize_Address when compiling in CodePeer
6391 -- mode since the routine contains an Unchecked_Conversion.
6393 elsif CodePeer_Mode then
6394 return;
6395 end if;
6397 -- Create the body of TSS primitive Finalize_Address. This automatically
6398 -- sets the TSS entry for the class-wide type.
6400 Make_Finalize_Address_Body (Typ);
6401 end Expand_Freeze_Class_Wide_Type;
6403 ------------------------------------
6404 -- Expand_Freeze_Enumeration_Type --
6405 ------------------------------------
6407 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
6408 Typ : constant Entity_Id := Entity (N);
6409 Loc : constant Source_Ptr := Sloc (Typ);
6410 Ent : Entity_Id;
6411 Lst : List_Id;
6412 Num : Nat;
6413 Arr : Entity_Id;
6414 Fent : Entity_Id;
6415 Ityp : Entity_Id;
6416 Is_Contiguous : Boolean;
6417 Pos_Expr : Node_Id;
6418 Last_Repval : Uint;
6420 Func : Entity_Id;
6421 pragma Warnings (Off, Func);
6423 begin
6424 -- Various optimizations possible if given representation is contiguous
6426 Is_Contiguous := True;
6428 Ent := First_Literal (Typ);
6429 Last_Repval := Enumeration_Rep (Ent);
6431 Next_Literal (Ent);
6432 while Present (Ent) loop
6433 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
6434 Is_Contiguous := False;
6435 exit;
6436 else
6437 Last_Repval := Enumeration_Rep (Ent);
6438 end if;
6440 Next_Literal (Ent);
6441 end loop;
6443 if Is_Contiguous then
6444 Set_Has_Contiguous_Rep (Typ);
6445 Ent := First_Literal (Typ);
6446 Num := 1;
6447 Lst := New_List (New_Occurrence_Of (Ent, Sloc (Ent)));
6449 else
6450 -- Build list of literal references
6452 Lst := New_List;
6453 Num := 0;
6455 Ent := First_Literal (Typ);
6456 while Present (Ent) loop
6457 Append_To (Lst, New_Occurrence_Of (Ent, Sloc (Ent)));
6458 Num := Num + 1;
6459 Next_Literal (Ent);
6460 end loop;
6461 end if;
6463 -- Now build an array declaration
6465 -- typA : array (Natural range 0 .. num - 1) of ctype :=
6466 -- (v, v, v, v, v, ....)
6468 -- where ctype is the corresponding integer type. If the representation
6469 -- is contiguous, we only keep the first literal, which provides the
6470 -- offset for Pos_To_Rep computations.
6472 Arr :=
6473 Make_Defining_Identifier (Loc,
6474 Chars => New_External_Name (Chars (Typ), 'A'));
6476 Append_Freeze_Action (Typ,
6477 Make_Object_Declaration (Loc,
6478 Defining_Identifier => Arr,
6479 Constant_Present => True,
6481 Object_Definition =>
6482 Make_Constrained_Array_Definition (Loc,
6483 Discrete_Subtype_Definitions => New_List (
6484 Make_Subtype_Indication (Loc,
6485 Subtype_Mark => New_Occurrence_Of (Standard_Natural, Loc),
6486 Constraint =>
6487 Make_Range_Constraint (Loc,
6488 Range_Expression =>
6489 Make_Range (Loc,
6490 Low_Bound =>
6491 Make_Integer_Literal (Loc, 0),
6492 High_Bound =>
6493 Make_Integer_Literal (Loc, Num - 1))))),
6495 Component_Definition =>
6496 Make_Component_Definition (Loc,
6497 Aliased_Present => False,
6498 Subtype_Indication => New_Occurrence_Of (Typ, Loc))),
6500 Expression =>
6501 Make_Aggregate (Loc,
6502 Expressions => Lst)));
6504 Set_Enum_Pos_To_Rep (Typ, Arr);
6506 -- Now we build the function that converts representation values to
6507 -- position values. This function has the form:
6509 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
6510 -- begin
6511 -- case ityp!(A) is
6512 -- when enum-lit'Enum_Rep => return posval;
6513 -- when enum-lit'Enum_Rep => return posval;
6514 -- ...
6515 -- when others =>
6516 -- [raise Constraint_Error when F "invalid data"]
6517 -- return -1;
6518 -- end case;
6519 -- end;
6521 -- Note: the F parameter determines whether the others case (no valid
6522 -- representation) raises Constraint_Error or returns a unique value
6523 -- of minus one. The latter case is used, e.g. in 'Valid code.
6525 -- Note: the reason we use Enum_Rep values in the case here is to avoid
6526 -- the code generator making inappropriate assumptions about the range
6527 -- of the values in the case where the value is invalid. ityp is a
6528 -- signed or unsigned integer type of appropriate width.
6530 -- Note: if exceptions are not supported, then we suppress the raise
6531 -- and return -1 unconditionally (this is an erroneous program in any
6532 -- case and there is no obligation to raise Constraint_Error here). We
6533 -- also do this if pragma Restrictions (No_Exceptions) is active.
6535 -- Is this right??? What about No_Exception_Propagation???
6537 -- Representations are signed
6539 if Enumeration_Rep (First_Literal (Typ)) < 0 then
6541 -- The underlying type is signed. Reset the Is_Unsigned_Type
6542 -- explicitly, because it might have been inherited from
6543 -- parent type.
6545 Set_Is_Unsigned_Type (Typ, False);
6547 if Esize (Typ) <= Standard_Integer_Size then
6548 Ityp := Standard_Integer;
6549 else
6550 Ityp := Universal_Integer;
6551 end if;
6553 -- Representations are unsigned
6555 else
6556 if Esize (Typ) <= Standard_Integer_Size then
6557 Ityp := RTE (RE_Unsigned);
6558 else
6559 Ityp := RTE (RE_Long_Long_Unsigned);
6560 end if;
6561 end if;
6563 -- The body of the function is a case statement. First collect case
6564 -- alternatives, or optimize the contiguous case.
6566 Lst := New_List;
6568 -- If representation is contiguous, Pos is computed by subtracting
6569 -- the representation of the first literal.
6571 if Is_Contiguous then
6572 Ent := First_Literal (Typ);
6574 if Enumeration_Rep (Ent) = Last_Repval then
6576 -- Another special case: for a single literal, Pos is zero
6578 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
6580 else
6581 Pos_Expr :=
6582 Convert_To (Standard_Integer,
6583 Make_Op_Subtract (Loc,
6584 Left_Opnd =>
6585 Unchecked_Convert_To
6586 (Ityp, Make_Identifier (Loc, Name_uA)),
6587 Right_Opnd =>
6588 Make_Integer_Literal (Loc,
6589 Intval => Enumeration_Rep (First_Literal (Typ)))));
6590 end if;
6592 Append_To (Lst,
6593 Make_Case_Statement_Alternative (Loc,
6594 Discrete_Choices => New_List (
6595 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
6596 Low_Bound =>
6597 Make_Integer_Literal (Loc,
6598 Intval => Enumeration_Rep (Ent)),
6599 High_Bound =>
6600 Make_Integer_Literal (Loc, Intval => Last_Repval))),
6602 Statements => New_List (
6603 Make_Simple_Return_Statement (Loc,
6604 Expression => Pos_Expr))));
6606 else
6607 Ent := First_Literal (Typ);
6608 while Present (Ent) loop
6609 Append_To (Lst,
6610 Make_Case_Statement_Alternative (Loc,
6611 Discrete_Choices => New_List (
6612 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
6613 Intval => Enumeration_Rep (Ent))),
6615 Statements => New_List (
6616 Make_Simple_Return_Statement (Loc,
6617 Expression =>
6618 Make_Integer_Literal (Loc,
6619 Intval => Enumeration_Pos (Ent))))));
6621 Next_Literal (Ent);
6622 end loop;
6623 end if;
6625 -- In normal mode, add the others clause with the test
6627 if not No_Exception_Handlers_Set then
6628 Append_To (Lst,
6629 Make_Case_Statement_Alternative (Loc,
6630 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
6631 Statements => New_List (
6632 Make_Raise_Constraint_Error (Loc,
6633 Condition => Make_Identifier (Loc, Name_uF),
6634 Reason => CE_Invalid_Data),
6635 Make_Simple_Return_Statement (Loc,
6636 Expression =>
6637 Make_Integer_Literal (Loc, -1)))));
6639 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
6640 -- active then return -1 (we cannot usefully raise Constraint_Error in
6641 -- this case). See description above for further details.
6643 else
6644 Append_To (Lst,
6645 Make_Case_Statement_Alternative (Loc,
6646 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
6647 Statements => New_List (
6648 Make_Simple_Return_Statement (Loc,
6649 Expression =>
6650 Make_Integer_Literal (Loc, -1)))));
6651 end if;
6653 -- Now we can build the function body
6655 Fent :=
6656 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
6658 Func :=
6659 Make_Subprogram_Body (Loc,
6660 Specification =>
6661 Make_Function_Specification (Loc,
6662 Defining_Unit_Name => Fent,
6663 Parameter_Specifications => New_List (
6664 Make_Parameter_Specification (Loc,
6665 Defining_Identifier =>
6666 Make_Defining_Identifier (Loc, Name_uA),
6667 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
6668 Make_Parameter_Specification (Loc,
6669 Defining_Identifier =>
6670 Make_Defining_Identifier (Loc, Name_uF),
6671 Parameter_Type =>
6672 New_Occurrence_Of (Standard_Boolean, Loc))),
6674 Result_Definition => New_Occurrence_Of (Standard_Integer, Loc)),
6676 Declarations => Empty_List,
6678 Handled_Statement_Sequence =>
6679 Make_Handled_Sequence_Of_Statements (Loc,
6680 Statements => New_List (
6681 Make_Case_Statement (Loc,
6682 Expression =>
6683 Unchecked_Convert_To
6684 (Ityp, Make_Identifier (Loc, Name_uA)),
6685 Alternatives => Lst))));
6687 Set_TSS (Typ, Fent);
6689 -- Set Pure flag (it will be reset if the current context is not Pure).
6690 -- We also pretend there was a pragma Pure_Function so that for purposes
6691 -- of optimization and constant-folding, we will consider the function
6692 -- Pure even if we are not in a Pure context).
6694 Set_Is_Pure (Fent);
6695 Set_Has_Pragma_Pure_Function (Fent);
6697 -- Unless we are in -gnatD mode, where we are debugging generated code,
6698 -- this is an internal entity for which we don't need debug info.
6700 if not Debug_Generated_Code then
6701 Set_Debug_Info_Off (Fent);
6702 end if;
6704 exception
6705 when RE_Not_Available =>
6706 return;
6707 end Expand_Freeze_Enumeration_Type;
6709 -------------------------------
6710 -- Expand_Freeze_Record_Type --
6711 -------------------------------
6713 procedure Expand_Freeze_Record_Type (N : Node_Id) is
6714 Def_Id : constant Node_Id := Entity (N);
6715 Type_Decl : constant Node_Id := Parent (Def_Id);
6716 Comp : Entity_Id;
6717 Comp_Typ : Entity_Id;
6718 Has_AACC : Boolean;
6719 Predef_List : List_Id;
6721 Renamed_Eq : Node_Id := Empty;
6722 -- Defining unit name for the predefined equality function in the case
6723 -- where the type has a primitive operation that is a renaming of
6724 -- predefined equality (but only if there is also an overriding
6725 -- user-defined equality function). Used to pass this entity from
6726 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
6728 Wrapper_Decl_List : List_Id := No_List;
6729 Wrapper_Body_List : List_Id := No_List;
6731 -- Start of processing for Expand_Freeze_Record_Type
6733 begin
6734 -- Build discriminant checking functions if not a derived type (for
6735 -- derived types that are not tagged types, always use the discriminant
6736 -- checking functions of the parent type). However, for untagged types
6737 -- the derivation may have taken place before the parent was frozen, so
6738 -- we copy explicitly the discriminant checking functions from the
6739 -- parent into the components of the derived type.
6741 if not Is_Derived_Type (Def_Id)
6742 or else Has_New_Non_Standard_Rep (Def_Id)
6743 or else Is_Tagged_Type (Def_Id)
6744 then
6745 Build_Discr_Checking_Funcs (Type_Decl);
6747 elsif Is_Derived_Type (Def_Id)
6748 and then not Is_Tagged_Type (Def_Id)
6750 -- If we have a derived Unchecked_Union, we do not inherit the
6751 -- discriminant checking functions from the parent type since the
6752 -- discriminants are non existent.
6754 and then not Is_Unchecked_Union (Def_Id)
6755 and then Has_Discriminants (Def_Id)
6756 then
6757 declare
6758 Old_Comp : Entity_Id;
6760 begin
6761 Old_Comp :=
6762 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
6763 Comp := First_Component (Def_Id);
6764 while Present (Comp) loop
6765 if Ekind (Comp) = E_Component
6766 and then Chars (Comp) = Chars (Old_Comp)
6767 then
6768 Set_Discriminant_Checking_Func (Comp,
6769 Discriminant_Checking_Func (Old_Comp));
6770 end if;
6772 Next_Component (Old_Comp);
6773 Next_Component (Comp);
6774 end loop;
6775 end;
6776 end if;
6778 if Is_Derived_Type (Def_Id)
6779 and then Is_Limited_Type (Def_Id)
6780 and then Is_Tagged_Type (Def_Id)
6781 then
6782 Check_Stream_Attributes (Def_Id);
6783 end if;
6785 -- Update task, protected, and controlled component flags, because some
6786 -- of the component types may have been private at the point of the
6787 -- record declaration. Detect anonymous access-to-controlled components.
6789 Has_AACC := False;
6791 Comp := First_Component (Def_Id);
6792 while Present (Comp) loop
6793 Comp_Typ := Etype (Comp);
6795 if Has_Task (Comp_Typ) then
6796 Set_Has_Task (Def_Id);
6797 end if;
6799 if Has_Protected (Comp_Typ) then
6800 Set_Has_Protected (Def_Id);
6801 end if;
6803 -- Do not set Has_Controlled_Component on a class-wide equivalent
6804 -- type. See Make_CW_Equivalent_Type.
6806 if not Is_Class_Wide_Equivalent_Type (Def_Id)
6807 and then (Has_Controlled_Component (Comp_Typ)
6808 or else (Chars (Comp) /= Name_uParent
6809 and then Is_Controlled (Comp_Typ)))
6810 then
6811 Set_Has_Controlled_Component (Def_Id);
6812 end if;
6814 -- Non-self-referential anonymous access-to-controlled component
6816 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
6817 and then Needs_Finalization (Designated_Type (Comp_Typ))
6818 and then Designated_Type (Comp_Typ) /= Def_Id
6819 then
6820 Has_AACC := True;
6821 end if;
6823 Next_Component (Comp);
6824 end loop;
6826 -- Handle constructors of untagged CPP_Class types
6828 if not Is_Tagged_Type (Def_Id) and then Is_CPP_Class (Def_Id) then
6829 Set_CPP_Constructors (Def_Id);
6830 end if;
6832 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
6833 -- for regular tagged types as well as for Ada types deriving from a C++
6834 -- Class, but not for tagged types directly corresponding to C++ classes
6835 -- In the later case we assume that it is created in the C++ side and we
6836 -- just use it.
6838 if Is_Tagged_Type (Def_Id) then
6840 -- Add the _Tag component
6842 if Underlying_Type (Etype (Def_Id)) = Def_Id then
6843 Expand_Tagged_Root (Def_Id);
6844 end if;
6846 if Is_CPP_Class (Def_Id) then
6847 Set_All_DT_Position (Def_Id);
6849 -- Create the tag entities with a minimum decoration
6851 if Tagged_Type_Expansion then
6852 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
6853 end if;
6855 Set_CPP_Constructors (Def_Id);
6857 else
6858 if not Building_Static_DT (Def_Id) then
6860 -- Usually inherited primitives are not delayed but the first
6861 -- Ada extension of a CPP_Class is an exception since the
6862 -- address of the inherited subprogram has to be inserted in
6863 -- the new Ada Dispatch Table and this is a freezing action.
6865 -- Similarly, if this is an inherited operation whose parent is
6866 -- not frozen yet, it is not in the DT of the parent, and we
6867 -- generate an explicit freeze node for the inherited operation
6868 -- so it is properly inserted in the DT of the current type.
6870 declare
6871 Elmt : Elmt_Id;
6872 Subp : Entity_Id;
6874 begin
6875 Elmt := First_Elmt (Primitive_Operations (Def_Id));
6876 while Present (Elmt) loop
6877 Subp := Node (Elmt);
6879 if Present (Alias (Subp)) then
6880 if Is_CPP_Class (Etype (Def_Id)) then
6881 Set_Has_Delayed_Freeze (Subp);
6883 elsif Has_Delayed_Freeze (Alias (Subp))
6884 and then not Is_Frozen (Alias (Subp))
6885 then
6886 Set_Is_Frozen (Subp, False);
6887 Set_Has_Delayed_Freeze (Subp);
6888 end if;
6889 end if;
6891 Next_Elmt (Elmt);
6892 end loop;
6893 end;
6894 end if;
6896 -- Unfreeze momentarily the type to add the predefined primitives
6897 -- operations. The reason we unfreeze is so that these predefined
6898 -- operations will indeed end up as primitive operations (which
6899 -- must be before the freeze point).
6901 Set_Is_Frozen (Def_Id, False);
6903 -- Do not add the spec of predefined primitives in case of
6904 -- CPP tagged type derivations that have convention CPP.
6906 if Is_CPP_Class (Root_Type (Def_Id))
6907 and then Convention (Def_Id) = Convention_CPP
6908 then
6909 null;
6911 -- Do not add the spec of predefined primitives in case of
6912 -- CIL and Java tagged types
6914 elsif Convention (Def_Id) = Convention_CIL
6915 or else Convention (Def_Id) = Convention_Java
6916 then
6917 null;
6919 -- Do not add the spec of the predefined primitives if we are
6920 -- compiling under restriction No_Dispatching_Calls.
6922 elsif not Restriction_Active (No_Dispatching_Calls) then
6923 Make_Predefined_Primitive_Specs
6924 (Def_Id, Predef_List, Renamed_Eq);
6925 Insert_List_Before_And_Analyze (N, Predef_List);
6926 end if;
6928 -- Ada 2005 (AI-391): For a nonabstract null extension, create
6929 -- wrapper functions for each nonoverridden inherited function
6930 -- with a controlling result of the type. The wrapper for such
6931 -- a function returns an extension aggregate that invokes the
6932 -- parent function.
6934 if Ada_Version >= Ada_2005
6935 and then not Is_Abstract_Type (Def_Id)
6936 and then Is_Null_Extension (Def_Id)
6937 then
6938 Make_Controlling_Function_Wrappers
6939 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
6940 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
6941 end if;
6943 -- Ada 2005 (AI-251): For a nonabstract type extension, build
6944 -- null procedure declarations for each set of homographic null
6945 -- procedures that are inherited from interface types but not
6946 -- overridden. This is done to ensure that the dispatch table
6947 -- entry associated with such null primitives are properly filled.
6949 if Ada_Version >= Ada_2005
6950 and then Etype (Def_Id) /= Def_Id
6951 and then not Is_Abstract_Type (Def_Id)
6952 and then Has_Interfaces (Def_Id)
6953 then
6954 Insert_Actions (N, Make_Null_Procedure_Specs (Def_Id));
6955 end if;
6957 Set_Is_Frozen (Def_Id);
6958 if not Is_Derived_Type (Def_Id)
6959 or else Is_Tagged_Type (Etype (Def_Id))
6960 then
6961 Set_All_DT_Position (Def_Id);
6963 -- If this is a type derived from an untagged private type whose
6964 -- full view is tagged, the type is marked tagged for layout
6965 -- reasons, but it has no dispatch table.
6967 elsif Is_Derived_Type (Def_Id)
6968 and then Is_Private_Type (Etype (Def_Id))
6969 and then not Is_Tagged_Type (Etype (Def_Id))
6970 then
6971 return;
6972 end if;
6974 -- Create and decorate the tags. Suppress their creation when
6975 -- VM_Target because the dispatching mechanism is handled
6976 -- internally by the VMs.
6978 if Tagged_Type_Expansion then
6979 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
6981 -- Generate dispatch table of locally defined tagged type.
6982 -- Dispatch tables of library level tagged types are built
6983 -- later (see Analyze_Declarations).
6985 if not Building_Static_DT (Def_Id) then
6986 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
6987 end if;
6989 elsif VM_Target /= No_VM then
6990 Append_Freeze_Actions (Def_Id, Make_VM_TSD (Def_Id));
6991 end if;
6993 -- If the type has unknown discriminants, propagate dispatching
6994 -- information to its underlying record view, which does not get
6995 -- its own dispatch table.
6997 if Is_Derived_Type (Def_Id)
6998 and then Has_Unknown_Discriminants (Def_Id)
6999 and then Present (Underlying_Record_View (Def_Id))
7000 then
7001 declare
7002 Rep : constant Entity_Id := Underlying_Record_View (Def_Id);
7003 begin
7004 Set_Access_Disp_Table
7005 (Rep, Access_Disp_Table (Def_Id));
7006 Set_Dispatch_Table_Wrappers
7007 (Rep, Dispatch_Table_Wrappers (Def_Id));
7008 Set_Direct_Primitive_Operations
7009 (Rep, Direct_Primitive_Operations (Def_Id));
7010 end;
7011 end if;
7013 -- Make sure that the primitives Initialize, Adjust and Finalize
7014 -- are Frozen before other TSS subprograms. We don't want them
7015 -- Frozen inside.
7017 if Is_Controlled (Def_Id) then
7018 if not Is_Limited_Type (Def_Id) then
7019 Append_Freeze_Actions (Def_Id,
7020 Freeze_Entity
7021 (Find_Prim_Op (Def_Id, Name_Adjust), Def_Id));
7022 end if;
7024 Append_Freeze_Actions (Def_Id,
7025 Freeze_Entity
7026 (Find_Prim_Op (Def_Id, Name_Initialize), Def_Id));
7028 Append_Freeze_Actions (Def_Id,
7029 Freeze_Entity
7030 (Find_Prim_Op (Def_Id, Name_Finalize), Def_Id));
7031 end if;
7033 -- Freeze rest of primitive operations. There is no need to handle
7034 -- the predefined primitives if we are compiling under restriction
7035 -- No_Dispatching_Calls.
7037 if not Restriction_Active (No_Dispatching_Calls) then
7038 Append_Freeze_Actions
7039 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
7040 end if;
7041 end if;
7043 -- In the untagged case, ever since Ada 83 an equality function must
7044 -- be provided for variant records that are not unchecked unions.
7045 -- In Ada 2012 the equality function composes, and thus must be built
7046 -- explicitly just as for tagged records.
7048 elsif Has_Discriminants (Def_Id)
7049 and then not Is_Limited_Type (Def_Id)
7050 then
7051 declare
7052 Comps : constant Node_Id :=
7053 Component_List (Type_Definition (Type_Decl));
7054 begin
7055 if Present (Comps)
7056 and then Present (Variant_Part (Comps))
7057 then
7058 Build_Variant_Record_Equality (Def_Id);
7059 end if;
7060 end;
7062 -- Otherwise create primitive equality operation (AI05-0123)
7064 -- This is done unconditionally to ensure that tools can be linked
7065 -- properly with user programs compiled with older language versions.
7066 -- In addition, this is needed because "=" composes for bounded strings
7067 -- in all language versions (see Exp_Ch4.Expand_Composite_Equality).
7069 elsif Comes_From_Source (Def_Id)
7070 and then Convention (Def_Id) = Convention_Ada
7071 and then not Is_Limited_Type (Def_Id)
7072 then
7073 Build_Untagged_Equality (Def_Id);
7074 end if;
7076 -- Before building the record initialization procedure, if we are
7077 -- dealing with a concurrent record value type, then we must go through
7078 -- the discriminants, exchanging discriminals between the concurrent
7079 -- type and the concurrent record value type. See the section "Handling
7080 -- of Discriminants" in the Einfo spec for details.
7082 if Is_Concurrent_Record_Type (Def_Id)
7083 and then Has_Discriminants (Def_Id)
7084 then
7085 declare
7086 Ctyp : constant Entity_Id :=
7087 Corresponding_Concurrent_Type (Def_Id);
7088 Conc_Discr : Entity_Id;
7089 Rec_Discr : Entity_Id;
7090 Temp : Entity_Id;
7092 begin
7093 Conc_Discr := First_Discriminant (Ctyp);
7094 Rec_Discr := First_Discriminant (Def_Id);
7095 while Present (Conc_Discr) loop
7096 Temp := Discriminal (Conc_Discr);
7097 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
7098 Set_Discriminal (Rec_Discr, Temp);
7100 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
7101 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
7103 Next_Discriminant (Conc_Discr);
7104 Next_Discriminant (Rec_Discr);
7105 end loop;
7106 end;
7107 end if;
7109 if Has_Controlled_Component (Def_Id) then
7110 Build_Controlling_Procs (Def_Id);
7111 end if;
7113 Adjust_Discriminants (Def_Id);
7115 if Tagged_Type_Expansion or else not Is_Interface (Def_Id) then
7117 -- Do not need init for interfaces on e.g. CIL since they're
7118 -- abstract. Helps operation of peverify (the PE Verify tool).
7120 Build_Record_Init_Proc (Type_Decl, Def_Id);
7121 end if;
7123 -- For tagged type that are not interfaces, build bodies of primitive
7124 -- operations. Note: do this after building the record initialization
7125 -- procedure, since the primitive operations may need the initialization
7126 -- routine. There is no need to add predefined primitives of interfaces
7127 -- because all their predefined primitives are abstract.
7129 if Is_Tagged_Type (Def_Id) and then not Is_Interface (Def_Id) then
7131 -- Do not add the body of predefined primitives in case of CPP tagged
7132 -- type derivations that have convention CPP.
7134 if Is_CPP_Class (Root_Type (Def_Id))
7135 and then Convention (Def_Id) = Convention_CPP
7136 then
7137 null;
7139 -- Do not add the body of predefined primitives in case of CIL and
7140 -- Java tagged types.
7142 elsif Convention (Def_Id) = Convention_CIL
7143 or else Convention (Def_Id) = Convention_Java
7144 then
7145 null;
7147 -- Do not add the body of the predefined primitives if we are
7148 -- compiling under restriction No_Dispatching_Calls or if we are
7149 -- compiling a CPP tagged type.
7151 elsif not Restriction_Active (No_Dispatching_Calls) then
7153 -- Create the body of TSS primitive Finalize_Address. This must
7154 -- be done before the bodies of all predefined primitives are
7155 -- created. If Def_Id is limited, Stream_Input and Stream_Read
7156 -- may produce build-in-place allocations and for those the
7157 -- expander needs Finalize_Address.
7159 Make_Finalize_Address_Body (Def_Id);
7160 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
7161 Append_Freeze_Actions (Def_Id, Predef_List);
7162 end if;
7164 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
7165 -- inherited functions, then add their bodies to the freeze actions.
7167 if Present (Wrapper_Body_List) then
7168 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
7169 end if;
7171 -- Create extra formals for the primitive operations of the type.
7172 -- This must be done before analyzing the body of the initialization
7173 -- procedure, because a self-referential type might call one of these
7174 -- primitives in the body of the init_proc itself.
7176 declare
7177 Elmt : Elmt_Id;
7178 Subp : Entity_Id;
7180 begin
7181 Elmt := First_Elmt (Primitive_Operations (Def_Id));
7182 while Present (Elmt) loop
7183 Subp := Node (Elmt);
7184 if not Has_Foreign_Convention (Subp)
7185 and then not Is_Predefined_Dispatching_Operation (Subp)
7186 then
7187 Create_Extra_Formals (Subp);
7188 end if;
7190 Next_Elmt (Elmt);
7191 end loop;
7192 end;
7193 end if;
7195 -- Create a heterogeneous finalization master to service the anonymous
7196 -- access-to-controlled components of the record type.
7198 if Has_AACC then
7199 declare
7200 Encl_Scope : constant Entity_Id := Scope (Def_Id);
7201 Ins_Node : constant Node_Id := Parent (Def_Id);
7202 Loc : constant Source_Ptr := Sloc (Def_Id);
7203 Fin_Mas_Id : Entity_Id;
7205 Attributes_Set : Boolean := False;
7206 Master_Built : Boolean := False;
7207 -- Two flags which control the creation and initialization of a
7208 -- common heterogeneous master.
7210 begin
7211 Comp := First_Component (Def_Id);
7212 while Present (Comp) loop
7213 Comp_Typ := Etype (Comp);
7215 -- A non-self-referential anonymous access-to-controlled
7216 -- component.
7218 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
7219 and then Needs_Finalization (Designated_Type (Comp_Typ))
7220 and then Designated_Type (Comp_Typ) /= Def_Id
7221 then
7222 if VM_Target = No_VM then
7224 -- Build a homogeneous master for the first anonymous
7225 -- access-to-controlled component. This master may be
7226 -- converted into a heterogeneous collection if more
7227 -- components are to follow.
7229 if not Master_Built then
7230 Master_Built := True;
7232 -- All anonymous access-to-controlled types allocate
7233 -- on the global pool. Note that the finalization
7234 -- master and the associated storage pool must be set
7235 -- on the root type (both are "root type only").
7237 Set_Associated_Storage_Pool
7238 (Root_Type (Comp_Typ), RTE (RE_Global_Pool_Object));
7240 Build_Finalization_Master
7241 (Typ => Root_Type (Comp_Typ),
7242 Ins_Node => Ins_Node,
7243 Encl_Scope => Encl_Scope);
7245 Fin_Mas_Id := Finalization_Master (Comp_Typ);
7247 -- Subsequent anonymous access-to-controlled components
7248 -- reuse the available master.
7250 else
7251 -- All anonymous access-to-controlled types allocate
7252 -- on the global pool. Note that both the finalization
7253 -- master and the associated storage pool must be set
7254 -- on the root type (both are "root type only").
7256 Set_Associated_Storage_Pool
7257 (Root_Type (Comp_Typ), RTE (RE_Global_Pool_Object));
7259 -- Shared the master among multiple components
7261 Set_Finalization_Master
7262 (Root_Type (Comp_Typ), Fin_Mas_Id);
7264 -- Convert the master into a heterogeneous collection.
7265 -- Generate:
7266 -- Set_Is_Heterogeneous (<Fin_Mas_Id>);
7268 if not Attributes_Set then
7269 Attributes_Set := True;
7271 Insert_Action (Ins_Node,
7272 Make_Procedure_Call_Statement (Loc,
7273 Name =>
7274 New_Occurrence_Of
7275 (RTE (RE_Set_Is_Heterogeneous), Loc),
7276 Parameter_Associations => New_List (
7277 New_Occurrence_Of (Fin_Mas_Id, Loc))));
7278 end if;
7279 end if;
7281 -- Since .NET/JVM targets do not support heterogeneous
7282 -- masters, each component must have its own master.
7284 else
7285 Build_Finalization_Master
7286 (Typ => Comp_Typ,
7287 Ins_Node => Ins_Node,
7288 Encl_Scope => Encl_Scope);
7289 end if;
7290 end if;
7292 Next_Component (Comp);
7293 end loop;
7294 end;
7295 end if;
7297 -- Check whether individual components have a defined invariant, and add
7298 -- the corresponding component invariant checks.
7300 -- Do not create an invariant procedure for some internally generated
7301 -- subtypes, in particular those created for objects of a class-wide
7302 -- type. Such types may have components to which invariant apply, but
7303 -- the corresponding checks will be applied when an object of the parent
7304 -- type is constructed.
7306 -- Such objects will show up in a class-wide postcondition, and the
7307 -- invariant will be checked, if necessary, upon return from the
7308 -- enclosing subprogram.
7310 if not Is_Class_Wide_Equivalent_Type (Def_Id) then
7311 Insert_Component_Invariant_Checks
7312 (N, Def_Id, Build_Record_Invariant_Proc (Def_Id, N));
7313 end if;
7314 end Expand_Freeze_Record_Type;
7316 ------------------------------
7317 -- Freeze_Stream_Operations --
7318 ------------------------------
7320 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
7321 Names : constant array (1 .. 4) of TSS_Name_Type :=
7322 (TSS_Stream_Input,
7323 TSS_Stream_Output,
7324 TSS_Stream_Read,
7325 TSS_Stream_Write);
7326 Stream_Op : Entity_Id;
7328 begin
7329 -- Primitive operations of tagged types are frozen when the dispatch
7330 -- table is constructed.
7332 if not Comes_From_Source (Typ) or else Is_Tagged_Type (Typ) then
7333 return;
7334 end if;
7336 for J in Names'Range loop
7337 Stream_Op := TSS (Typ, Names (J));
7339 if Present (Stream_Op)
7340 and then Is_Subprogram (Stream_Op)
7341 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
7342 N_Subprogram_Declaration
7343 and then not Is_Frozen (Stream_Op)
7344 then
7345 Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
7346 end if;
7347 end loop;
7348 end Freeze_Stream_Operations;
7350 -----------------
7351 -- Freeze_Type --
7352 -----------------
7354 -- Full type declarations are expanded at the point at which the type is
7355 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
7356 -- declarations generated by the freezing (e.g. the procedure generated
7357 -- for initialization) are chained in the Actions field list of the freeze
7358 -- node using Append_Freeze_Actions.
7360 function Freeze_Type (N : Node_Id) return Boolean is
7361 Def_Id : constant Entity_Id := Entity (N);
7362 RACW_Seen : Boolean := False;
7363 Result : Boolean := False;
7365 begin
7366 -- Process associated access types needing special processing
7368 if Present (Access_Types_To_Process (N)) then
7369 declare
7370 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
7372 begin
7373 while Present (E) loop
7374 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
7375 Validate_RACW_Primitives (Node (E));
7376 RACW_Seen := True;
7377 end if;
7379 E := Next_Elmt (E);
7380 end loop;
7381 end;
7383 -- If there are RACWs designating this type, make stubs now
7385 if RACW_Seen then
7386 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
7387 end if;
7388 end if;
7390 -- Freeze processing for record types
7392 if Is_Record_Type (Def_Id) then
7393 if Ekind (Def_Id) = E_Record_Type then
7394 Expand_Freeze_Record_Type (N);
7395 elsif Is_Class_Wide_Type (Def_Id) then
7396 Expand_Freeze_Class_Wide_Type (N);
7397 end if;
7399 -- Freeze processing for array types
7401 elsif Is_Array_Type (Def_Id) then
7402 Expand_Freeze_Array_Type (N);
7404 -- Freeze processing for access types
7406 -- For pool-specific access types, find out the pool object used for
7407 -- this type, needs actual expansion of it in some cases. Here are the
7408 -- different cases :
7410 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
7411 -- ---> don't use any storage pool
7413 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
7414 -- Expand:
7415 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
7417 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7418 -- ---> Storage Pool is the specified one
7420 -- See GNAT Pool packages in the Run-Time for more details
7422 elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
7423 declare
7424 Loc : constant Source_Ptr := Sloc (N);
7425 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
7426 Pool_Object : Entity_Id;
7428 Freeze_Action_Typ : Entity_Id;
7430 begin
7431 -- Case 1
7433 -- Rep Clause "for Def_Id'Storage_Size use 0;"
7434 -- ---> don't use any storage pool
7436 if No_Pool_Assigned (Def_Id) then
7437 null;
7439 -- Case 2
7441 -- Rep Clause : for Def_Id'Storage_Size use Expr.
7442 -- ---> Expand:
7443 -- Def_Id__Pool : Stack_Bounded_Pool
7444 -- (Expr, DT'Size, DT'Alignment);
7446 elsif Has_Storage_Size_Clause (Def_Id) then
7447 declare
7448 DT_Size : Node_Id;
7449 DT_Align : Node_Id;
7451 begin
7452 -- For unconstrained composite types we give a size of zero
7453 -- so that the pool knows that it needs a special algorithm
7454 -- for variable size object allocation.
7456 if Is_Composite_Type (Desig_Type)
7457 and then not Is_Constrained (Desig_Type)
7458 then
7459 DT_Size := Make_Integer_Literal (Loc, 0);
7460 DT_Align := Make_Integer_Literal (Loc, Maximum_Alignment);
7462 else
7463 DT_Size :=
7464 Make_Attribute_Reference (Loc,
7465 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7466 Attribute_Name => Name_Max_Size_In_Storage_Elements);
7468 DT_Align :=
7469 Make_Attribute_Reference (Loc,
7470 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7471 Attribute_Name => Name_Alignment);
7472 end if;
7474 Pool_Object :=
7475 Make_Defining_Identifier (Loc,
7476 Chars => New_External_Name (Chars (Def_Id), 'P'));
7478 -- We put the code associated with the pools in the entity
7479 -- that has the later freeze node, usually the access type
7480 -- but it can also be the designated_type; because the pool
7481 -- code requires both those types to be frozen
7483 if Is_Frozen (Desig_Type)
7484 and then (No (Freeze_Node (Desig_Type))
7485 or else Analyzed (Freeze_Node (Desig_Type)))
7486 then
7487 Freeze_Action_Typ := Def_Id;
7489 -- A Taft amendment type cannot get the freeze actions
7490 -- since the full view is not there.
7492 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
7493 and then No (Full_View (Desig_Type))
7494 then
7495 Freeze_Action_Typ := Def_Id;
7497 else
7498 Freeze_Action_Typ := Desig_Type;
7499 end if;
7501 Append_Freeze_Action (Freeze_Action_Typ,
7502 Make_Object_Declaration (Loc,
7503 Defining_Identifier => Pool_Object,
7504 Object_Definition =>
7505 Make_Subtype_Indication (Loc,
7506 Subtype_Mark =>
7507 New_Occurrence_Of
7508 (RTE (RE_Stack_Bounded_Pool), Loc),
7510 Constraint =>
7511 Make_Index_Or_Discriminant_Constraint (Loc,
7512 Constraints => New_List (
7514 -- First discriminant is the Pool Size
7516 New_Occurrence_Of (
7517 Storage_Size_Variable (Def_Id), Loc),
7519 -- Second discriminant is the element size
7521 DT_Size,
7523 -- Third discriminant is the alignment
7525 DT_Align)))));
7526 end;
7528 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
7530 -- Case 3
7532 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7533 -- ---> Storage Pool is the specified one
7535 -- When compiling in Ada 2012 mode, ensure that the accessibility
7536 -- level of the subpool access type is not deeper than that of the
7537 -- pool_with_subpools.
7539 elsif Ada_Version >= Ada_2012
7540 and then Present (Associated_Storage_Pool (Def_Id))
7542 -- Omit this check on .NET/JVM where pools are not supported
7544 and then VM_Target = No_VM
7546 -- Omit this check for the case of a configurable run-time that
7547 -- does not provide package System.Storage_Pools.Subpools.
7549 and then RTE_Available (RE_Root_Storage_Pool_With_Subpools)
7550 then
7551 declare
7552 Loc : constant Source_Ptr := Sloc (Def_Id);
7553 Pool : constant Entity_Id :=
7554 Associated_Storage_Pool (Def_Id);
7555 RSPWS : constant Entity_Id :=
7556 RTE (RE_Root_Storage_Pool_With_Subpools);
7558 begin
7559 -- It is known that the accessibility level of the access
7560 -- type is deeper than that of the pool.
7562 if Type_Access_Level (Def_Id) > Object_Access_Level (Pool)
7563 and then not Accessibility_Checks_Suppressed (Def_Id)
7564 and then not Accessibility_Checks_Suppressed (Pool)
7565 then
7566 -- Static case: the pool is known to be a descendant of
7567 -- Root_Storage_Pool_With_Subpools.
7569 if Is_Ancestor (RSPWS, Etype (Pool)) then
7570 Error_Msg_N
7571 ("??subpool access type has deeper accessibility "
7572 & "level than pool", Def_Id);
7574 Append_Freeze_Action (Def_Id,
7575 Make_Raise_Program_Error (Loc,
7576 Reason => PE_Accessibility_Check_Failed));
7578 -- Dynamic case: when the pool is of a class-wide type,
7579 -- it may or may not support subpools depending on the
7580 -- path of derivation. Generate:
7582 -- if Def_Id in RSPWS'Class then
7583 -- raise Program_Error;
7584 -- end if;
7586 elsif Is_Class_Wide_Type (Etype (Pool)) then
7587 Append_Freeze_Action (Def_Id,
7588 Make_If_Statement (Loc,
7589 Condition =>
7590 Make_In (Loc,
7591 Left_Opnd => New_Occurrence_Of (Pool, Loc),
7592 Right_Opnd =>
7593 New_Occurrence_Of
7594 (Class_Wide_Type (RSPWS), Loc)),
7596 Then_Statements => New_List (
7597 Make_Raise_Program_Error (Loc,
7598 Reason => PE_Accessibility_Check_Failed))));
7599 end if;
7600 end if;
7601 end;
7602 end if;
7604 -- For access-to-controlled types (including class-wide types and
7605 -- Taft-amendment types, which potentially have controlled
7606 -- components), expand the list controller object that will store
7607 -- the dynamically allocated objects. Don't do this transformation
7608 -- for expander-generated access types, but do it for types that
7609 -- are the full view of types derived from other private types.
7610 -- Also suppress the list controller in the case of a designated
7611 -- type with convention Java, since this is used when binding to
7612 -- Java API specs, where there's no equivalent of a finalization
7613 -- list and we don't want to pull in the finalization support if
7614 -- not needed.
7616 if not Comes_From_Source (Def_Id)
7617 and then not Has_Private_Declaration (Def_Id)
7618 then
7619 null;
7621 -- An exception is made for types defined in the run-time because
7622 -- Ada.Tags.Tag itself is such a type and cannot afford this
7623 -- unnecessary overhead that would generates a loop in the
7624 -- expansion scheme. Another exception is if Restrictions
7625 -- (No_Finalization) is active, since then we know nothing is
7626 -- controlled.
7628 elsif Restriction_Active (No_Finalization)
7629 or else In_Runtime (Def_Id)
7630 then
7631 null;
7633 -- Assume that incomplete and private types are always completed
7634 -- by a controlled full view.
7636 elsif Needs_Finalization (Desig_Type)
7637 or else
7638 (Is_Incomplete_Or_Private_Type (Desig_Type)
7639 and then No (Full_View (Desig_Type)))
7640 or else
7641 (Is_Array_Type (Desig_Type)
7642 and then Needs_Finalization (Component_Type (Desig_Type)))
7643 then
7644 Build_Finalization_Master (Def_Id);
7645 end if;
7646 end;
7648 -- Freeze processing for enumeration types
7650 elsif Ekind (Def_Id) = E_Enumeration_Type then
7652 -- We only have something to do if we have a non-standard
7653 -- representation (i.e. at least one literal whose pos value
7654 -- is not the same as its representation)
7656 if Has_Non_Standard_Rep (Def_Id) then
7657 Expand_Freeze_Enumeration_Type (N);
7658 end if;
7660 -- Private types that are completed by a derivation from a private
7661 -- type have an internally generated full view, that needs to be
7662 -- frozen. This must be done explicitly because the two views share
7663 -- the freeze node, and the underlying full view is not visible when
7664 -- the freeze node is analyzed.
7666 elsif Is_Private_Type (Def_Id)
7667 and then Is_Derived_Type (Def_Id)
7668 and then Present (Full_View (Def_Id))
7669 and then Is_Itype (Full_View (Def_Id))
7670 and then Has_Private_Declaration (Full_View (Def_Id))
7671 and then Freeze_Node (Full_View (Def_Id)) = N
7672 then
7673 Set_Entity (N, Full_View (Def_Id));
7674 Result := Freeze_Type (N);
7675 Set_Entity (N, Def_Id);
7677 -- All other types require no expander action. There are such cases
7678 -- (e.g. task types and protected types). In such cases, the freeze
7679 -- nodes are there for use by Gigi.
7681 end if;
7683 Freeze_Stream_Operations (N, Def_Id);
7684 return Result;
7686 exception
7687 when RE_Not_Available =>
7688 return False;
7689 end Freeze_Type;
7691 -------------------------
7692 -- Get_Simple_Init_Val --
7693 -------------------------
7695 function Get_Simple_Init_Val
7696 (T : Entity_Id;
7697 N : Node_Id;
7698 Size : Uint := No_Uint) return Node_Id
7700 Loc : constant Source_Ptr := Sloc (N);
7701 Val : Node_Id;
7702 Result : Node_Id;
7703 Val_RE : RE_Id;
7705 Size_To_Use : Uint;
7706 -- This is the size to be used for computation of the appropriate
7707 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
7709 IV_Attribute : constant Boolean :=
7710 Nkind (N) = N_Attribute_Reference
7711 and then Attribute_Name (N) = Name_Invalid_Value;
7713 Lo_Bound : Uint;
7714 Hi_Bound : Uint;
7715 -- These are the values computed by the procedure Check_Subtype_Bounds
7717 procedure Check_Subtype_Bounds;
7718 -- This procedure examines the subtype T, and its ancestor subtypes and
7719 -- derived types to determine the best known information about the
7720 -- bounds of the subtype. After the call Lo_Bound is set either to
7721 -- No_Uint if no information can be determined, or to a value which
7722 -- represents a known low bound, i.e. a valid value of the subtype can
7723 -- not be less than this value. Hi_Bound is similarly set to a known
7724 -- high bound (valid value cannot be greater than this).
7726 --------------------------
7727 -- Check_Subtype_Bounds --
7728 --------------------------
7730 procedure Check_Subtype_Bounds is
7731 ST1 : Entity_Id;
7732 ST2 : Entity_Id;
7733 Lo : Node_Id;
7734 Hi : Node_Id;
7735 Loval : Uint;
7736 Hival : Uint;
7738 begin
7739 Lo_Bound := No_Uint;
7740 Hi_Bound := No_Uint;
7742 -- Loop to climb ancestor subtypes and derived types
7744 ST1 := T;
7745 loop
7746 if not Is_Discrete_Type (ST1) then
7747 return;
7748 end if;
7750 Lo := Type_Low_Bound (ST1);
7751 Hi := Type_High_Bound (ST1);
7753 if Compile_Time_Known_Value (Lo) then
7754 Loval := Expr_Value (Lo);
7756 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
7757 Lo_Bound := Loval;
7758 end if;
7759 end if;
7761 if Compile_Time_Known_Value (Hi) then
7762 Hival := Expr_Value (Hi);
7764 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
7765 Hi_Bound := Hival;
7766 end if;
7767 end if;
7769 ST2 := Ancestor_Subtype (ST1);
7771 if No (ST2) then
7772 ST2 := Etype (ST1);
7773 end if;
7775 exit when ST1 = ST2;
7776 ST1 := ST2;
7777 end loop;
7778 end Check_Subtype_Bounds;
7780 -- Start of processing for Get_Simple_Init_Val
7782 begin
7783 -- For a private type, we should always have an underlying type (because
7784 -- this was already checked in Needs_Simple_Initialization). What we do
7785 -- is to get the value for the underlying type and then do an unchecked
7786 -- conversion to the private type.
7788 if Is_Private_Type (T) then
7789 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
7791 -- A special case, if the underlying value is null, then qualify it
7792 -- with the underlying type, so that the null is properly typed.
7793 -- Similarly, if it is an aggregate it must be qualified, because an
7794 -- unchecked conversion does not provide a context for it.
7796 if Nkind_In (Val, N_Null, N_Aggregate) then
7797 Val :=
7798 Make_Qualified_Expression (Loc,
7799 Subtype_Mark =>
7800 New_Occurrence_Of (Underlying_Type (T), Loc),
7801 Expression => Val);
7802 end if;
7804 Result := Unchecked_Convert_To (T, Val);
7806 -- Don't truncate result (important for Initialize/Normalize_Scalars)
7808 if Nkind (Result) = N_Unchecked_Type_Conversion
7809 and then Is_Scalar_Type (Underlying_Type (T))
7810 then
7811 Set_No_Truncation (Result);
7812 end if;
7814 return Result;
7816 -- Scalars with Default_Value aspect. The first subtype may now be
7817 -- private, so retrieve value from underlying type.
7819 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
7820 if Is_Private_Type (First_Subtype (T)) then
7821 return Unchecked_Convert_To (T,
7822 Default_Aspect_Value (Full_View (First_Subtype (T))));
7823 else
7824 return
7825 Convert_To (T, Default_Aspect_Value (First_Subtype (T)));
7826 end if;
7828 -- Otherwise, for scalars, we must have normalize/initialize scalars
7829 -- case, or if the node N is an 'Invalid_Value attribute node.
7831 elsif Is_Scalar_Type (T) then
7832 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
7834 -- Compute size of object. If it is given by the caller, we can use
7835 -- it directly, otherwise we use Esize (T) as an estimate. As far as
7836 -- we know this covers all cases correctly.
7838 if Size = No_Uint or else Size <= Uint_0 then
7839 Size_To_Use := UI_Max (Uint_1, Esize (T));
7840 else
7841 Size_To_Use := Size;
7842 end if;
7844 -- Maximum size to use is 64 bits, since we will create values of
7845 -- type Unsigned_64 and the range must fit this type.
7847 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
7848 Size_To_Use := Uint_64;
7849 end if;
7851 -- Check known bounds of subtype
7853 Check_Subtype_Bounds;
7855 -- Processing for Normalize_Scalars case
7857 if Normalize_Scalars and then not IV_Attribute then
7859 -- If zero is invalid, it is a convenient value to use that is
7860 -- for sure an appropriate invalid value in all situations.
7862 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7863 Val := Make_Integer_Literal (Loc, 0);
7865 -- Cases where all one bits is the appropriate invalid value
7867 -- For modular types, all 1 bits is either invalid or valid. If
7868 -- it is valid, then there is nothing that can be done since there
7869 -- are no invalid values (we ruled out zero already).
7871 -- For signed integer types that have no negative values, either
7872 -- there is room for negative values, or there is not. If there
7873 -- is, then all 1-bits may be interpreted as minus one, which is
7874 -- certainly invalid. Alternatively it is treated as the largest
7875 -- positive value, in which case the observation for modular types
7876 -- still applies.
7878 -- For float types, all 1-bits is a NaN (not a number), which is
7879 -- certainly an appropriately invalid value.
7881 elsif Is_Unsigned_Type (T)
7882 or else Is_Floating_Point_Type (T)
7883 or else Is_Enumeration_Type (T)
7884 then
7885 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
7887 -- Resolve as Unsigned_64, because the largest number we can
7888 -- generate is out of range of universal integer.
7890 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
7892 -- Case of signed types
7894 else
7895 declare
7896 Signed_Size : constant Uint :=
7897 UI_Min (Uint_63, Size_To_Use - 1);
7899 begin
7900 -- Normally we like to use the most negative number. The one
7901 -- exception is when this number is in the known subtype
7902 -- range and the largest positive number is not in the known
7903 -- subtype range.
7905 -- For this exceptional case, use largest positive value
7907 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
7908 and then Lo_Bound <= (-(2 ** Signed_Size))
7909 and then Hi_Bound < 2 ** Signed_Size
7910 then
7911 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
7913 -- Normal case of largest negative value
7915 else
7916 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
7917 end if;
7918 end;
7919 end if;
7921 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
7923 else
7924 -- For float types, use float values from System.Scalar_Values
7926 if Is_Floating_Point_Type (T) then
7927 if Root_Type (T) = Standard_Short_Float then
7928 Val_RE := RE_IS_Isf;
7929 elsif Root_Type (T) = Standard_Float then
7930 Val_RE := RE_IS_Ifl;
7931 elsif Root_Type (T) = Standard_Long_Float then
7932 Val_RE := RE_IS_Ilf;
7933 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
7934 Val_RE := RE_IS_Ill;
7935 end if;
7937 -- If zero is invalid, use zero values from System.Scalar_Values
7939 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7940 if Size_To_Use <= 8 then
7941 Val_RE := RE_IS_Iz1;
7942 elsif Size_To_Use <= 16 then
7943 Val_RE := RE_IS_Iz2;
7944 elsif Size_To_Use <= 32 then
7945 Val_RE := RE_IS_Iz4;
7946 else
7947 Val_RE := RE_IS_Iz8;
7948 end if;
7950 -- For unsigned, use unsigned values from System.Scalar_Values
7952 elsif Is_Unsigned_Type (T) then
7953 if Size_To_Use <= 8 then
7954 Val_RE := RE_IS_Iu1;
7955 elsif Size_To_Use <= 16 then
7956 Val_RE := RE_IS_Iu2;
7957 elsif Size_To_Use <= 32 then
7958 Val_RE := RE_IS_Iu4;
7959 else
7960 Val_RE := RE_IS_Iu8;
7961 end if;
7963 -- For signed, use signed values from System.Scalar_Values
7965 else
7966 if Size_To_Use <= 8 then
7967 Val_RE := RE_IS_Is1;
7968 elsif Size_To_Use <= 16 then
7969 Val_RE := RE_IS_Is2;
7970 elsif Size_To_Use <= 32 then
7971 Val_RE := RE_IS_Is4;
7972 else
7973 Val_RE := RE_IS_Is8;
7974 end if;
7975 end if;
7977 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
7978 end if;
7980 -- The final expression is obtained by doing an unchecked conversion
7981 -- of this result to the base type of the required subtype. Use the
7982 -- base type to prevent the unchecked conversion from chopping bits,
7983 -- and then we set Kill_Range_Check to preserve the "bad" value.
7985 Result := Unchecked_Convert_To (Base_Type (T), Val);
7987 -- Ensure result is not truncated, since we want the "bad" bits, and
7988 -- also kill range check on result.
7990 if Nkind (Result) = N_Unchecked_Type_Conversion then
7991 Set_No_Truncation (Result);
7992 Set_Kill_Range_Check (Result, True);
7993 end if;
7995 return Result;
7997 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
7999 elsif Is_Standard_String_Type (T) then
8000 pragma Assert (Init_Or_Norm_Scalars);
8002 return
8003 Make_Aggregate (Loc,
8004 Component_Associations => New_List (
8005 Make_Component_Association (Loc,
8006 Choices => New_List (
8007 Make_Others_Choice (Loc)),
8008 Expression =>
8009 Get_Simple_Init_Val
8010 (Component_Type (T), N, Esize (Root_Type (T))))));
8012 -- Access type is initialized to null
8014 elsif Is_Access_Type (T) then
8015 return Make_Null (Loc);
8017 -- No other possibilities should arise, since we should only be calling
8018 -- Get_Simple_Init_Val if Needs_Simple_Initialization returned True,
8019 -- indicating one of the above cases held.
8021 else
8022 raise Program_Error;
8023 end if;
8025 exception
8026 when RE_Not_Available =>
8027 return Empty;
8028 end Get_Simple_Init_Val;
8030 ------------------------------
8031 -- Has_New_Non_Standard_Rep --
8032 ------------------------------
8034 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
8035 begin
8036 if not Is_Derived_Type (T) then
8037 return Has_Non_Standard_Rep (T)
8038 or else Has_Non_Standard_Rep (Root_Type (T));
8040 -- If Has_Non_Standard_Rep is not set on the derived type, the
8041 -- representation is fully inherited.
8043 elsif not Has_Non_Standard_Rep (T) then
8044 return False;
8046 else
8047 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
8049 -- May need a more precise check here: the First_Rep_Item may be a
8050 -- stream attribute, which does not affect the representation of the
8051 -- type ???
8053 end if;
8054 end Has_New_Non_Standard_Rep;
8056 ----------------
8057 -- In_Runtime --
8058 ----------------
8060 function In_Runtime (E : Entity_Id) return Boolean is
8061 S1 : Entity_Id;
8063 begin
8064 S1 := Scope (E);
8065 while Scope (S1) /= Standard_Standard loop
8066 S1 := Scope (S1);
8067 end loop;
8069 return Is_RTU (S1, System) or else Is_RTU (S1, Ada);
8070 end In_Runtime;
8072 ---------------------------------------
8073 -- Insert_Component_Invariant_Checks --
8074 ---------------------------------------
8076 procedure Insert_Component_Invariant_Checks
8077 (N : Node_Id;
8078 Typ : Entity_Id;
8079 Proc : Node_Id)
8081 Loc : constant Source_Ptr := Sloc (Typ);
8082 Proc_Id : Entity_Id;
8084 begin
8085 if Present (Proc) then
8086 Proc_Id := Defining_Entity (Proc);
8088 if not Has_Invariants (Typ) then
8089 Set_Has_Invariants (Typ);
8090 Set_Is_Invariant_Procedure (Proc_Id);
8091 Set_Invariant_Procedure (Typ, Proc_Id);
8092 Insert_After (N, Proc);
8093 Analyze (Proc);
8095 else
8097 -- Find already created invariant subprogram, insert body of
8098 -- component invariant proc in its body, and add call after
8099 -- other checks.
8101 declare
8102 Bod : Node_Id;
8103 Inv_Id : constant Entity_Id := Invariant_Procedure (Typ);
8104 Call : constant Node_Id :=
8105 Make_Procedure_Call_Statement (Sloc (N),
8106 Name => New_Occurrence_Of (Proc_Id, Loc),
8107 Parameter_Associations =>
8108 New_List
8109 (New_Occurrence_Of (First_Formal (Inv_Id), Loc)));
8111 begin
8112 -- The invariant body has not been analyzed yet, so we do a
8113 -- sequential search forward, and retrieve it by name.
8115 Bod := Next (N);
8116 while Present (Bod) loop
8117 exit when Nkind (Bod) = N_Subprogram_Body
8118 and then Chars (Defining_Entity (Bod)) = Chars (Inv_Id);
8119 Next (Bod);
8120 end loop;
8122 -- If the body is not found, it is the case of an invariant
8123 -- appearing on a full declaration in a private part, in
8124 -- which case the type has been frozen but the invariant
8125 -- procedure for the composite type not created yet. Create
8126 -- body now.
8128 if No (Bod) then
8129 Build_Invariant_Procedure (Typ, Parent (Current_Scope));
8130 Bod := Unit_Declaration_Node
8131 (Corresponding_Body (Unit_Declaration_Node (Inv_Id)));
8132 end if;
8134 Append_To (Declarations (Bod), Proc);
8135 Append_To (Statements (Handled_Statement_Sequence (Bod)), Call);
8136 Analyze (Proc);
8137 Analyze (Call);
8138 end;
8139 end if;
8140 end if;
8141 end Insert_Component_Invariant_Checks;
8143 ----------------------------
8144 -- Initialization_Warning --
8145 ----------------------------
8147 procedure Initialization_Warning (E : Entity_Id) is
8148 Warning_Needed : Boolean;
8150 begin
8151 Warning_Needed := False;
8153 if Ekind (Current_Scope) = E_Package
8154 and then Static_Elaboration_Desired (Current_Scope)
8155 then
8156 if Is_Type (E) then
8157 if Is_Record_Type (E) then
8158 if Has_Discriminants (E)
8159 or else Is_Limited_Type (E)
8160 or else Has_Non_Standard_Rep (E)
8161 then
8162 Warning_Needed := True;
8164 else
8165 -- Verify that at least one component has an initialization
8166 -- expression. No need for a warning on a type if all its
8167 -- components have no initialization.
8169 declare
8170 Comp : Entity_Id;
8172 begin
8173 Comp := First_Component (E);
8174 while Present (Comp) loop
8175 if Ekind (Comp) = E_Discriminant
8176 or else
8177 (Nkind (Parent (Comp)) = N_Component_Declaration
8178 and then Present (Expression (Parent (Comp))))
8179 then
8180 Warning_Needed := True;
8181 exit;
8182 end if;
8184 Next_Component (Comp);
8185 end loop;
8186 end;
8187 end if;
8189 if Warning_Needed then
8190 Error_Msg_N
8191 ("Objects of the type cannot be initialized statically "
8192 & "by default??", Parent (E));
8193 end if;
8194 end if;
8196 else
8197 Error_Msg_N ("Object cannot be initialized statically??", E);
8198 end if;
8199 end if;
8200 end Initialization_Warning;
8202 ------------------
8203 -- Init_Formals --
8204 ------------------
8206 function Init_Formals (Typ : Entity_Id) return List_Id is
8207 Loc : constant Source_Ptr := Sloc (Typ);
8208 Formals : List_Id;
8210 begin
8211 -- First parameter is always _Init : in out typ. Note that we need this
8212 -- to be in/out because in the case of the task record value, there
8213 -- are default record fields (_Priority, _Size, -Task_Info) that may
8214 -- be referenced in the generated initialization routine.
8216 Formals := New_List (
8217 Make_Parameter_Specification (Loc,
8218 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uInit),
8219 In_Present => True,
8220 Out_Present => True,
8221 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
8223 -- For task record value, or type that contains tasks, add two more
8224 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
8225 -- We also add these parameters for the task record type case.
8227 if Has_Task (Typ)
8228 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
8229 then
8230 Append_To (Formals,
8231 Make_Parameter_Specification (Loc,
8232 Defining_Identifier =>
8233 Make_Defining_Identifier (Loc, Name_uMaster),
8234 Parameter_Type =>
8235 New_Occurrence_Of (RTE (RE_Master_Id), Loc)));
8237 -- Add _Chain (not done for sequential elaboration policy, see
8238 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
8240 if Partition_Elaboration_Policy /= 'S' then
8241 Append_To (Formals,
8242 Make_Parameter_Specification (Loc,
8243 Defining_Identifier =>
8244 Make_Defining_Identifier (Loc, Name_uChain),
8245 In_Present => True,
8246 Out_Present => True,
8247 Parameter_Type =>
8248 New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)));
8249 end if;
8251 Append_To (Formals,
8252 Make_Parameter_Specification (Loc,
8253 Defining_Identifier =>
8254 Make_Defining_Identifier (Loc, Name_uTask_Name),
8255 In_Present => True,
8256 Parameter_Type => New_Occurrence_Of (Standard_String, Loc)));
8257 end if;
8259 return Formals;
8261 exception
8262 when RE_Not_Available =>
8263 return Empty_List;
8264 end Init_Formals;
8266 -------------------------
8267 -- Init_Secondary_Tags --
8268 -------------------------
8270 procedure Init_Secondary_Tags
8271 (Typ : Entity_Id;
8272 Target : Node_Id;
8273 Stmts_List : List_Id;
8274 Fixed_Comps : Boolean := True;
8275 Variable_Comps : Boolean := True)
8277 Loc : constant Source_Ptr := Sloc (Target);
8279 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
8280 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8282 procedure Initialize_Tag
8283 (Typ : Entity_Id;
8284 Iface : Entity_Id;
8285 Tag_Comp : Entity_Id;
8286 Iface_Tag : Node_Id);
8287 -- Initialize the tag of the secondary dispatch table of Typ associated
8288 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8289 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
8290 -- of Typ CPP tagged type we generate code to inherit the contents of
8291 -- the dispatch table directly from the ancestor.
8293 --------------------
8294 -- Initialize_Tag --
8295 --------------------
8297 procedure Initialize_Tag
8298 (Typ : Entity_Id;
8299 Iface : Entity_Id;
8300 Tag_Comp : Entity_Id;
8301 Iface_Tag : Node_Id)
8303 Comp_Typ : Entity_Id;
8304 Offset_To_Top_Comp : Entity_Id := Empty;
8306 begin
8307 -- Initialize pointer to secondary DT associated with the interface
8309 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8310 Append_To (Stmts_List,
8311 Make_Assignment_Statement (Loc,
8312 Name =>
8313 Make_Selected_Component (Loc,
8314 Prefix => New_Copy_Tree (Target),
8315 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8316 Expression =>
8317 New_Occurrence_Of (Iface_Tag, Loc)));
8318 end if;
8320 Comp_Typ := Scope (Tag_Comp);
8322 -- Initialize the entries of the table of interfaces. We generate a
8323 -- different call when the parent of the type has variable size
8324 -- components.
8326 if Comp_Typ /= Etype (Comp_Typ)
8327 and then Is_Variable_Size_Record (Etype (Comp_Typ))
8328 and then Chars (Tag_Comp) /= Name_uTag
8329 then
8330 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
8332 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
8333 -- configurable run-time environment.
8335 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
8336 Error_Msg_CRT
8337 ("variable size record with interface types", Typ);
8338 return;
8339 end if;
8341 -- Generate:
8342 -- Set_Dynamic_Offset_To_Top
8343 -- (This => Init,
8344 -- Interface_T => Iface'Tag,
8345 -- Offset_Value => n,
8346 -- Offset_Func => Fn'Address)
8348 Append_To (Stmts_List,
8349 Make_Procedure_Call_Statement (Loc,
8350 Name =>
8351 New_Occurrence_Of (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
8352 Parameter_Associations => New_List (
8353 Make_Attribute_Reference (Loc,
8354 Prefix => New_Copy_Tree (Target),
8355 Attribute_Name => Name_Address),
8357 Unchecked_Convert_To (RTE (RE_Tag),
8358 New_Occurrence_Of
8359 (Node (First_Elmt (Access_Disp_Table (Iface))),
8360 Loc)),
8362 Unchecked_Convert_To
8363 (RTE (RE_Storage_Offset),
8364 Make_Attribute_Reference (Loc,
8365 Prefix =>
8366 Make_Selected_Component (Loc,
8367 Prefix => New_Copy_Tree (Target),
8368 Selector_Name =>
8369 New_Occurrence_Of (Tag_Comp, Loc)),
8370 Attribute_Name => Name_Position)),
8372 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
8373 Make_Attribute_Reference (Loc,
8374 Prefix => New_Occurrence_Of
8375 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
8376 Attribute_Name => Name_Address)))));
8378 -- In this case the next component stores the value of the offset
8379 -- to the top.
8381 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
8382 pragma Assert (Present (Offset_To_Top_Comp));
8384 Append_To (Stmts_List,
8385 Make_Assignment_Statement (Loc,
8386 Name =>
8387 Make_Selected_Component (Loc,
8388 Prefix => New_Copy_Tree (Target),
8389 Selector_Name =>
8390 New_Occurrence_Of (Offset_To_Top_Comp, Loc)),
8392 Expression =>
8393 Make_Attribute_Reference (Loc,
8394 Prefix =>
8395 Make_Selected_Component (Loc,
8396 Prefix => New_Copy_Tree (Target),
8397 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8398 Attribute_Name => Name_Position)));
8400 -- Normal case: No discriminants in the parent type
8402 else
8403 -- Don't need to set any value if this interface shares the
8404 -- primary dispatch table.
8406 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8407 Append_To (Stmts_List,
8408 Build_Set_Static_Offset_To_Top (Loc,
8409 Iface_Tag => New_Occurrence_Of (Iface_Tag, Loc),
8410 Offset_Value =>
8411 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8412 Make_Attribute_Reference (Loc,
8413 Prefix =>
8414 Make_Selected_Component (Loc,
8415 Prefix => New_Copy_Tree (Target),
8416 Selector_Name =>
8417 New_Occurrence_Of (Tag_Comp, Loc)),
8418 Attribute_Name => Name_Position))));
8419 end if;
8421 -- Generate:
8422 -- Register_Interface_Offset
8423 -- (This => Init,
8424 -- Interface_T => Iface'Tag,
8425 -- Is_Constant => True,
8426 -- Offset_Value => n,
8427 -- Offset_Func => null);
8429 if RTE_Available (RE_Register_Interface_Offset) then
8430 Append_To (Stmts_List,
8431 Make_Procedure_Call_Statement (Loc,
8432 Name =>
8433 New_Occurrence_Of
8434 (RTE (RE_Register_Interface_Offset), Loc),
8435 Parameter_Associations => New_List (
8436 Make_Attribute_Reference (Loc,
8437 Prefix => New_Copy_Tree (Target),
8438 Attribute_Name => Name_Address),
8440 Unchecked_Convert_To (RTE (RE_Tag),
8441 New_Occurrence_Of
8442 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
8444 New_Occurrence_Of (Standard_True, Loc),
8446 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8447 Make_Attribute_Reference (Loc,
8448 Prefix =>
8449 Make_Selected_Component (Loc,
8450 Prefix => New_Copy_Tree (Target),
8451 Selector_Name =>
8452 New_Occurrence_Of (Tag_Comp, Loc)),
8453 Attribute_Name => Name_Position)),
8455 Make_Null (Loc))));
8456 end if;
8457 end if;
8458 end Initialize_Tag;
8460 -- Local variables
8462 Full_Typ : Entity_Id;
8463 Ifaces_List : Elist_Id;
8464 Ifaces_Comp_List : Elist_Id;
8465 Ifaces_Tag_List : Elist_Id;
8466 Iface_Elmt : Elmt_Id;
8467 Iface_Comp_Elmt : Elmt_Id;
8468 Iface_Tag_Elmt : Elmt_Id;
8469 Tag_Comp : Node_Id;
8470 In_Variable_Pos : Boolean;
8472 -- Start of processing for Init_Secondary_Tags
8474 begin
8475 -- Handle private types
8477 if Present (Full_View (Typ)) then
8478 Full_Typ := Full_View (Typ);
8479 else
8480 Full_Typ := Typ;
8481 end if;
8483 Collect_Interfaces_Info
8484 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
8486 Iface_Elmt := First_Elmt (Ifaces_List);
8487 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
8488 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
8489 while Present (Iface_Elmt) loop
8490 Tag_Comp := Node (Iface_Comp_Elmt);
8492 -- Check if parent of record type has variable size components
8494 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
8495 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
8497 -- If we are compiling under the CPP full ABI compatibility mode and
8498 -- the ancestor is a CPP_Pragma tagged type then we generate code to
8499 -- initialize the secondary tag components from tags that reference
8500 -- secondary tables filled with copy of parent slots.
8502 if Is_CPP_Class (Root_Type (Full_Typ)) then
8504 -- Reject interface components located at variable offset in
8505 -- C++ derivations. This is currently unsupported.
8507 if not Fixed_Comps and then In_Variable_Pos then
8509 -- Locate the first dynamic component of the record. Done to
8510 -- improve the text of the warning.
8512 declare
8513 Comp : Entity_Id;
8514 Comp_Typ : Entity_Id;
8516 begin
8517 Comp := First_Entity (Typ);
8518 while Present (Comp) loop
8519 Comp_Typ := Etype (Comp);
8521 if Ekind (Comp) /= E_Discriminant
8522 and then not Is_Tag (Comp)
8523 then
8524 exit when
8525 (Is_Record_Type (Comp_Typ)
8526 and then
8527 Is_Variable_Size_Record (Base_Type (Comp_Typ)))
8528 or else
8529 (Is_Array_Type (Comp_Typ)
8530 and then Is_Variable_Size_Array (Comp_Typ));
8531 end if;
8533 Next_Entity (Comp);
8534 end loop;
8536 pragma Assert (Present (Comp));
8537 Error_Msg_Node_2 := Comp;
8538 Error_Msg_NE
8539 ("parent type & with dynamic component & cannot be parent"
8540 & " of 'C'P'P derivation if new interfaces are present",
8541 Typ, Scope (Original_Record_Component (Comp)));
8543 Error_Msg_Sloc :=
8544 Sloc (Scope (Original_Record_Component (Comp)));
8545 Error_Msg_NE
8546 ("type derived from 'C'P'P type & defined #",
8547 Typ, Scope (Original_Record_Component (Comp)));
8549 -- Avoid duplicated warnings
8551 exit;
8552 end;
8554 -- Initialize secondary tags
8556 else
8557 Append_To (Stmts_List,
8558 Make_Assignment_Statement (Loc,
8559 Name =>
8560 Make_Selected_Component (Loc,
8561 Prefix => New_Copy_Tree (Target),
8562 Selector_Name =>
8563 New_Occurrence_Of (Node (Iface_Comp_Elmt), Loc)),
8564 Expression =>
8565 New_Occurrence_Of (Node (Iface_Tag_Elmt), Loc)));
8566 end if;
8568 -- Otherwise generate code to initialize the tag
8570 else
8571 if (In_Variable_Pos and then Variable_Comps)
8572 or else (not In_Variable_Pos and then Fixed_Comps)
8573 then
8574 Initialize_Tag (Full_Typ,
8575 Iface => Node (Iface_Elmt),
8576 Tag_Comp => Tag_Comp,
8577 Iface_Tag => Node (Iface_Tag_Elmt));
8578 end if;
8579 end if;
8581 Next_Elmt (Iface_Elmt);
8582 Next_Elmt (Iface_Comp_Elmt);
8583 Next_Elmt (Iface_Tag_Elmt);
8584 end loop;
8585 end Init_Secondary_Tags;
8587 ------------------------
8588 -- Is_User_Defined_Eq --
8589 ------------------------
8591 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean is
8592 begin
8593 return Chars (Prim) = Name_Op_Eq
8594 and then Etype (First_Formal (Prim)) =
8595 Etype (Next_Formal (First_Formal (Prim)))
8596 and then Base_Type (Etype (Prim)) = Standard_Boolean;
8597 end Is_User_Defined_Equality;
8599 ----------------------------------------
8600 -- Make_Controlling_Function_Wrappers --
8601 ----------------------------------------
8603 procedure Make_Controlling_Function_Wrappers
8604 (Tag_Typ : Entity_Id;
8605 Decl_List : out List_Id;
8606 Body_List : out List_Id)
8608 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8609 Prim_Elmt : Elmt_Id;
8610 Subp : Entity_Id;
8611 Actual_List : List_Id;
8612 Formal_List : List_Id;
8613 Formal : Entity_Id;
8614 Par_Formal : Entity_Id;
8615 Formal_Node : Node_Id;
8616 Func_Body : Node_Id;
8617 Func_Decl : Node_Id;
8618 Func_Spec : Node_Id;
8619 Return_Stmt : Node_Id;
8621 begin
8622 Decl_List := New_List;
8623 Body_List := New_List;
8625 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
8627 while Present (Prim_Elmt) loop
8628 Subp := Node (Prim_Elmt);
8630 -- If a primitive function with a controlling result of the type has
8631 -- not been overridden by the user, then we must create a wrapper
8632 -- function here that effectively overrides it and invokes the
8633 -- (non-abstract) parent function. This can only occur for a null
8634 -- extension. Note that functions with anonymous controlling access
8635 -- results don't qualify and must be overridden. We also exclude
8636 -- Input attributes, since each type will have its own version of
8637 -- Input constructed by the expander. The test for Comes_From_Source
8638 -- is needed to distinguish inherited operations from renamings
8639 -- (which also have Alias set). We exclude internal entities with
8640 -- Interface_Alias to avoid generating duplicated wrappers since
8641 -- the primitive which covers the interface is also available in
8642 -- the list of primitive operations.
8644 -- The function may be abstract, or require_Overriding may be set
8645 -- for it, because tests for null extensions may already have reset
8646 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
8647 -- set, functions that need wrappers are recognized by having an
8648 -- alias that returns the parent type.
8650 if Comes_From_Source (Subp)
8651 or else No (Alias (Subp))
8652 or else Present (Interface_Alias (Subp))
8653 or else Ekind (Subp) /= E_Function
8654 or else not Has_Controlling_Result (Subp)
8655 or else Is_Access_Type (Etype (Subp))
8656 or else Is_Abstract_Subprogram (Alias (Subp))
8657 or else Is_TSS (Subp, TSS_Stream_Input)
8658 then
8659 goto Next_Prim;
8661 elsif Is_Abstract_Subprogram (Subp)
8662 or else Requires_Overriding (Subp)
8663 or else
8664 (Is_Null_Extension (Etype (Subp))
8665 and then Etype (Alias (Subp)) /= Etype (Subp))
8666 then
8667 Formal_List := No_List;
8668 Formal := First_Formal (Subp);
8670 if Present (Formal) then
8671 Formal_List := New_List;
8673 while Present (Formal) loop
8674 Append
8675 (Make_Parameter_Specification
8676 (Loc,
8677 Defining_Identifier =>
8678 Make_Defining_Identifier (Sloc (Formal),
8679 Chars => Chars (Formal)),
8680 In_Present => In_Present (Parent (Formal)),
8681 Out_Present => Out_Present (Parent (Formal)),
8682 Null_Exclusion_Present =>
8683 Null_Exclusion_Present (Parent (Formal)),
8684 Parameter_Type =>
8685 New_Occurrence_Of (Etype (Formal), Loc),
8686 Expression =>
8687 New_Copy_Tree (Expression (Parent (Formal)))),
8688 Formal_List);
8690 Next_Formal (Formal);
8691 end loop;
8692 end if;
8694 Func_Spec :=
8695 Make_Function_Specification (Loc,
8696 Defining_Unit_Name =>
8697 Make_Defining_Identifier (Loc,
8698 Chars => Chars (Subp)),
8699 Parameter_Specifications => Formal_List,
8700 Result_Definition =>
8701 New_Occurrence_Of (Etype (Subp), Loc));
8703 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
8704 Append_To (Decl_List, Func_Decl);
8706 -- Build a wrapper body that calls the parent function. The body
8707 -- contains a single return statement that returns an extension
8708 -- aggregate whose ancestor part is a call to the parent function,
8709 -- passing the formals as actuals (with any controlling arguments
8710 -- converted to the types of the corresponding formals of the
8711 -- parent function, which might be anonymous access types), and
8712 -- having a null extension.
8714 Formal := First_Formal (Subp);
8715 Par_Formal := First_Formal (Alias (Subp));
8716 Formal_Node := First (Formal_List);
8718 if Present (Formal) then
8719 Actual_List := New_List;
8720 else
8721 Actual_List := No_List;
8722 end if;
8724 while Present (Formal) loop
8725 if Is_Controlling_Formal (Formal) then
8726 Append_To (Actual_List,
8727 Make_Type_Conversion (Loc,
8728 Subtype_Mark =>
8729 New_Occurrence_Of (Etype (Par_Formal), Loc),
8730 Expression =>
8731 New_Occurrence_Of
8732 (Defining_Identifier (Formal_Node), Loc)));
8733 else
8734 Append_To
8735 (Actual_List,
8736 New_Occurrence_Of
8737 (Defining_Identifier (Formal_Node), Loc));
8738 end if;
8740 Next_Formal (Formal);
8741 Next_Formal (Par_Formal);
8742 Next (Formal_Node);
8743 end loop;
8745 Return_Stmt :=
8746 Make_Simple_Return_Statement (Loc,
8747 Expression =>
8748 Make_Extension_Aggregate (Loc,
8749 Ancestor_Part =>
8750 Make_Function_Call (Loc,
8751 Name =>
8752 New_Occurrence_Of (Alias (Subp), Loc),
8753 Parameter_Associations => Actual_List),
8754 Null_Record_Present => True));
8756 Func_Body :=
8757 Make_Subprogram_Body (Loc,
8758 Specification => New_Copy_Tree (Func_Spec),
8759 Declarations => Empty_List,
8760 Handled_Statement_Sequence =>
8761 Make_Handled_Sequence_Of_Statements (Loc,
8762 Statements => New_List (Return_Stmt)));
8764 Set_Defining_Unit_Name
8765 (Specification (Func_Body),
8766 Make_Defining_Identifier (Loc, Chars (Subp)));
8768 Append_To (Body_List, Func_Body);
8770 -- Replace the inherited function with the wrapper function in the
8771 -- primitive operations list. We add the minimum decoration needed
8772 -- to override interface primitives.
8774 Set_Ekind (Defining_Unit_Name (Func_Spec), E_Function);
8776 Override_Dispatching_Operation
8777 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec),
8778 Is_Wrapper => True);
8779 end if;
8781 <<Next_Prim>>
8782 Next_Elmt (Prim_Elmt);
8783 end loop;
8784 end Make_Controlling_Function_Wrappers;
8786 -------------------
8787 -- Make_Eq_Body --
8788 -------------------
8790 function Make_Eq_Body
8791 (Typ : Entity_Id;
8792 Eq_Name : Name_Id) return Node_Id
8794 Loc : constant Source_Ptr := Sloc (Parent (Typ));
8795 Decl : Node_Id;
8796 Def : constant Node_Id := Parent (Typ);
8797 Stmts : constant List_Id := New_List;
8798 Variant_Case : Boolean := Has_Discriminants (Typ);
8799 Comps : Node_Id := Empty;
8800 Typ_Def : Node_Id := Type_Definition (Def);
8802 begin
8803 Decl :=
8804 Predef_Spec_Or_Body (Loc,
8805 Tag_Typ => Typ,
8806 Name => Eq_Name,
8807 Profile => New_List (
8808 Make_Parameter_Specification (Loc,
8809 Defining_Identifier =>
8810 Make_Defining_Identifier (Loc, Name_X),
8811 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
8813 Make_Parameter_Specification (Loc,
8814 Defining_Identifier =>
8815 Make_Defining_Identifier (Loc, Name_Y),
8816 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
8818 Ret_Type => Standard_Boolean,
8819 For_Body => True);
8821 if Variant_Case then
8822 if Nkind (Typ_Def) = N_Derived_Type_Definition then
8823 Typ_Def := Record_Extension_Part (Typ_Def);
8824 end if;
8826 if Present (Typ_Def) then
8827 Comps := Component_List (Typ_Def);
8828 end if;
8830 Variant_Case :=
8831 Present (Comps) and then Present (Variant_Part (Comps));
8832 end if;
8834 if Variant_Case then
8835 Append_To (Stmts,
8836 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
8837 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
8838 Append_To (Stmts,
8839 Make_Simple_Return_Statement (Loc,
8840 Expression => New_Occurrence_Of (Standard_True, Loc)));
8842 else
8843 Append_To (Stmts,
8844 Make_Simple_Return_Statement (Loc,
8845 Expression =>
8846 Expand_Record_Equality
8847 (Typ,
8848 Typ => Typ,
8849 Lhs => Make_Identifier (Loc, Name_X),
8850 Rhs => Make_Identifier (Loc, Name_Y),
8851 Bodies => Declarations (Decl))));
8852 end if;
8854 Set_Handled_Statement_Sequence
8855 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8856 return Decl;
8857 end Make_Eq_Body;
8859 ------------------
8860 -- Make_Eq_Case --
8861 ------------------
8863 -- <Make_Eq_If shared components>
8865 -- case X.D1 is
8866 -- when V1 => <Make_Eq_Case> on subcomponents
8867 -- ...
8868 -- when Vn => <Make_Eq_Case> on subcomponents
8869 -- end case;
8871 function Make_Eq_Case
8872 (E : Entity_Id;
8873 CL : Node_Id;
8874 Discrs : Elist_Id := New_Elmt_List) return List_Id
8876 Loc : constant Source_Ptr := Sloc (E);
8877 Result : constant List_Id := New_List;
8878 Variant : Node_Id;
8879 Alt_List : List_Id;
8881 function Corresponding_Formal (C : Node_Id) return Entity_Id;
8882 -- Given the discriminant that controls a given variant of an unchecked
8883 -- union, find the formal of the equality function that carries the
8884 -- inferred value of the discriminant.
8886 function External_Name (E : Entity_Id) return Name_Id;
8887 -- The value of a given discriminant is conveyed in the corresponding
8888 -- formal parameter of the equality routine. The name of this formal
8889 -- parameter carries a one-character suffix which is removed here.
8891 --------------------------
8892 -- Corresponding_Formal --
8893 --------------------------
8895 function Corresponding_Formal (C : Node_Id) return Entity_Id is
8896 Discr : constant Entity_Id := Entity (Name (Variant_Part (C)));
8897 Elm : Elmt_Id;
8899 begin
8900 Elm := First_Elmt (Discrs);
8901 while Present (Elm) loop
8902 if Chars (Discr) = External_Name (Node (Elm)) then
8903 return Node (Elm);
8904 end if;
8906 Next_Elmt (Elm);
8907 end loop;
8909 -- A formal of the proper name must be found
8911 raise Program_Error;
8912 end Corresponding_Formal;
8914 -------------------
8915 -- External_Name --
8916 -------------------
8918 function External_Name (E : Entity_Id) return Name_Id is
8919 begin
8920 Get_Name_String (Chars (E));
8921 Name_Len := Name_Len - 1;
8922 return Name_Find;
8923 end External_Name;
8925 -- Start of processing for Make_Eq_Case
8927 begin
8928 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
8930 if No (Variant_Part (CL)) then
8931 return Result;
8932 end if;
8934 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
8936 if No (Variant) then
8937 return Result;
8938 end if;
8940 Alt_List := New_List;
8941 while Present (Variant) loop
8942 Append_To (Alt_List,
8943 Make_Case_Statement_Alternative (Loc,
8944 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
8945 Statements =>
8946 Make_Eq_Case (E, Component_List (Variant), Discrs)));
8947 Next_Non_Pragma (Variant);
8948 end loop;
8950 -- If we have an Unchecked_Union, use one of the parameters of the
8951 -- enclosing equality routine that captures the discriminant, to use
8952 -- as the expression in the generated case statement.
8954 if Is_Unchecked_Union (E) then
8955 Append_To (Result,
8956 Make_Case_Statement (Loc,
8957 Expression =>
8958 New_Occurrence_Of (Corresponding_Formal (CL), Loc),
8959 Alternatives => Alt_List));
8961 else
8962 Append_To (Result,
8963 Make_Case_Statement (Loc,
8964 Expression =>
8965 Make_Selected_Component (Loc,
8966 Prefix => Make_Identifier (Loc, Name_X),
8967 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
8968 Alternatives => Alt_List));
8969 end if;
8971 return Result;
8972 end Make_Eq_Case;
8974 ----------------
8975 -- Make_Eq_If --
8976 ----------------
8978 -- Generates:
8980 -- if
8981 -- X.C1 /= Y.C1
8982 -- or else
8983 -- X.C2 /= Y.C2
8984 -- ...
8985 -- then
8986 -- return False;
8987 -- end if;
8989 -- or a null statement if the list L is empty
8991 function Make_Eq_If
8992 (E : Entity_Id;
8993 L : List_Id) return Node_Id
8995 Loc : constant Source_Ptr := Sloc (E);
8996 C : Node_Id;
8997 Field_Name : Name_Id;
8998 Cond : Node_Id;
9000 begin
9001 if No (L) then
9002 return Make_Null_Statement (Loc);
9004 else
9005 Cond := Empty;
9007 C := First_Non_Pragma (L);
9008 while Present (C) loop
9009 Field_Name := Chars (Defining_Identifier (C));
9011 -- The tags must not be compared: they are not part of the value.
9012 -- Ditto for parent interfaces because their equality operator is
9013 -- abstract.
9015 -- Note also that in the following, we use Make_Identifier for
9016 -- the component names. Use of New_Occurrence_Of to identify the
9017 -- components would be incorrect because the wrong entities for
9018 -- discriminants could be picked up in the private type case.
9020 if Field_Name = Name_uParent
9021 and then Is_Interface (Etype (Defining_Identifier (C)))
9022 then
9023 null;
9025 elsif Field_Name /= Name_uTag then
9026 Evolve_Or_Else (Cond,
9027 Make_Op_Ne (Loc,
9028 Left_Opnd =>
9029 Make_Selected_Component (Loc,
9030 Prefix => Make_Identifier (Loc, Name_X),
9031 Selector_Name => Make_Identifier (Loc, Field_Name)),
9033 Right_Opnd =>
9034 Make_Selected_Component (Loc,
9035 Prefix => Make_Identifier (Loc, Name_Y),
9036 Selector_Name => Make_Identifier (Loc, Field_Name))));
9037 end if;
9039 Next_Non_Pragma (C);
9040 end loop;
9042 if No (Cond) then
9043 return Make_Null_Statement (Loc);
9045 else
9046 return
9047 Make_Implicit_If_Statement (E,
9048 Condition => Cond,
9049 Then_Statements => New_List (
9050 Make_Simple_Return_Statement (Loc,
9051 Expression => New_Occurrence_Of (Standard_False, Loc))));
9052 end if;
9053 end if;
9054 end Make_Eq_If;
9056 -------------------
9057 -- Make_Neq_Body --
9058 -------------------
9060 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id is
9062 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean;
9063 -- Returns true if Prim is a renaming of an unresolved predefined
9064 -- inequality operation.
9066 --------------------------------
9067 -- Is_Predefined_Neq_Renaming --
9068 --------------------------------
9070 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean is
9071 begin
9072 return Chars (Prim) /= Name_Op_Ne
9073 and then Present (Alias (Prim))
9074 and then Comes_From_Source (Prim)
9075 and then Is_Intrinsic_Subprogram (Alias (Prim))
9076 and then Chars (Alias (Prim)) = Name_Op_Ne;
9077 end Is_Predefined_Neq_Renaming;
9079 -- Local variables
9081 Loc : constant Source_Ptr := Sloc (Parent (Tag_Typ));
9082 Stmts : constant List_Id := New_List;
9083 Decl : Node_Id;
9084 Eq_Prim : Entity_Id;
9085 Left_Op : Entity_Id;
9086 Renaming_Prim : Entity_Id;
9087 Right_Op : Entity_Id;
9088 Target : Entity_Id;
9090 -- Start of processing for Make_Neq_Body
9092 begin
9093 -- For a call on a renaming of a dispatching subprogram that is
9094 -- overridden, if the overriding occurred before the renaming, then
9095 -- the body executed is that of the overriding declaration, even if the
9096 -- overriding declaration is not visible at the place of the renaming;
9097 -- otherwise, the inherited or predefined subprogram is called, see
9098 -- (RM 8.5.4(8))
9100 -- Stage 1: Search for a renaming of the inequality primitive and also
9101 -- search for an overriding of the equality primitive located before the
9102 -- renaming declaration.
9104 declare
9105 Elmt : Elmt_Id;
9106 Prim : Node_Id;
9108 begin
9109 Eq_Prim := Empty;
9110 Renaming_Prim := Empty;
9112 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9113 while Present (Elmt) loop
9114 Prim := Node (Elmt);
9116 if Is_User_Defined_Equality (Prim) and then No (Alias (Prim)) then
9117 if No (Renaming_Prim) then
9118 pragma Assert (No (Eq_Prim));
9119 Eq_Prim := Prim;
9120 end if;
9122 elsif Is_Predefined_Neq_Renaming (Prim) then
9123 Renaming_Prim := Prim;
9124 end if;
9126 Next_Elmt (Elmt);
9127 end loop;
9128 end;
9130 -- No further action needed if no renaming was found
9132 if No (Renaming_Prim) then
9133 return Empty;
9134 end if;
9136 -- Stage 2: Replace the renaming declaration by a subprogram declaration
9137 -- (required to add its body)
9139 Decl := Parent (Parent (Renaming_Prim));
9140 Rewrite (Decl,
9141 Make_Subprogram_Declaration (Loc,
9142 Specification => Specification (Decl)));
9143 Set_Analyzed (Decl);
9145 -- Remove the decoration of intrinsic renaming subprogram
9147 Set_Is_Intrinsic_Subprogram (Renaming_Prim, False);
9148 Set_Convention (Renaming_Prim, Convention_Ada);
9149 Set_Alias (Renaming_Prim, Empty);
9150 Set_Has_Completion (Renaming_Prim, False);
9152 -- Stage 3: Build the corresponding body
9154 Left_Op := First_Formal (Renaming_Prim);
9155 Right_Op := Next_Formal (Left_Op);
9157 Decl :=
9158 Predef_Spec_Or_Body (Loc,
9159 Tag_Typ => Tag_Typ,
9160 Name => Chars (Renaming_Prim),
9161 Profile => New_List (
9162 Make_Parameter_Specification (Loc,
9163 Defining_Identifier =>
9164 Make_Defining_Identifier (Loc, Chars (Left_Op)),
9165 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9167 Make_Parameter_Specification (Loc,
9168 Defining_Identifier =>
9169 Make_Defining_Identifier (Loc, Chars (Right_Op)),
9170 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9172 Ret_Type => Standard_Boolean,
9173 For_Body => True);
9175 -- If the overriding of the equality primitive occurred before the
9176 -- renaming, then generate:
9178 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9179 -- begin
9180 -- return not Oeq (X, Y);
9181 -- end;
9183 if Present (Eq_Prim) then
9184 Target := Eq_Prim;
9186 -- Otherwise build a nested subprogram which performs the predefined
9187 -- evaluation of the equality operator. That is, generate:
9189 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9190 -- function Oeq (X : Y) return Boolean is
9191 -- begin
9192 -- <<body of default implementation>>
9193 -- end;
9194 -- begin
9195 -- return not Oeq (X, Y);
9196 -- end;
9198 else
9199 declare
9200 Local_Subp : Node_Id;
9201 begin
9202 Local_Subp := Make_Eq_Body (Tag_Typ, Name_Op_Eq);
9203 Set_Declarations (Decl, New_List (Local_Subp));
9204 Target := Defining_Entity (Local_Subp);
9205 end;
9206 end if;
9208 Append_To (Stmts,
9209 Make_Simple_Return_Statement (Loc,
9210 Expression =>
9211 Make_Op_Not (Loc,
9212 Make_Function_Call (Loc,
9213 Name => New_Occurrence_Of (Target, Loc),
9214 Parameter_Associations => New_List (
9215 Make_Identifier (Loc, Chars (Left_Op)),
9216 Make_Identifier (Loc, Chars (Right_Op)))))));
9218 Set_Handled_Statement_Sequence
9219 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
9220 return Decl;
9221 end Make_Neq_Body;
9223 -------------------------------
9224 -- Make_Null_Procedure_Specs --
9225 -------------------------------
9227 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
9228 Decl_List : constant List_Id := New_List;
9229 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9230 Formal : Entity_Id;
9231 Formal_List : List_Id;
9232 New_Param_Spec : Node_Id;
9233 Parent_Subp : Entity_Id;
9234 Prim_Elmt : Elmt_Id;
9235 Subp : Entity_Id;
9237 begin
9238 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9239 while Present (Prim_Elmt) loop
9240 Subp := Node (Prim_Elmt);
9242 -- If a null procedure inherited from an interface has not been
9243 -- overridden, then we build a null procedure declaration to
9244 -- override the inherited procedure.
9246 Parent_Subp := Alias (Subp);
9248 if Present (Parent_Subp)
9249 and then Is_Null_Interface_Primitive (Parent_Subp)
9250 then
9251 Formal_List := No_List;
9252 Formal := First_Formal (Subp);
9254 if Present (Formal) then
9255 Formal_List := New_List;
9257 while Present (Formal) loop
9259 -- Copy the parameter spec including default expressions
9261 New_Param_Spec :=
9262 New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
9264 -- Generate a new defining identifier for the new formal.
9265 -- required because New_Copy_Tree does not duplicate
9266 -- semantic fields (except itypes).
9268 Set_Defining_Identifier (New_Param_Spec,
9269 Make_Defining_Identifier (Sloc (Formal),
9270 Chars => Chars (Formal)));
9272 -- For controlling arguments we must change their
9273 -- parameter type to reference the tagged type (instead
9274 -- of the interface type)
9276 if Is_Controlling_Formal (Formal) then
9277 if Nkind (Parameter_Type (Parent (Formal))) = N_Identifier
9278 then
9279 Set_Parameter_Type (New_Param_Spec,
9280 New_Occurrence_Of (Tag_Typ, Loc));
9282 else pragma Assert
9283 (Nkind (Parameter_Type (Parent (Formal))) =
9284 N_Access_Definition);
9285 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
9286 New_Occurrence_Of (Tag_Typ, Loc));
9287 end if;
9288 end if;
9290 Append (New_Param_Spec, Formal_List);
9292 Next_Formal (Formal);
9293 end loop;
9294 end if;
9296 Append_To (Decl_List,
9297 Make_Subprogram_Declaration (Loc,
9298 Make_Procedure_Specification (Loc,
9299 Defining_Unit_Name =>
9300 Make_Defining_Identifier (Loc, Chars (Subp)),
9301 Parameter_Specifications => Formal_List,
9302 Null_Present => True)));
9303 end if;
9305 Next_Elmt (Prim_Elmt);
9306 end loop;
9308 return Decl_List;
9309 end Make_Null_Procedure_Specs;
9311 -------------------------------------
9312 -- Make_Predefined_Primitive_Specs --
9313 -------------------------------------
9315 procedure Make_Predefined_Primitive_Specs
9316 (Tag_Typ : Entity_Id;
9317 Predef_List : out List_Id;
9318 Renamed_Eq : out Entity_Id)
9320 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
9321 -- Returns true if Prim is a renaming of an unresolved predefined
9322 -- equality operation.
9324 -------------------------------
9325 -- Is_Predefined_Eq_Renaming --
9326 -------------------------------
9328 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
9329 begin
9330 return Chars (Prim) /= Name_Op_Eq
9331 and then Present (Alias (Prim))
9332 and then Comes_From_Source (Prim)
9333 and then Is_Intrinsic_Subprogram (Alias (Prim))
9334 and then Chars (Alias (Prim)) = Name_Op_Eq;
9335 end Is_Predefined_Eq_Renaming;
9337 -- Local variables
9339 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9340 Res : constant List_Id := New_List;
9341 Eq_Name : Name_Id := Name_Op_Eq;
9342 Eq_Needed : Boolean;
9343 Eq_Spec : Node_Id;
9344 Prim : Elmt_Id;
9346 Has_Predef_Eq_Renaming : Boolean := False;
9347 -- Set to True if Tag_Typ has a primitive that renames the predefined
9348 -- equality operator. Used to implement (RM 8-5-4(8)).
9350 -- Start of processing for Make_Predefined_Primitive_Specs
9352 begin
9353 Renamed_Eq := Empty;
9355 -- Spec of _Size
9357 Append_To (Res, Predef_Spec_Or_Body (Loc,
9358 Tag_Typ => Tag_Typ,
9359 Name => Name_uSize,
9360 Profile => New_List (
9361 Make_Parameter_Specification (Loc,
9362 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9363 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9365 Ret_Type => Standard_Long_Long_Integer));
9367 -- Specs for dispatching stream attributes
9369 declare
9370 Stream_Op_TSS_Names :
9371 constant array (Integer range <>) of TSS_Name_Type :=
9372 (TSS_Stream_Read,
9373 TSS_Stream_Write,
9374 TSS_Stream_Input,
9375 TSS_Stream_Output);
9377 begin
9378 for Op in Stream_Op_TSS_Names'Range loop
9379 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
9380 Append_To (Res,
9381 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
9382 Stream_Op_TSS_Names (Op)));
9383 end if;
9384 end loop;
9385 end;
9387 -- Spec of "=" is expanded if the type is not limited and if a user
9388 -- defined "=" was not already declared for the non-full view of a
9389 -- private extension
9391 if not Is_Limited_Type (Tag_Typ) then
9392 Eq_Needed := True;
9393 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9394 while Present (Prim) loop
9396 -- If a primitive is encountered that renames the predefined
9397 -- equality operator before reaching any explicit equality
9398 -- primitive, then we still need to create a predefined equality
9399 -- function, because calls to it can occur via the renaming. A
9400 -- new name is created for the equality to avoid conflicting with
9401 -- any user-defined equality. (Note that this doesn't account for
9402 -- renamings of equality nested within subpackages???)
9404 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9405 Has_Predef_Eq_Renaming := True;
9406 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
9408 -- User-defined equality
9410 elsif Is_User_Defined_Equality (Node (Prim)) then
9411 if No (Alias (Node (Prim)))
9412 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
9413 N_Subprogram_Renaming_Declaration
9414 then
9415 Eq_Needed := False;
9416 exit;
9418 -- If the parent is not an interface type and has an abstract
9419 -- equality function, the inherited equality is abstract as
9420 -- well, and no body can be created for it.
9422 elsif not Is_Interface (Etype (Tag_Typ))
9423 and then Present (Alias (Node (Prim)))
9424 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
9425 then
9426 Eq_Needed := False;
9427 exit;
9429 -- If the type has an equality function corresponding with
9430 -- a primitive defined in an interface type, the inherited
9431 -- equality is abstract as well, and no body can be created
9432 -- for it.
9434 elsif Present (Alias (Node (Prim)))
9435 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
9436 and then
9437 Is_Interface
9438 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
9439 then
9440 Eq_Needed := False;
9441 exit;
9442 end if;
9443 end if;
9445 Next_Elmt (Prim);
9446 end loop;
9448 -- If a renaming of predefined equality was found but there was no
9449 -- user-defined equality (so Eq_Needed is still true), then set the
9450 -- name back to Name_Op_Eq. But in the case where a user-defined
9451 -- equality was located after such a renaming, then the predefined
9452 -- equality function is still needed, so Eq_Needed must be set back
9453 -- to True.
9455 if Eq_Name /= Name_Op_Eq then
9456 if Eq_Needed then
9457 Eq_Name := Name_Op_Eq;
9458 else
9459 Eq_Needed := True;
9460 end if;
9461 end if;
9463 if Eq_Needed then
9464 Eq_Spec := Predef_Spec_Or_Body (Loc,
9465 Tag_Typ => Tag_Typ,
9466 Name => Eq_Name,
9467 Profile => New_List (
9468 Make_Parameter_Specification (Loc,
9469 Defining_Identifier =>
9470 Make_Defining_Identifier (Loc, Name_X),
9471 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9473 Make_Parameter_Specification (Loc,
9474 Defining_Identifier =>
9475 Make_Defining_Identifier (Loc, Name_Y),
9476 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9477 Ret_Type => Standard_Boolean);
9478 Append_To (Res, Eq_Spec);
9480 if Has_Predef_Eq_Renaming then
9481 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
9483 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9484 while Present (Prim) loop
9486 -- Any renamings of equality that appeared before an
9487 -- overriding equality must be updated to refer to the
9488 -- entity for the predefined equality, otherwise calls via
9489 -- the renaming would get incorrectly resolved to call the
9490 -- user-defined equality function.
9492 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9493 Set_Alias (Node (Prim), Renamed_Eq);
9495 -- Exit upon encountering a user-defined equality
9497 elsif Chars (Node (Prim)) = Name_Op_Eq
9498 and then No (Alias (Node (Prim)))
9499 then
9500 exit;
9501 end if;
9503 Next_Elmt (Prim);
9504 end loop;
9505 end if;
9506 end if;
9508 -- Spec for dispatching assignment
9510 Append_To (Res, Predef_Spec_Or_Body (Loc,
9511 Tag_Typ => Tag_Typ,
9512 Name => Name_uAssign,
9513 Profile => New_List (
9514 Make_Parameter_Specification (Loc,
9515 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9516 Out_Present => True,
9517 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9519 Make_Parameter_Specification (Loc,
9520 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
9521 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)))));
9522 end if;
9524 -- Ada 2005: Generate declarations for the following primitive
9525 -- operations for limited interfaces and synchronized types that
9526 -- implement a limited interface.
9528 -- Disp_Asynchronous_Select
9529 -- Disp_Conditional_Select
9530 -- Disp_Get_Prim_Op_Kind
9531 -- Disp_Get_Task_Id
9532 -- Disp_Requeue
9533 -- Disp_Timed_Select
9535 -- Disable the generation of these bodies if No_Dispatching_Calls,
9536 -- Ravenscar or ZFP is active.
9538 if Ada_Version >= Ada_2005
9539 and then not Restriction_Active (No_Dispatching_Calls)
9540 and then not Restriction_Active (No_Select_Statements)
9541 and then RTE_Available (RE_Select_Specific_Data)
9542 then
9543 -- These primitives are defined abstract in interface types
9545 if Is_Interface (Tag_Typ)
9546 and then Is_Limited_Record (Tag_Typ)
9547 then
9548 Append_To (Res,
9549 Make_Abstract_Subprogram_Declaration (Loc,
9550 Specification =>
9551 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9553 Append_To (Res,
9554 Make_Abstract_Subprogram_Declaration (Loc,
9555 Specification =>
9556 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9558 Append_To (Res,
9559 Make_Abstract_Subprogram_Declaration (Loc,
9560 Specification =>
9561 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9563 Append_To (Res,
9564 Make_Abstract_Subprogram_Declaration (Loc,
9565 Specification =>
9566 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9568 Append_To (Res,
9569 Make_Abstract_Subprogram_Declaration (Loc,
9570 Specification =>
9571 Make_Disp_Requeue_Spec (Tag_Typ)));
9573 Append_To (Res,
9574 Make_Abstract_Subprogram_Declaration (Loc,
9575 Specification =>
9576 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9578 -- If ancestor is an interface type, declare non-abstract primitives
9579 -- to override the abstract primitives of the interface type.
9581 -- In VM targets we define these primitives in all root tagged types
9582 -- that are not interface types. Done because in VM targets we don't
9583 -- have secondary dispatch tables and any derivation of Tag_Typ may
9584 -- cover limited interfaces (which always have these primitives since
9585 -- they may be ancestors of synchronized interface types).
9587 elsif (not Is_Interface (Tag_Typ)
9588 and then Is_Interface (Etype (Tag_Typ))
9589 and then Is_Limited_Record (Etype (Tag_Typ)))
9590 or else
9591 (Is_Concurrent_Record_Type (Tag_Typ)
9592 and then Has_Interfaces (Tag_Typ))
9593 or else
9594 (not Tagged_Type_Expansion
9595 and then not Is_Interface (Tag_Typ)
9596 and then Tag_Typ = Root_Type (Tag_Typ))
9597 then
9598 Append_To (Res,
9599 Make_Subprogram_Declaration (Loc,
9600 Specification =>
9601 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9603 Append_To (Res,
9604 Make_Subprogram_Declaration (Loc,
9605 Specification =>
9606 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9608 Append_To (Res,
9609 Make_Subprogram_Declaration (Loc,
9610 Specification =>
9611 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9613 Append_To (Res,
9614 Make_Subprogram_Declaration (Loc,
9615 Specification =>
9616 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9618 Append_To (Res,
9619 Make_Subprogram_Declaration (Loc,
9620 Specification =>
9621 Make_Disp_Requeue_Spec (Tag_Typ)));
9623 Append_To (Res,
9624 Make_Subprogram_Declaration (Loc,
9625 Specification =>
9626 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9627 end if;
9628 end if;
9630 -- All tagged types receive their own Deep_Adjust and Deep_Finalize
9631 -- regardless of whether they are controlled or may contain controlled
9632 -- components.
9634 -- Do not generate the routines if finalization is disabled
9636 if Restriction_Active (No_Finalization) then
9637 null;
9639 -- Finalization is not available for CIL value types
9641 elsif Is_Value_Type (Tag_Typ) then
9642 null;
9644 else
9645 if not Is_Limited_Type (Tag_Typ) then
9646 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
9647 end if;
9649 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
9650 end if;
9652 Predef_List := Res;
9653 end Make_Predefined_Primitive_Specs;
9655 ---------------------------------
9656 -- Needs_Simple_Initialization --
9657 ---------------------------------
9659 function Needs_Simple_Initialization
9660 (T : Entity_Id;
9661 Consider_IS : Boolean := True) return Boolean
9663 Consider_IS_NS : constant Boolean :=
9664 Normalize_Scalars or (Initialize_Scalars and Consider_IS);
9666 begin
9667 -- Never need initialization if it is suppressed
9669 if Initialization_Suppressed (T) then
9670 return False;
9671 end if;
9673 -- Check for private type, in which case test applies to the underlying
9674 -- type of the private type.
9676 if Is_Private_Type (T) then
9677 declare
9678 RT : constant Entity_Id := Underlying_Type (T);
9679 begin
9680 if Present (RT) then
9681 return Needs_Simple_Initialization (RT);
9682 else
9683 return False;
9684 end if;
9685 end;
9687 -- Scalar type with Default_Value aspect requires initialization
9689 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
9690 return True;
9692 -- Cases needing simple initialization are access types, and, if pragma
9693 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
9694 -- types.
9696 elsif Is_Access_Type (T)
9697 or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
9698 then
9699 return True;
9701 -- If Initialize/Normalize_Scalars is in effect, string objects also
9702 -- need initialization, unless they are created in the course of
9703 -- expanding an aggregate (since in the latter case they will be
9704 -- filled with appropriate initializing values before they are used).
9706 elsif Consider_IS_NS
9707 and then Is_Standard_String_Type (T)
9708 and then
9709 (not Is_Itype (T)
9710 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
9711 then
9712 return True;
9714 else
9715 return False;
9716 end if;
9717 end Needs_Simple_Initialization;
9719 ----------------------
9720 -- Predef_Deep_Spec --
9721 ----------------------
9723 function Predef_Deep_Spec
9724 (Loc : Source_Ptr;
9725 Tag_Typ : Entity_Id;
9726 Name : TSS_Name_Type;
9727 For_Body : Boolean := False) return Node_Id
9729 Formals : List_Id;
9731 begin
9732 -- V : in out Tag_Typ
9734 Formals := New_List (
9735 Make_Parameter_Specification (Loc,
9736 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
9737 In_Present => True,
9738 Out_Present => True,
9739 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)));
9741 -- F : Boolean := True
9743 if Name = TSS_Deep_Adjust
9744 or else Name = TSS_Deep_Finalize
9745 then
9746 Append_To (Formals,
9747 Make_Parameter_Specification (Loc,
9748 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
9749 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
9750 Expression => New_Occurrence_Of (Standard_True, Loc)));
9751 end if;
9753 return
9754 Predef_Spec_Or_Body (Loc,
9755 Name => Make_TSS_Name (Tag_Typ, Name),
9756 Tag_Typ => Tag_Typ,
9757 Profile => Formals,
9758 For_Body => For_Body);
9760 exception
9761 when RE_Not_Available =>
9762 return Empty;
9763 end Predef_Deep_Spec;
9765 -------------------------
9766 -- Predef_Spec_Or_Body --
9767 -------------------------
9769 function Predef_Spec_Or_Body
9770 (Loc : Source_Ptr;
9771 Tag_Typ : Entity_Id;
9772 Name : Name_Id;
9773 Profile : List_Id;
9774 Ret_Type : Entity_Id := Empty;
9775 For_Body : Boolean := False) return Node_Id
9777 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
9778 Spec : Node_Id;
9780 begin
9781 Set_Is_Public (Id, Is_Public (Tag_Typ));
9783 -- The internal flag is set to mark these declarations because they have
9784 -- specific properties. First, they are primitives even if they are not
9785 -- defined in the type scope (the freezing point is not necessarily in
9786 -- the same scope). Second, the predefined equality can be overridden by
9787 -- a user-defined equality, no body will be generated in this case.
9789 Set_Is_Internal (Id);
9791 if not Debug_Generated_Code then
9792 Set_Debug_Info_Off (Id);
9793 end if;
9795 if No (Ret_Type) then
9796 Spec :=
9797 Make_Procedure_Specification (Loc,
9798 Defining_Unit_Name => Id,
9799 Parameter_Specifications => Profile);
9800 else
9801 Spec :=
9802 Make_Function_Specification (Loc,
9803 Defining_Unit_Name => Id,
9804 Parameter_Specifications => Profile,
9805 Result_Definition => New_Occurrence_Of (Ret_Type, Loc));
9806 end if;
9808 if Is_Interface (Tag_Typ) then
9809 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9811 -- If body case, return empty subprogram body. Note that this is ill-
9812 -- formed, because there is not even a null statement, and certainly not
9813 -- a return in the function case. The caller is expected to do surgery
9814 -- on the body to add the appropriate stuff.
9816 elsif For_Body then
9817 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
9819 -- For the case of an Input attribute predefined for an abstract type,
9820 -- generate an abstract specification. This will never be called, but we
9821 -- need the slot allocated in the dispatching table so that attributes
9822 -- typ'Class'Input and typ'Class'Output will work properly.
9824 elsif Is_TSS (Name, TSS_Stream_Input)
9825 and then Is_Abstract_Type (Tag_Typ)
9826 then
9827 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9829 -- Normal spec case, where we return a subprogram declaration
9831 else
9832 return Make_Subprogram_Declaration (Loc, Spec);
9833 end if;
9834 end Predef_Spec_Or_Body;
9836 -----------------------------
9837 -- Predef_Stream_Attr_Spec --
9838 -----------------------------
9840 function Predef_Stream_Attr_Spec
9841 (Loc : Source_Ptr;
9842 Tag_Typ : Entity_Id;
9843 Name : TSS_Name_Type;
9844 For_Body : Boolean := False) return Node_Id
9846 Ret_Type : Entity_Id;
9848 begin
9849 if Name = TSS_Stream_Input then
9850 Ret_Type := Tag_Typ;
9851 else
9852 Ret_Type := Empty;
9853 end if;
9855 return
9856 Predef_Spec_Or_Body
9857 (Loc,
9858 Name => Make_TSS_Name (Tag_Typ, Name),
9859 Tag_Typ => Tag_Typ,
9860 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
9861 Ret_Type => Ret_Type,
9862 For_Body => For_Body);
9863 end Predef_Stream_Attr_Spec;
9865 ---------------------------------
9866 -- Predefined_Primitive_Bodies --
9867 ---------------------------------
9869 function Predefined_Primitive_Bodies
9870 (Tag_Typ : Entity_Id;
9871 Renamed_Eq : Entity_Id) return List_Id
9873 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9874 Res : constant List_Id := New_List;
9875 Decl : Node_Id;
9876 Prim : Elmt_Id;
9877 Eq_Needed : Boolean;
9878 Eq_Name : Name_Id;
9879 Ent : Entity_Id;
9881 pragma Warnings (Off, Ent);
9883 begin
9884 pragma Assert (not Is_Interface (Tag_Typ));
9886 -- See if we have a predefined "=" operator
9888 if Present (Renamed_Eq) then
9889 Eq_Needed := True;
9890 Eq_Name := Chars (Renamed_Eq);
9892 -- If the parent is an interface type then it has defined all the
9893 -- predefined primitives abstract and we need to check if the type
9894 -- has some user defined "=" function which matches the profile of
9895 -- the Ada predefined equality operator to avoid generating it.
9897 elsif Is_Interface (Etype (Tag_Typ)) then
9898 Eq_Needed := True;
9899 Eq_Name := Name_Op_Eq;
9901 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9902 while Present (Prim) loop
9903 if Chars (Node (Prim)) = Name_Op_Eq
9904 and then not Is_Internal (Node (Prim))
9905 and then Present (First_Entity (Node (Prim)))
9907 -- The predefined equality primitive must have exactly two
9908 -- formals whose type is this tagged type
9910 and then Present (Last_Entity (Node (Prim)))
9911 and then Next_Entity (First_Entity (Node (Prim)))
9912 = Last_Entity (Node (Prim))
9913 and then Etype (First_Entity (Node (Prim))) = Tag_Typ
9914 and then Etype (Last_Entity (Node (Prim))) = Tag_Typ
9915 then
9916 Eq_Needed := False;
9917 Eq_Name := No_Name;
9918 exit;
9919 end if;
9921 Next_Elmt (Prim);
9922 end loop;
9924 else
9925 Eq_Needed := False;
9926 Eq_Name := No_Name;
9928 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9929 while Present (Prim) loop
9930 if Chars (Node (Prim)) = Name_Op_Eq
9931 and then Is_Internal (Node (Prim))
9932 then
9933 Eq_Needed := True;
9934 Eq_Name := Name_Op_Eq;
9935 exit;
9936 end if;
9938 Next_Elmt (Prim);
9939 end loop;
9940 end if;
9942 -- Body of _Size
9944 Decl := Predef_Spec_Or_Body (Loc,
9945 Tag_Typ => Tag_Typ,
9946 Name => Name_uSize,
9947 Profile => New_List (
9948 Make_Parameter_Specification (Loc,
9949 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9950 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9952 Ret_Type => Standard_Long_Long_Integer,
9953 For_Body => True);
9955 Set_Handled_Statement_Sequence (Decl,
9956 Make_Handled_Sequence_Of_Statements (Loc, New_List (
9957 Make_Simple_Return_Statement (Loc,
9958 Expression =>
9959 Make_Attribute_Reference (Loc,
9960 Prefix => Make_Identifier (Loc, Name_X),
9961 Attribute_Name => Name_Size)))));
9963 Append_To (Res, Decl);
9965 -- Bodies for Dispatching stream IO routines. We need these only for
9966 -- non-limited types (in the limited case there is no dispatching).
9967 -- We also skip them if dispatching or finalization are not available.
9969 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
9970 and then No (TSS (Tag_Typ, TSS_Stream_Read))
9971 then
9972 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
9973 Append_To (Res, Decl);
9974 end if;
9976 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
9977 and then No (TSS (Tag_Typ, TSS_Stream_Write))
9978 then
9979 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
9980 Append_To (Res, Decl);
9981 end if;
9983 -- Skip body of _Input for the abstract case, since the corresponding
9984 -- spec is abstract (see Predef_Spec_Or_Body).
9986 if not Is_Abstract_Type (Tag_Typ)
9987 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
9988 and then No (TSS (Tag_Typ, TSS_Stream_Input))
9989 then
9990 Build_Record_Or_Elementary_Input_Function
9991 (Loc, Tag_Typ, Decl, Ent);
9992 Append_To (Res, Decl);
9993 end if;
9995 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
9996 and then No (TSS (Tag_Typ, TSS_Stream_Output))
9997 then
9998 Build_Record_Or_Elementary_Output_Procedure (Loc, Tag_Typ, Decl, Ent);
9999 Append_To (Res, Decl);
10000 end if;
10002 -- Ada 2005: Generate bodies for the following primitive operations for
10003 -- limited interfaces and synchronized types that implement a limited
10004 -- interface.
10006 -- disp_asynchronous_select
10007 -- disp_conditional_select
10008 -- disp_get_prim_op_kind
10009 -- disp_get_task_id
10010 -- disp_timed_select
10012 -- The interface versions will have null bodies
10014 -- Disable the generation of these bodies if No_Dispatching_Calls,
10015 -- Ravenscar or ZFP is active.
10017 -- In VM targets we define these primitives in all root tagged types
10018 -- that are not interface types. Done because in VM targets we don't
10019 -- have secondary dispatch tables and any derivation of Tag_Typ may
10020 -- cover limited interfaces (which always have these primitives since
10021 -- they may be ancestors of synchronized interface types).
10023 if Ada_Version >= Ada_2005
10024 and then not Is_Interface (Tag_Typ)
10025 and then
10026 ((Is_Interface (Etype (Tag_Typ))
10027 and then Is_Limited_Record (Etype (Tag_Typ)))
10028 or else
10029 (Is_Concurrent_Record_Type (Tag_Typ)
10030 and then Has_Interfaces (Tag_Typ))
10031 or else
10032 (not Tagged_Type_Expansion
10033 and then Tag_Typ = Root_Type (Tag_Typ)))
10034 and then not Restriction_Active (No_Dispatching_Calls)
10035 and then not Restriction_Active (No_Select_Statements)
10036 and then RTE_Available (RE_Select_Specific_Data)
10037 then
10038 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
10039 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
10040 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
10041 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
10042 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
10043 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
10044 end if;
10046 if not Is_Limited_Type (Tag_Typ) and then not Is_Interface (Tag_Typ) then
10048 -- Body for equality
10050 if Eq_Needed then
10051 Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
10052 Append_To (Res, Decl);
10053 end if;
10055 -- Body for inequality (if required)
10057 Decl := Make_Neq_Body (Tag_Typ);
10059 if Present (Decl) then
10060 Append_To (Res, Decl);
10061 end if;
10063 -- Body for dispatching assignment
10065 Decl :=
10066 Predef_Spec_Or_Body (Loc,
10067 Tag_Typ => Tag_Typ,
10068 Name => Name_uAssign,
10069 Profile => New_List (
10070 Make_Parameter_Specification (Loc,
10071 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10072 Out_Present => True,
10073 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10075 Make_Parameter_Specification (Loc,
10076 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
10077 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10078 For_Body => True);
10080 Set_Handled_Statement_Sequence (Decl,
10081 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10082 Make_Assignment_Statement (Loc,
10083 Name => Make_Identifier (Loc, Name_X),
10084 Expression => Make_Identifier (Loc, Name_Y)))));
10086 Append_To (Res, Decl);
10087 end if;
10089 -- Generate empty bodies of routines Deep_Adjust and Deep_Finalize for
10090 -- tagged types which do not contain controlled components.
10092 -- Do not generate the routines if finalization is disabled
10094 if Restriction_Active (No_Finalization) then
10095 null;
10097 elsif not Has_Controlled_Component (Tag_Typ) then
10098 if not Is_Limited_Type (Tag_Typ) then
10099 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
10101 if Is_Controlled (Tag_Typ) then
10102 Set_Handled_Statement_Sequence (Decl,
10103 Make_Handled_Sequence_Of_Statements (Loc,
10104 Statements => New_List (
10105 Make_Adjust_Call (
10106 Obj_Ref => Make_Identifier (Loc, Name_V),
10107 Typ => Tag_Typ))));
10109 else
10110 Set_Handled_Statement_Sequence (Decl,
10111 Make_Handled_Sequence_Of_Statements (Loc,
10112 Statements => New_List (
10113 Make_Null_Statement (Loc))));
10114 end if;
10116 Append_To (Res, Decl);
10117 end if;
10119 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
10121 if Is_Controlled (Tag_Typ) then
10122 Set_Handled_Statement_Sequence (Decl,
10123 Make_Handled_Sequence_Of_Statements (Loc,
10124 Statements => New_List (
10125 Make_Final_Call
10126 (Obj_Ref => Make_Identifier (Loc, Name_V),
10127 Typ => Tag_Typ))));
10129 else
10130 Set_Handled_Statement_Sequence (Decl,
10131 Make_Handled_Sequence_Of_Statements (Loc,
10132 Statements => New_List (Make_Null_Statement (Loc))));
10133 end if;
10135 Append_To (Res, Decl);
10136 end if;
10138 return Res;
10139 end Predefined_Primitive_Bodies;
10141 ---------------------------------
10142 -- Predefined_Primitive_Freeze --
10143 ---------------------------------
10145 function Predefined_Primitive_Freeze
10146 (Tag_Typ : Entity_Id) return List_Id
10148 Res : constant List_Id := New_List;
10149 Prim : Elmt_Id;
10150 Frnodes : List_Id;
10152 begin
10153 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10154 while Present (Prim) loop
10155 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
10156 Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
10158 if Present (Frnodes) then
10159 Append_List_To (Res, Frnodes);
10160 end if;
10161 end if;
10163 Next_Elmt (Prim);
10164 end loop;
10166 return Res;
10167 end Predefined_Primitive_Freeze;
10169 -------------------------
10170 -- Stream_Operation_OK --
10171 -------------------------
10173 function Stream_Operation_OK
10174 (Typ : Entity_Id;
10175 Operation : TSS_Name_Type) return Boolean
10177 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
10179 begin
10180 -- Special case of a limited type extension: a default implementation
10181 -- of the stream attributes Read or Write exists if that attribute
10182 -- has been specified or is available for an ancestor type; a default
10183 -- implementation of the attribute Output (resp. Input) exists if the
10184 -- attribute has been specified or Write (resp. Read) is available for
10185 -- an ancestor type. The last condition only applies under Ada 2005.
10187 if Is_Limited_Type (Typ) and then Is_Tagged_Type (Typ) then
10188 if Operation = TSS_Stream_Read then
10189 Has_Predefined_Or_Specified_Stream_Attribute :=
10190 Has_Specified_Stream_Read (Typ);
10192 elsif Operation = TSS_Stream_Write then
10193 Has_Predefined_Or_Specified_Stream_Attribute :=
10194 Has_Specified_Stream_Write (Typ);
10196 elsif Operation = TSS_Stream_Input then
10197 Has_Predefined_Or_Specified_Stream_Attribute :=
10198 Has_Specified_Stream_Input (Typ)
10199 or else
10200 (Ada_Version >= Ada_2005
10201 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
10203 elsif Operation = TSS_Stream_Output then
10204 Has_Predefined_Or_Specified_Stream_Attribute :=
10205 Has_Specified_Stream_Output (Typ)
10206 or else
10207 (Ada_Version >= Ada_2005
10208 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
10209 end if;
10211 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
10213 if not Has_Predefined_Or_Specified_Stream_Attribute
10214 and then Is_Derived_Type (Typ)
10215 and then (Operation = TSS_Stream_Read
10216 or else Operation = TSS_Stream_Write)
10217 then
10218 Has_Predefined_Or_Specified_Stream_Attribute :=
10219 Present
10220 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
10221 end if;
10222 end if;
10224 -- If the type is not limited, or else is limited but the attribute is
10225 -- explicitly specified or is predefined for the type, then return True,
10226 -- unless other conditions prevail, such as restrictions prohibiting
10227 -- streams or dispatching operations. We also return True for limited
10228 -- interfaces, because they may be extended by nonlimited types and
10229 -- permit inheritance in this case (addresses cases where an abstract
10230 -- extension doesn't get 'Input declared, as per comments below, but
10231 -- 'Class'Input must still be allowed). Note that attempts to apply
10232 -- stream attributes to a limited interface or its class-wide type
10233 -- (or limited extensions thereof) will still get properly rejected
10234 -- by Check_Stream_Attribute.
10236 -- We exclude the Input operation from being a predefined subprogram in
10237 -- the case where the associated type is an abstract extension, because
10238 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
10239 -- we don't want an abstract version created because types derived from
10240 -- the abstract type may not even have Input available (for example if
10241 -- derived from a private view of the abstract type that doesn't have
10242 -- a visible Input), but a VM such as .NET or the Java VM can treat the
10243 -- operation as inherited anyway, and we don't want an abstract function
10244 -- to be (implicitly) inherited in that case because it can lead to a VM
10245 -- exception.
10247 -- Do not generate stream routines for type Finalization_Master because
10248 -- a master may never appear in types and therefore cannot be read or
10249 -- written.
10251 return
10252 (not Is_Limited_Type (Typ)
10253 or else Is_Interface (Typ)
10254 or else Has_Predefined_Or_Specified_Stream_Attribute)
10255 and then
10256 (Operation /= TSS_Stream_Input
10257 or else not Is_Abstract_Type (Typ)
10258 or else not Is_Derived_Type (Typ))
10259 and then not Has_Unknown_Discriminants (Typ)
10260 and then not
10261 (Is_Interface (Typ)
10262 and then
10263 (Is_Task_Interface (Typ)
10264 or else Is_Protected_Interface (Typ)
10265 or else Is_Synchronized_Interface (Typ)))
10266 and then not Restriction_Active (No_Streams)
10267 and then not Restriction_Active (No_Dispatch)
10268 and then not No_Run_Time_Mode
10269 and then RTE_Available (RE_Tag)
10270 and then No (Type_Without_Stream_Operation (Typ))
10271 and then RTE_Available (RE_Root_Stream_Type)
10272 and then not Is_RTE (Typ, RE_Finalization_Master);
10273 end Stream_Operation_OK;
10275 end Exp_Ch3;