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