]> git.ipfire.org Git - thirdparty/gcc.git/blob - gcc/ada/exp_ch3.adb
2010-10-26 Matthew Heaney <heaney@adacore.com>
[thirdparty/gcc.git] / gcc / ada / exp_ch3.adb
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-2010, 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 ------------------------------------------------------------------------------
25
26 with Atree; use Atree;
27 with Checks; use Checks;
28 with Einfo; use Einfo;
29 with Errout; use Errout;
30 with Exp_Aggr; use Exp_Aggr;
31 with Exp_Atag; use Exp_Atag;
32 with Exp_Ch4; use Exp_Ch4;
33 with Exp_Ch6; use Exp_Ch6;
34 with Exp_Ch7; use Exp_Ch7;
35 with Exp_Ch9; use Exp_Ch9;
36 with Exp_Ch11; use Exp_Ch11;
37 with Exp_Disp; use Exp_Disp;
38 with Exp_Dist; use Exp_Dist;
39 with Exp_Smem; use Exp_Smem;
40 with Exp_Strm; use Exp_Strm;
41 with Exp_Tss; use Exp_Tss;
42 with Exp_Util; use Exp_Util;
43 with Freeze; use Freeze;
44 with Namet; use Namet;
45 with Nlists; use Nlists;
46 with Nmake; use Nmake;
47 with Opt; use Opt;
48 with Restrict; use Restrict;
49 with Rident; use Rident;
50 with Rtsfind; use Rtsfind;
51 with Sem; use Sem;
52 with Sem_Aux; use Sem_Aux;
53 with Sem_Attr; use Sem_Attr;
54 with Sem_Cat; use Sem_Cat;
55 with Sem_Ch3; use Sem_Ch3;
56 with Sem_Ch6; use Sem_Ch6;
57 with Sem_Ch8; use Sem_Ch8;
58 with Sem_Disp; use Sem_Disp;
59 with Sem_Eval; use Sem_Eval;
60 with Sem_Mech; use Sem_Mech;
61 with Sem_Res; use Sem_Res;
62 with Sem_SCIL; use Sem_SCIL;
63 with Sem_Type; use Sem_Type;
64 with Sem_Util; use Sem_Util;
65 with Sinfo; use Sinfo;
66 with Stand; use Stand;
67 with Snames; use Snames;
68 with Targparm; use Targparm;
69 with Tbuild; use Tbuild;
70 with Ttypes; use Ttypes;
71 with Validsw; use Validsw;
72
73 package body Exp_Ch3 is
74
75 -----------------------
76 -- Local Subprograms --
77 -----------------------
78
79 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id;
80 -- Add the declaration of a finalization list to the freeze actions for
81 -- Def_Id, and return its defining identifier.
82
83 procedure Adjust_Discriminants (Rtype : Entity_Id);
84 -- This is used when freezing a record type. It attempts to construct
85 -- more restrictive subtypes for discriminants so that the max size of
86 -- the record can be calculated more accurately. See the body of this
87 -- procedure for details.
88
89 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
90 -- Build initialization procedure for given array type. Nod is a node
91 -- used for attachment of any actions required in its construction.
92 -- It also supplies the source location used for the procedure.
93
94 function Build_Discriminant_Formals
95 (Rec_Id : Entity_Id;
96 Use_Dl : Boolean) return List_Id;
97 -- This function uses the discriminants of a type to build a list of
98 -- formal parameters, used in Build_Init_Procedure among other places.
99 -- If the flag Use_Dl is set, the list is built using the already
100 -- defined discriminals of the type, as is the case for concurrent
101 -- types with discriminants. Otherwise new identifiers are created,
102 -- with the source names of the discriminants.
103
104 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
105 -- This function builds a static aggregate that can serve as the initial
106 -- value for an array type whose bounds are static, and whose component
107 -- type is a composite type that has a static equivalent aggregate.
108 -- The equivalent array aggregate is used both for object initialization
109 -- and for component initialization, when used in the following function.
110
111 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
112 -- This function builds a static aggregate that can serve as the initial
113 -- value for a record type whose components are scalar and initialized
114 -- with compile-time values, or arrays with similar initialization or
115 -- defaults. When possible, initialization of an object of the type can
116 -- be achieved by using a copy of the aggregate as an initial value, thus
117 -- removing the implicit call that would otherwise constitute elaboration
118 -- code.
119
120 function Build_Master_Renaming
121 (N : Node_Id;
122 T : Entity_Id) return Entity_Id;
123 -- If the designated type of an access type is a task type or contains
124 -- tasks, we make sure that a _Master variable is declared in the current
125 -- scope, and then declare a renaming for it:
126 --
127 -- atypeM : Master_Id renames _Master;
128 --
129 -- where atyp is the name of the access type. This declaration is used when
130 -- an allocator for the access type is expanded. The node is the full
131 -- declaration of the designated type that contains tasks. The renaming
132 -- declaration is inserted before N, and after the Master declaration.
133
134 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id);
135 -- Build record initialization procedure. N is the type declaration
136 -- node, and Pe is the corresponding entity for the record type.
137
138 procedure Build_Slice_Assignment (Typ : Entity_Id);
139 -- Build assignment procedure for one-dimensional arrays of controlled
140 -- types. Other array and slice assignments are expanded in-line, but
141 -- the code expansion for controlled components (when control actions
142 -- are active) can lead to very large blocks that GCC3 handles poorly.
143
144 procedure Build_Untagged_Equality (Typ : Entity_Id);
145 -- AI05-0123: Equality on untagged records composes. This procedure
146 -- builds the equality routine for an untagged record that has components
147 -- of a record type that has user-defined primitive equality operations.
148 -- The resulting operation is a TSS subprogram.
149
150 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
151 -- Create An Equality function for the non-tagged variant record 'Typ'
152 -- and attach it to the TSS list
153
154 procedure Check_Stream_Attributes (Typ : Entity_Id);
155 -- Check that if a limited extension has a parent with user-defined stream
156 -- attributes, and does not itself have user-defined stream-attributes,
157 -- then any limited component of the extension also has the corresponding
158 -- user-defined stream attributes.
159
160 procedure Clean_Task_Names
161 (Typ : Entity_Id;
162 Proc_Id : Entity_Id);
163 -- If an initialization procedure includes calls to generate names
164 -- for task subcomponents, indicate that secondary stack cleanup is
165 -- needed after an initialization. Typ is the component type, and Proc_Id
166 -- the initialization procedure for the enclosing composite type.
167
168 procedure Expand_Tagged_Root (T : Entity_Id);
169 -- Add a field _Tag at the beginning of the record. This field carries
170 -- the value of the access to the Dispatch table. This procedure is only
171 -- called on root type, the _Tag field being inherited by the descendants.
172
173 procedure Expand_Record_Controller (T : Entity_Id);
174 -- T must be a record type that Has_Controlled_Component. Add a field
175 -- _controller of type Record_Controller or Limited_Record_Controller
176 -- in the record T.
177
178 procedure Expand_Freeze_Array_Type (N : Node_Id);
179 -- Freeze an array type. Deals with building the initialization procedure,
180 -- creating the packed array type for a packed array and also with the
181 -- creation of the controlling procedures for the controlled case. The
182 -- argument N is the N_Freeze_Entity node for the type.
183
184 procedure Expand_Freeze_Enumeration_Type (N : Node_Id);
185 -- Freeze enumeration type with non-standard representation. Builds the
186 -- array and function needed to convert between enumeration pos and
187 -- enumeration representation values. N is the N_Freeze_Entity node
188 -- for the type.
189
190 procedure Expand_Freeze_Record_Type (N : Node_Id);
191 -- Freeze record type. Builds all necessary discriminant checking
192 -- and other ancillary functions, and builds dispatch tables where
193 -- needed. The argument N is the N_Freeze_Entity node. This processing
194 -- applies only to E_Record_Type entities, not to class wide types,
195 -- record subtypes, or private types.
196
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.
200
201 procedure Initialization_Warning (E : Entity_Id);
202 -- If static elaboration of the package is requested, indicate
203 -- when a type does meet the conditions for static initialization. If
204 -- E is a type, it has components that have no static initialization.
205 -- if E is an entity, its initial expression is not compile-time known.
206
207 function Init_Formals (Typ : Entity_Id) return List_Id;
208 -- This function builds the list of formals for an initialization routine.
209 -- The first formal is always _Init with the given type. For task value
210 -- record types and types containing tasks, three additional formals are
211 -- added:
212 --
213 -- _Master : Master_Id
214 -- _Chain : in out Activation_Chain
215 -- _Task_Name : String
216 --
217 -- The caller must append additional entries for discriminants if required.
218
219 function In_Runtime (E : Entity_Id) return Boolean;
220 -- Check if E is defined in the RTL (in a child of Ada or System). Used
221 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
222
223 function Is_Variable_Size_Array (E : Entity_Id) return Boolean;
224 -- Returns true if E has variable size components
225
226 function Is_Variable_Size_Record (E : Entity_Id) return Boolean;
227 -- Returns true if E has variable size components
228
229 function Make_Eq_Body
230 (Typ : Entity_Id;
231 Eq_Name : Name_Id) return Node_Id;
232 -- Build the body of a primitive equality operation for a tagged record
233 -- type, or in Ada 2012 for any record type that has components with a
234 -- user-defined equality. Factored out of Predefined_Primitive_Bodies.
235
236 function Make_Eq_Case
237 (E : Entity_Id;
238 CL : Node_Id;
239 Discr : Entity_Id := Empty) return List_Id;
240 -- Building block for variant record equality. Defined to share the code
241 -- between the tagged and non-tagged case. Given a Component_List node CL,
242 -- it generates an 'if' followed by a 'case' statement that compares all
243 -- components of local temporaries named X and Y (that are declared as
244 -- formals at some upper level). E provides the Sloc to be used for the
245 -- generated code. Discr is used as the case statement switch in the case
246 -- of Unchecked_Union equality.
247
248 function Make_Eq_If
249 (E : Entity_Id;
250 L : List_Id) return Node_Id;
251 -- Building block for variant record equality. Defined to share the code
252 -- between the tagged and non-tagged case. Given the list of components
253 -- (or discriminants) L, it generates a return statement that compares all
254 -- components of local temporaries named X and Y (that are declared as
255 -- formals at some upper level). E provides the Sloc to be used for the
256 -- generated code.
257
258 procedure Make_Predefined_Primitive_Specs
259 (Tag_Typ : Entity_Id;
260 Predef_List : out List_Id;
261 Renamed_Eq : out Entity_Id);
262 -- Create a list with the specs of the predefined primitive operations.
263 -- For tagged types that are interfaces all these primitives are defined
264 -- abstract.
265 --
266 -- The following entries are present for all tagged types, and provide
267 -- the results of the corresponding attribute applied to the object.
268 -- Dispatching is required in general, since the result of the attribute
269 -- will vary with the actual object subtype.
270 --
271 -- _alignment provides result of 'Alignment attribute
272 -- _size provides result of 'Size attribute
273 -- typSR provides result of 'Read attribute
274 -- typSW provides result of 'Write attribute
275 -- typSI provides result of 'Input attribute
276 -- typSO provides result of 'Output attribute
277 --
278 -- The following entries are additionally present for non-limited tagged
279 -- types, and implement additional dispatching operations for predefined
280 -- operations:
281 --
282 -- _equality implements "=" operator
283 -- _assign implements assignment operation
284 -- typDF implements deep finalization
285 -- typDA implements deep adjust
286 --
287 -- The latter two are empty procedures unless the type contains some
288 -- controlled components that require finalization actions (the deep
289 -- in the name refers to the fact that the action applies to components).
290 --
291 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
292 -- returns the value Empty, or else the defining unit name for the
293 -- predefined equality function in the case where the type has a primitive
294 -- operation that is a renaming of predefined equality (but only if there
295 -- is also an overriding user-defined equality function). The returned
296 -- Renamed_Eq will be passed to the corresponding parameter of
297 -- Predefined_Primitive_Bodies.
298
299 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
300 -- returns True if there are representation clauses for type T that are not
301 -- inherited. If the result is false, the init_proc and the discriminant
302 -- checking functions of the parent can be reused by a derived type.
303
304 procedure Make_Controlling_Function_Wrappers
305 (Tag_Typ : Entity_Id;
306 Decl_List : out List_Id;
307 Body_List : out List_Id);
308 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
309 -- associated with inherited functions with controlling results which
310 -- are not overridden. The body of each wrapper function consists solely
311 -- of a return statement whose expression is an extension aggregate
312 -- invoking the inherited subprogram's parent subprogram and extended
313 -- with a null association list.
314
315 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id;
316 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
317 -- null procedures inherited from an interface type that have not been
318 -- overridden. Only one null procedure will be created for a given set of
319 -- inherited null procedures with homographic profiles.
320
321 function Predef_Spec_Or_Body
322 (Loc : Source_Ptr;
323 Tag_Typ : Entity_Id;
324 Name : Name_Id;
325 Profile : List_Id;
326 Ret_Type : Entity_Id := Empty;
327 For_Body : Boolean := False) return Node_Id;
328 -- This function generates the appropriate expansion for a predefined
329 -- primitive operation specified by its name, parameter profile and
330 -- return type (Empty means this is a procedure). If For_Body is false,
331 -- then the returned node is a subprogram declaration. If For_Body is
332 -- true, then the returned node is a empty subprogram body containing
333 -- no declarations and no statements.
334
335 function Predef_Stream_Attr_Spec
336 (Loc : Source_Ptr;
337 Tag_Typ : Entity_Id;
338 Name : TSS_Name_Type;
339 For_Body : Boolean := False) return Node_Id;
340 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
341 -- input and output attribute whose specs are constructed in Exp_Strm.
342
343 function Predef_Deep_Spec
344 (Loc : Source_Ptr;
345 Tag_Typ : Entity_Id;
346 Name : TSS_Name_Type;
347 For_Body : Boolean := False) return Node_Id;
348 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
349 -- and _deep_finalize
350
351 function Predefined_Primitive_Bodies
352 (Tag_Typ : Entity_Id;
353 Renamed_Eq : Entity_Id) return List_Id;
354 -- Create the bodies of the predefined primitives that are described in
355 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
356 -- the defining unit name of the type's predefined equality as returned
357 -- by Make_Predefined_Primitive_Specs.
358
359 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
360 -- Freeze entities of all predefined primitive operations. This is needed
361 -- because the bodies of these operations do not normally do any freezing.
362
363 function Stream_Operation_OK
364 (Typ : Entity_Id;
365 Operation : TSS_Name_Type) return Boolean;
366 -- Check whether the named stream operation must be emitted for a given
367 -- type. The rules for inheritance of stream attributes by type extensions
368 -- are enforced by this function. Furthermore, various restrictions prevent
369 -- the generation of these operations, as a useful optimization or for
370 -- certification purposes.
371
372 ---------------------
373 -- Add_Final_Chain --
374 ---------------------
375
376 function Add_Final_Chain (Def_Id : Entity_Id) return Entity_Id is
377 Loc : constant Source_Ptr := Sloc (Def_Id);
378 Flist : Entity_Id;
379
380 begin
381 Flist :=
382 Make_Defining_Identifier (Loc,
383 New_External_Name (Chars (Def_Id), 'L'));
384
385 Append_Freeze_Action (Def_Id,
386 Make_Object_Declaration (Loc,
387 Defining_Identifier => Flist,
388 Object_Definition =>
389 New_Reference_To (RTE (RE_List_Controller), Loc)));
390
391 return Flist;
392 end Add_Final_Chain;
393
394 --------------------------
395 -- Adjust_Discriminants --
396 --------------------------
397
398 -- This procedure attempts to define subtypes for discriminants that are
399 -- more restrictive than those declared. Such a replacement is possible if
400 -- we can demonstrate that values outside the restricted range would cause
401 -- constraint errors in any case. The advantage of restricting the
402 -- discriminant types in this way is that the maximum size of the variant
403 -- record can be calculated more conservatively.
404
405 -- An example of a situation in which we can perform this type of
406 -- restriction is the following:
407
408 -- subtype B is range 1 .. 10;
409 -- type Q is array (B range <>) of Integer;
410
411 -- type V (N : Natural) is record
412 -- C : Q (1 .. N);
413 -- end record;
414
415 -- In this situation, we can restrict the upper bound of N to 10, since
416 -- any larger value would cause a constraint error in any case.
417
418 -- There are many situations in which such restriction is possible, but
419 -- for now, we just look for cases like the above, where the component
420 -- in question is a one dimensional array whose upper bound is one of
421 -- the record discriminants. Also the component must not be part of
422 -- any variant part, since then the component does not always exist.
423
424 procedure Adjust_Discriminants (Rtype : Entity_Id) is
425 Loc : constant Source_Ptr := Sloc (Rtype);
426 Comp : Entity_Id;
427 Ctyp : Entity_Id;
428 Ityp : Entity_Id;
429 Lo : Node_Id;
430 Hi : Node_Id;
431 P : Node_Id;
432 Loval : Uint;
433 Discr : Entity_Id;
434 Dtyp : Entity_Id;
435 Dhi : Node_Id;
436 Dhiv : Uint;
437 Ahi : Node_Id;
438 Ahiv : Uint;
439 Tnn : Entity_Id;
440
441 begin
442 Comp := First_Component (Rtype);
443 while Present (Comp) loop
444
445 -- If our parent is a variant, quit, we do not look at components
446 -- that are in variant parts, because they may not always exist.
447
448 P := Parent (Comp); -- component declaration
449 P := Parent (P); -- component list
450
451 exit when Nkind (Parent (P)) = N_Variant;
452
453 -- We are looking for a one dimensional array type
454
455 Ctyp := Etype (Comp);
456
457 if not Is_Array_Type (Ctyp)
458 or else Number_Dimensions (Ctyp) > 1
459 then
460 goto Continue;
461 end if;
462
463 -- The lower bound must be constant, and the upper bound is a
464 -- discriminant (which is a discriminant of the current record).
465
466 Ityp := Etype (First_Index (Ctyp));
467 Lo := Type_Low_Bound (Ityp);
468 Hi := Type_High_Bound (Ityp);
469
470 if not Compile_Time_Known_Value (Lo)
471 or else Nkind (Hi) /= N_Identifier
472 or else No (Entity (Hi))
473 or else Ekind (Entity (Hi)) /= E_Discriminant
474 then
475 goto Continue;
476 end if;
477
478 -- We have an array with appropriate bounds
479
480 Loval := Expr_Value (Lo);
481 Discr := Entity (Hi);
482 Dtyp := Etype (Discr);
483
484 -- See if the discriminant has a known upper bound
485
486 Dhi := Type_High_Bound (Dtyp);
487
488 if not Compile_Time_Known_Value (Dhi) then
489 goto Continue;
490 end if;
491
492 Dhiv := Expr_Value (Dhi);
493
494 -- See if base type of component array has known upper bound
495
496 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
497
498 if not Compile_Time_Known_Value (Ahi) then
499 goto Continue;
500 end if;
501
502 Ahiv := Expr_Value (Ahi);
503
504 -- The condition for doing the restriction is that the high bound
505 -- of the discriminant is greater than the low bound of the array,
506 -- and is also greater than the high bound of the base type index.
507
508 if Dhiv > Loval and then Dhiv > Ahiv then
509
510 -- We can reset the upper bound of the discriminant type to
511 -- whichever is larger, the low bound of the component, or
512 -- the high bound of the base type array index.
513
514 -- We build a subtype that is declared as
515
516 -- subtype Tnn is discr_type range discr_type'First .. max;
517
518 -- And insert this declaration into the tree. The type of the
519 -- discriminant is then reset to this more restricted subtype.
520
521 Tnn := Make_Temporary (Loc, 'T');
522
523 Insert_Action (Declaration_Node (Rtype),
524 Make_Subtype_Declaration (Loc,
525 Defining_Identifier => Tnn,
526 Subtype_Indication =>
527 Make_Subtype_Indication (Loc,
528 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
529 Constraint =>
530 Make_Range_Constraint (Loc,
531 Range_Expression =>
532 Make_Range (Loc,
533 Low_Bound =>
534 Make_Attribute_Reference (Loc,
535 Attribute_Name => Name_First,
536 Prefix => New_Occurrence_Of (Dtyp, Loc)),
537 High_Bound =>
538 Make_Integer_Literal (Loc,
539 Intval => UI_Max (Loval, Ahiv)))))));
540
541 Set_Etype (Discr, Tnn);
542 end if;
543
544 <<Continue>>
545 Next_Component (Comp);
546 end loop;
547 end Adjust_Discriminants;
548
549 ---------------------------
550 -- Build_Array_Init_Proc --
551 ---------------------------
552
553 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
554 Loc : constant Source_Ptr := Sloc (Nod);
555 Comp_Type : constant Entity_Id := Component_Type (A_Type);
556 Index_List : List_Id;
557 Proc_Id : Entity_Id;
558 Body_Stmts : List_Id;
559 Has_Default_Init : Boolean;
560
561 function Init_Component return List_Id;
562 -- Create one statement to initialize one array component, designated
563 -- by a full set of indexes.
564
565 function Init_One_Dimension (N : Int) return List_Id;
566 -- Create loop to initialize one dimension of the array. The single
567 -- statement in the loop body initializes the inner dimensions if any,
568 -- or else the single component. Note that this procedure is called
569 -- recursively, with N being the dimension to be initialized. A call
570 -- with N greater than the number of dimensions simply generates the
571 -- component initialization, terminating the recursion.
572
573 --------------------
574 -- Init_Component --
575 --------------------
576
577 function Init_Component return List_Id is
578 Comp : Node_Id;
579
580 begin
581 Comp :=
582 Make_Indexed_Component (Loc,
583 Prefix => Make_Identifier (Loc, Name_uInit),
584 Expressions => Index_List);
585
586 if Needs_Simple_Initialization (Comp_Type) then
587 Set_Assignment_OK (Comp);
588 return New_List (
589 Make_Assignment_Statement (Loc,
590 Name => Comp,
591 Expression =>
592 Get_Simple_Init_Val
593 (Comp_Type, Nod, Component_Size (A_Type))));
594
595 else
596 Clean_Task_Names (Comp_Type, Proc_Id);
597 return
598 Build_Initialization_Call
599 (Loc, Comp, Comp_Type,
600 In_Init_Proc => True,
601 Enclos_Type => A_Type);
602 end if;
603 end Init_Component;
604
605 ------------------------
606 -- Init_One_Dimension --
607 ------------------------
608
609 function Init_One_Dimension (N : Int) return List_Id is
610 Index : Entity_Id;
611
612 begin
613 -- If the component does not need initializing, then there is nothing
614 -- to do here, so we return a null body. This occurs when generating
615 -- the dummy Init_Proc needed for Initialize_Scalars processing.
616
617 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
618 and then not Needs_Simple_Initialization (Comp_Type)
619 and then not Has_Task (Comp_Type)
620 then
621 return New_List (Make_Null_Statement (Loc));
622
623 -- If all dimensions dealt with, we simply initialize the component
624
625 elsif N > Number_Dimensions (A_Type) then
626 return Init_Component;
627
628 -- Here we generate the required loop
629
630 else
631 Index :=
632 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
633
634 Append (New_Reference_To (Index, Loc), Index_List);
635
636 return New_List (
637 Make_Implicit_Loop_Statement (Nod,
638 Identifier => Empty,
639 Iteration_Scheme =>
640 Make_Iteration_Scheme (Loc,
641 Loop_Parameter_Specification =>
642 Make_Loop_Parameter_Specification (Loc,
643 Defining_Identifier => Index,
644 Discrete_Subtype_Definition =>
645 Make_Attribute_Reference (Loc,
646 Prefix => Make_Identifier (Loc, Name_uInit),
647 Attribute_Name => Name_Range,
648 Expressions => New_List (
649 Make_Integer_Literal (Loc, N))))),
650 Statements => Init_One_Dimension (N + 1)));
651 end if;
652 end Init_One_Dimension;
653
654 -- Start of processing for Build_Array_Init_Proc
655
656 begin
657 -- Nothing to generate in the following cases:
658
659 -- 1. Initialization is suppressed for the type
660 -- 2. The type is a value type, in the CIL sense.
661 -- 3. The type has CIL/JVM convention.
662 -- 4. An initialization already exists for the base type
663
664 if Suppress_Init_Proc (A_Type)
665 or else Is_Value_Type (Comp_Type)
666 or else Convention (A_Type) = Convention_CIL
667 or else Convention (A_Type) = Convention_Java
668 or else Present (Base_Init_Proc (A_Type))
669 then
670 return;
671 end if;
672
673 Index_List := New_List;
674
675 -- We need an initialization procedure if any of the following is true:
676
677 -- 1. The component type has an initialization procedure
678 -- 2. The component type needs simple initialization
679 -- 3. Tasks are present
680 -- 4. The type is marked as a public entity
681
682 -- The reason for the public entity test is to deal properly with the
683 -- Initialize_Scalars pragma. This pragma can be set in the client and
684 -- not in the declaring package, this means the client will make a call
685 -- to the initialization procedure (because one of conditions 1-3 must
686 -- apply in this case), and we must generate a procedure (even if it is
687 -- null) to satisfy the call in this case.
688
689 -- Exception: do not build an array init_proc for a type whose root
690 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
691 -- is no place to put the code, and in any case we handle initialization
692 -- of such types (in the Initialize_Scalars case, that's the only time
693 -- the issue arises) in a special manner anyway which does not need an
694 -- init_proc.
695
696 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
697 or else Needs_Simple_Initialization (Comp_Type)
698 or else Has_Task (Comp_Type);
699
700 if Has_Default_Init
701 or else (not Restriction_Active (No_Initialize_Scalars)
702 and then Is_Public (A_Type)
703 and then Root_Type (A_Type) /= Standard_String
704 and then Root_Type (A_Type) /= Standard_Wide_String
705 and then Root_Type (A_Type) /= Standard_Wide_Wide_String)
706 then
707 Proc_Id :=
708 Make_Defining_Identifier (Loc,
709 Chars => Make_Init_Proc_Name (A_Type));
710
711 -- If No_Default_Initialization restriction is active, then we don't
712 -- want to build an init_proc, but we need to mark that an init_proc
713 -- would be needed if this restriction was not active (so that we can
714 -- detect attempts to call it), so set a dummy init_proc in place.
715 -- This is only done though when actual default initialization is
716 -- needed (and not done when only Is_Public is True), since otherwise
717 -- objects such as arrays of scalars could be wrongly flagged as
718 -- violating the restriction.
719
720 if Restriction_Active (No_Default_Initialization) then
721 if Has_Default_Init then
722 Set_Init_Proc (A_Type, Proc_Id);
723 end if;
724
725 return;
726 end if;
727
728 Body_Stmts := Init_One_Dimension (1);
729
730 Discard_Node (
731 Make_Subprogram_Body (Loc,
732 Specification =>
733 Make_Procedure_Specification (Loc,
734 Defining_Unit_Name => Proc_Id,
735 Parameter_Specifications => Init_Formals (A_Type)),
736 Declarations => New_List,
737 Handled_Statement_Sequence =>
738 Make_Handled_Sequence_Of_Statements (Loc,
739 Statements => Body_Stmts)));
740
741 Set_Ekind (Proc_Id, E_Procedure);
742 Set_Is_Public (Proc_Id, Is_Public (A_Type));
743 Set_Is_Internal (Proc_Id);
744 Set_Has_Completion (Proc_Id);
745
746 if not Debug_Generated_Code then
747 Set_Debug_Info_Off (Proc_Id);
748 end if;
749
750 -- Set inlined unless controlled stuff or tasks around, in which
751 -- case we do not want to inline, because nested stuff may cause
752 -- difficulties in inter-unit inlining, and furthermore there is
753 -- in any case no point in inlining such complex init procs.
754
755 if not Has_Task (Proc_Id)
756 and then not Needs_Finalization (Proc_Id)
757 then
758 Set_Is_Inlined (Proc_Id);
759 end if;
760
761 -- Associate Init_Proc with type, and determine if the procedure
762 -- is null (happens because of the Initialize_Scalars pragma case,
763 -- where we have to generate a null procedure in case it is called
764 -- by a client with Initialize_Scalars set). Such procedures have
765 -- to be generated, but do not have to be called, so we mark them
766 -- as null to suppress the call.
767
768 Set_Init_Proc (A_Type, Proc_Id);
769
770 if List_Length (Body_Stmts) = 1
771
772 -- We must skip SCIL nodes because they may have been added to this
773 -- list by Insert_Actions.
774
775 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
776 then
777 Set_Is_Null_Init_Proc (Proc_Id);
778
779 else
780 -- Try to build a static aggregate to initialize statically
781 -- objects of the type. This can only be done for constrained
782 -- one-dimensional arrays with static bounds.
783
784 Set_Static_Initialization
785 (Proc_Id,
786 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
787 end if;
788 end if;
789 end Build_Array_Init_Proc;
790
791 -----------------------------
792 -- Build_Class_Wide_Master --
793 -----------------------------
794
795 procedure Build_Class_Wide_Master (T : Entity_Id) is
796 Loc : constant Source_Ptr := Sloc (T);
797 M_Id : Entity_Id;
798 Decl : Node_Id;
799 P : Node_Id;
800 Par : Node_Id;
801 Scop : Entity_Id;
802
803 begin
804 -- Nothing to do if there is no task hierarchy
805
806 if Restriction_Active (No_Task_Hierarchy) then
807 return;
808 end if;
809
810 -- Find declaration that created the access type: either a type
811 -- declaration, or an object declaration with an access definition,
812 -- in which case the type is anonymous.
813
814 if Is_Itype (T) then
815 P := Associated_Node_For_Itype (T);
816 else
817 P := Parent (T);
818 end if;
819
820 Scop := Find_Master_Scope (T);
821
822 -- Nothing to do if we already built a master entity for this scope
823
824 if not Has_Master_Entity (Scop) then
825
826 -- First build the master entity
827 -- _Master : constant Master_Id := Current_Master.all;
828 -- and insert it just before the current declaration.
829
830 Decl :=
831 Make_Object_Declaration (Loc,
832 Defining_Identifier =>
833 Make_Defining_Identifier (Loc, Name_uMaster),
834 Constant_Present => True,
835 Object_Definition => New_Reference_To (Standard_Integer, Loc),
836 Expression =>
837 Make_Explicit_Dereference (Loc,
838 New_Reference_To (RTE (RE_Current_Master), Loc)));
839
840 Set_Has_Master_Entity (Scop);
841 Insert_Action (P, Decl);
842 Analyze (Decl);
843
844 -- Now mark the containing scope as a task master. Masters
845 -- associated with return statements are already marked at
846 -- this stage (see Analyze_Subprogram_Body).
847
848 if Ekind (Current_Scope) /= E_Return_Statement then
849 Par := P;
850 while Nkind (Par) /= N_Compilation_Unit loop
851 Par := Parent (Par);
852
853 -- If we fall off the top, we are at the outer level, and the
854 -- environment task is our effective master, so nothing to mark.
855
856 if Nkind_In
857 (Par, N_Task_Body, N_Block_Statement, N_Subprogram_Body)
858 then
859 Set_Is_Task_Master (Par, True);
860 exit;
861 end if;
862 end loop;
863 end if;
864 end if;
865
866 -- Now define the renaming of the master_id
867
868 M_Id :=
869 Make_Defining_Identifier (Loc,
870 New_External_Name (Chars (T), 'M'));
871
872 Decl :=
873 Make_Object_Renaming_Declaration (Loc,
874 Defining_Identifier => M_Id,
875 Subtype_Mark => New_Reference_To (Standard_Integer, Loc),
876 Name => Make_Identifier (Loc, Name_uMaster));
877 Insert_Before (P, Decl);
878 Analyze (Decl);
879
880 Set_Master_Id (T, M_Id);
881
882 exception
883 when RE_Not_Available =>
884 return;
885 end Build_Class_Wide_Master;
886
887 --------------------------------
888 -- Build_Discr_Checking_Funcs --
889 --------------------------------
890
891 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
892 Rec_Id : Entity_Id;
893 Loc : Source_Ptr;
894 Enclosing_Func_Id : Entity_Id;
895 Sequence : Nat := 1;
896 Type_Def : Node_Id;
897 V : Node_Id;
898
899 function Build_Case_Statement
900 (Case_Id : Entity_Id;
901 Variant : Node_Id) return Node_Id;
902 -- Build a case statement containing only two alternatives. The first
903 -- alternative corresponds exactly to the discrete choices given on the
904 -- variant with contains the components that we are generating the
905 -- checks for. If the discriminant is one of these return False. The
906 -- second alternative is an OTHERS choice that will return True
907 -- indicating the discriminant did not match.
908
909 function Build_Dcheck_Function
910 (Case_Id : Entity_Id;
911 Variant : Node_Id) return Entity_Id;
912 -- Build the discriminant checking function for a given variant
913
914 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
915 -- Builds the discriminant checking function for each variant of the
916 -- given variant part of the record type.
917
918 --------------------------
919 -- Build_Case_Statement --
920 --------------------------
921
922 function Build_Case_Statement
923 (Case_Id : Entity_Id;
924 Variant : Node_Id) return Node_Id
925 is
926 Alt_List : constant List_Id := New_List;
927 Actuals_List : List_Id;
928 Case_Node : Node_Id;
929 Case_Alt_Node : Node_Id;
930 Choice : Node_Id;
931 Choice_List : List_Id;
932 D : Entity_Id;
933 Return_Node : Node_Id;
934
935 begin
936 Case_Node := New_Node (N_Case_Statement, Loc);
937
938 -- Replace the discriminant which controls the variant, with the name
939 -- of the formal of the checking function.
940
941 Set_Expression (Case_Node,
942 Make_Identifier (Loc, Chars (Case_Id)));
943
944 Choice := First (Discrete_Choices (Variant));
945
946 if Nkind (Choice) = N_Others_Choice then
947 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
948 else
949 Choice_List := New_Copy_List (Discrete_Choices (Variant));
950 end if;
951
952 if not Is_Empty_List (Choice_List) then
953 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
954 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
955
956 -- In case this is a nested variant, we need to return the result
957 -- of the discriminant checking function for the immediately
958 -- enclosing variant.
959
960 if Present (Enclosing_Func_Id) then
961 Actuals_List := New_List;
962
963 D := First_Discriminant (Rec_Id);
964 while Present (D) loop
965 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
966 Next_Discriminant (D);
967 end loop;
968
969 Return_Node :=
970 Make_Simple_Return_Statement (Loc,
971 Expression =>
972 Make_Function_Call (Loc,
973 Name =>
974 New_Reference_To (Enclosing_Func_Id, Loc),
975 Parameter_Associations =>
976 Actuals_List));
977
978 else
979 Return_Node :=
980 Make_Simple_Return_Statement (Loc,
981 Expression =>
982 New_Reference_To (Standard_False, Loc));
983 end if;
984
985 Set_Statements (Case_Alt_Node, New_List (Return_Node));
986 Append (Case_Alt_Node, Alt_List);
987 end if;
988
989 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
990 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
991 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
992
993 Return_Node :=
994 Make_Simple_Return_Statement (Loc,
995 Expression =>
996 New_Reference_To (Standard_True, Loc));
997
998 Set_Statements (Case_Alt_Node, New_List (Return_Node));
999 Append (Case_Alt_Node, Alt_List);
1000
1001 Set_Alternatives (Case_Node, Alt_List);
1002 return Case_Node;
1003 end Build_Case_Statement;
1004
1005 ---------------------------
1006 -- Build_Dcheck_Function --
1007 ---------------------------
1008
1009 function Build_Dcheck_Function
1010 (Case_Id : Entity_Id;
1011 Variant : Node_Id) return Entity_Id
1012 is
1013 Body_Node : Node_Id;
1014 Func_Id : Entity_Id;
1015 Parameter_List : List_Id;
1016 Spec_Node : Node_Id;
1017
1018 begin
1019 Body_Node := New_Node (N_Subprogram_Body, Loc);
1020 Sequence := Sequence + 1;
1021
1022 Func_Id :=
1023 Make_Defining_Identifier (Loc,
1024 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
1025
1026 Spec_Node := New_Node (N_Function_Specification, Loc);
1027 Set_Defining_Unit_Name (Spec_Node, Func_Id);
1028
1029 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
1030
1031 Set_Parameter_Specifications (Spec_Node, Parameter_List);
1032 Set_Result_Definition (Spec_Node,
1033 New_Reference_To (Standard_Boolean, Loc));
1034 Set_Specification (Body_Node, Spec_Node);
1035 Set_Declarations (Body_Node, New_List);
1036
1037 Set_Handled_Statement_Sequence (Body_Node,
1038 Make_Handled_Sequence_Of_Statements (Loc,
1039 Statements => New_List (
1040 Build_Case_Statement (Case_Id, Variant))));
1041
1042 Set_Ekind (Func_Id, E_Function);
1043 Set_Mechanism (Func_Id, Default_Mechanism);
1044 Set_Is_Inlined (Func_Id, True);
1045 Set_Is_Pure (Func_Id, True);
1046 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
1047 Set_Is_Internal (Func_Id, True);
1048
1049 if not Debug_Generated_Code then
1050 Set_Debug_Info_Off (Func_Id);
1051 end if;
1052
1053 Analyze (Body_Node);
1054
1055 Append_Freeze_Action (Rec_Id, Body_Node);
1056 Set_Dcheck_Function (Variant, Func_Id);
1057 return Func_Id;
1058 end Build_Dcheck_Function;
1059
1060 ----------------------------
1061 -- Build_Dcheck_Functions --
1062 ----------------------------
1063
1064 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1065 Component_List_Node : Node_Id;
1066 Decl : Entity_Id;
1067 Discr_Name : Entity_Id;
1068 Func_Id : Entity_Id;
1069 Variant : Node_Id;
1070 Saved_Enclosing_Func_Id : Entity_Id;
1071
1072 begin
1073 -- Build the discriminant-checking function for each variant, and
1074 -- label all components of that variant with the function's name.
1075 -- We only Generate a discriminant-checking function when the
1076 -- variant is not empty, to prevent the creation of dead code.
1077 -- The exception to that is when Frontend_Layout_On_Target is set,
1078 -- because the variant record size function generated in package
1079 -- Layout needs to generate calls to all discriminant-checking
1080 -- functions, including those for empty variants.
1081
1082 Discr_Name := Entity (Name (Variant_Part_Node));
1083 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1084
1085 while Present (Variant) loop
1086 Component_List_Node := Component_List (Variant);
1087
1088 if not Null_Present (Component_List_Node)
1089 or else Frontend_Layout_On_Target
1090 then
1091 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1092 Decl :=
1093 First_Non_Pragma (Component_Items (Component_List_Node));
1094
1095 while Present (Decl) loop
1096 Set_Discriminant_Checking_Func
1097 (Defining_Identifier (Decl), Func_Id);
1098
1099 Next_Non_Pragma (Decl);
1100 end loop;
1101
1102 if Present (Variant_Part (Component_List_Node)) then
1103 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1104 Enclosing_Func_Id := Func_Id;
1105 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1106 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1107 end if;
1108 end if;
1109
1110 Next_Non_Pragma (Variant);
1111 end loop;
1112 end Build_Dcheck_Functions;
1113
1114 -- Start of processing for Build_Discr_Checking_Funcs
1115
1116 begin
1117 -- Only build if not done already
1118
1119 if not Discr_Check_Funcs_Built (N) then
1120 Type_Def := Type_Definition (N);
1121
1122 if Nkind (Type_Def) = N_Record_Definition then
1123 if No (Component_List (Type_Def)) then -- null record.
1124 return;
1125 else
1126 V := Variant_Part (Component_List (Type_Def));
1127 end if;
1128
1129 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1130 if No (Component_List (Record_Extension_Part (Type_Def))) then
1131 return;
1132 else
1133 V := Variant_Part
1134 (Component_List (Record_Extension_Part (Type_Def)));
1135 end if;
1136 end if;
1137
1138 Rec_Id := Defining_Identifier (N);
1139
1140 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1141 Loc := Sloc (N);
1142 Enclosing_Func_Id := Empty;
1143 Build_Dcheck_Functions (V);
1144 end if;
1145
1146 Set_Discr_Check_Funcs_Built (N);
1147 end if;
1148 end Build_Discr_Checking_Funcs;
1149
1150 --------------------------------
1151 -- Build_Discriminant_Formals --
1152 --------------------------------
1153
1154 function Build_Discriminant_Formals
1155 (Rec_Id : Entity_Id;
1156 Use_Dl : Boolean) return List_Id
1157 is
1158 Loc : Source_Ptr := Sloc (Rec_Id);
1159 Parameter_List : constant List_Id := New_List;
1160 D : Entity_Id;
1161 Formal : Entity_Id;
1162 Formal_Type : Entity_Id;
1163 Param_Spec_Node : Node_Id;
1164
1165 begin
1166 if Has_Discriminants (Rec_Id) then
1167 D := First_Discriminant (Rec_Id);
1168 while Present (D) loop
1169 Loc := Sloc (D);
1170
1171 if Use_Dl then
1172 Formal := Discriminal (D);
1173 Formal_Type := Etype (Formal);
1174 else
1175 Formal := Make_Defining_Identifier (Loc, Chars (D));
1176 Formal_Type := Etype (D);
1177 end if;
1178
1179 Param_Spec_Node :=
1180 Make_Parameter_Specification (Loc,
1181 Defining_Identifier => Formal,
1182 Parameter_Type =>
1183 New_Reference_To (Formal_Type, Loc));
1184 Append (Param_Spec_Node, Parameter_List);
1185 Next_Discriminant (D);
1186 end loop;
1187 end if;
1188
1189 return Parameter_List;
1190 end Build_Discriminant_Formals;
1191
1192 --------------------------------------
1193 -- Build_Equivalent_Array_Aggregate --
1194 --------------------------------------
1195
1196 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1197 Loc : constant Source_Ptr := Sloc (T);
1198 Comp_Type : constant Entity_Id := Component_Type (T);
1199 Index_Type : constant Entity_Id := Etype (First_Index (T));
1200 Proc : constant Entity_Id := Base_Init_Proc (T);
1201 Lo, Hi : Node_Id;
1202 Aggr : Node_Id;
1203 Expr : Node_Id;
1204
1205 begin
1206 if not Is_Constrained (T)
1207 or else Number_Dimensions (T) > 1
1208 or else No (Proc)
1209 then
1210 Initialization_Warning (T);
1211 return Empty;
1212 end if;
1213
1214 Lo := Type_Low_Bound (Index_Type);
1215 Hi := Type_High_Bound (Index_Type);
1216
1217 if not Compile_Time_Known_Value (Lo)
1218 or else not Compile_Time_Known_Value (Hi)
1219 then
1220 Initialization_Warning (T);
1221 return Empty;
1222 end if;
1223
1224 if Is_Record_Type (Comp_Type)
1225 and then Present (Base_Init_Proc (Comp_Type))
1226 then
1227 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1228
1229 if No (Expr) then
1230 Initialization_Warning (T);
1231 return Empty;
1232 end if;
1233
1234 else
1235 Initialization_Warning (T);
1236 return Empty;
1237 end if;
1238
1239 Aggr := Make_Aggregate (Loc, No_List, New_List);
1240 Set_Etype (Aggr, T);
1241 Set_Aggregate_Bounds (Aggr,
1242 Make_Range (Loc,
1243 Low_Bound => New_Copy (Lo),
1244 High_Bound => New_Copy (Hi)));
1245 Set_Parent (Aggr, Parent (Proc));
1246
1247 Append_To (Component_Associations (Aggr),
1248 Make_Component_Association (Loc,
1249 Choices =>
1250 New_List (
1251 Make_Range (Loc,
1252 Low_Bound => New_Copy (Lo),
1253 High_Bound => New_Copy (Hi))),
1254 Expression => Expr));
1255
1256 if Static_Array_Aggregate (Aggr) then
1257 return Aggr;
1258 else
1259 Initialization_Warning (T);
1260 return Empty;
1261 end if;
1262 end Build_Equivalent_Array_Aggregate;
1263
1264 ---------------------------------------
1265 -- Build_Equivalent_Record_Aggregate --
1266 ---------------------------------------
1267
1268 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1269 Agg : Node_Id;
1270 Comp : Entity_Id;
1271 Comp_Type : Entity_Id;
1272
1273 -- Start of processing for Build_Equivalent_Record_Aggregate
1274
1275 begin
1276 if not Is_Record_Type (T)
1277 or else Has_Discriminants (T)
1278 or else Is_Limited_Type (T)
1279 or else Has_Non_Standard_Rep (T)
1280 then
1281 Initialization_Warning (T);
1282 return Empty;
1283 end if;
1284
1285 Comp := First_Component (T);
1286
1287 -- A null record needs no warning
1288
1289 if No (Comp) then
1290 return Empty;
1291 end if;
1292
1293 while Present (Comp) loop
1294
1295 -- Array components are acceptable if initialized by a positional
1296 -- aggregate with static components.
1297
1298 if Is_Array_Type (Etype (Comp)) then
1299 Comp_Type := Component_Type (Etype (Comp));
1300
1301 if Nkind (Parent (Comp)) /= N_Component_Declaration
1302 or else No (Expression (Parent (Comp)))
1303 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1304 then
1305 Initialization_Warning (T);
1306 return Empty;
1307
1308 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1309 and then
1310 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1311 or else
1312 not Compile_Time_Known_Value (Type_High_Bound (Comp_Type)))
1313 then
1314 Initialization_Warning (T);
1315 return Empty;
1316
1317 elsif
1318 not Static_Array_Aggregate (Expression (Parent (Comp)))
1319 then
1320 Initialization_Warning (T);
1321 return Empty;
1322 end if;
1323
1324 elsif Is_Scalar_Type (Etype (Comp)) then
1325 Comp_Type := Etype (Comp);
1326
1327 if Nkind (Parent (Comp)) /= N_Component_Declaration
1328 or else No (Expression (Parent (Comp)))
1329 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1330 or else not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1331 or else not
1332 Compile_Time_Known_Value (Type_High_Bound (Comp_Type))
1333 then
1334 Initialization_Warning (T);
1335 return Empty;
1336 end if;
1337
1338 -- For now, other types are excluded
1339
1340 else
1341 Initialization_Warning (T);
1342 return Empty;
1343 end if;
1344
1345 Next_Component (Comp);
1346 end loop;
1347
1348 -- All components have static initialization. Build positional aggregate
1349 -- from the given expressions or defaults.
1350
1351 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1352 Set_Parent (Agg, Parent (T));
1353
1354 Comp := First_Component (T);
1355 while Present (Comp) loop
1356 Append
1357 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1358 Next_Component (Comp);
1359 end loop;
1360
1361 Analyze_And_Resolve (Agg, T);
1362 return Agg;
1363 end Build_Equivalent_Record_Aggregate;
1364
1365 -------------------------------
1366 -- Build_Initialization_Call --
1367 -------------------------------
1368
1369 -- References to a discriminant inside the record type declaration can
1370 -- appear either in the subtype_indication to constrain a record or an
1371 -- array, or as part of a larger expression given for the initial value
1372 -- of a component. In both of these cases N appears in the record
1373 -- initialization procedure and needs to be replaced by the formal
1374 -- parameter of the initialization procedure which corresponds to that
1375 -- discriminant.
1376
1377 -- In the example below, references to discriminants D1 and D2 in proc_1
1378 -- are replaced by references to formals with the same name
1379 -- (discriminals)
1380
1381 -- A similar replacement is done for calls to any record initialization
1382 -- procedure for any components that are themselves of a record type.
1383
1384 -- type R (D1, D2 : Integer) is record
1385 -- X : Integer := F * D1;
1386 -- Y : Integer := F * D2;
1387 -- end record;
1388
1389 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1390 -- begin
1391 -- Out_2.D1 := D1;
1392 -- Out_2.D2 := D2;
1393 -- Out_2.X := F * D1;
1394 -- Out_2.Y := F * D2;
1395 -- end;
1396
1397 function Build_Initialization_Call
1398 (Loc : Source_Ptr;
1399 Id_Ref : Node_Id;
1400 Typ : Entity_Id;
1401 In_Init_Proc : Boolean := False;
1402 Enclos_Type : Entity_Id := Empty;
1403 Discr_Map : Elist_Id := New_Elmt_List;
1404 With_Default_Init : Boolean := False;
1405 Constructor_Ref : Node_Id := Empty) return List_Id
1406 is
1407 Res : constant List_Id := New_List;
1408 Arg : Node_Id;
1409 Args : List_Id;
1410 Controller_Typ : Entity_Id;
1411 Decl : Node_Id;
1412 Decls : List_Id;
1413 Discr : Entity_Id;
1414 First_Arg : Node_Id;
1415 Full_Init_Type : Entity_Id;
1416 Full_Type : Entity_Id := Typ;
1417 Init_Type : Entity_Id;
1418 Proc : Entity_Id;
1419
1420 begin
1421 pragma Assert (Constructor_Ref = Empty
1422 or else Is_CPP_Constructor_Call (Constructor_Ref));
1423
1424 if No (Constructor_Ref) then
1425 Proc := Base_Init_Proc (Typ);
1426 else
1427 Proc := Base_Init_Proc (Typ, Entity (Name (Constructor_Ref)));
1428 end if;
1429
1430 pragma Assert (Present (Proc));
1431 Init_Type := Etype (First_Formal (Proc));
1432 Full_Init_Type := Underlying_Type (Init_Type);
1433
1434 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1435 -- is active (in which case we make the call anyway, since in the
1436 -- actual compiled client it may be non null).
1437 -- Also nothing to do for value types.
1438
1439 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1440 or else Is_Value_Type (Typ)
1441 or else
1442 (Is_Array_Type (Typ) and then Is_Value_Type (Component_Type (Typ)))
1443 then
1444 return Empty_List;
1445 end if;
1446
1447 -- Go to full view if private type. In the case of successive
1448 -- private derivations, this can require more than one step.
1449
1450 while Is_Private_Type (Full_Type)
1451 and then Present (Full_View (Full_Type))
1452 loop
1453 Full_Type := Full_View (Full_Type);
1454 end loop;
1455
1456 -- If Typ is derived, the procedure is the initialization procedure for
1457 -- the root type. Wrap the argument in an conversion to make it type
1458 -- honest. Actually it isn't quite type honest, because there can be
1459 -- conflicts of views in the private type case. That is why we set
1460 -- Conversion_OK in the conversion node.
1461
1462 if (Is_Record_Type (Typ)
1463 or else Is_Array_Type (Typ)
1464 or else Is_Private_Type (Typ))
1465 and then Init_Type /= Base_Type (Typ)
1466 then
1467 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1468 Set_Etype (First_Arg, Init_Type);
1469
1470 else
1471 First_Arg := Id_Ref;
1472 end if;
1473
1474 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1475
1476 -- In the tasks case, add _Master as the value of the _Master parameter
1477 -- and _Chain as the value of the _Chain parameter. At the outer level,
1478 -- these will be variables holding the corresponding values obtained
1479 -- from GNARL. At inner levels, they will be the parameters passed down
1480 -- through the outer routines.
1481
1482 if Has_Task (Full_Type) then
1483 if Restriction_Active (No_Task_Hierarchy) then
1484 Append_To (Args,
1485 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
1486 else
1487 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1488 end if;
1489
1490 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1491
1492 -- Ada 2005 (AI-287): In case of default initialized components
1493 -- with tasks, we generate a null string actual parameter.
1494 -- This is just a workaround that must be improved later???
1495
1496 if With_Default_Init then
1497 Append_To (Args,
1498 Make_String_Literal (Loc,
1499 Strval => ""));
1500
1501 else
1502 Decls :=
1503 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1504 Decl := Last (Decls);
1505
1506 Append_To (Args,
1507 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1508 Append_List (Decls, Res);
1509 end if;
1510
1511 else
1512 Decls := No_List;
1513 Decl := Empty;
1514 end if;
1515
1516 -- Add discriminant values if discriminants are present
1517
1518 if Has_Discriminants (Full_Init_Type) then
1519 Discr := First_Discriminant (Full_Init_Type);
1520
1521 while Present (Discr) loop
1522
1523 -- If this is a discriminated concurrent type, the init_proc
1524 -- for the corresponding record is being called. Use that type
1525 -- directly to find the discriminant value, to handle properly
1526 -- intervening renamed discriminants.
1527
1528 declare
1529 T : Entity_Id := Full_Type;
1530
1531 begin
1532 if Is_Protected_Type (T) then
1533 T := Corresponding_Record_Type (T);
1534
1535 elsif Is_Private_Type (T)
1536 and then Present (Underlying_Full_View (T))
1537 and then Is_Protected_Type (Underlying_Full_View (T))
1538 then
1539 T := Corresponding_Record_Type (Underlying_Full_View (T));
1540 end if;
1541
1542 Arg :=
1543 Get_Discriminant_Value (
1544 Discr,
1545 T,
1546 Discriminant_Constraint (Full_Type));
1547 end;
1548
1549 if In_Init_Proc then
1550
1551 -- Replace any possible references to the discriminant in the
1552 -- call to the record initialization procedure with references
1553 -- to the appropriate formal parameter.
1554
1555 if Nkind (Arg) = N_Identifier
1556 and then Ekind (Entity (Arg)) = E_Discriminant
1557 then
1558 Arg := New_Reference_To (Discriminal (Entity (Arg)), Loc);
1559
1560 -- Case of access discriminants. We replace the reference
1561 -- to the type by a reference to the actual object
1562
1563 elsif Nkind (Arg) = N_Attribute_Reference
1564 and then Is_Access_Type (Etype (Arg))
1565 and then Is_Entity_Name (Prefix (Arg))
1566 and then Is_Type (Entity (Prefix (Arg)))
1567 then
1568 Arg :=
1569 Make_Attribute_Reference (Loc,
1570 Prefix => New_Copy (Prefix (Id_Ref)),
1571 Attribute_Name => Name_Unrestricted_Access);
1572
1573 -- Otherwise make a copy of the default expression. Note that
1574 -- we use the current Sloc for this, because we do not want the
1575 -- call to appear to be at the declaration point. Within the
1576 -- expression, replace discriminants with their discriminals.
1577
1578 else
1579 Arg :=
1580 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1581 end if;
1582
1583 else
1584 if Is_Constrained (Full_Type) then
1585 Arg := Duplicate_Subexpr_No_Checks (Arg);
1586 else
1587 -- The constraints come from the discriminant default exps,
1588 -- they must be reevaluated, so we use New_Copy_Tree but we
1589 -- ensure the proper Sloc (for any embedded calls).
1590
1591 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1592 end if;
1593 end if;
1594
1595 -- Ada 2005 (AI-287): In case of default initialized components,
1596 -- if the component is constrained with a discriminant of the
1597 -- enclosing type, we need to generate the corresponding selected
1598 -- component node to access the discriminant value. In other cases
1599 -- this is not required, either because we are inside the init
1600 -- proc and we use the corresponding formal, or else because the
1601 -- component is constrained by an expression.
1602
1603 if With_Default_Init
1604 and then Nkind (Id_Ref) = N_Selected_Component
1605 and then Nkind (Arg) = N_Identifier
1606 and then Ekind (Entity (Arg)) = E_Discriminant
1607 then
1608 Append_To (Args,
1609 Make_Selected_Component (Loc,
1610 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1611 Selector_Name => Arg));
1612 else
1613 Append_To (Args, Arg);
1614 end if;
1615
1616 Next_Discriminant (Discr);
1617 end loop;
1618 end if;
1619
1620 -- If this is a call to initialize the parent component of a derived
1621 -- tagged type, indicate that the tag should not be set in the parent.
1622
1623 if Is_Tagged_Type (Full_Init_Type)
1624 and then not Is_CPP_Class (Full_Init_Type)
1625 and then Nkind (Id_Ref) = N_Selected_Component
1626 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1627 then
1628 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1629
1630 elsif Present (Constructor_Ref) then
1631 Append_List_To (Args,
1632 New_Copy_List (Parameter_Associations (Constructor_Ref)));
1633 end if;
1634
1635 Append_To (Res,
1636 Make_Procedure_Call_Statement (Loc,
1637 Name => New_Occurrence_Of (Proc, Loc),
1638 Parameter_Associations => Args));
1639
1640 if Needs_Finalization (Typ)
1641 and then Nkind (Id_Ref) = N_Selected_Component
1642 then
1643 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1644 Append_List_To (Res,
1645 Make_Init_Call (
1646 Ref => New_Copy_Tree (First_Arg),
1647 Typ => Typ,
1648 Flist_Ref =>
1649 Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1650 With_Attach => Make_Integer_Literal (Loc, 1)));
1651
1652 -- If the enclosing type is an extension with new controlled
1653 -- components, it has his own record controller. If the parent
1654 -- also had a record controller, attach it to the new one.
1655
1656 -- Build_Init_Statements relies on the fact that in this specific
1657 -- case the last statement of the result is the attach call to
1658 -- the controller. If this is changed, it must be synchronized.
1659
1660 elsif Present (Enclos_Type)
1661 and then Has_New_Controlled_Component (Enclos_Type)
1662 and then Has_Controlled_Component (Typ)
1663 then
1664 if Is_Immutably_Limited_Type (Typ) then
1665 Controller_Typ := RTE (RE_Limited_Record_Controller);
1666 else
1667 Controller_Typ := RTE (RE_Record_Controller);
1668 end if;
1669
1670 Append_List_To (Res,
1671 Make_Init_Call (
1672 Ref =>
1673 Make_Selected_Component (Loc,
1674 Prefix => New_Copy_Tree (First_Arg),
1675 Selector_Name => Make_Identifier (Loc, Name_uController)),
1676 Typ => Controller_Typ,
1677 Flist_Ref => Find_Final_List (Typ, New_Copy_Tree (First_Arg)),
1678 With_Attach => Make_Integer_Literal (Loc, 1)));
1679 end if;
1680 end if;
1681
1682 return Res;
1683
1684 exception
1685 when RE_Not_Available =>
1686 return Empty_List;
1687 end Build_Initialization_Call;
1688
1689 ---------------------------
1690 -- Build_Master_Renaming --
1691 ---------------------------
1692
1693 function Build_Master_Renaming
1694 (N : Node_Id;
1695 T : Entity_Id) return Entity_Id
1696 is
1697 Loc : constant Source_Ptr := Sloc (N);
1698 M_Id : Entity_Id;
1699 Decl : Node_Id;
1700
1701 begin
1702 -- Nothing to do if there is no task hierarchy
1703
1704 if Restriction_Active (No_Task_Hierarchy) then
1705 return Empty;
1706 end if;
1707
1708 M_Id :=
1709 Make_Defining_Identifier (Loc,
1710 New_External_Name (Chars (T), 'M'));
1711
1712 Decl :=
1713 Make_Object_Renaming_Declaration (Loc,
1714 Defining_Identifier => M_Id,
1715 Subtype_Mark => New_Reference_To (RTE (RE_Master_Id), Loc),
1716 Name => Make_Identifier (Loc, Name_uMaster));
1717 Insert_Before (N, Decl);
1718 Analyze (Decl);
1719 return M_Id;
1720
1721 exception
1722 when RE_Not_Available =>
1723 return Empty;
1724 end Build_Master_Renaming;
1725
1726 ---------------------------
1727 -- Build_Master_Renaming --
1728 ---------------------------
1729
1730 procedure Build_Master_Renaming (N : Node_Id; T : Entity_Id) is
1731 M_Id : Entity_Id;
1732
1733 begin
1734 -- Nothing to do if there is no task hierarchy
1735
1736 if Restriction_Active (No_Task_Hierarchy) then
1737 return;
1738 end if;
1739
1740 M_Id := Build_Master_Renaming (N, T);
1741 Set_Master_Id (T, M_Id);
1742
1743 exception
1744 when RE_Not_Available =>
1745 return;
1746 end Build_Master_Renaming;
1747
1748 ----------------------------
1749 -- Build_Record_Init_Proc --
1750 ----------------------------
1751
1752 procedure Build_Record_Init_Proc (N : Node_Id; Pe : Entity_Id) is
1753 Loc : Source_Ptr := Sloc (N);
1754 Discr_Map : constant Elist_Id := New_Elmt_List;
1755 Proc_Id : Entity_Id;
1756 Rec_Type : Entity_Id;
1757 Set_Tag : Entity_Id := Empty;
1758
1759 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1760 -- Build a assignment statement node which assigns to record component
1761 -- its default expression if defined. The assignment left hand side is
1762 -- marked Assignment_OK so that initialization of limited private
1763 -- records works correctly, Return also the adjustment call for
1764 -- controlled objects
1765
1766 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1767 -- If the record has discriminants, adds assignment statements to
1768 -- statement list to initialize the discriminant values from the
1769 -- arguments of the initialization procedure.
1770
1771 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1772 -- Build a list representing a sequence of statements which initialize
1773 -- components of the given component list. This may involve building
1774 -- case statements for the variant parts.
1775
1776 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1777 -- Given a non-tagged type-derivation that declares discriminants,
1778 -- such as
1779 --
1780 -- type R (R1, R2 : Integer) is record ... end record;
1781 --
1782 -- type D (D1 : Integer) is new R (1, D1);
1783 --
1784 -- we make the _init_proc of D be
1785 --
1786 -- procedure _init_proc(X : D; D1 : Integer) is
1787 -- begin
1788 -- _init_proc( R(X), 1, D1);
1789 -- end _init_proc;
1790 --
1791 -- This function builds the call statement in this _init_proc.
1792
1793 procedure Build_CPP_Init_Procedure;
1794 -- Build the tree corresponding to the procedure specification and body
1795 -- of the IC procedure that initializes the C++ part of the dispatch
1796 -- table of an Ada tagged type that is a derivation of a CPP type.
1797 -- Install it as the CPP_Init TSS.
1798
1799 procedure Build_Init_Procedure;
1800 -- Build the tree corresponding to the procedure specification and body
1801 -- of the initialization procedure (by calling all the preceding
1802 -- auxiliary routines), and install it as the _init TSS.
1803
1804 procedure Build_Offset_To_Top_Functions;
1805 -- Ada 2005 (AI-251): Build the tree corresponding to the procedure spec
1806 -- and body of the Offset_To_Top function that is generated when the
1807 -- parent of a type with discriminants has secondary dispatch tables.
1808
1809 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id);
1810 -- Add range checks to components of discriminated records. S is a
1811 -- subtype indication of a record component. Check_List is a list
1812 -- to which the check actions are appended.
1813
1814 function Component_Needs_Simple_Initialization
1815 (T : Entity_Id) return Boolean;
1816 -- Determines if a component needs simple initialization, given its type
1817 -- T. This is the same as Needs_Simple_Initialization except for the
1818 -- following difference: the types Tag and Interface_Tag, that are
1819 -- access types which would normally require simple initialization to
1820 -- null, do not require initialization as components, since they are
1821 -- explicitly initialized by other means.
1822
1823 procedure Constrain_Array
1824 (SI : Node_Id;
1825 Check_List : List_Id);
1826 -- Called from Build_Record_Checks.
1827 -- Apply a list of index constraints to an unconstrained array type.
1828 -- The first parameter is the entity for the resulting subtype.
1829 -- Check_List is a list to which the check actions are appended.
1830
1831 procedure Constrain_Index
1832 (Index : Node_Id;
1833 S : Node_Id;
1834 Check_List : List_Id);
1835 -- Process an index constraint in a constrained array declaration.
1836 -- The constraint can be a subtype name, or a range with or without
1837 -- an explicit subtype mark. The index is the corresponding index of the
1838 -- unconstrained array. S is the range expression. Check_List is a list
1839 -- to which the check actions are appended (called from
1840 -- Build_Record_Checks).
1841
1842 function Parent_Subtype_Renaming_Discrims return Boolean;
1843 -- Returns True for base types N that rename discriminants, else False
1844
1845 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean;
1846 -- Determines whether a record initialization procedure needs to be
1847 -- generated for the given record type.
1848
1849 ----------------------
1850 -- Build_Assignment --
1851 ----------------------
1852
1853 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id is
1854 Exp : Node_Id := N;
1855 Lhs : Node_Id;
1856 Typ : constant Entity_Id := Underlying_Type (Etype (Id));
1857 Kind : Node_Kind := Nkind (N);
1858 Res : List_Id;
1859
1860 begin
1861 Loc := Sloc (N);
1862 Lhs :=
1863 Make_Selected_Component (Loc,
1864 Prefix => Make_Identifier (Loc, Name_uInit),
1865 Selector_Name => New_Occurrence_Of (Id, Loc));
1866 Set_Assignment_OK (Lhs);
1867
1868 -- Case of an access attribute applied to the current instance.
1869 -- Replace the reference to the type by a reference to the actual
1870 -- object. (Note that this handles the case of the top level of
1871 -- the expression being given by such an attribute, but does not
1872 -- cover uses nested within an initial value expression. Nested
1873 -- uses are unlikely to occur in practice, but are theoretically
1874 -- possible. It is not clear how to handle them without fully
1875 -- traversing the expression. ???
1876
1877 if Kind = N_Attribute_Reference
1878 and then (Attribute_Name (N) = Name_Unchecked_Access
1879 or else
1880 Attribute_Name (N) = Name_Unrestricted_Access)
1881 and then Is_Entity_Name (Prefix (N))
1882 and then Is_Type (Entity (Prefix (N)))
1883 and then Entity (Prefix (N)) = Rec_Type
1884 then
1885 Exp :=
1886 Make_Attribute_Reference (Loc,
1887 Prefix => Make_Identifier (Loc, Name_uInit),
1888 Attribute_Name => Name_Unrestricted_Access);
1889 end if;
1890
1891 -- Take a copy of Exp to ensure that later copies of this component
1892 -- declaration in derived types see the original tree, not a node
1893 -- rewritten during expansion of the init_proc. If the copy contains
1894 -- itypes, the scope of the new itypes is the init_proc being built.
1895
1896 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id);
1897
1898 Res := New_List (
1899 Make_Assignment_Statement (Loc,
1900 Name => Lhs,
1901 Expression => Exp));
1902
1903 Set_No_Ctrl_Actions (First (Res));
1904
1905 -- Adjust the tag if tagged (because of possible view conversions).
1906 -- Suppress the tag adjustment when VM_Target because VM tags are
1907 -- represented implicitly in objects.
1908
1909 if Is_Tagged_Type (Typ) and then Tagged_Type_Expansion then
1910 Append_To (Res,
1911 Make_Assignment_Statement (Loc,
1912 Name =>
1913 Make_Selected_Component (Loc,
1914 Prefix => New_Copy_Tree (Lhs, New_Scope => Proc_Id),
1915 Selector_Name =>
1916 New_Reference_To (First_Tag_Component (Typ), Loc)),
1917
1918 Expression =>
1919 Unchecked_Convert_To (RTE (RE_Tag),
1920 New_Reference_To
1921 (Node (First_Elmt (Access_Disp_Table (Typ))), Loc))));
1922 end if;
1923
1924 -- Adjust the component if controlled except if it is an aggregate
1925 -- that will be expanded inline.
1926
1927 if Kind = N_Qualified_Expression then
1928 Kind := Nkind (Expression (N));
1929 end if;
1930
1931 if Needs_Finalization (Typ)
1932 and then not (Nkind_In (Kind, N_Aggregate, N_Extension_Aggregate))
1933 and then not Is_Immutably_Limited_Type (Typ)
1934 then
1935 declare
1936 Ref : constant Node_Id :=
1937 New_Copy_Tree (Lhs, New_Scope => Proc_Id);
1938 begin
1939 Append_List_To (Res,
1940 Make_Adjust_Call (
1941 Ref => Ref,
1942 Typ => Etype (Id),
1943 Flist_Ref => Find_Final_List (Etype (Id), Ref),
1944 With_Attach => Make_Integer_Literal (Loc, 1)));
1945 end;
1946 end if;
1947
1948 return Res;
1949
1950 exception
1951 when RE_Not_Available =>
1952 return Empty_List;
1953 end Build_Assignment;
1954
1955 ------------------------------------
1956 -- Build_Discriminant_Assignments --
1957 ------------------------------------
1958
1959 procedure Build_Discriminant_Assignments (Statement_List : List_Id) is
1960 D : Entity_Id;
1961 Is_Tagged : constant Boolean := Is_Tagged_Type (Rec_Type);
1962
1963 begin
1964 if Has_Discriminants (Rec_Type)
1965 and then not Is_Unchecked_Union (Rec_Type)
1966 then
1967 D := First_Discriminant (Rec_Type);
1968
1969 while Present (D) loop
1970
1971 -- Don't generate the assignment for discriminants in derived
1972 -- tagged types if the discriminant is a renaming of some
1973 -- ancestor discriminant. This initialization will be done
1974 -- when initializing the _parent field of the derived record.
1975
1976 if Is_Tagged and then
1977 Present (Corresponding_Discriminant (D))
1978 then
1979 null;
1980
1981 else
1982 Loc := Sloc (D);
1983 Append_List_To (Statement_List,
1984 Build_Assignment (D,
1985 New_Reference_To (Discriminal (D), Loc)));
1986 end if;
1987
1988 Next_Discriminant (D);
1989 end loop;
1990 end if;
1991 end Build_Discriminant_Assignments;
1992
1993 --------------------------
1994 -- Build_Init_Call_Thru --
1995 --------------------------
1996
1997 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id is
1998 Parent_Proc : constant Entity_Id :=
1999 Base_Init_Proc (Etype (Rec_Type));
2000
2001 Parent_Type : constant Entity_Id :=
2002 Etype (First_Formal (Parent_Proc));
2003
2004 Uparent_Type : constant Entity_Id :=
2005 Underlying_Type (Parent_Type);
2006
2007 First_Discr_Param : Node_Id;
2008
2009 Parent_Discr : Entity_Id;
2010 First_Arg : Node_Id;
2011 Args : List_Id;
2012 Arg : Node_Id;
2013 Res : List_Id;
2014
2015 begin
2016 -- First argument (_Init) is the object to be initialized.
2017 -- ??? not sure where to get a reasonable Loc for First_Arg
2018
2019 First_Arg :=
2020 OK_Convert_To (Parent_Type,
2021 New_Reference_To (Defining_Identifier (First (Parameters)), Loc));
2022
2023 Set_Etype (First_Arg, Parent_Type);
2024
2025 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
2026
2027 -- In the tasks case,
2028 -- add _Master as the value of the _Master parameter
2029 -- add _Chain as the value of the _Chain parameter.
2030 -- add _Task_Name as the value of the _Task_Name parameter.
2031 -- At the outer level, these will be variables holding the
2032 -- corresponding values obtained from GNARL or the expander.
2033 --
2034 -- At inner levels, they will be the parameters passed down through
2035 -- the outer routines.
2036
2037 First_Discr_Param := Next (First (Parameters));
2038
2039 if Has_Task (Rec_Type) then
2040 if Restriction_Active (No_Task_Hierarchy) then
2041 Append_To (Args,
2042 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
2043 else
2044 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
2045 end if;
2046
2047 Append_To (Args, Make_Identifier (Loc, Name_uChain));
2048 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
2049 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
2050 end if;
2051
2052 -- Append discriminant values
2053
2054 if Has_Discriminants (Uparent_Type) then
2055 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2056
2057 Parent_Discr := First_Discriminant (Uparent_Type);
2058 while Present (Parent_Discr) loop
2059
2060 -- Get the initial value for this discriminant
2061 -- ??? needs to be cleaned up to use parent_Discr_Constr
2062 -- directly.
2063
2064 declare
2065 Discr_Value : Elmt_Id :=
2066 First_Elmt
2067 (Stored_Constraint (Rec_Type));
2068
2069 Discr : Entity_Id :=
2070 First_Stored_Discriminant (Uparent_Type);
2071 begin
2072 while Original_Record_Component (Parent_Discr) /= Discr loop
2073 Next_Stored_Discriminant (Discr);
2074 Next_Elmt (Discr_Value);
2075 end loop;
2076
2077 Arg := Node (Discr_Value);
2078 end;
2079
2080 -- Append it to the list
2081
2082 if Nkind (Arg) = N_Identifier
2083 and then Ekind (Entity (Arg)) = E_Discriminant
2084 then
2085 Append_To (Args,
2086 New_Reference_To (Discriminal (Entity (Arg)), Loc));
2087
2088 -- Case of access discriminants. We replace the reference
2089 -- to the type by a reference to the actual object.
2090
2091 -- Is above comment right??? Use of New_Copy below seems mighty
2092 -- suspicious ???
2093
2094 else
2095 Append_To (Args, New_Copy (Arg));
2096 end if;
2097
2098 Next_Discriminant (Parent_Discr);
2099 end loop;
2100 end if;
2101
2102 Res :=
2103 New_List (
2104 Make_Procedure_Call_Statement (Loc,
2105 Name => New_Occurrence_Of (Parent_Proc, Loc),
2106 Parameter_Associations => Args));
2107
2108 return Res;
2109 end Build_Init_Call_Thru;
2110
2111 -----------------------------------
2112 -- Build_Offset_To_Top_Functions --
2113 -----------------------------------
2114
2115 procedure Build_Offset_To_Top_Functions is
2116
2117 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id);
2118 -- Generate:
2119 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2120 -- begin
2121 -- return O.Iface_Comp'Position;
2122 -- end Fxx;
2123
2124 ----------------------------------
2125 -- Build_Offset_To_Top_Function --
2126 ----------------------------------
2127
2128 procedure Build_Offset_To_Top_Function (Iface_Comp : Entity_Id) is
2129 Body_Node : Node_Id;
2130 Func_Id : Entity_Id;
2131 Spec_Node : Node_Id;
2132
2133 begin
2134 Func_Id := Make_Temporary (Loc, 'F');
2135 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2136
2137 -- Generate
2138 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
2139
2140 Spec_Node := New_Node (N_Function_Specification, Loc);
2141 Set_Defining_Unit_Name (Spec_Node, Func_Id);
2142 Set_Parameter_Specifications (Spec_Node, New_List (
2143 Make_Parameter_Specification (Loc,
2144 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uO),
2145 In_Present => True,
2146 Parameter_Type => New_Reference_To (Rec_Type, Loc))));
2147 Set_Result_Definition (Spec_Node,
2148 New_Reference_To (RTE (RE_Storage_Offset), Loc));
2149
2150 -- Generate
2151 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2152 -- begin
2153 -- return O.Iface_Comp'Position;
2154 -- end Fxx;
2155
2156 Body_Node := New_Node (N_Subprogram_Body, Loc);
2157 Set_Specification (Body_Node, Spec_Node);
2158 Set_Declarations (Body_Node, New_List);
2159 Set_Handled_Statement_Sequence (Body_Node,
2160 Make_Handled_Sequence_Of_Statements (Loc,
2161 Statements => New_List (
2162 Make_Simple_Return_Statement (Loc,
2163 Expression =>
2164 Make_Attribute_Reference (Loc,
2165 Prefix =>
2166 Make_Selected_Component (Loc,
2167 Prefix => Make_Identifier (Loc, Name_uO),
2168 Selector_Name => New_Reference_To
2169 (Iface_Comp, Loc)),
2170 Attribute_Name => Name_Position)))));
2171
2172 Set_Ekind (Func_Id, E_Function);
2173 Set_Mechanism (Func_Id, Default_Mechanism);
2174 Set_Is_Internal (Func_Id, True);
2175
2176 if not Debug_Generated_Code then
2177 Set_Debug_Info_Off (Func_Id);
2178 end if;
2179
2180 Analyze (Body_Node);
2181
2182 Append_Freeze_Action (Rec_Type, Body_Node);
2183 end Build_Offset_To_Top_Function;
2184
2185 -- Local variables
2186
2187 Ifaces_Comp_List : Elist_Id;
2188 Iface_Comp_Elmt : Elmt_Id;
2189 Iface_Comp : Node_Id;
2190
2191 -- Start of processing for Build_Offset_To_Top_Functions
2192
2193 begin
2194 -- Offset_To_Top_Functions are built only for derivations of types
2195 -- with discriminants that cover interface types.
2196 -- Nothing is needed either in case of virtual machines, since
2197 -- interfaces are handled directly by the VM.
2198
2199 if not Is_Tagged_Type (Rec_Type)
2200 or else Etype (Rec_Type) = Rec_Type
2201 or else not Has_Discriminants (Etype (Rec_Type))
2202 or else not Tagged_Type_Expansion
2203 then
2204 return;
2205 end if;
2206
2207 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
2208
2209 -- For each interface type with secondary dispatch table we generate
2210 -- the Offset_To_Top_Functions (required to displace the pointer in
2211 -- interface conversions)
2212
2213 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
2214 while Present (Iface_Comp_Elmt) loop
2215 Iface_Comp := Node (Iface_Comp_Elmt);
2216 pragma Assert (Is_Interface (Related_Type (Iface_Comp)));
2217
2218 -- If the interface is a parent of Rec_Type it shares the primary
2219 -- dispatch table and hence there is no need to build the function
2220
2221 if not Is_Ancestor (Related_Type (Iface_Comp), Rec_Type) then
2222 Build_Offset_To_Top_Function (Iface_Comp);
2223 end if;
2224
2225 Next_Elmt (Iface_Comp_Elmt);
2226 end loop;
2227 end Build_Offset_To_Top_Functions;
2228
2229 ------------------------------
2230 -- Build_CPP_Init_Procedure --
2231 ------------------------------
2232
2233 procedure Build_CPP_Init_Procedure is
2234 Body_Node : Node_Id;
2235 Body_Stmts : List_Id;
2236 Flag_Id : Entity_Id;
2237 Flag_Decl : Node_Id;
2238 Handled_Stmt_Node : Node_Id;
2239 Init_Tags_List : List_Id;
2240 Proc_Id : Entity_Id;
2241 Proc_Spec_Node : Node_Id;
2242
2243 begin
2244 -- Check cases requiring no IC routine
2245
2246 if not Is_CPP_Class (Root_Type (Rec_Type))
2247 or else Is_CPP_Class (Rec_Type)
2248 or else CPP_Num_Prims (Rec_Type) = 0
2249 or else not Tagged_Type_Expansion
2250 or else No_Run_Time_Mode
2251 then
2252 return;
2253 end if;
2254
2255 -- Generate:
2256
2257 -- Flag : Boolean := False;
2258 --
2259 -- procedure Typ_IC is
2260 -- begin
2261 -- if not Flag then
2262 -- Copy C++ dispatch table slots from parent
2263 -- Update C++ slots of overridden primitives
2264 -- end if;
2265 -- end;
2266
2267 Flag_Id := Make_Temporary (Loc, 'F');
2268
2269 Flag_Decl :=
2270 Make_Object_Declaration (Loc,
2271 Defining_Identifier => Flag_Id,
2272 Object_Definition =>
2273 New_Reference_To (Standard_Boolean, Loc),
2274 Expression =>
2275 New_Reference_To (Standard_True, Loc));
2276
2277 Analyze (Flag_Decl);
2278 Append_Freeze_Action (Rec_Type, Flag_Decl);
2279
2280 Body_Stmts := New_List;
2281 Body_Node := New_Node (N_Subprogram_Body, Loc);
2282
2283 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2284
2285 Proc_Id :=
2286 Make_Defining_Identifier (Loc,
2287 Chars => Make_TSS_Name (Rec_Type, TSS_CPP_Init_Proc));
2288
2289 Set_Ekind (Proc_Id, E_Procedure);
2290 Set_Is_Internal (Proc_Id);
2291
2292 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2293
2294 Set_Parameter_Specifications (Proc_Spec_Node, New_List);
2295 Set_Specification (Body_Node, Proc_Spec_Node);
2296 Set_Declarations (Body_Node, New_List);
2297
2298 Init_Tags_List := Build_Inherit_CPP_Prims (Rec_Type);
2299
2300 Append_To (Init_Tags_List,
2301 Make_Assignment_Statement (Loc,
2302 Name =>
2303 New_Reference_To (Flag_Id, Loc),
2304 Expression =>
2305 New_Reference_To (Standard_False, Loc)));
2306
2307 Append_To (Body_Stmts,
2308 Make_If_Statement (Loc,
2309 Condition => New_Occurrence_Of (Flag_Id, Loc),
2310 Then_Statements => Init_Tags_List));
2311
2312 Handled_Stmt_Node :=
2313 New_Node (N_Handled_Sequence_Of_Statements, Loc);
2314 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2315 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2316 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2317
2318 if not Debug_Generated_Code then
2319 Set_Debug_Info_Off (Proc_Id);
2320 end if;
2321
2322 -- Associate CPP_Init_Proc with type
2323
2324 Set_Init_Proc (Rec_Type, Proc_Id);
2325 end Build_CPP_Init_Procedure;
2326
2327 --------------------------
2328 -- Build_Init_Procedure --
2329 --------------------------
2330
2331 procedure Build_Init_Procedure is
2332 Body_Node : Node_Id;
2333 Handled_Stmt_Node : Node_Id;
2334 Parameters : List_Id;
2335 Proc_Spec_Node : Node_Id;
2336 Body_Stmts : List_Id;
2337 Record_Extension_Node : Node_Id;
2338 Init_Tags_List : List_Id;
2339
2340 begin
2341 Body_Stmts := New_List;
2342 Body_Node := New_Node (N_Subprogram_Body, Loc);
2343 Set_Ekind (Proc_Id, E_Procedure);
2344
2345 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2346 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2347
2348 Parameters := Init_Formals (Rec_Type);
2349 Append_List_To (Parameters,
2350 Build_Discriminant_Formals (Rec_Type, True));
2351
2352 -- For tagged types, we add a flag to indicate whether the routine
2353 -- is called to initialize a parent component in the init_proc of
2354 -- a type extension. If the flag is false, we do not set the tag
2355 -- because it has been set already in the extension.
2356
2357 if Is_Tagged_Type (Rec_Type) then
2358 Set_Tag := Make_Temporary (Loc, 'P');
2359
2360 Append_To (Parameters,
2361 Make_Parameter_Specification (Loc,
2362 Defining_Identifier => Set_Tag,
2363 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
2364 Expression => New_Occurrence_Of (Standard_True, Loc)));
2365 end if;
2366
2367 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2368 Set_Specification (Body_Node, Proc_Spec_Node);
2369 Set_Declarations (Body_Node, New_List);
2370
2371 if Parent_Subtype_Renaming_Discrims then
2372
2373 -- N is a Derived_Type_Definition that renames the parameters
2374 -- of the ancestor type. We initialize it by expanding our
2375 -- discriminants and call the ancestor _init_proc with a
2376 -- type-converted object
2377
2378 Append_List_To (Body_Stmts,
2379 Build_Init_Call_Thru (Parameters));
2380
2381 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2382 Build_Discriminant_Assignments (Body_Stmts);
2383
2384 if not Null_Present (Type_Definition (N)) then
2385 Append_List_To (Body_Stmts,
2386 Build_Init_Statements (
2387 Component_List (Type_Definition (N))));
2388 end if;
2389
2390 else
2391 -- N is a Derived_Type_Definition with a possible non-empty
2392 -- extension. The initialization of a type extension consists
2393 -- in the initialization of the components in the extension.
2394
2395 Build_Discriminant_Assignments (Body_Stmts);
2396
2397 Record_Extension_Node :=
2398 Record_Extension_Part (Type_Definition (N));
2399
2400 if not Null_Present (Record_Extension_Node) then
2401 declare
2402 Stmts : constant List_Id :=
2403 Build_Init_Statements (
2404 Component_List (Record_Extension_Node));
2405
2406 begin
2407 -- The parent field must be initialized first because
2408 -- the offset of the new discriminants may depend on it
2409
2410 Prepend_To (Body_Stmts, Remove_Head (Stmts));
2411 Append_List_To (Body_Stmts, Stmts);
2412 end;
2413 end if;
2414 end if;
2415
2416 -- Add here the assignment to instantiate the Tag
2417
2418 -- The assignment corresponds to the code:
2419
2420 -- _Init._Tag := Typ'Tag;
2421
2422 -- Suppress the tag assignment when VM_Target because VM tags are
2423 -- represented implicitly in objects. It is also suppressed in case
2424 -- of CPP_Class types because in this case the tag is initialized in
2425 -- the C++ side.
2426
2427 if Is_Tagged_Type (Rec_Type)
2428 and then Tagged_Type_Expansion
2429 and then not No_Run_Time_Mode
2430 then
2431 -- Case 1: Ada tagged types with no CPP ancestor. Set the tags of
2432 -- the actual object and invoke the IP of the parent (in this
2433 -- order). The tag must be initialized before the call to the IP
2434 -- of the parent and the assignments to other components because
2435 -- the initial value of the components may depend on the tag (eg.
2436 -- through a dispatching operation on an access to the current
2437 -- type). The tag assignment is not done when initializing the
2438 -- parent component of a type extension, because in that case the
2439 -- tag is set in the extension.
2440
2441 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2442
2443 -- Initialize the primary tag component
2444
2445 Init_Tags_List := New_List (
2446 Make_Assignment_Statement (Loc,
2447 Name =>
2448 Make_Selected_Component (Loc,
2449 Prefix => Make_Identifier (Loc, Name_uInit),
2450 Selector_Name =>
2451 New_Reference_To
2452 (First_Tag_Component (Rec_Type), Loc)),
2453 Expression =>
2454 New_Reference_To
2455 (Node
2456 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2457
2458 -- Ada 2005 (AI-251): Initialize the secondary tags components
2459 -- located at fixed positions (tags whose position depends on
2460 -- variable size components are initialized later ---see below)
2461
2462 if Ada_Version >= Ada_2005
2463 and then not Is_Interface (Rec_Type)
2464 and then Has_Interfaces (Rec_Type)
2465 then
2466 Init_Secondary_Tags
2467 (Typ => Rec_Type,
2468 Target => Make_Identifier (Loc, Name_uInit),
2469 Stmts_List => Init_Tags_List,
2470 Fixed_Comps => True,
2471 Variable_Comps => False);
2472 end if;
2473
2474 Prepend_To (Body_Stmts,
2475 Make_If_Statement (Loc,
2476 Condition => New_Occurrence_Of (Set_Tag, Loc),
2477 Then_Statements => Init_Tags_List));
2478
2479 -- Case 2: CPP type. The imported C++ constructor takes care of
2480 -- tags initialization. No action needed here because the IP
2481 -- is built by Set_CPP_Constructors; in this case the IP is a
2482 -- wrapper that invokes the C++ constructor and copies the C++
2483 -- tags locally. Done to inherit the C++ slots in Ada derivations
2484 -- (see case 3).
2485
2486 elsif Is_CPP_Class (Rec_Type) then
2487 pragma Assert (False);
2488 null;
2489
2490 -- Case 3: Combined hierarchy containing C++ types and Ada tagged
2491 -- type derivations. Derivations of imported C++ classes add a
2492 -- complication, because we cannot inhibit tag setting in the
2493 -- constructor for the parent. Hence we initialize the tag after
2494 -- the call to the parent IP (that is, in reverse order compared
2495 -- with pure Ada hierarchies ---see comment on case 1).
2496
2497 else
2498 -- Initialize the primary tag
2499
2500 Init_Tags_List := New_List (
2501 Make_Assignment_Statement (Loc,
2502 Name =>
2503 Make_Selected_Component (Loc,
2504 Prefix => Make_Identifier (Loc, Name_uInit),
2505 Selector_Name =>
2506 New_Reference_To
2507 (First_Tag_Component (Rec_Type), Loc)),
2508 Expression =>
2509 New_Reference_To
2510 (Node
2511 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2512
2513 -- Ada 2005 (AI-251): Initialize the secondary tags components
2514 -- located at fixed positions (tags whose position depends on
2515 -- variable size components are initialized later ---see below)
2516
2517 if Ada_Version >= Ada_2005
2518 and then not Is_Interface (Rec_Type)
2519 and then Has_Interfaces (Rec_Type)
2520 then
2521 Init_Secondary_Tags
2522 (Typ => Rec_Type,
2523 Target => Make_Identifier (Loc, Name_uInit),
2524 Stmts_List => Init_Tags_List,
2525 Fixed_Comps => True,
2526 Variable_Comps => False);
2527 end if;
2528
2529 -- Initialize the tag component after invocation of parent IP.
2530
2531 -- Generate:
2532 -- parent_IP(_init.parent); // Invokes the C++ constructor
2533 -- [ typIC; ] // Inherit C++ slots from parent
2534 -- init_tags
2535
2536 declare
2537 Ins_Nod : Node_Id;
2538
2539 begin
2540 -- Search for the call to the IP of the parent. We assume
2541 -- that the first init_proc call is for the parent.
2542
2543 Ins_Nod := First (Body_Stmts);
2544 while Present (Next (Ins_Nod))
2545 and then (Nkind (Ins_Nod) /= N_Procedure_Call_Statement
2546 or else not Is_Init_Proc (Name (Ins_Nod)))
2547 loop
2548 Next (Ins_Nod);
2549 end loop;
2550
2551 -- The IC routine copies the inherited slots of the C+ part
2552 -- of the dispatch table from the parent and updates the
2553 -- overridden C++ slots.
2554
2555 if CPP_Num_Prims (Rec_Type) > 0 then
2556 declare
2557 Init_DT : Entity_Id;
2558 New_Nod : Node_Id;
2559
2560 begin
2561 Init_DT := CPP_Init_Proc (Rec_Type);
2562 pragma Assert (Present (Init_DT));
2563
2564 New_Nod :=
2565 Make_Procedure_Call_Statement (Loc,
2566 New_Reference_To (Init_DT, Loc));
2567 Insert_After (Ins_Nod, New_Nod);
2568
2569 -- Update location of init tag statements
2570
2571 Ins_Nod := New_Nod;
2572 end;
2573 end if;
2574
2575 Insert_List_After (Ins_Nod, Init_Tags_List);
2576 end;
2577 end if;
2578
2579 -- Ada 2005 (AI-251): Initialize the secondary tag components
2580 -- located at variable positions. We delay the generation of this
2581 -- code until here because the value of the attribute 'Position
2582 -- applied to variable size components of the parent type that
2583 -- depend on discriminants is only safely read at runtime after
2584 -- the parent components have been initialized.
2585
2586 if Ada_Version >= Ada_2005
2587 and then not Is_Interface (Rec_Type)
2588 and then Has_Interfaces (Rec_Type)
2589 and then Has_Discriminants (Etype (Rec_Type))
2590 and then Is_Variable_Size_Record (Etype (Rec_Type))
2591 then
2592 Init_Tags_List := New_List;
2593
2594 Init_Secondary_Tags
2595 (Typ => Rec_Type,
2596 Target => Make_Identifier (Loc, Name_uInit),
2597 Stmts_List => Init_Tags_List,
2598 Fixed_Comps => False,
2599 Variable_Comps => True);
2600
2601 if Is_Non_Empty_List (Init_Tags_List) then
2602 Append_List_To (Body_Stmts, Init_Tags_List);
2603 end if;
2604 end if;
2605 end if;
2606
2607 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2608 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2609 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2610 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2611
2612 if not Debug_Generated_Code then
2613 Set_Debug_Info_Off (Proc_Id);
2614 end if;
2615
2616 -- Associate Init_Proc with type, and determine if the procedure
2617 -- is null (happens because of the Initialize_Scalars pragma case,
2618 -- where we have to generate a null procedure in case it is called
2619 -- by a client with Initialize_Scalars set). Such procedures have
2620 -- to be generated, but do not have to be called, so we mark them
2621 -- as null to suppress the call.
2622
2623 Set_Init_Proc (Rec_Type, Proc_Id);
2624
2625 if List_Length (Body_Stmts) = 1
2626
2627 -- We must skip SCIL nodes because they may have been added to this
2628 -- list by Insert_Actions.
2629
2630 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
2631 and then VM_Target = No_VM
2632 then
2633 -- Even though the init proc may be null at this time it might get
2634 -- some stuff added to it later by the VM backend.
2635
2636 Set_Is_Null_Init_Proc (Proc_Id);
2637 end if;
2638 end Build_Init_Procedure;
2639
2640 ---------------------------
2641 -- Build_Init_Statements --
2642 ---------------------------
2643
2644 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2645 Check_List : constant List_Id := New_List;
2646 Alt_List : List_Id;
2647 Decl : Node_Id;
2648 Id : Entity_Id;
2649 Names : Node_Id;
2650 Statement_List : List_Id;
2651 Stmts : List_Id;
2652 Typ : Entity_Id;
2653 Variant : Node_Id;
2654
2655 Per_Object_Constraint_Components : Boolean;
2656
2657 function Has_Access_Constraint (E : Entity_Id) return Boolean;
2658 -- Components with access discriminants that depend on the current
2659 -- instance must be initialized after all other components.
2660
2661 ---------------------------
2662 -- Has_Access_Constraint --
2663 ---------------------------
2664
2665 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2666 Disc : Entity_Id;
2667 T : constant Entity_Id := Etype (E);
2668
2669 begin
2670 if Has_Per_Object_Constraint (E)
2671 and then Has_Discriminants (T)
2672 then
2673 Disc := First_Discriminant (T);
2674 while Present (Disc) loop
2675 if Is_Access_Type (Etype (Disc)) then
2676 return True;
2677 end if;
2678
2679 Next_Discriminant (Disc);
2680 end loop;
2681
2682 return False;
2683 else
2684 return False;
2685 end if;
2686 end Has_Access_Constraint;
2687
2688 -- Start of processing for Build_Init_Statements
2689
2690 begin
2691 if Null_Present (Comp_List) then
2692 return New_List (Make_Null_Statement (Loc));
2693 end if;
2694
2695 Statement_List := New_List;
2696
2697 -- Loop through visible declarations of task types and protected
2698 -- types moving any expanded code from the spec to the body of the
2699 -- init procedure.
2700
2701 if Is_Task_Record_Type (Rec_Type)
2702 or else Is_Protected_Record_Type (Rec_Type)
2703 then
2704 declare
2705 Decl : constant Node_Id :=
2706 Parent (Corresponding_Concurrent_Type (Rec_Type));
2707 Def : Node_Id;
2708 N1 : Node_Id;
2709 N2 : Node_Id;
2710
2711 begin
2712 if Is_Task_Record_Type (Rec_Type) then
2713 Def := Task_Definition (Decl);
2714 else
2715 Def := Protected_Definition (Decl);
2716 end if;
2717
2718 if Present (Def) then
2719 N1 := First (Visible_Declarations (Def));
2720 while Present (N1) loop
2721 N2 := N1;
2722 N1 := Next (N1);
2723
2724 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2725 or else Nkind (N2) in N_Raise_xxx_Error
2726 or else Nkind (N2) = N_Procedure_Call_Statement
2727 then
2728 Append_To (Statement_List,
2729 New_Copy_Tree (N2, New_Scope => Proc_Id));
2730 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2731 Analyze (N2);
2732 end if;
2733 end loop;
2734 end if;
2735 end;
2736 end if;
2737
2738 -- Loop through components, skipping pragmas, in 2 steps. The first
2739 -- step deals with regular components. The second step deals with
2740 -- components have per object constraints, and no explicit initia-
2741 -- lization.
2742
2743 Per_Object_Constraint_Components := False;
2744
2745 -- First step : regular components
2746
2747 Decl := First_Non_Pragma (Component_Items (Comp_List));
2748 while Present (Decl) loop
2749 Loc := Sloc (Decl);
2750 Build_Record_Checks
2751 (Subtype_Indication (Component_Definition (Decl)), Check_List);
2752
2753 Id := Defining_Identifier (Decl);
2754 Typ := Etype (Id);
2755
2756 if Has_Access_Constraint (Id)
2757 and then No (Expression (Decl))
2758 then
2759 -- Skip processing for now and ask for a second pass
2760
2761 Per_Object_Constraint_Components := True;
2762
2763 else
2764 -- Case of explicit initialization
2765
2766 if Present (Expression (Decl)) then
2767 if Is_CPP_Constructor_Call (Expression (Decl)) then
2768 Stmts :=
2769 Build_Initialization_Call
2770 (Loc,
2771 Id_Ref =>
2772 Make_Selected_Component (Loc,
2773 Prefix =>
2774 Make_Identifier (Loc, Name_uInit),
2775 Selector_Name => New_Occurrence_Of (Id, Loc)),
2776 Typ => Typ,
2777 In_Init_Proc => True,
2778 Enclos_Type => Rec_Type,
2779 Discr_Map => Discr_Map,
2780 Constructor_Ref => Expression (Decl));
2781 else
2782 Stmts := Build_Assignment (Id, Expression (Decl));
2783 end if;
2784
2785 -- Case of composite component with its own Init_Proc
2786
2787 elsif not Is_Interface (Typ)
2788 and then Has_Non_Null_Base_Init_Proc (Typ)
2789 then
2790 Stmts :=
2791 Build_Initialization_Call
2792 (Loc,
2793 Id_Ref =>
2794 Make_Selected_Component (Loc,
2795 Prefix => Make_Identifier (Loc, Name_uInit),
2796 Selector_Name => New_Occurrence_Of (Id, Loc)),
2797 Typ => Typ,
2798 In_Init_Proc => True,
2799 Enclos_Type => Rec_Type,
2800 Discr_Map => Discr_Map);
2801
2802 Clean_Task_Names (Typ, Proc_Id);
2803
2804 -- Case of component needing simple initialization
2805
2806 elsif Component_Needs_Simple_Initialization (Typ) then
2807 Stmts :=
2808 Build_Assignment
2809 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
2810
2811 -- Nothing needed for this case
2812
2813 else
2814 Stmts := No_List;
2815 end if;
2816
2817 if Present (Check_List) then
2818 Append_List_To (Statement_List, Check_List);
2819 end if;
2820
2821 if Present (Stmts) then
2822
2823 -- Add the initialization of the record controller before
2824 -- the _Parent field is attached to it when the attachment
2825 -- can occur. It does not work to simply initialize the
2826 -- controller first: it must be initialized after the parent
2827 -- if the parent holds discriminants that can be used to
2828 -- compute the offset of the controller. We assume here that
2829 -- the last statement of the initialization call is the
2830 -- attachment of the parent (see Build_Initialization_Call)
2831
2832 if Chars (Id) = Name_uController
2833 and then Rec_Type /= Etype (Rec_Type)
2834 and then Has_Controlled_Component (Etype (Rec_Type))
2835 and then Has_New_Controlled_Component (Rec_Type)
2836 and then Present (Last (Statement_List))
2837 then
2838 Insert_List_Before (Last (Statement_List), Stmts);
2839 else
2840 Append_List_To (Statement_List, Stmts);
2841 end if;
2842 end if;
2843 end if;
2844
2845 Next_Non_Pragma (Decl);
2846 end loop;
2847
2848 -- Set up tasks and protected object support. This needs to be done
2849 -- before any component with a per-object access discriminant
2850 -- constraint, or any variant part (which may contain such
2851 -- components) is initialized, because the initialization of these
2852 -- components may reference the enclosing concurrent object.
2853
2854 -- For a task record type, add the task create call and calls
2855 -- to bind any interrupt (signal) entries.
2856
2857 if Is_Task_Record_Type (Rec_Type) then
2858
2859 -- In the case of the restricted run time the ATCB has already
2860 -- been preallocated.
2861
2862 if Restricted_Profile then
2863 Append_To (Statement_List,
2864 Make_Assignment_Statement (Loc,
2865 Name => Make_Selected_Component (Loc,
2866 Prefix => Make_Identifier (Loc, Name_uInit),
2867 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
2868 Expression => Make_Attribute_Reference (Loc,
2869 Prefix =>
2870 Make_Selected_Component (Loc,
2871 Prefix => Make_Identifier (Loc, Name_uInit),
2872 Selector_Name =>
2873 Make_Identifier (Loc, Name_uATCB)),
2874 Attribute_Name => Name_Unchecked_Access)));
2875 end if;
2876
2877 Append_To (Statement_List, Make_Task_Create_Call (Rec_Type));
2878
2879 -- Generate the statements which map a string entry name to a
2880 -- task entry index. Note that the task may not have entries.
2881
2882 if Entry_Names_OK then
2883 Names := Build_Entry_Names (Rec_Type);
2884
2885 if Present (Names) then
2886 Append_To (Statement_List, Names);
2887 end if;
2888 end if;
2889
2890 declare
2891 Task_Type : constant Entity_Id :=
2892 Corresponding_Concurrent_Type (Rec_Type);
2893 Task_Decl : constant Node_Id := Parent (Task_Type);
2894 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
2895 Vis_Decl : Node_Id;
2896 Ent : Entity_Id;
2897
2898 begin
2899 if Present (Task_Def) then
2900 Vis_Decl := First (Visible_Declarations (Task_Def));
2901 while Present (Vis_Decl) loop
2902 Loc := Sloc (Vis_Decl);
2903
2904 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
2905 if Get_Attribute_Id (Chars (Vis_Decl)) =
2906 Attribute_Address
2907 then
2908 Ent := Entity (Name (Vis_Decl));
2909
2910 if Ekind (Ent) = E_Entry then
2911 Append_To (Statement_List,
2912 Make_Procedure_Call_Statement (Loc,
2913 Name => New_Reference_To (
2914 RTE (RE_Bind_Interrupt_To_Entry), Loc),
2915 Parameter_Associations => New_List (
2916 Make_Selected_Component (Loc,
2917 Prefix =>
2918 Make_Identifier (Loc, Name_uInit),
2919 Selector_Name =>
2920 Make_Identifier (Loc, Name_uTask_Id)),
2921 Entry_Index_Expression (
2922 Loc, Ent, Empty, Task_Type),
2923 Expression (Vis_Decl))));
2924 end if;
2925 end if;
2926 end if;
2927
2928 Next (Vis_Decl);
2929 end loop;
2930 end if;
2931 end;
2932 end if;
2933
2934 -- For a protected type, add statements generated by
2935 -- Make_Initialize_Protection.
2936
2937 if Is_Protected_Record_Type (Rec_Type) then
2938 Append_List_To (Statement_List,
2939 Make_Initialize_Protection (Rec_Type));
2940
2941 -- Generate the statements which map a string entry name to a
2942 -- protected entry index. Note that the protected type may not
2943 -- have entries.
2944
2945 if Entry_Names_OK then
2946 Names := Build_Entry_Names (Rec_Type);
2947
2948 if Present (Names) then
2949 Append_To (Statement_List, Names);
2950 end if;
2951 end if;
2952 end if;
2953
2954 if Per_Object_Constraint_Components then
2955
2956 -- Second pass: components with per-object constraints
2957
2958 Decl := First_Non_Pragma (Component_Items (Comp_List));
2959 while Present (Decl) loop
2960 Loc := Sloc (Decl);
2961 Id := Defining_Identifier (Decl);
2962 Typ := Etype (Id);
2963
2964 if Has_Access_Constraint (Id)
2965 and then No (Expression (Decl))
2966 then
2967 if Has_Non_Null_Base_Init_Proc (Typ) then
2968 Append_List_To (Statement_List,
2969 Build_Initialization_Call (Loc,
2970 Make_Selected_Component (Loc,
2971 Prefix => Make_Identifier (Loc, Name_uInit),
2972 Selector_Name => New_Occurrence_Of (Id, Loc)),
2973 Typ,
2974 In_Init_Proc => True,
2975 Enclos_Type => Rec_Type,
2976 Discr_Map => Discr_Map));
2977
2978 Clean_Task_Names (Typ, Proc_Id);
2979
2980 elsif Component_Needs_Simple_Initialization (Typ) then
2981 Append_List_To (Statement_List,
2982 Build_Assignment
2983 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
2984 end if;
2985 end if;
2986
2987 Next_Non_Pragma (Decl);
2988 end loop;
2989 end if;
2990
2991 -- Process the variant part
2992
2993 if Present (Variant_Part (Comp_List)) then
2994 Alt_List := New_List;
2995 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
2996 while Present (Variant) loop
2997 Loc := Sloc (Variant);
2998 Append_To (Alt_List,
2999 Make_Case_Statement_Alternative (Loc,
3000 Discrete_Choices =>
3001 New_Copy_List (Discrete_Choices (Variant)),
3002 Statements =>
3003 Build_Init_Statements (Component_List (Variant))));
3004 Next_Non_Pragma (Variant);
3005 end loop;
3006
3007 -- The expression of the case statement which is a reference
3008 -- to one of the discriminants is replaced by the appropriate
3009 -- formal parameter of the initialization procedure.
3010
3011 Append_To (Statement_List,
3012 Make_Case_Statement (Loc,
3013 Expression =>
3014 New_Reference_To (Discriminal (
3015 Entity (Name (Variant_Part (Comp_List)))), Loc),
3016 Alternatives => Alt_List));
3017 end if;
3018
3019 -- If no initializations when generated for component declarations
3020 -- corresponding to this Statement_List, append a null statement
3021 -- to the Statement_List to make it a valid Ada tree.
3022
3023 if Is_Empty_List (Statement_List) then
3024 Append (New_Node (N_Null_Statement, Loc), Statement_List);
3025 end if;
3026
3027 return Statement_List;
3028
3029 exception
3030 when RE_Not_Available =>
3031 return Empty_List;
3032 end Build_Init_Statements;
3033
3034 -------------------------
3035 -- Build_Record_Checks --
3036 -------------------------
3037
3038 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
3039 Subtype_Mark_Id : Entity_Id;
3040
3041 begin
3042 if Nkind (S) = N_Subtype_Indication then
3043 Find_Type (Subtype_Mark (S));
3044 Subtype_Mark_Id := Entity (Subtype_Mark (S));
3045
3046 -- Remaining processing depends on type
3047
3048 case Ekind (Subtype_Mark_Id) is
3049
3050 when Array_Kind =>
3051 Constrain_Array (S, Check_List);
3052
3053 when others =>
3054 null;
3055 end case;
3056 end if;
3057 end Build_Record_Checks;
3058
3059 -------------------------------------------
3060 -- Component_Needs_Simple_Initialization --
3061 -------------------------------------------
3062
3063 function Component_Needs_Simple_Initialization
3064 (T : Entity_Id) return Boolean
3065 is
3066 begin
3067 return
3068 Needs_Simple_Initialization (T)
3069 and then not Is_RTE (T, RE_Tag)
3070
3071 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
3072
3073 and then not Is_RTE (T, RE_Interface_Tag);
3074 end Component_Needs_Simple_Initialization;
3075
3076 ---------------------
3077 -- Constrain_Array --
3078 ---------------------
3079
3080 procedure Constrain_Array
3081 (SI : Node_Id;
3082 Check_List : List_Id)
3083 is
3084 C : constant Node_Id := Constraint (SI);
3085 Number_Of_Constraints : Nat := 0;
3086 Index : Node_Id;
3087 S, T : Entity_Id;
3088
3089 begin
3090 T := Entity (Subtype_Mark (SI));
3091
3092 if Ekind (T) in Access_Kind then
3093 T := Designated_Type (T);
3094 end if;
3095
3096 S := First (Constraints (C));
3097
3098 while Present (S) loop
3099 Number_Of_Constraints := Number_Of_Constraints + 1;
3100 Next (S);
3101 end loop;
3102
3103 -- In either case, the index constraint must provide a discrete
3104 -- range for each index of the array type and the type of each
3105 -- discrete range must be the same as that of the corresponding
3106 -- index. (RM 3.6.1)
3107
3108 S := First (Constraints (C));
3109 Index := First_Index (T);
3110 Analyze (Index);
3111
3112 -- Apply constraints to each index type
3113
3114 for J in 1 .. Number_Of_Constraints loop
3115 Constrain_Index (Index, S, Check_List);
3116 Next (Index);
3117 Next (S);
3118 end loop;
3119
3120 end Constrain_Array;
3121
3122 ---------------------
3123 -- Constrain_Index --
3124 ---------------------
3125
3126 procedure Constrain_Index
3127 (Index : Node_Id;
3128 S : Node_Id;
3129 Check_List : List_Id)
3130 is
3131 T : constant Entity_Id := Etype (Index);
3132
3133 begin
3134 if Nkind (S) = N_Range then
3135 Process_Range_Expr_In_Decl (S, T, Check_List);
3136 end if;
3137 end Constrain_Index;
3138
3139 --------------------------------------
3140 -- Parent_Subtype_Renaming_Discrims --
3141 --------------------------------------
3142
3143 function Parent_Subtype_Renaming_Discrims return Boolean is
3144 De : Entity_Id;
3145 Dp : Entity_Id;
3146
3147 begin
3148 if Base_Type (Pe) /= Pe then
3149 return False;
3150 end if;
3151
3152 if Etype (Pe) = Pe
3153 or else not Has_Discriminants (Pe)
3154 or else Is_Constrained (Pe)
3155 or else Is_Tagged_Type (Pe)
3156 then
3157 return False;
3158 end if;
3159
3160 -- If there are no explicit stored discriminants we have inherited
3161 -- the root type discriminants so far, so no renamings occurred.
3162
3163 if First_Discriminant (Pe) = First_Stored_Discriminant (Pe) then
3164 return False;
3165 end if;
3166
3167 -- Check if we have done some trivial renaming of the parent
3168 -- discriminants, i.e. something like
3169 --
3170 -- type DT (X1,X2: int) is new PT (X1,X2);
3171
3172 De := First_Discriminant (Pe);
3173 Dp := First_Discriminant (Etype (Pe));
3174
3175 while Present (De) loop
3176 pragma Assert (Present (Dp));
3177
3178 if Corresponding_Discriminant (De) /= Dp then
3179 return True;
3180 end if;
3181
3182 Next_Discriminant (De);
3183 Next_Discriminant (Dp);
3184 end loop;
3185
3186 return Present (Dp);
3187 end Parent_Subtype_Renaming_Discrims;
3188
3189 ------------------------
3190 -- Requires_Init_Proc --
3191 ------------------------
3192
3193 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3194 Comp_Decl : Node_Id;
3195 Id : Entity_Id;
3196 Typ : Entity_Id;
3197
3198 begin
3199 -- Definitely do not need one if specifically suppressed
3200
3201 if Suppress_Init_Proc (Rec_Id) then
3202 return False;
3203 end if;
3204
3205 -- If it is a type derived from a type with unknown discriminants,
3206 -- we cannot build an initialization procedure for it.
3207
3208 if Has_Unknown_Discriminants (Rec_Id)
3209 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3210 then
3211 return False;
3212 end if;
3213
3214 -- Otherwise we need to generate an initialization procedure if
3215 -- Is_CPP_Class is False and at least one of the following applies:
3216
3217 -- 1. Discriminants are present, since they need to be initialized
3218 -- with the appropriate discriminant constraint expressions.
3219 -- However, the discriminant of an unchecked union does not
3220 -- count, since the discriminant is not present.
3221
3222 -- 2. The type is a tagged type, since the implicit Tag component
3223 -- needs to be initialized with a pointer to the dispatch table.
3224
3225 -- 3. The type contains tasks
3226
3227 -- 4. One or more components has an initial value
3228
3229 -- 5. One or more components is for a type which itself requires
3230 -- an initialization procedure.
3231
3232 -- 6. One or more components is a type that requires simple
3233 -- initialization (see Needs_Simple_Initialization), except
3234 -- that types Tag and Interface_Tag are excluded, since fields
3235 -- of these types are initialized by other means.
3236
3237 -- 7. The type is the record type built for a task type (since at
3238 -- the very least, Create_Task must be called)
3239
3240 -- 8. The type is the record type built for a protected type (since
3241 -- at least Initialize_Protection must be called)
3242
3243 -- 9. The type is marked as a public entity. The reason we add this
3244 -- case (even if none of the above apply) is to properly handle
3245 -- Initialize_Scalars. If a package is compiled without an IS
3246 -- pragma, and the client is compiled with an IS pragma, then
3247 -- the client will think an initialization procedure is present
3248 -- and call it, when in fact no such procedure is required, but
3249 -- since the call is generated, there had better be a routine
3250 -- at the other end of the call, even if it does nothing!)
3251
3252 -- Note: the reason we exclude the CPP_Class case is because in this
3253 -- case the initialization is performed by the C++ constructors, and
3254 -- the IP is built by Set_CPP_Constructors.
3255
3256 if Is_CPP_Class (Rec_Id) then
3257 return False;
3258
3259 elsif Is_Interface (Rec_Id) then
3260 return False;
3261
3262 elsif (Has_Discriminants (Rec_Id)
3263 and then not Is_Unchecked_Union (Rec_Id))
3264 or else Is_Tagged_Type (Rec_Id)
3265 or else Is_Concurrent_Record_Type (Rec_Id)
3266 or else Has_Task (Rec_Id)
3267 then
3268 return True;
3269 end if;
3270
3271 Id := First_Component (Rec_Id);
3272 while Present (Id) loop
3273 Comp_Decl := Parent (Id);
3274 Typ := Etype (Id);
3275
3276 if Present (Expression (Comp_Decl))
3277 or else Has_Non_Null_Base_Init_Proc (Typ)
3278 or else Component_Needs_Simple_Initialization (Typ)
3279 then
3280 return True;
3281 end if;
3282
3283 Next_Component (Id);
3284 end loop;
3285
3286 -- As explained above, a record initialization procedure is needed
3287 -- for public types in case Initialize_Scalars applies to a client.
3288 -- However, such a procedure is not needed in the case where either
3289 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3290 -- applies. No_Initialize_Scalars excludes the possibility of using
3291 -- Initialize_Scalars in any partition, and No_Default_Initialization
3292 -- implies that no initialization should ever be done for objects of
3293 -- the type, so is incompatible with Initialize_Scalars.
3294
3295 if not Restriction_Active (No_Initialize_Scalars)
3296 and then not Restriction_Active (No_Default_Initialization)
3297 and then Is_Public (Rec_Id)
3298 then
3299 return True;
3300 end if;
3301
3302 return False;
3303 end Requires_Init_Proc;
3304
3305 -- Start of processing for Build_Record_Init_Proc
3306
3307 begin
3308 -- Check for value type, which means no initialization required
3309
3310 Rec_Type := Defining_Identifier (N);
3311
3312 if Is_Value_Type (Rec_Type) then
3313 return;
3314 end if;
3315
3316 -- This may be full declaration of a private type, in which case
3317 -- the visible entity is a record, and the private entity has been
3318 -- exchanged with it in the private part of the current package.
3319 -- The initialization procedure is built for the record type, which
3320 -- is retrievable from the private entity.
3321
3322 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3323 Rec_Type := Underlying_Type (Rec_Type);
3324 end if;
3325
3326 -- If there are discriminants, build the discriminant map to replace
3327 -- discriminants by their discriminals in complex bound expressions.
3328 -- These only arise for the corresponding records of synchronized types.
3329
3330 if Is_Concurrent_Record_Type (Rec_Type)
3331 and then Has_Discriminants (Rec_Type)
3332 then
3333 declare
3334 Disc : Entity_Id;
3335 begin
3336 Disc := First_Discriminant (Rec_Type);
3337 while Present (Disc) loop
3338 Append_Elmt (Disc, Discr_Map);
3339 Append_Elmt (Discriminal (Disc), Discr_Map);
3340 Next_Discriminant (Disc);
3341 end loop;
3342 end;
3343 end if;
3344
3345 -- Derived types that have no type extension can use the initialization
3346 -- procedure of their parent and do not need a procedure of their own.
3347 -- This is only correct if there are no representation clauses for the
3348 -- type or its parent, and if the parent has in fact been frozen so
3349 -- that its initialization procedure exists.
3350
3351 if Is_Derived_Type (Rec_Type)
3352 and then not Is_Tagged_Type (Rec_Type)
3353 and then not Is_Unchecked_Union (Rec_Type)
3354 and then not Has_New_Non_Standard_Rep (Rec_Type)
3355 and then not Parent_Subtype_Renaming_Discrims
3356 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3357 then
3358 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3359
3360 -- Otherwise if we need an initialization procedure, then build one,
3361 -- mark it as public and inlinable and as having a completion.
3362
3363 elsif Requires_Init_Proc (Rec_Type)
3364 or else Is_Unchecked_Union (Rec_Type)
3365 then
3366 Proc_Id :=
3367 Make_Defining_Identifier (Loc,
3368 Chars => Make_Init_Proc_Name (Rec_Type));
3369
3370 -- If No_Default_Initialization restriction is active, then we don't
3371 -- want to build an init_proc, but we need to mark that an init_proc
3372 -- would be needed if this restriction was not active (so that we can
3373 -- detect attempts to call it), so set a dummy init_proc in place.
3374
3375 if Restriction_Active (No_Default_Initialization) then
3376 Set_Init_Proc (Rec_Type, Proc_Id);
3377 return;
3378 end if;
3379
3380 Build_Offset_To_Top_Functions;
3381 Build_CPP_Init_Procedure;
3382 Build_Init_Procedure;
3383 Set_Is_Public (Proc_Id, Is_Public (Pe));
3384
3385 -- The initialization of protected records is not worth inlining.
3386 -- In addition, when compiled for another unit for inlining purposes,
3387 -- it may make reference to entities that have not been elaborated
3388 -- yet. The initialization of controlled records contains a nested
3389 -- clean-up procedure that makes it impractical to inline as well,
3390 -- and leads to undefined symbols if inlined in a different unit.
3391 -- Similar considerations apply to task types.
3392
3393 if not Is_Concurrent_Type (Rec_Type)
3394 and then not Has_Task (Rec_Type)
3395 and then not Needs_Finalization (Rec_Type)
3396 then
3397 Set_Is_Inlined (Proc_Id);
3398 end if;
3399
3400 Set_Is_Internal (Proc_Id);
3401 Set_Has_Completion (Proc_Id);
3402
3403 if not Debug_Generated_Code then
3404 Set_Debug_Info_Off (Proc_Id);
3405 end if;
3406
3407 declare
3408 Agg : constant Node_Id :=
3409 Build_Equivalent_Record_Aggregate (Rec_Type);
3410
3411 procedure Collect_Itypes (Comp : Node_Id);
3412 -- Generate references to itypes in the aggregate, because
3413 -- the first use of the aggregate may be in a nested scope.
3414
3415 --------------------
3416 -- Collect_Itypes --
3417 --------------------
3418
3419 procedure Collect_Itypes (Comp : Node_Id) is
3420 Ref : Node_Id;
3421 Sub_Aggr : Node_Id;
3422 Typ : constant Entity_Id := Etype (Comp);
3423
3424 begin
3425 if Is_Array_Type (Typ)
3426 and then Is_Itype (Typ)
3427 then
3428 Ref := Make_Itype_Reference (Loc);
3429 Set_Itype (Ref, Typ);
3430 Append_Freeze_Action (Rec_Type, Ref);
3431
3432 Ref := Make_Itype_Reference (Loc);
3433 Set_Itype (Ref, Etype (First_Index (Typ)));
3434 Append_Freeze_Action (Rec_Type, Ref);
3435
3436 Sub_Aggr := First (Expressions (Comp));
3437
3438 -- Recurse on nested arrays
3439
3440 while Present (Sub_Aggr) loop
3441 Collect_Itypes (Sub_Aggr);
3442 Next (Sub_Aggr);
3443 end loop;
3444 end if;
3445 end Collect_Itypes;
3446
3447 begin
3448 -- If there is a static initialization aggregate for the type,
3449 -- generate itype references for the types of its (sub)components,
3450 -- to prevent out-of-scope errors in the resulting tree.
3451 -- The aggregate may have been rewritten as a Raise node, in which
3452 -- case there are no relevant itypes.
3453
3454 if Present (Agg)
3455 and then Nkind (Agg) = N_Aggregate
3456 then
3457 Set_Static_Initialization (Proc_Id, Agg);
3458
3459 declare
3460 Comp : Node_Id;
3461 begin
3462 Comp := First (Component_Associations (Agg));
3463 while Present (Comp) loop
3464 Collect_Itypes (Expression (Comp));
3465 Next (Comp);
3466 end loop;
3467 end;
3468 end if;
3469 end;
3470 end if;
3471 end Build_Record_Init_Proc;
3472
3473 ----------------------------
3474 -- Build_Slice_Assignment --
3475 ----------------------------
3476
3477 -- Generates the following subprogram:
3478
3479 -- procedure Assign
3480 -- (Source, Target : Array_Type,
3481 -- Left_Lo, Left_Hi : Index;
3482 -- Right_Lo, Right_Hi : Index;
3483 -- Rev : Boolean)
3484 -- is
3485 -- Li1 : Index;
3486 -- Ri1 : Index;
3487
3488 -- begin
3489
3490 -- if Left_Hi < Left_Lo then
3491 -- return;
3492 -- end if;
3493
3494 -- if Rev then
3495 -- Li1 := Left_Hi;
3496 -- Ri1 := Right_Hi;
3497 -- else
3498 -- Li1 := Left_Lo;
3499 -- Ri1 := Right_Lo;
3500 -- end if;
3501
3502 -- loop
3503 -- Target (Li1) := Source (Ri1);
3504
3505 -- if Rev then
3506 -- exit when Li1 = Left_Lo;
3507 -- Li1 := Index'pred (Li1);
3508 -- Ri1 := Index'pred (Ri1);
3509 -- else
3510 -- exit when Li1 = Left_Hi;
3511 -- Li1 := Index'succ (Li1);
3512 -- Ri1 := Index'succ (Ri1);
3513 -- end if;
3514 -- end loop;
3515 -- end Assign;
3516
3517 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3518 Loc : constant Source_Ptr := Sloc (Typ);
3519 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3520
3521 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
3522 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
3523 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
3524 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
3525 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
3526 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
3527 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
3528 -- Formal parameters of procedure
3529
3530 Proc_Name : constant Entity_Id :=
3531 Make_Defining_Identifier (Loc,
3532 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3533
3534 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3535 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3536 -- Subscripts for left and right sides
3537
3538 Decls : List_Id;
3539 Loops : Node_Id;
3540 Stats : List_Id;
3541
3542 begin
3543 -- Build declarations for indexes
3544
3545 Decls := New_List;
3546
3547 Append_To (Decls,
3548 Make_Object_Declaration (Loc,
3549 Defining_Identifier => Lnn,
3550 Object_Definition =>
3551 New_Occurrence_Of (Index, Loc)));
3552
3553 Append_To (Decls,
3554 Make_Object_Declaration (Loc,
3555 Defining_Identifier => Rnn,
3556 Object_Definition =>
3557 New_Occurrence_Of (Index, Loc)));
3558
3559 Stats := New_List;
3560
3561 -- Build test for empty slice case
3562
3563 Append_To (Stats,
3564 Make_If_Statement (Loc,
3565 Condition =>
3566 Make_Op_Lt (Loc,
3567 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
3568 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
3569 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
3570
3571 -- Build initializations for indexes
3572
3573 declare
3574 F_Init : constant List_Id := New_List;
3575 B_Init : constant List_Id := New_List;
3576
3577 begin
3578 Append_To (F_Init,
3579 Make_Assignment_Statement (Loc,
3580 Name => New_Occurrence_Of (Lnn, Loc),
3581 Expression => New_Occurrence_Of (Left_Lo, Loc)));
3582
3583 Append_To (F_Init,
3584 Make_Assignment_Statement (Loc,
3585 Name => New_Occurrence_Of (Rnn, Loc),
3586 Expression => New_Occurrence_Of (Right_Lo, Loc)));
3587
3588 Append_To (B_Init,
3589 Make_Assignment_Statement (Loc,
3590 Name => New_Occurrence_Of (Lnn, Loc),
3591 Expression => New_Occurrence_Of (Left_Hi, Loc)));
3592
3593 Append_To (B_Init,
3594 Make_Assignment_Statement (Loc,
3595 Name => New_Occurrence_Of (Rnn, Loc),
3596 Expression => New_Occurrence_Of (Right_Hi, Loc)));
3597
3598 Append_To (Stats,
3599 Make_If_Statement (Loc,
3600 Condition => New_Occurrence_Of (Rev, Loc),
3601 Then_Statements => B_Init,
3602 Else_Statements => F_Init));
3603 end;
3604
3605 -- Now construct the assignment statement
3606
3607 Loops :=
3608 Make_Loop_Statement (Loc,
3609 Statements => New_List (
3610 Make_Assignment_Statement (Loc,
3611 Name =>
3612 Make_Indexed_Component (Loc,
3613 Prefix => New_Occurrence_Of (Larray, Loc),
3614 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
3615 Expression =>
3616 Make_Indexed_Component (Loc,
3617 Prefix => New_Occurrence_Of (Rarray, Loc),
3618 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
3619 End_Label => Empty);
3620
3621 -- Build the exit condition and increment/decrement statements
3622
3623 declare
3624 F_Ass : constant List_Id := New_List;
3625 B_Ass : constant List_Id := New_List;
3626
3627 begin
3628 Append_To (F_Ass,
3629 Make_Exit_Statement (Loc,
3630 Condition =>
3631 Make_Op_Eq (Loc,
3632 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3633 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
3634
3635 Append_To (F_Ass,
3636 Make_Assignment_Statement (Loc,
3637 Name => New_Occurrence_Of (Lnn, Loc),
3638 Expression =>
3639 Make_Attribute_Reference (Loc,
3640 Prefix =>
3641 New_Occurrence_Of (Index, Loc),
3642 Attribute_Name => Name_Succ,
3643 Expressions => New_List (
3644 New_Occurrence_Of (Lnn, Loc)))));
3645
3646 Append_To (F_Ass,
3647 Make_Assignment_Statement (Loc,
3648 Name => New_Occurrence_Of (Rnn, Loc),
3649 Expression =>
3650 Make_Attribute_Reference (Loc,
3651 Prefix =>
3652 New_Occurrence_Of (Index, Loc),
3653 Attribute_Name => Name_Succ,
3654 Expressions => New_List (
3655 New_Occurrence_Of (Rnn, Loc)))));
3656
3657 Append_To (B_Ass,
3658 Make_Exit_Statement (Loc,
3659 Condition =>
3660 Make_Op_Eq (Loc,
3661 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
3662 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
3663
3664 Append_To (B_Ass,
3665 Make_Assignment_Statement (Loc,
3666 Name => New_Occurrence_Of (Lnn, Loc),
3667 Expression =>
3668 Make_Attribute_Reference (Loc,
3669 Prefix =>
3670 New_Occurrence_Of (Index, Loc),
3671 Attribute_Name => Name_Pred,
3672 Expressions => New_List (
3673 New_Occurrence_Of (Lnn, Loc)))));
3674
3675 Append_To (B_Ass,
3676 Make_Assignment_Statement (Loc,
3677 Name => New_Occurrence_Of (Rnn, Loc),
3678 Expression =>
3679 Make_Attribute_Reference (Loc,
3680 Prefix =>
3681 New_Occurrence_Of (Index, Loc),
3682 Attribute_Name => Name_Pred,
3683 Expressions => New_List (
3684 New_Occurrence_Of (Rnn, Loc)))));
3685
3686 Append_To (Statements (Loops),
3687 Make_If_Statement (Loc,
3688 Condition => New_Occurrence_Of (Rev, Loc),
3689 Then_Statements => B_Ass,
3690 Else_Statements => F_Ass));
3691 end;
3692
3693 Append_To (Stats, Loops);
3694
3695 declare
3696 Spec : Node_Id;
3697 Formals : List_Id := New_List;
3698
3699 begin
3700 Formals := New_List (
3701 Make_Parameter_Specification (Loc,
3702 Defining_Identifier => Larray,
3703 Out_Present => True,
3704 Parameter_Type =>
3705 New_Reference_To (Base_Type (Typ), Loc)),
3706
3707 Make_Parameter_Specification (Loc,
3708 Defining_Identifier => Rarray,
3709 Parameter_Type =>
3710 New_Reference_To (Base_Type (Typ), Loc)),
3711
3712 Make_Parameter_Specification (Loc,
3713 Defining_Identifier => Left_Lo,
3714 Parameter_Type =>
3715 New_Reference_To (Index, Loc)),
3716
3717 Make_Parameter_Specification (Loc,
3718 Defining_Identifier => Left_Hi,
3719 Parameter_Type =>
3720 New_Reference_To (Index, Loc)),
3721
3722 Make_Parameter_Specification (Loc,
3723 Defining_Identifier => Right_Lo,
3724 Parameter_Type =>
3725 New_Reference_To (Index, Loc)),
3726
3727 Make_Parameter_Specification (Loc,
3728 Defining_Identifier => Right_Hi,
3729 Parameter_Type =>
3730 New_Reference_To (Index, Loc)));
3731
3732 Append_To (Formals,
3733 Make_Parameter_Specification (Loc,
3734 Defining_Identifier => Rev,
3735 Parameter_Type =>
3736 New_Reference_To (Standard_Boolean, Loc)));
3737
3738 Spec :=
3739 Make_Procedure_Specification (Loc,
3740 Defining_Unit_Name => Proc_Name,
3741 Parameter_Specifications => Formals);
3742
3743 Discard_Node (
3744 Make_Subprogram_Body (Loc,
3745 Specification => Spec,
3746 Declarations => Decls,
3747 Handled_Statement_Sequence =>
3748 Make_Handled_Sequence_Of_Statements (Loc,
3749 Statements => Stats)));
3750 end;
3751
3752 Set_TSS (Typ, Proc_Name);
3753 Set_Is_Pure (Proc_Name);
3754 end Build_Slice_Assignment;
3755
3756 -----------------------------
3757 -- Build_Untagged_Equality --
3758 -----------------------------
3759
3760 procedure Build_Untagged_Equality (Typ : Entity_Id) is
3761 Build_Eq : Boolean;
3762 Comp : Entity_Id;
3763 Decl : Node_Id;
3764 Op : Entity_Id;
3765 Prim : Elmt_Id;
3766 Eq_Op : Entity_Id;
3767
3768 function User_Defined_Eq (T : Entity_Id) return Entity_Id;
3769 -- Check whether the type T has a user-defined primitive equality. If so
3770 -- return it, else return Empty. If true for a component of Typ, we have
3771 -- to build the primitive equality for it.
3772
3773 ---------------------
3774 -- User_Defined_Eq --
3775 ---------------------
3776
3777 function User_Defined_Eq (T : Entity_Id) return Entity_Id is
3778 Prim : Elmt_Id;
3779 Op : Entity_Id;
3780
3781 begin
3782 Op := TSS (T, TSS_Composite_Equality);
3783
3784 if Present (Op) then
3785 return Op;
3786 end if;
3787
3788 Prim := First_Elmt (Collect_Primitive_Operations (T));
3789 while Present (Prim) loop
3790 Op := Node (Prim);
3791
3792 if Chars (Op) = Name_Op_Eq
3793 and then Etype (Op) = Standard_Boolean
3794 and then Etype (First_Formal (Op)) = T
3795 and then Etype (Next_Formal (First_Formal (Op))) = T
3796 then
3797 return Op;
3798 end if;
3799
3800 Next_Elmt (Prim);
3801 end loop;
3802
3803 return Empty;
3804 end User_Defined_Eq;
3805
3806 -- Start of processing for Build_Untagged_Equality
3807
3808 begin
3809 -- If a record component has a primitive equality operation, we must
3810 -- build the corresponding one for the current type.
3811
3812 Build_Eq := False;
3813 Comp := First_Component (Typ);
3814 while Present (Comp) loop
3815 if Is_Record_Type (Etype (Comp))
3816 and then Present (User_Defined_Eq (Etype (Comp)))
3817 then
3818 Build_Eq := True;
3819 end if;
3820
3821 Next_Component (Comp);
3822 end loop;
3823
3824 -- If there is a user-defined equality for the type, we do not create
3825 -- the implicit one.
3826
3827 Prim := First_Elmt (Collect_Primitive_Operations (Typ));
3828 Eq_Op := Empty;
3829 while Present (Prim) loop
3830 if Chars (Node (Prim)) = Name_Op_Eq
3831 and then Comes_From_Source (Node (Prim))
3832
3833 -- Don't we also need to check formal types and return type as in
3834 -- User_Defined_Eq above???
3835
3836 then
3837 Eq_Op := Node (Prim);
3838 Build_Eq := False;
3839 exit;
3840 end if;
3841
3842 Next_Elmt (Prim);
3843 end loop;
3844
3845 -- If the type is derived, inherit the operation, if present, from the
3846 -- parent type. It may have been declared after the type derivation. If
3847 -- the parent type itself is derived, it may have inherited an operation
3848 -- that has itself been overridden, so update its alias and related
3849 -- flags. Ditto for inequality.
3850
3851 if No (Eq_Op) and then Is_Derived_Type (Typ) then
3852 Prim := First_Elmt (Collect_Primitive_Operations (Etype (Typ)));
3853 while Present (Prim) loop
3854 if Chars (Node (Prim)) = Name_Op_Eq then
3855 Copy_TSS (Node (Prim), Typ);
3856 Build_Eq := False;
3857
3858 declare
3859 Op : constant Entity_Id := User_Defined_Eq (Typ);
3860 Eq_Op : constant Entity_Id := Node (Prim);
3861 NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
3862
3863 begin
3864 if Present (Op) then
3865 Set_Alias (Op, Eq_Op);
3866 Set_Is_Abstract_Subprogram
3867 (Op, Is_Abstract_Subprogram (Eq_Op));
3868
3869 if Chars (Next_Entity (Op)) = Name_Op_Ne then
3870 Set_Is_Abstract_Subprogram
3871 (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
3872 end if;
3873 end if;
3874 end;
3875
3876 exit;
3877 end if;
3878
3879 Next_Elmt (Prim);
3880 end loop;
3881 end if;
3882
3883 -- If not inherited and not user-defined, build body as for a type with
3884 -- tagged components.
3885
3886 if Build_Eq then
3887 Decl :=
3888 Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
3889 Op := Defining_Entity (Decl);
3890 Set_TSS (Typ, Op);
3891 Set_Is_Pure (Op);
3892
3893 if Is_Library_Level_Entity (Typ) then
3894 Set_Is_Public (Op);
3895 end if;
3896 end if;
3897 end Build_Untagged_Equality;
3898
3899 ------------------------------------
3900 -- Build_Variant_Record_Equality --
3901 ------------------------------------
3902
3903 -- Generates:
3904
3905 -- function _Equality (X, Y : T) return Boolean is
3906 -- begin
3907 -- -- Compare discriminants
3908
3909 -- if False or else X.D1 /= Y.D1 or else X.D2 /= Y.D2 then
3910 -- return False;
3911 -- end if;
3912
3913 -- -- Compare components
3914
3915 -- if False or else X.C1 /= Y.C1 or else X.C2 /= Y.C2 then
3916 -- return False;
3917 -- end if;
3918
3919 -- -- Compare variant part
3920
3921 -- case X.D1 is
3922 -- when V1 =>
3923 -- if False or else X.C2 /= Y.C2 or else X.C3 /= Y.C3 then
3924 -- return False;
3925 -- end if;
3926 -- ...
3927 -- when Vn =>
3928 -- if False or else X.Cn /= Y.Cn then
3929 -- return False;
3930 -- end if;
3931 -- end case;
3932
3933 -- return True;
3934 -- end _Equality;
3935
3936 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
3937 Loc : constant Source_Ptr := Sloc (Typ);
3938
3939 F : constant Entity_Id :=
3940 Make_Defining_Identifier (Loc,
3941 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
3942
3943 X : constant Entity_Id :=
3944 Make_Defining_Identifier (Loc,
3945 Chars => Name_X);
3946
3947 Y : constant Entity_Id :=
3948 Make_Defining_Identifier (Loc,
3949 Chars => Name_Y);
3950
3951 Def : constant Node_Id := Parent (Typ);
3952 Comps : constant Node_Id := Component_List (Type_Definition (Def));
3953 Stmts : constant List_Id := New_List;
3954 Pspecs : constant List_Id := New_List;
3955
3956 begin
3957 -- Derived Unchecked_Union types no longer inherit the equality function
3958 -- of their parent.
3959
3960 if Is_Derived_Type (Typ)
3961 and then not Is_Unchecked_Union (Typ)
3962 and then not Has_New_Non_Standard_Rep (Typ)
3963 then
3964 declare
3965 Parent_Eq : constant Entity_Id :=
3966 TSS (Root_Type (Typ), TSS_Composite_Equality);
3967
3968 begin
3969 if Present (Parent_Eq) then
3970 Copy_TSS (Parent_Eq, Typ);
3971 return;
3972 end if;
3973 end;
3974 end if;
3975
3976 Discard_Node (
3977 Make_Subprogram_Body (Loc,
3978 Specification =>
3979 Make_Function_Specification (Loc,
3980 Defining_Unit_Name => F,
3981 Parameter_Specifications => Pspecs,
3982 Result_Definition => New_Reference_To (Standard_Boolean, Loc)),
3983 Declarations => New_List,
3984 Handled_Statement_Sequence =>
3985 Make_Handled_Sequence_Of_Statements (Loc,
3986 Statements => Stmts)));
3987
3988 Append_To (Pspecs,
3989 Make_Parameter_Specification (Loc,
3990 Defining_Identifier => X,
3991 Parameter_Type => New_Reference_To (Typ, Loc)));
3992
3993 Append_To (Pspecs,
3994 Make_Parameter_Specification (Loc,
3995 Defining_Identifier => Y,
3996 Parameter_Type => New_Reference_To (Typ, Loc)));
3997
3998 -- Unchecked_Unions require additional machinery to support equality.
3999 -- Two extra parameters (A and B) are added to the equality function
4000 -- parameter list in order to capture the inferred values of the
4001 -- discriminants in later calls.
4002
4003 if Is_Unchecked_Union (Typ) then
4004 declare
4005 Discr_Type : constant Node_Id := Etype (First_Discriminant (Typ));
4006
4007 A : constant Node_Id :=
4008 Make_Defining_Identifier (Loc,
4009 Chars => Name_A);
4010
4011 B : constant Node_Id :=
4012 Make_Defining_Identifier (Loc,
4013 Chars => Name_B);
4014
4015 begin
4016 -- Add A and B to the parameter list
4017
4018 Append_To (Pspecs,
4019 Make_Parameter_Specification (Loc,
4020 Defining_Identifier => A,
4021 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
4022
4023 Append_To (Pspecs,
4024 Make_Parameter_Specification (Loc,
4025 Defining_Identifier => B,
4026 Parameter_Type => New_Reference_To (Discr_Type, Loc)));
4027
4028 -- Generate the following header code to compare the inferred
4029 -- discriminants:
4030
4031 -- if a /= b then
4032 -- return False;
4033 -- end if;
4034
4035 Append_To (Stmts,
4036 Make_If_Statement (Loc,
4037 Condition =>
4038 Make_Op_Ne (Loc,
4039 Left_Opnd => New_Reference_To (A, Loc),
4040 Right_Opnd => New_Reference_To (B, Loc)),
4041 Then_Statements => New_List (
4042 Make_Simple_Return_Statement (Loc,
4043 Expression => New_Occurrence_Of (Standard_False, Loc)))));
4044
4045 -- Generate component-by-component comparison. Note that we must
4046 -- propagate one of the inferred discriminant formals to act as
4047 -- the case statement switch.
4048
4049 Append_List_To (Stmts,
4050 Make_Eq_Case (Typ, Comps, A));
4051
4052 end;
4053
4054 -- Normal case (not unchecked union)
4055
4056 else
4057 Append_To (Stmts,
4058 Make_Eq_If (Typ,
4059 Discriminant_Specifications (Def)));
4060
4061 Append_List_To (Stmts,
4062 Make_Eq_Case (Typ, Comps));
4063 end if;
4064
4065 Append_To (Stmts,
4066 Make_Simple_Return_Statement (Loc,
4067 Expression => New_Reference_To (Standard_True, Loc)));
4068
4069 Set_TSS (Typ, F);
4070 Set_Is_Pure (F);
4071
4072 if not Debug_Generated_Code then
4073 Set_Debug_Info_Off (F);
4074 end if;
4075 end Build_Variant_Record_Equality;
4076
4077 -----------------------------
4078 -- Check_Stream_Attributes --
4079 -----------------------------
4080
4081 procedure Check_Stream_Attributes (Typ : Entity_Id) is
4082 Comp : Entity_Id;
4083 Par_Read : constant Boolean :=
4084 Stream_Attribute_Available (Typ, TSS_Stream_Read)
4085 and then not Has_Specified_Stream_Read (Typ);
4086 Par_Write : constant Boolean :=
4087 Stream_Attribute_Available (Typ, TSS_Stream_Write)
4088 and then not Has_Specified_Stream_Write (Typ);
4089
4090 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4091 -- Check that Comp has a user-specified Nam stream attribute
4092
4093 ----------------
4094 -- Check_Attr --
4095 ----------------
4096
4097 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4098 begin
4099 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4100 Error_Msg_Name_1 := Nam;
4101 Error_Msg_N
4102 ("|component& in limited extension must have% attribute", Comp);
4103 end if;
4104 end Check_Attr;
4105
4106 -- Start of processing for Check_Stream_Attributes
4107
4108 begin
4109 if Par_Read or else Par_Write then
4110 Comp := First_Component (Typ);
4111 while Present (Comp) loop
4112 if Comes_From_Source (Comp)
4113 and then Original_Record_Component (Comp) = Comp
4114 and then Is_Limited_Type (Etype (Comp))
4115 then
4116 if Par_Read then
4117 Check_Attr (Name_Read, TSS_Stream_Read);
4118 end if;
4119
4120 if Par_Write then
4121 Check_Attr (Name_Write, TSS_Stream_Write);
4122 end if;
4123 end if;
4124
4125 Next_Component (Comp);
4126 end loop;
4127 end if;
4128 end Check_Stream_Attributes;
4129
4130 -----------------------------
4131 -- Expand_Record_Extension --
4132 -----------------------------
4133
4134 -- Add a field _parent at the beginning of the record extension. This is
4135 -- used to implement inheritance. Here are some examples of expansion:
4136
4137 -- 1. no discriminants
4138 -- type T2 is new T1 with null record;
4139 -- gives
4140 -- type T2 is new T1 with record
4141 -- _Parent : T1;
4142 -- end record;
4143
4144 -- 2. renamed discriminants
4145 -- type T2 (B, C : Int) is new T1 (A => B) with record
4146 -- _Parent : T1 (A => B);
4147 -- D : Int;
4148 -- end;
4149
4150 -- 3. inherited discriminants
4151 -- type T2 is new T1 with record -- discriminant A inherited
4152 -- _Parent : T1 (A);
4153 -- D : Int;
4154 -- end;
4155
4156 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
4157 Indic : constant Node_Id := Subtype_Indication (Def);
4158 Loc : constant Source_Ptr := Sloc (Def);
4159 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
4160 Par_Subtype : Entity_Id;
4161 Comp_List : Node_Id;
4162 Comp_Decl : Node_Id;
4163 Parent_N : Node_Id;
4164 D : Entity_Id;
4165 List_Constr : constant List_Id := New_List;
4166
4167 begin
4168 -- Expand_Record_Extension is called directly from the semantics, so
4169 -- we must check to see whether expansion is active before proceeding
4170
4171 if not Expander_Active then
4172 return;
4173 end if;
4174
4175 -- This may be a derivation of an untagged private type whose full
4176 -- view is tagged, in which case the Derived_Type_Definition has no
4177 -- extension part. Build an empty one now.
4178
4179 if No (Rec_Ext_Part) then
4180 Rec_Ext_Part :=
4181 Make_Record_Definition (Loc,
4182 End_Label => Empty,
4183 Component_List => Empty,
4184 Null_Present => True);
4185
4186 Set_Record_Extension_Part (Def, Rec_Ext_Part);
4187 Mark_Rewrite_Insertion (Rec_Ext_Part);
4188 end if;
4189
4190 Comp_List := Component_List (Rec_Ext_Part);
4191
4192 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
4193
4194 -- If the derived type inherits its discriminants the type of the
4195 -- _parent field must be constrained by the inherited discriminants
4196
4197 if Has_Discriminants (T)
4198 and then Nkind (Indic) /= N_Subtype_Indication
4199 and then not Is_Constrained (Entity (Indic))
4200 then
4201 D := First_Discriminant (T);
4202 while Present (D) loop
4203 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
4204 Next_Discriminant (D);
4205 end loop;
4206
4207 Par_Subtype :=
4208 Process_Subtype (
4209 Make_Subtype_Indication (Loc,
4210 Subtype_Mark => New_Reference_To (Entity (Indic), Loc),
4211 Constraint =>
4212 Make_Index_Or_Discriminant_Constraint (Loc,
4213 Constraints => List_Constr)),
4214 Def);
4215
4216 -- Otherwise the original subtype_indication is just what is needed
4217
4218 else
4219 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
4220 end if;
4221
4222 Set_Parent_Subtype (T, Par_Subtype);
4223
4224 Comp_Decl :=
4225 Make_Component_Declaration (Loc,
4226 Defining_Identifier => Parent_N,
4227 Component_Definition =>
4228 Make_Component_Definition (Loc,
4229 Aliased_Present => False,
4230 Subtype_Indication => New_Reference_To (Par_Subtype, Loc)));
4231
4232 if Null_Present (Rec_Ext_Part) then
4233 Set_Component_List (Rec_Ext_Part,
4234 Make_Component_List (Loc,
4235 Component_Items => New_List (Comp_Decl),
4236 Variant_Part => Empty,
4237 Null_Present => False));
4238 Set_Null_Present (Rec_Ext_Part, False);
4239
4240 elsif Null_Present (Comp_List)
4241 or else Is_Empty_List (Component_Items (Comp_List))
4242 then
4243 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4244 Set_Null_Present (Comp_List, False);
4245
4246 else
4247 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4248 end if;
4249
4250 Analyze (Comp_Decl);
4251 end Expand_Record_Extension;
4252
4253 ------------------------------------
4254 -- Expand_N_Full_Type_Declaration --
4255 ------------------------------------
4256
4257 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
4258 Def_Id : constant Entity_Id := Defining_Identifier (N);
4259 B_Id : constant Entity_Id := Base_Type (Def_Id);
4260 Par_Id : Entity_Id;
4261 FN : Node_Id;
4262
4263 procedure Build_Master (Def_Id : Entity_Id);
4264 -- Create the master associated with Def_Id
4265
4266 ------------------
4267 -- Build_Master --
4268 ------------------
4269
4270 procedure Build_Master (Def_Id : Entity_Id) is
4271 begin
4272 -- Anonymous access types are created for the components of the
4273 -- record parameter for an entry declaration. No master is created
4274 -- for such a type.
4275
4276 if Has_Task (Designated_Type (Def_Id))
4277 and then Comes_From_Source (N)
4278 then
4279 Build_Master_Entity (Def_Id);
4280 Build_Master_Renaming (Parent (Def_Id), Def_Id);
4281
4282 -- Create a class-wide master because a Master_Id must be generated
4283 -- for access-to-limited-class-wide types whose root may be extended
4284 -- with task components.
4285
4286 -- Note: This code covers access-to-limited-interfaces because they
4287 -- can be used to reference tasks implementing them.
4288
4289 elsif Is_Class_Wide_Type (Designated_Type (Def_Id))
4290 and then Is_Limited_Type (Designated_Type (Def_Id))
4291 and then Tasking_Allowed
4292
4293 -- Do not create a class-wide master for types whose convention is
4294 -- Java since these types cannot embed Ada tasks anyway. Note that
4295 -- the following test cannot catch the following case:
4296
4297 -- package java.lang.Object is
4298 -- type Typ is tagged limited private;
4299 -- type Ref is access all Typ'Class;
4300 -- private
4301 -- type Typ is tagged limited ...;
4302 -- pragma Convention (Typ, Java)
4303 -- end;
4304
4305 -- Because the convention appears after we have done the
4306 -- processing for type Ref.
4307
4308 and then Convention (Designated_Type (Def_Id)) /= Convention_Java
4309 and then Convention (Designated_Type (Def_Id)) /= Convention_CIL
4310 then
4311 Build_Class_Wide_Master (Def_Id);
4312 end if;
4313 end Build_Master;
4314
4315 -- Start of processing for Expand_N_Full_Type_Declaration
4316
4317 begin
4318 if Is_Access_Type (Def_Id) then
4319 Build_Master (Def_Id);
4320
4321 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
4322 Expand_Access_Protected_Subprogram_Type (N);
4323 end if;
4324
4325 elsif Ada_Version >= Ada_2005
4326 and then Is_Array_Type (Def_Id)
4327 and then Is_Access_Type (Component_Type (Def_Id))
4328 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
4329 then
4330 Build_Master (Component_Type (Def_Id));
4331
4332 elsif Has_Task (Def_Id) then
4333 Expand_Previous_Access_Type (Def_Id);
4334
4335 elsif Ada_Version >= Ada_2005
4336 and then
4337 (Is_Record_Type (Def_Id)
4338 or else (Is_Array_Type (Def_Id)
4339 and then Is_Record_Type (Component_Type (Def_Id))))
4340 then
4341 declare
4342 Comp : Entity_Id;
4343 Typ : Entity_Id;
4344 M_Id : Entity_Id;
4345
4346 begin
4347 -- Look for the first anonymous access type component
4348
4349 if Is_Array_Type (Def_Id) then
4350 Comp := First_Entity (Component_Type (Def_Id));
4351 else
4352 Comp := First_Entity (Def_Id);
4353 end if;
4354
4355 while Present (Comp) loop
4356 Typ := Etype (Comp);
4357
4358 exit when Is_Access_Type (Typ)
4359 and then Ekind (Typ) = E_Anonymous_Access_Type;
4360
4361 Next_Entity (Comp);
4362 end loop;
4363
4364 -- If found we add a renaming declaration of master_id and we
4365 -- associate it to each anonymous access type component. Do
4366 -- nothing if the access type already has a master. This will be
4367 -- the case if the array type is the packed array created for a
4368 -- user-defined array type T, where the master_id is created when
4369 -- expanding the declaration for T.
4370
4371 if Present (Comp)
4372 and then Ekind (Typ) = E_Anonymous_Access_Type
4373 and then not Restriction_Active (No_Task_Hierarchy)
4374 and then No (Master_Id (Typ))
4375
4376 -- Do not consider run-times with no tasking support
4377
4378 and then RTE_Available (RE_Current_Master)
4379 and then Has_Task (Non_Limited_Designated_Type (Typ))
4380 then
4381 Build_Master_Entity (Def_Id);
4382 M_Id := Build_Master_Renaming (N, Def_Id);
4383
4384 if Is_Array_Type (Def_Id) then
4385 Comp := First_Entity (Component_Type (Def_Id));
4386 else
4387 Comp := First_Entity (Def_Id);
4388 end if;
4389
4390 while Present (Comp) loop
4391 Typ := Etype (Comp);
4392
4393 if Is_Access_Type (Typ)
4394 and then Ekind (Typ) = E_Anonymous_Access_Type
4395 then
4396 Set_Master_Id (Typ, M_Id);
4397 end if;
4398
4399 Next_Entity (Comp);
4400 end loop;
4401 end if;
4402 end;
4403 end if;
4404
4405 Par_Id := Etype (B_Id);
4406
4407 -- The parent type is private then we need to inherit any TSS operations
4408 -- from the full view.
4409
4410 if Ekind (Par_Id) in Private_Kind
4411 and then Present (Full_View (Par_Id))
4412 then
4413 Par_Id := Base_Type (Full_View (Par_Id));
4414 end if;
4415
4416 if Nkind (Type_Definition (Original_Node (N))) =
4417 N_Derived_Type_Definition
4418 and then not Is_Tagged_Type (Def_Id)
4419 and then Present (Freeze_Node (Par_Id))
4420 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
4421 then
4422 Ensure_Freeze_Node (B_Id);
4423 FN := Freeze_Node (B_Id);
4424
4425 if No (TSS_Elist (FN)) then
4426 Set_TSS_Elist (FN, New_Elmt_List);
4427 end if;
4428
4429 declare
4430 T_E : constant Elist_Id := TSS_Elist (FN);
4431 Elmt : Elmt_Id;
4432
4433 begin
4434 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4435 while Present (Elmt) loop
4436 if Chars (Node (Elmt)) /= Name_uInit then
4437 Append_Elmt (Node (Elmt), T_E);
4438 end if;
4439
4440 Next_Elmt (Elmt);
4441 end loop;
4442
4443 -- If the derived type itself is private with a full view, then
4444 -- associate the full view with the inherited TSS_Elist as well.
4445
4446 if Ekind (B_Id) in Private_Kind
4447 and then Present (Full_View (B_Id))
4448 then
4449 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4450 Set_TSS_Elist
4451 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4452 end if;
4453 end;
4454 end if;
4455 end Expand_N_Full_Type_Declaration;
4456
4457 ---------------------------------
4458 -- Expand_N_Object_Declaration --
4459 ---------------------------------
4460
4461 -- First we do special processing for objects of a tagged type where this
4462 -- is the point at which the type is frozen. The creation of the dispatch
4463 -- table and the initialization procedure have to be deferred to this
4464 -- point, since we reference previously declared primitive subprograms.
4465
4466 -- For all types, we call an initialization procedure if there is one
4467
4468 procedure Expand_N_Object_Declaration (N : Node_Id) is
4469 Def_Id : constant Entity_Id := Defining_Identifier (N);
4470 Expr : constant Node_Id := Expression (N);
4471 Loc : constant Source_Ptr := Sloc (N);
4472 Typ : constant Entity_Id := Etype (Def_Id);
4473 Base_Typ : constant Entity_Id := Base_Type (Typ);
4474 Expr_Q : Node_Id;
4475 Id_Ref : Node_Id;
4476 New_Ref : Node_Id;
4477
4478 Init_After : Node_Id := N;
4479 -- Node after which the init proc call is to be inserted. This is
4480 -- normally N, except for the case of a shared passive variable, in
4481 -- which case the init proc call must be inserted only after the bodies
4482 -- of the shared variable procedures have been seen.
4483
4484 function Rewrite_As_Renaming return Boolean;
4485 -- Indicate whether to rewrite a declaration with initialization into an
4486 -- object renaming declaration (see below).
4487
4488 -------------------------
4489 -- Rewrite_As_Renaming --
4490 -------------------------
4491
4492 function Rewrite_As_Renaming return Boolean is
4493 begin
4494 return not Aliased_Present (N)
4495 and then Is_Entity_Name (Expr_Q)
4496 and then Ekind (Entity (Expr_Q)) = E_Variable
4497 and then OK_To_Rename (Entity (Expr_Q))
4498 and then Is_Entity_Name (Object_Definition (N));
4499 end Rewrite_As_Renaming;
4500
4501 -- Start of processing for Expand_N_Object_Declaration
4502
4503 begin
4504 -- Don't do anything for deferred constants. All proper actions will be
4505 -- expanded during the full declaration.
4506
4507 if No (Expr) and Constant_Present (N) then
4508 return;
4509 end if;
4510
4511 -- Force construction of dispatch tables of library level tagged types
4512
4513 if Tagged_Type_Expansion
4514 and then Static_Dispatch_Tables
4515 and then Is_Library_Level_Entity (Def_Id)
4516 and then Is_Library_Level_Tagged_Type (Base_Typ)
4517 and then (Ekind (Base_Typ) = E_Record_Type
4518 or else Ekind (Base_Typ) = E_Protected_Type
4519 or else Ekind (Base_Typ) = E_Task_Type)
4520 and then not Has_Dispatch_Table (Base_Typ)
4521 then
4522 declare
4523 New_Nodes : List_Id := No_List;
4524
4525 begin
4526 if Is_Concurrent_Type (Base_Typ) then
4527 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
4528 else
4529 New_Nodes := Make_DT (Base_Typ, N);
4530 end if;
4531
4532 if not Is_Empty_List (New_Nodes) then
4533 Insert_List_Before (N, New_Nodes);
4534 end if;
4535 end;
4536 end if;
4537
4538 -- Make shared memory routines for shared passive variable
4539
4540 if Is_Shared_Passive (Def_Id) then
4541 Init_After := Make_Shared_Var_Procs (N);
4542 end if;
4543
4544 -- If tasks being declared, make sure we have an activation chain
4545 -- defined for the tasks (has no effect if we already have one), and
4546 -- also that a Master variable is established and that the appropriate
4547 -- enclosing construct is established as a task master.
4548
4549 if Has_Task (Typ) then
4550 Build_Activation_Chain_Entity (N);
4551 Build_Master_Entity (Def_Id);
4552 end if;
4553
4554 -- Build a list controller for declarations where the type is anonymous
4555 -- access and the designated type is controlled. Only declarations from
4556 -- source files receive such controllers in order to provide the same
4557 -- lifespan for any potential coextensions that may be associated with
4558 -- the object. Finalization lists of internal controlled anonymous
4559 -- access objects are already handled in Expand_N_Allocator.
4560
4561 if Comes_From_Source (N)
4562 and then Ekind (Typ) = E_Anonymous_Access_Type
4563 and then Is_Controlled (Directly_Designated_Type (Typ))
4564 and then No (Associated_Final_Chain (Typ))
4565 then
4566 Build_Final_List (N, Typ);
4567 end if;
4568
4569 -- Default initialization required, and no expression present
4570
4571 if No (Expr) then
4572
4573 -- For the default initialization case, if we have a private type
4574 -- with invariants, and invariant checks are enabled, then insert an
4575 -- invariant check after the object declaration. Note that it is OK
4576 -- to clobber the object with an invalid value since if the exception
4577 -- is raised, then the object will go out of scope.
4578
4579 if Has_Invariants (Typ)
4580 and then Present (Invariant_Procedure (Typ))
4581 then
4582 Insert_After (N,
4583 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
4584 end if;
4585
4586 -- Expand Initialize call for controlled objects. One may wonder why
4587 -- the Initialize Call is not done in the regular Init procedure
4588 -- attached to the record type. That's because the init procedure is
4589 -- recursively called on each component, including _Parent, thus the
4590 -- Init call for a controlled object would generate not only one
4591 -- Initialize call as it is required but one for each ancestor of
4592 -- its type. This processing is suppressed if No_Initialization set.
4593
4594 if not Needs_Finalization (Typ)
4595 or else No_Initialization (N)
4596 then
4597 null;
4598
4599 elsif not Abort_Allowed
4600 or else not Comes_From_Source (N)
4601 then
4602 Insert_Actions_After (Init_After,
4603 Make_Init_Call (
4604 Ref => New_Occurrence_Of (Def_Id, Loc),
4605 Typ => Base_Type (Typ),
4606 Flist_Ref => Find_Final_List (Def_Id),
4607 With_Attach => Make_Integer_Literal (Loc, 1)));
4608
4609 -- Abort allowed
4610
4611 else
4612 -- We need to protect the initialize call
4613
4614 -- begin
4615 -- Defer_Abort.all;
4616 -- Initialize (...);
4617 -- at end
4618 -- Undefer_Abort.all;
4619 -- end;
4620
4621 -- ??? this won't protect the initialize call for controlled
4622 -- components which are part of the init proc, so this block
4623 -- should probably also contain the call to _init_proc but this
4624 -- requires some code reorganization...
4625
4626 declare
4627 L : constant List_Id :=
4628 Make_Init_Call
4629 (Ref => New_Occurrence_Of (Def_Id, Loc),
4630 Typ => Base_Type (Typ),
4631 Flist_Ref => Find_Final_List (Def_Id),
4632 With_Attach => Make_Integer_Literal (Loc, 1));
4633
4634 Blk : constant Node_Id :=
4635 Make_Block_Statement (Loc,
4636 Handled_Statement_Sequence =>
4637 Make_Handled_Sequence_Of_Statements (Loc, L));
4638
4639 begin
4640 Prepend_To (L, Build_Runtime_Call (Loc, RE_Abort_Defer));
4641 Set_At_End_Proc (Handled_Statement_Sequence (Blk),
4642 New_Occurrence_Of (RTE (RE_Abort_Undefer_Direct), Loc));
4643 Insert_Actions_After (Init_After, New_List (Blk));
4644 Expand_At_End_Handler
4645 (Handled_Statement_Sequence (Blk), Entity (Identifier (Blk)));
4646 end;
4647 end if;
4648
4649 -- Call type initialization procedure if there is one. We build the
4650 -- call and put it immediately after the object declaration, so that
4651 -- it will be expanded in the usual manner. Note that this will
4652 -- result in proper handling of defaulted discriminants.
4653
4654 -- Need call if there is a base init proc
4655
4656 if Has_Non_Null_Base_Init_Proc (Typ)
4657
4658 -- Suppress call if No_Initialization set on declaration
4659
4660 and then not No_Initialization (N)
4661
4662 -- Suppress call for special case of value type for VM
4663
4664 and then not Is_Value_Type (Typ)
4665
4666 -- Suppress call if Suppress_Init_Proc set on the type. This is
4667 -- needed for the derived type case, where Suppress_Initialization
4668 -- may be set for the derived type, even if there is an init proc
4669 -- defined for the root type.
4670
4671 and then not Suppress_Init_Proc (Typ)
4672 then
4673 -- Return without initializing when No_Default_Initialization
4674 -- applies. Note that the actual restriction check occurs later,
4675 -- when the object is frozen, because we don't know yet whether
4676 -- the object is imported, which is a case where the check does
4677 -- not apply.
4678
4679 if Restriction_Active (No_Default_Initialization) then
4680 return;
4681 end if;
4682
4683 -- The call to the initialization procedure does NOT freeze the
4684 -- object being initialized. This is because the call is not a
4685 -- source level call. This works fine, because the only possible
4686 -- statements depending on freeze status that can appear after the
4687 -- Init_Proc call are rep clauses which can safely appear after
4688 -- actual references to the object. Note that this call may
4689 -- subsequently be removed (if a pragma Import is encountered),
4690 -- or moved to the freeze actions for the object (e.g. if an
4691 -- address clause is applied to the object, causing it to get
4692 -- delayed freezing).
4693
4694 Id_Ref := New_Reference_To (Def_Id, Loc);
4695 Set_Must_Not_Freeze (Id_Ref);
4696 Set_Assignment_OK (Id_Ref);
4697
4698 declare
4699 Init_Expr : constant Node_Id :=
4700 Static_Initialization (Base_Init_Proc (Typ));
4701 begin
4702 if Present (Init_Expr) then
4703 Set_Expression
4704 (N, New_Copy_Tree (Init_Expr, New_Scope => Current_Scope));
4705 return;
4706 else
4707 Initialization_Warning (Id_Ref);
4708
4709 Insert_Actions_After (Init_After,
4710 Build_Initialization_Call (Loc, Id_Ref, Typ));
4711 end if;
4712 end;
4713
4714 -- If simple initialization is required, then set an appropriate
4715 -- simple initialization expression in place. This special
4716 -- initialization is required even though No_Init_Flag is present,
4717 -- but is not needed if there was an explicit initialization.
4718
4719 -- An internally generated temporary needs no initialization because
4720 -- it will be assigned subsequently. In particular, there is no point
4721 -- in applying Initialize_Scalars to such a temporary.
4722
4723 elsif Needs_Simple_Initialization
4724 (Typ,
4725 Initialize_Scalars
4726 and then not Has_Following_Address_Clause (N))
4727 and then not Is_Internal (Def_Id)
4728 and then not Has_Init_Expression (N)
4729 then
4730 Set_No_Initialization (N, False);
4731 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
4732 Analyze_And_Resolve (Expression (N), Typ);
4733 end if;
4734
4735 -- Generate attribute for Persistent_BSS if needed
4736
4737 if Persistent_BSS_Mode
4738 and then Comes_From_Source (N)
4739 and then Is_Potentially_Persistent_Type (Typ)
4740 and then not Has_Init_Expression (N)
4741 and then Is_Library_Level_Entity (Def_Id)
4742 then
4743 declare
4744 Prag : Node_Id;
4745 begin
4746 Prag :=
4747 Make_Linker_Section_Pragma
4748 (Def_Id, Sloc (N), ".persistent.bss");
4749 Insert_After (N, Prag);
4750 Analyze (Prag);
4751 end;
4752 end if;
4753
4754 -- If access type, then we know it is null if not initialized
4755
4756 if Is_Access_Type (Typ) then
4757 Set_Is_Known_Null (Def_Id);
4758 end if;
4759
4760 -- Explicit initialization present
4761
4762 else
4763 -- Obtain actual expression from qualified expression
4764
4765 if Nkind (Expr) = N_Qualified_Expression then
4766 Expr_Q := Expression (Expr);
4767 else
4768 Expr_Q := Expr;
4769 end if;
4770
4771 -- When we have the appropriate type of aggregate in the expression
4772 -- (it has been determined during analysis of the aggregate by
4773 -- setting the delay flag), let's perform in place assignment and
4774 -- thus avoid creating a temporary.
4775
4776 if Is_Delayed_Aggregate (Expr_Q) then
4777 Convert_Aggr_In_Object_Decl (N);
4778
4779 -- Ada 2005 (AI-318-02): If the initialization expression is a call
4780 -- to a build-in-place function, then access to the declared object
4781 -- must be passed to the function. Currently we limit such functions
4782 -- to those with constrained limited result subtypes, but eventually
4783 -- plan to expand the allowed forms of functions that are treated as
4784 -- build-in-place.
4785
4786 elsif Ada_Version >= Ada_2005
4787 and then Is_Build_In_Place_Function_Call (Expr_Q)
4788 then
4789 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
4790
4791 -- The previous call expands the expression initializing the
4792 -- built-in-place object into further code that will be analyzed
4793 -- later. No further expansion needed here.
4794
4795 return;
4796
4797 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
4798 -- class-wide object to ensure that we copy the full object,
4799 -- unless we are targetting a VM where interfaces are handled by
4800 -- VM itself. Note that if the root type of Typ is an ancestor
4801 -- of Expr's type, both types share the same dispatch table and
4802 -- there is no need to displace the pointer.
4803
4804 elsif Comes_From_Source (N)
4805 and then Is_Interface (Typ)
4806 then
4807 pragma Assert (Is_Class_Wide_Type (Typ));
4808
4809 -- If the object is a return object of an inherently limited type,
4810 -- which implies build-in-place treatment, bypass the special
4811 -- treatment of class-wide interface initialization below. In this
4812 -- case, the expansion of the return statement will take care of
4813 -- creating the object (via allocator) and initializing it.
4814
4815 if Is_Return_Object (Def_Id)
4816 and then Is_Immutably_Limited_Type (Typ)
4817 then
4818 null;
4819
4820 elsif Tagged_Type_Expansion then
4821 declare
4822 Iface : constant Entity_Id := Root_Type (Typ);
4823 Expr_N : Node_Id := Expr;
4824 Expr_Typ : Entity_Id;
4825 New_Expr : Node_Id;
4826 Obj_Id : Entity_Id;
4827 Tag_Comp : Node_Id;
4828
4829 begin
4830 -- If the original node of the expression was a conversion
4831 -- to this specific class-wide interface type then we
4832 -- restore the original node because we must copy the object
4833 -- before displacing the pointer to reference the secondary
4834 -- tag component. This code must be kept synchronized with
4835 -- the expansion done by routine Expand_Interface_Conversion
4836
4837 if not Comes_From_Source (Expr_N)
4838 and then Nkind (Expr_N) = N_Explicit_Dereference
4839 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
4840 and then Etype (Original_Node (Expr_N)) = Typ
4841 then
4842 Rewrite (Expr_N, Original_Node (Expression (N)));
4843 end if;
4844
4845 -- Avoid expansion of redundant interface conversion
4846
4847 if Is_Interface (Etype (Expr_N))
4848 and then Nkind (Expr_N) = N_Type_Conversion
4849 and then Etype (Expr_N) = Typ
4850 then
4851 Expr_N := Expression (Expr_N);
4852 Set_Expression (N, Expr_N);
4853 end if;
4854
4855 Obj_Id := Make_Temporary (Loc, 'D', Expr_N);
4856 Expr_Typ := Base_Type (Etype (Expr_N));
4857
4858 if Is_Class_Wide_Type (Expr_Typ) then
4859 Expr_Typ := Root_Type (Expr_Typ);
4860 end if;
4861
4862 -- Replace
4863 -- CW : I'Class := Obj;
4864 -- by
4865 -- Tmp : T := Obj;
4866 -- type Ityp is not null access I'Class;
4867 -- CW : I'Class renames Ityp(Tmp.I_Tag'Address).all;
4868
4869 if Comes_From_Source (Expr_N)
4870 and then Nkind (Expr_N) = N_Identifier
4871 and then not Is_Interface (Expr_Typ)
4872 and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
4873 and then (Expr_Typ = Etype (Expr_Typ)
4874 or else not
4875 Is_Variable_Size_Record (Etype (Expr_Typ)))
4876 then
4877 -- Copy the object
4878
4879 Insert_Action (N,
4880 Make_Object_Declaration (Loc,
4881 Defining_Identifier => Obj_Id,
4882 Object_Definition =>
4883 New_Occurrence_Of (Expr_Typ, Loc),
4884 Expression =>
4885 Relocate_Node (Expr_N)));
4886
4887 -- Statically reference the tag associated with the
4888 -- interface
4889
4890 Tag_Comp :=
4891 Make_Selected_Component (Loc,
4892 Prefix => New_Occurrence_Of (Obj_Id, Loc),
4893 Selector_Name =>
4894 New_Reference_To
4895 (Find_Interface_Tag (Expr_Typ, Iface), Loc));
4896
4897 -- Replace
4898 -- IW : I'Class := Obj;
4899 -- by
4900 -- type Equiv_Record is record ... end record;
4901 -- implicit subtype CW is <Class_Wide_Subtype>;
4902 -- Tmp : CW := CW!(Obj);
4903 -- type Ityp is not null access I'Class;
4904 -- IW : I'Class renames
4905 -- Ityp!(Displace (Temp'Address, I'Tag)).all;
4906
4907 else
4908 -- Generate the equivalent record type and update the
4909 -- subtype indication to reference it.
4910
4911 Expand_Subtype_From_Expr
4912 (N => N,
4913 Unc_Type => Typ,
4914 Subtype_Indic => Object_Definition (N),
4915 Exp => Expr_N);
4916
4917 if not Is_Interface (Etype (Expr_N)) then
4918 New_Expr := Relocate_Node (Expr_N);
4919
4920 -- For interface types we use 'Address which displaces
4921 -- the pointer to the base of the object (if required)
4922
4923 else
4924 New_Expr :=
4925 Unchecked_Convert_To (Etype (Object_Definition (N)),
4926 Make_Explicit_Dereference (Loc,
4927 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4928 Make_Attribute_Reference (Loc,
4929 Prefix => Relocate_Node (Expr_N),
4930 Attribute_Name => Name_Address))));
4931 end if;
4932
4933 -- Copy the object
4934
4935 Insert_Action (N,
4936 Make_Object_Declaration (Loc,
4937 Defining_Identifier => Obj_Id,
4938 Object_Definition =>
4939 New_Occurrence_Of
4940 (Etype (Object_Definition (N)), Loc),
4941 Expression => New_Expr));
4942
4943 -- Dynamically reference the tag associated with the
4944 -- interface.
4945
4946 Tag_Comp :=
4947 Make_Function_Call (Loc,
4948 Name => New_Reference_To (RTE (RE_Displace), Loc),
4949 Parameter_Associations => New_List (
4950 Make_Attribute_Reference (Loc,
4951 Prefix => New_Occurrence_Of (Obj_Id, Loc),
4952 Attribute_Name => Name_Address),
4953 New_Reference_To
4954 (Node (First_Elmt (Access_Disp_Table (Iface))),
4955 Loc)));
4956 end if;
4957
4958 Rewrite (N,
4959 Make_Object_Renaming_Declaration (Loc,
4960 Defining_Identifier => Make_Temporary (Loc, 'D'),
4961 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
4962 Name => Convert_Tag_To_Interface (Typ, Tag_Comp)));
4963
4964 Analyze (N, Suppress => All_Checks);
4965
4966 -- Replace internal identifier of rewriten node by the
4967 -- identifier found in the sources. We also have to exchange
4968 -- entities containing their defining identifiers to ensure
4969 -- the correct replacement of the object declaration by this
4970 -- object renaming declaration ---because these identifiers
4971 -- were previously added by Enter_Name to the current scope.
4972 -- We must preserve the homonym chain of the source entity
4973 -- as well.
4974
4975 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
4976 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
4977 Exchange_Entities (Defining_Identifier (N), Def_Id);
4978 end;
4979 end if;
4980
4981 return;
4982
4983 else
4984 -- In most cases, we must check that the initial value meets any
4985 -- constraint imposed by the declared type. However, there is one
4986 -- very important exception to this rule. If the entity has an
4987 -- unconstrained nominal subtype, then it acquired its constraints
4988 -- from the expression in the first place, and not only does this
4989 -- mean that the constraint check is not needed, but an attempt to
4990 -- perform the constraint check can cause order of elaboration
4991 -- problems.
4992
4993 if not Is_Constr_Subt_For_U_Nominal (Typ) then
4994
4995 -- If this is an allocator for an aggregate that has been
4996 -- allocated in place, delay checks until assignments are
4997 -- made, because the discriminants are not initialized.
4998
4999 if Nkind (Expr) = N_Allocator
5000 and then No_Initialization (Expr)
5001 then
5002 null;
5003
5004 -- Otherwise apply a constraint check now if no prev error
5005
5006 elsif Nkind (Expr) /= N_Error then
5007 Apply_Constraint_Check (Expr, Typ);
5008
5009 -- If the expression has been marked as requiring a range
5010 -- generate it now and reset the flag.
5011
5012 if Do_Range_Check (Expr) then
5013 Set_Do_Range_Check (Expr, False);
5014
5015 if not Suppress_Assignment_Checks (N) then
5016 Generate_Range_Check
5017 (Expr, Typ, CE_Range_Check_Failed);
5018 end if;
5019 end if;
5020 end if;
5021 end if;
5022
5023 -- If the type is controlled and not inherently limited, then
5024 -- the target is adjusted after the copy and attached to the
5025 -- finalization list. However, no adjustment is done in the case
5026 -- where the object was initialized by a call to a function whose
5027 -- result is built in place, since no copy occurred. (Eventually
5028 -- we plan to support in-place function results for some cases
5029 -- of nonlimited types. ???) Similarly, no adjustment is required
5030 -- if we are going to rewrite the object declaration into a
5031 -- renaming declaration.
5032
5033 if Needs_Finalization (Typ)
5034 and then not Is_Immutably_Limited_Type (Typ)
5035 and then not Rewrite_As_Renaming
5036 then
5037 Insert_Actions_After (Init_After,
5038 Make_Adjust_Call (
5039 Ref => New_Reference_To (Def_Id, Loc),
5040 Typ => Base_Type (Typ),
5041 Flist_Ref => Find_Final_List (Def_Id),
5042 With_Attach => Make_Integer_Literal (Loc, 1)));
5043 end if;
5044
5045 -- For tagged types, when an init value is given, the tag has to
5046 -- be re-initialized separately in order to avoid the propagation
5047 -- of a wrong tag coming from a view conversion unless the type
5048 -- is class wide (in this case the tag comes from the init value).
5049 -- Suppress the tag assignment when VM_Target because VM tags are
5050 -- represented implicitly in objects. Ditto for types that are
5051 -- CPP_CLASS, and for initializations that are aggregates, because
5052 -- they have to have the right tag.
5053
5054 if Is_Tagged_Type (Typ)
5055 and then not Is_Class_Wide_Type (Typ)
5056 and then not Is_CPP_Class (Typ)
5057 and then Tagged_Type_Expansion
5058 and then Nkind (Expr) /= N_Aggregate
5059 then
5060 -- The re-assignment of the tag has to be done even if the
5061 -- object is a constant.
5062
5063 New_Ref :=
5064 Make_Selected_Component (Loc,
5065 Prefix => New_Reference_To (Def_Id, Loc),
5066 Selector_Name =>
5067 New_Reference_To (First_Tag_Component (Typ), Loc));
5068
5069 Set_Assignment_OK (New_Ref);
5070
5071 Insert_After (Init_After,
5072 Make_Assignment_Statement (Loc,
5073 Name => New_Ref,
5074 Expression =>
5075 Unchecked_Convert_To (RTE (RE_Tag),
5076 New_Reference_To
5077 (Node
5078 (First_Elmt
5079 (Access_Disp_Table (Base_Type (Typ)))),
5080 Loc))));
5081
5082 elsif Is_Tagged_Type (Typ)
5083 and then Is_CPP_Constructor_Call (Expr)
5084 then
5085 -- The call to the initialization procedure does NOT freeze the
5086 -- object being initialized.
5087
5088 Id_Ref := New_Reference_To (Def_Id, Loc);
5089 Set_Must_Not_Freeze (Id_Ref);
5090 Set_Assignment_OK (Id_Ref);
5091
5092 Insert_Actions_After (Init_After,
5093 Build_Initialization_Call (Loc, Id_Ref, Typ,
5094 Constructor_Ref => Expr));
5095
5096 -- We remove here the original call to the constructor
5097 -- to avoid its management in the backend
5098
5099 Set_Expression (N, Empty);
5100 return;
5101
5102 -- For discrete types, set the Is_Known_Valid flag if the
5103 -- initializing value is known to be valid.
5104
5105 elsif Is_Discrete_Type (Typ) and then Expr_Known_Valid (Expr) then
5106 Set_Is_Known_Valid (Def_Id);
5107
5108 elsif Is_Access_Type (Typ) then
5109
5110 -- For access types set the Is_Known_Non_Null flag if the
5111 -- initializing value is known to be non-null. We can also set
5112 -- Can_Never_Be_Null if this is a constant.
5113
5114 if Known_Non_Null (Expr) then
5115 Set_Is_Known_Non_Null (Def_Id, True);
5116
5117 if Constant_Present (N) then
5118 Set_Can_Never_Be_Null (Def_Id);
5119 end if;
5120 end if;
5121 end if;
5122
5123 -- If validity checking on copies, validate initial expression.
5124 -- But skip this if declaration is for a generic type, since it
5125 -- makes no sense to validate generic types. Not clear if this
5126 -- can happen for legal programs, but it definitely can arise
5127 -- from previous instantiation errors.
5128
5129 if Validity_Checks_On
5130 and then Validity_Check_Copies
5131 and then not Is_Generic_Type (Etype (Def_Id))
5132 then
5133 Ensure_Valid (Expr);
5134 Set_Is_Known_Valid (Def_Id);
5135 end if;
5136 end if;
5137
5138 -- Cases where the back end cannot handle the initialization directly
5139 -- In such cases, we expand an assignment that will be appropriately
5140 -- handled by Expand_N_Assignment_Statement.
5141
5142 -- The exclusion of the unconstrained case is wrong, but for now it
5143 -- is too much trouble ???
5144
5145 if (Is_Possibly_Unaligned_Slice (Expr)
5146 or else (Is_Possibly_Unaligned_Object (Expr)
5147 and then not Represented_As_Scalar (Etype (Expr))))
5148
5149 -- The exclusion of the unconstrained case is wrong, but for now
5150 -- it is too much trouble ???
5151
5152 and then not (Is_Array_Type (Etype (Expr))
5153 and then not Is_Constrained (Etype (Expr)))
5154 then
5155 declare
5156 Stat : constant Node_Id :=
5157 Make_Assignment_Statement (Loc,
5158 Name => New_Reference_To (Def_Id, Loc),
5159 Expression => Relocate_Node (Expr));
5160 begin
5161 Set_Expression (N, Empty);
5162 Set_No_Initialization (N);
5163 Set_Assignment_OK (Name (Stat));
5164 Set_No_Ctrl_Actions (Stat);
5165 Insert_After_And_Analyze (Init_After, Stat);
5166 end;
5167 end if;
5168
5169 -- Final transformation, if the initializing expression is an entity
5170 -- for a variable with OK_To_Rename set, then we transform:
5171
5172 -- X : typ := expr;
5173
5174 -- into
5175
5176 -- X : typ renames expr
5177
5178 -- provided that X is not aliased. The aliased case has to be
5179 -- excluded in general because Expr will not be aliased in general.
5180
5181 if Rewrite_As_Renaming then
5182 Rewrite (N,
5183 Make_Object_Renaming_Declaration (Loc,
5184 Defining_Identifier => Defining_Identifier (N),
5185 Subtype_Mark => Object_Definition (N),
5186 Name => Expr_Q));
5187
5188 -- We do not analyze this renaming declaration, because all its
5189 -- components have already been analyzed, and if we were to go
5190 -- ahead and analyze it, we would in effect be trying to generate
5191 -- another declaration of X, which won't do!
5192
5193 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
5194 Set_Analyzed (N);
5195 end if;
5196 end if;
5197
5198 -- Exception on library entity not available
5199
5200 exception
5201 when RE_Not_Available =>
5202 return;
5203 end Expand_N_Object_Declaration;
5204
5205 ---------------------------------
5206 -- Expand_N_Subtype_Indication --
5207 ---------------------------------
5208
5209 -- Add a check on the range of the subtype. The static case is partially
5210 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
5211 -- to check here for the static case in order to avoid generating
5212 -- extraneous expanded code. Also deal with validity checking.
5213
5214 procedure Expand_N_Subtype_Indication (N : Node_Id) is
5215 Ran : constant Node_Id := Range_Expression (Constraint (N));
5216 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
5217
5218 begin
5219 if Nkind (Constraint (N)) = N_Range_Constraint then
5220 Validity_Check_Range (Range_Expression (Constraint (N)));
5221 end if;
5222
5223 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
5224 Apply_Range_Check (Ran, Typ);
5225 end if;
5226 end Expand_N_Subtype_Indication;
5227
5228 ---------------------------
5229 -- Expand_N_Variant_Part --
5230 ---------------------------
5231
5232 -- If the last variant does not contain the Others choice, replace it with
5233 -- an N_Others_Choice node since Gigi always wants an Others. Note that we
5234 -- do not bother to call Analyze on the modified variant part, since it's
5235 -- only effect would be to compute the Others_Discrete_Choices node
5236 -- laboriously, and of course we already know the list of choices that
5237 -- corresponds to the others choice (it's the list we are replacing!)
5238
5239 procedure Expand_N_Variant_Part (N : Node_Id) is
5240 Last_Var : constant Node_Id := Last_Non_Pragma (Variants (N));
5241 Others_Node : Node_Id;
5242 begin
5243 if Nkind (First (Discrete_Choices (Last_Var))) /= N_Others_Choice then
5244 Others_Node := Make_Others_Choice (Sloc (Last_Var));
5245 Set_Others_Discrete_Choices
5246 (Others_Node, Discrete_Choices (Last_Var));
5247 Set_Discrete_Choices (Last_Var, New_List (Others_Node));
5248 end if;
5249 end Expand_N_Variant_Part;
5250
5251 ---------------------------------
5252 -- Expand_Previous_Access_Type --
5253 ---------------------------------
5254
5255 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
5256 T : Entity_Id := First_Entity (Current_Scope);
5257
5258 begin
5259 -- Find all access types declared in the current scope, whose
5260 -- designated type is Def_Id. If it does not have a Master_Id,
5261 -- create one now.
5262
5263 while Present (T) loop
5264 if Is_Access_Type (T)
5265 and then Designated_Type (T) = Def_Id
5266 and then No (Master_Id (T))
5267 then
5268 Build_Master_Entity (Def_Id);
5269 Build_Master_Renaming (Parent (Def_Id), T);
5270 end if;
5271
5272 Next_Entity (T);
5273 end loop;
5274 end Expand_Previous_Access_Type;
5275
5276 ------------------------------
5277 -- Expand_Record_Controller --
5278 ------------------------------
5279
5280 procedure Expand_Record_Controller (T : Entity_Id) is
5281 Def : Node_Id := Type_Definition (Parent (T));
5282 Comp_List : Node_Id;
5283 Comp_Decl : Node_Id;
5284 Loc : Source_Ptr;
5285 First_Comp : Node_Id;
5286 Controller_Type : Entity_Id;
5287 Ent : Entity_Id;
5288
5289 begin
5290 if Nkind (Def) = N_Derived_Type_Definition then
5291 Def := Record_Extension_Part (Def);
5292 end if;
5293
5294 if Null_Present (Def) then
5295 Set_Component_List (Def,
5296 Make_Component_List (Sloc (Def),
5297 Component_Items => Empty_List,
5298 Variant_Part => Empty,
5299 Null_Present => True));
5300 end if;
5301
5302 Comp_List := Component_List (Def);
5303
5304 if Null_Present (Comp_List)
5305 or else Is_Empty_List (Component_Items (Comp_List))
5306 then
5307 Loc := Sloc (Comp_List);
5308 else
5309 Loc := Sloc (First (Component_Items (Comp_List)));
5310 end if;
5311
5312 if Is_Immutably_Limited_Type (T) then
5313 Controller_Type := RTE (RE_Limited_Record_Controller);
5314 else
5315 Controller_Type := RTE (RE_Record_Controller);
5316 end if;
5317
5318 Ent := Make_Defining_Identifier (Loc, Name_uController);
5319
5320 Comp_Decl :=
5321 Make_Component_Declaration (Loc,
5322 Defining_Identifier => Ent,
5323 Component_Definition =>
5324 Make_Component_Definition (Loc,
5325 Aliased_Present => False,
5326 Subtype_Indication => New_Reference_To (Controller_Type, Loc)));
5327
5328 if Null_Present (Comp_List)
5329 or else Is_Empty_List (Component_Items (Comp_List))
5330 then
5331 Set_Component_Items (Comp_List, New_List (Comp_Decl));
5332 Set_Null_Present (Comp_List, False);
5333
5334 else
5335 -- The controller cannot be placed before the _Parent field since
5336 -- gigi lays out field in order and _parent must be first to preserve
5337 -- the polymorphism of tagged types.
5338
5339 First_Comp := First (Component_Items (Comp_List));
5340
5341 if not Is_Tagged_Type (T) then
5342 Insert_Before (First_Comp, Comp_Decl);
5343
5344 -- if T is a tagged type, place controller declaration after parent
5345 -- field and after eventual tags of interface types.
5346
5347 else
5348 while Present (First_Comp)
5349 and then
5350 (Chars (Defining_Identifier (First_Comp)) = Name_uParent
5351 or else Is_Tag (Defining_Identifier (First_Comp))
5352
5353 -- Ada 2005 (AI-251): The following condition covers secondary
5354 -- tags but also the adjacent component containing the offset
5355 -- to the base of the object (component generated if the parent
5356 -- has discriminants --- see Add_Interface_Tag_Components).
5357 -- This is required to avoid the addition of the controller
5358 -- between the secondary tag and its adjacent component.
5359
5360 or else Present
5361 (Related_Type
5362 (Defining_Identifier (First_Comp))))
5363 loop
5364 Next (First_Comp);
5365 end loop;
5366
5367 -- An empty tagged extension might consist only of the parent
5368 -- component. Otherwise insert the controller before the first
5369 -- component that is neither parent nor tag.
5370
5371 if Present (First_Comp) then
5372 Insert_Before (First_Comp, Comp_Decl);
5373 else
5374 Append (Comp_Decl, Component_Items (Comp_List));
5375 end if;
5376 end if;
5377 end if;
5378
5379 Push_Scope (T);
5380 Analyze (Comp_Decl);
5381 Set_Ekind (Ent, E_Component);
5382 Init_Component_Location (Ent);
5383
5384 -- Move the _controller entity ahead in the list of internal entities
5385 -- of the enclosing record so that it is selected instead of a
5386 -- potentially inherited one.
5387
5388 declare
5389 E : constant Entity_Id := Last_Entity (T);
5390 Comp : Entity_Id;
5391
5392 begin
5393 pragma Assert (Chars (E) = Name_uController);
5394
5395 Set_Next_Entity (E, First_Entity (T));
5396 Set_First_Entity (T, E);
5397
5398 Comp := Next_Entity (E);
5399 while Next_Entity (Comp) /= E loop
5400 Next_Entity (Comp);
5401 end loop;
5402
5403 Set_Next_Entity (Comp, Empty);
5404 Set_Last_Entity (T, Comp);
5405 end;
5406
5407 End_Scope;
5408
5409 exception
5410 when RE_Not_Available =>
5411 return;
5412 end Expand_Record_Controller;
5413
5414 ------------------------
5415 -- Expand_Tagged_Root --
5416 ------------------------
5417
5418 procedure Expand_Tagged_Root (T : Entity_Id) is
5419 Def : constant Node_Id := Type_Definition (Parent (T));
5420 Comp_List : Node_Id;
5421 Comp_Decl : Node_Id;
5422 Sloc_N : Source_Ptr;
5423
5424 begin
5425 if Null_Present (Def) then
5426 Set_Component_List (Def,
5427 Make_Component_List (Sloc (Def),
5428 Component_Items => Empty_List,
5429 Variant_Part => Empty,
5430 Null_Present => True));
5431 end if;
5432
5433 Comp_List := Component_List (Def);
5434
5435 if Null_Present (Comp_List)
5436 or else Is_Empty_List (Component_Items (Comp_List))
5437 then
5438 Sloc_N := Sloc (Comp_List);
5439 else
5440 Sloc_N := Sloc (First (Component_Items (Comp_List)));
5441 end if;
5442
5443 Comp_Decl :=
5444 Make_Component_Declaration (Sloc_N,
5445 Defining_Identifier => First_Tag_Component (T),
5446 Component_Definition =>
5447 Make_Component_Definition (Sloc_N,
5448 Aliased_Present => False,
5449 Subtype_Indication => New_Reference_To (RTE (RE_Tag), Sloc_N)));
5450
5451 if Null_Present (Comp_List)
5452 or else Is_Empty_List (Component_Items (Comp_List))
5453 then
5454 Set_Component_Items (Comp_List, New_List (Comp_Decl));
5455 Set_Null_Present (Comp_List, False);
5456
5457 else
5458 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
5459 end if;
5460
5461 -- We don't Analyze the whole expansion because the tag component has
5462 -- already been analyzed previously. Here we just insure that the tree
5463 -- is coherent with the semantic decoration
5464
5465 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
5466
5467 exception
5468 when RE_Not_Available =>
5469 return;
5470 end Expand_Tagged_Root;
5471
5472 ----------------------
5473 -- Clean_Task_Names --
5474 ----------------------
5475
5476 procedure Clean_Task_Names
5477 (Typ : Entity_Id;
5478 Proc_Id : Entity_Id)
5479 is
5480 begin
5481 if Has_Task (Typ)
5482 and then not Restriction_Active (No_Implicit_Heap_Allocations)
5483 and then not Global_Discard_Names
5484 and then Tagged_Type_Expansion
5485 then
5486 Set_Uses_Sec_Stack (Proc_Id);
5487 end if;
5488 end Clean_Task_Names;
5489
5490 ------------------------------
5491 -- Expand_Freeze_Array_Type --
5492 ------------------------------
5493
5494 procedure Expand_Freeze_Array_Type (N : Node_Id) is
5495 Typ : constant Entity_Id := Entity (N);
5496 Comp_Typ : constant Entity_Id := Component_Type (Typ);
5497 Base : constant Entity_Id := Base_Type (Typ);
5498
5499 begin
5500 if not Is_Bit_Packed_Array (Typ) then
5501
5502 -- If the component contains tasks, so does the array type. This may
5503 -- not be indicated in the array type because the component may have
5504 -- been a private type at the point of definition. Same if component
5505 -- type is controlled.
5506
5507 Set_Has_Task (Base, Has_Task (Comp_Typ));
5508 Set_Has_Controlled_Component (Base,
5509 Has_Controlled_Component (Comp_Typ)
5510 or else Is_Controlled (Comp_Typ));
5511
5512 if No (Init_Proc (Base)) then
5513
5514 -- If this is an anonymous array created for a declaration with
5515 -- an initial value, its init_proc will never be called. The
5516 -- initial value itself may have been expanded into assignments,
5517 -- in which case the object declaration is carries the
5518 -- No_Initialization flag.
5519
5520 if Is_Itype (Base)
5521 and then Nkind (Associated_Node_For_Itype (Base)) =
5522 N_Object_Declaration
5523 and then (Present (Expression (Associated_Node_For_Itype (Base)))
5524 or else
5525 No_Initialization (Associated_Node_For_Itype (Base)))
5526 then
5527 null;
5528
5529 -- We do not need an init proc for string or wide [wide] string,
5530 -- since the only time these need initialization in normalize or
5531 -- initialize scalars mode, and these types are treated specially
5532 -- and do not need initialization procedures.
5533
5534 elsif Root_Type (Base) = Standard_String
5535 or else Root_Type (Base) = Standard_Wide_String
5536 or else Root_Type (Base) = Standard_Wide_Wide_String
5537 then
5538 null;
5539
5540 -- Otherwise we have to build an init proc for the subtype
5541
5542 else
5543 Build_Array_Init_Proc (Base, N);
5544 end if;
5545 end if;
5546
5547 if Typ = Base then
5548 if Has_Controlled_Component (Base) then
5549 Build_Controlling_Procs (Base);
5550
5551 if not Is_Limited_Type (Comp_Typ)
5552 and then Number_Dimensions (Typ) = 1
5553 then
5554 Build_Slice_Assignment (Typ);
5555 end if;
5556
5557 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5558 and then Needs_Finalization (Directly_Designated_Type (Comp_Typ))
5559 then
5560 Set_Associated_Final_Chain (Comp_Typ, Add_Final_Chain (Typ));
5561 end if;
5562 end if;
5563
5564 -- For packed case, default initialization, except if the component type
5565 -- is itself a packed structure with an initialization procedure, or
5566 -- initialize/normalize scalars active, and we have a base type, or the
5567 -- type is public, because in that case a client might specify
5568 -- Normalize_Scalars and there better be a public Init_Proc for it.
5569
5570 elsif (Present (Init_Proc (Component_Type (Base)))
5571 and then No (Base_Init_Proc (Base)))
5572 or else (Init_Or_Norm_Scalars and then Base = Typ)
5573 or else Is_Public (Typ)
5574 then
5575 Build_Array_Init_Proc (Base, N);
5576 end if;
5577 end Expand_Freeze_Array_Type;
5578
5579 ------------------------------------
5580 -- Expand_Freeze_Enumeration_Type --
5581 ------------------------------------
5582
5583 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
5584 Typ : constant Entity_Id := Entity (N);
5585 Loc : constant Source_Ptr := Sloc (Typ);
5586 Ent : Entity_Id;
5587 Lst : List_Id;
5588 Num : Nat;
5589 Arr : Entity_Id;
5590 Fent : Entity_Id;
5591 Ityp : Entity_Id;
5592 Is_Contiguous : Boolean;
5593 Pos_Expr : Node_Id;
5594 Last_Repval : Uint;
5595
5596 Func : Entity_Id;
5597 pragma Warnings (Off, Func);
5598
5599 begin
5600 -- Various optimizations possible if given representation is contiguous
5601
5602 Is_Contiguous := True;
5603
5604 Ent := First_Literal (Typ);
5605 Last_Repval := Enumeration_Rep (Ent);
5606
5607 Next_Literal (Ent);
5608 while Present (Ent) loop
5609 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
5610 Is_Contiguous := False;
5611 exit;
5612 else
5613 Last_Repval := Enumeration_Rep (Ent);
5614 end if;
5615
5616 Next_Literal (Ent);
5617 end loop;
5618
5619 if Is_Contiguous then
5620 Set_Has_Contiguous_Rep (Typ);
5621 Ent := First_Literal (Typ);
5622 Num := 1;
5623 Lst := New_List (New_Reference_To (Ent, Sloc (Ent)));
5624
5625 else
5626 -- Build list of literal references
5627
5628 Lst := New_List;
5629 Num := 0;
5630
5631 Ent := First_Literal (Typ);
5632 while Present (Ent) loop
5633 Append_To (Lst, New_Reference_To (Ent, Sloc (Ent)));
5634 Num := Num + 1;
5635 Next_Literal (Ent);
5636 end loop;
5637 end if;
5638
5639 -- Now build an array declaration
5640
5641 -- typA : array (Natural range 0 .. num - 1) of ctype :=
5642 -- (v, v, v, v, v, ....)
5643
5644 -- where ctype is the corresponding integer type. If the representation
5645 -- is contiguous, we only keep the first literal, which provides the
5646 -- offset for Pos_To_Rep computations.
5647
5648 Arr :=
5649 Make_Defining_Identifier (Loc,
5650 Chars => New_External_Name (Chars (Typ), 'A'));
5651
5652 Append_Freeze_Action (Typ,
5653 Make_Object_Declaration (Loc,
5654 Defining_Identifier => Arr,
5655 Constant_Present => True,
5656
5657 Object_Definition =>
5658 Make_Constrained_Array_Definition (Loc,
5659 Discrete_Subtype_Definitions => New_List (
5660 Make_Subtype_Indication (Loc,
5661 Subtype_Mark => New_Reference_To (Standard_Natural, Loc),
5662 Constraint =>
5663 Make_Range_Constraint (Loc,
5664 Range_Expression =>
5665 Make_Range (Loc,
5666 Low_Bound =>
5667 Make_Integer_Literal (Loc, 0),
5668 High_Bound =>
5669 Make_Integer_Literal (Loc, Num - 1))))),
5670
5671 Component_Definition =>
5672 Make_Component_Definition (Loc,
5673 Aliased_Present => False,
5674 Subtype_Indication => New_Reference_To (Typ, Loc))),
5675
5676 Expression =>
5677 Make_Aggregate (Loc,
5678 Expressions => Lst)));
5679
5680 Set_Enum_Pos_To_Rep (Typ, Arr);
5681
5682 -- Now we build the function that converts representation values to
5683 -- position values. This function has the form:
5684
5685 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
5686 -- begin
5687 -- case ityp!(A) is
5688 -- when enum-lit'Enum_Rep => return posval;
5689 -- when enum-lit'Enum_Rep => return posval;
5690 -- ...
5691 -- when others =>
5692 -- [raise Constraint_Error when F "invalid data"]
5693 -- return -1;
5694 -- end case;
5695 -- end;
5696
5697 -- Note: the F parameter determines whether the others case (no valid
5698 -- representation) raises Constraint_Error or returns a unique value
5699 -- of minus one. The latter case is used, e.g. in 'Valid code.
5700
5701 -- Note: the reason we use Enum_Rep values in the case here is to avoid
5702 -- the code generator making inappropriate assumptions about the range
5703 -- of the values in the case where the value is invalid. ityp is a
5704 -- signed or unsigned integer type of appropriate width.
5705
5706 -- Note: if exceptions are not supported, then we suppress the raise
5707 -- and return -1 unconditionally (this is an erroneous program in any
5708 -- case and there is no obligation to raise Constraint_Error here!) We
5709 -- also do this if pragma Restrictions (No_Exceptions) is active.
5710
5711 -- Is this right??? What about No_Exception_Propagation???
5712
5713 -- Representations are signed
5714
5715 if Enumeration_Rep (First_Literal (Typ)) < 0 then
5716
5717 -- The underlying type is signed. Reset the Is_Unsigned_Type
5718 -- explicitly, because it might have been inherited from
5719 -- parent type.
5720
5721 Set_Is_Unsigned_Type (Typ, False);
5722
5723 if Esize (Typ) <= Standard_Integer_Size then
5724 Ityp := Standard_Integer;
5725 else
5726 Ityp := Universal_Integer;
5727 end if;
5728
5729 -- Representations are unsigned
5730
5731 else
5732 if Esize (Typ) <= Standard_Integer_Size then
5733 Ityp := RTE (RE_Unsigned);
5734 else
5735 Ityp := RTE (RE_Long_Long_Unsigned);
5736 end if;
5737 end if;
5738
5739 -- The body of the function is a case statement. First collect case
5740 -- alternatives, or optimize the contiguous case.
5741
5742 Lst := New_List;
5743
5744 -- If representation is contiguous, Pos is computed by subtracting
5745 -- the representation of the first literal.
5746
5747 if Is_Contiguous then
5748 Ent := First_Literal (Typ);
5749
5750 if Enumeration_Rep (Ent) = Last_Repval then
5751
5752 -- Another special case: for a single literal, Pos is zero
5753
5754 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
5755
5756 else
5757 Pos_Expr :=
5758 Convert_To (Standard_Integer,
5759 Make_Op_Subtract (Loc,
5760 Left_Opnd =>
5761 Unchecked_Convert_To (Ityp,
5762 Make_Identifier (Loc, Name_uA)),
5763 Right_Opnd =>
5764 Make_Integer_Literal (Loc,
5765 Intval =>
5766 Enumeration_Rep (First_Literal (Typ)))));
5767 end if;
5768
5769 Append_To (Lst,
5770 Make_Case_Statement_Alternative (Loc,
5771 Discrete_Choices => New_List (
5772 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
5773 Low_Bound =>
5774 Make_Integer_Literal (Loc,
5775 Intval => Enumeration_Rep (Ent)),
5776 High_Bound =>
5777 Make_Integer_Literal (Loc, Intval => Last_Repval))),
5778
5779 Statements => New_List (
5780 Make_Simple_Return_Statement (Loc,
5781 Expression => Pos_Expr))));
5782
5783 else
5784 Ent := First_Literal (Typ);
5785 while Present (Ent) loop
5786 Append_To (Lst,
5787 Make_Case_Statement_Alternative (Loc,
5788 Discrete_Choices => New_List (
5789 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
5790 Intval => Enumeration_Rep (Ent))),
5791
5792 Statements => New_List (
5793 Make_Simple_Return_Statement (Loc,
5794 Expression =>
5795 Make_Integer_Literal (Loc,
5796 Intval => Enumeration_Pos (Ent))))));
5797
5798 Next_Literal (Ent);
5799 end loop;
5800 end if;
5801
5802 -- In normal mode, add the others clause with the test
5803
5804 if not No_Exception_Handlers_Set then
5805 Append_To (Lst,
5806 Make_Case_Statement_Alternative (Loc,
5807 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5808 Statements => New_List (
5809 Make_Raise_Constraint_Error (Loc,
5810 Condition => Make_Identifier (Loc, Name_uF),
5811 Reason => CE_Invalid_Data),
5812 Make_Simple_Return_Statement (Loc,
5813 Expression =>
5814 Make_Integer_Literal (Loc, -1)))));
5815
5816 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
5817 -- active then return -1 (we cannot usefully raise Constraint_Error in
5818 -- this case). See description above for further details.
5819
5820 else
5821 Append_To (Lst,
5822 Make_Case_Statement_Alternative (Loc,
5823 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
5824 Statements => New_List (
5825 Make_Simple_Return_Statement (Loc,
5826 Expression =>
5827 Make_Integer_Literal (Loc, -1)))));
5828 end if;
5829
5830 -- Now we can build the function body
5831
5832 Fent :=
5833 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
5834
5835 Func :=
5836 Make_Subprogram_Body (Loc,
5837 Specification =>
5838 Make_Function_Specification (Loc,
5839 Defining_Unit_Name => Fent,
5840 Parameter_Specifications => New_List (
5841 Make_Parameter_Specification (Loc,
5842 Defining_Identifier =>
5843 Make_Defining_Identifier (Loc, Name_uA),
5844 Parameter_Type => New_Reference_To (Typ, Loc)),
5845 Make_Parameter_Specification (Loc,
5846 Defining_Identifier =>
5847 Make_Defining_Identifier (Loc, Name_uF),
5848 Parameter_Type => New_Reference_To (Standard_Boolean, Loc))),
5849
5850 Result_Definition => New_Reference_To (Standard_Integer, Loc)),
5851
5852 Declarations => Empty_List,
5853
5854 Handled_Statement_Sequence =>
5855 Make_Handled_Sequence_Of_Statements (Loc,
5856 Statements => New_List (
5857 Make_Case_Statement (Loc,
5858 Expression =>
5859 Unchecked_Convert_To (Ityp,
5860 Make_Identifier (Loc, Name_uA)),
5861 Alternatives => Lst))));
5862
5863 Set_TSS (Typ, Fent);
5864 Set_Is_Pure (Fent);
5865 -- The Pure flag will be reset is the current context is not pure.
5866 -- For optimization purposes and constant-folding, indicate that the
5867 -- Rep_To_Pos function can be considered free of side effects.
5868
5869 Set_Has_Pragma_Pure_Function (Fent);
5870
5871 if not Debug_Generated_Code then
5872 Set_Debug_Info_Off (Fent);
5873 end if;
5874
5875 exception
5876 when RE_Not_Available =>
5877 return;
5878 end Expand_Freeze_Enumeration_Type;
5879
5880 -------------------------------
5881 -- Expand_Freeze_Record_Type --
5882 -------------------------------
5883
5884 procedure Expand_Freeze_Record_Type (N : Node_Id) is
5885 Def_Id : constant Node_Id := Entity (N);
5886 Type_Decl : constant Node_Id := Parent (Def_Id);
5887 Comp : Entity_Id;
5888 Comp_Typ : Entity_Id;
5889 Predef_List : List_Id;
5890
5891 Flist : Entity_Id := Empty;
5892 -- Finalization list allocated for the case of a type with anonymous
5893 -- access components whose designated type is potentially controlled.
5894
5895 Renamed_Eq : Node_Id := Empty;
5896 -- Defining unit name for the predefined equality function in the case
5897 -- where the type has a primitive operation that is a renaming of
5898 -- predefined equality (but only if there is also an overriding
5899 -- user-defined equality function). Used to pass this entity from
5900 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
5901
5902 Wrapper_Decl_List : List_Id := No_List;
5903 Wrapper_Body_List : List_Id := No_List;
5904
5905 -- Start of processing for Expand_Freeze_Record_Type
5906
5907 begin
5908 -- Build discriminant checking functions if not a derived type (for
5909 -- derived types that are not tagged types, always use the discriminant
5910 -- checking functions of the parent type). However, for untagged types
5911 -- the derivation may have taken place before the parent was frozen, so
5912 -- we copy explicitly the discriminant checking functions from the
5913 -- parent into the components of the derived type.
5914
5915 if not Is_Derived_Type (Def_Id)
5916 or else Has_New_Non_Standard_Rep (Def_Id)
5917 or else Is_Tagged_Type (Def_Id)
5918 then
5919 Build_Discr_Checking_Funcs (Type_Decl);
5920
5921 elsif Is_Derived_Type (Def_Id)
5922 and then not Is_Tagged_Type (Def_Id)
5923
5924 -- If we have a derived Unchecked_Union, we do not inherit the
5925 -- discriminant checking functions from the parent type since the
5926 -- discriminants are non existent.
5927
5928 and then not Is_Unchecked_Union (Def_Id)
5929 and then Has_Discriminants (Def_Id)
5930 then
5931 declare
5932 Old_Comp : Entity_Id;
5933
5934 begin
5935 Old_Comp :=
5936 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
5937 Comp := First_Component (Def_Id);
5938 while Present (Comp) loop
5939 if Ekind (Comp) = E_Component
5940 and then Chars (Comp) = Chars (Old_Comp)
5941 then
5942 Set_Discriminant_Checking_Func (Comp,
5943 Discriminant_Checking_Func (Old_Comp));
5944 end if;
5945
5946 Next_Component (Old_Comp);
5947 Next_Component (Comp);
5948 end loop;
5949 end;
5950 end if;
5951
5952 if Is_Derived_Type (Def_Id)
5953 and then Is_Limited_Type (Def_Id)
5954 and then Is_Tagged_Type (Def_Id)
5955 then
5956 Check_Stream_Attributes (Def_Id);
5957 end if;
5958
5959 -- Update task and controlled component flags, because some of the
5960 -- component types may have been private at the point of the record
5961 -- declaration.
5962
5963 Comp := First_Component (Def_Id);
5964 while Present (Comp) loop
5965 Comp_Typ := Etype (Comp);
5966
5967 if Has_Task (Comp_Typ) then
5968 Set_Has_Task (Def_Id);
5969
5970 -- Do not set Has_Controlled_Component on a class-wide equivalent
5971 -- type. See Make_CW_Equivalent_Type.
5972
5973 elsif not Is_Class_Wide_Equivalent_Type (Def_Id)
5974 and then (Has_Controlled_Component (Comp_Typ)
5975 or else (Chars (Comp) /= Name_uParent
5976 and then Is_Controlled (Comp_Typ)))
5977 then
5978 Set_Has_Controlled_Component (Def_Id);
5979
5980 elsif Ekind (Comp_Typ) = E_Anonymous_Access_Type
5981 and then Needs_Finalization (Directly_Designated_Type (Comp_Typ))
5982 then
5983 if No (Flist) then
5984 Flist := Add_Final_Chain (Def_Id);
5985 end if;
5986
5987 Set_Associated_Final_Chain (Comp_Typ, Flist);
5988 end if;
5989
5990 Next_Component (Comp);
5991 end loop;
5992
5993 -- Handle constructors of non-tagged CPP_Class types
5994
5995 if not Is_Tagged_Type (Def_Id) and then Is_CPP_Class (Def_Id) then
5996 Set_CPP_Constructors (Def_Id);
5997 end if;
5998
5999 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
6000 -- for regular tagged types as well as for Ada types deriving from a C++
6001 -- Class, but not for tagged types directly corresponding to C++ classes
6002 -- In the later case we assume that it is created in the C++ side and we
6003 -- just use it.
6004
6005 if Is_Tagged_Type (Def_Id) then
6006
6007 -- Add the _Tag component
6008
6009 if Underlying_Type (Etype (Def_Id)) = Def_Id then
6010 Expand_Tagged_Root (Def_Id);
6011 end if;
6012
6013 if Is_CPP_Class (Def_Id) then
6014 Set_All_DT_Position (Def_Id);
6015
6016 -- Create the tag entities with a minimum decoration
6017
6018 if Tagged_Type_Expansion then
6019 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
6020 end if;
6021
6022 Set_CPP_Constructors (Def_Id);
6023
6024 else
6025 if not Building_Static_DT (Def_Id) then
6026
6027 -- Usually inherited primitives are not delayed but the first
6028 -- Ada extension of a CPP_Class is an exception since the
6029 -- address of the inherited subprogram has to be inserted in
6030 -- the new Ada Dispatch Table and this is a freezing action.
6031
6032 -- Similarly, if this is an inherited operation whose parent is
6033 -- not frozen yet, it is not in the DT of the parent, and we
6034 -- generate an explicit freeze node for the inherited operation
6035 -- so it is properly inserted in the DT of the current type.
6036
6037 declare
6038 Elmt : Elmt_Id;
6039 Subp : Entity_Id;
6040
6041 begin
6042 Elmt := First_Elmt (Primitive_Operations (Def_Id));
6043 while Present (Elmt) loop
6044 Subp := Node (Elmt);
6045
6046 if Present (Alias (Subp)) then
6047 if Is_CPP_Class (Etype (Def_Id)) then
6048 Set_Has_Delayed_Freeze (Subp);
6049
6050 elsif Has_Delayed_Freeze (Alias (Subp))
6051 and then not Is_Frozen (Alias (Subp))
6052 then
6053 Set_Is_Frozen (Subp, False);
6054 Set_Has_Delayed_Freeze (Subp);
6055 end if;
6056 end if;
6057
6058 Next_Elmt (Elmt);
6059 end loop;
6060 end;
6061 end if;
6062
6063 -- Unfreeze momentarily the type to add the predefined primitives
6064 -- operations. The reason we unfreeze is so that these predefined
6065 -- operations will indeed end up as primitive operations (which
6066 -- must be before the freeze point).
6067
6068 Set_Is_Frozen (Def_Id, False);
6069
6070 -- Do not add the spec of predefined primitives in case of
6071 -- CPP tagged type derivations that have convention CPP.
6072
6073 if Is_CPP_Class (Root_Type (Def_Id))
6074 and then Convention (Def_Id) = Convention_CPP
6075 then
6076 null;
6077
6078 -- Do not add the spec of predefined primitives in case of
6079 -- CIL and Java tagged types
6080
6081 elsif Convention (Def_Id) = Convention_CIL
6082 or else Convention (Def_Id) = Convention_Java
6083 then
6084 null;
6085
6086 -- Do not add the spec of the predefined primitives if we are
6087 -- compiling under restriction No_Dispatching_Calls
6088
6089 elsif not Restriction_Active (No_Dispatching_Calls) then
6090 Make_Predefined_Primitive_Specs
6091 (Def_Id, Predef_List, Renamed_Eq);
6092 Insert_List_Before_And_Analyze (N, Predef_List);
6093 end if;
6094
6095 -- Ada 2005 (AI-391): For a nonabstract null extension, create
6096 -- wrapper functions for each nonoverridden inherited function
6097 -- with a controlling result of the type. The wrapper for such
6098 -- a function returns an extension aggregate that invokes the
6099 -- the parent function.
6100
6101 if Ada_Version >= Ada_2005
6102 and then not Is_Abstract_Type (Def_Id)
6103 and then Is_Null_Extension (Def_Id)
6104 then
6105 Make_Controlling_Function_Wrappers
6106 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
6107 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
6108 end if;
6109
6110 -- Ada 2005 (AI-251): For a nonabstract type extension, build
6111 -- null procedure declarations for each set of homographic null
6112 -- procedures that are inherited from interface types but not
6113 -- overridden. This is done to ensure that the dispatch table
6114 -- entry associated with such null primitives are properly filled.
6115
6116 if Ada_Version >= Ada_2005
6117 and then Etype (Def_Id) /= Def_Id
6118 and then not Is_Abstract_Type (Def_Id)
6119 and then Has_Interfaces (Def_Id)
6120 then
6121 Insert_Actions (N, Make_Null_Procedure_Specs (Def_Id));
6122 end if;
6123
6124 Set_Is_Frozen (Def_Id);
6125 if not Is_Derived_Type (Def_Id)
6126 or else Is_Tagged_Type (Etype (Def_Id))
6127 then
6128 Set_All_DT_Position (Def_Id);
6129 end if;
6130
6131 -- Add the controlled component before the freezing actions
6132 -- referenced in those actions.
6133
6134 if Has_New_Controlled_Component (Def_Id) then
6135 Expand_Record_Controller (Def_Id);
6136 end if;
6137
6138 -- Create and decorate the tags. Suppress their creation when
6139 -- VM_Target because the dispatching mechanism is handled
6140 -- internally by the VMs.
6141
6142 if Tagged_Type_Expansion then
6143 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
6144
6145 -- Generate dispatch table of locally defined tagged type.
6146 -- Dispatch tables of library level tagged types are built
6147 -- later (see Analyze_Declarations).
6148
6149 if not Building_Static_DT (Def_Id) then
6150 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
6151 end if;
6152 end if;
6153
6154 -- If the type has unknown discriminants, propagate dispatching
6155 -- information to its underlying record view, which does not get
6156 -- its own dispatch table.
6157
6158 if Is_Derived_Type (Def_Id)
6159 and then Has_Unknown_Discriminants (Def_Id)
6160 and then Present (Underlying_Record_View (Def_Id))
6161 then
6162 declare
6163 Rep : constant Entity_Id :=
6164 Underlying_Record_View (Def_Id);
6165 begin
6166 Set_Access_Disp_Table
6167 (Rep, Access_Disp_Table (Def_Id));
6168 Set_Dispatch_Table_Wrappers
6169 (Rep, Dispatch_Table_Wrappers (Def_Id));
6170 Set_Direct_Primitive_Operations
6171 (Rep, Direct_Primitive_Operations (Def_Id));
6172 end;
6173 end if;
6174
6175 -- Make sure that the primitives Initialize, Adjust and Finalize
6176 -- are Frozen before other TSS subprograms. We don't want them
6177 -- Frozen inside.
6178
6179 if Is_Controlled (Def_Id) then
6180 if not Is_Limited_Type (Def_Id) then
6181 Append_Freeze_Actions (Def_Id,
6182 Freeze_Entity
6183 (Find_Prim_Op (Def_Id, Name_Adjust), Def_Id));
6184 end if;
6185
6186 Append_Freeze_Actions (Def_Id,
6187 Freeze_Entity
6188 (Find_Prim_Op (Def_Id, Name_Initialize), Def_Id));
6189
6190 Append_Freeze_Actions (Def_Id,
6191 Freeze_Entity
6192 (Find_Prim_Op (Def_Id, Name_Finalize), Def_Id));
6193 end if;
6194
6195 -- Freeze rest of primitive operations. There is no need to handle
6196 -- the predefined primitives if we are compiling under restriction
6197 -- No_Dispatching_Calls
6198
6199 if not Restriction_Active (No_Dispatching_Calls) then
6200 Append_Freeze_Actions
6201 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
6202 end if;
6203 end if;
6204
6205 -- In the non-tagged case, ever since Ada83 an equality function must
6206 -- be provided for variant records that are not unchecked unions.
6207 -- In Ada 2012 the equality function composes, and thus must be built
6208 -- explicitly just as for tagged records.
6209
6210 elsif Has_Discriminants (Def_Id)
6211 and then not Is_Limited_Type (Def_Id)
6212 then
6213 declare
6214 Comps : constant Node_Id :=
6215 Component_List (Type_Definition (Type_Decl));
6216 begin
6217 if Present (Comps)
6218 and then Present (Variant_Part (Comps))
6219 then
6220 Build_Variant_Record_Equality (Def_Id);
6221 end if;
6222 end;
6223
6224 -- Otherwise create primitive equality operation (AI05-0123)
6225
6226 -- This is done unconditionally to ensure that tools can be linked
6227 -- properly with user programs compiled with older language versions.
6228 -- It might be worth including a switch to revert to a non-composable
6229 -- equality for untagged records, even though no program depending on
6230 -- non-composability has surfaced ???
6231
6232 elsif Comes_From_Source (Def_Id)
6233 and then Convention (Def_Id) = Convention_Ada
6234 and then not Is_Limited_Type (Def_Id)
6235 then
6236 Build_Untagged_Equality (Def_Id);
6237 end if;
6238
6239 -- Before building the record initialization procedure, if we are
6240 -- dealing with a concurrent record value type, then we must go through
6241 -- the discriminants, exchanging discriminals between the concurrent
6242 -- type and the concurrent record value type. See the section "Handling
6243 -- of Discriminants" in the Einfo spec for details.
6244
6245 if Is_Concurrent_Record_Type (Def_Id)
6246 and then Has_Discriminants (Def_Id)
6247 then
6248 declare
6249 Ctyp : constant Entity_Id :=
6250 Corresponding_Concurrent_Type (Def_Id);
6251 Conc_Discr : Entity_Id;
6252 Rec_Discr : Entity_Id;
6253 Temp : Entity_Id;
6254
6255 begin
6256 Conc_Discr := First_Discriminant (Ctyp);
6257 Rec_Discr := First_Discriminant (Def_Id);
6258 while Present (Conc_Discr) loop
6259 Temp := Discriminal (Conc_Discr);
6260 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
6261 Set_Discriminal (Rec_Discr, Temp);
6262
6263 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
6264 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
6265
6266 Next_Discriminant (Conc_Discr);
6267 Next_Discriminant (Rec_Discr);
6268 end loop;
6269 end;
6270 end if;
6271
6272 if Has_Controlled_Component (Def_Id) then
6273 if No (Controller_Component (Def_Id)) then
6274 Expand_Record_Controller (Def_Id);
6275 end if;
6276
6277 Build_Controlling_Procs (Def_Id);
6278 end if;
6279
6280 Adjust_Discriminants (Def_Id);
6281
6282 if Tagged_Type_Expansion or else not Is_Interface (Def_Id) then
6283
6284 -- Do not need init for interfaces on e.g. CIL since they're
6285 -- abstract. Helps operation of peverify (the PE Verify tool).
6286
6287 Build_Record_Init_Proc (Type_Decl, Def_Id);
6288 end if;
6289
6290 -- For tagged type that are not interfaces, build bodies of primitive
6291 -- operations. Note: do this after building the record initialization
6292 -- procedure, since the primitive operations may need the initialization
6293 -- routine. There is no need to add predefined primitives of interfaces
6294 -- because all their predefined primitives are abstract.
6295
6296 if Is_Tagged_Type (Def_Id)
6297 and then not Is_Interface (Def_Id)
6298 then
6299 -- Do not add the body of predefined primitives in case of
6300 -- CPP tagged type derivations that have convention CPP.
6301
6302 if Is_CPP_Class (Root_Type (Def_Id))
6303 and then Convention (Def_Id) = Convention_CPP
6304 then
6305 null;
6306
6307 -- Do not add the body of predefined primitives in case of
6308 -- CIL and Java tagged types.
6309
6310 elsif Convention (Def_Id) = Convention_CIL
6311 or else Convention (Def_Id) = Convention_Java
6312 then
6313 null;
6314
6315 -- Do not add the body of the predefined primitives if we are
6316 -- compiling under restriction No_Dispatching_Calls or if we are
6317 -- compiling a CPP tagged type.
6318
6319 elsif not Restriction_Active (No_Dispatching_Calls) then
6320 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
6321 Append_Freeze_Actions (Def_Id, Predef_List);
6322 end if;
6323
6324 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
6325 -- inherited functions, then add their bodies to the freeze actions.
6326
6327 if Present (Wrapper_Body_List) then
6328 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
6329 end if;
6330
6331 -- Create extra formals for the primitive operations of the type.
6332 -- This must be done before analyzing the body of the initialization
6333 -- procedure, because a self-referential type might call one of these
6334 -- primitives in the body of the init_proc itself.
6335
6336 declare
6337 Elmt : Elmt_Id;
6338 Subp : Entity_Id;
6339
6340 begin
6341 Elmt := First_Elmt (Primitive_Operations (Def_Id));
6342 while Present (Elmt) loop
6343 Subp := Node (Elmt);
6344 if not Has_Foreign_Convention (Subp)
6345 and then not Is_Predefined_Dispatching_Operation (Subp)
6346 then
6347 Create_Extra_Formals (Subp);
6348 end if;
6349
6350 Next_Elmt (Elmt);
6351 end loop;
6352 end;
6353 end if;
6354 end Expand_Freeze_Record_Type;
6355
6356 ------------------------------
6357 -- Freeze_Stream_Operations --
6358 ------------------------------
6359
6360 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
6361 Names : constant array (1 .. 4) of TSS_Name_Type :=
6362 (TSS_Stream_Input,
6363 TSS_Stream_Output,
6364 TSS_Stream_Read,
6365 TSS_Stream_Write);
6366 Stream_Op : Entity_Id;
6367
6368 begin
6369 -- Primitive operations of tagged types are frozen when the dispatch
6370 -- table is constructed.
6371
6372 if not Comes_From_Source (Typ)
6373 or else Is_Tagged_Type (Typ)
6374 then
6375 return;
6376 end if;
6377
6378 for J in Names'Range loop
6379 Stream_Op := TSS (Typ, Names (J));
6380
6381 if Present (Stream_Op)
6382 and then Is_Subprogram (Stream_Op)
6383 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
6384 N_Subprogram_Declaration
6385 and then not Is_Frozen (Stream_Op)
6386 then
6387 Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
6388 end if;
6389 end loop;
6390 end Freeze_Stream_Operations;
6391
6392 -----------------
6393 -- Freeze_Type --
6394 -----------------
6395
6396 -- Full type declarations are expanded at the point at which the type is
6397 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
6398 -- declarations generated by the freezing (e.g. the procedure generated
6399 -- for initialization) are chained in the Actions field list of the freeze
6400 -- node using Append_Freeze_Actions.
6401
6402 function Freeze_Type (N : Node_Id) return Boolean is
6403 Def_Id : constant Entity_Id := Entity (N);
6404 RACW_Seen : Boolean := False;
6405 Result : Boolean := False;
6406
6407 begin
6408 -- Process associated access types needing special processing
6409
6410 if Present (Access_Types_To_Process (N)) then
6411 declare
6412 E : Elmt_Id := First_Elmt (Access_Types_To_Process (N));
6413 begin
6414 while Present (E) loop
6415
6416 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
6417 Validate_RACW_Primitives (Node (E));
6418 RACW_Seen := True;
6419 end if;
6420
6421 E := Next_Elmt (E);
6422 end loop;
6423 end;
6424
6425 if RACW_Seen then
6426
6427 -- If there are RACWs designating this type, make stubs now
6428
6429 Remote_Types_Tagged_Full_View_Encountered (Def_Id);
6430 end if;
6431 end if;
6432
6433 -- Freeze processing for record types
6434
6435 if Is_Record_Type (Def_Id) then
6436 if Ekind (Def_Id) = E_Record_Type then
6437 Expand_Freeze_Record_Type (N);
6438
6439 -- The subtype may have been declared before the type was frozen. If
6440 -- the type has controlled components it is necessary to create the
6441 -- entity for the controller explicitly because it did not exist at
6442 -- the point of the subtype declaration. Only the entity is needed,
6443 -- the back-end will obtain the layout from the type. This is only
6444 -- necessary if this is constrained subtype whose component list is
6445 -- not shared with the base type.
6446
6447 elsif Ekind (Def_Id) = E_Record_Subtype
6448 and then Has_Discriminants (Def_Id)
6449 and then Last_Entity (Def_Id) /= Last_Entity (Base_Type (Def_Id))
6450 and then Present (Controller_Component (Def_Id))
6451 then
6452 declare
6453 Old_C : constant Entity_Id := Controller_Component (Def_Id);
6454 New_C : Entity_Id;
6455
6456 begin
6457 if Scope (Old_C) = Base_Type (Def_Id) then
6458
6459 -- The entity is the one in the parent. Create new one
6460
6461 New_C := New_Copy (Old_C);
6462 Set_Parent (New_C, Parent (Old_C));
6463 Push_Scope (Def_Id);
6464 Enter_Name (New_C);
6465 End_Scope;
6466 end if;
6467 end;
6468
6469 if Is_Itype (Def_Id)
6470 and then Is_Record_Type (Underlying_Type (Scope (Def_Id)))
6471 then
6472 -- The freeze node is only used to introduce the controller,
6473 -- the back-end has no use for it for a discriminated
6474 -- component.
6475
6476 Set_Freeze_Node (Def_Id, Empty);
6477 Set_Has_Delayed_Freeze (Def_Id, False);
6478 Result := True;
6479 end if;
6480
6481 -- Similar process if the controller of the subtype is not present
6482 -- but the parent has it. This can happen with constrained
6483 -- record components where the subtype is an itype.
6484
6485 elsif Ekind (Def_Id) = E_Record_Subtype
6486 and then Is_Itype (Def_Id)
6487 and then No (Controller_Component (Def_Id))
6488 and then Present (Controller_Component (Etype (Def_Id)))
6489 then
6490 declare
6491 Old_C : constant Entity_Id :=
6492 Controller_Component (Etype (Def_Id));
6493 New_C : constant Entity_Id := New_Copy (Old_C);
6494
6495 begin
6496 Set_Next_Entity (New_C, First_Entity (Def_Id));
6497 Set_First_Entity (Def_Id, New_C);
6498
6499 -- The freeze node is only used to introduce the controller,
6500 -- the back-end has no use for it for a discriminated
6501 -- component.
6502
6503 Set_Freeze_Node (Def_Id, Empty);
6504 Set_Has_Delayed_Freeze (Def_Id, False);
6505 Result := True;
6506 end;
6507 end if;
6508
6509 -- Freeze processing for array types
6510
6511 elsif Is_Array_Type (Def_Id) then
6512 Expand_Freeze_Array_Type (N);
6513
6514 -- Freeze processing for access types
6515
6516 -- For pool-specific access types, find out the pool object used for
6517 -- this type, needs actual expansion of it in some cases. Here are the
6518 -- different cases :
6519
6520 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
6521 -- ---> don't use any storage pool
6522
6523 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
6524 -- Expand:
6525 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
6526
6527 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
6528 -- ---> Storage Pool is the specified one
6529
6530 -- See GNAT Pool packages in the Run-Time for more details
6531
6532 elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
6533 declare
6534 Loc : constant Source_Ptr := Sloc (N);
6535 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
6536 Pool_Object : Entity_Id;
6537
6538 Freeze_Action_Typ : Entity_Id;
6539
6540 begin
6541 -- Case 1
6542
6543 -- Rep Clause "for Def_Id'Storage_Size use 0;"
6544 -- ---> don't use any storage pool
6545
6546 if No_Pool_Assigned (Def_Id) then
6547 null;
6548
6549 -- Case 2
6550
6551 -- Rep Clause : for Def_Id'Storage_Size use Expr.
6552 -- ---> Expand:
6553 -- Def_Id__Pool : Stack_Bounded_Pool
6554 -- (Expr, DT'Size, DT'Alignment);
6555
6556 elsif Has_Storage_Size_Clause (Def_Id) then
6557 declare
6558 DT_Size : Node_Id;
6559 DT_Align : Node_Id;
6560
6561 begin
6562 -- For unconstrained composite types we give a size of zero
6563 -- so that the pool knows that it needs a special algorithm
6564 -- for variable size object allocation.
6565
6566 if Is_Composite_Type (Desig_Type)
6567 and then not Is_Constrained (Desig_Type)
6568 then
6569 DT_Size :=
6570 Make_Integer_Literal (Loc, 0);
6571
6572 DT_Align :=
6573 Make_Integer_Literal (Loc, Maximum_Alignment);
6574
6575 else
6576 DT_Size :=
6577 Make_Attribute_Reference (Loc,
6578 Prefix => New_Reference_To (Desig_Type, Loc),
6579 Attribute_Name => Name_Max_Size_In_Storage_Elements);
6580
6581 DT_Align :=
6582 Make_Attribute_Reference (Loc,
6583 Prefix => New_Reference_To (Desig_Type, Loc),
6584 Attribute_Name => Name_Alignment);
6585 end if;
6586
6587 Pool_Object :=
6588 Make_Defining_Identifier (Loc,
6589 Chars => New_External_Name (Chars (Def_Id), 'P'));
6590
6591 -- We put the code associated with the pools in the entity
6592 -- that has the later freeze node, usually the access type
6593 -- but it can also be the designated_type; because the pool
6594 -- code requires both those types to be frozen
6595
6596 if Is_Frozen (Desig_Type)
6597 and then (No (Freeze_Node (Desig_Type))
6598 or else Analyzed (Freeze_Node (Desig_Type)))
6599 then
6600 Freeze_Action_Typ := Def_Id;
6601
6602 -- A Taft amendment type cannot get the freeze actions
6603 -- since the full view is not there.
6604
6605 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
6606 and then No (Full_View (Desig_Type))
6607 then
6608 Freeze_Action_Typ := Def_Id;
6609
6610 else
6611 Freeze_Action_Typ := Desig_Type;
6612 end if;
6613
6614 Append_Freeze_Action (Freeze_Action_Typ,
6615 Make_Object_Declaration (Loc,
6616 Defining_Identifier => Pool_Object,
6617 Object_Definition =>
6618 Make_Subtype_Indication (Loc,
6619 Subtype_Mark =>
6620 New_Reference_To
6621 (RTE (RE_Stack_Bounded_Pool), Loc),
6622
6623 Constraint =>
6624 Make_Index_Or_Discriminant_Constraint (Loc,
6625 Constraints => New_List (
6626
6627 -- First discriminant is the Pool Size
6628
6629 New_Reference_To (
6630 Storage_Size_Variable (Def_Id), Loc),
6631
6632 -- Second discriminant is the element size
6633
6634 DT_Size,
6635
6636 -- Third discriminant is the alignment
6637
6638 DT_Align)))));
6639 end;
6640
6641 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
6642
6643 -- Case 3
6644
6645 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
6646 -- ---> Storage Pool is the specified one
6647
6648 elsif Present (Associated_Storage_Pool (Def_Id)) then
6649
6650 -- Nothing to do the associated storage pool has been attached
6651 -- when analyzing the rep. clause
6652
6653 null;
6654 end if;
6655
6656 -- For access-to-controlled types (including class-wide types and
6657 -- Taft-amendment types which potentially have controlled
6658 -- components), expand the list controller object that will store
6659 -- the dynamically allocated objects. Do not do this
6660 -- transformation for expander-generated access types, but do it
6661 -- for types that are the full view of types derived from other
6662 -- private types. Also suppress the list controller in the case
6663 -- of a designated type with convention Java, since this is used
6664 -- when binding to Java API specs, where there's no equivalent of
6665 -- a finalization list and we don't want to pull in the
6666 -- finalization support if not needed.
6667
6668 if not Comes_From_Source (Def_Id)
6669 and then not Has_Private_Declaration (Def_Id)
6670 then
6671 null;
6672
6673 elsif (Needs_Finalization (Desig_Type)
6674 and then Convention (Desig_Type) /= Convention_Java
6675 and then Convention (Desig_Type) /= Convention_CIL)
6676 or else
6677 (Is_Incomplete_Or_Private_Type (Desig_Type)
6678 and then No (Full_View (Desig_Type))
6679
6680 -- An exception is made for types defined in the run-time
6681 -- because Ada.Tags.Tag itself is such a type and cannot
6682 -- afford this unnecessary overhead that would generates a
6683 -- loop in the expansion scheme...
6684
6685 and then not In_Runtime (Def_Id)
6686
6687 -- Another exception is if Restrictions (No_Finalization)
6688 -- is active, since then we know nothing is controlled.
6689
6690 and then not Restriction_Active (No_Finalization))
6691
6692 -- If the designated type is not frozen yet, its controlled
6693 -- status must be retrieved explicitly.
6694
6695 or else (Is_Array_Type (Desig_Type)
6696 and then not Is_Frozen (Desig_Type)
6697 and then Needs_Finalization (Component_Type (Desig_Type)))
6698
6699 -- The designated type has controlled anonymous access
6700 -- discriminants.
6701
6702 or else Has_Controlled_Coextensions (Desig_Type)
6703 then
6704 Set_Associated_Final_Chain (Def_Id, Add_Final_Chain (Def_Id));
6705 end if;
6706 end;
6707
6708 -- Freeze processing for enumeration types
6709
6710 elsif Ekind (Def_Id) = E_Enumeration_Type then
6711
6712 -- We only have something to do if we have a non-standard
6713 -- representation (i.e. at least one literal whose pos value
6714 -- is not the same as its representation)
6715
6716 if Has_Non_Standard_Rep (Def_Id) then
6717 Expand_Freeze_Enumeration_Type (N);
6718 end if;
6719
6720 -- Private types that are completed by a derivation from a private
6721 -- type have an internally generated full view, that needs to be
6722 -- frozen. This must be done explicitly because the two views share
6723 -- the freeze node, and the underlying full view is not visible when
6724 -- the freeze node is analyzed.
6725
6726 elsif Is_Private_Type (Def_Id)
6727 and then Is_Derived_Type (Def_Id)
6728 and then Present (Full_View (Def_Id))
6729 and then Is_Itype (Full_View (Def_Id))
6730 and then Has_Private_Declaration (Full_View (Def_Id))
6731 and then Freeze_Node (Full_View (Def_Id)) = N
6732 then
6733 Set_Entity (N, Full_View (Def_Id));
6734 Result := Freeze_Type (N);
6735 Set_Entity (N, Def_Id);
6736
6737 -- All other types require no expander action. There are such cases
6738 -- (e.g. task types and protected types). In such cases, the freeze
6739 -- nodes are there for use by Gigi.
6740
6741 end if;
6742
6743 Freeze_Stream_Operations (N, Def_Id);
6744 return Result;
6745
6746 exception
6747 when RE_Not_Available =>
6748 return False;
6749 end Freeze_Type;
6750
6751 -------------------------
6752 -- Get_Simple_Init_Val --
6753 -------------------------
6754
6755 function Get_Simple_Init_Val
6756 (T : Entity_Id;
6757 N : Node_Id;
6758 Size : Uint := No_Uint) return Node_Id
6759 is
6760 Loc : constant Source_Ptr := Sloc (N);
6761 Val : Node_Id;
6762 Result : Node_Id;
6763 Val_RE : RE_Id;
6764
6765 Size_To_Use : Uint;
6766 -- This is the size to be used for computation of the appropriate
6767 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
6768
6769 IV_Attribute : constant Boolean :=
6770 Nkind (N) = N_Attribute_Reference
6771 and then Attribute_Name (N) = Name_Invalid_Value;
6772
6773 Lo_Bound : Uint;
6774 Hi_Bound : Uint;
6775 -- These are the values computed by the procedure Check_Subtype_Bounds
6776
6777 procedure Check_Subtype_Bounds;
6778 -- This procedure examines the subtype T, and its ancestor subtypes and
6779 -- derived types to determine the best known information about the
6780 -- bounds of the subtype. After the call Lo_Bound is set either to
6781 -- No_Uint if no information can be determined, or to a value which
6782 -- represents a known low bound, i.e. a valid value of the subtype can
6783 -- not be less than this value. Hi_Bound is similarly set to a known
6784 -- high bound (valid value cannot be greater than this).
6785
6786 --------------------------
6787 -- Check_Subtype_Bounds --
6788 --------------------------
6789
6790 procedure Check_Subtype_Bounds is
6791 ST1 : Entity_Id;
6792 ST2 : Entity_Id;
6793 Lo : Node_Id;
6794 Hi : Node_Id;
6795 Loval : Uint;
6796 Hival : Uint;
6797
6798 begin
6799 Lo_Bound := No_Uint;
6800 Hi_Bound := No_Uint;
6801
6802 -- Loop to climb ancestor subtypes and derived types
6803
6804 ST1 := T;
6805 loop
6806 if not Is_Discrete_Type (ST1) then
6807 return;
6808 end if;
6809
6810 Lo := Type_Low_Bound (ST1);
6811 Hi := Type_High_Bound (ST1);
6812
6813 if Compile_Time_Known_Value (Lo) then
6814 Loval := Expr_Value (Lo);
6815
6816 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
6817 Lo_Bound := Loval;
6818 end if;
6819 end if;
6820
6821 if Compile_Time_Known_Value (Hi) then
6822 Hival := Expr_Value (Hi);
6823
6824 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
6825 Hi_Bound := Hival;
6826 end if;
6827 end if;
6828
6829 ST2 := Ancestor_Subtype (ST1);
6830
6831 if No (ST2) then
6832 ST2 := Etype (ST1);
6833 end if;
6834
6835 exit when ST1 = ST2;
6836 ST1 := ST2;
6837 end loop;
6838 end Check_Subtype_Bounds;
6839
6840 -- Start of processing for Get_Simple_Init_Val
6841
6842 begin
6843 -- For a private type, we should always have an underlying type
6844 -- (because this was already checked in Needs_Simple_Initialization).
6845 -- What we do is to get the value for the underlying type and then do
6846 -- an Unchecked_Convert to the private type.
6847
6848 if Is_Private_Type (T) then
6849 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
6850
6851 -- A special case, if the underlying value is null, then qualify it
6852 -- with the underlying type, so that the null is properly typed
6853 -- Similarly, if it is an aggregate it must be qualified, because an
6854 -- unchecked conversion does not provide a context for it.
6855
6856 if Nkind_In (Val, N_Null, N_Aggregate) then
6857 Val :=
6858 Make_Qualified_Expression (Loc,
6859 Subtype_Mark =>
6860 New_Occurrence_Of (Underlying_Type (T), Loc),
6861 Expression => Val);
6862 end if;
6863
6864 Result := Unchecked_Convert_To (T, Val);
6865
6866 -- Don't truncate result (important for Initialize/Normalize_Scalars)
6867
6868 if Nkind (Result) = N_Unchecked_Type_Conversion
6869 and then Is_Scalar_Type (Underlying_Type (T))
6870 then
6871 Set_No_Truncation (Result);
6872 end if;
6873
6874 return Result;
6875
6876 -- For scalars, we must have normalize/initialize scalars case, or
6877 -- if the node N is an 'Invalid_Value attribute node.
6878
6879 elsif Is_Scalar_Type (T) then
6880 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
6881
6882 -- Compute size of object. If it is given by the caller, we can use
6883 -- it directly, otherwise we use Esize (T) as an estimate. As far as
6884 -- we know this covers all cases correctly.
6885
6886 if Size = No_Uint or else Size <= Uint_0 then
6887 Size_To_Use := UI_Max (Uint_1, Esize (T));
6888 else
6889 Size_To_Use := Size;
6890 end if;
6891
6892 -- Maximum size to use is 64 bits, since we will create values
6893 -- of type Unsigned_64 and the range must fit this type.
6894
6895 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
6896 Size_To_Use := Uint_64;
6897 end if;
6898
6899 -- Check known bounds of subtype
6900
6901 Check_Subtype_Bounds;
6902
6903 -- Processing for Normalize_Scalars case
6904
6905 if Normalize_Scalars and then not IV_Attribute then
6906
6907 -- If zero is invalid, it is a convenient value to use that is
6908 -- for sure an appropriate invalid value in all situations.
6909
6910 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6911 Val := Make_Integer_Literal (Loc, 0);
6912
6913 -- Cases where all one bits is the appropriate invalid value
6914
6915 -- For modular types, all 1 bits is either invalid or valid. If
6916 -- it is valid, then there is nothing that can be done since there
6917 -- are no invalid values (we ruled out zero already).
6918
6919 -- For signed integer types that have no negative values, either
6920 -- there is room for negative values, or there is not. If there
6921 -- is, then all 1 bits may be interpreted as minus one, which is
6922 -- certainly invalid. Alternatively it is treated as the largest
6923 -- positive value, in which case the observation for modular types
6924 -- still applies.
6925
6926 -- For float types, all 1-bits is a NaN (not a number), which is
6927 -- certainly an appropriately invalid value.
6928
6929 elsif Is_Unsigned_Type (T)
6930 or else Is_Floating_Point_Type (T)
6931 or else Is_Enumeration_Type (T)
6932 then
6933 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
6934
6935 -- Resolve as Unsigned_64, because the largest number we
6936 -- can generate is out of range of universal integer.
6937
6938 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
6939
6940 -- Case of signed types
6941
6942 else
6943 declare
6944 Signed_Size : constant Uint :=
6945 UI_Min (Uint_63, Size_To_Use - 1);
6946
6947 begin
6948 -- Normally we like to use the most negative number. The
6949 -- one exception is when this number is in the known
6950 -- subtype range and the largest positive number is not in
6951 -- the known subtype range.
6952
6953 -- For this exceptional case, use largest positive value
6954
6955 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
6956 and then Lo_Bound <= (-(2 ** Signed_Size))
6957 and then Hi_Bound < 2 ** Signed_Size
6958 then
6959 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
6960
6961 -- Normal case of largest negative value
6962
6963 else
6964 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
6965 end if;
6966 end;
6967 end if;
6968
6969 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
6970
6971 else
6972 -- For float types, use float values from System.Scalar_Values
6973
6974 if Is_Floating_Point_Type (T) then
6975 if Root_Type (T) = Standard_Short_Float then
6976 Val_RE := RE_IS_Isf;
6977 elsif Root_Type (T) = Standard_Float then
6978 Val_RE := RE_IS_Ifl;
6979 elsif Root_Type (T) = Standard_Long_Float then
6980 Val_RE := RE_IS_Ilf;
6981 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
6982 Val_RE := RE_IS_Ill;
6983 end if;
6984
6985 -- If zero is invalid, use zero values from System.Scalar_Values
6986
6987 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
6988 if Size_To_Use <= 8 then
6989 Val_RE := RE_IS_Iz1;
6990 elsif Size_To_Use <= 16 then
6991 Val_RE := RE_IS_Iz2;
6992 elsif Size_To_Use <= 32 then
6993 Val_RE := RE_IS_Iz4;
6994 else
6995 Val_RE := RE_IS_Iz8;
6996 end if;
6997
6998 -- For unsigned, use unsigned values from System.Scalar_Values
6999
7000 elsif Is_Unsigned_Type (T) then
7001 if Size_To_Use <= 8 then
7002 Val_RE := RE_IS_Iu1;
7003 elsif Size_To_Use <= 16 then
7004 Val_RE := RE_IS_Iu2;
7005 elsif Size_To_Use <= 32 then
7006 Val_RE := RE_IS_Iu4;
7007 else
7008 Val_RE := RE_IS_Iu8;
7009 end if;
7010
7011 -- For signed, use signed values from System.Scalar_Values
7012
7013 else
7014 if Size_To_Use <= 8 then
7015 Val_RE := RE_IS_Is1;
7016 elsif Size_To_Use <= 16 then
7017 Val_RE := RE_IS_Is2;
7018 elsif Size_To_Use <= 32 then
7019 Val_RE := RE_IS_Is4;
7020 else
7021 Val_RE := RE_IS_Is8;
7022 end if;
7023 end if;
7024
7025 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
7026 end if;
7027
7028 -- The final expression is obtained by doing an unchecked conversion
7029 -- of this result to the base type of the required subtype. We use
7030 -- the base type to avoid the unchecked conversion from chopping
7031 -- bits, and then we set Kill_Range_Check to preserve the "bad"
7032 -- value.
7033
7034 Result := Unchecked_Convert_To (Base_Type (T), Val);
7035
7036 -- Ensure result is not truncated, since we want the "bad" bits
7037 -- and also kill range check on result.
7038
7039 if Nkind (Result) = N_Unchecked_Type_Conversion then
7040 Set_No_Truncation (Result);
7041 Set_Kill_Range_Check (Result, True);
7042 end if;
7043
7044 return Result;
7045
7046 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
7047
7048 elsif Root_Type (T) = Standard_String
7049 or else
7050 Root_Type (T) = Standard_Wide_String
7051 or else
7052 Root_Type (T) = Standard_Wide_Wide_String
7053 then
7054 pragma Assert (Init_Or_Norm_Scalars);
7055
7056 return
7057 Make_Aggregate (Loc,
7058 Component_Associations => New_List (
7059 Make_Component_Association (Loc,
7060 Choices => New_List (
7061 Make_Others_Choice (Loc)),
7062 Expression =>
7063 Get_Simple_Init_Val
7064 (Component_Type (T), N, Esize (Root_Type (T))))));
7065
7066 -- Access type is initialized to null
7067
7068 elsif Is_Access_Type (T) then
7069 return
7070 Make_Null (Loc);
7071
7072 -- No other possibilities should arise, since we should only be
7073 -- calling Get_Simple_Init_Val if Needs_Simple_Initialization
7074 -- returned True, indicating one of the above cases held.
7075
7076 else
7077 raise Program_Error;
7078 end if;
7079
7080 exception
7081 when RE_Not_Available =>
7082 return Empty;
7083 end Get_Simple_Init_Val;
7084
7085 ------------------------------
7086 -- Has_New_Non_Standard_Rep --
7087 ------------------------------
7088
7089 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
7090 begin
7091 if not Is_Derived_Type (T) then
7092 return Has_Non_Standard_Rep (T)
7093 or else Has_Non_Standard_Rep (Root_Type (T));
7094
7095 -- If Has_Non_Standard_Rep is not set on the derived type, the
7096 -- representation is fully inherited.
7097
7098 elsif not Has_Non_Standard_Rep (T) then
7099 return False;
7100
7101 else
7102 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
7103
7104 -- May need a more precise check here: the First_Rep_Item may
7105 -- be a stream attribute, which does not affect the representation
7106 -- of the type ???
7107 end if;
7108 end Has_New_Non_Standard_Rep;
7109
7110 ----------------
7111 -- In_Runtime --
7112 ----------------
7113
7114 function In_Runtime (E : Entity_Id) return Boolean is
7115 S1 : Entity_Id;
7116
7117 begin
7118 S1 := Scope (E);
7119 while Scope (S1) /= Standard_Standard loop
7120 S1 := Scope (S1);
7121 end loop;
7122
7123 return Chars (S1) = Name_System or else Chars (S1) = Name_Ada;
7124 end In_Runtime;
7125
7126 ----------------------------
7127 -- Initialization_Warning --
7128 ----------------------------
7129
7130 procedure Initialization_Warning (E : Entity_Id) is
7131 Warning_Needed : Boolean;
7132
7133 begin
7134 Warning_Needed := False;
7135
7136 if Ekind (Current_Scope) = E_Package
7137 and then Static_Elaboration_Desired (Current_Scope)
7138 then
7139 if Is_Type (E) then
7140 if Is_Record_Type (E) then
7141 if Has_Discriminants (E)
7142 or else Is_Limited_Type (E)
7143 or else Has_Non_Standard_Rep (E)
7144 then
7145 Warning_Needed := True;
7146
7147 else
7148 -- Verify that at least one component has an initialization
7149 -- expression. No need for a warning on a type if all its
7150 -- components have no initialization.
7151
7152 declare
7153 Comp : Entity_Id;
7154
7155 begin
7156 Comp := First_Component (E);
7157 while Present (Comp) loop
7158 if Ekind (Comp) = E_Discriminant
7159 or else
7160 (Nkind (Parent (Comp)) = N_Component_Declaration
7161 and then Present (Expression (Parent (Comp))))
7162 then
7163 Warning_Needed := True;
7164 exit;
7165 end if;
7166
7167 Next_Component (Comp);
7168 end loop;
7169 end;
7170 end if;
7171
7172 if Warning_Needed then
7173 Error_Msg_N
7174 ("Objects of the type cannot be initialized " &
7175 "statically by default?",
7176 Parent (E));
7177 end if;
7178 end if;
7179
7180 else
7181 Error_Msg_N ("Object cannot be initialized statically?", E);
7182 end if;
7183 end if;
7184 end Initialization_Warning;
7185
7186 ------------------
7187 -- Init_Formals --
7188 ------------------
7189
7190 function Init_Formals (Typ : Entity_Id) return List_Id is
7191 Loc : constant Source_Ptr := Sloc (Typ);
7192 Formals : List_Id;
7193
7194 begin
7195 -- First parameter is always _Init : in out typ. Note that we need
7196 -- this to be in/out because in the case of the task record value,
7197 -- there are default record fields (_Priority, _Size, -Task_Info)
7198 -- that may be referenced in the generated initialization routine.
7199
7200 Formals := New_List (
7201 Make_Parameter_Specification (Loc,
7202 Defining_Identifier =>
7203 Make_Defining_Identifier (Loc, Name_uInit),
7204 In_Present => True,
7205 Out_Present => True,
7206 Parameter_Type => New_Reference_To (Typ, Loc)));
7207
7208 -- For task record value, or type that contains tasks, add two more
7209 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
7210 -- We also add these parameters for the task record type case.
7211
7212 if Has_Task (Typ)
7213 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
7214 then
7215 Append_To (Formals,
7216 Make_Parameter_Specification (Loc,
7217 Defining_Identifier =>
7218 Make_Defining_Identifier (Loc, Name_uMaster),
7219 Parameter_Type => New_Reference_To (RTE (RE_Master_Id), Loc)));
7220
7221 Append_To (Formals,
7222 Make_Parameter_Specification (Loc,
7223 Defining_Identifier =>
7224 Make_Defining_Identifier (Loc, Name_uChain),
7225 In_Present => True,
7226 Out_Present => True,
7227 Parameter_Type =>
7228 New_Reference_To (RTE (RE_Activation_Chain), Loc)));
7229
7230 Append_To (Formals,
7231 Make_Parameter_Specification (Loc,
7232 Defining_Identifier =>
7233 Make_Defining_Identifier (Loc, Name_uTask_Name),
7234 In_Present => True,
7235 Parameter_Type =>
7236 New_Reference_To (Standard_String, Loc)));
7237 end if;
7238
7239 return Formals;
7240
7241 exception
7242 when RE_Not_Available =>
7243 return Empty_List;
7244 end Init_Formals;
7245
7246 -------------------------
7247 -- Init_Secondary_Tags --
7248 -------------------------
7249
7250 procedure Init_Secondary_Tags
7251 (Typ : Entity_Id;
7252 Target : Node_Id;
7253 Stmts_List : List_Id;
7254 Fixed_Comps : Boolean := True;
7255 Variable_Comps : Boolean := True)
7256 is
7257 Loc : constant Source_Ptr := Sloc (Target);
7258
7259 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
7260 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
7261
7262 procedure Initialize_Tag
7263 (Typ : Entity_Id;
7264 Iface : Entity_Id;
7265 Tag_Comp : Entity_Id;
7266 Iface_Tag : Node_Id);
7267 -- Initialize the tag of the secondary dispatch table of Typ associated
7268 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
7269 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
7270 -- of Typ CPP tagged type we generate code to inherit the contents of
7271 -- the dispatch table directly from the ancestor.
7272
7273 --------------------
7274 -- Initialize_Tag --
7275 --------------------
7276
7277 procedure Initialize_Tag
7278 (Typ : Entity_Id;
7279 Iface : Entity_Id;
7280 Tag_Comp : Entity_Id;
7281 Iface_Tag : Node_Id)
7282 is
7283 Comp_Typ : Entity_Id;
7284 Offset_To_Top_Comp : Entity_Id := Empty;
7285
7286 begin
7287 -- Initialize the pointer to the secondary DT associated with the
7288 -- interface.
7289
7290 if not Is_Ancestor (Iface, Typ) then
7291 Append_To (Stmts_List,
7292 Make_Assignment_Statement (Loc,
7293 Name =>
7294 Make_Selected_Component (Loc,
7295 Prefix => New_Copy_Tree (Target),
7296 Selector_Name => New_Reference_To (Tag_Comp, Loc)),
7297 Expression =>
7298 New_Reference_To (Iface_Tag, Loc)));
7299 end if;
7300
7301 Comp_Typ := Scope (Tag_Comp);
7302
7303 -- Initialize the entries of the table of interfaces. We generate a
7304 -- different call when the parent of the type has variable size
7305 -- components.
7306
7307 if Comp_Typ /= Etype (Comp_Typ)
7308 and then Is_Variable_Size_Record (Etype (Comp_Typ))
7309 and then Chars (Tag_Comp) /= Name_uTag
7310 then
7311 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
7312
7313 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
7314 -- configurable run-time environment.
7315
7316 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
7317 Error_Msg_CRT
7318 ("variable size record with interface types", Typ);
7319 return;
7320 end if;
7321
7322 -- Generate:
7323 -- Set_Dynamic_Offset_To_Top
7324 -- (This => Init,
7325 -- Interface_T => Iface'Tag,
7326 -- Offset_Value => n,
7327 -- Offset_Func => Fn'Address)
7328
7329 Append_To (Stmts_List,
7330 Make_Procedure_Call_Statement (Loc,
7331 Name => New_Reference_To
7332 (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
7333 Parameter_Associations => New_List (
7334 Make_Attribute_Reference (Loc,
7335 Prefix => New_Copy_Tree (Target),
7336 Attribute_Name => Name_Address),
7337
7338 Unchecked_Convert_To (RTE (RE_Tag),
7339 New_Reference_To
7340 (Node (First_Elmt (Access_Disp_Table (Iface))),
7341 Loc)),
7342
7343 Unchecked_Convert_To
7344 (RTE (RE_Storage_Offset),
7345 Make_Attribute_Reference (Loc,
7346 Prefix =>
7347 Make_Selected_Component (Loc,
7348 Prefix => New_Copy_Tree (Target),
7349 Selector_Name =>
7350 New_Reference_To (Tag_Comp, Loc)),
7351 Attribute_Name => Name_Position)),
7352
7353 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
7354 Make_Attribute_Reference (Loc,
7355 Prefix => New_Reference_To
7356 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
7357 Attribute_Name => Name_Address)))));
7358
7359 -- In this case the next component stores the value of the
7360 -- offset to the top.
7361
7362 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
7363 pragma Assert (Present (Offset_To_Top_Comp));
7364
7365 Append_To (Stmts_List,
7366 Make_Assignment_Statement (Loc,
7367 Name =>
7368 Make_Selected_Component (Loc,
7369 Prefix => New_Copy_Tree (Target),
7370 Selector_Name => New_Reference_To
7371 (Offset_To_Top_Comp, Loc)),
7372 Expression =>
7373 Make_Attribute_Reference (Loc,
7374 Prefix =>
7375 Make_Selected_Component (Loc,
7376 Prefix => New_Copy_Tree (Target),
7377 Selector_Name =>
7378 New_Reference_To (Tag_Comp, Loc)),
7379 Attribute_Name => Name_Position)));
7380
7381 -- Normal case: No discriminants in the parent type
7382
7383 else
7384 -- Don't need to set any value if this interface shares
7385 -- the primary dispatch table.
7386
7387 if not Is_Ancestor (Iface, Typ) then
7388 Append_To (Stmts_List,
7389 Build_Set_Static_Offset_To_Top (Loc,
7390 Iface_Tag => New_Reference_To (Iface_Tag, Loc),
7391 Offset_Value =>
7392 Unchecked_Convert_To (RTE (RE_Storage_Offset),
7393 Make_Attribute_Reference (Loc,
7394 Prefix =>
7395 Make_Selected_Component (Loc,
7396 Prefix => New_Copy_Tree (Target),
7397 Selector_Name =>
7398 New_Reference_To (Tag_Comp, Loc)),
7399 Attribute_Name => Name_Position))));
7400 end if;
7401
7402 -- Generate:
7403 -- Register_Interface_Offset
7404 -- (This => Init,
7405 -- Interface_T => Iface'Tag,
7406 -- Is_Constant => True,
7407 -- Offset_Value => n,
7408 -- Offset_Func => null);
7409
7410 if RTE_Available (RE_Register_Interface_Offset) then
7411 Append_To (Stmts_List,
7412 Make_Procedure_Call_Statement (Loc,
7413 Name => New_Reference_To
7414 (RTE (RE_Register_Interface_Offset), Loc),
7415 Parameter_Associations => New_List (
7416 Make_Attribute_Reference (Loc,
7417 Prefix => New_Copy_Tree (Target),
7418 Attribute_Name => Name_Address),
7419
7420 Unchecked_Convert_To (RTE (RE_Tag),
7421 New_Reference_To
7422 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
7423
7424 New_Occurrence_Of (Standard_True, Loc),
7425
7426 Unchecked_Convert_To
7427 (RTE (RE_Storage_Offset),
7428 Make_Attribute_Reference (Loc,
7429 Prefix =>
7430 Make_Selected_Component (Loc,
7431 Prefix => New_Copy_Tree (Target),
7432 Selector_Name =>
7433 New_Reference_To (Tag_Comp, Loc)),
7434 Attribute_Name => Name_Position)),
7435
7436 Make_Null (Loc))));
7437 end if;
7438 end if;
7439 end Initialize_Tag;
7440
7441 -- Local variables
7442
7443 Full_Typ : Entity_Id;
7444 Ifaces_List : Elist_Id;
7445 Ifaces_Comp_List : Elist_Id;
7446 Ifaces_Tag_List : Elist_Id;
7447 Iface_Elmt : Elmt_Id;
7448 Iface_Comp_Elmt : Elmt_Id;
7449 Iface_Tag_Elmt : Elmt_Id;
7450 Tag_Comp : Node_Id;
7451 In_Variable_Pos : Boolean;
7452
7453 -- Start of processing for Init_Secondary_Tags
7454
7455 begin
7456 -- Handle private types
7457
7458 if Present (Full_View (Typ)) then
7459 Full_Typ := Full_View (Typ);
7460 else
7461 Full_Typ := Typ;
7462 end if;
7463
7464 Collect_Interfaces_Info
7465 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
7466
7467 Iface_Elmt := First_Elmt (Ifaces_List);
7468 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
7469 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
7470 while Present (Iface_Elmt) loop
7471 Tag_Comp := Node (Iface_Comp_Elmt);
7472
7473 -- Check if parent of record type has variable size components
7474
7475 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
7476 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
7477
7478 -- If we are compiling under the CPP full ABI compatibility mode and
7479 -- the ancestor is a CPP_Pragma tagged type then we generate code to
7480 -- initialize the secondary tag components from tags that reference
7481 -- secondary tables filled with copy of parent slots.
7482
7483 if Is_CPP_Class (Root_Type (Full_Typ)) then
7484
7485 -- Reject interface components located at variable offset in
7486 -- C++ derivations. This is currently unsupported.
7487
7488 if not Fixed_Comps and then In_Variable_Pos then
7489
7490 -- Locate the first dynamic component of the record. Done to
7491 -- improve the text of the warning.
7492
7493 declare
7494 Comp : Entity_Id;
7495 Comp_Typ : Entity_Id;
7496
7497 begin
7498 Comp := First_Entity (Typ);
7499 while Present (Comp) loop
7500 Comp_Typ := Etype (Comp);
7501
7502 if Ekind (Comp) /= E_Discriminant
7503 and then not Is_Tag (Comp)
7504 then
7505 exit when
7506 (Is_Record_Type (Comp_Typ)
7507 and then Is_Variable_Size_Record
7508 (Base_Type (Comp_Typ)))
7509 or else
7510 (Is_Array_Type (Comp_Typ)
7511 and then Is_Variable_Size_Array (Comp_Typ));
7512 end if;
7513
7514 Next_Entity (Comp);
7515 end loop;
7516
7517 pragma Assert (Present (Comp));
7518 Error_Msg_Node_2 := Comp;
7519 Error_Msg_NE
7520 ("parent type & with dynamic component & cannot be parent"
7521 & " of 'C'P'P derivation if new interfaces are present",
7522 Typ, Scope (Original_Record_Component (Comp)));
7523
7524 Error_Msg_Sloc :=
7525 Sloc (Scope (Original_Record_Component (Comp)));
7526 Error_Msg_NE
7527 ("type derived from 'C'P'P type & defined #",
7528 Typ, Scope (Original_Record_Component (Comp)));
7529
7530 -- Avoid duplicated warnings
7531
7532 exit;
7533 end;
7534
7535 -- Initialize secondary tags
7536
7537 else
7538 Append_To (Stmts_List,
7539 Make_Assignment_Statement (Loc,
7540 Name =>
7541 Make_Selected_Component (Loc,
7542 Prefix => New_Copy_Tree (Target),
7543 Selector_Name =>
7544 New_Reference_To (Node (Iface_Comp_Elmt), Loc)),
7545 Expression =>
7546 New_Reference_To (Node (Iface_Tag_Elmt), Loc)));
7547 end if;
7548
7549 -- Otherwise generate code to initialize the tag
7550
7551 else
7552 if (In_Variable_Pos and then Variable_Comps)
7553 or else (not In_Variable_Pos and then Fixed_Comps)
7554 then
7555 Initialize_Tag (Full_Typ,
7556 Iface => Node (Iface_Elmt),
7557 Tag_Comp => Tag_Comp,
7558 Iface_Tag => Node (Iface_Tag_Elmt));
7559 end if;
7560 end if;
7561
7562 Next_Elmt (Iface_Elmt);
7563 Next_Elmt (Iface_Comp_Elmt);
7564 Next_Elmt (Iface_Tag_Elmt);
7565 end loop;
7566 end Init_Secondary_Tags;
7567
7568 ----------------------------
7569 -- Is_Variable_Size_Array --
7570 ----------------------------
7571
7572 function Is_Variable_Size_Array (E : Entity_Id) return Boolean is
7573
7574 function Is_Constant_Bound (Exp : Node_Id) return Boolean;
7575 -- To simplify handling of array components. Determines whether the
7576 -- given bound is constant (a constant or enumeration literal, or an
7577 -- integer literal) as opposed to per-object, through an expression
7578 -- or a discriminant.
7579
7580 -----------------------
7581 -- Is_Constant_Bound --
7582 -----------------------
7583
7584 function Is_Constant_Bound (Exp : Node_Id) return Boolean is
7585 begin
7586 if Nkind (Exp) = N_Integer_Literal then
7587 return True;
7588 else
7589 return
7590 Is_Entity_Name (Exp)
7591 and then Present (Entity (Exp))
7592 and then
7593 (Ekind (Entity (Exp)) = E_Constant
7594 or else Ekind (Entity (Exp)) = E_Enumeration_Literal);
7595 end if;
7596 end Is_Constant_Bound;
7597
7598 -- Local variables
7599
7600 Idx : Node_Id;
7601
7602 -- Start of processing for Is_Variable_Sized_Array
7603
7604 begin
7605 pragma Assert (Is_Array_Type (E));
7606
7607 -- Check if some index is initialized with a non-constant value
7608
7609 Idx := First_Index (E);
7610 while Present (Idx) loop
7611 if Nkind (Idx) = N_Range then
7612 if not Is_Constant_Bound (Low_Bound (Idx))
7613 or else not Is_Constant_Bound (High_Bound (Idx))
7614 then
7615 return True;
7616 end if;
7617 end if;
7618
7619 Idx := Next_Index (Idx);
7620 end loop;
7621
7622 return False;
7623 end Is_Variable_Size_Array;
7624
7625 -----------------------------
7626 -- Is_Variable_Size_Record --
7627 -----------------------------
7628
7629 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
7630 Comp : Entity_Id;
7631 Comp_Typ : Entity_Id;
7632
7633 begin
7634 pragma Assert (Is_Record_Type (E));
7635
7636 Comp := First_Entity (E);
7637 while Present (Comp) loop
7638 Comp_Typ := Etype (Comp);
7639
7640 -- Recursive call if the record type has discriminants
7641
7642 if Is_Record_Type (Comp_Typ)
7643 and then Has_Discriminants (Comp_Typ)
7644 and then Is_Variable_Size_Record (Comp_Typ)
7645 then
7646 return True;
7647
7648 elsif Is_Array_Type (Comp_Typ)
7649 and then Is_Variable_Size_Array (Comp_Typ)
7650 then
7651 return True;
7652 end if;
7653
7654 Next_Entity (Comp);
7655 end loop;
7656
7657 return False;
7658 end Is_Variable_Size_Record;
7659
7660 ----------------------------------------
7661 -- Make_Controlling_Function_Wrappers --
7662 ----------------------------------------
7663
7664 procedure Make_Controlling_Function_Wrappers
7665 (Tag_Typ : Entity_Id;
7666 Decl_List : out List_Id;
7667 Body_List : out List_Id)
7668 is
7669 Loc : constant Source_Ptr := Sloc (Tag_Typ);
7670 Prim_Elmt : Elmt_Id;
7671 Subp : Entity_Id;
7672 Actual_List : List_Id;
7673 Formal_List : List_Id;
7674 Formal : Entity_Id;
7675 Par_Formal : Entity_Id;
7676 Formal_Node : Node_Id;
7677 Func_Body : Node_Id;
7678 Func_Decl : Node_Id;
7679 Func_Spec : Node_Id;
7680 Return_Stmt : Node_Id;
7681
7682 begin
7683 Decl_List := New_List;
7684 Body_List := New_List;
7685
7686 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7687
7688 while Present (Prim_Elmt) loop
7689 Subp := Node (Prim_Elmt);
7690
7691 -- If a primitive function with a controlling result of the type has
7692 -- not been overridden by the user, then we must create a wrapper
7693 -- function here that effectively overrides it and invokes the
7694 -- (non-abstract) parent function. This can only occur for a null
7695 -- extension. Note that functions with anonymous controlling access
7696 -- results don't qualify and must be overridden. We also exclude
7697 -- Input attributes, since each type will have its own version of
7698 -- Input constructed by the expander. The test for Comes_From_Source
7699 -- is needed to distinguish inherited operations from renamings
7700 -- (which also have Alias set).
7701
7702 -- The function may be abstract, or require_Overriding may be set
7703 -- for it, because tests for null extensions may already have reset
7704 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
7705 -- set, functions that need wrappers are recognized by having an
7706 -- alias that returns the parent type.
7707
7708 if Comes_From_Source (Subp)
7709 or else No (Alias (Subp))
7710 or else Ekind (Subp) /= E_Function
7711 or else not Has_Controlling_Result (Subp)
7712 or else Is_Access_Type (Etype (Subp))
7713 or else Is_Abstract_Subprogram (Alias (Subp))
7714 or else Is_TSS (Subp, TSS_Stream_Input)
7715 then
7716 goto Next_Prim;
7717
7718 elsif Is_Abstract_Subprogram (Subp)
7719 or else Requires_Overriding (Subp)
7720 or else
7721 (Is_Null_Extension (Etype (Subp))
7722 and then Etype (Alias (Subp)) /= Etype (Subp))
7723 then
7724 Formal_List := No_List;
7725 Formal := First_Formal (Subp);
7726
7727 if Present (Formal) then
7728 Formal_List := New_List;
7729
7730 while Present (Formal) loop
7731 Append
7732 (Make_Parameter_Specification
7733 (Loc,
7734 Defining_Identifier =>
7735 Make_Defining_Identifier (Sloc (Formal),
7736 Chars => Chars (Formal)),
7737 In_Present => In_Present (Parent (Formal)),
7738 Out_Present => Out_Present (Parent (Formal)),
7739 Null_Exclusion_Present =>
7740 Null_Exclusion_Present (Parent (Formal)),
7741 Parameter_Type =>
7742 New_Reference_To (Etype (Formal), Loc),
7743 Expression =>
7744 New_Copy_Tree (Expression (Parent (Formal)))),
7745 Formal_List);
7746
7747 Next_Formal (Formal);
7748 end loop;
7749 end if;
7750
7751 Func_Spec :=
7752 Make_Function_Specification (Loc,
7753 Defining_Unit_Name =>
7754 Make_Defining_Identifier (Loc,
7755 Chars => Chars (Subp)),
7756 Parameter_Specifications => Formal_List,
7757 Result_Definition =>
7758 New_Reference_To (Etype (Subp), Loc));
7759
7760 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
7761 Append_To (Decl_List, Func_Decl);
7762
7763 -- Build a wrapper body that calls the parent function. The body
7764 -- contains a single return statement that returns an extension
7765 -- aggregate whose ancestor part is a call to the parent function,
7766 -- passing the formals as actuals (with any controlling arguments
7767 -- converted to the types of the corresponding formals of the
7768 -- parent function, which might be anonymous access types), and
7769 -- having a null extension.
7770
7771 Formal := First_Formal (Subp);
7772 Par_Formal := First_Formal (Alias (Subp));
7773 Formal_Node := First (Formal_List);
7774
7775 if Present (Formal) then
7776 Actual_List := New_List;
7777 else
7778 Actual_List := No_List;
7779 end if;
7780
7781 while Present (Formal) loop
7782 if Is_Controlling_Formal (Formal) then
7783 Append_To (Actual_List,
7784 Make_Type_Conversion (Loc,
7785 Subtype_Mark =>
7786 New_Occurrence_Of (Etype (Par_Formal), Loc),
7787 Expression =>
7788 New_Reference_To
7789 (Defining_Identifier (Formal_Node), Loc)));
7790 else
7791 Append_To
7792 (Actual_List,
7793 New_Reference_To
7794 (Defining_Identifier (Formal_Node), Loc));
7795 end if;
7796
7797 Next_Formal (Formal);
7798 Next_Formal (Par_Formal);
7799 Next (Formal_Node);
7800 end loop;
7801
7802 Return_Stmt :=
7803 Make_Simple_Return_Statement (Loc,
7804 Expression =>
7805 Make_Extension_Aggregate (Loc,
7806 Ancestor_Part =>
7807 Make_Function_Call (Loc,
7808 Name => New_Reference_To (Alias (Subp), Loc),
7809 Parameter_Associations => Actual_List),
7810 Null_Record_Present => True));
7811
7812 Func_Body :=
7813 Make_Subprogram_Body (Loc,
7814 Specification => New_Copy_Tree (Func_Spec),
7815 Declarations => Empty_List,
7816 Handled_Statement_Sequence =>
7817 Make_Handled_Sequence_Of_Statements (Loc,
7818 Statements => New_List (Return_Stmt)));
7819
7820 Set_Defining_Unit_Name
7821 (Specification (Func_Body),
7822 Make_Defining_Identifier (Loc, Chars (Subp)));
7823
7824 Append_To (Body_List, Func_Body);
7825
7826 -- Replace the inherited function with the wrapper function
7827 -- in the primitive operations list.
7828
7829 Override_Dispatching_Operation
7830 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec));
7831 end if;
7832
7833 <<Next_Prim>>
7834 Next_Elmt (Prim_Elmt);
7835 end loop;
7836 end Make_Controlling_Function_Wrappers;
7837
7838 -------------------
7839 -- Make_Eq_Body --
7840 -------------------
7841
7842 function Make_Eq_Body
7843 (Typ : Entity_Id;
7844 Eq_Name : Name_Id) return Node_Id
7845 is
7846 Loc : constant Source_Ptr := Sloc (Parent (Typ));
7847 Decl : Node_Id;
7848 Def : constant Node_Id := Parent (Typ);
7849 Stmts : constant List_Id := New_List;
7850 Variant_Case : Boolean := Has_Discriminants (Typ);
7851 Comps : Node_Id := Empty;
7852 Typ_Def : Node_Id := Type_Definition (Def);
7853
7854 begin
7855 Decl :=
7856 Predef_Spec_Or_Body (Loc,
7857 Tag_Typ => Typ,
7858 Name => Eq_Name,
7859 Profile => New_List (
7860 Make_Parameter_Specification (Loc,
7861 Defining_Identifier =>
7862 Make_Defining_Identifier (Loc, Name_X),
7863 Parameter_Type => New_Reference_To (Typ, Loc)),
7864
7865 Make_Parameter_Specification (Loc,
7866 Defining_Identifier =>
7867 Make_Defining_Identifier (Loc, Name_Y),
7868 Parameter_Type => New_Reference_To (Typ, Loc))),
7869
7870 Ret_Type => Standard_Boolean,
7871 For_Body => True);
7872
7873 if Variant_Case then
7874 if Nkind (Typ_Def) = N_Derived_Type_Definition then
7875 Typ_Def := Record_Extension_Part (Typ_Def);
7876 end if;
7877
7878 if Present (Typ_Def) then
7879 Comps := Component_List (Typ_Def);
7880 end if;
7881
7882 Variant_Case :=
7883 Present (Comps) and then Present (Variant_Part (Comps));
7884 end if;
7885
7886 if Variant_Case then
7887 Append_To (Stmts,
7888 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
7889 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
7890 Append_To (Stmts,
7891 Make_Simple_Return_Statement (Loc,
7892 Expression => New_Reference_To (Standard_True, Loc)));
7893
7894 else
7895 Append_To (Stmts,
7896 Make_Simple_Return_Statement (Loc,
7897 Expression =>
7898 Expand_Record_Equality
7899 (Typ,
7900 Typ => Typ,
7901 Lhs => Make_Identifier (Loc, Name_X),
7902 Rhs => Make_Identifier (Loc, Name_Y),
7903 Bodies => Declarations (Decl))));
7904 end if;
7905
7906 Set_Handled_Statement_Sequence
7907 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
7908 return Decl;
7909 end Make_Eq_Body;
7910
7911 ------------------
7912 -- Make_Eq_Case --
7913 ------------------
7914
7915 -- <Make_Eq_If shared components>
7916 -- case X.D1 is
7917 -- when V1 => <Make_Eq_Case> on subcomponents
7918 -- ...
7919 -- when Vn => <Make_Eq_Case> on subcomponents
7920 -- end case;
7921
7922 function Make_Eq_Case
7923 (E : Entity_Id;
7924 CL : Node_Id;
7925 Discr : Entity_Id := Empty) return List_Id
7926 is
7927 Loc : constant Source_Ptr := Sloc (E);
7928 Result : constant List_Id := New_List;
7929 Variant : Node_Id;
7930 Alt_List : List_Id;
7931
7932 begin
7933 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
7934
7935 if No (Variant_Part (CL)) then
7936 return Result;
7937 end if;
7938
7939 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
7940
7941 if No (Variant) then
7942 return Result;
7943 end if;
7944
7945 Alt_List := New_List;
7946
7947 while Present (Variant) loop
7948 Append_To (Alt_List,
7949 Make_Case_Statement_Alternative (Loc,
7950 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
7951 Statements => Make_Eq_Case (E, Component_List (Variant))));
7952
7953 Next_Non_Pragma (Variant);
7954 end loop;
7955
7956 -- If we have an Unchecked_Union, use one of the parameters that
7957 -- captures the discriminants.
7958
7959 if Is_Unchecked_Union (E) then
7960 Append_To (Result,
7961 Make_Case_Statement (Loc,
7962 Expression => New_Reference_To (Discr, Loc),
7963 Alternatives => Alt_List));
7964
7965 else
7966 Append_To (Result,
7967 Make_Case_Statement (Loc,
7968 Expression =>
7969 Make_Selected_Component (Loc,
7970 Prefix => Make_Identifier (Loc, Name_X),
7971 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
7972 Alternatives => Alt_List));
7973 end if;
7974
7975 return Result;
7976 end Make_Eq_Case;
7977
7978 ----------------
7979 -- Make_Eq_If --
7980 ----------------
7981
7982 -- Generates:
7983
7984 -- if
7985 -- X.C1 /= Y.C1
7986 -- or else
7987 -- X.C2 /= Y.C2
7988 -- ...
7989 -- then
7990 -- return False;
7991 -- end if;
7992
7993 -- or a null statement if the list L is empty
7994
7995 function Make_Eq_If
7996 (E : Entity_Id;
7997 L : List_Id) return Node_Id
7998 is
7999 Loc : constant Source_Ptr := Sloc (E);
8000 C : Node_Id;
8001 Field_Name : Name_Id;
8002 Cond : Node_Id;
8003
8004 begin
8005 if No (L) then
8006 return Make_Null_Statement (Loc);
8007
8008 else
8009 Cond := Empty;
8010
8011 C := First_Non_Pragma (L);
8012 while Present (C) loop
8013 Field_Name := Chars (Defining_Identifier (C));
8014
8015 -- The tags must not be compared: they are not part of the value.
8016 -- Ditto for the controller component, if present.
8017
8018 -- Note also that in the following, we use Make_Identifier for
8019 -- the component names. Use of New_Reference_To to identify the
8020 -- components would be incorrect because the wrong entities for
8021 -- discriminants could be picked up in the private type case.
8022
8023 if Field_Name /= Name_uTag
8024 and then
8025 Field_Name /= Name_uController
8026 then
8027 Evolve_Or_Else (Cond,
8028 Make_Op_Ne (Loc,
8029 Left_Opnd =>
8030 Make_Selected_Component (Loc,
8031 Prefix => Make_Identifier (Loc, Name_X),
8032 Selector_Name =>
8033 Make_Identifier (Loc, Field_Name)),
8034
8035 Right_Opnd =>
8036 Make_Selected_Component (Loc,
8037 Prefix => Make_Identifier (Loc, Name_Y),
8038 Selector_Name =>
8039 Make_Identifier (Loc, Field_Name))));
8040 end if;
8041
8042 Next_Non_Pragma (C);
8043 end loop;
8044
8045 if No (Cond) then
8046 return Make_Null_Statement (Loc);
8047
8048 else
8049 return
8050 Make_Implicit_If_Statement (E,
8051 Condition => Cond,
8052 Then_Statements => New_List (
8053 Make_Simple_Return_Statement (Loc,
8054 Expression => New_Occurrence_Of (Standard_False, Loc))));
8055 end if;
8056 end if;
8057 end Make_Eq_If;
8058
8059 -------------------------------
8060 -- Make_Null_Procedure_Specs --
8061 -------------------------------
8062
8063 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
8064 Decl_List : constant List_Id := New_List;
8065 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8066 Formal : Entity_Id;
8067 Formal_List : List_Id;
8068 New_Param_Spec : Node_Id;
8069 Parent_Subp : Entity_Id;
8070 Prim_Elmt : Elmt_Id;
8071 Subp : Entity_Id;
8072
8073 begin
8074 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
8075 while Present (Prim_Elmt) loop
8076 Subp := Node (Prim_Elmt);
8077
8078 -- If a null procedure inherited from an interface has not been
8079 -- overridden, then we build a null procedure declaration to
8080 -- override the inherited procedure.
8081
8082 Parent_Subp := Alias (Subp);
8083
8084 if Present (Parent_Subp)
8085 and then Is_Null_Interface_Primitive (Parent_Subp)
8086 then
8087 Formal_List := No_List;
8088 Formal := First_Formal (Subp);
8089
8090 if Present (Formal) then
8091 Formal_List := New_List;
8092
8093 while Present (Formal) loop
8094
8095 -- Copy the parameter spec including default expressions
8096
8097 New_Param_Spec :=
8098 New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
8099
8100 -- Generate a new defining identifier for the new formal.
8101 -- required because New_Copy_Tree does not duplicate
8102 -- semantic fields (except itypes).
8103
8104 Set_Defining_Identifier (New_Param_Spec,
8105 Make_Defining_Identifier (Sloc (Formal),
8106 Chars => Chars (Formal)));
8107
8108 -- For controlling arguments we must change their
8109 -- parameter type to reference the tagged type (instead
8110 -- of the interface type)
8111
8112 if Is_Controlling_Formal (Formal) then
8113 if Nkind (Parameter_Type (Parent (Formal)))
8114 = N_Identifier
8115 then
8116 Set_Parameter_Type (New_Param_Spec,
8117 New_Occurrence_Of (Tag_Typ, Loc));
8118
8119 else pragma Assert
8120 (Nkind (Parameter_Type (Parent (Formal)))
8121 = N_Access_Definition);
8122 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
8123 New_Occurrence_Of (Tag_Typ, Loc));
8124 end if;
8125 end if;
8126
8127 Append (New_Param_Spec, Formal_List);
8128
8129 Next_Formal (Formal);
8130 end loop;
8131 end if;
8132
8133 Append_To (Decl_List,
8134 Make_Subprogram_Declaration (Loc,
8135 Make_Procedure_Specification (Loc,
8136 Defining_Unit_Name =>
8137 Make_Defining_Identifier (Loc, Chars (Subp)),
8138 Parameter_Specifications => Formal_List,
8139 Null_Present => True)));
8140 end if;
8141
8142 Next_Elmt (Prim_Elmt);
8143 end loop;
8144
8145 return Decl_List;
8146 end Make_Null_Procedure_Specs;
8147
8148 -------------------------------------
8149 -- Make_Predefined_Primitive_Specs --
8150 -------------------------------------
8151
8152 procedure Make_Predefined_Primitive_Specs
8153 (Tag_Typ : Entity_Id;
8154 Predef_List : out List_Id;
8155 Renamed_Eq : out Entity_Id)
8156 is
8157 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8158 Res : constant List_Id := New_List;
8159 Prim : Elmt_Id;
8160 Eq_Needed : Boolean;
8161 Eq_Spec : Node_Id;
8162 Eq_Name : Name_Id := Name_Op_Eq;
8163
8164 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
8165 -- Returns true if Prim is a renaming of an unresolved predefined
8166 -- equality operation.
8167
8168 -------------------------------
8169 -- Is_Predefined_Eq_Renaming --
8170 -------------------------------
8171
8172 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
8173 begin
8174 return Chars (Prim) /= Name_Op_Eq
8175 and then Present (Alias (Prim))
8176 and then Comes_From_Source (Prim)
8177 and then Is_Intrinsic_Subprogram (Alias (Prim))
8178 and then Chars (Alias (Prim)) = Name_Op_Eq;
8179 end Is_Predefined_Eq_Renaming;
8180
8181 -- Start of processing for Make_Predefined_Primitive_Specs
8182
8183 begin
8184 Renamed_Eq := Empty;
8185
8186 -- Spec of _Size
8187
8188 Append_To (Res, Predef_Spec_Or_Body (Loc,
8189 Tag_Typ => Tag_Typ,
8190 Name => Name_uSize,
8191 Profile => New_List (
8192 Make_Parameter_Specification (Loc,
8193 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8194 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8195
8196 Ret_Type => Standard_Long_Long_Integer));
8197
8198 -- Spec of _Alignment
8199
8200 Append_To (Res, Predef_Spec_Or_Body (Loc,
8201 Tag_Typ => Tag_Typ,
8202 Name => Name_uAlignment,
8203 Profile => New_List (
8204 Make_Parameter_Specification (Loc,
8205 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8206 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8207
8208 Ret_Type => Standard_Integer));
8209
8210 -- Specs for dispatching stream attributes
8211
8212 declare
8213 Stream_Op_TSS_Names :
8214 constant array (Integer range <>) of TSS_Name_Type :=
8215 (TSS_Stream_Read,
8216 TSS_Stream_Write,
8217 TSS_Stream_Input,
8218 TSS_Stream_Output);
8219
8220 begin
8221 for Op in Stream_Op_TSS_Names'Range loop
8222 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
8223 Append_To (Res,
8224 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
8225 Stream_Op_TSS_Names (Op)));
8226 end if;
8227 end loop;
8228 end;
8229
8230 -- Spec of "=" is expanded if the type is not limited and if a
8231 -- user defined "=" was not already declared for the non-full
8232 -- view of a private extension
8233
8234 if not Is_Limited_Type (Tag_Typ) then
8235 Eq_Needed := True;
8236 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8237 while Present (Prim) loop
8238
8239 -- If a primitive is encountered that renames the predefined
8240 -- equality operator before reaching any explicit equality
8241 -- primitive, then we still need to create a predefined equality
8242 -- function, because calls to it can occur via the renaming. A new
8243 -- name is created for the equality to avoid conflicting with any
8244 -- user-defined equality. (Note that this doesn't account for
8245 -- renamings of equality nested within subpackages???)
8246
8247 if Is_Predefined_Eq_Renaming (Node (Prim)) then
8248 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
8249
8250 -- User-defined equality
8251
8252 elsif Chars (Node (Prim)) = Name_Op_Eq
8253 and then Etype (First_Formal (Node (Prim))) =
8254 Etype (Next_Formal (First_Formal (Node (Prim))))
8255 and then Base_Type (Etype (Node (Prim))) = Standard_Boolean
8256 then
8257 if No (Alias (Node (Prim)))
8258 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
8259 N_Subprogram_Renaming_Declaration
8260 then
8261 Eq_Needed := False;
8262 exit;
8263
8264 -- If the parent is not an interface type and has an abstract
8265 -- equality function, the inherited equality is abstract as
8266 -- well, and no body can be created for it.
8267
8268 elsif not Is_Interface (Etype (Tag_Typ))
8269 and then Present (Alias (Node (Prim)))
8270 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
8271 then
8272 Eq_Needed := False;
8273 exit;
8274
8275 -- If the type has an equality function corresponding with
8276 -- a primitive defined in an interface type, the inherited
8277 -- equality is abstract as well, and no body can be created
8278 -- for it.
8279
8280 elsif Present (Alias (Node (Prim)))
8281 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
8282 and then
8283 Is_Interface
8284 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
8285 then
8286 Eq_Needed := False;
8287 exit;
8288 end if;
8289 end if;
8290
8291 Next_Elmt (Prim);
8292 end loop;
8293
8294 -- If a renaming of predefined equality was found but there was no
8295 -- user-defined equality (so Eq_Needed is still true), then set the
8296 -- name back to Name_Op_Eq. But in the case where a user-defined
8297 -- equality was located after such a renaming, then the predefined
8298 -- equality function is still needed, so Eq_Needed must be set back
8299 -- to True.
8300
8301 if Eq_Name /= Name_Op_Eq then
8302 if Eq_Needed then
8303 Eq_Name := Name_Op_Eq;
8304 else
8305 Eq_Needed := True;
8306 end if;
8307 end if;
8308
8309 if Eq_Needed then
8310 Eq_Spec := Predef_Spec_Or_Body (Loc,
8311 Tag_Typ => Tag_Typ,
8312 Name => Eq_Name,
8313 Profile => New_List (
8314 Make_Parameter_Specification (Loc,
8315 Defining_Identifier =>
8316 Make_Defining_Identifier (Loc, Name_X),
8317 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8318 Make_Parameter_Specification (Loc,
8319 Defining_Identifier =>
8320 Make_Defining_Identifier (Loc, Name_Y),
8321 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8322 Ret_Type => Standard_Boolean);
8323 Append_To (Res, Eq_Spec);
8324
8325 if Eq_Name /= Name_Op_Eq then
8326 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
8327
8328 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8329 while Present (Prim) loop
8330
8331 -- Any renamings of equality that appeared before an
8332 -- overriding equality must be updated to refer to the
8333 -- entity for the predefined equality, otherwise calls via
8334 -- the renaming would get incorrectly resolved to call the
8335 -- user-defined equality function.
8336
8337 if Is_Predefined_Eq_Renaming (Node (Prim)) then
8338 Set_Alias (Node (Prim), Renamed_Eq);
8339
8340 -- Exit upon encountering a user-defined equality
8341
8342 elsif Chars (Node (Prim)) = Name_Op_Eq
8343 and then No (Alias (Node (Prim)))
8344 then
8345 exit;
8346 end if;
8347
8348 Next_Elmt (Prim);
8349 end loop;
8350 end if;
8351 end if;
8352
8353 -- Spec for dispatching assignment
8354
8355 Append_To (Res, Predef_Spec_Or_Body (Loc,
8356 Tag_Typ => Tag_Typ,
8357 Name => Name_uAssign,
8358 Profile => New_List (
8359 Make_Parameter_Specification (Loc,
8360 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8361 Out_Present => True,
8362 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8363
8364 Make_Parameter_Specification (Loc,
8365 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
8366 Parameter_Type => New_Reference_To (Tag_Typ, Loc)))));
8367 end if;
8368
8369 -- Ada 2005: Generate declarations for the following primitive
8370 -- operations for limited interfaces and synchronized types that
8371 -- implement a limited interface.
8372
8373 -- Disp_Asynchronous_Select
8374 -- Disp_Conditional_Select
8375 -- Disp_Get_Prim_Op_Kind
8376 -- Disp_Get_Task_Id
8377 -- Disp_Requeue
8378 -- Disp_Timed_Select
8379
8380 -- These operations cannot be implemented on VM targets, so we simply
8381 -- disable their generation in this case. Disable the generation of
8382 -- these bodies if No_Dispatching_Calls, Ravenscar or ZFP is active.
8383
8384 if Ada_Version >= Ada_2005
8385 and then Tagged_Type_Expansion
8386 and then not Restriction_Active (No_Dispatching_Calls)
8387 and then not Restriction_Active (No_Select_Statements)
8388 and then RTE_Available (RE_Select_Specific_Data)
8389 then
8390 -- These primitives are defined abstract in interface types
8391
8392 if Is_Interface (Tag_Typ)
8393 and then Is_Limited_Record (Tag_Typ)
8394 then
8395 Append_To (Res,
8396 Make_Abstract_Subprogram_Declaration (Loc,
8397 Specification =>
8398 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
8399
8400 Append_To (Res,
8401 Make_Abstract_Subprogram_Declaration (Loc,
8402 Specification =>
8403 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
8404
8405 Append_To (Res,
8406 Make_Abstract_Subprogram_Declaration (Loc,
8407 Specification =>
8408 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
8409
8410 Append_To (Res,
8411 Make_Abstract_Subprogram_Declaration (Loc,
8412 Specification =>
8413 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
8414
8415 Append_To (Res,
8416 Make_Abstract_Subprogram_Declaration (Loc,
8417 Specification =>
8418 Make_Disp_Requeue_Spec (Tag_Typ)));
8419
8420 Append_To (Res,
8421 Make_Abstract_Subprogram_Declaration (Loc,
8422 Specification =>
8423 Make_Disp_Timed_Select_Spec (Tag_Typ)));
8424
8425 -- If the ancestor is an interface type we declare non-abstract
8426 -- primitives to override the abstract primitives of the interface
8427 -- type.
8428
8429 elsif (not Is_Interface (Tag_Typ)
8430 and then Is_Interface (Etype (Tag_Typ))
8431 and then Is_Limited_Record (Etype (Tag_Typ)))
8432 or else
8433 (Is_Concurrent_Record_Type (Tag_Typ)
8434 and then Has_Interfaces (Tag_Typ))
8435 then
8436 Append_To (Res,
8437 Make_Subprogram_Declaration (Loc,
8438 Specification =>
8439 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
8440
8441 Append_To (Res,
8442 Make_Subprogram_Declaration (Loc,
8443 Specification =>
8444 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
8445
8446 Append_To (Res,
8447 Make_Subprogram_Declaration (Loc,
8448 Specification =>
8449 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
8450
8451 Append_To (Res,
8452 Make_Subprogram_Declaration (Loc,
8453 Specification =>
8454 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
8455
8456 Append_To (Res,
8457 Make_Subprogram_Declaration (Loc,
8458 Specification =>
8459 Make_Disp_Requeue_Spec (Tag_Typ)));
8460
8461 Append_To (Res,
8462 Make_Subprogram_Declaration (Loc,
8463 Specification =>
8464 Make_Disp_Timed_Select_Spec (Tag_Typ)));
8465 end if;
8466 end if;
8467
8468 -- Specs for finalization actions that may be required in case a future
8469 -- extension contain a controlled element. We generate those only for
8470 -- root tagged types where they will get dummy bodies or when the type
8471 -- has controlled components and their body must be generated. It is
8472 -- also impossible to provide those for tagged types defined within
8473 -- s-finimp since it would involve circularity problems
8474
8475 if In_Finalization_Root (Tag_Typ) then
8476 null;
8477
8478 -- We also skip these if finalization is not available
8479
8480 elsif Restriction_Active (No_Finalization) then
8481 null;
8482
8483 -- Skip these for CIL Value types, where finalization is not available
8484
8485 elsif Is_Value_Type (Tag_Typ) then
8486 null;
8487
8488 elsif Etype (Tag_Typ) = Tag_Typ
8489 or else Needs_Finalization (Tag_Typ)
8490
8491 -- Ada 2005 (AI-251): We must also generate these subprograms if
8492 -- the immediate ancestor is an interface to ensure the correct
8493 -- initialization of its dispatch table.
8494
8495 or else (not Is_Interface (Tag_Typ)
8496 and then Is_Interface (Etype (Tag_Typ)))
8497
8498 -- Ada 205 (AI-251): We must also generate these subprograms if
8499 -- the parent of an nonlimited interface is a limited interface
8500
8501 or else (Is_Interface (Tag_Typ)
8502 and then not Is_Limited_Interface (Tag_Typ)
8503 and then Is_Limited_Interface (Etype (Tag_Typ)))
8504 then
8505 if not Is_Limited_Type (Tag_Typ) then
8506 Append_To (Res,
8507 Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
8508 end if;
8509
8510 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
8511 end if;
8512
8513 Predef_List := Res;
8514 end Make_Predefined_Primitive_Specs;
8515
8516 ---------------------------------
8517 -- Needs_Simple_Initialization --
8518 ---------------------------------
8519
8520 function Needs_Simple_Initialization
8521 (T : Entity_Id;
8522 Consider_IS : Boolean := True) return Boolean
8523 is
8524 Consider_IS_NS : constant Boolean :=
8525 Normalize_Scalars
8526 or (Initialize_Scalars and Consider_IS);
8527
8528 begin
8529 -- Check for private type, in which case test applies to the underlying
8530 -- type of the private type.
8531
8532 if Is_Private_Type (T) then
8533 declare
8534 RT : constant Entity_Id := Underlying_Type (T);
8535
8536 begin
8537 if Present (RT) then
8538 return Needs_Simple_Initialization (RT);
8539 else
8540 return False;
8541 end if;
8542 end;
8543
8544 -- Cases needing simple initialization are access types, and, if pragma
8545 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
8546 -- types.
8547
8548 elsif Is_Access_Type (T)
8549 or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
8550 then
8551 return True;
8552
8553 -- If Initialize/Normalize_Scalars is in effect, string objects also
8554 -- need initialization, unless they are created in the course of
8555 -- expanding an aggregate (since in the latter case they will be
8556 -- filled with appropriate initializing values before they are used).
8557
8558 elsif Consider_IS_NS
8559 and then
8560 (Root_Type (T) = Standard_String
8561 or else Root_Type (T) = Standard_Wide_String
8562 or else Root_Type (T) = Standard_Wide_Wide_String)
8563 and then
8564 (not Is_Itype (T)
8565 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
8566 then
8567 return True;
8568
8569 else
8570 return False;
8571 end if;
8572 end Needs_Simple_Initialization;
8573
8574 ----------------------
8575 -- Predef_Deep_Spec --
8576 ----------------------
8577
8578 function Predef_Deep_Spec
8579 (Loc : Source_Ptr;
8580 Tag_Typ : Entity_Id;
8581 Name : TSS_Name_Type;
8582 For_Body : Boolean := False) return Node_Id
8583 is
8584 Prof : List_Id;
8585 Type_B : Entity_Id;
8586
8587 begin
8588 if Name = TSS_Deep_Finalize then
8589 Prof := New_List;
8590 Type_B := Standard_Boolean;
8591
8592 else
8593 Prof := New_List (
8594 Make_Parameter_Specification (Loc,
8595 Defining_Identifier => Make_Defining_Identifier (Loc, Name_L),
8596 In_Present => True,
8597 Out_Present => True,
8598 Parameter_Type =>
8599 New_Reference_To (RTE (RE_Finalizable_Ptr), Loc)));
8600 Type_B := Standard_Short_Short_Integer;
8601 end if;
8602
8603 Append_To (Prof,
8604 Make_Parameter_Specification (Loc,
8605 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
8606 In_Present => True,
8607 Out_Present => True,
8608 Parameter_Type => New_Reference_To (Tag_Typ, Loc)));
8609
8610 Append_To (Prof,
8611 Make_Parameter_Specification (Loc,
8612 Defining_Identifier => Make_Defining_Identifier (Loc, Name_B),
8613 Parameter_Type => New_Reference_To (Type_B, Loc)));
8614
8615 return Predef_Spec_Or_Body (Loc,
8616 Name => Make_TSS_Name (Tag_Typ, Name),
8617 Tag_Typ => Tag_Typ,
8618 Profile => Prof,
8619 For_Body => For_Body);
8620
8621 exception
8622 when RE_Not_Available =>
8623 return Empty;
8624 end Predef_Deep_Spec;
8625
8626 -------------------------
8627 -- Predef_Spec_Or_Body --
8628 -------------------------
8629
8630 function Predef_Spec_Or_Body
8631 (Loc : Source_Ptr;
8632 Tag_Typ : Entity_Id;
8633 Name : Name_Id;
8634 Profile : List_Id;
8635 Ret_Type : Entity_Id := Empty;
8636 For_Body : Boolean := False) return Node_Id
8637 is
8638 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
8639 Spec : Node_Id;
8640
8641 begin
8642 Set_Is_Public (Id, Is_Public (Tag_Typ));
8643
8644 -- The internal flag is set to mark these declarations because they have
8645 -- specific properties. First, they are primitives even if they are not
8646 -- defined in the type scope (the freezing point is not necessarily in
8647 -- the same scope). Second, the predefined equality can be overridden by
8648 -- a user-defined equality, no body will be generated in this case.
8649
8650 Set_Is_Internal (Id);
8651
8652 if not Debug_Generated_Code then
8653 Set_Debug_Info_Off (Id);
8654 end if;
8655
8656 if No (Ret_Type) then
8657 Spec :=
8658 Make_Procedure_Specification (Loc,
8659 Defining_Unit_Name => Id,
8660 Parameter_Specifications => Profile);
8661 else
8662 Spec :=
8663 Make_Function_Specification (Loc,
8664 Defining_Unit_Name => Id,
8665 Parameter_Specifications => Profile,
8666 Result_Definition =>
8667 New_Reference_To (Ret_Type, Loc));
8668 end if;
8669
8670 if Is_Interface (Tag_Typ) then
8671 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
8672
8673 -- If body case, return empty subprogram body. Note that this is ill-
8674 -- formed, because there is not even a null statement, and certainly not
8675 -- a return in the function case. The caller is expected to do surgery
8676 -- on the body to add the appropriate stuff.
8677
8678 elsif For_Body then
8679 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
8680
8681 -- For the case of an Input attribute predefined for an abstract type,
8682 -- generate an abstract specification. This will never be called, but we
8683 -- need the slot allocated in the dispatching table so that attributes
8684 -- typ'Class'Input and typ'Class'Output will work properly.
8685
8686 elsif Is_TSS (Name, TSS_Stream_Input)
8687 and then Is_Abstract_Type (Tag_Typ)
8688 then
8689 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
8690
8691 -- Normal spec case, where we return a subprogram declaration
8692
8693 else
8694 return Make_Subprogram_Declaration (Loc, Spec);
8695 end if;
8696 end Predef_Spec_Or_Body;
8697
8698 -----------------------------
8699 -- Predef_Stream_Attr_Spec --
8700 -----------------------------
8701
8702 function Predef_Stream_Attr_Spec
8703 (Loc : Source_Ptr;
8704 Tag_Typ : Entity_Id;
8705 Name : TSS_Name_Type;
8706 For_Body : Boolean := False) return Node_Id
8707 is
8708 Ret_Type : Entity_Id;
8709
8710 begin
8711 if Name = TSS_Stream_Input then
8712 Ret_Type := Tag_Typ;
8713 else
8714 Ret_Type := Empty;
8715 end if;
8716
8717 return Predef_Spec_Or_Body (Loc,
8718 Name => Make_TSS_Name (Tag_Typ, Name),
8719 Tag_Typ => Tag_Typ,
8720 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
8721 Ret_Type => Ret_Type,
8722 For_Body => For_Body);
8723 end Predef_Stream_Attr_Spec;
8724
8725 ---------------------------------
8726 -- Predefined_Primitive_Bodies --
8727 ---------------------------------
8728
8729 function Predefined_Primitive_Bodies
8730 (Tag_Typ : Entity_Id;
8731 Renamed_Eq : Entity_Id) return List_Id
8732 is
8733 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8734 Res : constant List_Id := New_List;
8735 Decl : Node_Id;
8736 Prim : Elmt_Id;
8737 Eq_Needed : Boolean;
8738 Eq_Name : Name_Id;
8739 Ent : Entity_Id;
8740
8741 pragma Warnings (Off, Ent);
8742
8743 begin
8744 pragma Assert (not Is_Interface (Tag_Typ));
8745
8746 -- See if we have a predefined "=" operator
8747
8748 if Present (Renamed_Eq) then
8749 Eq_Needed := True;
8750 Eq_Name := Chars (Renamed_Eq);
8751
8752 -- If the parent is an interface type then it has defined all the
8753 -- predefined primitives abstract and we need to check if the type
8754 -- has some user defined "=" function to avoid generating it.
8755
8756 elsif Is_Interface (Etype (Tag_Typ)) then
8757 Eq_Needed := True;
8758 Eq_Name := Name_Op_Eq;
8759
8760 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8761 while Present (Prim) loop
8762 if Chars (Node (Prim)) = Name_Op_Eq
8763 and then not Is_Internal (Node (Prim))
8764 then
8765 Eq_Needed := False;
8766 Eq_Name := No_Name;
8767 exit;
8768 end if;
8769
8770 Next_Elmt (Prim);
8771 end loop;
8772
8773 else
8774 Eq_Needed := False;
8775 Eq_Name := No_Name;
8776
8777 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
8778 while Present (Prim) loop
8779 if Chars (Node (Prim)) = Name_Op_Eq
8780 and then Is_Internal (Node (Prim))
8781 then
8782 Eq_Needed := True;
8783 Eq_Name := Name_Op_Eq;
8784 exit;
8785 end if;
8786
8787 Next_Elmt (Prim);
8788 end loop;
8789 end if;
8790
8791 -- Body of _Alignment
8792
8793 Decl := Predef_Spec_Or_Body (Loc,
8794 Tag_Typ => Tag_Typ,
8795 Name => Name_uAlignment,
8796 Profile => New_List (
8797 Make_Parameter_Specification (Loc,
8798 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8799 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8800
8801 Ret_Type => Standard_Integer,
8802 For_Body => True);
8803
8804 Set_Handled_Statement_Sequence (Decl,
8805 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8806 Make_Simple_Return_Statement (Loc,
8807 Expression =>
8808 Make_Attribute_Reference (Loc,
8809 Prefix => Make_Identifier (Loc, Name_X),
8810 Attribute_Name => Name_Alignment)))));
8811
8812 Append_To (Res, Decl);
8813
8814 -- Body of _Size
8815
8816 Decl := Predef_Spec_Or_Body (Loc,
8817 Tag_Typ => Tag_Typ,
8818 Name => Name_uSize,
8819 Profile => New_List (
8820 Make_Parameter_Specification (Loc,
8821 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8822 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8823
8824 Ret_Type => Standard_Long_Long_Integer,
8825 For_Body => True);
8826
8827 Set_Handled_Statement_Sequence (Decl,
8828 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8829 Make_Simple_Return_Statement (Loc,
8830 Expression =>
8831 Make_Attribute_Reference (Loc,
8832 Prefix => Make_Identifier (Loc, Name_X),
8833 Attribute_Name => Name_Size)))));
8834
8835 Append_To (Res, Decl);
8836
8837 -- Bodies for Dispatching stream IO routines. We need these only for
8838 -- non-limited types (in the limited case there is no dispatching).
8839 -- We also skip them if dispatching or finalization are not available.
8840
8841 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
8842 and then No (TSS (Tag_Typ, TSS_Stream_Read))
8843 then
8844 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
8845 Append_To (Res, Decl);
8846 end if;
8847
8848 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
8849 and then No (TSS (Tag_Typ, TSS_Stream_Write))
8850 then
8851 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
8852 Append_To (Res, Decl);
8853 end if;
8854
8855 -- Skip body of _Input for the abstract case, since the corresponding
8856 -- spec is abstract (see Predef_Spec_Or_Body).
8857
8858 if not Is_Abstract_Type (Tag_Typ)
8859 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
8860 and then No (TSS (Tag_Typ, TSS_Stream_Input))
8861 then
8862 Build_Record_Or_Elementary_Input_Function
8863 (Loc, Tag_Typ, Decl, Ent);
8864 Append_To (Res, Decl);
8865 end if;
8866
8867 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
8868 and then No (TSS (Tag_Typ, TSS_Stream_Output))
8869 then
8870 Build_Record_Or_Elementary_Output_Procedure
8871 (Loc, Tag_Typ, Decl, Ent);
8872 Append_To (Res, Decl);
8873 end if;
8874
8875 -- Ada 2005: Generate bodies for the following primitive operations for
8876 -- limited interfaces and synchronized types that implement a limited
8877 -- interface.
8878
8879 -- disp_asynchronous_select
8880 -- disp_conditional_select
8881 -- disp_get_prim_op_kind
8882 -- disp_get_task_id
8883 -- disp_timed_select
8884
8885 -- The interface versions will have null bodies
8886
8887 -- These operations cannot be implemented on VM targets, so we simply
8888 -- disable their generation in this case. Disable the generation of
8889 -- these bodies if No_Dispatching_Calls, Ravenscar or ZFP is active.
8890
8891 if Ada_Version >= Ada_2005
8892 and then Tagged_Type_Expansion
8893 and then not Is_Interface (Tag_Typ)
8894 and then
8895 ((Is_Interface (Etype (Tag_Typ))
8896 and then Is_Limited_Record (Etype (Tag_Typ)))
8897 or else (Is_Concurrent_Record_Type (Tag_Typ)
8898 and then Has_Interfaces (Tag_Typ)))
8899 and then not Restriction_Active (No_Dispatching_Calls)
8900 and then not Restriction_Active (No_Select_Statements)
8901 and then RTE_Available (RE_Select_Specific_Data)
8902 then
8903 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
8904 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
8905 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
8906 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
8907 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
8908 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
8909 end if;
8910
8911 if not Is_Limited_Type (Tag_Typ)
8912 and then not Is_Interface (Tag_Typ)
8913 then
8914 -- Body for equality
8915
8916 if Eq_Needed then
8917 Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
8918 Append_To (Res, Decl);
8919 end if;
8920
8921 -- Body for dispatching assignment
8922
8923 Decl :=
8924 Predef_Spec_Or_Body (Loc,
8925 Tag_Typ => Tag_Typ,
8926 Name => Name_uAssign,
8927 Profile => New_List (
8928 Make_Parameter_Specification (Loc,
8929 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
8930 Out_Present => True,
8931 Parameter_Type => New_Reference_To (Tag_Typ, Loc)),
8932
8933 Make_Parameter_Specification (Loc,
8934 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
8935 Parameter_Type => New_Reference_To (Tag_Typ, Loc))),
8936 For_Body => True);
8937
8938 Set_Handled_Statement_Sequence (Decl,
8939 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8940 Make_Assignment_Statement (Loc,
8941 Name => Make_Identifier (Loc, Name_X),
8942 Expression => Make_Identifier (Loc, Name_Y)))));
8943
8944 Append_To (Res, Decl);
8945 end if;
8946
8947 -- Generate dummy bodies for finalization actions of types that have
8948 -- no controlled components.
8949
8950 -- Skip this processing if we are in the finalization routine in the
8951 -- runtime itself, otherwise we get hopelessly circularly confused!
8952
8953 if In_Finalization_Root (Tag_Typ) then
8954 null;
8955
8956 -- Skip this if finalization is not available
8957
8958 elsif Restriction_Active (No_Finalization) then
8959 null;
8960
8961 elsif (Etype (Tag_Typ) = Tag_Typ
8962 or else Is_Controlled (Tag_Typ)
8963
8964 -- Ada 2005 (AI-251): We must also generate these subprograms
8965 -- if the immediate ancestor of Tag_Typ is an interface to
8966 -- ensure the correct initialization of its dispatch table.
8967
8968 or else (not Is_Interface (Tag_Typ)
8969 and then
8970 Is_Interface (Etype (Tag_Typ))))
8971 and then not Has_Controlled_Component (Tag_Typ)
8972 then
8973 if not Is_Limited_Type (Tag_Typ) then
8974 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
8975
8976 if Is_Controlled (Tag_Typ) then
8977 Set_Handled_Statement_Sequence (Decl,
8978 Make_Handled_Sequence_Of_Statements (Loc,
8979 Make_Adjust_Call (
8980 Ref => Make_Identifier (Loc, Name_V),
8981 Typ => Tag_Typ,
8982 Flist_Ref => Make_Identifier (Loc, Name_L),
8983 With_Attach => Make_Identifier (Loc, Name_B))));
8984
8985 else
8986 Set_Handled_Statement_Sequence (Decl,
8987 Make_Handled_Sequence_Of_Statements (Loc, New_List (
8988 Make_Null_Statement (Loc))));
8989 end if;
8990
8991 Append_To (Res, Decl);
8992 end if;
8993
8994 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
8995
8996 if Is_Controlled (Tag_Typ) then
8997 Set_Handled_Statement_Sequence (Decl,
8998 Make_Handled_Sequence_Of_Statements (Loc,
8999 Make_Final_Call (
9000 Ref => Make_Identifier (Loc, Name_V),
9001 Typ => Tag_Typ,
9002 With_Detach => Make_Identifier (Loc, Name_B))));
9003
9004 else
9005 Set_Handled_Statement_Sequence (Decl,
9006 Make_Handled_Sequence_Of_Statements (Loc, New_List (
9007 Make_Null_Statement (Loc))));
9008 end if;
9009
9010 Append_To (Res, Decl);
9011 end if;
9012
9013 return Res;
9014 end Predefined_Primitive_Bodies;
9015
9016 ---------------------------------
9017 -- Predefined_Primitive_Freeze --
9018 ---------------------------------
9019
9020 function Predefined_Primitive_Freeze
9021 (Tag_Typ : Entity_Id) return List_Id
9022 is
9023 Res : constant List_Id := New_List;
9024 Prim : Elmt_Id;
9025 Frnodes : List_Id;
9026
9027 begin
9028 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9029 while Present (Prim) loop
9030 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
9031 Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
9032
9033 if Present (Frnodes) then
9034 Append_List_To (Res, Frnodes);
9035 end if;
9036 end if;
9037
9038 Next_Elmt (Prim);
9039 end loop;
9040
9041 return Res;
9042 end Predefined_Primitive_Freeze;
9043
9044 -------------------------
9045 -- Stream_Operation_OK --
9046 -------------------------
9047
9048 function Stream_Operation_OK
9049 (Typ : Entity_Id;
9050 Operation : TSS_Name_Type) return Boolean
9051 is
9052 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
9053
9054 begin
9055 -- Special case of a limited type extension: a default implementation
9056 -- of the stream attributes Read or Write exists if that attribute
9057 -- has been specified or is available for an ancestor type; a default
9058 -- implementation of the attribute Output (resp. Input) exists if the
9059 -- attribute has been specified or Write (resp. Read) is available for
9060 -- an ancestor type. The last condition only applies under Ada 2005.
9061
9062 if Is_Limited_Type (Typ)
9063 and then Is_Tagged_Type (Typ)
9064 then
9065 if Operation = TSS_Stream_Read then
9066 Has_Predefined_Or_Specified_Stream_Attribute :=
9067 Has_Specified_Stream_Read (Typ);
9068
9069 elsif Operation = TSS_Stream_Write then
9070 Has_Predefined_Or_Specified_Stream_Attribute :=
9071 Has_Specified_Stream_Write (Typ);
9072
9073 elsif Operation = TSS_Stream_Input then
9074 Has_Predefined_Or_Specified_Stream_Attribute :=
9075 Has_Specified_Stream_Input (Typ)
9076 or else
9077 (Ada_Version >= Ada_2005
9078 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
9079
9080 elsif Operation = TSS_Stream_Output then
9081 Has_Predefined_Or_Specified_Stream_Attribute :=
9082 Has_Specified_Stream_Output (Typ)
9083 or else
9084 (Ada_Version >= Ada_2005
9085 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
9086 end if;
9087
9088 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
9089
9090 if not Has_Predefined_Or_Specified_Stream_Attribute
9091 and then Is_Derived_Type (Typ)
9092 and then (Operation = TSS_Stream_Read
9093 or else Operation = TSS_Stream_Write)
9094 then
9095 Has_Predefined_Or_Specified_Stream_Attribute :=
9096 Present
9097 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
9098 end if;
9099 end if;
9100
9101 -- If the type is not limited, or else is limited but the attribute is
9102 -- explicitly specified or is predefined for the type, then return True,
9103 -- unless other conditions prevail, such as restrictions prohibiting
9104 -- streams or dispatching operations. We also return True for limited
9105 -- interfaces, because they may be extended by nonlimited types and
9106 -- permit inheritance in this case (addresses cases where an abstract
9107 -- extension doesn't get 'Input declared, as per comments below, but
9108 -- 'Class'Input must still be allowed). Note that attempts to apply
9109 -- stream attributes to a limited interface or its class-wide type
9110 -- (or limited extensions thereof) will still get properly rejected
9111 -- by Check_Stream_Attribute.
9112
9113 -- We exclude the Input operation from being a predefined subprogram in
9114 -- the case where the associated type is an abstract extension, because
9115 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
9116 -- we don't want an abstract version created because types derived from
9117 -- the abstract type may not even have Input available (for example if
9118 -- derived from a private view of the abstract type that doesn't have
9119 -- a visible Input), but a VM such as .NET or the Java VM can treat the
9120 -- operation as inherited anyway, and we don't want an abstract function
9121 -- to be (implicitly) inherited in that case because it can lead to a VM
9122 -- exception.
9123
9124 return (not Is_Limited_Type (Typ)
9125 or else Is_Interface (Typ)
9126 or else Has_Predefined_Or_Specified_Stream_Attribute)
9127 and then (Operation /= TSS_Stream_Input
9128 or else not Is_Abstract_Type (Typ)
9129 or else not Is_Derived_Type (Typ))
9130 and then not Has_Unknown_Discriminants (Typ)
9131 and then not (Is_Interface (Typ)
9132 and then (Is_Task_Interface (Typ)
9133 or else Is_Protected_Interface (Typ)
9134 or else Is_Synchronized_Interface (Typ)))
9135 and then not Restriction_Active (No_Streams)
9136 and then not Restriction_Active (No_Dispatch)
9137 and then not No_Run_Time_Mode
9138 and then RTE_Available (RE_Tag)
9139 and then RTE_Available (RE_Root_Stream_Type);
9140 end Stream_Operation_OK;
9141
9142 end Exp_Ch3;