* g++.dg/template/using30.C: Move ...
[official-gcc.git] / gcc / ada / exp_ch3.adb
blobf2f42d4d9fdbbab207bc5939a09d074000da9637
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 Aspects; use Aspects;
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Aggr; use Exp_Aggr;
32 with Exp_Atag; use Exp_Atag;
33 with Exp_Ch4; use Exp_Ch4;
34 with Exp_Ch6; use Exp_Ch6;
35 with Exp_Ch7; use Exp_Ch7;
36 with Exp_Ch9; use Exp_Ch9;
37 with Exp_Ch11; use Exp_Ch11;
38 with Exp_Dbug; use Exp_Dbug;
39 with Exp_Disp; use Exp_Disp;
40 with Exp_Dist; use Exp_Dist;
41 with Exp_Smem; use Exp_Smem;
42 with Exp_Strm; use Exp_Strm;
43 with Exp_Tss; use Exp_Tss;
44 with Exp_Util; use Exp_Util;
45 with Freeze; use Freeze;
46 with Namet; use Namet;
47 with Nlists; use Nlists;
48 with Nmake; use Nmake;
49 with Opt; use Opt;
50 with Restrict; use Restrict;
51 with Rident; use Rident;
52 with Rtsfind; use Rtsfind;
53 with Sem; use Sem;
54 with Sem_Aux; use Sem_Aux;
55 with Sem_Attr; use Sem_Attr;
56 with Sem_Cat; use Sem_Cat;
57 with Sem_Ch3; use Sem_Ch3;
58 with Sem_Ch6; use Sem_Ch6;
59 with Sem_Ch8; use Sem_Ch8;
60 with Sem_Ch13; use Sem_Ch13;
61 with Sem_Disp; use Sem_Disp;
62 with Sem_Eval; use Sem_Eval;
63 with Sem_Mech; use Sem_Mech;
64 with Sem_Res; use Sem_Res;
65 with Sem_SCIL; use Sem_SCIL;
66 with Sem_Type; use Sem_Type;
67 with Sem_Util; use Sem_Util;
68 with Sinfo; use Sinfo;
69 with Stand; use Stand;
70 with Snames; use Snames;
71 with Targparm; use Targparm;
72 with Tbuild; use Tbuild;
73 with Ttypes; use Ttypes;
74 with Validsw; use Validsw;
76 package body Exp_Ch3 is
78 -----------------------
79 -- Local Subprograms --
80 -----------------------
82 procedure Adjust_Discriminants (Rtype : Entity_Id);
83 -- This is used when freezing a record type. It attempts to construct
84 -- more restrictive subtypes for discriminants so that the max size of
85 -- the record can be calculated more accurately. See the body of this
86 -- procedure for details.
88 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
89 -- Build initialization procedure for given array type. Nod is a node
90 -- used for attachment of any actions required in its construction.
91 -- It also supplies the source location used for the procedure.
93 function Build_Array_Invariant_Proc
94 (A_Type : Entity_Id;
95 Nod : Node_Id) return Node_Id;
96 -- If the component of type of array type has invariants, build procedure
97 -- that checks invariant on all components of the array. Ada 2012 specifies
98 -- that an invariant on some type T must be applied to in-out parameters
99 -- and return values that include a part of type T. If the array type has
100 -- an otherwise specified invariant, the component check procedure is
101 -- called from within the user-specified invariant. Otherwise this becomes
102 -- the invariant procedure for the array type.
104 function Build_Record_Invariant_Proc
105 (R_Type : Entity_Id;
106 Nod : Node_Id) return Node_Id;
107 -- Ditto for record types.
109 function Build_Discriminant_Formals
110 (Rec_Id : Entity_Id;
111 Use_Dl : Boolean) return List_Id;
112 -- This function uses the discriminants of a type to build a list of
113 -- formal parameters, used in Build_Init_Procedure among other places.
114 -- If the flag Use_Dl is set, the list is built using the already
115 -- defined discriminals of the type, as is the case for concurrent
116 -- types with discriminants. Otherwise new identifiers are created,
117 -- with the source names of the discriminants.
119 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
120 -- This function builds a static aggregate that can serve as the initial
121 -- value for an array type whose bounds are static, and whose component
122 -- type is a composite type that has a static equivalent aggregate.
123 -- The equivalent array aggregate is used both for object initialization
124 -- and for component initialization, when used in the following function.
126 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
127 -- This function builds a static aggregate that can serve as the initial
128 -- value for a record type whose components are scalar and initialized
129 -- with compile-time values, or arrays with similar initialization or
130 -- defaults. When possible, initialization of an object of the type can
131 -- be achieved by using a copy of the aggregate as an initial value, thus
132 -- removing the implicit call that would otherwise constitute elaboration
133 -- code.
135 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id);
136 -- Build record initialization procedure. N is the type declaration
137 -- node, and Rec_Ent is the corresponding entity for the record type.
139 procedure Build_Slice_Assignment (Typ : Entity_Id);
140 -- Build assignment procedure for one-dimensional arrays of controlled
141 -- types. Other array and slice assignments are expanded in-line, but
142 -- the code expansion for controlled components (when control actions
143 -- are active) can lead to very large blocks that GCC3 handles poorly.
145 procedure Build_Untagged_Equality (Typ : Entity_Id);
146 -- AI05-0123: Equality on untagged records composes. This procedure
147 -- builds the equality routine for an untagged record that has components
148 -- of a record type that has user-defined primitive equality operations.
149 -- The resulting operation is a TSS subprogram.
151 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
152 -- Create An Equality function for the untagged variant record Typ and
153 -- attach it to the TSS list
155 procedure Check_Stream_Attributes (Typ : Entity_Id);
156 -- Check that if a limited extension has a parent with user-defined stream
157 -- attributes, and does not itself have user-defined stream-attributes,
158 -- then any limited component of the extension also has the corresponding
159 -- user-defined stream attributes.
161 procedure Clean_Task_Names
162 (Typ : Entity_Id;
163 Proc_Id : Entity_Id);
164 -- If an initialization procedure includes calls to generate names
165 -- for task subcomponents, indicate that secondary stack cleanup is
166 -- needed after an initialization. Typ is the component type, and Proc_Id
167 -- the initialization procedure for the enclosing composite type.
169 procedure Expand_Freeze_Array_Type (N : Node_Id);
170 -- Freeze an array type. Deals with building the initialization procedure,
171 -- creating the packed array type for a packed array and also with the
172 -- creation of the controlling procedures for the controlled case. The
173 -- argument N is the N_Freeze_Entity node for the type.
175 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id);
176 -- Freeze a class-wide type. Build routine Finalize_Address for the purpose
177 -- of finalizing controlled derivations from the class-wide's root type.
179 procedure Expand_Freeze_Enumeration_Type (N : Node_Id);
180 -- Freeze enumeration type with non-standard representation. Builds the
181 -- array and function needed to convert between enumeration pos and
182 -- enumeration representation values. N is the N_Freeze_Entity node
183 -- for the type.
185 procedure Expand_Freeze_Record_Type (N : Node_Id);
186 -- Freeze record type. Builds all necessary discriminant checking
187 -- and other ancillary functions, and builds dispatch tables where
188 -- needed. The argument N is the N_Freeze_Entity node. This processing
189 -- applies only to E_Record_Type entities, not to class wide types,
190 -- record subtypes, or private types.
192 procedure Expand_Tagged_Root (T : Entity_Id);
193 -- Add a field _Tag at the beginning of the record. This field carries
194 -- the value of the access to the Dispatch table. This procedure is only
195 -- called on root type, the _Tag field being inherited by the descendants.
197 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
198 -- Treat user-defined stream operations as renaming_as_body if the
199 -- subprogram they rename is not frozen when the type is frozen.
201 procedure Insert_Component_Invariant_Checks
202 (N : Node_Id;
203 Typ : Entity_Id;
204 Proc : Node_Id);
205 -- If a composite type has invariants and also has components with defined
206 -- invariants. the component invariant procedure is inserted into the user-
207 -- defined invariant procedure and added to the checks to be performed.
209 procedure Initialization_Warning (E : Entity_Id);
210 -- If static elaboration of the package is requested, indicate
211 -- when a type does meet the conditions for static initialization. If
212 -- E is a type, it has components that have no static initialization.
213 -- if E is an entity, its initial expression is not compile-time known.
215 function Init_Formals (Typ : Entity_Id) return List_Id;
216 -- This function builds the list of formals for an initialization routine.
217 -- The first formal is always _Init with the given type. For task value
218 -- record types and types containing tasks, three additional formals are
219 -- added:
221 -- _Master : Master_Id
222 -- _Chain : in out Activation_Chain
223 -- _Task_Name : String
225 -- The caller must append additional entries for discriminants if required.
227 function In_Runtime (E : Entity_Id) return Boolean;
228 -- Check if E is defined in the RTL (in a child of Ada or System). Used
229 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
231 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean;
232 -- Returns true if Prim is a user defined equality function
234 function Make_Eq_Body
235 (Typ : Entity_Id;
236 Eq_Name : Name_Id) return Node_Id;
237 -- Build the body of a primitive equality operation for a tagged record
238 -- type, or in Ada 2012 for any record type that has components with a
239 -- user-defined equality. Factored out of Predefined_Primitive_Bodies.
241 function Make_Eq_Case
242 (E : Entity_Id;
243 CL : Node_Id;
244 Discrs : Elist_Id := New_Elmt_List) return List_Id;
245 -- Building block for variant record equality. Defined to share the code
246 -- between the tagged and untagged case. Given a Component_List node CL,
247 -- it generates an 'if' followed by a 'case' statement that compares all
248 -- components of local temporaries named X and Y (that are declared as
249 -- formals at some upper level). E provides the Sloc to be used for the
250 -- generated code.
252 -- IF E is an unchecked_union, Discrs is the list of formals created for
253 -- the inferred discriminants of one operand. These formals are used in
254 -- the generated case statements for each variant of the unchecked union.
256 function Make_Eq_If
257 (E : Entity_Id;
258 L : List_Id) return Node_Id;
259 -- Building block for variant record equality. Defined to share the code
260 -- between the tagged and untagged case. Given the list of components
261 -- (or discriminants) L, it generates a return statement that compares all
262 -- components of local temporaries named X and Y (that are declared as
263 -- formals at some upper level). E provides the Sloc to be used for the
264 -- generated code.
266 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id;
267 -- Search for a renaming of the inequality dispatching primitive of
268 -- this tagged type. If found then build and return the corresponding
269 -- rename-as-body inequality subprogram; otherwise return Empty.
271 procedure Make_Predefined_Primitive_Specs
272 (Tag_Typ : Entity_Id;
273 Predef_List : out List_Id;
274 Renamed_Eq : out Entity_Id);
275 -- Create a list with the specs of the predefined primitive operations.
276 -- For tagged types that are interfaces all these primitives are defined
277 -- abstract.
279 -- The following entries are present for all tagged types, and provide
280 -- the results of the corresponding attribute applied to the object.
281 -- Dispatching is required in general, since the result of the attribute
282 -- will vary with the actual object subtype.
284 -- _size provides result of 'Size attribute
285 -- typSR provides result of 'Read attribute
286 -- typSW provides result of 'Write attribute
287 -- typSI provides result of 'Input attribute
288 -- typSO provides result of 'Output attribute
290 -- The following entries are additionally present for non-limited tagged
291 -- types, and implement additional dispatching operations for predefined
292 -- operations:
294 -- _equality implements "=" operator
295 -- _assign implements assignment operation
296 -- typDF implements deep finalization
297 -- typDA implements deep adjust
299 -- The latter two are empty procedures unless the type contains some
300 -- controlled components that require finalization actions (the deep
301 -- in the name refers to the fact that the action applies to components).
303 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
304 -- returns the value Empty, or else the defining unit name for the
305 -- predefined equality function in the case where the type has a primitive
306 -- operation that is a renaming of predefined equality (but only if there
307 -- is also an overriding user-defined equality function). The returned
308 -- Renamed_Eq will be passed to the corresponding parameter of
309 -- Predefined_Primitive_Bodies.
311 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
312 -- returns True if there are representation clauses for type T that are not
313 -- inherited. If the result is false, the init_proc and the discriminant
314 -- checking functions of the parent can be reused by a derived type.
316 procedure Make_Controlling_Function_Wrappers
317 (Tag_Typ : Entity_Id;
318 Decl_List : out List_Id;
319 Body_List : out List_Id);
320 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
321 -- associated with inherited functions with controlling results which
322 -- are not overridden. The body of each wrapper function consists solely
323 -- of a return statement whose expression is an extension aggregate
324 -- invoking the inherited subprogram's parent subprogram and extended
325 -- with a null association list.
327 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id;
328 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
329 -- null procedures inherited from an interface type that have not been
330 -- overridden. Only one null procedure will be created for a given set of
331 -- inherited null procedures with homographic profiles.
333 function Predef_Spec_Or_Body
334 (Loc : Source_Ptr;
335 Tag_Typ : Entity_Id;
336 Name : Name_Id;
337 Profile : List_Id;
338 Ret_Type : Entity_Id := Empty;
339 For_Body : Boolean := False) return Node_Id;
340 -- This function generates the appropriate expansion for a predefined
341 -- primitive operation specified by its name, parameter profile and
342 -- return type (Empty means this is a procedure). If For_Body is false,
343 -- then the returned node is a subprogram declaration. If For_Body is
344 -- true, then the returned node is a empty subprogram body containing
345 -- no declarations and no statements.
347 function Predef_Stream_Attr_Spec
348 (Loc : Source_Ptr;
349 Tag_Typ : Entity_Id;
350 Name : TSS_Name_Type;
351 For_Body : Boolean := False) return Node_Id;
352 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
353 -- input and output attribute whose specs are constructed in Exp_Strm.
355 function Predef_Deep_Spec
356 (Loc : Source_Ptr;
357 Tag_Typ : Entity_Id;
358 Name : TSS_Name_Type;
359 For_Body : Boolean := False) return Node_Id;
360 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
361 -- and _deep_finalize
363 function Predefined_Primitive_Bodies
364 (Tag_Typ : Entity_Id;
365 Renamed_Eq : Entity_Id) return List_Id;
366 -- Create the bodies of the predefined primitives that are described in
367 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
368 -- the defining unit name of the type's predefined equality as returned
369 -- by Make_Predefined_Primitive_Specs.
371 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
372 -- Freeze entities of all predefined primitive operations. This is needed
373 -- because the bodies of these operations do not normally do any freezing.
375 function Stream_Operation_OK
376 (Typ : Entity_Id;
377 Operation : TSS_Name_Type) return Boolean;
378 -- Check whether the named stream operation must be emitted for a given
379 -- type. The rules for inheritance of stream attributes by type extensions
380 -- are enforced by this function. Furthermore, various restrictions prevent
381 -- the generation of these operations, as a useful optimization or for
382 -- certification purposes and to save unnecessary generated code.
384 --------------------------
385 -- Adjust_Discriminants --
386 --------------------------
388 -- This procedure attempts to define subtypes for discriminants that are
389 -- more restrictive than those declared. Such a replacement is possible if
390 -- we can demonstrate that values outside the restricted range would cause
391 -- constraint errors in any case. The advantage of restricting the
392 -- discriminant types in this way is that the maximum size of the variant
393 -- record can be calculated more conservatively.
395 -- An example of a situation in which we can perform this type of
396 -- restriction is the following:
398 -- subtype B is range 1 .. 10;
399 -- type Q is array (B range <>) of Integer;
401 -- type V (N : Natural) is record
402 -- C : Q (1 .. N);
403 -- end record;
405 -- In this situation, we can restrict the upper bound of N to 10, since
406 -- any larger value would cause a constraint error in any case.
408 -- There are many situations in which such restriction is possible, but
409 -- for now, we just look for cases like the above, where the component
410 -- in question is a one dimensional array whose upper bound is one of
411 -- the record discriminants. Also the component must not be part of
412 -- any variant part, since then the component does not always exist.
414 procedure Adjust_Discriminants (Rtype : Entity_Id) is
415 Loc : constant Source_Ptr := Sloc (Rtype);
416 Comp : Entity_Id;
417 Ctyp : Entity_Id;
418 Ityp : Entity_Id;
419 Lo : Node_Id;
420 Hi : Node_Id;
421 P : Node_Id;
422 Loval : Uint;
423 Discr : Entity_Id;
424 Dtyp : Entity_Id;
425 Dhi : Node_Id;
426 Dhiv : Uint;
427 Ahi : Node_Id;
428 Ahiv : Uint;
429 Tnn : Entity_Id;
431 begin
432 Comp := First_Component (Rtype);
433 while Present (Comp) loop
435 -- If our parent is a variant, quit, we do not look at components
436 -- that are in variant parts, because they may not always exist.
438 P := Parent (Comp); -- component declaration
439 P := Parent (P); -- component list
441 exit when Nkind (Parent (P)) = N_Variant;
443 -- We are looking for a one dimensional array type
445 Ctyp := Etype (Comp);
447 if not Is_Array_Type (Ctyp) or else Number_Dimensions (Ctyp) > 1 then
448 goto Continue;
449 end if;
451 -- The lower bound must be constant, and the upper bound is a
452 -- discriminant (which is a discriminant of the current record).
454 Ityp := Etype (First_Index (Ctyp));
455 Lo := Type_Low_Bound (Ityp);
456 Hi := Type_High_Bound (Ityp);
458 if not Compile_Time_Known_Value (Lo)
459 or else Nkind (Hi) /= N_Identifier
460 or else No (Entity (Hi))
461 or else Ekind (Entity (Hi)) /= E_Discriminant
462 then
463 goto Continue;
464 end if;
466 -- We have an array with appropriate bounds
468 Loval := Expr_Value (Lo);
469 Discr := Entity (Hi);
470 Dtyp := Etype (Discr);
472 -- See if the discriminant has a known upper bound
474 Dhi := Type_High_Bound (Dtyp);
476 if not Compile_Time_Known_Value (Dhi) then
477 goto Continue;
478 end if;
480 Dhiv := Expr_Value (Dhi);
482 -- See if base type of component array has known upper bound
484 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
486 if not Compile_Time_Known_Value (Ahi) then
487 goto Continue;
488 end if;
490 Ahiv := Expr_Value (Ahi);
492 -- The condition for doing the restriction is that the high bound
493 -- of the discriminant is greater than the low bound of the array,
494 -- and is also greater than the high bound of the base type index.
496 if Dhiv > Loval and then Dhiv > Ahiv then
498 -- We can reset the upper bound of the discriminant type to
499 -- whichever is larger, the low bound of the component, or
500 -- the high bound of the base type array index.
502 -- We build a subtype that is declared as
504 -- subtype Tnn is discr_type range discr_type'First .. max;
506 -- And insert this declaration into the tree. The type of the
507 -- discriminant is then reset to this more restricted subtype.
509 Tnn := Make_Temporary (Loc, 'T');
511 Insert_Action (Declaration_Node (Rtype),
512 Make_Subtype_Declaration (Loc,
513 Defining_Identifier => Tnn,
514 Subtype_Indication =>
515 Make_Subtype_Indication (Loc,
516 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
517 Constraint =>
518 Make_Range_Constraint (Loc,
519 Range_Expression =>
520 Make_Range (Loc,
521 Low_Bound =>
522 Make_Attribute_Reference (Loc,
523 Attribute_Name => Name_First,
524 Prefix => New_Occurrence_Of (Dtyp, Loc)),
525 High_Bound =>
526 Make_Integer_Literal (Loc,
527 Intval => UI_Max (Loval, Ahiv)))))));
529 Set_Etype (Discr, Tnn);
530 end if;
532 <<Continue>>
533 Next_Component (Comp);
534 end loop;
535 end Adjust_Discriminants;
537 ---------------------------
538 -- Build_Array_Init_Proc --
539 ---------------------------
541 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
542 Comp_Type : constant Entity_Id := Component_Type (A_Type);
543 Body_Stmts : List_Id;
544 Has_Default_Init : Boolean;
545 Index_List : List_Id;
546 Loc : Source_Ptr;
547 Proc_Id : Entity_Id;
549 function Init_Component return List_Id;
550 -- Create one statement to initialize one array component, designated
551 -- by a full set of indexes.
553 function Init_One_Dimension (N : Int) return List_Id;
554 -- Create loop to initialize one dimension of the array. The single
555 -- statement in the loop body initializes the inner dimensions if any,
556 -- or else the single component. Note that this procedure is called
557 -- recursively, with N being the dimension to be initialized. A call
558 -- with N greater than the number of dimensions simply generates the
559 -- component initialization, terminating the recursion.
561 --------------------
562 -- Init_Component --
563 --------------------
565 function Init_Component return List_Id is
566 Comp : Node_Id;
568 begin
569 Comp :=
570 Make_Indexed_Component (Loc,
571 Prefix => Make_Identifier (Loc, Name_uInit),
572 Expressions => Index_List);
574 if Has_Default_Aspect (A_Type) then
575 Set_Assignment_OK (Comp);
576 return New_List (
577 Make_Assignment_Statement (Loc,
578 Name => Comp,
579 Expression =>
580 Convert_To (Comp_Type,
581 Default_Aspect_Component_Value (First_Subtype (A_Type)))));
583 elsif Needs_Simple_Initialization (Comp_Type) then
584 Set_Assignment_OK (Comp);
585 return New_List (
586 Make_Assignment_Statement (Loc,
587 Name => Comp,
588 Expression =>
589 Get_Simple_Init_Val
590 (Comp_Type, Nod, Component_Size (A_Type))));
592 else
593 Clean_Task_Names (Comp_Type, Proc_Id);
594 return
595 Build_Initialization_Call
596 (Loc, Comp, Comp_Type,
597 In_Init_Proc => True,
598 Enclos_Type => A_Type);
599 end if;
600 end Init_Component;
602 ------------------------
603 -- Init_One_Dimension --
604 ------------------------
606 function Init_One_Dimension (N : Int) return List_Id is
607 Index : Entity_Id;
609 begin
610 -- If the component does not need initializing, then there is nothing
611 -- to do here, so we return a null body. This occurs when generating
612 -- the dummy Init_Proc needed for Initialize_Scalars processing.
614 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
615 and then not Needs_Simple_Initialization (Comp_Type)
616 and then not Has_Task (Comp_Type)
617 and then not Has_Default_Aspect (A_Type)
618 then
619 return New_List (Make_Null_Statement (Loc));
621 -- If all dimensions dealt with, we simply initialize the component
623 elsif N > Number_Dimensions (A_Type) then
624 return Init_Component;
626 -- Here we generate the required loop
628 else
629 Index :=
630 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
632 Append (New_Occurrence_Of (Index, Loc), Index_List);
634 return New_List (
635 Make_Implicit_Loop_Statement (Nod,
636 Identifier => Empty,
637 Iteration_Scheme =>
638 Make_Iteration_Scheme (Loc,
639 Loop_Parameter_Specification =>
640 Make_Loop_Parameter_Specification (Loc,
641 Defining_Identifier => Index,
642 Discrete_Subtype_Definition =>
643 Make_Attribute_Reference (Loc,
644 Prefix =>
645 Make_Identifier (Loc, Name_uInit),
646 Attribute_Name => Name_Range,
647 Expressions => New_List (
648 Make_Integer_Literal (Loc, N))))),
649 Statements => Init_One_Dimension (N + 1)));
650 end if;
651 end Init_One_Dimension;
653 -- Start of processing for Build_Array_Init_Proc
655 begin
656 -- The init proc is created when analyzing the freeze node for the type,
657 -- but it properly belongs with the array type declaration. However, if
658 -- the freeze node is for a subtype of a type declared in another unit
659 -- it seems preferable to use the freeze node as the source location of
660 -- the init proc. In any case this is preferable for gcov usage, and
661 -- the Sloc is not otherwise used by the compiler.
663 if In_Open_Scopes (Scope (A_Type)) then
664 Loc := Sloc (A_Type);
665 else
666 Loc := Sloc (Nod);
667 end if;
669 -- Nothing to generate in the following cases:
671 -- 1. Initialization is suppressed for the type
672 -- 2. The type is a value type, in the CIL sense.
673 -- 3. The type has CIL/JVM convention.
674 -- 4. An initialization already exists for the base type
676 if Initialization_Suppressed (A_Type)
677 or else Is_Value_Type (Comp_Type)
678 or else Convention (A_Type) = Convention_CIL
679 or else Convention (A_Type) = Convention_Java
680 or else Present (Base_Init_Proc (A_Type))
681 then
682 return;
683 end if;
685 Index_List := New_List;
687 -- We need an initialization procedure if any of the following is true:
689 -- 1. The component type has an initialization procedure
690 -- 2. The component type needs simple initialization
691 -- 3. Tasks are present
692 -- 4. The type is marked as a public entity
693 -- 5. The array type has a Default_Component_Value aspect
695 -- The reason for the public entity test is to deal properly with the
696 -- Initialize_Scalars pragma. This pragma can be set in the client and
697 -- not in the declaring package, this means the client will make a call
698 -- to the initialization procedure (because one of conditions 1-3 must
699 -- apply in this case), and we must generate a procedure (even if it is
700 -- null) to satisfy the call in this case.
702 -- Exception: do not build an array init_proc for a type whose root
703 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
704 -- is no place to put the code, and in any case we handle initialization
705 -- of such types (in the Initialize_Scalars case, that's the only time
706 -- the issue arises) in a special manner anyway which does not need an
707 -- init_proc.
709 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
710 or else Needs_Simple_Initialization (Comp_Type)
711 or else Has_Task (Comp_Type)
712 or else Has_Default_Aspect (A_Type);
714 if Has_Default_Init
715 or else (not Restriction_Active (No_Initialize_Scalars)
716 and then Is_Public (A_Type)
717 and then not Is_Standard_String_Type (A_Type))
718 then
719 Proc_Id :=
720 Make_Defining_Identifier (Loc,
721 Chars => Make_Init_Proc_Name (A_Type));
723 -- If No_Default_Initialization restriction is active, then we don't
724 -- want to build an init_proc, but we need to mark that an init_proc
725 -- would be needed if this restriction was not active (so that we can
726 -- detect attempts to call it), so set a dummy init_proc in place.
727 -- This is only done though when actual default initialization is
728 -- needed (and not done when only Is_Public is True), since otherwise
729 -- objects such as arrays of scalars could be wrongly flagged as
730 -- violating the restriction.
732 if Restriction_Active (No_Default_Initialization) then
733 if Has_Default_Init then
734 Set_Init_Proc (A_Type, Proc_Id);
735 end if;
737 return;
738 end if;
740 Body_Stmts := Init_One_Dimension (1);
742 Discard_Node (
743 Make_Subprogram_Body (Loc,
744 Specification =>
745 Make_Procedure_Specification (Loc,
746 Defining_Unit_Name => Proc_Id,
747 Parameter_Specifications => Init_Formals (A_Type)),
748 Declarations => New_List,
749 Handled_Statement_Sequence =>
750 Make_Handled_Sequence_Of_Statements (Loc,
751 Statements => Body_Stmts)));
753 Set_Ekind (Proc_Id, E_Procedure);
754 Set_Is_Public (Proc_Id, Is_Public (A_Type));
755 Set_Is_Internal (Proc_Id);
756 Set_Has_Completion (Proc_Id);
758 if not Debug_Generated_Code then
759 Set_Debug_Info_Off (Proc_Id);
760 end if;
762 -- Set inlined unless controlled stuff or tasks around, in which
763 -- case we do not want to inline, because nested stuff may cause
764 -- difficulties in inter-unit inlining, and furthermore there is
765 -- in any case no point in inlining such complex init procs.
767 if not Has_Task (Proc_Id)
768 and then not Needs_Finalization (Proc_Id)
769 then
770 Set_Is_Inlined (Proc_Id);
771 end if;
773 -- Associate Init_Proc with type, and determine if the procedure
774 -- is null (happens because of the Initialize_Scalars pragma case,
775 -- where we have to generate a null procedure in case it is called
776 -- by a client with Initialize_Scalars set). Such procedures have
777 -- to be generated, but do not have to be called, so we mark them
778 -- as null to suppress the call.
780 Set_Init_Proc (A_Type, Proc_Id);
782 if List_Length (Body_Stmts) = 1
784 -- We must skip SCIL nodes because they may have been added to this
785 -- list by Insert_Actions.
787 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
788 then
789 Set_Is_Null_Init_Proc (Proc_Id);
791 else
792 -- Try to build a static aggregate to statically initialize
793 -- objects of the type. This can only be done for constrained
794 -- one-dimensional arrays with static bounds.
796 Set_Static_Initialization
797 (Proc_Id,
798 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
799 end if;
800 end if;
801 end Build_Array_Init_Proc;
803 --------------------------------
804 -- Build_Array_Invariant_Proc --
805 --------------------------------
807 function Build_Array_Invariant_Proc
808 (A_Type : Entity_Id;
809 Nod : Node_Id) return Node_Id
811 Loc : constant Source_Ptr := Sloc (Nod);
813 Object_Name : constant Name_Id := New_Internal_Name ('I');
814 -- Name for argument of invariant procedure
816 Object_Entity : constant Node_Id :=
817 Make_Defining_Identifier (Loc, Object_Name);
818 -- The procedure declaration entity for the argument
820 Body_Stmts : List_Id;
821 Index_List : List_Id;
822 Proc_Id : Entity_Id;
823 Proc_Body : Node_Id;
825 function Build_Component_Invariant_Call return Node_Id;
826 -- Create one statement to verify invariant on one array component,
827 -- designated by a full set of indexes.
829 function Check_One_Dimension (N : Int) return List_Id;
830 -- Create loop to check on one dimension of the array. The single
831 -- statement in the loop body checks the inner dimensions if any, or
832 -- else a single component. This procedure is called recursively, with
833 -- N being the dimension to be initialized. A call with N greater than
834 -- the number of dimensions generates the component initialization
835 -- and terminates the recursion.
837 ------------------------------------
838 -- Build_Component_Invariant_Call --
839 ------------------------------------
841 function Build_Component_Invariant_Call return Node_Id is
842 Comp : Node_Id;
843 begin
844 Comp :=
845 Make_Indexed_Component (Loc,
846 Prefix => New_Occurrence_Of (Object_Entity, Loc),
847 Expressions => Index_List);
848 return
849 Make_Procedure_Call_Statement (Loc,
850 Name =>
851 New_Occurrence_Of
852 (Invariant_Procedure (Component_Type (A_Type)), Loc),
853 Parameter_Associations => New_List (Comp));
854 end Build_Component_Invariant_Call;
856 -------------------------
857 -- Check_One_Dimension --
858 -------------------------
860 function Check_One_Dimension (N : Int) return List_Id is
861 Index : Entity_Id;
863 begin
864 -- If all dimensions dealt with, we simply check invariant of the
865 -- component.
867 if N > Number_Dimensions (A_Type) then
868 return New_List (Build_Component_Invariant_Call);
870 -- Else generate one loop and recurse
872 else
873 Index :=
874 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
876 Append (New_Occurrence_Of (Index, Loc), Index_List);
878 return New_List (
879 Make_Implicit_Loop_Statement (Nod,
880 Identifier => Empty,
881 Iteration_Scheme =>
882 Make_Iteration_Scheme (Loc,
883 Loop_Parameter_Specification =>
884 Make_Loop_Parameter_Specification (Loc,
885 Defining_Identifier => Index,
886 Discrete_Subtype_Definition =>
887 Make_Attribute_Reference (Loc,
888 Prefix =>
889 New_Occurrence_Of (Object_Entity, Loc),
890 Attribute_Name => Name_Range,
891 Expressions => New_List (
892 Make_Integer_Literal (Loc, N))))),
893 Statements => Check_One_Dimension (N + 1)));
894 end if;
895 end Check_One_Dimension;
897 -- Start of processing for Build_Array_Invariant_Proc
899 begin
900 Index_List := New_List;
902 Proc_Id :=
903 Make_Defining_Identifier (Loc,
904 Chars => New_External_Name (Chars (A_Type), "CInvariant"));
906 Body_Stmts := Check_One_Dimension (1);
908 Proc_Body :=
909 Make_Subprogram_Body (Loc,
910 Specification =>
911 Make_Procedure_Specification (Loc,
912 Defining_Unit_Name => Proc_Id,
913 Parameter_Specifications => New_List (
914 Make_Parameter_Specification (Loc,
915 Defining_Identifier => Object_Entity,
916 Parameter_Type => New_Occurrence_Of (A_Type, Loc)))),
918 Declarations => Empty_List,
919 Handled_Statement_Sequence =>
920 Make_Handled_Sequence_Of_Statements (Loc,
921 Statements => Body_Stmts));
923 Set_Ekind (Proc_Id, E_Procedure);
924 Set_Is_Public (Proc_Id, Is_Public (A_Type));
925 Set_Is_Internal (Proc_Id);
926 Set_Has_Completion (Proc_Id);
928 if not Debug_Generated_Code then
929 Set_Debug_Info_Off (Proc_Id);
930 end if;
932 return Proc_Body;
933 end Build_Array_Invariant_Proc;
935 --------------------------------
936 -- Build_Discr_Checking_Funcs --
937 --------------------------------
939 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
940 Rec_Id : Entity_Id;
941 Loc : Source_Ptr;
942 Enclosing_Func_Id : Entity_Id;
943 Sequence : Nat := 1;
944 Type_Def : Node_Id;
945 V : Node_Id;
947 function Build_Case_Statement
948 (Case_Id : Entity_Id;
949 Variant : Node_Id) return Node_Id;
950 -- Build a case statement containing only two alternatives. The first
951 -- alternative corresponds exactly to the discrete choices given on the
952 -- variant with contains the components that we are generating the
953 -- checks for. If the discriminant is one of these return False. The
954 -- second alternative is an OTHERS choice that will return True
955 -- indicating the discriminant did not match.
957 function Build_Dcheck_Function
958 (Case_Id : Entity_Id;
959 Variant : Node_Id) return Entity_Id;
960 -- Build the discriminant checking function for a given variant
962 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
963 -- Builds the discriminant checking function for each variant of the
964 -- given variant part of the record type.
966 --------------------------
967 -- Build_Case_Statement --
968 --------------------------
970 function Build_Case_Statement
971 (Case_Id : Entity_Id;
972 Variant : Node_Id) return Node_Id
974 Alt_List : constant List_Id := New_List;
975 Actuals_List : List_Id;
976 Case_Node : Node_Id;
977 Case_Alt_Node : Node_Id;
978 Choice : Node_Id;
979 Choice_List : List_Id;
980 D : Entity_Id;
981 Return_Node : Node_Id;
983 begin
984 Case_Node := New_Node (N_Case_Statement, Loc);
986 -- Replace the discriminant which controls the variant with the name
987 -- of the formal of the checking function.
989 Set_Expression (Case_Node, Make_Identifier (Loc, Chars (Case_Id)));
991 Choice := First (Discrete_Choices (Variant));
993 if Nkind (Choice) = N_Others_Choice then
994 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
995 else
996 Choice_List := New_Copy_List (Discrete_Choices (Variant));
997 end if;
999 if not Is_Empty_List (Choice_List) then
1000 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1001 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1003 -- In case this is a nested variant, we need to return the result
1004 -- of the discriminant checking function for the immediately
1005 -- enclosing variant.
1007 if Present (Enclosing_Func_Id) then
1008 Actuals_List := New_List;
1010 D := First_Discriminant (Rec_Id);
1011 while Present (D) loop
1012 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
1013 Next_Discriminant (D);
1014 end loop;
1016 Return_Node :=
1017 Make_Simple_Return_Statement (Loc,
1018 Expression =>
1019 Make_Function_Call (Loc,
1020 Name =>
1021 New_Occurrence_Of (Enclosing_Func_Id, Loc),
1022 Parameter_Associations =>
1023 Actuals_List));
1025 else
1026 Return_Node :=
1027 Make_Simple_Return_Statement (Loc,
1028 Expression =>
1029 New_Occurrence_Of (Standard_False, Loc));
1030 end if;
1032 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1033 Append (Case_Alt_Node, Alt_List);
1034 end if;
1036 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1037 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
1038 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1040 Return_Node :=
1041 Make_Simple_Return_Statement (Loc,
1042 Expression =>
1043 New_Occurrence_Of (Standard_True, Loc));
1045 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1046 Append (Case_Alt_Node, Alt_List);
1048 Set_Alternatives (Case_Node, Alt_List);
1049 return Case_Node;
1050 end Build_Case_Statement;
1052 ---------------------------
1053 -- Build_Dcheck_Function --
1054 ---------------------------
1056 function Build_Dcheck_Function
1057 (Case_Id : Entity_Id;
1058 Variant : Node_Id) return Entity_Id
1060 Body_Node : Node_Id;
1061 Func_Id : Entity_Id;
1062 Parameter_List : List_Id;
1063 Spec_Node : Node_Id;
1065 begin
1066 Body_Node := New_Node (N_Subprogram_Body, Loc);
1067 Sequence := Sequence + 1;
1069 Func_Id :=
1070 Make_Defining_Identifier (Loc,
1071 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
1072 Set_Is_Discriminant_Check_Function (Func_Id);
1074 Spec_Node := New_Node (N_Function_Specification, Loc);
1075 Set_Defining_Unit_Name (Spec_Node, Func_Id);
1077 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
1079 Set_Parameter_Specifications (Spec_Node, Parameter_List);
1080 Set_Result_Definition (Spec_Node,
1081 New_Occurrence_Of (Standard_Boolean, Loc));
1082 Set_Specification (Body_Node, Spec_Node);
1083 Set_Declarations (Body_Node, New_List);
1085 Set_Handled_Statement_Sequence (Body_Node,
1086 Make_Handled_Sequence_Of_Statements (Loc,
1087 Statements => New_List (
1088 Build_Case_Statement (Case_Id, Variant))));
1090 Set_Ekind (Func_Id, E_Function);
1091 Set_Mechanism (Func_Id, Default_Mechanism);
1092 Set_Is_Inlined (Func_Id, True);
1093 Set_Is_Pure (Func_Id, True);
1094 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
1095 Set_Is_Internal (Func_Id, True);
1097 if not Debug_Generated_Code then
1098 Set_Debug_Info_Off (Func_Id);
1099 end if;
1101 Analyze (Body_Node);
1103 Append_Freeze_Action (Rec_Id, Body_Node);
1104 Set_Dcheck_Function (Variant, Func_Id);
1105 return Func_Id;
1106 end Build_Dcheck_Function;
1108 ----------------------------
1109 -- Build_Dcheck_Functions --
1110 ----------------------------
1112 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1113 Component_List_Node : Node_Id;
1114 Decl : Entity_Id;
1115 Discr_Name : Entity_Id;
1116 Func_Id : Entity_Id;
1117 Variant : Node_Id;
1118 Saved_Enclosing_Func_Id : Entity_Id;
1120 begin
1121 -- Build the discriminant-checking function for each variant, and
1122 -- label all components of that variant with the function's name.
1123 -- We only Generate a discriminant-checking function when the
1124 -- variant is not empty, to prevent the creation of dead code.
1125 -- The exception to that is when Frontend_Layout_On_Target is set,
1126 -- because the variant record size function generated in package
1127 -- Layout needs to generate calls to all discriminant-checking
1128 -- functions, including those for empty variants.
1130 Discr_Name := Entity (Name (Variant_Part_Node));
1131 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1133 while Present (Variant) loop
1134 Component_List_Node := Component_List (Variant);
1136 if not Null_Present (Component_List_Node)
1137 or else Frontend_Layout_On_Target
1138 then
1139 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1140 Decl :=
1141 First_Non_Pragma (Component_Items (Component_List_Node));
1143 while Present (Decl) loop
1144 Set_Discriminant_Checking_Func
1145 (Defining_Identifier (Decl), Func_Id);
1147 Next_Non_Pragma (Decl);
1148 end loop;
1150 if Present (Variant_Part (Component_List_Node)) then
1151 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1152 Enclosing_Func_Id := Func_Id;
1153 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1154 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1155 end if;
1156 end if;
1158 Next_Non_Pragma (Variant);
1159 end loop;
1160 end Build_Dcheck_Functions;
1162 -- Start of processing for Build_Discr_Checking_Funcs
1164 begin
1165 -- Only build if not done already
1167 if not Discr_Check_Funcs_Built (N) then
1168 Type_Def := Type_Definition (N);
1170 if Nkind (Type_Def) = N_Record_Definition then
1171 if No (Component_List (Type_Def)) then -- null record.
1172 return;
1173 else
1174 V := Variant_Part (Component_List (Type_Def));
1175 end if;
1177 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1178 if No (Component_List (Record_Extension_Part (Type_Def))) then
1179 return;
1180 else
1181 V := Variant_Part
1182 (Component_List (Record_Extension_Part (Type_Def)));
1183 end if;
1184 end if;
1186 Rec_Id := Defining_Identifier (N);
1188 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1189 Loc := Sloc (N);
1190 Enclosing_Func_Id := Empty;
1191 Build_Dcheck_Functions (V);
1192 end if;
1194 Set_Discr_Check_Funcs_Built (N);
1195 end if;
1196 end Build_Discr_Checking_Funcs;
1198 --------------------------------
1199 -- Build_Discriminant_Formals --
1200 --------------------------------
1202 function Build_Discriminant_Formals
1203 (Rec_Id : Entity_Id;
1204 Use_Dl : Boolean) return List_Id
1206 Loc : Source_Ptr := Sloc (Rec_Id);
1207 Parameter_List : constant List_Id := New_List;
1208 D : Entity_Id;
1209 Formal : Entity_Id;
1210 Formal_Type : Entity_Id;
1211 Param_Spec_Node : Node_Id;
1213 begin
1214 if Has_Discriminants (Rec_Id) then
1215 D := First_Discriminant (Rec_Id);
1216 while Present (D) loop
1217 Loc := Sloc (D);
1219 if Use_Dl then
1220 Formal := Discriminal (D);
1221 Formal_Type := Etype (Formal);
1222 else
1223 Formal := Make_Defining_Identifier (Loc, Chars (D));
1224 Formal_Type := Etype (D);
1225 end if;
1227 Param_Spec_Node :=
1228 Make_Parameter_Specification (Loc,
1229 Defining_Identifier => Formal,
1230 Parameter_Type =>
1231 New_Occurrence_Of (Formal_Type, Loc));
1232 Append (Param_Spec_Node, Parameter_List);
1233 Next_Discriminant (D);
1234 end loop;
1235 end if;
1237 return Parameter_List;
1238 end Build_Discriminant_Formals;
1240 --------------------------------------
1241 -- Build_Equivalent_Array_Aggregate --
1242 --------------------------------------
1244 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1245 Loc : constant Source_Ptr := Sloc (T);
1246 Comp_Type : constant Entity_Id := Component_Type (T);
1247 Index_Type : constant Entity_Id := Etype (First_Index (T));
1248 Proc : constant Entity_Id := Base_Init_Proc (T);
1249 Lo, Hi : Node_Id;
1250 Aggr : Node_Id;
1251 Expr : Node_Id;
1253 begin
1254 if not Is_Constrained (T)
1255 or else Number_Dimensions (T) > 1
1256 or else No (Proc)
1257 then
1258 Initialization_Warning (T);
1259 return Empty;
1260 end if;
1262 Lo := Type_Low_Bound (Index_Type);
1263 Hi := Type_High_Bound (Index_Type);
1265 if not Compile_Time_Known_Value (Lo)
1266 or else not Compile_Time_Known_Value (Hi)
1267 then
1268 Initialization_Warning (T);
1269 return Empty;
1270 end if;
1272 if Is_Record_Type (Comp_Type)
1273 and then Present (Base_Init_Proc (Comp_Type))
1274 then
1275 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1277 if No (Expr) then
1278 Initialization_Warning (T);
1279 return Empty;
1280 end if;
1282 else
1283 Initialization_Warning (T);
1284 return Empty;
1285 end if;
1287 Aggr := Make_Aggregate (Loc, No_List, New_List);
1288 Set_Etype (Aggr, T);
1289 Set_Aggregate_Bounds (Aggr,
1290 Make_Range (Loc,
1291 Low_Bound => New_Copy (Lo),
1292 High_Bound => New_Copy (Hi)));
1293 Set_Parent (Aggr, Parent (Proc));
1295 Append_To (Component_Associations (Aggr),
1296 Make_Component_Association (Loc,
1297 Choices =>
1298 New_List (
1299 Make_Range (Loc,
1300 Low_Bound => New_Copy (Lo),
1301 High_Bound => New_Copy (Hi))),
1302 Expression => Expr));
1304 if Static_Array_Aggregate (Aggr) then
1305 return Aggr;
1306 else
1307 Initialization_Warning (T);
1308 return Empty;
1309 end if;
1310 end Build_Equivalent_Array_Aggregate;
1312 ---------------------------------------
1313 -- Build_Equivalent_Record_Aggregate --
1314 ---------------------------------------
1316 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1317 Agg : Node_Id;
1318 Comp : Entity_Id;
1319 Comp_Type : Entity_Id;
1321 -- Start of processing for Build_Equivalent_Record_Aggregate
1323 begin
1324 if not Is_Record_Type (T)
1325 or else Has_Discriminants (T)
1326 or else Is_Limited_Type (T)
1327 or else Has_Non_Standard_Rep (T)
1328 then
1329 Initialization_Warning (T);
1330 return Empty;
1331 end if;
1333 Comp := First_Component (T);
1335 -- A null record needs no warning
1337 if No (Comp) then
1338 return Empty;
1339 end if;
1341 while Present (Comp) loop
1343 -- Array components are acceptable if initialized by a positional
1344 -- aggregate with static components.
1346 if Is_Array_Type (Etype (Comp)) then
1347 Comp_Type := Component_Type (Etype (Comp));
1349 if Nkind (Parent (Comp)) /= N_Component_Declaration
1350 or else No (Expression (Parent (Comp)))
1351 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1352 then
1353 Initialization_Warning (T);
1354 return Empty;
1356 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1357 and then
1358 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1359 or else
1360 not Compile_Time_Known_Value (Type_High_Bound (Comp_Type)))
1361 then
1362 Initialization_Warning (T);
1363 return Empty;
1365 elsif
1366 not Static_Array_Aggregate (Expression (Parent (Comp)))
1367 then
1368 Initialization_Warning (T);
1369 return Empty;
1370 end if;
1372 elsif Is_Scalar_Type (Etype (Comp)) then
1373 Comp_Type := Etype (Comp);
1375 if Nkind (Parent (Comp)) /= N_Component_Declaration
1376 or else No (Expression (Parent (Comp)))
1377 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1378 or else not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1379 or else not
1380 Compile_Time_Known_Value (Type_High_Bound (Comp_Type))
1381 then
1382 Initialization_Warning (T);
1383 return Empty;
1384 end if;
1386 -- For now, other types are excluded
1388 else
1389 Initialization_Warning (T);
1390 return Empty;
1391 end if;
1393 Next_Component (Comp);
1394 end loop;
1396 -- All components have static initialization. Build positional aggregate
1397 -- from the given expressions or defaults.
1399 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1400 Set_Parent (Agg, Parent (T));
1402 Comp := First_Component (T);
1403 while Present (Comp) loop
1404 Append
1405 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1406 Next_Component (Comp);
1407 end loop;
1409 Analyze_And_Resolve (Agg, T);
1410 return Agg;
1411 end Build_Equivalent_Record_Aggregate;
1413 -------------------------------
1414 -- Build_Initialization_Call --
1415 -------------------------------
1417 -- References to a discriminant inside the record type declaration can
1418 -- appear either in the subtype_indication to constrain a record or an
1419 -- array, or as part of a larger expression given for the initial value
1420 -- of a component. In both of these cases N appears in the record
1421 -- initialization procedure and needs to be replaced by the formal
1422 -- parameter of the initialization procedure which corresponds to that
1423 -- discriminant.
1425 -- In the example below, references to discriminants D1 and D2 in proc_1
1426 -- are replaced by references to formals with the same name
1427 -- (discriminals)
1429 -- A similar replacement is done for calls to any record initialization
1430 -- procedure for any components that are themselves of a record type.
1432 -- type R (D1, D2 : Integer) is record
1433 -- X : Integer := F * D1;
1434 -- Y : Integer := F * D2;
1435 -- end record;
1437 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1438 -- begin
1439 -- Out_2.D1 := D1;
1440 -- Out_2.D2 := D2;
1441 -- Out_2.X := F * D1;
1442 -- Out_2.Y := F * D2;
1443 -- end;
1445 function Build_Initialization_Call
1446 (Loc : Source_Ptr;
1447 Id_Ref : Node_Id;
1448 Typ : Entity_Id;
1449 In_Init_Proc : Boolean := False;
1450 Enclos_Type : Entity_Id := Empty;
1451 Discr_Map : Elist_Id := New_Elmt_List;
1452 With_Default_Init : Boolean := False;
1453 Constructor_Ref : Node_Id := Empty) return List_Id
1455 Res : constant List_Id := New_List;
1456 Arg : Node_Id;
1457 Args : List_Id;
1458 Decls : List_Id;
1459 Decl : Node_Id;
1460 Discr : Entity_Id;
1461 First_Arg : Node_Id;
1462 Full_Init_Type : Entity_Id;
1463 Full_Type : Entity_Id;
1464 Init_Type : Entity_Id;
1465 Proc : Entity_Id;
1467 begin
1468 pragma Assert (Constructor_Ref = Empty
1469 or else Is_CPP_Constructor_Call (Constructor_Ref));
1471 if No (Constructor_Ref) then
1472 Proc := Base_Init_Proc (Typ);
1473 else
1474 Proc := Base_Init_Proc (Typ, Entity (Name (Constructor_Ref)));
1475 end if;
1477 pragma Assert (Present (Proc));
1478 Init_Type := Etype (First_Formal (Proc));
1479 Full_Init_Type := Underlying_Type (Init_Type);
1481 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1482 -- is active (in which case we make the call anyway, since in the
1483 -- actual compiled client it may be non null).
1484 -- Also nothing to do for value types.
1486 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1487 or else Is_Value_Type (Typ)
1488 or else
1489 (Is_Array_Type (Typ) and then Is_Value_Type (Component_Type (Typ)))
1490 then
1491 return Empty_List;
1492 end if;
1494 Full_Type := Typ;
1496 -- Use the [underlying] full view when dealing with a private type. This
1497 -- may require several steps depending on derivations.
1499 loop
1500 if Is_Private_Type (Full_Type) then
1501 if Present (Full_View (Full_Type)) then
1502 Full_Type := Full_View (Full_Type);
1504 elsif Present (Underlying_Full_View (Full_Type)) then
1505 Full_Type := Underlying_Full_View (Full_Type);
1507 -- When a private type acts as a generic actual and lacks a full
1508 -- view, use the base type.
1510 elsif Is_Generic_Actual_Type (Full_Type) then
1511 Full_Type := Base_Type (Full_Type);
1513 -- The loop has recovered the [underlying] full view, stop the
1514 -- traversal.
1516 else
1517 exit;
1518 end if;
1520 -- The type is not private, nothing to do
1522 else
1523 exit;
1524 end if;
1525 end loop;
1527 -- If Typ is derived, the procedure is the initialization procedure for
1528 -- the root type. Wrap the argument in an conversion to make it type
1529 -- honest. Actually it isn't quite type honest, because there can be
1530 -- conflicts of views in the private type case. That is why we set
1531 -- Conversion_OK in the conversion node.
1533 if (Is_Record_Type (Typ)
1534 or else Is_Array_Type (Typ)
1535 or else Is_Private_Type (Typ))
1536 and then Init_Type /= Base_Type (Typ)
1537 then
1538 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1539 Set_Etype (First_Arg, Init_Type);
1541 else
1542 First_Arg := Id_Ref;
1543 end if;
1545 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1547 -- In the tasks case, add _Master as the value of the _Master parameter
1548 -- and _Chain as the value of the _Chain parameter. At the outer level,
1549 -- these will be variables holding the corresponding values obtained
1550 -- from GNARL. At inner levels, they will be the parameters passed down
1551 -- through the outer routines.
1553 if Has_Task (Full_Type) then
1554 if Restriction_Active (No_Task_Hierarchy) then
1555 Append_To (Args,
1556 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
1557 else
1558 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1559 end if;
1561 -- Add _Chain (not done for sequential elaboration policy, see
1562 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
1564 if Partition_Elaboration_Policy /= 'S' then
1565 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1566 end if;
1568 -- Ada 2005 (AI-287): In case of default initialized components
1569 -- with tasks, we generate a null string actual parameter.
1570 -- This is just a workaround that must be improved later???
1572 if With_Default_Init then
1573 Append_To (Args,
1574 Make_String_Literal (Loc,
1575 Strval => ""));
1577 else
1578 Decls :=
1579 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1580 Decl := Last (Decls);
1582 Append_To (Args,
1583 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1584 Append_List (Decls, Res);
1585 end if;
1587 else
1588 Decls := No_List;
1589 Decl := Empty;
1590 end if;
1592 -- Add discriminant values if discriminants are present
1594 if Has_Discriminants (Full_Init_Type) then
1595 Discr := First_Discriminant (Full_Init_Type);
1597 while Present (Discr) loop
1599 -- If this is a discriminated concurrent type, the init_proc
1600 -- for the corresponding record is being called. Use that type
1601 -- directly to find the discriminant value, to handle properly
1602 -- intervening renamed discriminants.
1604 declare
1605 T : Entity_Id := Full_Type;
1607 begin
1608 if Is_Protected_Type (T) then
1609 T := Corresponding_Record_Type (T);
1610 end if;
1612 Arg :=
1613 Get_Discriminant_Value (
1614 Discr,
1616 Discriminant_Constraint (Full_Type));
1617 end;
1619 -- If the target has access discriminants, and is constrained by
1620 -- an access to the enclosing construct, i.e. a current instance,
1621 -- replace the reference to the type by a reference to the object.
1623 if Nkind (Arg) = N_Attribute_Reference
1624 and then Is_Access_Type (Etype (Arg))
1625 and then Is_Entity_Name (Prefix (Arg))
1626 and then Is_Type (Entity (Prefix (Arg)))
1627 then
1628 Arg :=
1629 Make_Attribute_Reference (Loc,
1630 Prefix => New_Copy (Prefix (Id_Ref)),
1631 Attribute_Name => Name_Unrestricted_Access);
1633 elsif In_Init_Proc then
1635 -- Replace any possible references to the discriminant in the
1636 -- call to the record initialization procedure with references
1637 -- to the appropriate formal parameter.
1639 if Nkind (Arg) = N_Identifier
1640 and then Ekind (Entity (Arg)) = E_Discriminant
1641 then
1642 Arg := New_Occurrence_Of (Discriminal (Entity (Arg)), Loc);
1644 -- Otherwise make a copy of the default expression. Note that
1645 -- we use the current Sloc for this, because we do not want the
1646 -- call to appear to be at the declaration point. Within the
1647 -- expression, replace discriminants with their discriminals.
1649 else
1650 Arg :=
1651 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1652 end if;
1654 else
1655 if Is_Constrained (Full_Type) then
1656 Arg := Duplicate_Subexpr_No_Checks (Arg);
1657 else
1658 -- The constraints come from the discriminant default exps,
1659 -- they must be reevaluated, so we use New_Copy_Tree but we
1660 -- ensure the proper Sloc (for any embedded calls).
1662 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1663 end if;
1664 end if;
1666 -- Ada 2005 (AI-287): In case of default initialized components,
1667 -- if the component is constrained with a discriminant of the
1668 -- enclosing type, we need to generate the corresponding selected
1669 -- component node to access the discriminant value. In other cases
1670 -- this is not required, either because we are inside the init
1671 -- proc and we use the corresponding formal, or else because the
1672 -- component is constrained by an expression.
1674 if With_Default_Init
1675 and then Nkind (Id_Ref) = N_Selected_Component
1676 and then Nkind (Arg) = N_Identifier
1677 and then Ekind (Entity (Arg)) = E_Discriminant
1678 then
1679 Append_To (Args,
1680 Make_Selected_Component (Loc,
1681 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1682 Selector_Name => Arg));
1683 else
1684 Append_To (Args, Arg);
1685 end if;
1687 Next_Discriminant (Discr);
1688 end loop;
1689 end if;
1691 -- If this is a call to initialize the parent component of a derived
1692 -- tagged type, indicate that the tag should not be set in the parent.
1694 if Is_Tagged_Type (Full_Init_Type)
1695 and then not Is_CPP_Class (Full_Init_Type)
1696 and then Nkind (Id_Ref) = N_Selected_Component
1697 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1698 then
1699 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1701 elsif Present (Constructor_Ref) then
1702 Append_List_To (Args,
1703 New_Copy_List (Parameter_Associations (Constructor_Ref)));
1704 end if;
1706 Append_To (Res,
1707 Make_Procedure_Call_Statement (Loc,
1708 Name => New_Occurrence_Of (Proc, Loc),
1709 Parameter_Associations => Args));
1711 if Needs_Finalization (Typ)
1712 and then Nkind (Id_Ref) = N_Selected_Component
1713 then
1714 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1715 Append_To (Res,
1716 Make_Init_Call
1717 (Obj_Ref => New_Copy_Tree (First_Arg),
1718 Typ => Typ));
1719 end if;
1720 end if;
1722 return Res;
1724 exception
1725 when RE_Not_Available =>
1726 return Empty_List;
1727 end Build_Initialization_Call;
1729 ----------------------------
1730 -- Build_Record_Init_Proc --
1731 ----------------------------
1733 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id) is
1734 Decls : constant List_Id := New_List;
1735 Discr_Map : constant Elist_Id := New_Elmt_List;
1736 Loc : constant Source_Ptr := Sloc (Rec_Ent);
1737 Counter : Int := 0;
1738 Proc_Id : Entity_Id;
1739 Rec_Type : Entity_Id;
1740 Set_Tag : Entity_Id := Empty;
1742 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1743 -- Build an assignment statement which assigns the default expression
1744 -- to its corresponding record component if defined. The left hand side
1745 -- of the assignment is marked Assignment_OK so that initialization of
1746 -- limited private records works correctly. This routine may also build
1747 -- an adjustment call if the component is controlled.
1749 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1750 -- If the record has discriminants, add assignment statements to
1751 -- Statement_List to initialize the discriminant values from the
1752 -- arguments of the initialization procedure.
1754 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1755 -- Build a list representing a sequence of statements which initialize
1756 -- components of the given component list. This may involve building
1757 -- case statements for the variant parts. Append any locally declared
1758 -- objects on list Decls.
1760 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1761 -- Given an untagged type-derivation that declares discriminants, e.g.
1763 -- type R (R1, R2 : Integer) is record ... end record;
1764 -- type D (D1 : Integer) is new R (1, D1);
1766 -- we make the _init_proc of D be
1768 -- procedure _init_proc (X : D; D1 : Integer) is
1769 -- begin
1770 -- _init_proc (R (X), 1, D1);
1771 -- end _init_proc;
1773 -- This function builds the call statement in this _init_proc.
1775 procedure Build_CPP_Init_Procedure;
1776 -- Build the tree corresponding to the procedure specification and body
1777 -- of the IC procedure that initializes the C++ part of the dispatch
1778 -- table of an Ada tagged type that is a derivation of a CPP type.
1779 -- Install it as the CPP_Init TSS.
1781 procedure Build_Init_Procedure;
1782 -- Build the tree corresponding to the procedure specification and body
1783 -- of the initialization procedure and install it as the _init TSS.
1785 procedure Build_Offset_To_Top_Functions;
1786 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1787 -- and body of Offset_To_Top, a function used in conjuction with types
1788 -- having secondary dispatch tables.
1790 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1791 -- Add range checks to components of discriminated records. S is a
1792 -- subtype indication of a record component. Check_List is a list
1793 -- to which the check actions are appended.
1795 function Component_Needs_Simple_Initialization
1796 (T : Entity_Id) return Boolean;
1797 -- Determine if a component needs simple initialization, given its type
1798 -- T. This routine is the same as Needs_Simple_Initialization except for
1799 -- components of type Tag and Interface_Tag. These two access types do
1800 -- not require initialization since they are explicitly initialized by
1801 -- other means.
1803 function Parent_Subtype_Renaming_Discrims return Boolean;
1804 -- Returns True for base types N that rename discriminants, else False
1806 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1807 -- Determine whether a record initialization procedure needs to be
1808 -- generated for the given record type.
1810 ----------------------
1811 -- Build_Assignment --
1812 ----------------------
1814 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1815 N_Loc : constant Source_Ptr := Sloc (N);
1816 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1817 Exp : Node_Id := N;
1818 Kind : Node_Kind := Nkind (N);
1819 Lhs : Node_Id;
1820 Res : List_Id;
1822 begin
1823 Lhs :=
1824 Make_Selected_Component (N_Loc,
1825 Prefix => Make_Identifier (Loc, Name_uInit),
1826 Selector_Name => New_Occurrence_Of (Id, N_Loc));
1827 Set_Assignment_OK (Lhs);
1829 -- Case of an access attribute applied to the current instance.
1830 -- Replace the reference to the type by a reference to the actual
1831 -- object. (Note that this handles the case of the top level of
1832 -- the expression being given by such an attribute, but does not
1833 -- cover uses nested within an initial value expression. Nested
1834 -- uses are unlikely to occur in practice, but are theoretically
1835 -- possible.) It is not clear how to handle them without fully
1836 -- traversing the expression. ???
1838 if Kind = N_Attribute_Reference
1839 and then Nam_In (Attribute_Name (N), Name_Unchecked_Access,
1840 Name_Unrestricted_Access)
1841 and then Is_Entity_Name (Prefix (N))
1842 and then Is_Type (Entity (Prefix (N)))
1843 and then Entity (Prefix (N)) = Rec_Type
1844 then
1845 Exp :=
1846 Make_Attribute_Reference (N_Loc,
1847 Prefix =>
1848 Make_Identifier (N_Loc, Name_uInit),
1849 Attribute_Name => Name_Unrestricted_Access);
1850 end if;
1852 -- Take a copy of Exp to ensure that later copies of this component
1853 -- declaration in derived types see the original tree, not a node
1854 -- rewritten during expansion of the init_proc. If the copy contains
1855 -- itypes, the scope of the new itypes is the init_proc being built.
1857 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id);
1859 Res := New_List (
1860 Make_Assignment_Statement (Loc,
1861 Name => Lhs,
1862 Expression => Exp));
1864 Set_No_Ctrl_Actions (First (Res));
1866 -- Adjust the tag if tagged (because of possible view conversions).
1867 -- Suppress the tag adjustment when VM_Target because VM tags are
1868 -- represented implicitly in objects.
1870 if Is_Tagged_Type (Typ) and then Tagged_Type_Expansion then
1871 Append_To (Res,
1872 Make_Assignment_Statement (N_Loc,
1873 Name =>
1874 Make_Selected_Component (N_Loc,
1875 Prefix =>
1876 New_Copy_Tree (Lhs, New_Scope => Proc_Id),
1877 Selector_Name =>
1878 New_Occurrence_Of (First_Tag_Component (Typ), N_Loc)),
1880 Expression =>
1881 Unchecked_Convert_To (RTE (RE_Tag),
1882 New_Occurrence_Of
1883 (Node
1884 (First_Elmt
1885 (Access_Disp_Table (Underlying_Type (Typ)))),
1886 N_Loc))));
1887 end if;
1889 -- Adjust the component if controlled except if it is an aggregate
1890 -- that will be expanded inline.
1892 if Kind = N_Qualified_Expression then
1893 Kind := Nkind (Expression (N));
1894 end if;
1896 if Needs_Finalization (Typ)
1897 and then not (Nkind_In (Kind, N_Aggregate, N_Extension_Aggregate))
1898 and then not Is_Limited_View (Typ)
1899 then
1900 Append_To (Res,
1901 Make_Adjust_Call
1902 (Obj_Ref => New_Copy_Tree (Lhs),
1903 Typ => Etype (Id)));
1904 end if;
1906 return Res;
1908 exception
1909 when RE_Not_Available =>
1910 return Empty_List;
1911 end Build_Assignment;
1913 ------------------------------------
1914 -- Build_Discriminant_Assignments --
1915 ------------------------------------
1917 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1918 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1919 D : Entity_Id;
1920 D_Loc : Source_Ptr;
1922 begin
1923 if Has_Discriminants (Rec_Type)
1924 and then not Is_Unchecked_Union (Rec_Type)
1925 then
1926 D := First_Discriminant (Rec_Type);
1927 while Present (D) loop
1929 -- Don't generate the assignment for discriminants in derived
1930 -- tagged types if the discriminant is a renaming of some
1931 -- ancestor discriminant. This initialization will be done
1932 -- when initializing the _parent field of the derived record.
1934 if Is_Tagged
1935 and then Present (Corresponding_Discriminant (D))
1936 then
1937 null;
1939 else
1940 D_Loc := Sloc (D);
1941 Append_List_To (Statement_List,
1942 Build_Assignment (D,
1943 New_Occurrence_Of (Discriminal (D), D_Loc)));
1944 end if;
1946 Next_Discriminant (D);
1947 end loop;
1948 end if;
1949 end Build_Discriminant_Assignments;
1951 --------------------------
1952 -- Build_Init_Call_Thru --
1953 --------------------------
1955 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1956 Parent_Proc : constant Entity_Id :=
1957 Base_Init_Proc (Etype (Rec_Type));
1959 Parent_Type : constant Entity_Id :=
1960 Etype (First_Formal (Parent_Proc));
1962 Uparent_Type : constant Entity_Id :=
1963 Underlying_Type (Parent_Type);
1965 First_Discr_Param : Node_Id;
1967 Arg : Node_Id;
1968 Args : List_Id;
1969 First_Arg : Node_Id;
1970 Parent_Discr : Entity_Id;
1971 Res : List_Id;
1973 begin
1974 -- First argument (_Init) is the object to be initialized.
1975 -- ??? not sure where to get a reasonable Loc for First_Arg
1977 First_Arg :=
1978 OK_Convert_To (Parent_Type,
1979 New_Occurrence_Of
1980 (Defining_Identifier (First (Parameters)), Loc));
1982 Set_Etype (First_Arg, Parent_Type);
1984 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
1986 -- In the tasks case,
1987 -- add _Master as the value of the _Master parameter
1988 -- add _Chain as the value of the _Chain parameter.
1989 -- add _Task_Name as the value of the _Task_Name parameter.
1990 -- At the outer level, these will be variables holding the
1991 -- corresponding values obtained from GNARL or the expander.
1993 -- At inner levels, they will be the parameters passed down through
1994 -- the outer routines.
1996 First_Discr_Param := Next (First (Parameters));
1998 if Has_Task (Rec_Type) then
1999 if Restriction_Active (No_Task_Hierarchy) then
2000 Append_To (Args,
2001 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
2002 else
2003 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
2004 end if;
2006 -- Add _Chain (not done for sequential elaboration policy, see
2007 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
2009 if Partition_Elaboration_Policy /= 'S' then
2010 Append_To (Args, Make_Identifier (Loc, Name_uChain));
2011 end if;
2013 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
2014 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
2015 end if;
2017 -- Append discriminant values
2019 if Has_Discriminants (Uparent_Type) then
2020 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2022 Parent_Discr := First_Discriminant (Uparent_Type);
2023 while Present (Parent_Discr) loop
2025 -- Get the initial value for this discriminant
2026 -- ??? needs to be cleaned up to use parent_Discr_Constr
2027 -- directly.
2029 declare
2030 Discr : Entity_Id :=
2031 First_Stored_Discriminant (Uparent_Type);
2033 Discr_Value : Elmt_Id :=
2034 First_Elmt (Stored_Constraint (Rec_Type));
2036 begin
2037 while Original_Record_Component (Parent_Discr) /= Discr loop
2038 Next_Stored_Discriminant (Discr);
2039 Next_Elmt (Discr_Value);
2040 end loop;
2042 Arg := Node (Discr_Value);
2043 end;
2045 -- Append it to the list
2047 if Nkind (Arg) = N_Identifier
2048 and then Ekind (Entity (Arg)) = E_Discriminant
2049 then
2050 Append_To (Args,
2051 New_Occurrence_Of (Discriminal (Entity (Arg)), Loc));
2053 -- Case of access discriminants. We replace the reference
2054 -- to the type by a reference to the actual object.
2056 -- Is above comment right??? Use of New_Copy below seems mighty
2057 -- suspicious ???
2059 else
2060 Append_To (Args, New_Copy (Arg));
2061 end if;
2063 Next_Discriminant (Parent_Discr);
2064 end loop;
2065 end if;
2067 Res :=
2068 New_List (
2069 Make_Procedure_Call_Statement (Loc,
2070 Name =>
2071 New_Occurrence_Of (Parent_Proc, Loc),
2072 Parameter_Associations => Args));
2074 return Res;
2075 end Build_Init_Call_Thru;
2077 -----------------------------------
2078 -- Build_Offset_To_Top_Functions --
2079 -----------------------------------
2081 procedure Build_Offset_To_Top_Functions is
2083 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2084 -- Generate:
2085 -- function Fxx (O : Address) return Storage_Offset is
2086 -- type Acc is access all <Typ>;
2087 -- begin
2088 -- return Acc!(O).Iface_Comp'Position;
2089 -- end Fxx;
2091 ----------------------------------
2092 -- Build_Offset_To_Top_Function --
2093 ----------------------------------
2095 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2096 Body_Node : Node_Id;
2097 Func_Id : Entity_Id;
2098 Spec_Node : Node_Id;
2099 Acc_Type : Entity_Id;
2101 begin
2102 Func_Id := Make_Temporary (Loc, 'F');
2103 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2105 -- Generate
2106 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2108 Spec_Node := New_Node (N_Function_Specification, Loc);
2109 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2110 Set_Parameter_Specifications (Spec_Node, New_List (
2111 Make_Parameter_Specification (Loc,
2112 Defining_Identifier =>
2113 Make_Defining_Identifier (Loc, Name_uO),
2114 In_Present => True,
2115 Parameter_Type =>
2116 New_Occurrence_Of (RTE (RE_Address), Loc))));
2117 Set_Result_Definition (Spec_Node,
2118 New_Occurrence_Of (RTE (RE_Storage_Offset), Loc));
2120 -- Generate
2121 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2122 -- begin
2123 -- return O.Iface_Comp'Position;
2124 -- end Fxx;
2126 Body_Node := New_Node (N_Subprogram_Body, Loc);
2127 Set_Specification (Body_Node, Spec_Node);
2129 Acc_Type := Make_Temporary (Loc, 'T');
2130 Set_Declarations (Body_Node, New_List (
2131 Make_Full_Type_Declaration (Loc,
2132 Defining_Identifier => Acc_Type,
2133 Type_Definition =>
2134 Make_Access_To_Object_Definition (Loc,
2135 All_Present => True,
2136 Null_Exclusion_Present => False,
2137 Constant_Present => False,
2138 Subtype_Indication =>
2139 New_Occurrence_Of (Rec_Type, Loc)))));
2141 Set_Handled_Statement_Sequence (Body_Node,
2142 Make_Handled_Sequence_Of_Statements (Loc,
2143 Statements => New_List (
2144 Make_Simple_Return_Statement (Loc,
2145 Expression =>
2146 Make_Attribute_Reference (Loc,
2147 Prefix =>
2148 Make_Selected_Component (Loc,
2149 Prefix =>
2150 Unchecked_Convert_To (Acc_Type,
2151 Make_Identifier (Loc, Name_uO)),
2152 Selector_Name =>
2153 New_Occurrence_Of (Iface_Comp, Loc)),
2154 Attribute_Name => Name_Position)))));
2156 Set_Ekind (Func_Id, E_Function);
2157 Set_Mechanism (Func_Id, Default_Mechanism);
2158 Set_Is_Internal (Func_Id, True);
2160 if not Debug_Generated_Code then
2161 Set_Debug_Info_Off (Func_Id);
2162 end if;
2164 Analyze (Body_Node);
2166 Append_Freeze_Action (Rec_Type, Body_Node);
2167 end Build_Offset_To_Top_Function;
2169 -- Local variables
2171 Iface_Comp : Node_Id;
2172 Iface_Comp_Elmt : Elmt_Id;
2173 Ifaces_Comp_List : Elist_Id;
2175 -- Start of processing for Build_Offset_To_Top_Functions
2177 begin
2178 -- Offset_To_Top_Functions are built only for derivations of types
2179 -- with discriminants that cover interface types.
2180 -- Nothing is needed either in case of virtual machines, since
2181 -- interfaces are handled directly by the VM.
2183 if not Is_Tagged_Type (Rec_Type)
2184 or else Etype (Rec_Type) = Rec_Type
2185 or else not Has_Discriminants (Etype (Rec_Type))
2186 or else not Tagged_Type_Expansion
2187 then
2188 return;
2189 end if;
2191 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2193 -- For each interface type with secondary dispatch table we generate
2194 -- the Offset_To_Top_Functions (required to displace the pointer in
2195 -- interface conversions)
2197 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2198 while Present (Iface_Comp_Elmt) loop
2199 Iface_Comp := Node (Iface_Comp_Elmt);
2200 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2202 -- If the interface is a parent of Rec_Type it shares the primary
2203 -- dispatch table and hence there is no need to build the function
2205 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type,
2206 Use_Full_View => True)
2207 then
2208 Build_Offset_To_Top_Function (Iface_Comp);
2209 end if;
2211 Next_Elmt (Iface_Comp_Elmt);
2212 end loop;
2213 end Build_Offset_To_Top_Functions;
2215 ------------------------------
2216 -- Build_CPP_Init_Procedure --
2217 ------------------------------
2219 procedure Build_CPP_Init_Procedure is
2220 Body_Node : Node_Id;
2221 Body_Stmts : List_Id;
2222 Flag_Id : Entity_Id;
2223 Handled_Stmt_Node : Node_Id;
2224 Init_Tags_List : List_Id;
2225 Proc_Id : Entity_Id;
2226 Proc_Spec_Node : Node_Id;
2228 begin
2229 -- Check cases requiring no IC routine
2231 if not Is_CPP_Class (Root_Type (Rec_Type))
2232 or else Is_CPP_Class (Rec_Type)
2233 or else CPP_Num_Prims (Rec_Type) = 0
2234 or else not Tagged_Type_Expansion
2235 or else No_Run_Time_Mode
2236 then
2237 return;
2238 end if;
2240 -- Generate:
2242 -- Flag : Boolean := False;
2244 -- procedure Typ_IC is
2245 -- begin
2246 -- if not Flag then
2247 -- Copy C++ dispatch table slots from parent
2248 -- Update C++ slots of overridden primitives
2249 -- end if;
2250 -- end;
2252 Flag_Id := Make_Temporary (Loc, 'F');
2254 Append_Freeze_Action (Rec_Type,
2255 Make_Object_Declaration (Loc,
2256 Defining_Identifier => Flag_Id,
2257 Object_Definition =>
2258 New_Occurrence_Of (Standard_Boolean, Loc),
2259 Expression =>
2260 New_Occurrence_Of (Standard_True, Loc)));
2262 Body_Stmts := New_List;
2263 Body_Node := New_Node (N_Subprogram_Body, Loc);
2265 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2267 Proc_Id :=
2268 Make_Defining_Identifier (Loc,
2269 Chars => Make_TSS_Name (Rec_Type, TSS_CPP_Init_Proc));
2271 Set_Ekind (Proc_Id, E_Procedure);
2272 Set_Is_Internal (Proc_Id);
2274 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2276 Set_Parameter_Specifications (Proc_Spec_Node, New_List);
2277 Set_Specification (Body_Node, Proc_Spec_Node);
2278 Set_Declarations (Body_Node, New_List);
2280 Init_Tags_List := Build_Inherit_CPP_Prims (Rec_Type);
2282 Append_To (Init_Tags_List,
2283 Make_Assignment_Statement (Loc,
2284 Name =>
2285 New_Occurrence_Of (Flag_Id, Loc),
2286 Expression =>
2287 New_Occurrence_Of (Standard_False, Loc)));
2289 Append_To (Body_Stmts,
2290 Make_If_Statement (Loc,
2291 Condition => New_Occurrence_Of (Flag_Id, Loc),
2292 Then_Statements => Init_Tags_List));
2294 Handled_Stmt_Node :=
2295 New_Node (N_Handled_Sequence_Of_Statements, Loc);
2296 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2297 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2298 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2300 if not Debug_Generated_Code then
2301 Set_Debug_Info_Off (Proc_Id);
2302 end if;
2304 -- Associate CPP_Init_Proc with type
2306 Set_Init_Proc (Rec_Type, Proc_Id);
2307 end Build_CPP_Init_Procedure;
2309 --------------------------
2310 -- Build_Init_Procedure --
2311 --------------------------
2313 procedure Build_Init_Procedure is
2314 Body_Stmts : List_Id;
2315 Body_Node : Node_Id;
2316 Handled_Stmt_Node : Node_Id;
2317 Init_Tags_List : List_Id;
2318 Parameters : List_Id;
2319 Proc_Spec_Node : Node_Id;
2320 Record_Extension_Node : Node_Id;
2322 begin
2323 Body_Stmts := New_List;
2324 Body_Node := New_Node (N_Subprogram_Body, Loc);
2325 Set_Ekind (Proc_Id, E_Procedure);
2327 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2328 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2330 Parameters := Init_Formals (Rec_Type);
2331 Append_List_To (Parameters,
2332 Build_Discriminant_Formals (Rec_Type, True));
2334 -- For tagged types, we add a flag to indicate whether the routine
2335 -- is called to initialize a parent component in the init_proc of
2336 -- a type extension. If the flag is false, we do not set the tag
2337 -- because it has been set already in the extension.
2339 if Is_Tagged_Type (Rec_Type) then
2340 Set_Tag := Make_Temporary (Loc, 'P');
2342 Append_To (Parameters,
2343 Make_Parameter_Specification (Loc,
2344 Defining_Identifier => Set_Tag,
2345 Parameter_Type =>
2346 New_Occurrence_Of (Standard_Boolean, Loc),
2347 Expression =>
2348 New_Occurrence_Of (Standard_True, Loc)));
2349 end if;
2351 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2352 Set_Specification (Body_Node, Proc_Spec_Node);
2353 Set_Declarations (Body_Node, Decls);
2355 -- N is a Derived_Type_Definition that renames the parameters of the
2356 -- ancestor type. We initialize it by expanding our discriminants and
2357 -- call the ancestor _init_proc with a type-converted object.
2359 if Parent_Subtype_Renaming_Discrims then
2360 Append_List_To (Body_Stmts, Build_Init_Call_Thru (Parameters));
2362 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2363 Build_Discriminant_Assignments (Body_Stmts);
2365 if not Null_Present (Type_Definition (N)) then
2366 Append_List_To (Body_Stmts,
2367 Build_Init_Statements (Component_List (Type_Definition (N))));
2368 end if;
2370 -- N is a Derived_Type_Definition with a possible non-empty
2371 -- extension. The initialization of a type extension consists in the
2372 -- initialization of the components in the extension.
2374 else
2375 Build_Discriminant_Assignments (Body_Stmts);
2377 Record_Extension_Node :=
2378 Record_Extension_Part (Type_Definition (N));
2380 if not Null_Present (Record_Extension_Node) then
2381 declare
2382 Stmts : constant List_Id :=
2383 Build_Init_Statements (
2384 Component_List (Record_Extension_Node));
2386 begin
2387 -- The parent field must be initialized first because the
2388 -- offset of the new discriminants may depend on it. This is
2389 -- not needed if the parent is an interface type because in
2390 -- such case the initialization of the _parent field was not
2391 -- generated.
2393 if not Is_Interface (Etype (Rec_Ent))
2394 and then Nkind (First (Stmts)) = N_Procedure_Call_Statement
2395 and then Is_Init_Proc (Name (First (Stmts)))
2396 then
2397 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2398 end if;
2400 Append_List_To (Body_Stmts, Stmts);
2401 end;
2402 end if;
2403 end if;
2405 -- Add here the assignment to instantiate the Tag
2407 -- The assignment corresponds to the code:
2409 -- _Init._Tag := Typ'Tag;
2411 -- Suppress the tag assignment when VM_Target because VM tags are
2412 -- represented implicitly in objects. It is also suppressed in case
2413 -- of CPP_Class types because in this case the tag is initialized in
2414 -- the C++ side.
2416 if Is_Tagged_Type (Rec_Type)
2417 and then Tagged_Type_Expansion
2418 and then not No_Run_Time_Mode
2419 then
2420 -- Case 1: Ada tagged types with no CPP ancestor. Set the tags of
2421 -- the actual object and invoke the IP of the parent (in this
2422 -- order). The tag must be initialized before the call to the IP
2423 -- of the parent and the assignments to other components because
2424 -- the initial value of the components may depend on the tag (eg.
2425 -- through a dispatching operation on an access to the current
2426 -- type). The tag assignment is not done when initializing the
2427 -- parent component of a type extension, because in that case the
2428 -- tag is set in the extension.
2430 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2432 -- Initialize the primary tag component
2434 Init_Tags_List := New_List (
2435 Make_Assignment_Statement (Loc,
2436 Name =>
2437 Make_Selected_Component (Loc,
2438 Prefix => Make_Identifier (Loc, Name_uInit),
2439 Selector_Name =>
2440 New_Occurrence_Of
2441 (First_Tag_Component (Rec_Type), Loc)),
2442 Expression =>
2443 New_Occurrence_Of
2444 (Node
2445 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2447 -- Ada 2005 (AI-251): Initialize the secondary tags components
2448 -- located at fixed positions (tags whose position depends on
2449 -- variable size components are initialized later ---see below)
2451 if Ada_Version >= Ada_2005
2452 and then not Is_Interface (Rec_Type)
2453 and then Has_Interfaces (Rec_Type)
2454 then
2455 Init_Secondary_Tags
2456 (Typ => Rec_Type,
2457 Target => Make_Identifier (Loc, Name_uInit),
2458 Stmts_List => Init_Tags_List,
2459 Fixed_Comps => True,
2460 Variable_Comps => False);
2461 end if;
2463 Prepend_To (Body_Stmts,
2464 Make_If_Statement (Loc,
2465 Condition => New_Occurrence_Of (Set_Tag, Loc),
2466 Then_Statements => Init_Tags_List));
2468 -- Case 2: CPP type. The imported C++ constructor takes care of
2469 -- tags initialization. No action needed here because the IP
2470 -- is built by Set_CPP_Constructors; in this case the IP is a
2471 -- wrapper that invokes the C++ constructor and copies the C++
2472 -- tags locally. Done to inherit the C++ slots in Ada derivations
2473 -- (see case 3).
2475 elsif Is_CPP_Class (Rec_Type) then
2476 pragma Assert (False);
2477 null;
2479 -- Case 3: Combined hierarchy containing C++ types and Ada tagged
2480 -- type derivations. Derivations of imported C++ classes add a
2481 -- complication, because we cannot inhibit tag setting in the
2482 -- constructor for the parent. Hence we initialize the tag after
2483 -- the call to the parent IP (that is, in reverse order compared
2484 -- with pure Ada hierarchies ---see comment on case 1).
2486 else
2487 -- Initialize the primary tag
2489 Init_Tags_List := New_List (
2490 Make_Assignment_Statement (Loc,
2491 Name =>
2492 Make_Selected_Component (Loc,
2493 Prefix => Make_Identifier (Loc, Name_uInit),
2494 Selector_Name =>
2495 New_Occurrence_Of
2496 (First_Tag_Component (Rec_Type), Loc)),
2497 Expression =>
2498 New_Occurrence_Of
2499 (Node
2500 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2502 -- Ada 2005 (AI-251): Initialize the secondary tags components
2503 -- located at fixed positions (tags whose position depends on
2504 -- variable size components are initialized later ---see below)
2506 if Ada_Version >= Ada_2005
2507 and then not Is_Interface (Rec_Type)
2508 and then Has_Interfaces (Rec_Type)
2509 then
2510 Init_Secondary_Tags
2511 (Typ => Rec_Type,
2512 Target => Make_Identifier (Loc, Name_uInit),
2513 Stmts_List => Init_Tags_List,
2514 Fixed_Comps => True,
2515 Variable_Comps => False);
2516 end if;
2518 -- Initialize the tag component after invocation of parent IP.
2520 -- Generate:
2521 -- parent_IP(_init.parent); // Invokes the C++ constructor
2522 -- [ typIC; ] // Inherit C++ slots from parent
2523 -- init_tags
2525 declare
2526 Ins_Nod : Node_Id;
2528 begin
2529 -- Search for the call to the IP of the parent. We assume
2530 -- that the first init_proc call is for the parent.
2532 Ins_Nod := First (Body_Stmts);
2533 while Present (Next (Ins_Nod))
2534 and then (Nkind (Ins_Nod) /= N_Procedure_Call_Statement
2535 or else not Is_Init_Proc (Name (Ins_Nod)))
2536 loop
2537 Next (Ins_Nod);
2538 end loop;
2540 -- The IC routine copies the inherited slots of the C+ part
2541 -- of the dispatch table from the parent and updates the
2542 -- overridden C++ slots.
2544 if CPP_Num_Prims (Rec_Type) > 0 then
2545 declare
2546 Init_DT : Entity_Id;
2547 New_Nod : Node_Id;
2549 begin
2550 Init_DT := CPP_Init_Proc (Rec_Type);
2551 pragma Assert (Present (Init_DT));
2553 New_Nod :=
2554 Make_Procedure_Call_Statement (Loc,
2555 New_Occurrence_Of (Init_DT, Loc));
2556 Insert_After (Ins_Nod, New_Nod);
2558 -- Update location of init tag statements
2560 Ins_Nod := New_Nod;
2561 end;
2562 end if;
2564 Insert_List_After (Ins_Nod, Init_Tags_List);
2565 end;
2566 end if;
2568 -- Ada 2005 (AI-251): Initialize the secondary tag components
2569 -- located at variable positions. We delay the generation of this
2570 -- code until here because the value of the attribute 'Position
2571 -- applied to variable size components of the parent type that
2572 -- depend on discriminants is only safely read at runtime after
2573 -- the parent components have been initialized.
2575 if Ada_Version >= Ada_2005
2576 and then not Is_Interface (Rec_Type)
2577 and then Has_Interfaces (Rec_Type)
2578 and then Has_Discriminants (Etype (Rec_Type))
2579 and then Is_Variable_Size_Record (Etype (Rec_Type))
2580 then
2581 Init_Tags_List := New_List;
2583 Init_Secondary_Tags
2584 (Typ => Rec_Type,
2585 Target => Make_Identifier (Loc, Name_uInit),
2586 Stmts_List => Init_Tags_List,
2587 Fixed_Comps => False,
2588 Variable_Comps => True);
2590 if Is_Non_Empty_List (Init_Tags_List) then
2591 Append_List_To (Body_Stmts, Init_Tags_List);
2592 end if;
2593 end if;
2594 end if;
2596 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2597 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2599 -- Generate:
2600 -- Deep_Finalize (_init, C1, ..., CN);
2601 -- raise;
2603 if Counter > 0
2604 and then Needs_Finalization (Rec_Type)
2605 and then not Is_Abstract_Type (Rec_Type)
2606 and then not Restriction_Active (No_Exception_Propagation)
2607 then
2608 declare
2609 DF_Call : Node_Id;
2610 DF_Id : Entity_Id;
2612 begin
2613 -- Create a local version of Deep_Finalize which has indication
2614 -- of partial initialization state.
2616 DF_Id := Make_Temporary (Loc, 'F');
2618 Append_To (Decls, Make_Local_Deep_Finalize (Rec_Type, DF_Id));
2620 DF_Call :=
2621 Make_Procedure_Call_Statement (Loc,
2622 Name => New_Occurrence_Of (DF_Id, Loc),
2623 Parameter_Associations => New_List (
2624 Make_Identifier (Loc, Name_uInit),
2625 New_Occurrence_Of (Standard_False, Loc)));
2627 -- Do not emit warnings related to the elaboration order when a
2628 -- controlled object is declared before the body of Finalize is
2629 -- seen.
2631 Set_No_Elaboration_Check (DF_Call);
2633 Set_Exception_Handlers (Handled_Stmt_Node, New_List (
2634 Make_Exception_Handler (Loc,
2635 Exception_Choices => New_List (
2636 Make_Others_Choice (Loc)),
2637 Statements => New_List (
2638 DF_Call,
2639 Make_Raise_Statement (Loc)))));
2640 end;
2641 else
2642 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2643 end if;
2645 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2647 if not Debug_Generated_Code then
2648 Set_Debug_Info_Off (Proc_Id);
2649 end if;
2651 -- Associate Init_Proc with type, and determine if the procedure
2652 -- is null (happens because of the Initialize_Scalars pragma case,
2653 -- where we have to generate a null procedure in case it is called
2654 -- by a client with Initialize_Scalars set). Such procedures have
2655 -- to be generated, but do not have to be called, so we mark them
2656 -- as null to suppress the call.
2658 Set_Init_Proc (Rec_Type, Proc_Id);
2660 if List_Length (Body_Stmts) = 1
2662 -- We must skip SCIL nodes because they may have been added to this
2663 -- list by Insert_Actions.
2665 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
2666 and then VM_Target = No_VM
2667 then
2668 -- Even though the init proc may be null at this time it might get
2669 -- some stuff added to it later by the VM backend.
2671 Set_Is_Null_Init_Proc (Proc_Id);
2672 end if;
2673 end Build_Init_Procedure;
2675 ---------------------------
2676 -- Build_Init_Statements --
2677 ---------------------------
2679 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2680 Checks : constant List_Id := New_List;
2681 Actions : List_Id := No_List;
2682 Counter_Id : Entity_Id := Empty;
2683 Comp_Loc : Source_Ptr;
2684 Decl : Node_Id;
2685 Has_POC : Boolean;
2686 Id : Entity_Id;
2687 Parent_Stmts : List_Id;
2688 Stmts : List_Id;
2689 Typ : Entity_Id;
2691 procedure Increment_Counter (Loc : Source_Ptr);
2692 -- Generate an "increment by one" statement for the current counter
2693 -- and append it to the list Stmts.
2695 procedure Make_Counter (Loc : Source_Ptr);
2696 -- Create a new counter for the current component list. The routine
2697 -- creates a new defining Id, adds an object declaration and sets
2698 -- the Id generator for the next variant.
2700 -----------------------
2701 -- Increment_Counter --
2702 -----------------------
2704 procedure Increment_Counter (Loc : Source_Ptr) is
2705 begin
2706 -- Generate:
2707 -- Counter := Counter + 1;
2709 Append_To (Stmts,
2710 Make_Assignment_Statement (Loc,
2711 Name => New_Occurrence_Of (Counter_Id, Loc),
2712 Expression =>
2713 Make_Op_Add (Loc,
2714 Left_Opnd => New_Occurrence_Of (Counter_Id, Loc),
2715 Right_Opnd => Make_Integer_Literal (Loc, 1))));
2716 end Increment_Counter;
2718 ------------------
2719 -- Make_Counter --
2720 ------------------
2722 procedure Make_Counter (Loc : Source_Ptr) is
2723 begin
2724 -- Increment the Id generator
2726 Counter := Counter + 1;
2728 -- Create the entity and declaration
2730 Counter_Id :=
2731 Make_Defining_Identifier (Loc,
2732 Chars => New_External_Name ('C', Counter));
2734 -- Generate:
2735 -- Cnn : Integer := 0;
2737 Append_To (Decls,
2738 Make_Object_Declaration (Loc,
2739 Defining_Identifier => Counter_Id,
2740 Object_Definition =>
2741 New_Occurrence_Of (Standard_Integer, Loc),
2742 Expression =>
2743 Make_Integer_Literal (Loc, 0)));
2744 end Make_Counter;
2746 -- Start of processing for Build_Init_Statements
2748 begin
2749 if Null_Present (Comp_List) then
2750 return New_List (Make_Null_Statement (Loc));
2751 end if;
2753 Parent_Stmts := New_List;
2754 Stmts := New_List;
2756 -- Loop through visible declarations of task types and protected
2757 -- types moving any expanded code from the spec to the body of the
2758 -- init procedure.
2760 if Is_Task_Record_Type (Rec_Type)
2761 or else Is_Protected_Record_Type (Rec_Type)
2762 then
2763 declare
2764 Decl : constant Node_Id :=
2765 Parent (Corresponding_Concurrent_Type (Rec_Type));
2766 Def : Node_Id;
2767 N1 : Node_Id;
2768 N2 : Node_Id;
2770 begin
2771 if Is_Task_Record_Type (Rec_Type) then
2772 Def := Task_Definition (Decl);
2773 else
2774 Def := Protected_Definition (Decl);
2775 end if;
2777 if Present (Def) then
2778 N1 := First (Visible_Declarations (Def));
2779 while Present (N1) loop
2780 N2 := N1;
2781 N1 := Next (N1);
2783 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2784 or else Nkind (N2) in N_Raise_xxx_Error
2785 or else Nkind (N2) = N_Procedure_Call_Statement
2786 then
2787 Append_To (Stmts,
2788 New_Copy_Tree (N2, New_Scope => Proc_Id));
2789 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2790 Analyze (N2);
2791 end if;
2792 end loop;
2793 end if;
2794 end;
2795 end if;
2797 -- Loop through components, skipping pragmas, in 2 steps. The first
2798 -- step deals with regular components. The second step deals with
2799 -- components that have per object constraints and no explicit
2800 -- initialization.
2802 Has_POC := False;
2804 -- First pass : regular components
2806 Decl := First_Non_Pragma (Component_Items (Comp_List));
2807 while Present (Decl) loop
2808 Comp_Loc := Sloc (Decl);
2809 Build_Record_Checks
2810 (Subtype_Indication (Component_Definition (Decl)), Checks);
2812 Id := Defining_Identifier (Decl);
2813 Typ := Etype (Id);
2815 -- Leave any processing of per-object constrained component for
2816 -- the second pass.
2818 if Has_Access_Constraint (Id) and then No (Expression (Decl)) then
2819 Has_POC := True;
2821 -- Regular component cases
2823 else
2824 -- In the context of the init proc, references to discriminants
2825 -- resolve to denote the discriminals: this is where we can
2826 -- freeze discriminant dependent component subtypes.
2828 if not Is_Frozen (Typ) then
2829 Append_List_To (Stmts, Freeze_Entity (Typ, N));
2830 end if;
2832 -- Explicit initialization
2834 if Present (Expression (Decl)) then
2835 if Is_CPP_Constructor_Call (Expression (Decl)) then
2836 Actions :=
2837 Build_Initialization_Call
2838 (Comp_Loc,
2839 Id_Ref =>
2840 Make_Selected_Component (Comp_Loc,
2841 Prefix =>
2842 Make_Identifier (Comp_Loc, Name_uInit),
2843 Selector_Name =>
2844 New_Occurrence_Of (Id, Comp_Loc)),
2845 Typ => Typ,
2846 In_Init_Proc => True,
2847 Enclos_Type => Rec_Type,
2848 Discr_Map => Discr_Map,
2849 Constructor_Ref => Expression (Decl));
2850 else
2851 Actions := Build_Assignment (Id, Expression (Decl));
2852 end if;
2854 -- CPU, Dispatching_Domain, Priority and Size components are
2855 -- filled with the corresponding rep item expression of the
2856 -- concurrent type (if any).
2858 elsif Ekind (Scope (Id)) = E_Record_Type
2859 and then Present (Corresponding_Concurrent_Type (Scope (Id)))
2860 and then Nam_In (Chars (Id), Name_uCPU,
2861 Name_uDispatching_Domain,
2862 Name_uPriority)
2863 then
2864 declare
2865 Exp : Node_Id;
2866 Nam : Name_Id;
2867 Ritem : Node_Id;
2869 begin
2870 if Chars (Id) = Name_uCPU then
2871 Nam := Name_CPU;
2873 elsif Chars (Id) = Name_uDispatching_Domain then
2874 Nam := Name_Dispatching_Domain;
2876 elsif Chars (Id) = Name_uPriority then
2877 Nam := Name_Priority;
2878 end if;
2880 -- Get the Rep Item (aspect specification, attribute
2881 -- definition clause or pragma) of the corresponding
2882 -- concurrent type.
2884 Ritem :=
2885 Get_Rep_Item
2886 (Corresponding_Concurrent_Type (Scope (Id)),
2887 Nam,
2888 Check_Parents => False);
2890 if Present (Ritem) then
2892 -- Pragma case
2894 if Nkind (Ritem) = N_Pragma then
2895 Exp := First (Pragma_Argument_Associations (Ritem));
2897 if Nkind (Exp) = N_Pragma_Argument_Association then
2898 Exp := Expression (Exp);
2899 end if;
2901 -- Conversion for Priority expression
2903 if Nam = Name_Priority then
2904 if Pragma_Name (Ritem) = Name_Priority
2905 and then not GNAT_Mode
2906 then
2907 Exp := Convert_To (RTE (RE_Priority), Exp);
2908 else
2909 Exp :=
2910 Convert_To (RTE (RE_Any_Priority), Exp);
2911 end if;
2912 end if;
2914 -- Aspect/Attribute definition clause case
2916 else
2917 Exp := Expression (Ritem);
2919 -- Conversion for Priority expression
2921 if Nam = Name_Priority then
2922 if Chars (Ritem) = Name_Priority
2923 and then not GNAT_Mode
2924 then
2925 Exp := Convert_To (RTE (RE_Priority), Exp);
2926 else
2927 Exp :=
2928 Convert_To (RTE (RE_Any_Priority), Exp);
2929 end if;
2930 end if;
2931 end if;
2933 -- Conversion for Dispatching_Domain value
2935 if Nam = Name_Dispatching_Domain then
2936 Exp :=
2937 Unchecked_Convert_To
2938 (RTE (RE_Dispatching_Domain_Access), Exp);
2939 end if;
2941 Actions := Build_Assignment (Id, Exp);
2943 -- Nothing needed if no Rep Item
2945 else
2946 Actions := No_List;
2947 end if;
2948 end;
2950 -- Composite component with its own Init_Proc
2952 elsif not Is_Interface (Typ)
2953 and then Has_Non_Null_Base_Init_Proc (Typ)
2954 then
2955 Actions :=
2956 Build_Initialization_Call
2957 (Comp_Loc,
2958 Make_Selected_Component (Comp_Loc,
2959 Prefix =>
2960 Make_Identifier (Comp_Loc, Name_uInit),
2961 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
2962 Typ,
2963 In_Init_Proc => True,
2964 Enclos_Type => Rec_Type,
2965 Discr_Map => Discr_Map);
2967 Clean_Task_Names (Typ, Proc_Id);
2969 -- Simple initialization
2971 elsif Component_Needs_Simple_Initialization (Typ) then
2972 Actions :=
2973 Build_Assignment
2974 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
2976 -- Nothing needed for this case
2978 else
2979 Actions := No_List;
2980 end if;
2982 if Present (Checks) then
2983 if Chars (Id) = Name_uParent then
2984 Append_List_To (Parent_Stmts, Checks);
2985 else
2986 Append_List_To (Stmts, Checks);
2987 end if;
2988 end if;
2990 if Present (Actions) then
2991 if Chars (Id) = Name_uParent then
2992 Append_List_To (Parent_Stmts, Actions);
2994 else
2995 Append_List_To (Stmts, Actions);
2997 -- Preserve initialization state in the current counter
2999 if Needs_Finalization (Typ) then
3000 if No (Counter_Id) then
3001 Make_Counter (Comp_Loc);
3002 end if;
3004 Increment_Counter (Comp_Loc);
3005 end if;
3006 end if;
3007 end if;
3008 end if;
3010 Next_Non_Pragma (Decl);
3011 end loop;
3013 -- The parent field must be initialized first because variable
3014 -- size components of the parent affect the location of all the
3015 -- new components.
3017 Prepend_List_To (Stmts, Parent_Stmts);
3019 -- Set up tasks and protected object support. This needs to be done
3020 -- before any component with a per-object access discriminant
3021 -- constraint, or any variant part (which may contain such
3022 -- components) is initialized, because the initialization of these
3023 -- components may reference the enclosing concurrent object.
3025 -- For a task record type, add the task create call and calls to bind
3026 -- any interrupt (signal) entries.
3028 if Is_Task_Record_Type (Rec_Type) then
3030 -- In the case of the restricted run time the ATCB has already
3031 -- been preallocated.
3033 if Restricted_Profile then
3034 Append_To (Stmts,
3035 Make_Assignment_Statement (Loc,
3036 Name =>
3037 Make_Selected_Component (Loc,
3038 Prefix => Make_Identifier (Loc, Name_uInit),
3039 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
3040 Expression =>
3041 Make_Attribute_Reference (Loc,
3042 Prefix =>
3043 Make_Selected_Component (Loc,
3044 Prefix => Make_Identifier (Loc, Name_uInit),
3045 Selector_Name => Make_Identifier (Loc, Name_uATCB)),
3046 Attribute_Name => Name_Unchecked_Access)));
3047 end if;
3049 Append_To (Stmts, Make_Task_Create_Call (Rec_Type));
3051 declare
3052 Task_Type : constant Entity_Id :=
3053 Corresponding_Concurrent_Type (Rec_Type);
3054 Task_Decl : constant Node_Id := Parent (Task_Type);
3055 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
3056 Decl_Loc : Source_Ptr;
3057 Ent : Entity_Id;
3058 Vis_Decl : Node_Id;
3060 begin
3061 if Present (Task_Def) then
3062 Vis_Decl := First (Visible_Declarations (Task_Def));
3063 while Present (Vis_Decl) loop
3064 Decl_Loc := Sloc (Vis_Decl);
3066 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
3067 if Get_Attribute_Id (Chars (Vis_Decl)) =
3068 Attribute_Address
3069 then
3070 Ent := Entity (Name (Vis_Decl));
3072 if Ekind (Ent) = E_Entry then
3073 Append_To (Stmts,
3074 Make_Procedure_Call_Statement (Decl_Loc,
3075 Name =>
3076 New_Occurrence_Of (RTE (
3077 RE_Bind_Interrupt_To_Entry), Decl_Loc),
3078 Parameter_Associations => New_List (
3079 Make_Selected_Component (Decl_Loc,
3080 Prefix =>
3081 Make_Identifier (Decl_Loc, Name_uInit),
3082 Selector_Name =>
3083 Make_Identifier
3084 (Decl_Loc, Name_uTask_Id)),
3085 Entry_Index_Expression
3086 (Decl_Loc, Ent, Empty, Task_Type),
3087 Expression (Vis_Decl))));
3088 end if;
3089 end if;
3090 end if;
3092 Next (Vis_Decl);
3093 end loop;
3094 end if;
3095 end;
3096 end if;
3098 -- For a protected type, add statements generated by
3099 -- Make_Initialize_Protection.
3101 if Is_Protected_Record_Type (Rec_Type) then
3102 Append_List_To (Stmts,
3103 Make_Initialize_Protection (Rec_Type));
3104 end if;
3106 -- Second pass: components with per-object constraints
3108 if Has_POC then
3109 Decl := First_Non_Pragma (Component_Items (Comp_List));
3110 while Present (Decl) loop
3111 Comp_Loc := Sloc (Decl);
3112 Id := Defining_Identifier (Decl);
3113 Typ := Etype (Id);
3115 if Has_Access_Constraint (Id)
3116 and then No (Expression (Decl))
3117 then
3118 if Has_Non_Null_Base_Init_Proc (Typ) then
3119 Append_List_To (Stmts,
3120 Build_Initialization_Call (Comp_Loc,
3121 Make_Selected_Component (Comp_Loc,
3122 Prefix =>
3123 Make_Identifier (Comp_Loc, Name_uInit),
3124 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3125 Typ,
3126 In_Init_Proc => True,
3127 Enclos_Type => Rec_Type,
3128 Discr_Map => Discr_Map));
3130 Clean_Task_Names (Typ, Proc_Id);
3132 -- Preserve initialization state in the current counter
3134 if Needs_Finalization (Typ) then
3135 if No (Counter_Id) then
3136 Make_Counter (Comp_Loc);
3137 end if;
3139 Increment_Counter (Comp_Loc);
3140 end if;
3142 elsif Component_Needs_Simple_Initialization (Typ) then
3143 Append_List_To (Stmts,
3144 Build_Assignment
3145 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
3146 end if;
3147 end if;
3149 Next_Non_Pragma (Decl);
3150 end loop;
3151 end if;
3153 -- Process the variant part
3155 if Present (Variant_Part (Comp_List)) then
3156 declare
3157 Variant_Alts : constant List_Id := New_List;
3158 Var_Loc : Source_Ptr;
3159 Variant : Node_Id;
3161 begin
3162 Variant :=
3163 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3164 while Present (Variant) loop
3165 Var_Loc := Sloc (Variant);
3166 Append_To (Variant_Alts,
3167 Make_Case_Statement_Alternative (Var_Loc,
3168 Discrete_Choices =>
3169 New_Copy_List (Discrete_Choices (Variant)),
3170 Statements =>
3171 Build_Init_Statements (Component_List (Variant))));
3172 Next_Non_Pragma (Variant);
3173 end loop;
3175 -- The expression of the case statement which is a reference
3176 -- to one of the discriminants is replaced by the appropriate
3177 -- formal parameter of the initialization procedure.
3179 Append_To (Stmts,
3180 Make_Case_Statement (Var_Loc,
3181 Expression =>
3182 New_Occurrence_Of (Discriminal (
3183 Entity (Name (Variant_Part (Comp_List)))), Var_Loc),
3184 Alternatives => Variant_Alts));
3185 end;
3186 end if;
3188 -- If no initializations when generated for component declarations
3189 -- corresponding to this Stmts, append a null statement to Stmts to
3190 -- to make it a valid Ada tree.
3192 if Is_Empty_List (Stmts) then
3193 Append (Make_Null_Statement (Loc), Stmts);
3194 end if;
3196 return Stmts;
3198 exception
3199 when RE_Not_Available =>
3200 return Empty_List;
3201 end Build_Init_Statements;
3203 -------------------------
3204 -- Build_Record_Checks --
3205 -------------------------
3207 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
3208 Subtype_Mark_Id : Entity_Id;
3210 procedure Constrain_Array
3211 (SI : Node_Id;
3212 Check_List : List_Id);
3213 -- Apply a list of index constraints to an unconstrained array type.
3214 -- The first parameter is the entity for the resulting subtype.
3215 -- Check_List is a list to which the check actions are appended.
3217 ---------------------
3218 -- Constrain_Array --
3219 ---------------------
3221 procedure Constrain_Array
3222 (SI : Node_Id;
3223 Check_List : List_Id)
3225 C : constant Node_Id := Constraint (SI);
3226 Number_Of_Constraints : Nat := 0;
3227 Index : Node_Id;
3228 S, T : Entity_Id;
3230 procedure Constrain_Index
3231 (Index : Node_Id;
3232 S : Node_Id;
3233 Check_List : List_Id);
3234 -- Process an index constraint in a constrained array declaration.
3235 -- The constraint can be either a subtype name or a range with or
3236 -- without an explicit subtype mark. Index is the corresponding
3237 -- index of the unconstrained array. S is the range expression.
3238 -- Check_List is a list to which the check actions are appended.
3240 ---------------------
3241 -- Constrain_Index --
3242 ---------------------
3244 procedure Constrain_Index
3245 (Index : Node_Id;
3246 S : Node_Id;
3247 Check_List : List_Id)
3249 T : constant Entity_Id := Etype (Index);
3251 begin
3252 if Nkind (S) = N_Range then
3253 Process_Range_Expr_In_Decl (S, T, Check_List => Check_List);
3254 end if;
3255 end Constrain_Index;
3257 -- Start of processing for Constrain_Array
3259 begin
3260 T := Entity (Subtype_Mark (SI));
3262 if Is_Access_Type (T) then
3263 T := Designated_Type (T);
3264 end if;
3266 S := First (Constraints (C));
3268 while Present (S) loop
3269 Number_Of_Constraints := Number_Of_Constraints + 1;
3270 Next (S);
3271 end loop;
3273 -- In either case, the index constraint must provide a discrete
3274 -- range for each index of the array type and the type of each
3275 -- discrete range must be the same as that of the corresponding
3276 -- index. (RM 3.6.1)
3278 S := First (Constraints (C));
3279 Index := First_Index (T);
3280 Analyze (Index);
3282 -- Apply constraints to each index type
3284 for J in 1 .. Number_Of_Constraints loop
3285 Constrain_Index (Index, S, Check_List);
3286 Next (Index);
3287 Next (S);
3288 end loop;
3289 end Constrain_Array;
3291 -- Start of processing for Build_Record_Checks
3293 begin
3294 if Nkind (S) = N_Subtype_Indication then
3295 Find_Type (Subtype_Mark (S));
3296 Subtype_Mark_Id := Entity (Subtype_Mark (S));
3298 -- Remaining processing depends on type
3300 case Ekind (Subtype_Mark_Id) is
3302 when Array_Kind =>
3303 Constrain_Array (S, Check_List);
3305 when others =>
3306 null;
3307 end case;
3308 end if;
3309 end Build_Record_Checks;
3311 -------------------------------------------
3312 -- Component_Needs_Simple_Initialization --
3313 -------------------------------------------
3315 function Component_Needs_Simple_Initialization
3316 (T : Entity_Id) return Boolean
3318 begin
3319 return
3320 Needs_Simple_Initialization (T)
3321 and then not Is_RTE (T, RE_Tag)
3323 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
3325 and then not Is_RTE (T, RE_Interface_Tag);
3326 end Component_Needs_Simple_Initialization;
3328 --------------------------------------
3329 -- Parent_Subtype_Renaming_Discrims --
3330 --------------------------------------
3332 function Parent_Subtype_Renaming_Discrims return Boolean is
3333 De : Entity_Id;
3334 Dp : Entity_Id;
3336 begin
3337 if Base_Type (Rec_Ent) /= Rec_Ent then
3338 return False;
3339 end if;
3341 if Etype (Rec_Ent) = Rec_Ent
3342 or else not Has_Discriminants (Rec_Ent)
3343 or else Is_Constrained (Rec_Ent)
3344 or else Is_Tagged_Type (Rec_Ent)
3345 then
3346 return False;
3347 end if;
3349 -- If there are no explicit stored discriminants we have inherited
3350 -- the root type discriminants so far, so no renamings occurred.
3352 if First_Discriminant (Rec_Ent) =
3353 First_Stored_Discriminant (Rec_Ent)
3354 then
3355 return False;
3356 end if;
3358 -- Check if we have done some trivial renaming of the parent
3359 -- discriminants, i.e. something like
3361 -- type DT (X1, X2: int) is new PT (X1, X2);
3363 De := First_Discriminant (Rec_Ent);
3364 Dp := First_Discriminant (Etype (Rec_Ent));
3365 while Present (De) loop
3366 pragma Assert (Present (Dp));
3368 if Corresponding_Discriminant (De) /= Dp then
3369 return True;
3370 end if;
3372 Next_Discriminant (De);
3373 Next_Discriminant (Dp);
3374 end loop;
3376 return Present (Dp);
3377 end Parent_Subtype_Renaming_Discrims;
3379 ------------------------
3380 -- Requires_Init_Proc --
3381 ------------------------
3383 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3384 Comp_Decl : Node_Id;
3385 Id : Entity_Id;
3386 Typ : Entity_Id;
3388 begin
3389 -- Definitely do not need one if specifically suppressed
3391 if Initialization_Suppressed (Rec_Id) then
3392 return False;
3393 end if;
3395 -- If it is a type derived from a type with unknown discriminants,
3396 -- we cannot build an initialization procedure for it.
3398 if Has_Unknown_Discriminants (Rec_Id)
3399 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3400 then
3401 return False;
3402 end if;
3404 -- Otherwise we need to generate an initialization procedure if
3405 -- Is_CPP_Class is False and at least one of the following applies:
3407 -- 1. Discriminants are present, since they need to be initialized
3408 -- with the appropriate discriminant constraint expressions.
3409 -- However, the discriminant of an unchecked union does not
3410 -- count, since the discriminant is not present.
3412 -- 2. The type is a tagged type, since the implicit Tag component
3413 -- needs to be initialized with a pointer to the dispatch table.
3415 -- 3. The type contains tasks
3417 -- 4. One or more components has an initial value
3419 -- 5. One or more components is for a type which itself requires
3420 -- an initialization procedure.
3422 -- 6. One or more components is a type that requires simple
3423 -- initialization (see Needs_Simple_Initialization), except
3424 -- that types Tag and Interface_Tag are excluded, since fields
3425 -- of these types are initialized by other means.
3427 -- 7. The type is the record type built for a task type (since at
3428 -- the very least, Create_Task must be called)
3430 -- 8. The type is the record type built for a protected type (since
3431 -- at least Initialize_Protection must be called)
3433 -- 9. The type is marked as a public entity. The reason we add this
3434 -- case (even if none of the above apply) is to properly handle
3435 -- Initialize_Scalars. If a package is compiled without an IS
3436 -- pragma, and the client is compiled with an IS pragma, then
3437 -- the client will think an initialization procedure is present
3438 -- and call it, when in fact no such procedure is required, but
3439 -- since the call is generated, there had better be a routine
3440 -- at the other end of the call, even if it does nothing).
3442 -- Note: the reason we exclude the CPP_Class case is because in this
3443 -- case the initialization is performed by the C++ constructors, and
3444 -- the IP is built by Set_CPP_Constructors.
3446 if Is_CPP_Class (Rec_Id) then
3447 return False;
3449 elsif Is_Interface (Rec_Id) then
3450 return False;
3452 elsif (Has_Discriminants (Rec_Id)
3453 and then not Is_Unchecked_Union (Rec_Id))
3454 or else Is_Tagged_Type (Rec_Id)
3455 or else Is_Concurrent_Record_Type (Rec_Id)
3456 or else Has_Task (Rec_Id)
3457 then
3458 return True;
3459 end if;
3461 Id := First_Component (Rec_Id);
3462 while Present (Id) loop
3463 Comp_Decl := Parent (Id);
3464 Typ := Etype (Id);
3466 if Present (Expression (Comp_Decl))
3467 or else Has_Non_Null_Base_Init_Proc (Typ)
3468 or else Component_Needs_Simple_Initialization (Typ)
3469 then
3470 return True;
3471 end if;
3473 Next_Component (Id);
3474 end loop;
3476 -- As explained above, a record initialization procedure is needed
3477 -- for public types in case Initialize_Scalars applies to a client.
3478 -- However, such a procedure is not needed in the case where either
3479 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3480 -- applies. No_Initialize_Scalars excludes the possibility of using
3481 -- Initialize_Scalars in any partition, and No_Default_Initialization
3482 -- implies that no initialization should ever be done for objects of
3483 -- the type, so is incompatible with Initialize_Scalars.
3485 if not Restriction_Active (No_Initialize_Scalars)
3486 and then not Restriction_Active (No_Default_Initialization)
3487 and then Is_Public (Rec_Id)
3488 then
3489 return True;
3490 end if;
3492 return False;
3493 end Requires_Init_Proc;
3495 -- Start of processing for Build_Record_Init_Proc
3497 begin
3498 -- Check for value type, which means no initialization required
3500 Rec_Type := Defining_Identifier (N);
3502 if Is_Value_Type (Rec_Type) then
3503 return;
3504 end if;
3506 -- This may be full declaration of a private type, in which case
3507 -- the visible entity is a record, and the private entity has been
3508 -- exchanged with it in the private part of the current package.
3509 -- The initialization procedure is built for the record type, which
3510 -- is retrievable from the private entity.
3512 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3513 Rec_Type := Underlying_Type (Rec_Type);
3514 end if;
3516 -- If we have a variant record with restriction No_Implicit_Conditionals
3517 -- in effect, then we skip building the procedure. This is safe because
3518 -- if we can see the restriction, so can any caller, calls to initialize
3519 -- such records are not allowed for variant records if this restriction
3520 -- is active.
3522 if Has_Variant_Part (Rec_Type)
3523 and then Restriction_Active (No_Implicit_Conditionals)
3524 then
3525 return;
3526 end if;
3528 -- If there are discriminants, build the discriminant map to replace
3529 -- discriminants by their discriminals in complex bound expressions.
3530 -- These only arise for the corresponding records of synchronized types.
3532 if Is_Concurrent_Record_Type (Rec_Type)
3533 and then Has_Discriminants (Rec_Type)
3534 then
3535 declare
3536 Disc : Entity_Id;
3537 begin
3538 Disc := First_Discriminant (Rec_Type);
3539 while Present (Disc) loop
3540 Append_Elmt (Disc, Discr_Map);
3541 Append_Elmt (Discriminal (Disc), Discr_Map);
3542 Next_Discriminant (Disc);
3543 end loop;
3544 end;
3545 end if;
3547 -- Derived types that have no type extension can use the initialization
3548 -- procedure of their parent and do not need a procedure of their own.
3549 -- This is only correct if there are no representation clauses for the
3550 -- type or its parent, and if the parent has in fact been frozen so
3551 -- that its initialization procedure exists.
3553 if Is_Derived_Type (Rec_Type)
3554 and then not Is_Tagged_Type (Rec_Type)
3555 and then not Is_Unchecked_Union (Rec_Type)
3556 and then not Has_New_Non_Standard_Rep (Rec_Type)
3557 and then not Parent_Subtype_Renaming_Discrims
3558 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3559 then
3560 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3562 -- Otherwise if we need an initialization procedure, then build one,
3563 -- mark it as public and inlinable and as having a completion.
3565 elsif Requires_Init_Proc (Rec_Type)
3566 or else Is_Unchecked_Union (Rec_Type)
3567 then
3568 Proc_Id :=
3569 Make_Defining_Identifier (Loc,
3570 Chars => Make_Init_Proc_Name (Rec_Type));
3572 -- If No_Default_Initialization restriction is active, then we don't
3573 -- want to build an init_proc, but we need to mark that an init_proc
3574 -- would be needed if this restriction was not active (so that we can
3575 -- detect attempts to call it), so set a dummy init_proc in place.
3577 if Restriction_Active (No_Default_Initialization) then
3578 Set_Init_Proc (Rec_Type, Proc_Id);
3579 return;
3580 end if;
3582 Build_Offset_To_Top_Functions;
3583 Build_CPP_Init_Procedure;
3584 Build_Init_Procedure;
3585 Set_Is_Public (Proc_Id, Is_Public (Rec_Ent));
3587 -- The initialization of protected records is not worth inlining.
3588 -- In addition, when compiled for another unit for inlining purposes,
3589 -- it may make reference to entities that have not been elaborated
3590 -- yet. The initialization of controlled records contains a nested
3591 -- clean-up procedure that makes it impractical to inline as well,
3592 -- and leads to undefined symbols if inlined in a different unit.
3593 -- Similar considerations apply to task types.
3595 if not Is_Concurrent_Type (Rec_Type)
3596 and then not Has_Task (Rec_Type)
3597 and then not Needs_Finalization (Rec_Type)
3598 then
3599 Set_Is_Inlined (Proc_Id);
3600 end if;
3602 Set_Is_Internal (Proc_Id);
3603 Set_Has_Completion (Proc_Id);
3605 if not Debug_Generated_Code then
3606 Set_Debug_Info_Off (Proc_Id);
3607 end if;
3609 declare
3610 Agg : constant Node_Id :=
3611 Build_Equivalent_Record_Aggregate (Rec_Type);
3613 procedure Collect_Itypes (Comp : Node_Id);
3614 -- Generate references to itypes in the aggregate, because
3615 -- the first use of the aggregate may be in a nested scope.
3617 --------------------
3618 -- Collect_Itypes --
3619 --------------------
3621 procedure Collect_Itypes (Comp : Node_Id) is
3622 Ref : Node_Id;
3623 Sub_Aggr : Node_Id;
3624 Typ : constant Entity_Id := Etype (Comp);
3626 begin
3627 if Is_Array_Type (Typ) and then Is_Itype (Typ) then
3628 Ref := Make_Itype_Reference (Loc);
3629 Set_Itype (Ref, Typ);
3630 Append_Freeze_Action (Rec_Type, Ref);
3632 Ref := Make_Itype_Reference (Loc);
3633 Set_Itype (Ref, Etype (First_Index (Typ)));
3634 Append_Freeze_Action (Rec_Type, Ref);
3636 Sub_Aggr := First (Expressions (Comp));
3638 -- Recurse on nested arrays
3640 while Present (Sub_Aggr) loop
3641 Collect_Itypes (Sub_Aggr);
3642 Next (Sub_Aggr);
3643 end loop;
3644 end if;
3645 end Collect_Itypes;
3647 begin
3648 -- If there is a static initialization aggregate for the type,
3649 -- generate itype references for the types of its (sub)components,
3650 -- to prevent out-of-scope errors in the resulting tree.
3651 -- The aggregate may have been rewritten as a Raise node, in which
3652 -- case there are no relevant itypes.
3654 if Present (Agg) and then Nkind (Agg) = N_Aggregate then
3655 Set_Static_Initialization (Proc_Id, Agg);
3657 declare
3658 Comp : Node_Id;
3659 begin
3660 Comp := First (Component_Associations (Agg));
3661 while Present (Comp) loop
3662 Collect_Itypes (Expression (Comp));
3663 Next (Comp);
3664 end loop;
3665 end;
3666 end if;
3667 end;
3668 end if;
3669 end Build_Record_Init_Proc;
3671 --------------------------------
3672 -- Build_Record_Invariant_Proc --
3673 --------------------------------
3675 function Build_Record_Invariant_Proc
3676 (R_Type : Entity_Id;
3677 Nod : Node_Id) return Node_Id
3679 Loc : constant Source_Ptr := Sloc (Nod);
3681 Object_Name : constant Name_Id := New_Internal_Name ('I');
3682 -- Name for argument of invariant procedure
3684 Object_Entity : constant Node_Id :=
3685 Make_Defining_Identifier (Loc, Object_Name);
3686 -- The procedure declaration entity for the argument
3688 Invariant_Found : Boolean;
3689 -- Set if any component needs an invariant check.
3691 Proc_Id : Entity_Id;
3692 Proc_Body : Node_Id;
3693 Stmts : List_Id;
3694 Type_Def : Node_Id;
3696 function Build_Invariant_Checks (Comp_List : Node_Id) return List_Id;
3697 -- Recursive procedure that generates a list of checks for components
3698 -- that need it, and recurses through variant parts when present.
3700 function Build_Component_Invariant_Call (Comp : Entity_Id)
3701 return Node_Id;
3702 -- Build call to invariant procedure for a record component.
3704 ------------------------------------
3705 -- Build_Component_Invariant_Call --
3706 ------------------------------------
3708 function Build_Component_Invariant_Call (Comp : Entity_Id)
3709 return Node_Id
3711 Sel_Comp : Node_Id;
3712 Typ : Entity_Id;
3713 Call : Node_Id;
3715 begin
3716 Invariant_Found := True;
3717 Typ := Etype (Comp);
3719 Sel_Comp :=
3720 Make_Selected_Component (Loc,
3721 Prefix => New_Occurrence_Of (Object_Entity, Loc),
3722 Selector_Name => New_Occurrence_Of (Comp, Loc));
3724 if Is_Access_Type (Typ) then
3726 -- If the access component designates a type with an invariant,
3727 -- the check applies to the designated object. The access type
3728 -- itself may have an invariant, in which case it applies to the
3729 -- access value directly.
3731 -- Note: we are assuming that invariants will not occur on both
3732 -- the access type and the type that it designates. This is not
3733 -- really justified but it is hard to imagine that this case will
3734 -- ever cause trouble ???
3736 if not (Has_Invariants (Typ)) then
3737 Sel_Comp := Make_Explicit_Dereference (Loc, Sel_Comp);
3738 Typ := Designated_Type (Typ);
3739 end if;
3740 end if;
3742 -- The aspect is type-specific, so retrieve it from the base type
3744 Call :=
3745 Make_Procedure_Call_Statement (Loc,
3746 Name =>
3747 New_Occurrence_Of (Invariant_Procedure (Base_Type (Typ)), Loc),
3748 Parameter_Associations => New_List (Sel_Comp));
3750 if Is_Access_Type (Etype (Comp)) then
3751 Call :=
3752 Make_If_Statement (Loc,
3753 Condition =>
3754 Make_Op_Ne (Loc,
3755 Left_Opnd => Make_Null (Loc),
3756 Right_Opnd =>
3757 Make_Selected_Component (Loc,
3758 Prefix => New_Occurrence_Of (Object_Entity, Loc),
3759 Selector_Name => New_Occurrence_Of (Comp, Loc))),
3760 Then_Statements => New_List (Call));
3761 end if;
3763 return Call;
3764 end Build_Component_Invariant_Call;
3766 ----------------------------
3767 -- Build_Invariant_Checks --
3768 ----------------------------
3770 function Build_Invariant_Checks (Comp_List : Node_Id) return List_Id is
3771 Decl : Node_Id;
3772 Id : Entity_Id;
3773 Stmts : List_Id;
3775 begin
3776 Stmts := New_List;
3777 Decl := First_Non_Pragma (Component_Items (Comp_List));
3778 while Present (Decl) loop
3779 if Nkind (Decl) = N_Component_Declaration then
3780 Id := Defining_Identifier (Decl);
3782 if Has_Invariants (Etype (Id))
3783 and then In_Open_Scopes (Scope (R_Type))
3784 then
3785 if Has_Unchecked_Union (R_Type) then
3786 Error_Msg_NE
3787 ("invariants cannot be checked on components of "
3788 & "unchecked_union type&?", Decl, R_Type);
3789 return Empty_List;
3791 else
3792 Append_To (Stmts, Build_Component_Invariant_Call (Id));
3793 end if;
3795 elsif Is_Access_Type (Etype (Id))
3796 and then not Is_Access_Constant (Etype (Id))
3797 and then Has_Invariants (Designated_Type (Etype (Id)))
3798 and then In_Open_Scopes (Scope (Designated_Type (Etype (Id))))
3799 then
3800 Append_To (Stmts, Build_Component_Invariant_Call (Id));
3801 end if;
3802 end if;
3804 Next (Decl);
3805 end loop;
3807 if Present (Variant_Part (Comp_List)) then
3808 declare
3809 Variant_Alts : constant List_Id := New_List;
3810 Var_Loc : Source_Ptr;
3811 Variant : Node_Id;
3812 Variant_Stmts : List_Id;
3814 begin
3815 Variant :=
3816 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3817 while Present (Variant) loop
3818 Variant_Stmts :=
3819 Build_Invariant_Checks (Component_List (Variant));
3820 Var_Loc := Sloc (Variant);
3821 Append_To (Variant_Alts,
3822 Make_Case_Statement_Alternative (Var_Loc,
3823 Discrete_Choices =>
3824 New_Copy_List (Discrete_Choices (Variant)),
3825 Statements => Variant_Stmts));
3827 Next_Non_Pragma (Variant);
3828 end loop;
3830 -- The expression in the case statement is the reference to
3831 -- the discriminant of the target object.
3833 Append_To (Stmts,
3834 Make_Case_Statement (Var_Loc,
3835 Expression =>
3836 Make_Selected_Component (Var_Loc,
3837 Prefix => New_Occurrence_Of (Object_Entity, Var_Loc),
3838 Selector_Name => New_Occurrence_Of
3839 (Entity
3840 (Name (Variant_Part (Comp_List))), Var_Loc)),
3841 Alternatives => Variant_Alts));
3842 end;
3843 end if;
3845 return Stmts;
3846 end Build_Invariant_Checks;
3848 -- Start of processing for Build_Record_Invariant_Proc
3850 begin
3851 Invariant_Found := False;
3852 Type_Def := Type_Definition (Parent (R_Type));
3854 if Nkind (Type_Def) = N_Record_Definition
3855 and then not Null_Present (Type_Def)
3856 then
3857 Stmts := Build_Invariant_Checks (Component_List (Type_Def));
3858 else
3859 return Empty;
3860 end if;
3862 if not Invariant_Found then
3863 return Empty;
3864 end if;
3866 -- The name of the invariant procedure reflects the fact that the
3867 -- checks correspond to invariants on the component types. The
3868 -- record type itself may have invariants that will create a separate
3869 -- procedure whose name carries the Invariant suffix.
3871 Proc_Id :=
3872 Make_Defining_Identifier (Loc,
3873 Chars => New_External_Name (Chars (R_Type), "CInvariant"));
3875 Proc_Body :=
3876 Make_Subprogram_Body (Loc,
3877 Specification =>
3878 Make_Procedure_Specification (Loc,
3879 Defining_Unit_Name => Proc_Id,
3880 Parameter_Specifications => New_List (
3881 Make_Parameter_Specification (Loc,
3882 Defining_Identifier => Object_Entity,
3883 Parameter_Type => New_Occurrence_Of (R_Type, Loc)))),
3885 Declarations => Empty_List,
3886 Handled_Statement_Sequence =>
3887 Make_Handled_Sequence_Of_Statements (Loc,
3888 Statements => Stmts));
3890 Set_Ekind (Proc_Id, E_Procedure);
3891 Set_Is_Public (Proc_Id, Is_Public (R_Type));
3892 Set_Is_Internal (Proc_Id);
3893 Set_Has_Completion (Proc_Id);
3895 return Proc_Body;
3896 -- Insert_After (Nod, Proc_Body);
3897 -- Analyze (Proc_Body);
3898 end Build_Record_Invariant_Proc;
3900 ----------------------------
3901 -- Build_Slice_Assignment --
3902 ----------------------------
3904 -- Generates the following subprogram:
3906 -- procedure Assign
3907 -- (Source, Target : Array_Type,
3908 -- Left_Lo, Left_Hi : Index;
3909 -- Right_Lo, Right_Hi : Index;
3910 -- Rev : Boolean)
3911 -- is
3912 -- Li1 : Index;
3913 -- Ri1 : Index;
3915 -- begin
3917 -- if Left_Hi < Left_Lo then
3918 -- return;
3919 -- end if;
3921 -- if Rev then
3922 -- Li1 := Left_Hi;
3923 -- Ri1 := Right_Hi;
3924 -- else
3925 -- Li1 := Left_Lo;
3926 -- Ri1 := Right_Lo;
3927 -- end if;
3929 -- loop
3930 -- Target (Li1) := Source (Ri1);
3932 -- if Rev then
3933 -- exit when Li1 = Left_Lo;
3934 -- Li1 := Index'pred (Li1);
3935 -- Ri1 := Index'pred (Ri1);
3936 -- else
3937 -- exit when Li1 = Left_Hi;
3938 -- Li1 := Index'succ (Li1);
3939 -- Ri1 := Index'succ (Ri1);
3940 -- end if;
3941 -- end loop;
3942 -- end Assign;
3944 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3945 Loc : constant Source_Ptr := Sloc (Typ);
3946 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3948 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
3949 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
3950 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
3951 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
3952 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
3953 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
3954 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
3955 -- Formal parameters of procedure
3957 Proc_Name : constant Entity_Id :=
3958 Make_Defining_Identifier (Loc,
3959 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3961 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3962 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3963 -- Subscripts for left and right sides
3965 Decls : List_Id;
3966 Loops : Node_Id;
3967 Stats : List_Id;
3969 begin
3970 -- Build declarations for indexes
3972 Decls := New_List;
3974 Append_To (Decls,
3975 Make_Object_Declaration (Loc,
3976 Defining_Identifier => Lnn,
3977 Object_Definition =>
3978 New_Occurrence_Of (Index, Loc)));
3980 Append_To (Decls,
3981 Make_Object_Declaration (Loc,
3982 Defining_Identifier => Rnn,
3983 Object_Definition =>
3984 New_Occurrence_Of (Index, Loc)));
3986 Stats := New_List;
3988 -- Build test for empty slice case
3990 Append_To (Stats,
3991 Make_If_Statement (Loc,
3992 Condition =>
3993 Make_Op_Lt (Loc,
3994 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
3995 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3996 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
3998 -- Build initializations for indexes
4000 declare
4001 F_Init : constant List_Id := New_List;
4002 B_Init : constant List_Id := New_List;
4004 begin
4005 Append_To (F_Init,
4006 Make_Assignment_Statement (Loc,
4007 Name => New_Occurrence_Of (Lnn, Loc),
4008 Expression => New_Occurrence_Of (Left_Lo, Loc)));
4010 Append_To (F_Init,
4011 Make_Assignment_Statement (Loc,
4012 Name => New_Occurrence_Of (Rnn, Loc),
4013 Expression => New_Occurrence_Of (Right_Lo, Loc)));
4015 Append_To (B_Init,
4016 Make_Assignment_Statement (Loc,
4017 Name => New_Occurrence_Of (Lnn, Loc),
4018 Expression => New_Occurrence_Of (Left_Hi, Loc)));
4020 Append_To (B_Init,
4021 Make_Assignment_Statement (Loc,
4022 Name => New_Occurrence_Of (Rnn, Loc),
4023 Expression => New_Occurrence_Of (Right_Hi, Loc)));
4025 Append_To (Stats,
4026 Make_If_Statement (Loc,
4027 Condition => New_Occurrence_Of (Rev, Loc),
4028 Then_Statements => B_Init,
4029 Else_Statements => F_Init));
4030 end;
4032 -- Now construct the assignment statement
4034 Loops :=
4035 Make_Loop_Statement (Loc,
4036 Statements => New_List (
4037 Make_Assignment_Statement (Loc,
4038 Name =>
4039 Make_Indexed_Component (Loc,
4040 Prefix => New_Occurrence_Of (Larray, Loc),
4041 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
4042 Expression =>
4043 Make_Indexed_Component (Loc,
4044 Prefix => New_Occurrence_Of (Rarray, Loc),
4045 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
4046 End_Label => Empty);
4048 -- Build the exit condition and increment/decrement statements
4050 declare
4051 F_Ass : constant List_Id := New_List;
4052 B_Ass : constant List_Id := New_List;
4054 begin
4055 Append_To (F_Ass,
4056 Make_Exit_Statement (Loc,
4057 Condition =>
4058 Make_Op_Eq (Loc,
4059 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4060 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
4062 Append_To (F_Ass,
4063 Make_Assignment_Statement (Loc,
4064 Name => New_Occurrence_Of (Lnn, Loc),
4065 Expression =>
4066 Make_Attribute_Reference (Loc,
4067 Prefix =>
4068 New_Occurrence_Of (Index, Loc),
4069 Attribute_Name => Name_Succ,
4070 Expressions => New_List (
4071 New_Occurrence_Of (Lnn, Loc)))));
4073 Append_To (F_Ass,
4074 Make_Assignment_Statement (Loc,
4075 Name => New_Occurrence_Of (Rnn, Loc),
4076 Expression =>
4077 Make_Attribute_Reference (Loc,
4078 Prefix =>
4079 New_Occurrence_Of (Index, Loc),
4080 Attribute_Name => Name_Succ,
4081 Expressions => New_List (
4082 New_Occurrence_Of (Rnn, Loc)))));
4084 Append_To (B_Ass,
4085 Make_Exit_Statement (Loc,
4086 Condition =>
4087 Make_Op_Eq (Loc,
4088 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4089 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
4091 Append_To (B_Ass,
4092 Make_Assignment_Statement (Loc,
4093 Name => New_Occurrence_Of (Lnn, Loc),
4094 Expression =>
4095 Make_Attribute_Reference (Loc,
4096 Prefix =>
4097 New_Occurrence_Of (Index, Loc),
4098 Attribute_Name => Name_Pred,
4099 Expressions => New_List (
4100 New_Occurrence_Of (Lnn, Loc)))));
4102 Append_To (B_Ass,
4103 Make_Assignment_Statement (Loc,
4104 Name => New_Occurrence_Of (Rnn, Loc),
4105 Expression =>
4106 Make_Attribute_Reference (Loc,
4107 Prefix =>
4108 New_Occurrence_Of (Index, Loc),
4109 Attribute_Name => Name_Pred,
4110 Expressions => New_List (
4111 New_Occurrence_Of (Rnn, Loc)))));
4113 Append_To (Statements (Loops),
4114 Make_If_Statement (Loc,
4115 Condition => New_Occurrence_Of (Rev, Loc),
4116 Then_Statements => B_Ass,
4117 Else_Statements => F_Ass));
4118 end;
4120 Append_To (Stats, Loops);
4122 declare
4123 Spec : Node_Id;
4124 Formals : List_Id := New_List;
4126 begin
4127 Formals := New_List (
4128 Make_Parameter_Specification (Loc,
4129 Defining_Identifier => Larray,
4130 Out_Present => True,
4131 Parameter_Type =>
4132 New_Occurrence_Of (Base_Type (Typ), Loc)),
4134 Make_Parameter_Specification (Loc,
4135 Defining_Identifier => Rarray,
4136 Parameter_Type =>
4137 New_Occurrence_Of (Base_Type (Typ), Loc)),
4139 Make_Parameter_Specification (Loc,
4140 Defining_Identifier => Left_Lo,
4141 Parameter_Type =>
4142 New_Occurrence_Of (Index, Loc)),
4144 Make_Parameter_Specification (Loc,
4145 Defining_Identifier => Left_Hi,
4146 Parameter_Type =>
4147 New_Occurrence_Of (Index, Loc)),
4149 Make_Parameter_Specification (Loc,
4150 Defining_Identifier => Right_Lo,
4151 Parameter_Type =>
4152 New_Occurrence_Of (Index, Loc)),
4154 Make_Parameter_Specification (Loc,
4155 Defining_Identifier => Right_Hi,
4156 Parameter_Type =>
4157 New_Occurrence_Of (Index, Loc)));
4159 Append_To (Formals,
4160 Make_Parameter_Specification (Loc,
4161 Defining_Identifier => Rev,
4162 Parameter_Type =>
4163 New_Occurrence_Of (Standard_Boolean, Loc)));
4165 Spec :=
4166 Make_Procedure_Specification (Loc,
4167 Defining_Unit_Name => Proc_Name,
4168 Parameter_Specifications => Formals);
4170 Discard_Node (
4171 Make_Subprogram_Body (Loc,
4172 Specification => Spec,
4173 Declarations => Decls,
4174 Handled_Statement_Sequence =>
4175 Make_Handled_Sequence_Of_Statements (Loc,
4176 Statements => Stats)));
4177 end;
4179 Set_TSS (Typ, Proc_Name);
4180 Set_Is_Pure (Proc_Name);
4181 end Build_Slice_Assignment;
4183 -----------------------------
4184 -- Build_Untagged_Equality --
4185 -----------------------------
4187 procedure Build_Untagged_Equality (Typ : Entity_Id) is
4188 Build_Eq : Boolean;
4189 Comp : Entity_Id;
4190 Decl : Node_Id;
4191 Op : Entity_Id;
4192 Prim : Elmt_Id;
4193 Eq_Op : Entity_Id;
4195 function User_Defined_Eq (T : Entity_Id) return Entity_Id;
4196 -- Check whether the type T has a user-defined primitive equality. If so
4197 -- return it, else return Empty. If true for a component of Typ, we have
4198 -- to build the primitive equality for it.
4200 ---------------------
4201 -- User_Defined_Eq --
4202 ---------------------
4204 function User_Defined_Eq (T : Entity_Id) return Entity_Id is
4205 Prim : Elmt_Id;
4206 Op : Entity_Id;
4208 begin
4209 Op := TSS (T, TSS_Composite_Equality);
4211 if Present (Op) then
4212 return Op;
4213 end if;
4215 Prim := First_Elmt (Collect_Primitive_Operations (T));
4216 while Present (Prim) loop
4217 Op := Node (Prim);
4219 if Chars (Op) = Name_Op_Eq
4220 and then Etype (Op) = Standard_Boolean
4221 and then Etype (First_Formal (Op)) = T
4222 and then Etype (Next_Formal (First_Formal (Op))) = T
4223 then
4224 return Op;
4225 end if;
4227 Next_Elmt (Prim);
4228 end loop;
4230 return Empty;
4231 end User_Defined_Eq;
4233 -- Start of processing for Build_Untagged_Equality
4235 begin
4236 -- If a record component has a primitive equality operation, we must
4237 -- build the corresponding one for the current type.
4239 Build_Eq := False;
4240 Comp := First_Component (Typ);
4241 while Present (Comp) loop
4242 if Is_Record_Type (Etype (Comp))
4243 and then Present (User_Defined_Eq (Etype (Comp)))
4244 then
4245 Build_Eq := True;
4246 end if;
4248 Next_Component (Comp);
4249 end loop;
4251 -- If there is a user-defined equality for the type, we do not create
4252 -- the implicit one.
4254 Prim := First_Elmt (Collect_Primitive_Operations (Typ));
4255 Eq_Op := Empty;
4256 while Present (Prim) loop
4257 if Chars (Node (Prim)) = Name_Op_Eq
4258 and then Comes_From_Source (Node (Prim))
4260 -- Don't we also need to check formal types and return type as in
4261 -- User_Defined_Eq above???
4263 then
4264 Eq_Op := Node (Prim);
4265 Build_Eq := False;
4266 exit;
4267 end if;
4269 Next_Elmt (Prim);
4270 end loop;
4272 -- If the type is derived, inherit the operation, if present, from the
4273 -- parent type. It may have been declared after the type derivation. If
4274 -- the parent type itself is derived, it may have inherited an operation
4275 -- that has itself been overridden, so update its alias and related
4276 -- flags. Ditto for inequality.
4278 if No (Eq_Op) and then Is_Derived_Type (Typ) then
4279 Prim := First_Elmt (Collect_Primitive_Operations (Etype (Typ)));
4280 while Present (Prim) loop
4281 if Chars (Node (Prim)) = Name_Op_Eq then
4282 Copy_TSS (Node (Prim), Typ);
4283 Build_Eq := False;
4285 declare
4286 Op : constant Entity_Id := User_Defined_Eq (Typ);
4287 Eq_Op : constant Entity_Id := Node (Prim);
4288 NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
4290 begin
4291 if Present (Op) then
4292 Set_Alias (Op, Eq_Op);
4293 Set_Is_Abstract_Subprogram
4294 (Op, Is_Abstract_Subprogram (Eq_Op));
4296 if Chars (Next_Entity (Op)) = Name_Op_Ne then
4297 Set_Is_Abstract_Subprogram
4298 (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
4299 end if;
4300 end if;
4301 end;
4303 exit;
4304 end if;
4306 Next_Elmt (Prim);
4307 end loop;
4308 end if;
4310 -- If not inherited and not user-defined, build body as for a type with
4311 -- tagged components.
4313 if Build_Eq then
4314 Decl :=
4315 Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
4316 Op := Defining_Entity (Decl);
4317 Set_TSS (Typ, Op);
4318 Set_Is_Pure (Op);
4320 if Is_Library_Level_Entity (Typ) then
4321 Set_Is_Public (Op);
4322 end if;
4323 end if;
4324 end Build_Untagged_Equality;
4326 -----------------------------------
4327 -- Build_Variant_Record_Equality --
4328 -----------------------------------
4330 -- Generates:
4332 -- function _Equality (X, Y : T) return Boolean is
4333 -- begin
4334 -- -- Compare discriminants
4336 -- if X.D1 /= Y.D1 or else X.D2 /= Y.D2 or else ... then
4337 -- return False;
4338 -- end if;
4340 -- -- Compare components
4342 -- if X.C1 /= Y.C1 or else X.C2 /= Y.C2 or else ... then
4343 -- return False;
4344 -- end if;
4346 -- -- Compare variant part
4348 -- case X.D1 is
4349 -- when V1 =>
4350 -- if X.C2 /= Y.C2 or else X.C3 /= Y.C3 or else ... then
4351 -- return False;
4352 -- end if;
4353 -- ...
4354 -- when Vn =>
4355 -- if X.Cn /= Y.Cn or else ... then
4356 -- return False;
4357 -- end if;
4358 -- end case;
4360 -- return True;
4361 -- end _Equality;
4363 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
4364 Loc : constant Source_Ptr := Sloc (Typ);
4366 F : constant Entity_Id :=
4367 Make_Defining_Identifier (Loc,
4368 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
4370 X : constant Entity_Id := Make_Defining_Identifier (Loc, Name_X);
4371 Y : constant Entity_Id := Make_Defining_Identifier (Loc, Name_Y);
4373 Def : constant Node_Id := Parent (Typ);
4374 Comps : constant Node_Id := Component_List (Type_Definition (Def));
4375 Stmts : constant List_Id := New_List;
4376 Pspecs : constant List_Id := New_List;
4378 begin
4379 -- If we have a variant record with restriction No_Implicit_Conditionals
4380 -- in effect, then we skip building the procedure. This is safe because
4381 -- if we can see the restriction, so can any caller, calls to equality
4382 -- test routines are not allowed for variant records if this restriction
4383 -- is active.
4385 if Restriction_Active (No_Implicit_Conditionals) then
4386 return;
4387 end if;
4389 -- Derived Unchecked_Union types no longer inherit the equality function
4390 -- of their parent.
4392 if Is_Derived_Type (Typ)
4393 and then not Is_Unchecked_Union (Typ)
4394 and then not Has_New_Non_Standard_Rep (Typ)
4395 then
4396 declare
4397 Parent_Eq : constant Entity_Id :=
4398 TSS (Root_Type (Typ), TSS_Composite_Equality);
4399 begin
4400 if Present (Parent_Eq) then
4401 Copy_TSS (Parent_Eq, Typ);
4402 return;
4403 end if;
4404 end;
4405 end if;
4407 Discard_Node (
4408 Make_Subprogram_Body (Loc,
4409 Specification =>
4410 Make_Function_Specification (Loc,
4411 Defining_Unit_Name => F,
4412 Parameter_Specifications => Pspecs,
4413 Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
4414 Declarations => New_List,
4415 Handled_Statement_Sequence =>
4416 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
4418 Append_To (Pspecs,
4419 Make_Parameter_Specification (Loc,
4420 Defining_Identifier => X,
4421 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4423 Append_To (Pspecs,
4424 Make_Parameter_Specification (Loc,
4425 Defining_Identifier => Y,
4426 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4428 -- Unchecked_Unions require additional machinery to support equality.
4429 -- Two extra parameters (A and B) are added to the equality function
4430 -- parameter list for each discriminant of the type, in order to
4431 -- capture the inferred values of the discriminants in equality calls.
4432 -- The names of the parameters match the names of the corresponding
4433 -- discriminant, with an added suffix.
4435 if Is_Unchecked_Union (Typ) then
4436 declare
4437 Discr : Entity_Id;
4438 Discr_Type : Entity_Id;
4439 A, B : Entity_Id;
4440 New_Discrs : Elist_Id;
4442 begin
4443 New_Discrs := New_Elmt_List;
4445 Discr := First_Discriminant (Typ);
4446 while Present (Discr) loop
4447 Discr_Type := Etype (Discr);
4448 A := Make_Defining_Identifier (Loc,
4449 Chars => New_External_Name (Chars (Discr), 'A'));
4451 B := Make_Defining_Identifier (Loc,
4452 Chars => New_External_Name (Chars (Discr), 'B'));
4454 -- Add new parameters to the parameter list
4456 Append_To (Pspecs,
4457 Make_Parameter_Specification (Loc,
4458 Defining_Identifier => A,
4459 Parameter_Type =>
4460 New_Occurrence_Of (Discr_Type, Loc)));
4462 Append_To (Pspecs,
4463 Make_Parameter_Specification (Loc,
4464 Defining_Identifier => B,
4465 Parameter_Type =>
4466 New_Occurrence_Of (Discr_Type, Loc)));
4468 Append_Elmt (A, New_Discrs);
4470 -- Generate the following code to compare each of the inferred
4471 -- discriminants:
4473 -- if a /= b then
4474 -- return False;
4475 -- end if;
4477 Append_To (Stmts,
4478 Make_If_Statement (Loc,
4479 Condition =>
4480 Make_Op_Ne (Loc,
4481 Left_Opnd => New_Occurrence_Of (A, Loc),
4482 Right_Opnd => New_Occurrence_Of (B, Loc)),
4483 Then_Statements => New_List (
4484 Make_Simple_Return_Statement (Loc,
4485 Expression =>
4486 New_Occurrence_Of (Standard_False, Loc)))));
4487 Next_Discriminant (Discr);
4488 end loop;
4490 -- Generate component-by-component comparison. Note that we must
4491 -- propagate the inferred discriminants formals to act as
4492 -- the case statement switch. Their value is added when an
4493 -- equality call on unchecked unions is expanded.
4495 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps, New_Discrs));
4496 end;
4498 -- Normal case (not unchecked union)
4500 else
4501 Append_To (Stmts,
4502 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
4503 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
4504 end if;
4506 Append_To (Stmts,
4507 Make_Simple_Return_Statement (Loc,
4508 Expression => New_Occurrence_Of (Standard_True, Loc)));
4510 Set_TSS (Typ, F);
4511 Set_Is_Pure (F);
4513 if not Debug_Generated_Code then
4514 Set_Debug_Info_Off (F);
4515 end if;
4516 end Build_Variant_Record_Equality;
4518 -----------------------------
4519 -- Check_Stream_Attributes --
4520 -----------------------------
4522 procedure Check_Stream_Attributes (Typ : Entity_Id) is
4523 Comp : Entity_Id;
4524 Par_Read : constant Boolean :=
4525 Stream_Attribute_Available (Typ, TSS_Stream_Read)
4526 and then not Has_Specified_Stream_Read (Typ);
4527 Par_Write : constant Boolean :=
4528 Stream_Attribute_Available (Typ, TSS_Stream_Write)
4529 and then not Has_Specified_Stream_Write (Typ);
4531 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4532 -- Check that Comp has a user-specified Nam stream attribute
4534 ----------------
4535 -- Check_Attr --
4536 ----------------
4538 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4539 begin
4540 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4541 Error_Msg_Name_1 := Nam;
4542 Error_Msg_N
4543 ("|component& in limited extension must have% attribute", Comp);
4544 end if;
4545 end Check_Attr;
4547 -- Start of processing for Check_Stream_Attributes
4549 begin
4550 if Par_Read or else Par_Write then
4551 Comp := First_Component (Typ);
4552 while Present (Comp) loop
4553 if Comes_From_Source (Comp)
4554 and then Original_Record_Component (Comp) = Comp
4555 and then Is_Limited_Type (Etype (Comp))
4556 then
4557 if Par_Read then
4558 Check_Attr (Name_Read, TSS_Stream_Read);
4559 end if;
4561 if Par_Write then
4562 Check_Attr (Name_Write, TSS_Stream_Write);
4563 end if;
4564 end if;
4566 Next_Component (Comp);
4567 end loop;
4568 end if;
4569 end Check_Stream_Attributes;
4571 -----------------------------
4572 -- Expand_Record_Extension --
4573 -----------------------------
4575 -- Add a field _parent at the beginning of the record extension. This is
4576 -- used to implement inheritance. Here are some examples of expansion:
4578 -- 1. no discriminants
4579 -- type T2 is new T1 with null record;
4580 -- gives
4581 -- type T2 is new T1 with record
4582 -- _Parent : T1;
4583 -- end record;
4585 -- 2. renamed discriminants
4586 -- type T2 (B, C : Int) is new T1 (A => B) with record
4587 -- _Parent : T1 (A => B);
4588 -- D : Int;
4589 -- end;
4591 -- 3. inherited discriminants
4592 -- type T2 is new T1 with record -- discriminant A inherited
4593 -- _Parent : T1 (A);
4594 -- D : Int;
4595 -- end;
4597 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
4598 Indic : constant Node_Id := Subtype_Indication (Def);
4599 Loc : constant Source_Ptr := Sloc (Def);
4600 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
4601 Par_Subtype : Entity_Id;
4602 Comp_List : Node_Id;
4603 Comp_Decl : Node_Id;
4604 Parent_N : Node_Id;
4605 D : Entity_Id;
4606 List_Constr : constant List_Id := New_List;
4608 begin
4609 -- Expand_Record_Extension is called directly from the semantics, so
4610 -- we must check to see whether expansion is active before proceeding,
4611 -- because this affects the visibility of selected components in bodies
4612 -- of instances.
4614 if not Expander_Active then
4615 return;
4616 end if;
4618 -- This may be a derivation of an untagged private type whose full
4619 -- view is tagged, in which case the Derived_Type_Definition has no
4620 -- extension part. Build an empty one now.
4622 if No (Rec_Ext_Part) then
4623 Rec_Ext_Part :=
4624 Make_Record_Definition (Loc,
4625 End_Label => Empty,
4626 Component_List => Empty,
4627 Null_Present => True);
4629 Set_Record_Extension_Part (Def, Rec_Ext_Part);
4630 Mark_Rewrite_Insertion (Rec_Ext_Part);
4631 end if;
4633 Comp_List := Component_List (Rec_Ext_Part);
4635 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
4637 -- If the derived type inherits its discriminants the type of the
4638 -- _parent field must be constrained by the inherited discriminants
4640 if Has_Discriminants (T)
4641 and then Nkind (Indic) /= N_Subtype_Indication
4642 and then not Is_Constrained (Entity (Indic))
4643 then
4644 D := First_Discriminant (T);
4645 while Present (D) loop
4646 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
4647 Next_Discriminant (D);
4648 end loop;
4650 Par_Subtype :=
4651 Process_Subtype (
4652 Make_Subtype_Indication (Loc,
4653 Subtype_Mark => New_Occurrence_Of (Entity (Indic), Loc),
4654 Constraint =>
4655 Make_Index_Or_Discriminant_Constraint (Loc,
4656 Constraints => List_Constr)),
4657 Def);
4659 -- Otherwise the original subtype_indication is just what is needed
4661 else
4662 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
4663 end if;
4665 Set_Parent_Subtype (T, Par_Subtype);
4667 Comp_Decl :=
4668 Make_Component_Declaration (Loc,
4669 Defining_Identifier => Parent_N,
4670 Component_Definition =>
4671 Make_Component_Definition (Loc,
4672 Aliased_Present => False,
4673 Subtype_Indication => New_Occurrence_Of (Par_Subtype, Loc)));
4675 if Null_Present (Rec_Ext_Part) then
4676 Set_Component_List (Rec_Ext_Part,
4677 Make_Component_List (Loc,
4678 Component_Items => New_List (Comp_Decl),
4679 Variant_Part => Empty,
4680 Null_Present => False));
4681 Set_Null_Present (Rec_Ext_Part, False);
4683 elsif Null_Present (Comp_List)
4684 or else Is_Empty_List (Component_Items (Comp_List))
4685 then
4686 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4687 Set_Null_Present (Comp_List, False);
4689 else
4690 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4691 end if;
4693 Analyze (Comp_Decl);
4694 end Expand_Record_Extension;
4696 ------------------------------------
4697 -- Expand_N_Full_Type_Declaration --
4698 ------------------------------------
4700 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
4701 procedure Build_Master (Ptr_Typ : Entity_Id);
4702 -- Create the master associated with Ptr_Typ
4704 ------------------
4705 -- Build_Master --
4706 ------------------
4708 procedure Build_Master (Ptr_Typ : Entity_Id) is
4709 Desig_Typ : Entity_Id := Designated_Type (Ptr_Typ);
4711 begin
4712 -- If the designated type is an incomplete view coming from a
4713 -- limited-with'ed package, we need to use the nonlimited view in
4714 -- case it has tasks.
4716 if Ekind (Desig_Typ) in Incomplete_Kind
4717 and then Present (Non_Limited_View (Desig_Typ))
4718 then
4719 Desig_Typ := Non_Limited_View (Desig_Typ);
4720 end if;
4722 -- Anonymous access types are created for the components of the
4723 -- record parameter for an entry declaration. No master is created
4724 -- for such a type.
4726 if Comes_From_Source (N) and then Has_Task (Desig_Typ) then
4727 Build_Master_Entity (Ptr_Typ);
4728 Build_Master_Renaming (Ptr_Typ);
4730 -- Create a class-wide master because a Master_Id must be generated
4731 -- for access-to-limited-class-wide types whose root may be extended
4732 -- with task components.
4734 -- Note: This code covers access-to-limited-interfaces because they
4735 -- can be used to reference tasks implementing them.
4737 elsif Is_Limited_Class_Wide_Type (Desig_Typ)
4738 and then Tasking_Allowed
4740 -- Do not create a class-wide master for types whose convention is
4741 -- Java since these types cannot embed Ada tasks anyway. Note that
4742 -- the following test cannot catch the following case:
4744 -- package java.lang.Object is
4745 -- type Typ is tagged limited private;
4746 -- type Ref is access all Typ'Class;
4747 -- private
4748 -- type Typ is tagged limited ...;
4749 -- pragma Convention (Typ, Java)
4750 -- end;
4752 -- Because the convention appears after we have done the
4753 -- processing for type Ref.
4755 and then Convention (Desig_Typ) /= Convention_Java
4756 and then Convention (Desig_Typ) /= Convention_CIL
4757 then
4758 Build_Class_Wide_Master (Ptr_Typ);
4759 end if;
4760 end Build_Master;
4762 -- Local declarations
4764 Def_Id : constant Entity_Id := Defining_Identifier (N);
4765 B_Id : constant Entity_Id := Base_Type (Def_Id);
4766 FN : Node_Id;
4767 Par_Id : Entity_Id;
4769 -- Start of processing for Expand_N_Full_Type_Declaration
4771 begin
4772 if Is_Access_Type (Def_Id) then
4773 Build_Master (Def_Id);
4775 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
4776 Expand_Access_Protected_Subprogram_Type (N);
4777 end if;
4779 -- Array of anonymous access-to-task pointers
4781 elsif Ada_Version >= Ada_2005
4782 and then Is_Array_Type (Def_Id)
4783 and then Is_Access_Type (Component_Type (Def_Id))
4784 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
4785 then
4786 Build_Master (Component_Type (Def_Id));
4788 elsif Has_Task (Def_Id) then
4789 Expand_Previous_Access_Type (Def_Id);
4791 -- Check the components of a record type or array of records for
4792 -- anonymous access-to-task pointers.
4794 elsif Ada_Version >= Ada_2005
4795 and then (Is_Record_Type (Def_Id)
4796 or else
4797 (Is_Array_Type (Def_Id)
4798 and then Is_Record_Type (Component_Type (Def_Id))))
4799 then
4800 declare
4801 Comp : Entity_Id;
4802 First : Boolean;
4803 M_Id : Entity_Id;
4804 Typ : Entity_Id;
4806 begin
4807 if Is_Array_Type (Def_Id) then
4808 Comp := First_Entity (Component_Type (Def_Id));
4809 else
4810 Comp := First_Entity (Def_Id);
4811 end if;
4813 -- Examine all components looking for anonymous access-to-task
4814 -- types.
4816 First := True;
4817 while Present (Comp) loop
4818 Typ := Etype (Comp);
4820 if Ekind (Typ) = E_Anonymous_Access_Type
4821 and then Has_Task (Available_View (Designated_Type (Typ)))
4822 and then No (Master_Id (Typ))
4823 then
4824 -- Ensure that the record or array type have a _master
4826 if First then
4827 Build_Master_Entity (Def_Id);
4828 Build_Master_Renaming (Typ);
4829 M_Id := Master_Id (Typ);
4831 First := False;
4833 -- Reuse the same master to service any additional types
4835 else
4836 Set_Master_Id (Typ, M_Id);
4837 end if;
4838 end if;
4840 Next_Entity (Comp);
4841 end loop;
4842 end;
4843 end if;
4845 Par_Id := Etype (B_Id);
4847 -- The parent type is private then we need to inherit any TSS operations
4848 -- from the full view.
4850 if Ekind (Par_Id) in Private_Kind
4851 and then Present (Full_View (Par_Id))
4852 then
4853 Par_Id := Base_Type (Full_View (Par_Id));
4854 end if;
4856 if Nkind (Type_Definition (Original_Node (N))) =
4857 N_Derived_Type_Definition
4858 and then not Is_Tagged_Type (Def_Id)
4859 and then Present (Freeze_Node (Par_Id))
4860 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
4861 then
4862 Ensure_Freeze_Node (B_Id);
4863 FN := Freeze_Node (B_Id);
4865 if No (TSS_Elist (FN)) then
4866 Set_TSS_Elist (FN, New_Elmt_List);
4867 end if;
4869 declare
4870 T_E : constant Elist_Id := TSS_Elist (FN);
4871 Elmt : Elmt_Id;
4873 begin
4874 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4875 while Present (Elmt) loop
4876 if Chars (Node (Elmt)) /= Name_uInit then
4877 Append_Elmt (Node (Elmt), T_E);
4878 end if;
4880 Next_Elmt (Elmt);
4881 end loop;
4883 -- If the derived type itself is private with a full view, then
4884 -- associate the full view with the inherited TSS_Elist as well.
4886 if Ekind (B_Id) in Private_Kind
4887 and then Present (Full_View (B_Id))
4888 then
4889 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4890 Set_TSS_Elist
4891 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4892 end if;
4893 end;
4894 end if;
4895 end Expand_N_Full_Type_Declaration;
4897 ---------------------------------
4898 -- Expand_N_Object_Declaration --
4899 ---------------------------------
4901 procedure Expand_N_Object_Declaration (N : Node_Id) is
4902 Def_Id : constant Entity_Id := Defining_Identifier (N);
4903 Expr : constant Node_Id := Expression (N);
4904 Loc : constant Source_Ptr := Sloc (N);
4905 Obj_Def : constant Node_Id := Object_Definition (N);
4906 Typ : constant Entity_Id := Etype (Def_Id);
4907 Base_Typ : constant Entity_Id := Base_Type (Typ);
4908 Expr_Q : Node_Id;
4910 function Build_Equivalent_Aggregate return Boolean;
4911 -- If the object has a constrained discriminated type and no initial
4912 -- value, it may be possible to build an equivalent aggregate instead,
4913 -- and prevent an actual call to the initialization procedure.
4915 procedure Default_Initialize_Object (After : Node_Id);
4916 -- Generate all default initialization actions for object Def_Id. Any
4917 -- new code is inserted after node After.
4919 function Rewrite_As_Renaming return Boolean;
4920 -- Indicate whether to rewrite a declaration with initialization into an
4921 -- object renaming declaration (see below).
4923 --------------------------------
4924 -- Build_Equivalent_Aggregate --
4925 --------------------------------
4927 function Build_Equivalent_Aggregate return Boolean is
4928 Aggr : Node_Id;
4929 Comp : Entity_Id;
4930 Discr : Elmt_Id;
4931 Full_Type : Entity_Id;
4933 begin
4934 Full_Type := Typ;
4936 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
4937 Full_Type := Full_View (Typ);
4938 end if;
4940 -- Only perform this transformation if Elaboration_Code is forbidden
4941 -- or undesirable, and if this is a global entity of a constrained
4942 -- record type.
4944 -- If Initialize_Scalars might be active this transformation cannot
4945 -- be performed either, because it will lead to different semantics
4946 -- or because elaboration code will in fact be created.
4948 if Ekind (Full_Type) /= E_Record_Subtype
4949 or else not Has_Discriminants (Full_Type)
4950 or else not Is_Constrained (Full_Type)
4951 or else Is_Controlled (Full_Type)
4952 or else Is_Limited_Type (Full_Type)
4953 or else not Restriction_Active (No_Initialize_Scalars)
4954 then
4955 return False;
4956 end if;
4958 if Ekind (Current_Scope) = E_Package
4959 and then
4960 (Restriction_Active (No_Elaboration_Code)
4961 or else Is_Preelaborated (Current_Scope))
4962 then
4963 -- Building a static aggregate is possible if the discriminants
4964 -- have static values and the other components have static
4965 -- defaults or none.
4967 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
4968 while Present (Discr) loop
4969 if not Is_OK_Static_Expression (Node (Discr)) then
4970 return False;
4971 end if;
4973 Next_Elmt (Discr);
4974 end loop;
4976 -- Check that initialized components are OK, and that non-
4977 -- initialized components do not require a call to their own
4978 -- initialization procedure.
4980 Comp := First_Component (Full_Type);
4981 while Present (Comp) loop
4982 if Ekind (Comp) = E_Component
4983 and then Present (Expression (Parent (Comp)))
4984 and then
4985 not Is_OK_Static_Expression (Expression (Parent (Comp)))
4986 then
4987 return False;
4989 elsif Has_Non_Null_Base_Init_Proc (Etype (Comp)) then
4990 return False;
4992 end if;
4994 Next_Component (Comp);
4995 end loop;
4997 -- Everything is static, assemble the aggregate, discriminant
4998 -- values first.
5000 Aggr :=
5001 Make_Aggregate (Loc,
5002 Expressions => New_List,
5003 Component_Associations => New_List);
5005 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5006 while Present (Discr) loop
5007 Append_To (Expressions (Aggr), New_Copy (Node (Discr)));
5008 Next_Elmt (Discr);
5009 end loop;
5011 -- Now collect values of initialized components
5013 Comp := First_Component (Full_Type);
5014 while Present (Comp) loop
5015 if Ekind (Comp) = E_Component
5016 and then Present (Expression (Parent (Comp)))
5017 then
5018 Append_To (Component_Associations (Aggr),
5019 Make_Component_Association (Loc,
5020 Choices => New_List (New_Occurrence_Of (Comp, Loc)),
5021 Expression => New_Copy_Tree
5022 (Expression (Parent (Comp)))));
5023 end if;
5025 Next_Component (Comp);
5026 end loop;
5028 -- Finally, box-initialize remaining components
5030 Append_To (Component_Associations (Aggr),
5031 Make_Component_Association (Loc,
5032 Choices => New_List (Make_Others_Choice (Loc)),
5033 Expression => Empty));
5034 Set_Box_Present (Last (Component_Associations (Aggr)));
5035 Set_Expression (N, Aggr);
5037 if Typ /= Full_Type then
5038 Analyze_And_Resolve (Aggr, Full_View (Base_Type (Full_Type)));
5039 Rewrite (Aggr, Unchecked_Convert_To (Typ, Aggr));
5040 Analyze_And_Resolve (Aggr, Typ);
5041 else
5042 Analyze_And_Resolve (Aggr, Full_Type);
5043 end if;
5045 return True;
5047 else
5048 return False;
5049 end if;
5050 end Build_Equivalent_Aggregate;
5052 -------------------------------
5053 -- Default_Initialize_Object --
5054 -------------------------------
5056 procedure Default_Initialize_Object (After : Node_Id) is
5057 function New_Object_Reference return Node_Id;
5058 -- Return a new reference to Def_Id with attributes Assignment_OK and
5059 -- Must_Not_Freeze already set.
5061 --------------------------
5062 -- New_Object_Reference --
5063 --------------------------
5065 function New_Object_Reference return Node_Id is
5066 Obj_Ref : constant Node_Id := New_Occurrence_Of (Def_Id, Loc);
5068 begin
5069 -- The call to the type init proc or [Deep_]Finalize must not
5070 -- freeze the related object as the call is internally generated.
5071 -- This way legal rep clauses that apply to the object will not be
5072 -- flagged. Note that the initialization call may be removed if
5073 -- pragma Import is encountered or moved to the freeze actions of
5074 -- the object because of an address clause.
5076 Set_Assignment_OK (Obj_Ref);
5077 Set_Must_Not_Freeze (Obj_Ref);
5079 return Obj_Ref;
5080 end New_Object_Reference;
5082 -- Local variables
5084 Abrt_Blk : Node_Id;
5085 Abrt_HSS : Node_Id;
5086 Abrt_Id : Entity_Id;
5087 Abrt_Stmts : List_Id;
5088 Aggr_Init : Node_Id;
5089 Comp_Init : List_Id := No_List;
5090 Fin_Call : Node_Id;
5091 Fin_Stmts : List_Id := No_List;
5092 Obj_Init : Node_Id := Empty;
5093 Obj_Ref : Node_Id;
5095 Dummy : Entity_Id;
5096 -- This variable captures a dummy internal entity, see the comment
5097 -- associated with its use.
5099 -- Start of processing for Default_Initialize_Object
5101 begin
5102 -- Default initialization is suppressed for objects that are already
5103 -- known to be imported (i.e. whose declaration specifies the Import
5104 -- aspect). Note that for objects with a pragma Import, we generate
5105 -- initialization here, and then remove it downstream when processing
5106 -- the pragma. It is also suppressed for variables for which a pragma
5107 -- Suppress_Initialization has been explicitly given
5109 if Is_Imported (Def_Id) or else Suppress_Initialization (Def_Id) then
5110 return;
5111 end if;
5113 -- Step 1: Initialize the object
5115 if Needs_Finalization (Typ) and then not No_Initialization (N) then
5116 Obj_Init :=
5117 Make_Init_Call
5118 (Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5119 Typ => Typ);
5120 end if;
5122 -- Step 2: Initialize the components of the object
5124 -- Do not initialize the components if their initialization is
5125 -- prohibited or the type represents a value type in a .NET VM.
5127 if Has_Non_Null_Base_Init_Proc (Typ)
5128 and then not No_Initialization (N)
5129 and then not Initialization_Suppressed (Typ)
5130 and then not Is_Value_Type (Typ)
5131 then
5132 -- Do not initialize the components if No_Default_Initialization
5133 -- applies as the the actual restriction check will occur later
5134 -- when the object is frozen as it is not known yet whether the
5135 -- object is imported or not.
5137 if not Restriction_Active (No_Default_Initialization) then
5139 -- If the values of the components are compile-time known, use
5140 -- their prebuilt aggregate form directly.
5142 Aggr_Init := Static_Initialization (Base_Init_Proc (Typ));
5144 if Present (Aggr_Init) then
5145 Set_Expression
5146 (N, New_Copy_Tree (Aggr_Init, New_Scope => Current_Scope));
5148 -- If type has discriminants, try to build an equivalent
5149 -- aggregate using discriminant values from the declaration.
5150 -- This is a useful optimization, in particular if restriction
5151 -- No_Elaboration_Code is active.
5153 elsif Build_Equivalent_Aggregate then
5154 null;
5156 -- Otherwise invoke the type init proc
5158 else
5159 Obj_Ref := New_Object_Reference;
5161 if Comes_From_Source (Def_Id) then
5162 Initialization_Warning (Obj_Ref);
5163 end if;
5165 Comp_Init := Build_Initialization_Call (Loc, Obj_Ref, Typ);
5166 end if;
5167 end if;
5169 -- Provide a default value if the object needs simple initialization
5170 -- and does not already have an initial value. A generated temporary
5171 -- do not require initialization because it will be assigned later.
5173 elsif Needs_Simple_Initialization
5174 (Typ, Initialize_Scalars
5175 and then No (Following_Address_Clause (N)))
5176 and then not Is_Internal (Def_Id)
5177 and then not Has_Init_Expression (N)
5178 then
5179 Set_No_Initialization (N, False);
5180 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
5181 Analyze_And_Resolve (Expression (N), Typ);
5182 end if;
5184 -- Step 3: Add partial finalization and abort actions, generate:
5186 -- Type_Init_Proc (Obj);
5187 -- begin
5188 -- Deep_Initialize (Obj);
5189 -- exception
5190 -- when others =>
5191 -- Deep_Finalize (Obj, Self => False);
5192 -- raise;
5193 -- end;
5195 -- Step 3a: Build the finalization block (if applicable)
5197 -- The finalization block is required when both the object and its
5198 -- controlled components are to be initialized. The block finalizes
5199 -- the components if the object initialization fails.
5201 if Has_Controlled_Component (Typ)
5202 and then Present (Comp_Init)
5203 and then Present (Obj_Init)
5204 and then not Restriction_Active (No_Exception_Propagation)
5205 then
5206 -- Generate:
5207 -- Type_Init_Proc (Obj);
5209 Fin_Stmts := Comp_Init;
5211 -- Generate:
5212 -- begin
5213 -- Deep_Initialize (Obj);
5214 -- exception
5215 -- when others =>
5216 -- Deep_Finalize (Obj, Self => False);
5217 -- raise;
5218 -- end;
5220 Fin_Call :=
5221 Make_Final_Call
5222 (Obj_Ref => New_Object_Reference,
5223 Typ => Typ,
5224 Skip_Self => True);
5226 if Present (Fin_Call) then
5228 -- Do not emit warnings related to the elaboration order when a
5229 -- controlled object is declared before the body of Finalize is
5230 -- seen.
5232 Set_No_Elaboration_Check (Fin_Call);
5234 Append_To (Fin_Stmts,
5235 Make_Block_Statement (Loc,
5236 Declarations => No_List,
5238 Handled_Statement_Sequence =>
5239 Make_Handled_Sequence_Of_Statements (Loc,
5240 Statements => New_List (Obj_Init),
5242 Exception_Handlers => New_List (
5243 Make_Exception_Handler (Loc,
5244 Exception_Choices => New_List (
5245 Make_Others_Choice (Loc)),
5247 Statements => New_List (
5248 Fin_Call,
5249 Make_Raise_Statement (Loc)))))));
5250 end if;
5252 -- Finalization is not required, the initialization calls are passed
5253 -- to the abort block building circuitry, generate:
5255 -- Type_Init_Proc (Obj);
5256 -- Deep_Initialize (Obj);
5258 else
5259 if Present (Comp_Init) then
5260 Fin_Stmts := Comp_Init;
5261 end if;
5263 if Present (Obj_Init) then
5264 if No (Fin_Stmts) then
5265 Fin_Stmts := New_List;
5266 end if;
5268 Append_To (Fin_Stmts, Obj_Init);
5269 end if;
5270 end if;
5272 -- Step 3b: Build the abort block (if applicable)
5274 -- The abort block is required when aborts are allowed in order to
5275 -- protect both initialization calls.
5277 if Present (Comp_Init) and then Present (Obj_Init) then
5278 if Abort_Allowed then
5280 -- Generate:
5281 -- Abort_Defer;
5283 Prepend_To
5284 (Fin_Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
5286 -- Generate:
5287 -- begin
5288 -- Abort_Defer;
5289 -- <finalization statements>
5290 -- at end
5291 -- Abort_Undefer_Direct;
5292 -- end;
5294 Abrt_HSS :=
5295 Make_Handled_Sequence_Of_Statements (Loc,
5296 Statements => Fin_Stmts,
5297 At_End_Proc =>
5298 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
5300 Abrt_Blk :=
5301 Make_Block_Statement (Loc,
5302 Declarations => No_List,
5303 Handled_Statement_Sequence => Abrt_HSS);
5305 Add_Block_Identifier (Abrt_Blk, Abrt_Id);
5306 Expand_At_End_Handler (Abrt_HSS, Abrt_Id);
5308 Abrt_Stmts := New_List (Abrt_Blk);
5310 -- Abort is not required
5312 else
5313 -- Generate a dummy entity to ensure that the internal symbols
5314 -- are in sync when a unit is compiled with and without aborts.
5315 -- The entity is a block with proper scope and type.
5317 Dummy := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
5318 Set_Etype (Dummy, Standard_Void_Type);
5319 Abrt_Stmts := Fin_Stmts;
5320 end if;
5322 -- No initialization calls present
5324 else
5325 Abrt_Stmts := Fin_Stmts;
5326 end if;
5328 -- Step 4: Insert the whole initialization sequence into the tree
5330 Insert_Actions_After (After, Abrt_Stmts);
5331 end Default_Initialize_Object;
5333 -------------------------
5334 -- Rewrite_As_Renaming --
5335 -------------------------
5337 function Rewrite_As_Renaming return Boolean is
5338 begin
5339 return not Aliased_Present (N)
5340 and then Is_Entity_Name (Expr_Q)
5341 and then Ekind (Entity (Expr_Q)) = E_Variable
5342 and then OK_To_Rename (Entity (Expr_Q))
5343 and then Is_Entity_Name (Obj_Def);
5344 end Rewrite_As_Renaming;
5346 -- Local variables
5348 Next_N : constant Node_Id := Next (N);
5349 Id_Ref : Node_Id;
5351 Init_After : Node_Id := N;
5352 -- Node after which the initialization actions are to be inserted. This
5353 -- is normally N, except for the case of a shared passive variable, in
5354 -- which case the init proc call must be inserted only after the bodies
5355 -- of the shared variable procedures have been seen.
5357 Tag_Assign : Node_Id;
5359 -- Start of processing for Expand_N_Object_Declaration
5361 begin
5362 -- Don't do anything for deferred constants. All proper actions will be
5363 -- expanded during the full declaration.
5365 if No (Expr) and Constant_Present (N) then
5366 return;
5367 end if;
5369 -- The type of the object cannot be abstract. This is diagnosed at the
5370 -- point the object is frozen, which happens after the declaration is
5371 -- fully expanded, so simply return now.
5373 if Is_Abstract_Type (Typ) then
5374 return;
5375 end if;
5377 -- First we do special processing for objects of a tagged type where
5378 -- this is the point at which the type is frozen. The creation of the
5379 -- dispatch table and the initialization procedure have to be deferred
5380 -- to this point, since we reference previously declared primitive
5381 -- subprograms.
5383 -- Force construction of dispatch tables of library level tagged types
5385 if Tagged_Type_Expansion
5386 and then Static_Dispatch_Tables
5387 and then Is_Library_Level_Entity (Def_Id)
5388 and then Is_Library_Level_Tagged_Type (Base_Typ)
5389 and then Ekind_In (Base_Typ, E_Record_Type,
5390 E_Protected_Type,
5391 E_Task_Type)
5392 and then not Has_Dispatch_Table (Base_Typ)
5393 then
5394 declare
5395 New_Nodes : List_Id := No_List;
5397 begin
5398 if Is_Concurrent_Type (Base_Typ) then
5399 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
5400 else
5401 New_Nodes := Make_DT (Base_Typ, N);
5402 end if;
5404 if not Is_Empty_List (New_Nodes) then
5405 Insert_List_Before (N, New_Nodes);
5406 end if;
5407 end;
5408 end if;
5410 -- Make shared memory routines for shared passive variable
5412 if Is_Shared_Passive (Def_Id) then
5413 Init_After := Make_Shared_Var_Procs (N);
5414 end if;
5416 -- If tasks being declared, make sure we have an activation chain
5417 -- defined for the tasks (has no effect if we already have one), and
5418 -- also that a Master variable is established and that the appropriate
5419 -- enclosing construct is established as a task master.
5421 if Has_Task (Typ) then
5422 Build_Activation_Chain_Entity (N);
5423 Build_Master_Entity (Def_Id);
5424 end if;
5426 -- Default initialization required, and no expression present
5428 if No (Expr) then
5430 -- If we have a type with a variant part, the initialization proc
5431 -- will contain implicit tests of the discriminant values, which
5432 -- counts as a violation of the restriction No_Implicit_Conditionals.
5434 if Has_Variant_Part (Typ) then
5435 declare
5436 Msg : Boolean;
5438 begin
5439 Check_Restriction (Msg, No_Implicit_Conditionals, Obj_Def);
5441 if Msg then
5442 Error_Msg_N
5443 ("\initialization of variant record tests discriminants",
5444 Obj_Def);
5445 return;
5446 end if;
5447 end;
5448 end if;
5450 -- For the default initialization case, if we have a private type
5451 -- with invariants, and invariant checks are enabled, then insert an
5452 -- invariant check after the object declaration. Note that it is OK
5453 -- to clobber the object with an invalid value since if the exception
5454 -- is raised, then the object will go out of scope. In the case where
5455 -- an array object is initialized with an aggregate, the expression
5456 -- is removed. Check flag Has_Init_Expression to avoid generating a
5457 -- junk invariant check and flag No_Initialization to avoid checking
5458 -- an uninitialized object such as a compiler temporary used for an
5459 -- aggregate.
5461 if Has_Invariants (Base_Typ)
5462 and then Present (Invariant_Procedure (Base_Typ))
5463 and then not Has_Init_Expression (N)
5464 and then not No_Initialization (N)
5465 then
5466 -- If entity has an address clause or aspect, make invariant
5467 -- call into a freeze action for the explicit freeze node for
5468 -- object. Otherwise insert invariant check after declaration.
5470 if Present (Following_Address_Clause (N))
5471 or else Has_Aspect (Def_Id, Aspect_Address)
5472 then
5473 Ensure_Freeze_Node (Def_Id);
5474 Set_Has_Delayed_Freeze (Def_Id);
5475 Set_Is_Frozen (Def_Id, False);
5476 Append_Freeze_Action (Def_Id,
5477 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
5479 else
5480 Insert_After (N,
5481 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
5482 end if;
5483 end if;
5485 Default_Initialize_Object (Init_After);
5487 -- Generate attribute for Persistent_BSS if needed
5489 if Persistent_BSS_Mode
5490 and then Comes_From_Source (N)
5491 and then Is_Potentially_Persistent_Type (Typ)
5492 and then not Has_Init_Expression (N)
5493 and then Is_Library_Level_Entity (Def_Id)
5494 then
5495 declare
5496 Prag : Node_Id;
5497 begin
5498 Prag :=
5499 Make_Linker_Section_Pragma
5500 (Def_Id, Sloc (N), ".persistent.bss");
5501 Insert_After (N, Prag);
5502 Analyze (Prag);
5503 end;
5504 end if;
5506 -- If access type, then we know it is null if not initialized
5508 if Is_Access_Type (Typ) then
5509 Set_Is_Known_Null (Def_Id);
5510 end if;
5512 -- Explicit initialization present
5514 else
5515 -- Obtain actual expression from qualified expression
5517 if Nkind (Expr) = N_Qualified_Expression then
5518 Expr_Q := Expression (Expr);
5519 else
5520 Expr_Q := Expr;
5521 end if;
5523 -- When we have the appropriate type of aggregate in the expression
5524 -- (it has been determined during analysis of the aggregate by
5525 -- setting the delay flag), let's perform in place assignment and
5526 -- thus avoid creating a temporary.
5528 if Is_Delayed_Aggregate (Expr_Q) then
5529 Convert_Aggr_In_Object_Decl (N);
5531 -- Ada 2005 (AI-318-02): If the initialization expression is a call
5532 -- to a build-in-place function, then access to the declared object
5533 -- must be passed to the function. Currently we limit such functions
5534 -- to those with constrained limited result subtypes, but eventually
5535 -- plan to expand the allowed forms of functions that are treated as
5536 -- build-in-place.
5538 elsif Ada_Version >= Ada_2005
5539 and then Is_Build_In_Place_Function_Call (Expr_Q)
5540 then
5541 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
5543 -- The previous call expands the expression initializing the
5544 -- built-in-place object into further code that will be analyzed
5545 -- later. No further expansion needed here.
5547 return;
5549 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
5550 -- class-wide interface object to ensure that we copy the full
5551 -- object, unless we are targetting a VM where interfaces are handled
5552 -- by VM itself. Note that if the root type of Typ is an ancestor of
5553 -- Expr's type, both types share the same dispatch table and there is
5554 -- no need to displace the pointer.
5556 elsif Is_Interface (Typ)
5558 -- Avoid never-ending recursion because if Equivalent_Type is set
5559 -- then we've done it already and must not do it again.
5561 and then not
5562 (Nkind (Obj_Def) = N_Identifier
5563 and then Present (Equivalent_Type (Entity (Obj_Def))))
5564 then
5565 pragma Assert (Is_Class_Wide_Type (Typ));
5567 -- If the object is a return object of an inherently limited type,
5568 -- which implies build-in-place treatment, bypass the special
5569 -- treatment of class-wide interface initialization below. In this
5570 -- case, the expansion of the return statement will take care of
5571 -- creating the object (via allocator) and initializing it.
5573 if Is_Return_Object (Def_Id) and then Is_Limited_View (Typ) then
5574 null;
5576 elsif Tagged_Type_Expansion then
5577 declare
5578 Iface : constant Entity_Id := Root_Type (Typ);
5579 Expr_N : Node_Id := Expr;
5580 Expr_Typ : Entity_Id;
5581 New_Expr : Node_Id;
5582 Obj_Id : Entity_Id;
5583 Tag_Comp : Node_Id;
5585 begin
5586 -- If the original node of the expression was a conversion
5587 -- to this specific class-wide interface type then restore
5588 -- the original node because we must copy the object before
5589 -- displacing the pointer to reference the secondary tag
5590 -- component. This code must be kept synchronized with the
5591 -- expansion done by routine Expand_Interface_Conversion
5593 if not Comes_From_Source (Expr_N)
5594 and then Nkind (Expr_N) = N_Explicit_Dereference
5595 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
5596 and then Etype (Original_Node (Expr_N)) = Typ
5597 then
5598 Rewrite (Expr_N, Original_Node (Expression (N)));
5599 end if;
5601 -- Avoid expansion of redundant interface conversion
5603 if Is_Interface (Etype (Expr_N))
5604 and then Nkind (Expr_N) = N_Type_Conversion
5605 and then Etype (Expr_N) = Typ
5606 then
5607 Expr_N := Expression (Expr_N);
5608 Set_Expression (N, Expr_N);
5609 end if;
5611 Obj_Id := Make_Temporary (Loc, 'D', Expr_N);
5612 Expr_Typ := Base_Type (Etype (Expr_N));
5614 if Is_Class_Wide_Type (Expr_Typ) then
5615 Expr_Typ := Root_Type (Expr_Typ);
5616 end if;
5618 -- Replace
5619 -- CW : I'Class := Obj;
5620 -- by
5621 -- Tmp : T := Obj;
5622 -- type Ityp is not null access I'Class;
5623 -- CW : I'Class renames Ityp (Tmp.I_Tag'Address).all;
5625 if Comes_From_Source (Expr_N)
5626 and then Nkind (Expr_N) = N_Identifier
5627 and then not Is_Interface (Expr_Typ)
5628 and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
5629 and then (Expr_Typ = Etype (Expr_Typ)
5630 or else not
5631 Is_Variable_Size_Record (Etype (Expr_Typ)))
5632 then
5633 -- Copy the object
5635 Insert_Action (N,
5636 Make_Object_Declaration (Loc,
5637 Defining_Identifier => Obj_Id,
5638 Object_Definition =>
5639 New_Occurrence_Of (Expr_Typ, Loc),
5640 Expression => Relocate_Node (Expr_N)));
5642 -- Statically reference the tag associated with the
5643 -- interface
5645 Tag_Comp :=
5646 Make_Selected_Component (Loc,
5647 Prefix => New_Occurrence_Of (Obj_Id, Loc),
5648 Selector_Name =>
5649 New_Occurrence_Of
5650 (Find_Interface_Tag (Expr_Typ, Iface), Loc));
5652 -- Replace
5653 -- IW : I'Class := Obj;
5654 -- by
5655 -- type Equiv_Record is record ... end record;
5656 -- implicit subtype CW is <Class_Wide_Subtype>;
5657 -- Tmp : CW := CW!(Obj);
5658 -- type Ityp is not null access I'Class;
5659 -- IW : I'Class renames
5660 -- Ityp!(Displace (Temp'Address, I'Tag)).all;
5662 else
5663 -- Generate the equivalent record type and update the
5664 -- subtype indication to reference it.
5666 Expand_Subtype_From_Expr
5667 (N => N,
5668 Unc_Type => Typ,
5669 Subtype_Indic => Obj_Def,
5670 Exp => Expr_N);
5672 if not Is_Interface (Etype (Expr_N)) then
5673 New_Expr := Relocate_Node (Expr_N);
5675 -- For interface types we use 'Address which displaces
5676 -- the pointer to the base of the object (if required)
5678 else
5679 New_Expr :=
5680 Unchecked_Convert_To (Etype (Obj_Def),
5681 Make_Explicit_Dereference (Loc,
5682 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
5683 Make_Attribute_Reference (Loc,
5684 Prefix => Relocate_Node (Expr_N),
5685 Attribute_Name => Name_Address))));
5686 end if;
5688 -- Copy the object
5690 if not Is_Limited_Record (Expr_Typ) then
5691 Insert_Action (N,
5692 Make_Object_Declaration (Loc,
5693 Defining_Identifier => Obj_Id,
5694 Object_Definition =>
5695 New_Occurrence_Of (Etype (Obj_Def), Loc),
5696 Expression => New_Expr));
5698 -- Rename limited type object since they cannot be copied
5699 -- This case occurs when the initialization expression
5700 -- has been previously expanded into a temporary object.
5702 else pragma Assert (not Comes_From_Source (Expr_Q));
5703 Insert_Action (N,
5704 Make_Object_Renaming_Declaration (Loc,
5705 Defining_Identifier => Obj_Id,
5706 Subtype_Mark =>
5707 New_Occurrence_Of (Etype (Obj_Def), Loc),
5708 Name =>
5709 Unchecked_Convert_To
5710 (Etype (Obj_Def), New_Expr)));
5711 end if;
5713 -- Dynamically reference the tag associated with the
5714 -- interface.
5716 Tag_Comp :=
5717 Make_Function_Call (Loc,
5718 Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
5719 Parameter_Associations => New_List (
5720 Make_Attribute_Reference (Loc,
5721 Prefix => New_Occurrence_Of (Obj_Id, Loc),
5722 Attribute_Name => Name_Address),
5723 New_Occurrence_Of
5724 (Node (First_Elmt (Access_Disp_Table (Iface))),
5725 Loc)));
5726 end if;
5728 Rewrite (N,
5729 Make_Object_Renaming_Declaration (Loc,
5730 Defining_Identifier => Make_Temporary (Loc, 'D'),
5731 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
5732 Name =>
5733 Convert_Tag_To_Interface (Typ, Tag_Comp)));
5735 -- If the original entity comes from source, then mark the
5736 -- new entity as needing debug information, even though it's
5737 -- defined by a generated renaming that does not come from
5738 -- source, so that Materialize_Entity will be set on the
5739 -- entity when Debug_Renaming_Declaration is called during
5740 -- analysis.
5742 if Comes_From_Source (Def_Id) then
5743 Set_Debug_Info_Needed (Defining_Identifier (N));
5744 end if;
5746 Analyze (N, Suppress => All_Checks);
5748 -- Replace internal identifier of rewritten node by the
5749 -- identifier found in the sources. We also have to exchange
5750 -- entities containing their defining identifiers to ensure
5751 -- the correct replacement of the object declaration by this
5752 -- object renaming declaration because these identifiers
5753 -- were previously added by Enter_Name to the current scope.
5754 -- We must preserve the homonym chain of the source entity
5755 -- as well. We must also preserve the kind of the entity,
5756 -- which may be a constant. Preserve entity chain because
5757 -- itypes may have been generated already, and the full
5758 -- chain must be preserved for final freezing. Finally,
5759 -- preserve Comes_From_Source setting, so that debugging
5760 -- and cross-referencing information is properly kept, and
5761 -- preserve source location, to prevent spurious errors when
5762 -- entities are declared (they must have their own Sloc).
5764 declare
5765 New_Id : constant Entity_Id := Defining_Identifier (N);
5766 Next_Temp : constant Entity_Id := Next_Entity (New_Id);
5767 S_Flag : constant Boolean :=
5768 Comes_From_Source (Def_Id);
5770 begin
5771 Set_Next_Entity (New_Id, Next_Entity (Def_Id));
5772 Set_Next_Entity (Def_Id, Next_Temp);
5774 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
5775 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
5776 Set_Ekind (Defining_Identifier (N), Ekind (Def_Id));
5777 Set_Sloc (Defining_Identifier (N), Sloc (Def_Id));
5779 Set_Comes_From_Source (Def_Id, False);
5780 Exchange_Entities (Defining_Identifier (N), Def_Id);
5781 Set_Comes_From_Source (Def_Id, S_Flag);
5782 end;
5783 end;
5784 end if;
5786 return;
5788 -- Common case of explicit object initialization
5790 else
5791 -- In most cases, we must check that the initial value meets any
5792 -- constraint imposed by the declared type. However, there is one
5793 -- very important exception to this rule. If the entity has an
5794 -- unconstrained nominal subtype, then it acquired its constraints
5795 -- from the expression in the first place, and not only does this
5796 -- mean that the constraint check is not needed, but an attempt to
5797 -- perform the constraint check can cause order of elaboration
5798 -- problems.
5800 if not Is_Constr_Subt_For_U_Nominal (Typ) then
5802 -- If this is an allocator for an aggregate that has been
5803 -- allocated in place, delay checks until assignments are
5804 -- made, because the discriminants are not initialized.
5806 if Nkind (Expr) = N_Allocator and then No_Initialization (Expr)
5807 then
5808 null;
5810 -- Otherwise apply a constraint check now if no prev error
5812 elsif Nkind (Expr) /= N_Error then
5813 Apply_Constraint_Check (Expr, Typ);
5815 -- Deal with possible range check
5817 if Do_Range_Check (Expr) then
5819 -- If assignment checks are suppressed, turn off flag
5821 if Suppress_Assignment_Checks (N) then
5822 Set_Do_Range_Check (Expr, False);
5824 -- Otherwise generate the range check
5826 else
5827 Generate_Range_Check
5828 (Expr, Typ, CE_Range_Check_Failed);
5829 end if;
5830 end if;
5831 end if;
5832 end if;
5834 -- If the type is controlled and not inherently limited, then
5835 -- the target is adjusted after the copy and attached to the
5836 -- finalization list. However, no adjustment is done in the case
5837 -- where the object was initialized by a call to a function whose
5838 -- result is built in place, since no copy occurred. (Eventually
5839 -- we plan to support in-place function results for some cases
5840 -- of nonlimited types. ???) Similarly, no adjustment is required
5841 -- if we are going to rewrite the object declaration into a
5842 -- renaming declaration.
5844 if Needs_Finalization (Typ)
5845 and then not Is_Limited_View (Typ)
5846 and then not Rewrite_As_Renaming
5847 then
5848 Insert_Action_After (Init_After,
5849 Make_Adjust_Call (
5850 Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5851 Typ => Base_Typ));
5852 end if;
5854 -- For tagged types, when an init value is given, the tag has to
5855 -- be re-initialized separately in order to avoid the propagation
5856 -- of a wrong tag coming from a view conversion unless the type
5857 -- is class wide (in this case the tag comes from the init value).
5858 -- Suppress the tag assignment when VM_Target because VM tags are
5859 -- represented implicitly in objects. Ditto for types that are
5860 -- CPP_CLASS, and for initializations that are aggregates, because
5861 -- they have to have the right tag.
5863 -- The re-assignment of the tag has to be done even if the object
5864 -- is a constant. The assignment must be analyzed after the
5865 -- declaration. If an address clause follows, this is handled as
5866 -- part of the freeze actions for the object, otherwise insert
5867 -- tag assignment here.
5869 Tag_Assign := Make_Tag_Assignment (N);
5871 if Present (Tag_Assign) then
5872 if Present (Following_Address_Clause (N)) then
5873 Ensure_Freeze_Node (Def_Id);
5875 else
5876 Insert_Action_After (Init_After, Tag_Assign);
5877 end if;
5879 -- Handle C++ constructor calls. Note that we do not check that
5880 -- Typ is a tagged type since the equivalent Ada type of a C++
5881 -- class that has no virtual methods is an untagged limited
5882 -- record type.
5884 elsif Is_CPP_Constructor_Call (Expr) then
5886 -- The call to the initialization procedure does NOT freeze the
5887 -- object being initialized.
5889 Id_Ref := New_Occurrence_Of (Def_Id, Loc);
5890 Set_Must_Not_Freeze (Id_Ref);
5891 Set_Assignment_OK (Id_Ref);
5893 Insert_Actions_After (Init_After,
5894 Build_Initialization_Call (Loc, Id_Ref, Typ,
5895 Constructor_Ref => Expr));
5897 -- We remove here the original call to the constructor
5898 -- to avoid its management in the backend
5900 Set_Expression (N, Empty);
5901 return;
5903 -- Handle initialization of limited tagged types
5905 elsif Is_Tagged_Type (Typ)
5906 and then Is_Class_Wide_Type (Typ)
5907 and then Is_Limited_Record (Typ)
5908 then
5909 -- Given that the type is limited we cannot perform a copy. If
5910 -- Expr_Q is the reference to a variable we mark the variable
5911 -- as OK_To_Rename to expand this declaration into a renaming
5912 -- declaration (see bellow).
5914 if Is_Entity_Name (Expr_Q) then
5915 Set_OK_To_Rename (Entity (Expr_Q));
5917 -- If we cannot convert the expression into a renaming we must
5918 -- consider it an internal error because the backend does not
5919 -- have support to handle it.
5921 else
5922 pragma Assert (False);
5923 raise Program_Error;
5924 end if;
5926 -- For discrete types, set the Is_Known_Valid flag if the
5927 -- initializing value is known to be valid. Only do this for
5928 -- source assignments, since otherwise we can end up turning
5929 -- on the known valid flag prematurely from inserted code.
5931 elsif Comes_From_Source (N)
5932 and then Is_Discrete_Type (Typ)
5933 and then Expr_Known_Valid (Expr)
5934 then
5935 Set_Is_Known_Valid (Def_Id);
5937 elsif Is_Access_Type (Typ) then
5939 -- For access types set the Is_Known_Non_Null flag if the
5940 -- initializing value is known to be non-null. We can also set
5941 -- Can_Never_Be_Null if this is a constant.
5943 if Known_Non_Null (Expr) then
5944 Set_Is_Known_Non_Null (Def_Id, True);
5946 if Constant_Present (N) then
5947 Set_Can_Never_Be_Null (Def_Id);
5948 end if;
5949 end if;
5950 end if;
5952 -- If validity checking on copies, validate initial expression.
5953 -- But skip this if declaration is for a generic type, since it
5954 -- makes no sense to validate generic types. Not clear if this
5955 -- can happen for legal programs, but it definitely can arise
5956 -- from previous instantiation errors.
5958 if Validity_Checks_On
5959 and then Validity_Check_Copies
5960 and then not Is_Generic_Type (Etype (Def_Id))
5961 then
5962 Ensure_Valid (Expr);
5963 Set_Is_Known_Valid (Def_Id);
5964 end if;
5965 end if;
5967 -- Cases where the back end cannot handle the initialization directly
5968 -- In such cases, we expand an assignment that will be appropriately
5969 -- handled by Expand_N_Assignment_Statement.
5971 -- The exclusion of the unconstrained case is wrong, but for now it
5972 -- is too much trouble ???
5974 if (Is_Possibly_Unaligned_Slice (Expr)
5975 or else (Is_Possibly_Unaligned_Object (Expr)
5976 and then not Represented_As_Scalar (Etype (Expr))))
5977 and then not (Is_Array_Type (Etype (Expr))
5978 and then not Is_Constrained (Etype (Expr)))
5979 then
5980 declare
5981 Stat : constant Node_Id :=
5982 Make_Assignment_Statement (Loc,
5983 Name => New_Occurrence_Of (Def_Id, Loc),
5984 Expression => Relocate_Node (Expr));
5985 begin
5986 Set_Expression (N, Empty);
5987 Set_No_Initialization (N);
5988 Set_Assignment_OK (Name (Stat));
5989 Set_No_Ctrl_Actions (Stat);
5990 Insert_After_And_Analyze (Init_After, Stat);
5991 end;
5992 end if;
5994 -- Final transformation, if the initializing expression is an entity
5995 -- for a variable with OK_To_Rename set, then we transform:
5997 -- X : typ := expr;
5999 -- into
6001 -- X : typ renames expr
6003 -- provided that X is not aliased. The aliased case has to be
6004 -- excluded in general because Expr will not be aliased in general.
6006 if Rewrite_As_Renaming then
6007 Rewrite (N,
6008 Make_Object_Renaming_Declaration (Loc,
6009 Defining_Identifier => Defining_Identifier (N),
6010 Subtype_Mark => Obj_Def,
6011 Name => Expr_Q));
6013 -- We do not analyze this renaming declaration, because all its
6014 -- components have already been analyzed, and if we were to go
6015 -- ahead and analyze it, we would in effect be trying to generate
6016 -- another declaration of X, which won't do.
6018 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
6019 Set_Analyzed (N);
6021 -- We do need to deal with debug issues for this renaming
6023 -- First, if entity comes from source, then mark it as needing
6024 -- debug information, even though it is defined by a generated
6025 -- renaming that does not come from source.
6027 if Comes_From_Source (Defining_Identifier (N)) then
6028 Set_Debug_Info_Needed (Defining_Identifier (N));
6029 end if;
6031 -- Now call the routine to generate debug info for the renaming
6033 declare
6034 Decl : constant Node_Id := Debug_Renaming_Declaration (N);
6035 begin
6036 if Present (Decl) then
6037 Insert_Action (N, Decl);
6038 end if;
6039 end;
6040 end if;
6041 end if;
6043 if Nkind (N) = N_Object_Declaration
6044 and then Nkind (Obj_Def) = N_Access_Definition
6045 and then not Is_Local_Anonymous_Access (Etype (Def_Id))
6046 then
6047 -- An Ada 2012 stand-alone object of an anonymous access type
6049 declare
6050 Loc : constant Source_Ptr := Sloc (N);
6052 Level : constant Entity_Id :=
6053 Make_Defining_Identifier (Sloc (N),
6054 Chars =>
6055 New_External_Name (Chars (Def_Id), Suffix => "L"));
6057 Level_Expr : Node_Id;
6058 Level_Decl : Node_Id;
6060 begin
6061 Set_Ekind (Level, Ekind (Def_Id));
6062 Set_Etype (Level, Standard_Natural);
6063 Set_Scope (Level, Scope (Def_Id));
6065 if No (Expr) then
6067 -- Set accessibility level of null
6069 Level_Expr :=
6070 Make_Integer_Literal (Loc, Scope_Depth (Standard_Standard));
6072 else
6073 Level_Expr := Dynamic_Accessibility_Level (Expr);
6074 end if;
6076 Level_Decl :=
6077 Make_Object_Declaration (Loc,
6078 Defining_Identifier => Level,
6079 Object_Definition =>
6080 New_Occurrence_Of (Standard_Natural, Loc),
6081 Expression => Level_Expr,
6082 Constant_Present => Constant_Present (N),
6083 Has_Init_Expression => True);
6085 Insert_Action_After (Init_After, Level_Decl);
6087 Set_Extra_Accessibility (Def_Id, Level);
6088 end;
6089 end if;
6091 -- At this point the object is fully initialized by either invoking the
6092 -- related type init proc, routine [Deep_]Initialize or performing in-
6093 -- place assingments for an array object. If the related type is subject
6094 -- to pragma Default_Initial_Condition, add a runtime check to verify
6095 -- the assumption of the pragma. Generate:
6097 -- <Base_Typ>Default_Init_Cond (<Base_Typ> (Def_Id));
6099 -- Note that the check is generated for source objects only
6101 if Comes_From_Source (Def_Id)
6102 and then (Has_Default_Init_Cond (Base_Typ)
6103 or else
6104 Has_Inherited_Default_Init_Cond (Base_Typ))
6105 then
6106 declare
6107 DIC_Call : constant Node_Id :=
6108 Build_Default_Init_Cond_Call (Loc, Def_Id, Base_Typ);
6109 begin
6110 if Present (Next_N) then
6111 Insert_Before_And_Analyze (Next_N, DIC_Call);
6113 -- The object declaration is the last node in a declarative or a
6114 -- statement list.
6116 else
6117 Append_To (List_Containing (N), DIC_Call);
6118 Analyze (DIC_Call);
6119 end if;
6120 end;
6121 end if;
6123 -- Exception on library entity not available
6125 exception
6126 when RE_Not_Available =>
6127 return;
6128 end Expand_N_Object_Declaration;
6130 ---------------------------------
6131 -- Expand_N_Subtype_Indication --
6132 ---------------------------------
6134 -- Add a check on the range of the subtype. The static case is partially
6135 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
6136 -- to check here for the static case in order to avoid generating
6137 -- extraneous expanded code. Also deal with validity checking.
6139 procedure Expand_N_Subtype_Indication (N : Node_Id) is
6140 Ran : constant Node_Id := Range_Expression (Constraint (N));
6141 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6143 begin
6144 if Nkind (Constraint (N)) = N_Range_Constraint then
6145 Validity_Check_Range (Range_Expression (Constraint (N)));
6146 end if;
6148 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
6149 Apply_Range_Check (Ran, Typ);
6150 end if;
6151 end Expand_N_Subtype_Indication;
6153 ---------------------------
6154 -- Expand_N_Variant_Part --
6155 ---------------------------
6157 -- Note: this procedure no longer has any effect. It used to be that we
6158 -- would replace the choices in the last variant by a when others, and
6159 -- also expanded static predicates in variant choices here, but both of
6160 -- those activities were being done too early, since we can't check the
6161 -- choices until the statically predicated subtypes are frozen, which can
6162 -- happen as late as the free point of the record, and we can't change the
6163 -- last choice to an others before checking the choices, which is now done
6164 -- at the freeze point of the record.
6166 procedure Expand_N_Variant_Part (N : Node_Id) is
6167 begin
6168 null;
6169 end Expand_N_Variant_Part;
6171 ---------------------------------
6172 -- Expand_Previous_Access_Type --
6173 ---------------------------------
6175 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
6176 Ptr_Typ : Entity_Id;
6178 begin
6179 -- Find all access types in the current scope whose designated type is
6180 -- Def_Id and build master renamings for them.
6182 Ptr_Typ := First_Entity (Current_Scope);
6183 while Present (Ptr_Typ) loop
6184 if Is_Access_Type (Ptr_Typ)
6185 and then Designated_Type (Ptr_Typ) = Def_Id
6186 and then No (Master_Id (Ptr_Typ))
6187 then
6188 -- Ensure that the designated type has a master
6190 Build_Master_Entity (Def_Id);
6192 -- Private and incomplete types complicate the insertion of master
6193 -- renamings because the access type may precede the full view of
6194 -- the designated type. For this reason, the master renamings are
6195 -- inserted relative to the designated type.
6197 Build_Master_Renaming (Ptr_Typ, Ins_Nod => Parent (Def_Id));
6198 end if;
6200 Next_Entity (Ptr_Typ);
6201 end loop;
6202 end Expand_Previous_Access_Type;
6204 ------------------------
6205 -- Expand_Tagged_Root --
6206 ------------------------
6208 procedure Expand_Tagged_Root (T : Entity_Id) is
6209 Def : constant Node_Id := Type_Definition (Parent (T));
6210 Comp_List : Node_Id;
6211 Comp_Decl : Node_Id;
6212 Sloc_N : Source_Ptr;
6214 begin
6215 if Null_Present (Def) then
6216 Set_Component_List (Def,
6217 Make_Component_List (Sloc (Def),
6218 Component_Items => Empty_List,
6219 Variant_Part => Empty,
6220 Null_Present => True));
6221 end if;
6223 Comp_List := Component_List (Def);
6225 if Null_Present (Comp_List)
6226 or else Is_Empty_List (Component_Items (Comp_List))
6227 then
6228 Sloc_N := Sloc (Comp_List);
6229 else
6230 Sloc_N := Sloc (First (Component_Items (Comp_List)));
6231 end if;
6233 Comp_Decl :=
6234 Make_Component_Declaration (Sloc_N,
6235 Defining_Identifier => First_Tag_Component (T),
6236 Component_Definition =>
6237 Make_Component_Definition (Sloc_N,
6238 Aliased_Present => False,
6239 Subtype_Indication => New_Occurrence_Of (RTE (RE_Tag), Sloc_N)));
6241 if Null_Present (Comp_List)
6242 or else Is_Empty_List (Component_Items (Comp_List))
6243 then
6244 Set_Component_Items (Comp_List, New_List (Comp_Decl));
6245 Set_Null_Present (Comp_List, False);
6247 else
6248 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
6249 end if;
6251 -- We don't Analyze the whole expansion because the tag component has
6252 -- already been analyzed previously. Here we just insure that the tree
6253 -- is coherent with the semantic decoration
6255 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
6257 exception
6258 when RE_Not_Available =>
6259 return;
6260 end Expand_Tagged_Root;
6262 ----------------------
6263 -- Clean_Task_Names --
6264 ----------------------
6266 procedure Clean_Task_Names
6267 (Typ : Entity_Id;
6268 Proc_Id : Entity_Id)
6270 begin
6271 if Has_Task (Typ)
6272 and then not Restriction_Active (No_Implicit_Heap_Allocations)
6273 and then not Global_Discard_Names
6274 and then Tagged_Type_Expansion
6275 then
6276 Set_Uses_Sec_Stack (Proc_Id);
6277 end if;
6278 end Clean_Task_Names;
6280 ------------------------------
6281 -- Expand_Freeze_Array_Type --
6282 ------------------------------
6284 procedure Expand_Freeze_Array_Type (N : Node_Id) is
6285 Typ : constant Entity_Id := Entity (N);
6286 Comp_Typ : constant Entity_Id := Component_Type (Typ);
6287 Base : constant Entity_Id := Base_Type (Typ);
6289 begin
6290 if not Is_Bit_Packed_Array (Typ) then
6292 -- If the component contains tasks, so does the array type. This may
6293 -- not be indicated in the array type because the component may have
6294 -- been a private type at the point of definition. Same if component
6295 -- type is controlled or contains protected objects.
6297 Set_Has_Task (Base, Has_Task (Comp_Typ));
6298 Set_Has_Protected (Base, Has_Protected (Comp_Typ));
6299 Set_Has_Controlled_Component
6300 (Base, Has_Controlled_Component
6301 (Comp_Typ)
6302 or else
6303 Is_Controlled (Comp_Typ));
6305 if No (Init_Proc (Base)) then
6307 -- If this is an anonymous array created for a declaration with
6308 -- an initial value, its init_proc will never be called. The
6309 -- initial value itself may have been expanded into assignments,
6310 -- in which case the object declaration is carries the
6311 -- No_Initialization flag.
6313 if Is_Itype (Base)
6314 and then Nkind (Associated_Node_For_Itype (Base)) =
6315 N_Object_Declaration
6316 and then
6317 (Present (Expression (Associated_Node_For_Itype (Base)))
6318 or else No_Initialization (Associated_Node_For_Itype (Base)))
6319 then
6320 null;
6322 -- We do not need an init proc for string or wide [wide] string,
6323 -- since the only time these need initialization in normalize or
6324 -- initialize scalars mode, and these types are treated specially
6325 -- and do not need initialization procedures.
6327 elsif Is_Standard_String_Type (Base) then
6328 null;
6330 -- Otherwise we have to build an init proc for the subtype
6332 else
6333 Build_Array_Init_Proc (Base, N);
6334 end if;
6335 end if;
6337 if Typ = Base then
6338 if Has_Controlled_Component (Base) then
6339 Build_Controlling_Procs (Base);
6341 if not Is_Limited_Type (Comp_Typ)
6342 and then Number_Dimensions (Typ) = 1
6343 then
6344 Build_Slice_Assignment (Typ);
6345 end if;
6346 end if;
6348 -- Create a finalization master to service the anonymous access
6349 -- components of the array.
6351 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
6352 and then Needs_Finalization (Designated_Type (Comp_Typ))
6353 then
6354 Build_Finalization_Master
6355 (Typ => Comp_Typ,
6356 Ins_Node => Parent (Typ),
6357 Encl_Scope => Scope (Typ));
6358 end if;
6359 end if;
6361 -- For packed case, default initialization, except if the component type
6362 -- is itself a packed structure with an initialization procedure, or
6363 -- initialize/normalize scalars active, and we have a base type, or the
6364 -- type is public, because in that case a client might specify
6365 -- Normalize_Scalars and there better be a public Init_Proc for it.
6367 elsif (Present (Init_Proc (Component_Type (Base)))
6368 and then No (Base_Init_Proc (Base)))
6369 or else (Init_Or_Norm_Scalars and then Base = Typ)
6370 or else Is_Public (Typ)
6371 then
6372 Build_Array_Init_Proc (Base, N);
6373 end if;
6375 if Has_Invariants (Component_Type (Base))
6376 and then Typ = Base
6377 and then In_Open_Scopes (Scope (Component_Type (Base)))
6378 then
6379 -- Generate component invariant checking procedure. This is only
6380 -- relevant if the array type is within the scope of the component
6381 -- type. Otherwise an array object can only be built using the public
6382 -- subprograms for the component type, and calls to those will have
6383 -- invariant checks. The invariant procedure is only generated for
6384 -- a base type, not a subtype.
6386 Insert_Component_Invariant_Checks
6387 (N, Base, Build_Array_Invariant_Proc (Base, N));
6388 end if;
6389 end Expand_Freeze_Array_Type;
6391 -----------------------------------
6392 -- Expand_Freeze_Class_Wide_Type --
6393 -----------------------------------
6395 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id) is
6396 Typ : constant Entity_Id := Entity (N);
6397 Root : constant Entity_Id := Root_Type (Typ);
6399 function Is_C_Derivation (Typ : Entity_Id) return Boolean;
6400 -- Given a type, determine whether it is derived from a C or C++ root
6402 ---------------------
6403 -- Is_C_Derivation --
6404 ---------------------
6406 function Is_C_Derivation (Typ : Entity_Id) return Boolean is
6407 T : Entity_Id := Typ;
6409 begin
6410 loop
6411 if Is_CPP_Class (T)
6412 or else Convention (T) = Convention_C
6413 or else Convention (T) = Convention_CPP
6414 then
6415 return True;
6416 end if;
6418 exit when T = Etype (T);
6420 T := Etype (T);
6421 end loop;
6423 return False;
6424 end Is_C_Derivation;
6426 -- Start of processing for Expand_Freeze_Class_Wide_Type
6428 begin
6429 -- Certain run-time configurations and targets do not provide support
6430 -- for controlled types.
6432 if Restriction_Active (No_Finalization) then
6433 return;
6435 -- Do not create TSS routine Finalize_Address when dispatching calls are
6436 -- disabled since the core of the routine is a dispatching call.
6438 elsif Restriction_Active (No_Dispatching_Calls) then
6439 return;
6441 -- Do not create TSS routine Finalize_Address for concurrent class-wide
6442 -- types. Ignore C, C++, CIL and Java types since it is assumed that the
6443 -- non-Ada side will handle their destruction.
6445 elsif Is_Concurrent_Type (Root)
6446 or else Is_C_Derivation (Root)
6447 or else Convention (Typ) = Convention_CIL
6448 or else Convention (Typ) = Convention_CPP
6449 or else Convention (Typ) = Convention_Java
6450 then
6451 return;
6453 -- Do not create TSS routine Finalize_Address for .NET/JVM because these
6454 -- targets do not support address arithmetic and unchecked conversions.
6456 elsif VM_Target /= No_VM then
6457 return;
6459 -- Do not create TSS routine Finalize_Address when compiling in CodePeer
6460 -- mode since the routine contains an Unchecked_Conversion.
6462 elsif CodePeer_Mode then
6463 return;
6464 end if;
6466 -- Create the body of TSS primitive Finalize_Address. This automatically
6467 -- sets the TSS entry for the class-wide type.
6469 Make_Finalize_Address_Body (Typ);
6470 end Expand_Freeze_Class_Wide_Type;
6472 ------------------------------------
6473 -- Expand_Freeze_Enumeration_Type --
6474 ------------------------------------
6476 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
6477 Typ : constant Entity_Id := Entity (N);
6478 Loc : constant Source_Ptr := Sloc (Typ);
6479 Ent : Entity_Id;
6480 Lst : List_Id;
6481 Num : Nat;
6482 Arr : Entity_Id;
6483 Fent : Entity_Id;
6484 Ityp : Entity_Id;
6485 Is_Contiguous : Boolean;
6486 Pos_Expr : Node_Id;
6487 Last_Repval : Uint;
6489 Func : Entity_Id;
6490 pragma Warnings (Off, Func);
6492 begin
6493 -- Various optimizations possible if given representation is contiguous
6495 Is_Contiguous := True;
6497 Ent := First_Literal (Typ);
6498 Last_Repval := Enumeration_Rep (Ent);
6500 Next_Literal (Ent);
6501 while Present (Ent) loop
6502 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
6503 Is_Contiguous := False;
6504 exit;
6505 else
6506 Last_Repval := Enumeration_Rep (Ent);
6507 end if;
6509 Next_Literal (Ent);
6510 end loop;
6512 if Is_Contiguous then
6513 Set_Has_Contiguous_Rep (Typ);
6514 Ent := First_Literal (Typ);
6515 Num := 1;
6516 Lst := New_List (New_Occurrence_Of (Ent, Sloc (Ent)));
6518 else
6519 -- Build list of literal references
6521 Lst := New_List;
6522 Num := 0;
6524 Ent := First_Literal (Typ);
6525 while Present (Ent) loop
6526 Append_To (Lst, New_Occurrence_Of (Ent, Sloc (Ent)));
6527 Num := Num + 1;
6528 Next_Literal (Ent);
6529 end loop;
6530 end if;
6532 -- Now build an array declaration
6534 -- typA : array (Natural range 0 .. num - 1) of ctype :=
6535 -- (v, v, v, v, v, ....)
6537 -- where ctype is the corresponding integer type. If the representation
6538 -- is contiguous, we only keep the first literal, which provides the
6539 -- offset for Pos_To_Rep computations.
6541 Arr :=
6542 Make_Defining_Identifier (Loc,
6543 Chars => New_External_Name (Chars (Typ), 'A'));
6545 Append_Freeze_Action (Typ,
6546 Make_Object_Declaration (Loc,
6547 Defining_Identifier => Arr,
6548 Constant_Present => True,
6550 Object_Definition =>
6551 Make_Constrained_Array_Definition (Loc,
6552 Discrete_Subtype_Definitions => New_List (
6553 Make_Subtype_Indication (Loc,
6554 Subtype_Mark => New_Occurrence_Of (Standard_Natural, Loc),
6555 Constraint =>
6556 Make_Range_Constraint (Loc,
6557 Range_Expression =>
6558 Make_Range (Loc,
6559 Low_Bound =>
6560 Make_Integer_Literal (Loc, 0),
6561 High_Bound =>
6562 Make_Integer_Literal (Loc, Num - 1))))),
6564 Component_Definition =>
6565 Make_Component_Definition (Loc,
6566 Aliased_Present => False,
6567 Subtype_Indication => New_Occurrence_Of (Typ, Loc))),
6569 Expression =>
6570 Make_Aggregate (Loc,
6571 Expressions => Lst)));
6573 Set_Enum_Pos_To_Rep (Typ, Arr);
6575 -- Now we build the function that converts representation values to
6576 -- position values. This function has the form:
6578 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
6579 -- begin
6580 -- case ityp!(A) is
6581 -- when enum-lit'Enum_Rep => return posval;
6582 -- when enum-lit'Enum_Rep => return posval;
6583 -- ...
6584 -- when others =>
6585 -- [raise Constraint_Error when F "invalid data"]
6586 -- return -1;
6587 -- end case;
6588 -- end;
6590 -- Note: the F parameter determines whether the others case (no valid
6591 -- representation) raises Constraint_Error or returns a unique value
6592 -- of minus one. The latter case is used, e.g. in 'Valid code.
6594 -- Note: the reason we use Enum_Rep values in the case here is to avoid
6595 -- the code generator making inappropriate assumptions about the range
6596 -- of the values in the case where the value is invalid. ityp is a
6597 -- signed or unsigned integer type of appropriate width.
6599 -- Note: if exceptions are not supported, then we suppress the raise
6600 -- and return -1 unconditionally (this is an erroneous program in any
6601 -- case and there is no obligation to raise Constraint_Error here). We
6602 -- also do this if pragma Restrictions (No_Exceptions) is active.
6604 -- Is this right??? What about No_Exception_Propagation???
6606 -- Representations are signed
6608 if Enumeration_Rep (First_Literal (Typ)) < 0 then
6610 -- The underlying type is signed. Reset the Is_Unsigned_Type
6611 -- explicitly, because it might have been inherited from
6612 -- parent type.
6614 Set_Is_Unsigned_Type (Typ, False);
6616 if Esize (Typ) <= Standard_Integer_Size then
6617 Ityp := Standard_Integer;
6618 else
6619 Ityp := Universal_Integer;
6620 end if;
6622 -- Representations are unsigned
6624 else
6625 if Esize (Typ) <= Standard_Integer_Size then
6626 Ityp := RTE (RE_Unsigned);
6627 else
6628 Ityp := RTE (RE_Long_Long_Unsigned);
6629 end if;
6630 end if;
6632 -- The body of the function is a case statement. First collect case
6633 -- alternatives, or optimize the contiguous case.
6635 Lst := New_List;
6637 -- If representation is contiguous, Pos is computed by subtracting
6638 -- the representation of the first literal.
6640 if Is_Contiguous then
6641 Ent := First_Literal (Typ);
6643 if Enumeration_Rep (Ent) = Last_Repval then
6645 -- Another special case: for a single literal, Pos is zero
6647 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
6649 else
6650 Pos_Expr :=
6651 Convert_To (Standard_Integer,
6652 Make_Op_Subtract (Loc,
6653 Left_Opnd =>
6654 Unchecked_Convert_To
6655 (Ityp, Make_Identifier (Loc, Name_uA)),
6656 Right_Opnd =>
6657 Make_Integer_Literal (Loc,
6658 Intval => Enumeration_Rep (First_Literal (Typ)))));
6659 end if;
6661 Append_To (Lst,
6662 Make_Case_Statement_Alternative (Loc,
6663 Discrete_Choices => New_List (
6664 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
6665 Low_Bound =>
6666 Make_Integer_Literal (Loc,
6667 Intval => Enumeration_Rep (Ent)),
6668 High_Bound =>
6669 Make_Integer_Literal (Loc, Intval => Last_Repval))),
6671 Statements => New_List (
6672 Make_Simple_Return_Statement (Loc,
6673 Expression => Pos_Expr))));
6675 else
6676 Ent := First_Literal (Typ);
6677 while Present (Ent) loop
6678 Append_To (Lst,
6679 Make_Case_Statement_Alternative (Loc,
6680 Discrete_Choices => New_List (
6681 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
6682 Intval => Enumeration_Rep (Ent))),
6684 Statements => New_List (
6685 Make_Simple_Return_Statement (Loc,
6686 Expression =>
6687 Make_Integer_Literal (Loc,
6688 Intval => Enumeration_Pos (Ent))))));
6690 Next_Literal (Ent);
6691 end loop;
6692 end if;
6694 -- In normal mode, add the others clause with the test
6696 if not No_Exception_Handlers_Set then
6697 Append_To (Lst,
6698 Make_Case_Statement_Alternative (Loc,
6699 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
6700 Statements => New_List (
6701 Make_Raise_Constraint_Error (Loc,
6702 Condition => Make_Identifier (Loc, Name_uF),
6703 Reason => CE_Invalid_Data),
6704 Make_Simple_Return_Statement (Loc,
6705 Expression =>
6706 Make_Integer_Literal (Loc, -1)))));
6708 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
6709 -- active then return -1 (we cannot usefully raise Constraint_Error in
6710 -- this case). See description above for further details.
6712 else
6713 Append_To (Lst,
6714 Make_Case_Statement_Alternative (Loc,
6715 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
6716 Statements => New_List (
6717 Make_Simple_Return_Statement (Loc,
6718 Expression =>
6719 Make_Integer_Literal (Loc, -1)))));
6720 end if;
6722 -- Now we can build the function body
6724 Fent :=
6725 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
6727 Func :=
6728 Make_Subprogram_Body (Loc,
6729 Specification =>
6730 Make_Function_Specification (Loc,
6731 Defining_Unit_Name => Fent,
6732 Parameter_Specifications => New_List (
6733 Make_Parameter_Specification (Loc,
6734 Defining_Identifier =>
6735 Make_Defining_Identifier (Loc, Name_uA),
6736 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
6737 Make_Parameter_Specification (Loc,
6738 Defining_Identifier =>
6739 Make_Defining_Identifier (Loc, Name_uF),
6740 Parameter_Type =>
6741 New_Occurrence_Of (Standard_Boolean, Loc))),
6743 Result_Definition => New_Occurrence_Of (Standard_Integer, Loc)),
6745 Declarations => Empty_List,
6747 Handled_Statement_Sequence =>
6748 Make_Handled_Sequence_Of_Statements (Loc,
6749 Statements => New_List (
6750 Make_Case_Statement (Loc,
6751 Expression =>
6752 Unchecked_Convert_To
6753 (Ityp, Make_Identifier (Loc, Name_uA)),
6754 Alternatives => Lst))));
6756 Set_TSS (Typ, Fent);
6758 -- Set Pure flag (it will be reset if the current context is not Pure).
6759 -- We also pretend there was a pragma Pure_Function so that for purposes
6760 -- of optimization and constant-folding, we will consider the function
6761 -- Pure even if we are not in a Pure context).
6763 Set_Is_Pure (Fent);
6764 Set_Has_Pragma_Pure_Function (Fent);
6766 -- Unless we are in -gnatD mode, where we are debugging generated code,
6767 -- this is an internal entity for which we don't need debug info.
6769 if not Debug_Generated_Code then
6770 Set_Debug_Info_Off (Fent);
6771 end if;
6773 exception
6774 when RE_Not_Available =>
6775 return;
6776 end Expand_Freeze_Enumeration_Type;
6778 -------------------------------
6779 -- Expand_Freeze_Record_Type --
6780 -------------------------------
6782 procedure Expand_Freeze_Record_Type (N : Node_Id) is
6783 Def_Id : constant Node_Id := Entity (N);
6784 Type_Decl : constant Node_Id := Parent (Def_Id);
6785 Comp : Entity_Id;
6786 Comp_Typ : Entity_Id;
6787 Has_AACC : Boolean;
6788 Predef_List : List_Id;
6790 Renamed_Eq : Node_Id := Empty;
6791 -- Defining unit name for the predefined equality function in the case
6792 -- where the type has a primitive operation that is a renaming of
6793 -- predefined equality (but only if there is also an overriding
6794 -- user-defined equality function). Used to pass this entity from
6795 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
6797 Wrapper_Decl_List : List_Id := No_List;
6798 Wrapper_Body_List : List_Id := No_List;
6800 -- Start of processing for Expand_Freeze_Record_Type
6802 begin
6803 -- Build discriminant checking functions if not a derived type (for
6804 -- derived types that are not tagged types, always use the discriminant
6805 -- checking functions of the parent type). However, for untagged types
6806 -- the derivation may have taken place before the parent was frozen, so
6807 -- we copy explicitly the discriminant checking functions from the
6808 -- parent into the components of the derived type.
6810 if not Is_Derived_Type (Def_Id)
6811 or else Has_New_Non_Standard_Rep (Def_Id)
6812 or else Is_Tagged_Type (Def_Id)
6813 then
6814 Build_Discr_Checking_Funcs (Type_Decl);
6816 elsif Is_Derived_Type (Def_Id)
6817 and then not Is_Tagged_Type (Def_Id)
6819 -- If we have a derived Unchecked_Union, we do not inherit the
6820 -- discriminant checking functions from the parent type since the
6821 -- discriminants are non existent.
6823 and then not Is_Unchecked_Union (Def_Id)
6824 and then Has_Discriminants (Def_Id)
6825 then
6826 declare
6827 Old_Comp : Entity_Id;
6829 begin
6830 Old_Comp :=
6831 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
6832 Comp := First_Component (Def_Id);
6833 while Present (Comp) loop
6834 if Ekind (Comp) = E_Component
6835 and then Chars (Comp) = Chars (Old_Comp)
6836 then
6837 Set_Discriminant_Checking_Func (Comp,
6838 Discriminant_Checking_Func (Old_Comp));
6839 end if;
6841 Next_Component (Old_Comp);
6842 Next_Component (Comp);
6843 end loop;
6844 end;
6845 end if;
6847 if Is_Derived_Type (Def_Id)
6848 and then Is_Limited_Type (Def_Id)
6849 and then Is_Tagged_Type (Def_Id)
6850 then
6851 Check_Stream_Attributes (Def_Id);
6852 end if;
6854 -- Update task, protected, and controlled component flags, because some
6855 -- of the component types may have been private at the point of the
6856 -- record declaration. Detect anonymous access-to-controlled components.
6858 Has_AACC := False;
6860 Comp := First_Component (Def_Id);
6861 while Present (Comp) loop
6862 Comp_Typ := Etype (Comp);
6864 if Has_Task (Comp_Typ) then
6865 Set_Has_Task (Def_Id);
6866 end if;
6868 if Has_Protected (Comp_Typ) then
6869 Set_Has_Protected (Def_Id);
6870 end if;
6872 -- Do not set Has_Controlled_Component on a class-wide equivalent
6873 -- type. See Make_CW_Equivalent_Type.
6875 if not Is_Class_Wide_Equivalent_Type (Def_Id)
6876 and then (Has_Controlled_Component (Comp_Typ)
6877 or else (Chars (Comp) /= Name_uParent
6878 and then Is_Controlled (Comp_Typ)))
6879 then
6880 Set_Has_Controlled_Component (Def_Id);
6881 end if;
6883 -- Non-self-referential anonymous access-to-controlled component
6885 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
6886 and then Needs_Finalization (Designated_Type (Comp_Typ))
6887 and then Designated_Type (Comp_Typ) /= Def_Id
6888 then
6889 Has_AACC := True;
6890 end if;
6892 Next_Component (Comp);
6893 end loop;
6895 -- Handle constructors of untagged CPP_Class types
6897 if not Is_Tagged_Type (Def_Id) and then Is_CPP_Class (Def_Id) then
6898 Set_CPP_Constructors (Def_Id);
6899 end if;
6901 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
6902 -- for regular tagged types as well as for Ada types deriving from a C++
6903 -- Class, but not for tagged types directly corresponding to C++ classes
6904 -- In the later case we assume that it is created in the C++ side and we
6905 -- just use it.
6907 if Is_Tagged_Type (Def_Id) then
6909 -- Add the _Tag component
6911 if Underlying_Type (Etype (Def_Id)) = Def_Id then
6912 Expand_Tagged_Root (Def_Id);
6913 end if;
6915 if Is_CPP_Class (Def_Id) then
6916 Set_All_DT_Position (Def_Id);
6918 -- Create the tag entities with a minimum decoration
6920 if Tagged_Type_Expansion then
6921 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
6922 end if;
6924 Set_CPP_Constructors (Def_Id);
6926 else
6927 if not Building_Static_DT (Def_Id) then
6929 -- Usually inherited primitives are not delayed but the first
6930 -- Ada extension of a CPP_Class is an exception since the
6931 -- address of the inherited subprogram has to be inserted in
6932 -- the new Ada Dispatch Table and this is a freezing action.
6934 -- Similarly, if this is an inherited operation whose parent is
6935 -- not frozen yet, it is not in the DT of the parent, and we
6936 -- generate an explicit freeze node for the inherited operation
6937 -- so it is properly inserted in the DT of the current type.
6939 declare
6940 Elmt : Elmt_Id;
6941 Subp : Entity_Id;
6943 begin
6944 Elmt := First_Elmt (Primitive_Operations (Def_Id));
6945 while Present (Elmt) loop
6946 Subp := Node (Elmt);
6948 if Present (Alias (Subp)) then
6949 if Is_CPP_Class (Etype (Def_Id)) then
6950 Set_Has_Delayed_Freeze (Subp);
6952 elsif Has_Delayed_Freeze (Alias (Subp))
6953 and then not Is_Frozen (Alias (Subp))
6954 then
6955 Set_Is_Frozen (Subp, False);
6956 Set_Has_Delayed_Freeze (Subp);
6957 end if;
6958 end if;
6960 Next_Elmt (Elmt);
6961 end loop;
6962 end;
6963 end if;
6965 -- Unfreeze momentarily the type to add the predefined primitives
6966 -- operations. The reason we unfreeze is so that these predefined
6967 -- operations will indeed end up as primitive operations (which
6968 -- must be before the freeze point).
6970 Set_Is_Frozen (Def_Id, False);
6972 -- Do not add the spec of predefined primitives in case of
6973 -- CPP tagged type derivations that have convention CPP.
6975 if Is_CPP_Class (Root_Type (Def_Id))
6976 and then Convention (Def_Id) = Convention_CPP
6977 then
6978 null;
6980 -- Do not add the spec of predefined primitives in case of
6981 -- CIL and Java tagged types
6983 elsif Convention (Def_Id) = Convention_CIL
6984 or else Convention (Def_Id) = Convention_Java
6985 then
6986 null;
6988 -- Do not add the spec of the predefined primitives if we are
6989 -- compiling under restriction No_Dispatching_Calls.
6991 elsif not Restriction_Active (No_Dispatching_Calls) then
6992 Make_Predefined_Primitive_Specs
6993 (Def_Id, Predef_List, Renamed_Eq);
6994 Insert_List_Before_And_Analyze (N, Predef_List);
6995 end if;
6997 -- Ada 2005 (AI-391): For a nonabstract null extension, create
6998 -- wrapper functions for each nonoverridden inherited function
6999 -- with a controlling result of the type. The wrapper for such
7000 -- a function returns an extension aggregate that invokes the
7001 -- parent function.
7003 if Ada_Version >= Ada_2005
7004 and then not Is_Abstract_Type (Def_Id)
7005 and then Is_Null_Extension (Def_Id)
7006 then
7007 Make_Controlling_Function_Wrappers
7008 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
7009 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
7010 end if;
7012 -- Ada 2005 (AI-251): For a nonabstract type extension, build
7013 -- null procedure declarations for each set of homographic null
7014 -- procedures that are inherited from interface types but not
7015 -- overridden. This is done to ensure that the dispatch table
7016 -- entry associated with such null primitives are properly filled.
7018 if Ada_Version >= Ada_2005
7019 and then Etype (Def_Id) /= Def_Id
7020 and then not Is_Abstract_Type (Def_Id)
7021 and then Has_Interfaces (Def_Id)
7022 then
7023 Insert_Actions (N, Make_Null_Procedure_Specs (Def_Id));
7024 end if;
7026 Set_Is_Frozen (Def_Id);
7027 if not Is_Derived_Type (Def_Id)
7028 or else Is_Tagged_Type (Etype (Def_Id))
7029 then
7030 Set_All_DT_Position (Def_Id);
7032 -- If this is a type derived from an untagged private type whose
7033 -- full view is tagged, the type is marked tagged for layout
7034 -- reasons, but it has no dispatch table.
7036 elsif Is_Derived_Type (Def_Id)
7037 and then Is_Private_Type (Etype (Def_Id))
7038 and then not Is_Tagged_Type (Etype (Def_Id))
7039 then
7040 return;
7041 end if;
7043 -- Create and decorate the tags. Suppress their creation when
7044 -- VM_Target because the dispatching mechanism is handled
7045 -- internally by the VMs.
7047 if Tagged_Type_Expansion then
7048 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
7050 -- Generate dispatch table of locally defined tagged type.
7051 -- Dispatch tables of library level tagged types are built
7052 -- later (see Analyze_Declarations).
7054 if not Building_Static_DT (Def_Id) then
7055 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
7056 end if;
7058 elsif VM_Target /= No_VM then
7059 Append_Freeze_Actions (Def_Id, Make_VM_TSD (Def_Id));
7060 end if;
7062 -- If the type has unknown discriminants, propagate dispatching
7063 -- information to its underlying record view, which does not get
7064 -- its own dispatch table.
7066 if Is_Derived_Type (Def_Id)
7067 and then Has_Unknown_Discriminants (Def_Id)
7068 and then Present (Underlying_Record_View (Def_Id))
7069 then
7070 declare
7071 Rep : constant Entity_Id := Underlying_Record_View (Def_Id);
7072 begin
7073 Set_Access_Disp_Table
7074 (Rep, Access_Disp_Table (Def_Id));
7075 Set_Dispatch_Table_Wrappers
7076 (Rep, Dispatch_Table_Wrappers (Def_Id));
7077 Set_Direct_Primitive_Operations
7078 (Rep, Direct_Primitive_Operations (Def_Id));
7079 end;
7080 end if;
7082 -- Make sure that the primitives Initialize, Adjust and Finalize
7083 -- are Frozen before other TSS subprograms. We don't want them
7084 -- Frozen inside.
7086 if Is_Controlled (Def_Id) then
7087 if not Is_Limited_Type (Def_Id) then
7088 Append_Freeze_Actions (Def_Id,
7089 Freeze_Entity
7090 (Find_Prim_Op (Def_Id, Name_Adjust), Def_Id));
7091 end if;
7093 Append_Freeze_Actions (Def_Id,
7094 Freeze_Entity
7095 (Find_Prim_Op (Def_Id, Name_Initialize), Def_Id));
7097 Append_Freeze_Actions (Def_Id,
7098 Freeze_Entity
7099 (Find_Prim_Op (Def_Id, Name_Finalize), Def_Id));
7100 end if;
7102 -- Freeze rest of primitive operations. There is no need to handle
7103 -- the predefined primitives if we are compiling under restriction
7104 -- No_Dispatching_Calls.
7106 if not Restriction_Active (No_Dispatching_Calls) then
7107 Append_Freeze_Actions
7108 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
7109 end if;
7110 end if;
7112 -- In the untagged case, ever since Ada 83 an equality function must
7113 -- be provided for variant records that are not unchecked unions.
7114 -- In Ada 2012 the equality function composes, and thus must be built
7115 -- explicitly just as for tagged records.
7117 elsif Has_Discriminants (Def_Id)
7118 and then not Is_Limited_Type (Def_Id)
7119 then
7120 declare
7121 Comps : constant Node_Id :=
7122 Component_List (Type_Definition (Type_Decl));
7123 begin
7124 if Present (Comps)
7125 and then Present (Variant_Part (Comps))
7126 then
7127 Build_Variant_Record_Equality (Def_Id);
7128 end if;
7129 end;
7131 -- Otherwise create primitive equality operation (AI05-0123)
7133 -- This is done unconditionally to ensure that tools can be linked
7134 -- properly with user programs compiled with older language versions.
7135 -- In addition, this is needed because "=" composes for bounded strings
7136 -- in all language versions (see Exp_Ch4.Expand_Composite_Equality).
7138 elsif Comes_From_Source (Def_Id)
7139 and then Convention (Def_Id) = Convention_Ada
7140 and then not Is_Limited_Type (Def_Id)
7141 then
7142 Build_Untagged_Equality (Def_Id);
7143 end if;
7145 -- Before building the record initialization procedure, if we are
7146 -- dealing with a concurrent record value type, then we must go through
7147 -- the discriminants, exchanging discriminals between the concurrent
7148 -- type and the concurrent record value type. See the section "Handling
7149 -- of Discriminants" in the Einfo spec for details.
7151 if Is_Concurrent_Record_Type (Def_Id)
7152 and then Has_Discriminants (Def_Id)
7153 then
7154 declare
7155 Ctyp : constant Entity_Id :=
7156 Corresponding_Concurrent_Type (Def_Id);
7157 Conc_Discr : Entity_Id;
7158 Rec_Discr : Entity_Id;
7159 Temp : Entity_Id;
7161 begin
7162 Conc_Discr := First_Discriminant (Ctyp);
7163 Rec_Discr := First_Discriminant (Def_Id);
7164 while Present (Conc_Discr) loop
7165 Temp := Discriminal (Conc_Discr);
7166 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
7167 Set_Discriminal (Rec_Discr, Temp);
7169 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
7170 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
7172 Next_Discriminant (Conc_Discr);
7173 Next_Discriminant (Rec_Discr);
7174 end loop;
7175 end;
7176 end if;
7178 if Has_Controlled_Component (Def_Id) then
7179 Build_Controlling_Procs (Def_Id);
7180 end if;
7182 Adjust_Discriminants (Def_Id);
7184 if Tagged_Type_Expansion or else not Is_Interface (Def_Id) then
7186 -- Do not need init for interfaces on e.g. CIL since they're
7187 -- abstract. Helps operation of peverify (the PE Verify tool).
7189 Build_Record_Init_Proc (Type_Decl, Def_Id);
7190 end if;
7192 -- For tagged type that are not interfaces, build bodies of primitive
7193 -- operations. Note: do this after building the record initialization
7194 -- procedure, since the primitive operations may need the initialization
7195 -- routine. There is no need to add predefined primitives of interfaces
7196 -- because all their predefined primitives are abstract.
7198 if Is_Tagged_Type (Def_Id) and then not Is_Interface (Def_Id) then
7200 -- Do not add the body of predefined primitives in case of CPP tagged
7201 -- type derivations that have convention CPP.
7203 if Is_CPP_Class (Root_Type (Def_Id))
7204 and then Convention (Def_Id) = Convention_CPP
7205 then
7206 null;
7208 -- Do not add the body of predefined primitives in case of CIL and
7209 -- Java tagged types.
7211 elsif Convention (Def_Id) = Convention_CIL
7212 or else Convention (Def_Id) = Convention_Java
7213 then
7214 null;
7216 -- Do not add the body of the predefined primitives if we are
7217 -- compiling under restriction No_Dispatching_Calls or if we are
7218 -- compiling a CPP tagged type.
7220 elsif not Restriction_Active (No_Dispatching_Calls) then
7222 -- Create the body of TSS primitive Finalize_Address. This must
7223 -- be done before the bodies of all predefined primitives are
7224 -- created. If Def_Id is limited, Stream_Input and Stream_Read
7225 -- may produce build-in-place allocations and for those the
7226 -- expander needs Finalize_Address.
7228 Make_Finalize_Address_Body (Def_Id);
7229 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
7230 Append_Freeze_Actions (Def_Id, Predef_List);
7231 end if;
7233 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
7234 -- inherited functions, then add their bodies to the freeze actions.
7236 if Present (Wrapper_Body_List) then
7237 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
7238 end if;
7240 -- Create extra formals for the primitive operations of the type.
7241 -- This must be done before analyzing the body of the initialization
7242 -- procedure, because a self-referential type might call one of these
7243 -- primitives in the body of the init_proc itself.
7245 declare
7246 Elmt : Elmt_Id;
7247 Subp : Entity_Id;
7249 begin
7250 Elmt := First_Elmt (Primitive_Operations (Def_Id));
7251 while Present (Elmt) loop
7252 Subp := Node (Elmt);
7253 if not Has_Foreign_Convention (Subp)
7254 and then not Is_Predefined_Dispatching_Operation (Subp)
7255 then
7256 Create_Extra_Formals (Subp);
7257 end if;
7259 Next_Elmt (Elmt);
7260 end loop;
7261 end;
7262 end if;
7264 -- Create a heterogeneous finalization master to service the anonymous
7265 -- access-to-controlled components of the record type.
7267 if Has_AACC then
7268 declare
7269 Encl_Scope : constant Entity_Id := Scope (Def_Id);
7270 Ins_Node : constant Node_Id := Parent (Def_Id);
7271 Loc : constant Source_Ptr := Sloc (Def_Id);
7272 Fin_Mas_Id : Entity_Id;
7274 Attributes_Set : Boolean := False;
7275 Master_Built : Boolean := False;
7276 -- Two flags which control the creation and initialization of a
7277 -- common heterogeneous master.
7279 begin
7280 Comp := First_Component (Def_Id);
7281 while Present (Comp) loop
7282 Comp_Typ := Etype (Comp);
7284 -- A non-self-referential anonymous access-to-controlled
7285 -- component.
7287 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
7288 and then Needs_Finalization (Designated_Type (Comp_Typ))
7289 and then Designated_Type (Comp_Typ) /= Def_Id
7290 then
7291 if VM_Target = No_VM then
7293 -- Build a homogeneous master for the first anonymous
7294 -- access-to-controlled component. This master may be
7295 -- converted into a heterogeneous collection if more
7296 -- components are to follow.
7298 if not Master_Built then
7299 Master_Built := True;
7301 -- All anonymous access-to-controlled types allocate
7302 -- on the global pool. Note that the finalization
7303 -- master and the associated storage pool must be set
7304 -- on the root type (both are "root type only").
7306 Set_Associated_Storage_Pool
7307 (Root_Type (Comp_Typ), RTE (RE_Global_Pool_Object));
7309 Build_Finalization_Master
7310 (Typ => Root_Type (Comp_Typ),
7311 Ins_Node => Ins_Node,
7312 Encl_Scope => Encl_Scope);
7314 Fin_Mas_Id := Finalization_Master (Comp_Typ);
7316 -- Subsequent anonymous access-to-controlled components
7317 -- reuse the available master.
7319 else
7320 -- All anonymous access-to-controlled types allocate
7321 -- on the global pool. Note that both the finalization
7322 -- master and the associated storage pool must be set
7323 -- on the root type (both are "root type only").
7325 Set_Associated_Storage_Pool
7326 (Root_Type (Comp_Typ), RTE (RE_Global_Pool_Object));
7328 -- Shared the master among multiple components
7330 Set_Finalization_Master
7331 (Root_Type (Comp_Typ), Fin_Mas_Id);
7333 -- Convert the master into a heterogeneous collection.
7334 -- Generate:
7335 -- Set_Is_Heterogeneous (<Fin_Mas_Id>);
7337 if not Attributes_Set then
7338 Attributes_Set := True;
7340 Insert_Action (Ins_Node,
7341 Make_Procedure_Call_Statement (Loc,
7342 Name =>
7343 New_Occurrence_Of
7344 (RTE (RE_Set_Is_Heterogeneous), Loc),
7345 Parameter_Associations => New_List (
7346 New_Occurrence_Of (Fin_Mas_Id, Loc))));
7347 end if;
7348 end if;
7350 -- Since .NET/JVM targets do not support heterogeneous
7351 -- masters, each component must have its own master.
7353 else
7354 Build_Finalization_Master
7355 (Typ => Comp_Typ,
7356 Ins_Node => Ins_Node,
7357 Encl_Scope => Encl_Scope);
7358 end if;
7359 end if;
7361 Next_Component (Comp);
7362 end loop;
7363 end;
7364 end if;
7366 -- Check whether individual components have a defined invariant, and add
7367 -- the corresponding component invariant checks.
7369 -- Do not create an invariant procedure for some internally generated
7370 -- subtypes, in particular those created for objects of a class-wide
7371 -- type. Such types may have components to which invariant apply, but
7372 -- the corresponding checks will be applied when an object of the parent
7373 -- type is constructed.
7375 -- Such objects will show up in a class-wide postcondition, and the
7376 -- invariant will be checked, if necessary, upon return from the
7377 -- enclosing subprogram.
7379 if not Is_Class_Wide_Equivalent_Type (Def_Id) then
7380 Insert_Component_Invariant_Checks
7381 (N, Def_Id, Build_Record_Invariant_Proc (Def_Id, N));
7382 end if;
7383 end Expand_Freeze_Record_Type;
7385 ------------------------------
7386 -- Freeze_Stream_Operations --
7387 ------------------------------
7389 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
7390 Names : constant array (1 .. 4) of TSS_Name_Type :=
7391 (TSS_Stream_Input,
7392 TSS_Stream_Output,
7393 TSS_Stream_Read,
7394 TSS_Stream_Write);
7395 Stream_Op : Entity_Id;
7397 begin
7398 -- Primitive operations of tagged types are frozen when the dispatch
7399 -- table is constructed.
7401 if not Comes_From_Source (Typ) or else Is_Tagged_Type (Typ) then
7402 return;
7403 end if;
7405 for J in Names'Range loop
7406 Stream_Op := TSS (Typ, Names (J));
7408 if Present (Stream_Op)
7409 and then Is_Subprogram (Stream_Op)
7410 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
7411 N_Subprogram_Declaration
7412 and then not Is_Frozen (Stream_Op)
7413 then
7414 Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
7415 end if;
7416 end loop;
7417 end Freeze_Stream_Operations;
7419 -----------------
7420 -- Freeze_Type --
7421 -----------------
7423 -- Full type declarations are expanded at the point at which the type is
7424 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
7425 -- declarations generated by the freezing (e.g. the procedure generated
7426 -- for initialization) are chained in the Actions field list of the freeze
7427 -- node using Append_Freeze_Actions.
7429 function Freeze_Type (N : Node_Id) return Boolean is
7430 Def_Id : constant Entity_Id := Entity (N);
7431 RACW_Seen : Boolean := False;
7432 Result : Boolean := False;
7434 begin
7435 -- Process associated access types needing special processing
7437 if Present (Access_Types_To_Process (N)) then
7438 declare
7439 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
7441 begin
7442 while Present (E) loop
7443 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
7444 Validate_RACW_Primitives (Node (E));
7445 RACW_Seen := True;
7446 end if;
7448 E := Next_Elmt (E);
7449 end loop;
7450 end;
7452 -- If there are RACWs designating this type, make stubs now
7454 if RACW_Seen then
7455 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
7456 end if;
7457 end if;
7459 -- Freeze processing for record types
7461 if Is_Record_Type (Def_Id) then
7462 if Ekind (Def_Id) = E_Record_Type then
7463 Expand_Freeze_Record_Type (N);
7464 elsif Is_Class_Wide_Type (Def_Id) then
7465 Expand_Freeze_Class_Wide_Type (N);
7466 end if;
7468 -- Freeze processing for array types
7470 elsif Is_Array_Type (Def_Id) then
7471 Expand_Freeze_Array_Type (N);
7473 -- Freeze processing for access types
7475 -- For pool-specific access types, find out the pool object used for
7476 -- this type, needs actual expansion of it in some cases. Here are the
7477 -- different cases :
7479 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
7480 -- ---> don't use any storage pool
7482 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
7483 -- Expand:
7484 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
7486 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7487 -- ---> Storage Pool is the specified one
7489 -- See GNAT Pool packages in the Run-Time for more details
7491 elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
7492 declare
7493 Loc : constant Source_Ptr := Sloc (N);
7494 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
7495 Pool_Object : Entity_Id;
7497 Freeze_Action_Typ : Entity_Id;
7499 begin
7500 -- Case 1
7502 -- Rep Clause "for Def_Id'Storage_Size use 0;"
7503 -- ---> don't use any storage pool
7505 if No_Pool_Assigned (Def_Id) then
7506 null;
7508 -- Case 2
7510 -- Rep Clause : for Def_Id'Storage_Size use Expr.
7511 -- ---> Expand:
7512 -- Def_Id__Pool : Stack_Bounded_Pool
7513 -- (Expr, DT'Size, DT'Alignment);
7515 elsif Has_Storage_Size_Clause (Def_Id) then
7516 declare
7517 DT_Size : Node_Id;
7518 DT_Align : Node_Id;
7520 begin
7521 -- For unconstrained composite types we give a size of zero
7522 -- so that the pool knows that it needs a special algorithm
7523 -- for variable size object allocation.
7525 if Is_Composite_Type (Desig_Type)
7526 and then not Is_Constrained (Desig_Type)
7527 then
7528 DT_Size := Make_Integer_Literal (Loc, 0);
7529 DT_Align := Make_Integer_Literal (Loc, Maximum_Alignment);
7531 else
7532 DT_Size :=
7533 Make_Attribute_Reference (Loc,
7534 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7535 Attribute_Name => Name_Max_Size_In_Storage_Elements);
7537 DT_Align :=
7538 Make_Attribute_Reference (Loc,
7539 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7540 Attribute_Name => Name_Alignment);
7541 end if;
7543 Pool_Object :=
7544 Make_Defining_Identifier (Loc,
7545 Chars => New_External_Name (Chars (Def_Id), 'P'));
7547 -- We put the code associated with the pools in the entity
7548 -- that has the later freeze node, usually the access type
7549 -- but it can also be the designated_type; because the pool
7550 -- code requires both those types to be frozen
7552 if Is_Frozen (Desig_Type)
7553 and then (No (Freeze_Node (Desig_Type))
7554 or else Analyzed (Freeze_Node (Desig_Type)))
7555 then
7556 Freeze_Action_Typ := Def_Id;
7558 -- A Taft amendment type cannot get the freeze actions
7559 -- since the full view is not there.
7561 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
7562 and then No (Full_View (Desig_Type))
7563 then
7564 Freeze_Action_Typ := Def_Id;
7566 else
7567 Freeze_Action_Typ := Desig_Type;
7568 end if;
7570 Append_Freeze_Action (Freeze_Action_Typ,
7571 Make_Object_Declaration (Loc,
7572 Defining_Identifier => Pool_Object,
7573 Object_Definition =>
7574 Make_Subtype_Indication (Loc,
7575 Subtype_Mark =>
7576 New_Occurrence_Of
7577 (RTE (RE_Stack_Bounded_Pool), Loc),
7579 Constraint =>
7580 Make_Index_Or_Discriminant_Constraint (Loc,
7581 Constraints => New_List (
7583 -- First discriminant is the Pool Size
7585 New_Occurrence_Of (
7586 Storage_Size_Variable (Def_Id), Loc),
7588 -- Second discriminant is the element size
7590 DT_Size,
7592 -- Third discriminant is the alignment
7594 DT_Align)))));
7595 end;
7597 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
7599 -- Case 3
7601 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7602 -- ---> Storage Pool is the specified one
7604 -- When compiling in Ada 2012 mode, ensure that the accessibility
7605 -- level of the subpool access type is not deeper than that of the
7606 -- pool_with_subpools.
7608 elsif Ada_Version >= Ada_2012
7609 and then Present (Associated_Storage_Pool (Def_Id))
7611 -- Omit this check on .NET/JVM where pools are not supported
7613 and then VM_Target = No_VM
7615 -- Omit this check for the case of a configurable run-time that
7616 -- does not provide package System.Storage_Pools.Subpools.
7618 and then RTE_Available (RE_Root_Storage_Pool_With_Subpools)
7619 then
7620 declare
7621 Loc : constant Source_Ptr := Sloc (Def_Id);
7622 Pool : constant Entity_Id :=
7623 Associated_Storage_Pool (Def_Id);
7624 RSPWS : constant Entity_Id :=
7625 RTE (RE_Root_Storage_Pool_With_Subpools);
7627 begin
7628 -- It is known that the accessibility level of the access
7629 -- type is deeper than that of the pool.
7631 if Type_Access_Level (Def_Id) > Object_Access_Level (Pool)
7632 and then not Accessibility_Checks_Suppressed (Def_Id)
7633 and then not Accessibility_Checks_Suppressed (Pool)
7634 then
7635 -- Static case: the pool is known to be a descendant of
7636 -- Root_Storage_Pool_With_Subpools.
7638 if Is_Ancestor (RSPWS, Etype (Pool)) then
7639 Error_Msg_N
7640 ("??subpool access type has deeper accessibility "
7641 & "level than pool", Def_Id);
7643 Append_Freeze_Action (Def_Id,
7644 Make_Raise_Program_Error (Loc,
7645 Reason => PE_Accessibility_Check_Failed));
7647 -- Dynamic case: when the pool is of a class-wide type,
7648 -- it may or may not support subpools depending on the
7649 -- path of derivation. Generate:
7651 -- if Def_Id in RSPWS'Class then
7652 -- raise Program_Error;
7653 -- end if;
7655 elsif Is_Class_Wide_Type (Etype (Pool)) then
7656 Append_Freeze_Action (Def_Id,
7657 Make_If_Statement (Loc,
7658 Condition =>
7659 Make_In (Loc,
7660 Left_Opnd => New_Occurrence_Of (Pool, Loc),
7661 Right_Opnd =>
7662 New_Occurrence_Of
7663 (Class_Wide_Type (RSPWS), Loc)),
7665 Then_Statements => New_List (
7666 Make_Raise_Program_Error (Loc,
7667 Reason => PE_Accessibility_Check_Failed))));
7668 end if;
7669 end if;
7670 end;
7671 end if;
7673 -- For access-to-controlled types (including class-wide types and
7674 -- Taft-amendment types, which potentially have controlled
7675 -- components), expand the list controller object that will store
7676 -- the dynamically allocated objects. Don't do this transformation
7677 -- for expander-generated access types, but do it for types that
7678 -- are the full view of types derived from other private types.
7679 -- Also suppress the list controller in the case of a designated
7680 -- type with convention Java, since this is used when binding to
7681 -- Java API specs, where there's no equivalent of a finalization
7682 -- list and we don't want to pull in the finalization support if
7683 -- not needed.
7685 if not Comes_From_Source (Def_Id)
7686 and then not Has_Private_Declaration (Def_Id)
7687 then
7688 null;
7690 -- An exception is made for types defined in the run-time because
7691 -- Ada.Tags.Tag itself is such a type and cannot afford this
7692 -- unnecessary overhead that would generates a loop in the
7693 -- expansion scheme. Another exception is if Restrictions
7694 -- (No_Finalization) is active, since then we know nothing is
7695 -- controlled.
7697 elsif Restriction_Active (No_Finalization)
7698 or else In_Runtime (Def_Id)
7699 then
7700 null;
7702 -- Assume that incomplete and private types are always completed
7703 -- by a controlled full view.
7705 elsif Needs_Finalization (Desig_Type)
7706 or else
7707 (Is_Incomplete_Or_Private_Type (Desig_Type)
7708 and then No (Full_View (Desig_Type)))
7709 or else
7710 (Is_Array_Type (Desig_Type)
7711 and then Needs_Finalization (Component_Type (Desig_Type)))
7712 then
7713 Build_Finalization_Master (Def_Id);
7714 end if;
7715 end;
7717 -- Freeze processing for enumeration types
7719 elsif Ekind (Def_Id) = E_Enumeration_Type then
7721 -- We only have something to do if we have a non-standard
7722 -- representation (i.e. at least one literal whose pos value
7723 -- is not the same as its representation)
7725 if Has_Non_Standard_Rep (Def_Id) then
7726 Expand_Freeze_Enumeration_Type (N);
7727 end if;
7729 -- Private types that are completed by a derivation from a private
7730 -- type have an internally generated full view, that needs to be
7731 -- frozen. This must be done explicitly because the two views share
7732 -- the freeze node, and the underlying full view is not visible when
7733 -- the freeze node is analyzed.
7735 elsif Is_Private_Type (Def_Id)
7736 and then Is_Derived_Type (Def_Id)
7737 and then Present (Full_View (Def_Id))
7738 and then Is_Itype (Full_View (Def_Id))
7739 and then Has_Private_Declaration (Full_View (Def_Id))
7740 and then Freeze_Node (Full_View (Def_Id)) = N
7741 then
7742 Set_Entity (N, Full_View (Def_Id));
7743 Result := Freeze_Type (N);
7744 Set_Entity (N, Def_Id);
7746 -- All other types require no expander action. There are such cases
7747 -- (e.g. task types and protected types). In such cases, the freeze
7748 -- nodes are there for use by Gigi.
7750 end if;
7752 Freeze_Stream_Operations (N, Def_Id);
7753 return Result;
7755 exception
7756 when RE_Not_Available =>
7757 return False;
7758 end Freeze_Type;
7760 -------------------------
7761 -- Get_Simple_Init_Val --
7762 -------------------------
7764 function Get_Simple_Init_Val
7765 (T : Entity_Id;
7766 N : Node_Id;
7767 Size : Uint := No_Uint) return Node_Id
7769 Loc : constant Source_Ptr := Sloc (N);
7770 Val : Node_Id;
7771 Result : Node_Id;
7772 Val_RE : RE_Id;
7774 Size_To_Use : Uint;
7775 -- This is the size to be used for computation of the appropriate
7776 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
7778 IV_Attribute : constant Boolean :=
7779 Nkind (N) = N_Attribute_Reference
7780 and then Attribute_Name (N) = Name_Invalid_Value;
7782 Lo_Bound : Uint;
7783 Hi_Bound : Uint;
7784 -- These are the values computed by the procedure Check_Subtype_Bounds
7786 procedure Check_Subtype_Bounds;
7787 -- This procedure examines the subtype T, and its ancestor subtypes and
7788 -- derived types to determine the best known information about the
7789 -- bounds of the subtype. After the call Lo_Bound is set either to
7790 -- No_Uint if no information can be determined, or to a value which
7791 -- represents a known low bound, i.e. a valid value of the subtype can
7792 -- not be less than this value. Hi_Bound is similarly set to a known
7793 -- high bound (valid value cannot be greater than this).
7795 --------------------------
7796 -- Check_Subtype_Bounds --
7797 --------------------------
7799 procedure Check_Subtype_Bounds is
7800 ST1 : Entity_Id;
7801 ST2 : Entity_Id;
7802 Lo : Node_Id;
7803 Hi : Node_Id;
7804 Loval : Uint;
7805 Hival : Uint;
7807 begin
7808 Lo_Bound := No_Uint;
7809 Hi_Bound := No_Uint;
7811 -- Loop to climb ancestor subtypes and derived types
7813 ST1 := T;
7814 loop
7815 if not Is_Discrete_Type (ST1) then
7816 return;
7817 end if;
7819 Lo := Type_Low_Bound (ST1);
7820 Hi := Type_High_Bound (ST1);
7822 if Compile_Time_Known_Value (Lo) then
7823 Loval := Expr_Value (Lo);
7825 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
7826 Lo_Bound := Loval;
7827 end if;
7828 end if;
7830 if Compile_Time_Known_Value (Hi) then
7831 Hival := Expr_Value (Hi);
7833 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
7834 Hi_Bound := Hival;
7835 end if;
7836 end if;
7838 ST2 := Ancestor_Subtype (ST1);
7840 if No (ST2) then
7841 ST2 := Etype (ST1);
7842 end if;
7844 exit when ST1 = ST2;
7845 ST1 := ST2;
7846 end loop;
7847 end Check_Subtype_Bounds;
7849 -- Start of processing for Get_Simple_Init_Val
7851 begin
7852 -- For a private type, we should always have an underlying type (because
7853 -- this was already checked in Needs_Simple_Initialization). What we do
7854 -- is to get the value for the underlying type and then do an unchecked
7855 -- conversion to the private type.
7857 if Is_Private_Type (T) then
7858 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
7860 -- A special case, if the underlying value is null, then qualify it
7861 -- with the underlying type, so that the null is properly typed.
7862 -- Similarly, if it is an aggregate it must be qualified, because an
7863 -- unchecked conversion does not provide a context for it.
7865 if Nkind_In (Val, N_Null, N_Aggregate) then
7866 Val :=
7867 Make_Qualified_Expression (Loc,
7868 Subtype_Mark =>
7869 New_Occurrence_Of (Underlying_Type (T), Loc),
7870 Expression => Val);
7871 end if;
7873 Result := Unchecked_Convert_To (T, Val);
7875 -- Don't truncate result (important for Initialize/Normalize_Scalars)
7877 if Nkind (Result) = N_Unchecked_Type_Conversion
7878 and then Is_Scalar_Type (Underlying_Type (T))
7879 then
7880 Set_No_Truncation (Result);
7881 end if;
7883 return Result;
7885 -- Scalars with Default_Value aspect. The first subtype may now be
7886 -- private, so retrieve value from underlying type.
7888 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
7889 if Is_Private_Type (First_Subtype (T)) then
7890 return Unchecked_Convert_To (T,
7891 Default_Aspect_Value (Full_View (First_Subtype (T))));
7892 else
7893 return
7894 Convert_To (T, Default_Aspect_Value (First_Subtype (T)));
7895 end if;
7897 -- Otherwise, for scalars, we must have normalize/initialize scalars
7898 -- case, or if the node N is an 'Invalid_Value attribute node.
7900 elsif Is_Scalar_Type (T) then
7901 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
7903 -- Compute size of object. If it is given by the caller, we can use
7904 -- it directly, otherwise we use Esize (T) as an estimate. As far as
7905 -- we know this covers all cases correctly.
7907 if Size = No_Uint or else Size <= Uint_0 then
7908 Size_To_Use := UI_Max (Uint_1, Esize (T));
7909 else
7910 Size_To_Use := Size;
7911 end if;
7913 -- Maximum size to use is 64 bits, since we will create values of
7914 -- type Unsigned_64 and the range must fit this type.
7916 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
7917 Size_To_Use := Uint_64;
7918 end if;
7920 -- Check known bounds of subtype
7922 Check_Subtype_Bounds;
7924 -- Processing for Normalize_Scalars case
7926 if Normalize_Scalars and then not IV_Attribute then
7928 -- If zero is invalid, it is a convenient value to use that is
7929 -- for sure an appropriate invalid value in all situations.
7931 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
7932 Val := Make_Integer_Literal (Loc, 0);
7934 -- Cases where all one bits is the appropriate invalid value
7936 -- For modular types, all 1 bits is either invalid or valid. If
7937 -- it is valid, then there is nothing that can be done since there
7938 -- are no invalid values (we ruled out zero already).
7940 -- For signed integer types that have no negative values, either
7941 -- there is room for negative values, or there is not. If there
7942 -- is, then all 1-bits may be interpreted as minus one, which is
7943 -- certainly invalid. Alternatively it is treated as the largest
7944 -- positive value, in which case the observation for modular types
7945 -- still applies.
7947 -- For float types, all 1-bits is a NaN (not a number), which is
7948 -- certainly an appropriately invalid value.
7950 elsif Is_Unsigned_Type (T)
7951 or else Is_Floating_Point_Type (T)
7952 or else Is_Enumeration_Type (T)
7953 then
7954 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
7956 -- Resolve as Unsigned_64, because the largest number we can
7957 -- generate is out of range of universal integer.
7959 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
7961 -- Case of signed types
7963 else
7964 declare
7965 Signed_Size : constant Uint :=
7966 UI_Min (Uint_63, Size_To_Use - 1);
7968 begin
7969 -- Normally we like to use the most negative number. The one
7970 -- exception is when this number is in the known subtype
7971 -- range and the largest positive number is not in the known
7972 -- subtype range.
7974 -- For this exceptional case, use largest positive value
7976 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
7977 and then Lo_Bound <= (-(2 ** Signed_Size))
7978 and then Hi_Bound < 2 ** Signed_Size
7979 then
7980 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
7982 -- Normal case of largest negative value
7984 else
7985 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
7986 end if;
7987 end;
7988 end if;
7990 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
7992 else
7993 -- For float types, use float values from System.Scalar_Values
7995 if Is_Floating_Point_Type (T) then
7996 if Root_Type (T) = Standard_Short_Float then
7997 Val_RE := RE_IS_Isf;
7998 elsif Root_Type (T) = Standard_Float then
7999 Val_RE := RE_IS_Ifl;
8000 elsif Root_Type (T) = Standard_Long_Float then
8001 Val_RE := RE_IS_Ilf;
8002 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
8003 Val_RE := RE_IS_Ill;
8004 end if;
8006 -- If zero is invalid, use zero values from System.Scalar_Values
8008 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
8009 if Size_To_Use <= 8 then
8010 Val_RE := RE_IS_Iz1;
8011 elsif Size_To_Use <= 16 then
8012 Val_RE := RE_IS_Iz2;
8013 elsif Size_To_Use <= 32 then
8014 Val_RE := RE_IS_Iz4;
8015 else
8016 Val_RE := RE_IS_Iz8;
8017 end if;
8019 -- For unsigned, use unsigned values from System.Scalar_Values
8021 elsif Is_Unsigned_Type (T) then
8022 if Size_To_Use <= 8 then
8023 Val_RE := RE_IS_Iu1;
8024 elsif Size_To_Use <= 16 then
8025 Val_RE := RE_IS_Iu2;
8026 elsif Size_To_Use <= 32 then
8027 Val_RE := RE_IS_Iu4;
8028 else
8029 Val_RE := RE_IS_Iu8;
8030 end if;
8032 -- For signed, use signed values from System.Scalar_Values
8034 else
8035 if Size_To_Use <= 8 then
8036 Val_RE := RE_IS_Is1;
8037 elsif Size_To_Use <= 16 then
8038 Val_RE := RE_IS_Is2;
8039 elsif Size_To_Use <= 32 then
8040 Val_RE := RE_IS_Is4;
8041 else
8042 Val_RE := RE_IS_Is8;
8043 end if;
8044 end if;
8046 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
8047 end if;
8049 -- The final expression is obtained by doing an unchecked conversion
8050 -- of this result to the base type of the required subtype. Use the
8051 -- base type to prevent the unchecked conversion from chopping bits,
8052 -- and then we set Kill_Range_Check to preserve the "bad" value.
8054 Result := Unchecked_Convert_To (Base_Type (T), Val);
8056 -- Ensure result is not truncated, since we want the "bad" bits, and
8057 -- also kill range check on result.
8059 if Nkind (Result) = N_Unchecked_Type_Conversion then
8060 Set_No_Truncation (Result);
8061 Set_Kill_Range_Check (Result, True);
8062 end if;
8064 return Result;
8066 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
8068 elsif Is_Standard_String_Type (T) then
8069 pragma Assert (Init_Or_Norm_Scalars);
8071 return
8072 Make_Aggregate (Loc,
8073 Component_Associations => New_List (
8074 Make_Component_Association (Loc,
8075 Choices => New_List (
8076 Make_Others_Choice (Loc)),
8077 Expression =>
8078 Get_Simple_Init_Val
8079 (Component_Type (T), N, Esize (Root_Type (T))))));
8081 -- Access type is initialized to null
8083 elsif Is_Access_Type (T) then
8084 return Make_Null (Loc);
8086 -- No other possibilities should arise, since we should only be calling
8087 -- Get_Simple_Init_Val if Needs_Simple_Initialization returned True,
8088 -- indicating one of the above cases held.
8090 else
8091 raise Program_Error;
8092 end if;
8094 exception
8095 when RE_Not_Available =>
8096 return Empty;
8097 end Get_Simple_Init_Val;
8099 ------------------------------
8100 -- Has_New_Non_Standard_Rep --
8101 ------------------------------
8103 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
8104 begin
8105 if not Is_Derived_Type (T) then
8106 return Has_Non_Standard_Rep (T)
8107 or else Has_Non_Standard_Rep (Root_Type (T));
8109 -- If Has_Non_Standard_Rep is not set on the derived type, the
8110 -- representation is fully inherited.
8112 elsif not Has_Non_Standard_Rep (T) then
8113 return False;
8115 else
8116 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
8118 -- May need a more precise check here: the First_Rep_Item may be a
8119 -- stream attribute, which does not affect the representation of the
8120 -- type ???
8122 end if;
8123 end Has_New_Non_Standard_Rep;
8125 ----------------
8126 -- In_Runtime --
8127 ----------------
8129 function In_Runtime (E : Entity_Id) return Boolean is
8130 S1 : Entity_Id;
8132 begin
8133 S1 := Scope (E);
8134 while Scope (S1) /= Standard_Standard loop
8135 S1 := Scope (S1);
8136 end loop;
8138 return Is_RTU (S1, System) or else Is_RTU (S1, Ada);
8139 end In_Runtime;
8141 ---------------------------------------
8142 -- Insert_Component_Invariant_Checks --
8143 ---------------------------------------
8145 procedure Insert_Component_Invariant_Checks
8146 (N : Node_Id;
8147 Typ : Entity_Id;
8148 Proc : Node_Id)
8150 Loc : constant Source_Ptr := Sloc (Typ);
8151 Proc_Id : Entity_Id;
8153 begin
8154 if Present (Proc) then
8155 Proc_Id := Defining_Entity (Proc);
8157 if not Has_Invariants (Typ) then
8158 Set_Has_Invariants (Typ);
8159 Set_Is_Invariant_Procedure (Proc_Id);
8160 Set_Invariant_Procedure (Typ, Proc_Id);
8161 Insert_After (N, Proc);
8162 Analyze (Proc);
8164 else
8166 -- Find already created invariant subprogram, insert body of
8167 -- component invariant proc in its body, and add call after
8168 -- other checks.
8170 declare
8171 Bod : Node_Id;
8172 Inv_Id : constant Entity_Id := Invariant_Procedure (Typ);
8173 Call : constant Node_Id :=
8174 Make_Procedure_Call_Statement (Sloc (N),
8175 Name => New_Occurrence_Of (Proc_Id, Loc),
8176 Parameter_Associations =>
8177 New_List
8178 (New_Occurrence_Of (First_Formal (Inv_Id), Loc)));
8180 begin
8181 -- The invariant body has not been analyzed yet, so we do a
8182 -- sequential search forward, and retrieve it by name.
8184 Bod := Next (N);
8185 while Present (Bod) loop
8186 exit when Nkind (Bod) = N_Subprogram_Body
8187 and then Chars (Defining_Entity (Bod)) = Chars (Inv_Id);
8188 Next (Bod);
8189 end loop;
8191 -- If the body is not found, it is the case of an invariant
8192 -- appearing on a full declaration in a private part, in
8193 -- which case the type has been frozen but the invariant
8194 -- procedure for the composite type not created yet. Create
8195 -- body now.
8197 if No (Bod) then
8198 Build_Invariant_Procedure (Typ, Parent (Current_Scope));
8199 Bod := Unit_Declaration_Node
8200 (Corresponding_Body (Unit_Declaration_Node (Inv_Id)));
8201 end if;
8203 Append_To (Declarations (Bod), Proc);
8204 Append_To (Statements (Handled_Statement_Sequence (Bod)), Call);
8205 Analyze (Proc);
8206 Analyze (Call);
8207 end;
8208 end if;
8209 end if;
8210 end Insert_Component_Invariant_Checks;
8212 ----------------------------
8213 -- Initialization_Warning --
8214 ----------------------------
8216 procedure Initialization_Warning (E : Entity_Id) is
8217 Warning_Needed : Boolean;
8219 begin
8220 Warning_Needed := False;
8222 if Ekind (Current_Scope) = E_Package
8223 and then Static_Elaboration_Desired (Current_Scope)
8224 then
8225 if Is_Type (E) then
8226 if Is_Record_Type (E) then
8227 if Has_Discriminants (E)
8228 or else Is_Limited_Type (E)
8229 or else Has_Non_Standard_Rep (E)
8230 then
8231 Warning_Needed := True;
8233 else
8234 -- Verify that at least one component has an initialization
8235 -- expression. No need for a warning on a type if all its
8236 -- components have no initialization.
8238 declare
8239 Comp : Entity_Id;
8241 begin
8242 Comp := First_Component (E);
8243 while Present (Comp) loop
8244 if Ekind (Comp) = E_Discriminant
8245 or else
8246 (Nkind (Parent (Comp)) = N_Component_Declaration
8247 and then Present (Expression (Parent (Comp))))
8248 then
8249 Warning_Needed := True;
8250 exit;
8251 end if;
8253 Next_Component (Comp);
8254 end loop;
8255 end;
8256 end if;
8258 if Warning_Needed then
8259 Error_Msg_N
8260 ("Objects of the type cannot be initialized statically "
8261 & "by default??", Parent (E));
8262 end if;
8263 end if;
8265 else
8266 Error_Msg_N ("Object cannot be initialized statically??", E);
8267 end if;
8268 end if;
8269 end Initialization_Warning;
8271 ------------------
8272 -- Init_Formals --
8273 ------------------
8275 function Init_Formals (Typ : Entity_Id) return List_Id is
8276 Loc : constant Source_Ptr := Sloc (Typ);
8277 Formals : List_Id;
8279 begin
8280 -- First parameter is always _Init : in out typ. Note that we need this
8281 -- to be in/out because in the case of the task record value, there
8282 -- are default record fields (_Priority, _Size, -Task_Info) that may
8283 -- be referenced in the generated initialization routine.
8285 Formals := New_List (
8286 Make_Parameter_Specification (Loc,
8287 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uInit),
8288 In_Present => True,
8289 Out_Present => True,
8290 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
8292 -- For task record value, or type that contains tasks, add two more
8293 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
8294 -- We also add these parameters for the task record type case.
8296 if Has_Task (Typ)
8297 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
8298 then
8299 Append_To (Formals,
8300 Make_Parameter_Specification (Loc,
8301 Defining_Identifier =>
8302 Make_Defining_Identifier (Loc, Name_uMaster),
8303 Parameter_Type =>
8304 New_Occurrence_Of (RTE (RE_Master_Id), Loc)));
8306 -- Add _Chain (not done for sequential elaboration policy, see
8307 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
8309 if Partition_Elaboration_Policy /= 'S' then
8310 Append_To (Formals,
8311 Make_Parameter_Specification (Loc,
8312 Defining_Identifier =>
8313 Make_Defining_Identifier (Loc, Name_uChain),
8314 In_Present => True,
8315 Out_Present => True,
8316 Parameter_Type =>
8317 New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)));
8318 end if;
8320 Append_To (Formals,
8321 Make_Parameter_Specification (Loc,
8322 Defining_Identifier =>
8323 Make_Defining_Identifier (Loc, Name_uTask_Name),
8324 In_Present => True,
8325 Parameter_Type => New_Occurrence_Of (Standard_String, Loc)));
8326 end if;
8328 return Formals;
8330 exception
8331 when RE_Not_Available =>
8332 return Empty_List;
8333 end Init_Formals;
8335 -------------------------
8336 -- Init_Secondary_Tags --
8337 -------------------------
8339 procedure Init_Secondary_Tags
8340 (Typ : Entity_Id;
8341 Target : Node_Id;
8342 Stmts_List : List_Id;
8343 Fixed_Comps : Boolean := True;
8344 Variable_Comps : Boolean := True)
8346 Loc : constant Source_Ptr := Sloc (Target);
8348 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
8349 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8351 procedure Initialize_Tag
8352 (Typ : Entity_Id;
8353 Iface : Entity_Id;
8354 Tag_Comp : Entity_Id;
8355 Iface_Tag : Node_Id);
8356 -- Initialize the tag of the secondary dispatch table of Typ associated
8357 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8358 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
8359 -- of Typ CPP tagged type we generate code to inherit the contents of
8360 -- the dispatch table directly from the ancestor.
8362 --------------------
8363 -- Initialize_Tag --
8364 --------------------
8366 procedure Initialize_Tag
8367 (Typ : Entity_Id;
8368 Iface : Entity_Id;
8369 Tag_Comp : Entity_Id;
8370 Iface_Tag : Node_Id)
8372 Comp_Typ : Entity_Id;
8373 Offset_To_Top_Comp : Entity_Id := Empty;
8375 begin
8376 -- Initialize pointer to secondary DT associated with the interface
8378 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8379 Append_To (Stmts_List,
8380 Make_Assignment_Statement (Loc,
8381 Name =>
8382 Make_Selected_Component (Loc,
8383 Prefix => New_Copy_Tree (Target),
8384 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8385 Expression =>
8386 New_Occurrence_Of (Iface_Tag, Loc)));
8387 end if;
8389 Comp_Typ := Scope (Tag_Comp);
8391 -- Initialize the entries of the table of interfaces. We generate a
8392 -- different call when the parent of the type has variable size
8393 -- components.
8395 if Comp_Typ /= Etype (Comp_Typ)
8396 and then Is_Variable_Size_Record (Etype (Comp_Typ))
8397 and then Chars (Tag_Comp) /= Name_uTag
8398 then
8399 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
8401 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
8402 -- configurable run-time environment.
8404 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
8405 Error_Msg_CRT
8406 ("variable size record with interface types", Typ);
8407 return;
8408 end if;
8410 -- Generate:
8411 -- Set_Dynamic_Offset_To_Top
8412 -- (This => Init,
8413 -- Interface_T => Iface'Tag,
8414 -- Offset_Value => n,
8415 -- Offset_Func => Fn'Address)
8417 Append_To (Stmts_List,
8418 Make_Procedure_Call_Statement (Loc,
8419 Name =>
8420 New_Occurrence_Of (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
8421 Parameter_Associations => New_List (
8422 Make_Attribute_Reference (Loc,
8423 Prefix => New_Copy_Tree (Target),
8424 Attribute_Name => Name_Address),
8426 Unchecked_Convert_To (RTE (RE_Tag),
8427 New_Occurrence_Of
8428 (Node (First_Elmt (Access_Disp_Table (Iface))),
8429 Loc)),
8431 Unchecked_Convert_To
8432 (RTE (RE_Storage_Offset),
8433 Make_Attribute_Reference (Loc,
8434 Prefix =>
8435 Make_Selected_Component (Loc,
8436 Prefix => New_Copy_Tree (Target),
8437 Selector_Name =>
8438 New_Occurrence_Of (Tag_Comp, Loc)),
8439 Attribute_Name => Name_Position)),
8441 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
8442 Make_Attribute_Reference (Loc,
8443 Prefix => New_Occurrence_Of
8444 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
8445 Attribute_Name => Name_Address)))));
8447 -- In this case the next component stores the value of the offset
8448 -- to the top.
8450 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
8451 pragma Assert (Present (Offset_To_Top_Comp));
8453 Append_To (Stmts_List,
8454 Make_Assignment_Statement (Loc,
8455 Name =>
8456 Make_Selected_Component (Loc,
8457 Prefix => New_Copy_Tree (Target),
8458 Selector_Name =>
8459 New_Occurrence_Of (Offset_To_Top_Comp, Loc)),
8461 Expression =>
8462 Make_Attribute_Reference (Loc,
8463 Prefix =>
8464 Make_Selected_Component (Loc,
8465 Prefix => New_Copy_Tree (Target),
8466 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8467 Attribute_Name => Name_Position)));
8469 -- Normal case: No discriminants in the parent type
8471 else
8472 -- Don't need to set any value if this interface shares the
8473 -- primary dispatch table.
8475 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8476 Append_To (Stmts_List,
8477 Build_Set_Static_Offset_To_Top (Loc,
8478 Iface_Tag => New_Occurrence_Of (Iface_Tag, Loc),
8479 Offset_Value =>
8480 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8481 Make_Attribute_Reference (Loc,
8482 Prefix =>
8483 Make_Selected_Component (Loc,
8484 Prefix => New_Copy_Tree (Target),
8485 Selector_Name =>
8486 New_Occurrence_Of (Tag_Comp, Loc)),
8487 Attribute_Name => Name_Position))));
8488 end if;
8490 -- Generate:
8491 -- Register_Interface_Offset
8492 -- (This => Init,
8493 -- Interface_T => Iface'Tag,
8494 -- Is_Constant => True,
8495 -- Offset_Value => n,
8496 -- Offset_Func => null);
8498 if RTE_Available (RE_Register_Interface_Offset) then
8499 Append_To (Stmts_List,
8500 Make_Procedure_Call_Statement (Loc,
8501 Name =>
8502 New_Occurrence_Of
8503 (RTE (RE_Register_Interface_Offset), Loc),
8504 Parameter_Associations => New_List (
8505 Make_Attribute_Reference (Loc,
8506 Prefix => New_Copy_Tree (Target),
8507 Attribute_Name => Name_Address),
8509 Unchecked_Convert_To (RTE (RE_Tag),
8510 New_Occurrence_Of
8511 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
8513 New_Occurrence_Of (Standard_True, Loc),
8515 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8516 Make_Attribute_Reference (Loc,
8517 Prefix =>
8518 Make_Selected_Component (Loc,
8519 Prefix => New_Copy_Tree (Target),
8520 Selector_Name =>
8521 New_Occurrence_Of (Tag_Comp, Loc)),
8522 Attribute_Name => Name_Position)),
8524 Make_Null (Loc))));
8525 end if;
8526 end if;
8527 end Initialize_Tag;
8529 -- Local variables
8531 Full_Typ : Entity_Id;
8532 Ifaces_List : Elist_Id;
8533 Ifaces_Comp_List : Elist_Id;
8534 Ifaces_Tag_List : Elist_Id;
8535 Iface_Elmt : Elmt_Id;
8536 Iface_Comp_Elmt : Elmt_Id;
8537 Iface_Tag_Elmt : Elmt_Id;
8538 Tag_Comp : Node_Id;
8539 In_Variable_Pos : Boolean;
8541 -- Start of processing for Init_Secondary_Tags
8543 begin
8544 -- Handle private types
8546 if Present (Full_View (Typ)) then
8547 Full_Typ := Full_View (Typ);
8548 else
8549 Full_Typ := Typ;
8550 end if;
8552 Collect_Interfaces_Info
8553 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
8555 Iface_Elmt := First_Elmt (Ifaces_List);
8556 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
8557 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
8558 while Present (Iface_Elmt) loop
8559 Tag_Comp := Node (Iface_Comp_Elmt);
8561 -- Check if parent of record type has variable size components
8563 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
8564 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
8566 -- If we are compiling under the CPP full ABI compatibility mode and
8567 -- the ancestor is a CPP_Pragma tagged type then we generate code to
8568 -- initialize the secondary tag components from tags that reference
8569 -- secondary tables filled with copy of parent slots.
8571 if Is_CPP_Class (Root_Type (Full_Typ)) then
8573 -- Reject interface components located at variable offset in
8574 -- C++ derivations. This is currently unsupported.
8576 if not Fixed_Comps and then In_Variable_Pos then
8578 -- Locate the first dynamic component of the record. Done to
8579 -- improve the text of the warning.
8581 declare
8582 Comp : Entity_Id;
8583 Comp_Typ : Entity_Id;
8585 begin
8586 Comp := First_Entity (Typ);
8587 while Present (Comp) loop
8588 Comp_Typ := Etype (Comp);
8590 if Ekind (Comp) /= E_Discriminant
8591 and then not Is_Tag (Comp)
8592 then
8593 exit when
8594 (Is_Record_Type (Comp_Typ)
8595 and then
8596 Is_Variable_Size_Record (Base_Type (Comp_Typ)))
8597 or else
8598 (Is_Array_Type (Comp_Typ)
8599 and then Is_Variable_Size_Array (Comp_Typ));
8600 end if;
8602 Next_Entity (Comp);
8603 end loop;
8605 pragma Assert (Present (Comp));
8606 Error_Msg_Node_2 := Comp;
8607 Error_Msg_NE
8608 ("parent type & with dynamic component & cannot be parent"
8609 & " of 'C'P'P derivation if new interfaces are present",
8610 Typ, Scope (Original_Record_Component (Comp)));
8612 Error_Msg_Sloc :=
8613 Sloc (Scope (Original_Record_Component (Comp)));
8614 Error_Msg_NE
8615 ("type derived from 'C'P'P type & defined #",
8616 Typ, Scope (Original_Record_Component (Comp)));
8618 -- Avoid duplicated warnings
8620 exit;
8621 end;
8623 -- Initialize secondary tags
8625 else
8626 Append_To (Stmts_List,
8627 Make_Assignment_Statement (Loc,
8628 Name =>
8629 Make_Selected_Component (Loc,
8630 Prefix => New_Copy_Tree (Target),
8631 Selector_Name =>
8632 New_Occurrence_Of (Node (Iface_Comp_Elmt), Loc)),
8633 Expression =>
8634 New_Occurrence_Of (Node (Iface_Tag_Elmt), Loc)));
8635 end if;
8637 -- Otherwise generate code to initialize the tag
8639 else
8640 if (In_Variable_Pos and then Variable_Comps)
8641 or else (not In_Variable_Pos and then Fixed_Comps)
8642 then
8643 Initialize_Tag (Full_Typ,
8644 Iface => Node (Iface_Elmt),
8645 Tag_Comp => Tag_Comp,
8646 Iface_Tag => Node (Iface_Tag_Elmt));
8647 end if;
8648 end if;
8650 Next_Elmt (Iface_Elmt);
8651 Next_Elmt (Iface_Comp_Elmt);
8652 Next_Elmt (Iface_Tag_Elmt);
8653 end loop;
8654 end Init_Secondary_Tags;
8656 ------------------------
8657 -- Is_User_Defined_Eq --
8658 ------------------------
8660 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean is
8661 begin
8662 return Chars (Prim) = Name_Op_Eq
8663 and then Etype (First_Formal (Prim)) =
8664 Etype (Next_Formal (First_Formal (Prim)))
8665 and then Base_Type (Etype (Prim)) = Standard_Boolean;
8666 end Is_User_Defined_Equality;
8668 ----------------------------------------
8669 -- Make_Controlling_Function_Wrappers --
8670 ----------------------------------------
8672 procedure Make_Controlling_Function_Wrappers
8673 (Tag_Typ : Entity_Id;
8674 Decl_List : out List_Id;
8675 Body_List : out List_Id)
8677 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8678 Prim_Elmt : Elmt_Id;
8679 Subp : Entity_Id;
8680 Actual_List : List_Id;
8681 Formal_List : List_Id;
8682 Formal : Entity_Id;
8683 Par_Formal : Entity_Id;
8684 Formal_Node : Node_Id;
8685 Func_Body : Node_Id;
8686 Func_Decl : Node_Id;
8687 Func_Spec : Node_Id;
8688 Return_Stmt : Node_Id;
8690 begin
8691 Decl_List := New_List;
8692 Body_List := New_List;
8694 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
8696 while Present (Prim_Elmt) loop
8697 Subp := Node (Prim_Elmt);
8699 -- If a primitive function with a controlling result of the type has
8700 -- not been overridden by the user, then we must create a wrapper
8701 -- function here that effectively overrides it and invokes the
8702 -- (non-abstract) parent function. This can only occur for a null
8703 -- extension. Note that functions with anonymous controlling access
8704 -- results don't qualify and must be overridden. We also exclude
8705 -- Input attributes, since each type will have its own version of
8706 -- Input constructed by the expander. The test for Comes_From_Source
8707 -- is needed to distinguish inherited operations from renamings
8708 -- (which also have Alias set). We exclude internal entities with
8709 -- Interface_Alias to avoid generating duplicated wrappers since
8710 -- the primitive which covers the interface is also available in
8711 -- the list of primitive operations.
8713 -- The function may be abstract, or require_Overriding may be set
8714 -- for it, because tests for null extensions may already have reset
8715 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
8716 -- set, functions that need wrappers are recognized by having an
8717 -- alias that returns the parent type.
8719 if Comes_From_Source (Subp)
8720 or else No (Alias (Subp))
8721 or else Present (Interface_Alias (Subp))
8722 or else Ekind (Subp) /= E_Function
8723 or else not Has_Controlling_Result (Subp)
8724 or else Is_Access_Type (Etype (Subp))
8725 or else Is_Abstract_Subprogram (Alias (Subp))
8726 or else Is_TSS (Subp, TSS_Stream_Input)
8727 then
8728 goto Next_Prim;
8730 elsif Is_Abstract_Subprogram (Subp)
8731 or else Requires_Overriding (Subp)
8732 or else
8733 (Is_Null_Extension (Etype (Subp))
8734 and then Etype (Alias (Subp)) /= Etype (Subp))
8735 then
8736 Formal_List := No_List;
8737 Formal := First_Formal (Subp);
8739 if Present (Formal) then
8740 Formal_List := New_List;
8742 while Present (Formal) loop
8743 Append
8744 (Make_Parameter_Specification
8745 (Loc,
8746 Defining_Identifier =>
8747 Make_Defining_Identifier (Sloc (Formal),
8748 Chars => Chars (Formal)),
8749 In_Present => In_Present (Parent (Formal)),
8750 Out_Present => Out_Present (Parent (Formal)),
8751 Null_Exclusion_Present =>
8752 Null_Exclusion_Present (Parent (Formal)),
8753 Parameter_Type =>
8754 New_Occurrence_Of (Etype (Formal), Loc),
8755 Expression =>
8756 New_Copy_Tree (Expression (Parent (Formal)))),
8757 Formal_List);
8759 Next_Formal (Formal);
8760 end loop;
8761 end if;
8763 Func_Spec :=
8764 Make_Function_Specification (Loc,
8765 Defining_Unit_Name =>
8766 Make_Defining_Identifier (Loc,
8767 Chars => Chars (Subp)),
8768 Parameter_Specifications => Formal_List,
8769 Result_Definition =>
8770 New_Occurrence_Of (Etype (Subp), Loc));
8772 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
8773 Append_To (Decl_List, Func_Decl);
8775 -- Build a wrapper body that calls the parent function. The body
8776 -- contains a single return statement that returns an extension
8777 -- aggregate whose ancestor part is a call to the parent function,
8778 -- passing the formals as actuals (with any controlling arguments
8779 -- converted to the types of the corresponding formals of the
8780 -- parent function, which might be anonymous access types), and
8781 -- having a null extension.
8783 Formal := First_Formal (Subp);
8784 Par_Formal := First_Formal (Alias (Subp));
8785 Formal_Node := First (Formal_List);
8787 if Present (Formal) then
8788 Actual_List := New_List;
8789 else
8790 Actual_List := No_List;
8791 end if;
8793 while Present (Formal) loop
8794 if Is_Controlling_Formal (Formal) then
8795 Append_To (Actual_List,
8796 Make_Type_Conversion (Loc,
8797 Subtype_Mark =>
8798 New_Occurrence_Of (Etype (Par_Formal), Loc),
8799 Expression =>
8800 New_Occurrence_Of
8801 (Defining_Identifier (Formal_Node), Loc)));
8802 else
8803 Append_To
8804 (Actual_List,
8805 New_Occurrence_Of
8806 (Defining_Identifier (Formal_Node), Loc));
8807 end if;
8809 Next_Formal (Formal);
8810 Next_Formal (Par_Formal);
8811 Next (Formal_Node);
8812 end loop;
8814 Return_Stmt :=
8815 Make_Simple_Return_Statement (Loc,
8816 Expression =>
8817 Make_Extension_Aggregate (Loc,
8818 Ancestor_Part =>
8819 Make_Function_Call (Loc,
8820 Name =>
8821 New_Occurrence_Of (Alias (Subp), Loc),
8822 Parameter_Associations => Actual_List),
8823 Null_Record_Present => True));
8825 Func_Body :=
8826 Make_Subprogram_Body (Loc,
8827 Specification => New_Copy_Tree (Func_Spec),
8828 Declarations => Empty_List,
8829 Handled_Statement_Sequence =>
8830 Make_Handled_Sequence_Of_Statements (Loc,
8831 Statements => New_List (Return_Stmt)));
8833 Set_Defining_Unit_Name
8834 (Specification (Func_Body),
8835 Make_Defining_Identifier (Loc, Chars (Subp)));
8837 Append_To (Body_List, Func_Body);
8839 -- Replace the inherited function with the wrapper function in the
8840 -- primitive operations list. We add the minimum decoration needed
8841 -- to override interface primitives.
8843 Set_Ekind (Defining_Unit_Name (Func_Spec), E_Function);
8845 Override_Dispatching_Operation
8846 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec),
8847 Is_Wrapper => True);
8848 end if;
8850 <<Next_Prim>>
8851 Next_Elmt (Prim_Elmt);
8852 end loop;
8853 end Make_Controlling_Function_Wrappers;
8855 -------------------
8856 -- Make_Eq_Body --
8857 -------------------
8859 function Make_Eq_Body
8860 (Typ : Entity_Id;
8861 Eq_Name : Name_Id) return Node_Id
8863 Loc : constant Source_Ptr := Sloc (Parent (Typ));
8864 Decl : Node_Id;
8865 Def : constant Node_Id := Parent (Typ);
8866 Stmts : constant List_Id := New_List;
8867 Variant_Case : Boolean := Has_Discriminants (Typ);
8868 Comps : Node_Id := Empty;
8869 Typ_Def : Node_Id := Type_Definition (Def);
8871 begin
8872 Decl :=
8873 Predef_Spec_Or_Body (Loc,
8874 Tag_Typ => Typ,
8875 Name => Eq_Name,
8876 Profile => New_List (
8877 Make_Parameter_Specification (Loc,
8878 Defining_Identifier =>
8879 Make_Defining_Identifier (Loc, Name_X),
8880 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
8882 Make_Parameter_Specification (Loc,
8883 Defining_Identifier =>
8884 Make_Defining_Identifier (Loc, Name_Y),
8885 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
8887 Ret_Type => Standard_Boolean,
8888 For_Body => True);
8890 if Variant_Case then
8891 if Nkind (Typ_Def) = N_Derived_Type_Definition then
8892 Typ_Def := Record_Extension_Part (Typ_Def);
8893 end if;
8895 if Present (Typ_Def) then
8896 Comps := Component_List (Typ_Def);
8897 end if;
8899 Variant_Case :=
8900 Present (Comps) and then Present (Variant_Part (Comps));
8901 end if;
8903 if Variant_Case then
8904 Append_To (Stmts,
8905 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
8906 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
8907 Append_To (Stmts,
8908 Make_Simple_Return_Statement (Loc,
8909 Expression => New_Occurrence_Of (Standard_True, Loc)));
8911 else
8912 Append_To (Stmts,
8913 Make_Simple_Return_Statement (Loc,
8914 Expression =>
8915 Expand_Record_Equality
8916 (Typ,
8917 Typ => Typ,
8918 Lhs => Make_Identifier (Loc, Name_X),
8919 Rhs => Make_Identifier (Loc, Name_Y),
8920 Bodies => Declarations (Decl))));
8921 end if;
8923 Set_Handled_Statement_Sequence
8924 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
8925 return Decl;
8926 end Make_Eq_Body;
8928 ------------------
8929 -- Make_Eq_Case --
8930 ------------------
8932 -- <Make_Eq_If shared components>
8934 -- case X.D1 is
8935 -- when V1 => <Make_Eq_Case> on subcomponents
8936 -- ...
8937 -- when Vn => <Make_Eq_Case> on subcomponents
8938 -- end case;
8940 function Make_Eq_Case
8941 (E : Entity_Id;
8942 CL : Node_Id;
8943 Discrs : Elist_Id := New_Elmt_List) return List_Id
8945 Loc : constant Source_Ptr := Sloc (E);
8946 Result : constant List_Id := New_List;
8947 Variant : Node_Id;
8948 Alt_List : List_Id;
8950 function Corresponding_Formal (C : Node_Id) return Entity_Id;
8951 -- Given the discriminant that controls a given variant of an unchecked
8952 -- union, find the formal of the equality function that carries the
8953 -- inferred value of the discriminant.
8955 function External_Name (E : Entity_Id) return Name_Id;
8956 -- The value of a given discriminant is conveyed in the corresponding
8957 -- formal parameter of the equality routine. The name of this formal
8958 -- parameter carries a one-character suffix which is removed here.
8960 --------------------------
8961 -- Corresponding_Formal --
8962 --------------------------
8964 function Corresponding_Formal (C : Node_Id) return Entity_Id is
8965 Discr : constant Entity_Id := Entity (Name (Variant_Part (C)));
8966 Elm : Elmt_Id;
8968 begin
8969 Elm := First_Elmt (Discrs);
8970 while Present (Elm) loop
8971 if Chars (Discr) = External_Name (Node (Elm)) then
8972 return Node (Elm);
8973 end if;
8975 Next_Elmt (Elm);
8976 end loop;
8978 -- A formal of the proper name must be found
8980 raise Program_Error;
8981 end Corresponding_Formal;
8983 -------------------
8984 -- External_Name --
8985 -------------------
8987 function External_Name (E : Entity_Id) return Name_Id is
8988 begin
8989 Get_Name_String (Chars (E));
8990 Name_Len := Name_Len - 1;
8991 return Name_Find;
8992 end External_Name;
8994 -- Start of processing for Make_Eq_Case
8996 begin
8997 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
8999 if No (Variant_Part (CL)) then
9000 return Result;
9001 end if;
9003 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
9005 if No (Variant) then
9006 return Result;
9007 end if;
9009 Alt_List := New_List;
9010 while Present (Variant) loop
9011 Append_To (Alt_List,
9012 Make_Case_Statement_Alternative (Loc,
9013 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
9014 Statements =>
9015 Make_Eq_Case (E, Component_List (Variant), Discrs)));
9016 Next_Non_Pragma (Variant);
9017 end loop;
9019 -- If we have an Unchecked_Union, use one of the parameters of the
9020 -- enclosing equality routine that captures the discriminant, to use
9021 -- as the expression in the generated case statement.
9023 if Is_Unchecked_Union (E) then
9024 Append_To (Result,
9025 Make_Case_Statement (Loc,
9026 Expression =>
9027 New_Occurrence_Of (Corresponding_Formal (CL), Loc),
9028 Alternatives => Alt_List));
9030 else
9031 Append_To (Result,
9032 Make_Case_Statement (Loc,
9033 Expression =>
9034 Make_Selected_Component (Loc,
9035 Prefix => Make_Identifier (Loc, Name_X),
9036 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
9037 Alternatives => Alt_List));
9038 end if;
9040 return Result;
9041 end Make_Eq_Case;
9043 ----------------
9044 -- Make_Eq_If --
9045 ----------------
9047 -- Generates:
9049 -- if
9050 -- X.C1 /= Y.C1
9051 -- or else
9052 -- X.C2 /= Y.C2
9053 -- ...
9054 -- then
9055 -- return False;
9056 -- end if;
9058 -- or a null statement if the list L is empty
9060 function Make_Eq_If
9061 (E : Entity_Id;
9062 L : List_Id) return Node_Id
9064 Loc : constant Source_Ptr := Sloc (E);
9065 C : Node_Id;
9066 Field_Name : Name_Id;
9067 Cond : Node_Id;
9069 begin
9070 if No (L) then
9071 return Make_Null_Statement (Loc);
9073 else
9074 Cond := Empty;
9076 C := First_Non_Pragma (L);
9077 while Present (C) loop
9078 Field_Name := Chars (Defining_Identifier (C));
9080 -- The tags must not be compared: they are not part of the value.
9081 -- Ditto for parent interfaces because their equality operator is
9082 -- abstract.
9084 -- Note also that in the following, we use Make_Identifier for
9085 -- the component names. Use of New_Occurrence_Of to identify the
9086 -- components would be incorrect because the wrong entities for
9087 -- discriminants could be picked up in the private type case.
9089 if Field_Name = Name_uParent
9090 and then Is_Interface (Etype (Defining_Identifier (C)))
9091 then
9092 null;
9094 elsif Field_Name /= Name_uTag then
9095 Evolve_Or_Else (Cond,
9096 Make_Op_Ne (Loc,
9097 Left_Opnd =>
9098 Make_Selected_Component (Loc,
9099 Prefix => Make_Identifier (Loc, Name_X),
9100 Selector_Name => Make_Identifier (Loc, Field_Name)),
9102 Right_Opnd =>
9103 Make_Selected_Component (Loc,
9104 Prefix => Make_Identifier (Loc, Name_Y),
9105 Selector_Name => Make_Identifier (Loc, Field_Name))));
9106 end if;
9108 Next_Non_Pragma (C);
9109 end loop;
9111 if No (Cond) then
9112 return Make_Null_Statement (Loc);
9114 else
9115 return
9116 Make_Implicit_If_Statement (E,
9117 Condition => Cond,
9118 Then_Statements => New_List (
9119 Make_Simple_Return_Statement (Loc,
9120 Expression => New_Occurrence_Of (Standard_False, Loc))));
9121 end if;
9122 end if;
9123 end Make_Eq_If;
9125 -------------------
9126 -- Make_Neq_Body --
9127 -------------------
9129 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id is
9131 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean;
9132 -- Returns true if Prim is a renaming of an unresolved predefined
9133 -- inequality operation.
9135 --------------------------------
9136 -- Is_Predefined_Neq_Renaming --
9137 --------------------------------
9139 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean is
9140 begin
9141 return Chars (Prim) /= Name_Op_Ne
9142 and then Present (Alias (Prim))
9143 and then Comes_From_Source (Prim)
9144 and then Is_Intrinsic_Subprogram (Alias (Prim))
9145 and then Chars (Alias (Prim)) = Name_Op_Ne;
9146 end Is_Predefined_Neq_Renaming;
9148 -- Local variables
9150 Loc : constant Source_Ptr := Sloc (Parent (Tag_Typ));
9151 Stmts : constant List_Id := New_List;
9152 Decl : Node_Id;
9153 Eq_Prim : Entity_Id;
9154 Left_Op : Entity_Id;
9155 Renaming_Prim : Entity_Id;
9156 Right_Op : Entity_Id;
9157 Target : Entity_Id;
9159 -- Start of processing for Make_Neq_Body
9161 begin
9162 -- For a call on a renaming of a dispatching subprogram that is
9163 -- overridden, if the overriding occurred before the renaming, then
9164 -- the body executed is that of the overriding declaration, even if the
9165 -- overriding declaration is not visible at the place of the renaming;
9166 -- otherwise, the inherited or predefined subprogram is called, see
9167 -- (RM 8.5.4(8))
9169 -- Stage 1: Search for a renaming of the inequality primitive and also
9170 -- search for an overriding of the equality primitive located before the
9171 -- renaming declaration.
9173 declare
9174 Elmt : Elmt_Id;
9175 Prim : Node_Id;
9177 begin
9178 Eq_Prim := Empty;
9179 Renaming_Prim := Empty;
9181 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9182 while Present (Elmt) loop
9183 Prim := Node (Elmt);
9185 if Is_User_Defined_Equality (Prim) and then No (Alias (Prim)) then
9186 if No (Renaming_Prim) then
9187 pragma Assert (No (Eq_Prim));
9188 Eq_Prim := Prim;
9189 end if;
9191 elsif Is_Predefined_Neq_Renaming (Prim) then
9192 Renaming_Prim := Prim;
9193 end if;
9195 Next_Elmt (Elmt);
9196 end loop;
9197 end;
9199 -- No further action needed if no renaming was found
9201 if No (Renaming_Prim) then
9202 return Empty;
9203 end if;
9205 -- Stage 2: Replace the renaming declaration by a subprogram declaration
9206 -- (required to add its body)
9208 Decl := Parent (Parent (Renaming_Prim));
9209 Rewrite (Decl,
9210 Make_Subprogram_Declaration (Loc,
9211 Specification => Specification (Decl)));
9212 Set_Analyzed (Decl);
9214 -- Remove the decoration of intrinsic renaming subprogram
9216 Set_Is_Intrinsic_Subprogram (Renaming_Prim, False);
9217 Set_Convention (Renaming_Prim, Convention_Ada);
9218 Set_Alias (Renaming_Prim, Empty);
9219 Set_Has_Completion (Renaming_Prim, False);
9221 -- Stage 3: Build the corresponding body
9223 Left_Op := First_Formal (Renaming_Prim);
9224 Right_Op := Next_Formal (Left_Op);
9226 Decl :=
9227 Predef_Spec_Or_Body (Loc,
9228 Tag_Typ => Tag_Typ,
9229 Name => Chars (Renaming_Prim),
9230 Profile => New_List (
9231 Make_Parameter_Specification (Loc,
9232 Defining_Identifier =>
9233 Make_Defining_Identifier (Loc, Chars (Left_Op)),
9234 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9236 Make_Parameter_Specification (Loc,
9237 Defining_Identifier =>
9238 Make_Defining_Identifier (Loc, Chars (Right_Op)),
9239 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9241 Ret_Type => Standard_Boolean,
9242 For_Body => True);
9244 -- If the overriding of the equality primitive occurred before the
9245 -- renaming, then generate:
9247 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9248 -- begin
9249 -- return not Oeq (X, Y);
9250 -- end;
9252 if Present (Eq_Prim) then
9253 Target := Eq_Prim;
9255 -- Otherwise build a nested subprogram which performs the predefined
9256 -- evaluation of the equality operator. That is, generate:
9258 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9259 -- function Oeq (X : Y) return Boolean is
9260 -- begin
9261 -- <<body of default implementation>>
9262 -- end;
9263 -- begin
9264 -- return not Oeq (X, Y);
9265 -- end;
9267 else
9268 declare
9269 Local_Subp : Node_Id;
9270 begin
9271 Local_Subp := Make_Eq_Body (Tag_Typ, Name_Op_Eq);
9272 Set_Declarations (Decl, New_List (Local_Subp));
9273 Target := Defining_Entity (Local_Subp);
9274 end;
9275 end if;
9277 Append_To (Stmts,
9278 Make_Simple_Return_Statement (Loc,
9279 Expression =>
9280 Make_Op_Not (Loc,
9281 Make_Function_Call (Loc,
9282 Name => New_Occurrence_Of (Target, Loc),
9283 Parameter_Associations => New_List (
9284 Make_Identifier (Loc, Chars (Left_Op)),
9285 Make_Identifier (Loc, Chars (Right_Op)))))));
9287 Set_Handled_Statement_Sequence
9288 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
9289 return Decl;
9290 end Make_Neq_Body;
9292 -------------------------------
9293 -- Make_Null_Procedure_Specs --
9294 -------------------------------
9296 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
9297 Decl_List : constant List_Id := New_List;
9298 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9299 Formal : Entity_Id;
9300 Formal_List : List_Id;
9301 New_Param_Spec : Node_Id;
9302 Parent_Subp : Entity_Id;
9303 Prim_Elmt : Elmt_Id;
9304 Subp : Entity_Id;
9306 begin
9307 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9308 while Present (Prim_Elmt) loop
9309 Subp := Node (Prim_Elmt);
9311 -- If a null procedure inherited from an interface has not been
9312 -- overridden, then we build a null procedure declaration to
9313 -- override the inherited procedure.
9315 Parent_Subp := Alias (Subp);
9317 if Present (Parent_Subp)
9318 and then Is_Null_Interface_Primitive (Parent_Subp)
9319 then
9320 Formal_List := No_List;
9321 Formal := First_Formal (Subp);
9323 if Present (Formal) then
9324 Formal_List := New_List;
9326 while Present (Formal) loop
9328 -- Copy the parameter spec including default expressions
9330 New_Param_Spec :=
9331 New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
9333 -- Generate a new defining identifier for the new formal.
9334 -- required because New_Copy_Tree does not duplicate
9335 -- semantic fields (except itypes).
9337 Set_Defining_Identifier (New_Param_Spec,
9338 Make_Defining_Identifier (Sloc (Formal),
9339 Chars => Chars (Formal)));
9341 -- For controlling arguments we must change their
9342 -- parameter type to reference the tagged type (instead
9343 -- of the interface type)
9345 if Is_Controlling_Formal (Formal) then
9346 if Nkind (Parameter_Type (Parent (Formal))) = N_Identifier
9347 then
9348 Set_Parameter_Type (New_Param_Spec,
9349 New_Occurrence_Of (Tag_Typ, Loc));
9351 else pragma Assert
9352 (Nkind (Parameter_Type (Parent (Formal))) =
9353 N_Access_Definition);
9354 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
9355 New_Occurrence_Of (Tag_Typ, Loc));
9356 end if;
9357 end if;
9359 Append (New_Param_Spec, Formal_List);
9361 Next_Formal (Formal);
9362 end loop;
9363 end if;
9365 Append_To (Decl_List,
9366 Make_Subprogram_Declaration (Loc,
9367 Make_Procedure_Specification (Loc,
9368 Defining_Unit_Name =>
9369 Make_Defining_Identifier (Loc, Chars (Subp)),
9370 Parameter_Specifications => Formal_List,
9371 Null_Present => True)));
9372 end if;
9374 Next_Elmt (Prim_Elmt);
9375 end loop;
9377 return Decl_List;
9378 end Make_Null_Procedure_Specs;
9380 -------------------------------------
9381 -- Make_Predefined_Primitive_Specs --
9382 -------------------------------------
9384 procedure Make_Predefined_Primitive_Specs
9385 (Tag_Typ : Entity_Id;
9386 Predef_List : out List_Id;
9387 Renamed_Eq : out Entity_Id)
9389 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
9390 -- Returns true if Prim is a renaming of an unresolved predefined
9391 -- equality operation.
9393 -------------------------------
9394 -- Is_Predefined_Eq_Renaming --
9395 -------------------------------
9397 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
9398 begin
9399 return Chars (Prim) /= Name_Op_Eq
9400 and then Present (Alias (Prim))
9401 and then Comes_From_Source (Prim)
9402 and then Is_Intrinsic_Subprogram (Alias (Prim))
9403 and then Chars (Alias (Prim)) = Name_Op_Eq;
9404 end Is_Predefined_Eq_Renaming;
9406 -- Local variables
9408 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9409 Res : constant List_Id := New_List;
9410 Eq_Name : Name_Id := Name_Op_Eq;
9411 Eq_Needed : Boolean;
9412 Eq_Spec : Node_Id;
9413 Prim : Elmt_Id;
9415 Has_Predef_Eq_Renaming : Boolean := False;
9416 -- Set to True if Tag_Typ has a primitive that renames the predefined
9417 -- equality operator. Used to implement (RM 8-5-4(8)).
9419 -- Start of processing for Make_Predefined_Primitive_Specs
9421 begin
9422 Renamed_Eq := Empty;
9424 -- Spec of _Size
9426 Append_To (Res, Predef_Spec_Or_Body (Loc,
9427 Tag_Typ => Tag_Typ,
9428 Name => Name_uSize,
9429 Profile => New_List (
9430 Make_Parameter_Specification (Loc,
9431 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9432 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9434 Ret_Type => Standard_Long_Long_Integer));
9436 -- Specs for dispatching stream attributes
9438 declare
9439 Stream_Op_TSS_Names :
9440 constant array (Integer range <>) of TSS_Name_Type :=
9441 (TSS_Stream_Read,
9442 TSS_Stream_Write,
9443 TSS_Stream_Input,
9444 TSS_Stream_Output);
9446 begin
9447 for Op in Stream_Op_TSS_Names'Range loop
9448 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
9449 Append_To (Res,
9450 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
9451 Stream_Op_TSS_Names (Op)));
9452 end if;
9453 end loop;
9454 end;
9456 -- Spec of "=" is expanded if the type is not limited and if a user
9457 -- defined "=" was not already declared for the non-full view of a
9458 -- private extension
9460 if not Is_Limited_Type (Tag_Typ) then
9461 Eq_Needed := True;
9462 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9463 while Present (Prim) loop
9465 -- If a primitive is encountered that renames the predefined
9466 -- equality operator before reaching any explicit equality
9467 -- primitive, then we still need to create a predefined equality
9468 -- function, because calls to it can occur via the renaming. A
9469 -- new name is created for the equality to avoid conflicting with
9470 -- any user-defined equality. (Note that this doesn't account for
9471 -- renamings of equality nested within subpackages???)
9473 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9474 Has_Predef_Eq_Renaming := True;
9475 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
9477 -- User-defined equality
9479 elsif Is_User_Defined_Equality (Node (Prim)) then
9480 if No (Alias (Node (Prim)))
9481 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
9482 N_Subprogram_Renaming_Declaration
9483 then
9484 Eq_Needed := False;
9485 exit;
9487 -- If the parent is not an interface type and has an abstract
9488 -- equality function, the inherited equality is abstract as
9489 -- well, and no body can be created for it.
9491 elsif not Is_Interface (Etype (Tag_Typ))
9492 and then Present (Alias (Node (Prim)))
9493 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
9494 then
9495 Eq_Needed := False;
9496 exit;
9498 -- If the type has an equality function corresponding with
9499 -- a primitive defined in an interface type, the inherited
9500 -- equality is abstract as well, and no body can be created
9501 -- for it.
9503 elsif Present (Alias (Node (Prim)))
9504 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
9505 and then
9506 Is_Interface
9507 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
9508 then
9509 Eq_Needed := False;
9510 exit;
9511 end if;
9512 end if;
9514 Next_Elmt (Prim);
9515 end loop;
9517 -- If a renaming of predefined equality was found but there was no
9518 -- user-defined equality (so Eq_Needed is still true), then set the
9519 -- name back to Name_Op_Eq. But in the case where a user-defined
9520 -- equality was located after such a renaming, then the predefined
9521 -- equality function is still needed, so Eq_Needed must be set back
9522 -- to True.
9524 if Eq_Name /= Name_Op_Eq then
9525 if Eq_Needed then
9526 Eq_Name := Name_Op_Eq;
9527 else
9528 Eq_Needed := True;
9529 end if;
9530 end if;
9532 if Eq_Needed then
9533 Eq_Spec := Predef_Spec_Or_Body (Loc,
9534 Tag_Typ => Tag_Typ,
9535 Name => Eq_Name,
9536 Profile => New_List (
9537 Make_Parameter_Specification (Loc,
9538 Defining_Identifier =>
9539 Make_Defining_Identifier (Loc, Name_X),
9540 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9542 Make_Parameter_Specification (Loc,
9543 Defining_Identifier =>
9544 Make_Defining_Identifier (Loc, Name_Y),
9545 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9546 Ret_Type => Standard_Boolean);
9547 Append_To (Res, Eq_Spec);
9549 if Has_Predef_Eq_Renaming then
9550 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
9552 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9553 while Present (Prim) loop
9555 -- Any renamings of equality that appeared before an
9556 -- overriding equality must be updated to refer to the
9557 -- entity for the predefined equality, otherwise calls via
9558 -- the renaming would get incorrectly resolved to call the
9559 -- user-defined equality function.
9561 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9562 Set_Alias (Node (Prim), Renamed_Eq);
9564 -- Exit upon encountering a user-defined equality
9566 elsif Chars (Node (Prim)) = Name_Op_Eq
9567 and then No (Alias (Node (Prim)))
9568 then
9569 exit;
9570 end if;
9572 Next_Elmt (Prim);
9573 end loop;
9574 end if;
9575 end if;
9577 -- Spec for dispatching assignment
9579 Append_To (Res, Predef_Spec_Or_Body (Loc,
9580 Tag_Typ => Tag_Typ,
9581 Name => Name_uAssign,
9582 Profile => New_List (
9583 Make_Parameter_Specification (Loc,
9584 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9585 Out_Present => True,
9586 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9588 Make_Parameter_Specification (Loc,
9589 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
9590 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)))));
9591 end if;
9593 -- Ada 2005: Generate declarations for the following primitive
9594 -- operations for limited interfaces and synchronized types that
9595 -- implement a limited interface.
9597 -- Disp_Asynchronous_Select
9598 -- Disp_Conditional_Select
9599 -- Disp_Get_Prim_Op_Kind
9600 -- Disp_Get_Task_Id
9601 -- Disp_Requeue
9602 -- Disp_Timed_Select
9604 -- Disable the generation of these bodies if No_Dispatching_Calls,
9605 -- Ravenscar or ZFP is active.
9607 if Ada_Version >= Ada_2005
9608 and then not Restriction_Active (No_Dispatching_Calls)
9609 and then not Restriction_Active (No_Select_Statements)
9610 and then RTE_Available (RE_Select_Specific_Data)
9611 then
9612 -- These primitives are defined abstract in interface types
9614 if Is_Interface (Tag_Typ)
9615 and then Is_Limited_Record (Tag_Typ)
9616 then
9617 Append_To (Res,
9618 Make_Abstract_Subprogram_Declaration (Loc,
9619 Specification =>
9620 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9622 Append_To (Res,
9623 Make_Abstract_Subprogram_Declaration (Loc,
9624 Specification =>
9625 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9627 Append_To (Res,
9628 Make_Abstract_Subprogram_Declaration (Loc,
9629 Specification =>
9630 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9632 Append_To (Res,
9633 Make_Abstract_Subprogram_Declaration (Loc,
9634 Specification =>
9635 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9637 Append_To (Res,
9638 Make_Abstract_Subprogram_Declaration (Loc,
9639 Specification =>
9640 Make_Disp_Requeue_Spec (Tag_Typ)));
9642 Append_To (Res,
9643 Make_Abstract_Subprogram_Declaration (Loc,
9644 Specification =>
9645 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9647 -- If ancestor is an interface type, declare non-abstract primitives
9648 -- to override the abstract primitives of the interface type.
9650 -- In VM targets we define these primitives in all root tagged types
9651 -- that are not interface types. Done because in VM targets we don't
9652 -- have secondary dispatch tables and any derivation of Tag_Typ may
9653 -- cover limited interfaces (which always have these primitives since
9654 -- they may be ancestors of synchronized interface types).
9656 elsif (not Is_Interface (Tag_Typ)
9657 and then Is_Interface (Etype (Tag_Typ))
9658 and then Is_Limited_Record (Etype (Tag_Typ)))
9659 or else
9660 (Is_Concurrent_Record_Type (Tag_Typ)
9661 and then Has_Interfaces (Tag_Typ))
9662 or else
9663 (not Tagged_Type_Expansion
9664 and then not Is_Interface (Tag_Typ)
9665 and then Tag_Typ = Root_Type (Tag_Typ))
9666 then
9667 Append_To (Res,
9668 Make_Subprogram_Declaration (Loc,
9669 Specification =>
9670 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9672 Append_To (Res,
9673 Make_Subprogram_Declaration (Loc,
9674 Specification =>
9675 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9677 Append_To (Res,
9678 Make_Subprogram_Declaration (Loc,
9679 Specification =>
9680 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9682 Append_To (Res,
9683 Make_Subprogram_Declaration (Loc,
9684 Specification =>
9685 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9687 Append_To (Res,
9688 Make_Subprogram_Declaration (Loc,
9689 Specification =>
9690 Make_Disp_Requeue_Spec (Tag_Typ)));
9692 Append_To (Res,
9693 Make_Subprogram_Declaration (Loc,
9694 Specification =>
9695 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9696 end if;
9697 end if;
9699 -- All tagged types receive their own Deep_Adjust and Deep_Finalize
9700 -- regardless of whether they are controlled or may contain controlled
9701 -- components.
9703 -- Do not generate the routines if finalization is disabled
9705 if Restriction_Active (No_Finalization) then
9706 null;
9708 -- Finalization is not available for CIL value types
9710 elsif Is_Value_Type (Tag_Typ) then
9711 null;
9713 else
9714 if not Is_Limited_Type (Tag_Typ) then
9715 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
9716 end if;
9718 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
9719 end if;
9721 Predef_List := Res;
9722 end Make_Predefined_Primitive_Specs;
9724 -------------------------
9725 -- Make_Tag_Assignment --
9726 -------------------------
9728 function Make_Tag_Assignment (N : Node_Id) return Node_Id is
9729 Loc : constant Source_Ptr := Sloc (N);
9730 Def_If : constant Entity_Id := Defining_Identifier (N);
9731 Expr : constant Node_Id := Expression (N);
9732 Typ : constant Entity_Id := Etype (Def_If);
9733 Full_Typ : constant Entity_Id := Underlying_Type (Typ);
9734 New_Ref : Node_Id;
9736 begin
9737 if Is_Tagged_Type (Typ)
9738 and then not Is_Class_Wide_Type (Typ)
9739 and then not Is_CPP_Class (Typ)
9740 and then Tagged_Type_Expansion
9741 and then Nkind (Expr) /= N_Aggregate
9742 and then (Nkind (Expr) /= N_Qualified_Expression
9743 or else Nkind (Expression (Expr)) /= N_Aggregate)
9744 then
9745 New_Ref :=
9746 Make_Selected_Component (Loc,
9747 Prefix => New_Occurrence_Of (Def_If, Loc),
9748 Selector_Name =>
9749 New_Occurrence_Of (First_Tag_Component (Full_Typ), Loc));
9750 Set_Assignment_OK (New_Ref);
9752 return
9753 Make_Assignment_Statement (Loc,
9754 Name => New_Ref,
9755 Expression =>
9756 Unchecked_Convert_To (RTE (RE_Tag),
9757 New_Occurrence_Of (Node
9758 (First_Elmt (Access_Disp_Table (Full_Typ))), Loc)));
9759 else
9760 return Empty;
9761 end if;
9762 end Make_Tag_Assignment;
9764 ---------------------------------
9765 -- Needs_Simple_Initialization --
9766 ---------------------------------
9768 function Needs_Simple_Initialization
9769 (T : Entity_Id;
9770 Consider_IS : Boolean := True) return Boolean
9772 Consider_IS_NS : constant Boolean :=
9773 Normalize_Scalars or (Initialize_Scalars and Consider_IS);
9775 begin
9776 -- Never need initialization if it is suppressed
9778 if Initialization_Suppressed (T) then
9779 return False;
9780 end if;
9782 -- Check for private type, in which case test applies to the underlying
9783 -- type of the private type.
9785 if Is_Private_Type (T) then
9786 declare
9787 RT : constant Entity_Id := Underlying_Type (T);
9788 begin
9789 if Present (RT) then
9790 return Needs_Simple_Initialization (RT);
9791 else
9792 return False;
9793 end if;
9794 end;
9796 -- Scalar type with Default_Value aspect requires initialization
9798 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
9799 return True;
9801 -- Cases needing simple initialization are access types, and, if pragma
9802 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
9803 -- types.
9805 elsif Is_Access_Type (T)
9806 or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
9807 then
9808 return True;
9810 -- If Initialize/Normalize_Scalars is in effect, string objects also
9811 -- need initialization, unless they are created in the course of
9812 -- expanding an aggregate (since in the latter case they will be
9813 -- filled with appropriate initializing values before they are used).
9815 elsif Consider_IS_NS
9816 and then Is_Standard_String_Type (T)
9817 and then
9818 (not Is_Itype (T)
9819 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
9820 then
9821 return True;
9823 else
9824 return False;
9825 end if;
9826 end Needs_Simple_Initialization;
9828 ----------------------
9829 -- Predef_Deep_Spec --
9830 ----------------------
9832 function Predef_Deep_Spec
9833 (Loc : Source_Ptr;
9834 Tag_Typ : Entity_Id;
9835 Name : TSS_Name_Type;
9836 For_Body : Boolean := False) return Node_Id
9838 Formals : List_Id;
9840 begin
9841 -- V : in out Tag_Typ
9843 Formals := New_List (
9844 Make_Parameter_Specification (Loc,
9845 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
9846 In_Present => True,
9847 Out_Present => True,
9848 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)));
9850 -- F : Boolean := True
9852 if Name = TSS_Deep_Adjust
9853 or else Name = TSS_Deep_Finalize
9854 then
9855 Append_To (Formals,
9856 Make_Parameter_Specification (Loc,
9857 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
9858 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
9859 Expression => New_Occurrence_Of (Standard_True, Loc)));
9860 end if;
9862 return
9863 Predef_Spec_Or_Body (Loc,
9864 Name => Make_TSS_Name (Tag_Typ, Name),
9865 Tag_Typ => Tag_Typ,
9866 Profile => Formals,
9867 For_Body => For_Body);
9869 exception
9870 when RE_Not_Available =>
9871 return Empty;
9872 end Predef_Deep_Spec;
9874 -------------------------
9875 -- Predef_Spec_Or_Body --
9876 -------------------------
9878 function Predef_Spec_Or_Body
9879 (Loc : Source_Ptr;
9880 Tag_Typ : Entity_Id;
9881 Name : Name_Id;
9882 Profile : List_Id;
9883 Ret_Type : Entity_Id := Empty;
9884 For_Body : Boolean := False) return Node_Id
9886 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
9887 Spec : Node_Id;
9889 begin
9890 Set_Is_Public (Id, Is_Public (Tag_Typ));
9892 -- The internal flag is set to mark these declarations because they have
9893 -- specific properties. First, they are primitives even if they are not
9894 -- defined in the type scope (the freezing point is not necessarily in
9895 -- the same scope). Second, the predefined equality can be overridden by
9896 -- a user-defined equality, no body will be generated in this case.
9898 Set_Is_Internal (Id);
9900 if not Debug_Generated_Code then
9901 Set_Debug_Info_Off (Id);
9902 end if;
9904 if No (Ret_Type) then
9905 Spec :=
9906 Make_Procedure_Specification (Loc,
9907 Defining_Unit_Name => Id,
9908 Parameter_Specifications => Profile);
9909 else
9910 Spec :=
9911 Make_Function_Specification (Loc,
9912 Defining_Unit_Name => Id,
9913 Parameter_Specifications => Profile,
9914 Result_Definition => New_Occurrence_Of (Ret_Type, Loc));
9915 end if;
9917 if Is_Interface (Tag_Typ) then
9918 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9920 -- If body case, return empty subprogram body. Note that this is ill-
9921 -- formed, because there is not even a null statement, and certainly not
9922 -- a return in the function case. The caller is expected to do surgery
9923 -- on the body to add the appropriate stuff.
9925 elsif For_Body then
9926 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
9928 -- For the case of an Input attribute predefined for an abstract type,
9929 -- generate an abstract specification. This will never be called, but we
9930 -- need the slot allocated in the dispatching table so that attributes
9931 -- typ'Class'Input and typ'Class'Output will work properly.
9933 elsif Is_TSS (Name, TSS_Stream_Input)
9934 and then Is_Abstract_Type (Tag_Typ)
9935 then
9936 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
9938 -- Normal spec case, where we return a subprogram declaration
9940 else
9941 return Make_Subprogram_Declaration (Loc, Spec);
9942 end if;
9943 end Predef_Spec_Or_Body;
9945 -----------------------------
9946 -- Predef_Stream_Attr_Spec --
9947 -----------------------------
9949 function Predef_Stream_Attr_Spec
9950 (Loc : Source_Ptr;
9951 Tag_Typ : Entity_Id;
9952 Name : TSS_Name_Type;
9953 For_Body : Boolean := False) return Node_Id
9955 Ret_Type : Entity_Id;
9957 begin
9958 if Name = TSS_Stream_Input then
9959 Ret_Type := Tag_Typ;
9960 else
9961 Ret_Type := Empty;
9962 end if;
9964 return
9965 Predef_Spec_Or_Body
9966 (Loc,
9967 Name => Make_TSS_Name (Tag_Typ, Name),
9968 Tag_Typ => Tag_Typ,
9969 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
9970 Ret_Type => Ret_Type,
9971 For_Body => For_Body);
9972 end Predef_Stream_Attr_Spec;
9974 ---------------------------------
9975 -- Predefined_Primitive_Bodies --
9976 ---------------------------------
9978 function Predefined_Primitive_Bodies
9979 (Tag_Typ : Entity_Id;
9980 Renamed_Eq : Entity_Id) return List_Id
9982 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9983 Res : constant List_Id := New_List;
9984 Decl : Node_Id;
9985 Prim : Elmt_Id;
9986 Eq_Needed : Boolean;
9987 Eq_Name : Name_Id;
9988 Ent : Entity_Id;
9990 pragma Warnings (Off, Ent);
9992 begin
9993 pragma Assert (not Is_Interface (Tag_Typ));
9995 -- See if we have a predefined "=" operator
9997 if Present (Renamed_Eq) then
9998 Eq_Needed := True;
9999 Eq_Name := Chars (Renamed_Eq);
10001 -- If the parent is an interface type then it has defined all the
10002 -- predefined primitives abstract and we need to check if the type
10003 -- has some user defined "=" function which matches the profile of
10004 -- the Ada predefined equality operator to avoid generating it.
10006 elsif Is_Interface (Etype (Tag_Typ)) then
10007 Eq_Needed := True;
10008 Eq_Name := Name_Op_Eq;
10010 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10011 while Present (Prim) loop
10012 if Chars (Node (Prim)) = Name_Op_Eq
10013 and then not Is_Internal (Node (Prim))
10014 and then Present (First_Entity (Node (Prim)))
10016 -- The predefined equality primitive must have exactly two
10017 -- formals whose type is this tagged type
10019 and then Present (Last_Entity (Node (Prim)))
10020 and then Next_Entity (First_Entity (Node (Prim)))
10021 = Last_Entity (Node (Prim))
10022 and then Etype (First_Entity (Node (Prim))) = Tag_Typ
10023 and then Etype (Last_Entity (Node (Prim))) = Tag_Typ
10024 then
10025 Eq_Needed := False;
10026 Eq_Name := No_Name;
10027 exit;
10028 end if;
10030 Next_Elmt (Prim);
10031 end loop;
10033 else
10034 Eq_Needed := False;
10035 Eq_Name := No_Name;
10037 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10038 while Present (Prim) loop
10039 if Chars (Node (Prim)) = Name_Op_Eq
10040 and then Is_Internal (Node (Prim))
10041 then
10042 Eq_Needed := True;
10043 Eq_Name := Name_Op_Eq;
10044 exit;
10045 end if;
10047 Next_Elmt (Prim);
10048 end loop;
10049 end if;
10051 -- Body of _Size
10053 Decl := Predef_Spec_Or_Body (Loc,
10054 Tag_Typ => Tag_Typ,
10055 Name => Name_uSize,
10056 Profile => New_List (
10057 Make_Parameter_Specification (Loc,
10058 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10059 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10061 Ret_Type => Standard_Long_Long_Integer,
10062 For_Body => True);
10064 Set_Handled_Statement_Sequence (Decl,
10065 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10066 Make_Simple_Return_Statement (Loc,
10067 Expression =>
10068 Make_Attribute_Reference (Loc,
10069 Prefix => Make_Identifier (Loc, Name_X),
10070 Attribute_Name => Name_Size)))));
10072 Append_To (Res, Decl);
10074 -- Bodies for Dispatching stream IO routines. We need these only for
10075 -- non-limited types (in the limited case there is no dispatching).
10076 -- We also skip them if dispatching or finalization are not available
10077 -- or if stream operations are prohibited by restriction No_Streams or
10078 -- from use of pragma/aspect No_Tagged_Streams.
10080 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
10081 and then No (TSS (Tag_Typ, TSS_Stream_Read))
10082 then
10083 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
10084 Append_To (Res, Decl);
10085 end if;
10087 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
10088 and then No (TSS (Tag_Typ, TSS_Stream_Write))
10089 then
10090 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
10091 Append_To (Res, Decl);
10092 end if;
10094 -- Skip body of _Input for the abstract case, since the corresponding
10095 -- spec is abstract (see Predef_Spec_Or_Body).
10097 if not Is_Abstract_Type (Tag_Typ)
10098 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
10099 and then No (TSS (Tag_Typ, TSS_Stream_Input))
10100 then
10101 Build_Record_Or_Elementary_Input_Function
10102 (Loc, Tag_Typ, Decl, Ent);
10103 Append_To (Res, Decl);
10104 end if;
10106 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
10107 and then No (TSS (Tag_Typ, TSS_Stream_Output))
10108 then
10109 Build_Record_Or_Elementary_Output_Procedure (Loc, Tag_Typ, Decl, Ent);
10110 Append_To (Res, Decl);
10111 end if;
10113 -- Ada 2005: Generate bodies for the following primitive operations for
10114 -- limited interfaces and synchronized types that implement a limited
10115 -- interface.
10117 -- disp_asynchronous_select
10118 -- disp_conditional_select
10119 -- disp_get_prim_op_kind
10120 -- disp_get_task_id
10121 -- disp_timed_select
10123 -- The interface versions will have null bodies
10125 -- Disable the generation of these bodies if No_Dispatching_Calls,
10126 -- Ravenscar or ZFP is active.
10128 -- In VM targets we define these primitives in all root tagged types
10129 -- that are not interface types. Done because in VM targets we don't
10130 -- have secondary dispatch tables and any derivation of Tag_Typ may
10131 -- cover limited interfaces (which always have these primitives since
10132 -- they may be ancestors of synchronized interface types).
10134 if Ada_Version >= Ada_2005
10135 and then not Is_Interface (Tag_Typ)
10136 and then
10137 ((Is_Interface (Etype (Tag_Typ))
10138 and then Is_Limited_Record (Etype (Tag_Typ)))
10139 or else
10140 (Is_Concurrent_Record_Type (Tag_Typ)
10141 and then Has_Interfaces (Tag_Typ))
10142 or else
10143 (not Tagged_Type_Expansion
10144 and then Tag_Typ = Root_Type (Tag_Typ)))
10145 and then not Restriction_Active (No_Dispatching_Calls)
10146 and then not Restriction_Active (No_Select_Statements)
10147 and then RTE_Available (RE_Select_Specific_Data)
10148 then
10149 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
10150 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
10151 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
10152 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
10153 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
10154 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
10155 end if;
10157 if not Is_Limited_Type (Tag_Typ) and then not Is_Interface (Tag_Typ) then
10159 -- Body for equality
10161 if Eq_Needed then
10162 Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
10163 Append_To (Res, Decl);
10164 end if;
10166 -- Body for inequality (if required)
10168 Decl := Make_Neq_Body (Tag_Typ);
10170 if Present (Decl) then
10171 Append_To (Res, Decl);
10172 end if;
10174 -- Body for dispatching assignment
10176 Decl :=
10177 Predef_Spec_Or_Body (Loc,
10178 Tag_Typ => Tag_Typ,
10179 Name => Name_uAssign,
10180 Profile => New_List (
10181 Make_Parameter_Specification (Loc,
10182 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10183 Out_Present => True,
10184 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10186 Make_Parameter_Specification (Loc,
10187 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
10188 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10189 For_Body => True);
10191 Set_Handled_Statement_Sequence (Decl,
10192 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10193 Make_Assignment_Statement (Loc,
10194 Name => Make_Identifier (Loc, Name_X),
10195 Expression => Make_Identifier (Loc, Name_Y)))));
10197 Append_To (Res, Decl);
10198 end if;
10200 -- Generate empty bodies of routines Deep_Adjust and Deep_Finalize for
10201 -- tagged types which do not contain controlled components.
10203 -- Do not generate the routines if finalization is disabled
10205 if Restriction_Active (No_Finalization) then
10206 null;
10208 elsif not Has_Controlled_Component (Tag_Typ) then
10209 if not Is_Limited_Type (Tag_Typ) then
10210 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
10212 if Is_Controlled (Tag_Typ) then
10213 Set_Handled_Statement_Sequence (Decl,
10214 Make_Handled_Sequence_Of_Statements (Loc,
10215 Statements => New_List (
10216 Make_Adjust_Call (
10217 Obj_Ref => Make_Identifier (Loc, Name_V),
10218 Typ => Tag_Typ))));
10220 else
10221 Set_Handled_Statement_Sequence (Decl,
10222 Make_Handled_Sequence_Of_Statements (Loc,
10223 Statements => New_List (
10224 Make_Null_Statement (Loc))));
10225 end if;
10227 Append_To (Res, Decl);
10228 end if;
10230 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
10232 if Is_Controlled (Tag_Typ) then
10233 Set_Handled_Statement_Sequence (Decl,
10234 Make_Handled_Sequence_Of_Statements (Loc,
10235 Statements => New_List (
10236 Make_Final_Call
10237 (Obj_Ref => Make_Identifier (Loc, Name_V),
10238 Typ => Tag_Typ))));
10240 else
10241 Set_Handled_Statement_Sequence (Decl,
10242 Make_Handled_Sequence_Of_Statements (Loc,
10243 Statements => New_List (Make_Null_Statement (Loc))));
10244 end if;
10246 Append_To (Res, Decl);
10247 end if;
10249 return Res;
10250 end Predefined_Primitive_Bodies;
10252 ---------------------------------
10253 -- Predefined_Primitive_Freeze --
10254 ---------------------------------
10256 function Predefined_Primitive_Freeze
10257 (Tag_Typ : Entity_Id) return List_Id
10259 Res : constant List_Id := New_List;
10260 Prim : Elmt_Id;
10261 Frnodes : List_Id;
10263 begin
10264 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10265 while Present (Prim) loop
10266 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
10267 Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
10269 if Present (Frnodes) then
10270 Append_List_To (Res, Frnodes);
10271 end if;
10272 end if;
10274 Next_Elmt (Prim);
10275 end loop;
10277 return Res;
10278 end Predefined_Primitive_Freeze;
10280 -------------------------
10281 -- Stream_Operation_OK --
10282 -------------------------
10284 function Stream_Operation_OK
10285 (Typ : Entity_Id;
10286 Operation : TSS_Name_Type) return Boolean
10288 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
10290 begin
10291 -- Special case of a limited type extension: a default implementation
10292 -- of the stream attributes Read or Write exists if that attribute
10293 -- has been specified or is available for an ancestor type; a default
10294 -- implementation of the attribute Output (resp. Input) exists if the
10295 -- attribute has been specified or Write (resp. Read) is available for
10296 -- an ancestor type. The last condition only applies under Ada 2005.
10298 if Is_Limited_Type (Typ) and then Is_Tagged_Type (Typ) then
10299 if Operation = TSS_Stream_Read then
10300 Has_Predefined_Or_Specified_Stream_Attribute :=
10301 Has_Specified_Stream_Read (Typ);
10303 elsif Operation = TSS_Stream_Write then
10304 Has_Predefined_Or_Specified_Stream_Attribute :=
10305 Has_Specified_Stream_Write (Typ);
10307 elsif Operation = TSS_Stream_Input then
10308 Has_Predefined_Or_Specified_Stream_Attribute :=
10309 Has_Specified_Stream_Input (Typ)
10310 or else
10311 (Ada_Version >= Ada_2005
10312 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
10314 elsif Operation = TSS_Stream_Output then
10315 Has_Predefined_Or_Specified_Stream_Attribute :=
10316 Has_Specified_Stream_Output (Typ)
10317 or else
10318 (Ada_Version >= Ada_2005
10319 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
10320 end if;
10322 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
10324 if not Has_Predefined_Or_Specified_Stream_Attribute
10325 and then Is_Derived_Type (Typ)
10326 and then (Operation = TSS_Stream_Read
10327 or else Operation = TSS_Stream_Write)
10328 then
10329 Has_Predefined_Or_Specified_Stream_Attribute :=
10330 Present
10331 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
10332 end if;
10333 end if;
10335 -- If the type is not limited, or else is limited but the attribute is
10336 -- explicitly specified or is predefined for the type, then return True,
10337 -- unless other conditions prevail, such as restrictions prohibiting
10338 -- streams or dispatching operations. We also return True for limited
10339 -- interfaces, because they may be extended by nonlimited types and
10340 -- permit inheritance in this case (addresses cases where an abstract
10341 -- extension doesn't get 'Input declared, as per comments below, but
10342 -- 'Class'Input must still be allowed). Note that attempts to apply
10343 -- stream attributes to a limited interface or its class-wide type
10344 -- (or limited extensions thereof) will still get properly rejected
10345 -- by Check_Stream_Attribute.
10347 -- We exclude the Input operation from being a predefined subprogram in
10348 -- the case where the associated type is an abstract extension, because
10349 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
10350 -- we don't want an abstract version created because types derived from
10351 -- the abstract type may not even have Input available (for example if
10352 -- derived from a private view of the abstract type that doesn't have
10353 -- a visible Input), but a VM such as .NET or the Java VM can treat the
10354 -- operation as inherited anyway, and we don't want an abstract function
10355 -- to be (implicitly) inherited in that case because it can lead to a VM
10356 -- exception.
10358 -- Do not generate stream routines for type Finalization_Master because
10359 -- a master may never appear in types and therefore cannot be read or
10360 -- written.
10362 return
10363 (not Is_Limited_Type (Typ)
10364 or else Is_Interface (Typ)
10365 or else Has_Predefined_Or_Specified_Stream_Attribute)
10366 and then
10367 (Operation /= TSS_Stream_Input
10368 or else not Is_Abstract_Type (Typ)
10369 or else not Is_Derived_Type (Typ))
10370 and then not Has_Unknown_Discriminants (Typ)
10371 and then not
10372 (Is_Interface (Typ)
10373 and then
10374 (Is_Task_Interface (Typ)
10375 or else Is_Protected_Interface (Typ)
10376 or else Is_Synchronized_Interface (Typ)))
10377 and then not Restriction_Active (No_Streams)
10378 and then not Restriction_Active (No_Dispatch)
10379 and then No (No_Tagged_Streams_Pragma (Typ))
10380 and then not No_Run_Time_Mode
10381 and then RTE_Available (RE_Tag)
10382 and then No (Type_Without_Stream_Operation (Typ))
10383 and then RTE_Available (RE_Root_Stream_Type)
10384 and then not Is_RTE (Typ, RE_Finalization_Master);
10385 end Stream_Operation_OK;
10387 end Exp_Ch3;