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