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