2015-09-28 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / ada / exp_ch3.adb
blob885e63a4ae9d80387d37fa8d2186933de76ff84f
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-2015, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Aspects; use Aspects;
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Aggr; use Exp_Aggr;
32 with Exp_Atag; use Exp_Atag;
33 with Exp_Ch4; use Exp_Ch4;
34 with Exp_Ch6; use Exp_Ch6;
35 with Exp_Ch7; use Exp_Ch7;
36 with Exp_Ch9; use Exp_Ch9;
37 with Exp_Ch11; use Exp_Ch11;
38 with Exp_Dbug; use Exp_Dbug;
39 with Exp_Disp; use Exp_Disp;
40 with Exp_Dist; use Exp_Dist;
41 with Exp_Smem; use Exp_Smem;
42 with Exp_Strm; use Exp_Strm;
43 with Exp_Tss; use Exp_Tss;
44 with Exp_Util; use Exp_Util;
45 with Freeze; use Freeze;
46 with Ghost; use Ghost;
47 with Inline; use Inline;
48 with Namet; use Namet;
49 with Nlists; use Nlists;
50 with Nmake; use Nmake;
51 with Opt; use Opt;
52 with Restrict; use Restrict;
53 with Rident; use Rident;
54 with Rtsfind; use Rtsfind;
55 with Sem; use Sem;
56 with Sem_Aux; use Sem_Aux;
57 with Sem_Attr; use Sem_Attr;
58 with Sem_Cat; use Sem_Cat;
59 with Sem_Ch3; use Sem_Ch3;
60 with Sem_Ch6; use Sem_Ch6;
61 with Sem_Ch8; use Sem_Ch8;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Disp; use Sem_Disp;
64 with Sem_Eval; use Sem_Eval;
65 with Sem_Mech; use Sem_Mech;
66 with Sem_Res; use Sem_Res;
67 with Sem_SCIL; use Sem_SCIL;
68 with Sem_Type; use Sem_Type;
69 with Sem_Util; use Sem_Util;
70 with Sinfo; use Sinfo;
71 with Stand; use Stand;
72 with Snames; use Snames;
73 with Targparm; use Targparm;
74 with Tbuild; use Tbuild;
75 with Ttypes; use Ttypes;
76 with Validsw; use Validsw;
78 package body Exp_Ch3 is
80 -----------------------
81 -- Local Subprograms --
82 -----------------------
84 procedure Adjust_Discriminants (Rtype : Entity_Id);
85 -- This is used when freezing a record type. It attempts to construct
86 -- more restrictive subtypes for discriminants so that the max size of
87 -- the record can be calculated more accurately. See the body of this
88 -- procedure for details.
90 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id);
91 -- Build initialization procedure for given array type. Nod is a node
92 -- used for attachment of any actions required in its construction.
93 -- It also supplies the source location used for the procedure.
95 function Build_Array_Invariant_Proc
96 (A_Type : Entity_Id;
97 Nod : Node_Id) return Node_Id;
98 -- If the component of type of array type has invariants, build procedure
99 -- that checks invariant on all components of the array. Ada 2012 specifies
100 -- that an invariant on some type T must be applied to in-out parameters
101 -- and return values that include a part of type T. If the array type has
102 -- an otherwise specified invariant, the component check procedure is
103 -- called from within the user-specified invariant. Otherwise this becomes
104 -- the invariant procedure for the array type.
106 function Build_Record_Invariant_Proc
107 (R_Type : Entity_Id;
108 Nod : Node_Id) return Node_Id;
109 -- Ditto for record types.
111 function Build_Discriminant_Formals
112 (Rec_Id : Entity_Id;
113 Use_Dl : Boolean) return List_Id;
114 -- This function uses the discriminants of a type to build a list of
115 -- formal parameters, used in Build_Init_Procedure among other places.
116 -- If the flag Use_Dl is set, the list is built using the already
117 -- defined discriminals of the type, as is the case for concurrent
118 -- types with discriminants. Otherwise new identifiers are created,
119 -- with the source names of the discriminants.
121 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id;
122 -- This function builds a static aggregate that can serve as the initial
123 -- value for an array type whose bounds are static, and whose component
124 -- type is a composite type that has a static equivalent aggregate.
125 -- The equivalent array aggregate is used both for object initialization
126 -- and for component initialization, when used in the following function.
128 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id;
129 -- This function builds a static aggregate that can serve as the initial
130 -- value for a record type whose components are scalar and initialized
131 -- with compile-time values, or arrays with similar initialization or
132 -- defaults. When possible, initialization of an object of the type can
133 -- be achieved by using a copy of the aggregate as an initial value, thus
134 -- removing the implicit call that would otherwise constitute elaboration
135 -- code.
137 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id);
138 -- Build record initialization procedure. N is the type declaration
139 -- node, and Rec_Ent is the corresponding entity for the record type.
141 procedure Build_Slice_Assignment (Typ : Entity_Id);
142 -- Build assignment procedure for one-dimensional arrays of controlled
143 -- types. Other array and slice assignments are expanded in-line, but
144 -- the code expansion for controlled components (when control actions
145 -- are active) can lead to very large blocks that GCC3 handles poorly.
147 procedure Build_Untagged_Equality (Typ : Entity_Id);
148 -- AI05-0123: Equality on untagged records composes. This procedure
149 -- builds the equality routine for an untagged record that has components
150 -- of a record type that has user-defined primitive equality operations.
151 -- The resulting operation is a TSS subprogram.
153 procedure Build_Variant_Record_Equality (Typ : Entity_Id);
154 -- Create An Equality function for the untagged variant record Typ and
155 -- attach it to the TSS list
157 procedure Check_Stream_Attributes (Typ : Entity_Id);
158 -- Check that if a limited extension has a parent with user-defined stream
159 -- attributes, and does not itself have user-defined stream-attributes,
160 -- then any limited component of the extension also has the corresponding
161 -- user-defined stream attributes.
163 procedure Clean_Task_Names
164 (Typ : Entity_Id;
165 Proc_Id : Entity_Id);
166 -- If an initialization procedure includes calls to generate names
167 -- for task subcomponents, indicate that secondary stack cleanup is
168 -- needed after an initialization. Typ is the component type, and Proc_Id
169 -- the initialization procedure for the enclosing composite type.
171 procedure Expand_Freeze_Array_Type (N : Node_Id);
172 -- Freeze an array type. Deals with building the initialization procedure,
173 -- creating the packed array type for a packed array and also with the
174 -- creation of the controlling procedures for the controlled case. The
175 -- argument N is the N_Freeze_Entity node for the type.
177 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id);
178 -- Freeze a class-wide type. Build routine Finalize_Address for the purpose
179 -- of finalizing controlled derivations from the class-wide's root type.
181 procedure Expand_Freeze_Enumeration_Type (N : Node_Id);
182 -- Freeze enumeration type with non-standard representation. Builds the
183 -- array and function needed to convert between enumeration pos and
184 -- enumeration representation values. N is the N_Freeze_Entity node
185 -- for the type.
187 procedure Expand_Freeze_Record_Type (N : Node_Id);
188 -- Freeze record type. Builds all necessary discriminant checking
189 -- and other ancillary functions, and builds dispatch tables where
190 -- needed. The argument N is the N_Freeze_Entity node. This processing
191 -- applies only to E_Record_Type entities, not to class wide types,
192 -- record subtypes, or private types.
194 procedure Expand_Tagged_Root (T : Entity_Id);
195 -- Add a field _Tag at the beginning of the record. This field carries
196 -- the value of the access to the Dispatch table. This procedure is only
197 -- called on root type, the _Tag field being inherited by the descendants.
199 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id);
200 -- Treat user-defined stream operations as renaming_as_body if the
201 -- subprogram they rename is not frozen when the type is frozen.
203 procedure Insert_Component_Invariant_Checks
204 (N : Node_Id;
205 Typ : Entity_Id;
206 Proc : Node_Id);
207 -- If a composite type has invariants and also has components with defined
208 -- invariants. the component invariant procedure is inserted into the user-
209 -- defined invariant procedure and added to the checks to be performed.
211 procedure Initialization_Warning (E : Entity_Id);
212 -- If static elaboration of the package is requested, indicate
213 -- when a type does meet the conditions for static initialization. If
214 -- E is a type, it has components that have no static initialization.
215 -- if E is an entity, its initial expression is not compile-time known.
217 function Init_Formals (Typ : Entity_Id) return List_Id;
218 -- This function builds the list of formals for an initialization routine.
219 -- The first formal is always _Init with the given type. For task value
220 -- record types and types containing tasks, three additional formals are
221 -- added:
223 -- _Master : Master_Id
224 -- _Chain : in out Activation_Chain
225 -- _Task_Name : String
227 -- The caller must append additional entries for discriminants if required.
229 function In_Runtime (E : Entity_Id) return Boolean;
230 -- Check if E is defined in the RTL (in a child of Ada or System). Used
231 -- to avoid to bring in the overhead of _Input, _Output for tagged types.
233 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean;
234 -- Returns true if Prim is a user defined equality function
236 function Make_Eq_Body
237 (Typ : Entity_Id;
238 Eq_Name : Name_Id) return Node_Id;
239 -- Build the body of a primitive equality operation for a tagged record
240 -- type, or in Ada 2012 for any record type that has components with a
241 -- user-defined equality. Factored out of Predefined_Primitive_Bodies.
243 function Make_Eq_Case
244 (E : Entity_Id;
245 CL : Node_Id;
246 Discrs : Elist_Id := New_Elmt_List) return List_Id;
247 -- Building block for variant record equality. Defined to share the code
248 -- between the tagged and untagged case. Given a Component_List node CL,
249 -- it generates an 'if' followed by a 'case' statement that compares all
250 -- components of local temporaries named X and Y (that are declared as
251 -- formals at some upper level). E provides the Sloc to be used for the
252 -- generated code.
254 -- IF E is an unchecked_union, Discrs is the list of formals created for
255 -- the inferred discriminants of one operand. These formals are used in
256 -- the generated case statements for each variant of the unchecked union.
258 function Make_Eq_If
259 (E : Entity_Id;
260 L : List_Id) return Node_Id;
261 -- Building block for variant record equality. Defined to share the code
262 -- between the tagged and untagged case. Given the list of components
263 -- (or discriminants) L, it generates a return statement that compares all
264 -- components of local temporaries named X and Y (that are declared as
265 -- formals at some upper level). E provides the Sloc to be used for the
266 -- generated code.
268 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id;
269 -- Search for a renaming of the inequality dispatching primitive of
270 -- this tagged type. If found then build and return the corresponding
271 -- rename-as-body inequality subprogram; otherwise return Empty.
273 procedure Make_Predefined_Primitive_Specs
274 (Tag_Typ : Entity_Id;
275 Predef_List : out List_Id;
276 Renamed_Eq : out Entity_Id);
277 -- Create a list with the specs of the predefined primitive operations.
278 -- For tagged types that are interfaces all these primitives are defined
279 -- abstract.
281 -- The following entries are present for all tagged types, and provide
282 -- the results of the corresponding attribute applied to the object.
283 -- Dispatching is required in general, since the result of the attribute
284 -- will vary with the actual object subtype.
286 -- _size provides result of 'Size attribute
287 -- typSR provides result of 'Read attribute
288 -- typSW provides result of 'Write attribute
289 -- typSI provides result of 'Input attribute
290 -- typSO provides result of 'Output attribute
292 -- The following entries are additionally present for non-limited tagged
293 -- types, and implement additional dispatching operations for predefined
294 -- operations:
296 -- _equality implements "=" operator
297 -- _assign implements assignment operation
298 -- typDF implements deep finalization
299 -- typDA implements deep adjust
301 -- The latter two are empty procedures unless the type contains some
302 -- controlled components that require finalization actions (the deep
303 -- in the name refers to the fact that the action applies to components).
305 -- The list is returned in Predef_List. The Parameter Renamed_Eq either
306 -- returns the value Empty, or else the defining unit name for the
307 -- predefined equality function in the case where the type has a primitive
308 -- operation that is a renaming of predefined equality (but only if there
309 -- is also an overriding user-defined equality function). The returned
310 -- Renamed_Eq will be passed to the corresponding parameter of
311 -- Predefined_Primitive_Bodies.
313 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean;
314 -- Returns True if there are representation clauses for type T that are not
315 -- inherited. If the result is false, the init_proc and the discriminant
316 -- checking functions of the parent can be reused by a derived type.
318 procedure Make_Controlling_Function_Wrappers
319 (Tag_Typ : Entity_Id;
320 Decl_List : out List_Id;
321 Body_List : out List_Id);
322 -- Ada 2005 (AI-391): Makes specs and bodies for the wrapper functions
323 -- associated with inherited functions with controlling results which
324 -- are not overridden. The body of each wrapper function consists solely
325 -- of a return statement whose expression is an extension aggregate
326 -- invoking the inherited subprogram's parent subprogram and extended
327 -- with a null association list.
329 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id;
330 -- Ada 2005 (AI-251): Makes specs for null procedures associated with any
331 -- null procedures inherited from an interface type that have not been
332 -- overridden. Only one null procedure will be created for a given set of
333 -- inherited null procedures with homographic profiles.
335 function Predef_Spec_Or_Body
336 (Loc : Source_Ptr;
337 Tag_Typ : Entity_Id;
338 Name : Name_Id;
339 Profile : List_Id;
340 Ret_Type : Entity_Id := Empty;
341 For_Body : Boolean := False) return Node_Id;
342 -- This function generates the appropriate expansion for a predefined
343 -- primitive operation specified by its name, parameter profile and
344 -- return type (Empty means this is a procedure). If For_Body is false,
345 -- then the returned node is a subprogram declaration. If For_Body is
346 -- true, then the returned node is a empty subprogram body containing
347 -- no declarations and no statements.
349 function Predef_Stream_Attr_Spec
350 (Loc : Source_Ptr;
351 Tag_Typ : Entity_Id;
352 Name : TSS_Name_Type;
353 For_Body : Boolean := False) return Node_Id;
354 -- Specialized version of Predef_Spec_Or_Body that apply to read, write,
355 -- input and output attribute whose specs are constructed in Exp_Strm.
357 function Predef_Deep_Spec
358 (Loc : Source_Ptr;
359 Tag_Typ : Entity_Id;
360 Name : TSS_Name_Type;
361 For_Body : Boolean := False) return Node_Id;
362 -- Specialized version of Predef_Spec_Or_Body that apply to _deep_adjust
363 -- and _deep_finalize
365 function Predefined_Primitive_Bodies
366 (Tag_Typ : Entity_Id;
367 Renamed_Eq : Entity_Id) return List_Id;
368 -- Create the bodies of the predefined primitives that are described in
369 -- Predefined_Primitive_Specs. When not empty, Renamed_Eq must denote
370 -- the defining unit name of the type's predefined equality as returned
371 -- by Make_Predefined_Primitive_Specs.
373 function Predefined_Primitive_Freeze (Tag_Typ : Entity_Id) return List_Id;
374 -- Freeze entities of all predefined primitive operations. This is needed
375 -- because the bodies of these operations do not normally do any freezing.
377 function Stream_Operation_OK
378 (Typ : Entity_Id;
379 Operation : TSS_Name_Type) return Boolean;
380 -- Check whether the named stream operation must be emitted for a given
381 -- type. The rules for inheritance of stream attributes by type extensions
382 -- are enforced by this function. Furthermore, various restrictions prevent
383 -- the generation of these operations, as a useful optimization or for
384 -- certification purposes and to save unnecessary generated code.
386 --------------------------
387 -- Adjust_Discriminants --
388 --------------------------
390 -- This procedure attempts to define subtypes for discriminants that are
391 -- more restrictive than those declared. Such a replacement is possible if
392 -- we can demonstrate that values outside the restricted range would cause
393 -- constraint errors in any case. The advantage of restricting the
394 -- discriminant types in this way is that the maximum size of the variant
395 -- record can be calculated more conservatively.
397 -- An example of a situation in which we can perform this type of
398 -- restriction is the following:
400 -- subtype B is range 1 .. 10;
401 -- type Q is array (B range <>) of Integer;
403 -- type V (N : Natural) is record
404 -- C : Q (1 .. N);
405 -- end record;
407 -- In this situation, we can restrict the upper bound of N to 10, since
408 -- any larger value would cause a constraint error in any case.
410 -- There are many situations in which such restriction is possible, but
411 -- for now, we just look for cases like the above, where the component
412 -- in question is a one dimensional array whose upper bound is one of
413 -- the record discriminants. Also the component must not be part of
414 -- any variant part, since then the component does not always exist.
416 procedure Adjust_Discriminants (Rtype : Entity_Id) is
417 Loc : constant Source_Ptr := Sloc (Rtype);
418 Comp : Entity_Id;
419 Ctyp : Entity_Id;
420 Ityp : Entity_Id;
421 Lo : Node_Id;
422 Hi : Node_Id;
423 P : Node_Id;
424 Loval : Uint;
425 Discr : Entity_Id;
426 Dtyp : Entity_Id;
427 Dhi : Node_Id;
428 Dhiv : Uint;
429 Ahi : Node_Id;
430 Ahiv : Uint;
431 Tnn : Entity_Id;
433 begin
434 Comp := First_Component (Rtype);
435 while Present (Comp) loop
437 -- If our parent is a variant, quit, we do not look at components
438 -- that are in variant parts, because they may not always exist.
440 P := Parent (Comp); -- component declaration
441 P := Parent (P); -- component list
443 exit when Nkind (Parent (P)) = N_Variant;
445 -- We are looking for a one dimensional array type
447 Ctyp := Etype (Comp);
449 if not Is_Array_Type (Ctyp) or else Number_Dimensions (Ctyp) > 1 then
450 goto Continue;
451 end if;
453 -- The lower bound must be constant, and the upper bound is a
454 -- discriminant (which is a discriminant of the current record).
456 Ityp := Etype (First_Index (Ctyp));
457 Lo := Type_Low_Bound (Ityp);
458 Hi := Type_High_Bound (Ityp);
460 if not Compile_Time_Known_Value (Lo)
461 or else Nkind (Hi) /= N_Identifier
462 or else No (Entity (Hi))
463 or else Ekind (Entity (Hi)) /= E_Discriminant
464 then
465 goto Continue;
466 end if;
468 -- We have an array with appropriate bounds
470 Loval := Expr_Value (Lo);
471 Discr := Entity (Hi);
472 Dtyp := Etype (Discr);
474 -- See if the discriminant has a known upper bound
476 Dhi := Type_High_Bound (Dtyp);
478 if not Compile_Time_Known_Value (Dhi) then
479 goto Continue;
480 end if;
482 Dhiv := Expr_Value (Dhi);
484 -- See if base type of component array has known upper bound
486 Ahi := Type_High_Bound (Etype (First_Index (Base_Type (Ctyp))));
488 if not Compile_Time_Known_Value (Ahi) then
489 goto Continue;
490 end if;
492 Ahiv := Expr_Value (Ahi);
494 -- The condition for doing the restriction is that the high bound
495 -- of the discriminant is greater than the low bound of the array,
496 -- and is also greater than the high bound of the base type index.
498 if Dhiv > Loval and then Dhiv > Ahiv then
500 -- We can reset the upper bound of the discriminant type to
501 -- whichever is larger, the low bound of the component, or
502 -- the high bound of the base type array index.
504 -- We build a subtype that is declared as
506 -- subtype Tnn is discr_type range discr_type'First .. max;
508 -- And insert this declaration into the tree. The type of the
509 -- discriminant is then reset to this more restricted subtype.
511 Tnn := Make_Temporary (Loc, 'T');
513 Insert_Action (Declaration_Node (Rtype),
514 Make_Subtype_Declaration (Loc,
515 Defining_Identifier => Tnn,
516 Subtype_Indication =>
517 Make_Subtype_Indication (Loc,
518 Subtype_Mark => New_Occurrence_Of (Dtyp, Loc),
519 Constraint =>
520 Make_Range_Constraint (Loc,
521 Range_Expression =>
522 Make_Range (Loc,
523 Low_Bound =>
524 Make_Attribute_Reference (Loc,
525 Attribute_Name => Name_First,
526 Prefix => New_Occurrence_Of (Dtyp, Loc)),
527 High_Bound =>
528 Make_Integer_Literal (Loc,
529 Intval => UI_Max (Loval, Ahiv)))))));
531 Set_Etype (Discr, Tnn);
532 end if;
534 <<Continue>>
535 Next_Component (Comp);
536 end loop;
537 end Adjust_Discriminants;
539 ---------------------------
540 -- Build_Array_Init_Proc --
541 ---------------------------
543 procedure Build_Array_Init_Proc (A_Type : Entity_Id; Nod : Node_Id) is
544 Comp_Type : constant Entity_Id := Component_Type (A_Type);
545 Body_Stmts : List_Id;
546 Has_Default_Init : Boolean;
547 Index_List : List_Id;
548 Loc : Source_Ptr;
549 Proc_Id : Entity_Id;
551 function Init_Component return List_Id;
552 -- Create one statement to initialize one array component, designated
553 -- by a full set of indexes.
555 function Init_One_Dimension (N : Int) return List_Id;
556 -- Create loop to initialize one dimension of the array. The single
557 -- statement in the loop body initializes the inner dimensions if any,
558 -- or else the single component. Note that this procedure is called
559 -- recursively, with N being the dimension to be initialized. A call
560 -- with N greater than the number of dimensions simply generates the
561 -- component initialization, terminating the recursion.
563 --------------------
564 -- Init_Component --
565 --------------------
567 function Init_Component return List_Id is
568 Comp : Node_Id;
570 begin
571 Comp :=
572 Make_Indexed_Component (Loc,
573 Prefix => Make_Identifier (Loc, Name_uInit),
574 Expressions => Index_List);
576 if Has_Default_Aspect (A_Type) then
577 Set_Assignment_OK (Comp);
578 return New_List (
579 Make_Assignment_Statement (Loc,
580 Name => Comp,
581 Expression =>
582 Convert_To (Comp_Type,
583 Default_Aspect_Component_Value (First_Subtype (A_Type)))));
585 elsif Needs_Simple_Initialization (Comp_Type) then
586 Set_Assignment_OK (Comp);
587 return New_List (
588 Make_Assignment_Statement (Loc,
589 Name => Comp,
590 Expression =>
591 Get_Simple_Init_Val
592 (Comp_Type, Nod, Component_Size (A_Type))));
594 else
595 Clean_Task_Names (Comp_Type, Proc_Id);
596 return
597 Build_Initialization_Call
598 (Loc, Comp, Comp_Type,
599 In_Init_Proc => True,
600 Enclos_Type => A_Type);
601 end if;
602 end Init_Component;
604 ------------------------
605 -- Init_One_Dimension --
606 ------------------------
608 function Init_One_Dimension (N : Int) return List_Id is
609 Index : Entity_Id;
611 begin
612 -- If the component does not need initializing, then there is nothing
613 -- to do here, so we return a null body. This occurs when generating
614 -- the dummy Init_Proc needed for Initialize_Scalars processing.
616 if not Has_Non_Null_Base_Init_Proc (Comp_Type)
617 and then not Needs_Simple_Initialization (Comp_Type)
618 and then not Has_Task (Comp_Type)
619 and then not Has_Default_Aspect (A_Type)
620 then
621 return New_List (Make_Null_Statement (Loc));
623 -- If all dimensions dealt with, we simply initialize the component
625 elsif N > Number_Dimensions (A_Type) then
626 return Init_Component;
628 -- Here we generate the required loop
630 else
631 Index :=
632 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
634 Append (New_Occurrence_Of (Index, Loc), Index_List);
636 return New_List (
637 Make_Implicit_Loop_Statement (Nod,
638 Identifier => Empty,
639 Iteration_Scheme =>
640 Make_Iteration_Scheme (Loc,
641 Loop_Parameter_Specification =>
642 Make_Loop_Parameter_Specification (Loc,
643 Defining_Identifier => Index,
644 Discrete_Subtype_Definition =>
645 Make_Attribute_Reference (Loc,
646 Prefix =>
647 Make_Identifier (Loc, Name_uInit),
648 Attribute_Name => Name_Range,
649 Expressions => New_List (
650 Make_Integer_Literal (Loc, N))))),
651 Statements => Init_One_Dimension (N + 1)));
652 end if;
653 end Init_One_Dimension;
655 -- Start of processing for Build_Array_Init_Proc
657 begin
658 -- The init proc is created when analyzing the freeze node for the type,
659 -- but it properly belongs with the array type declaration. However, if
660 -- the freeze node is for a subtype of a type declared in another unit
661 -- it seems preferable to use the freeze node as the source location of
662 -- the init proc. In any case this is preferable for gcov usage, and
663 -- the Sloc is not otherwise used by the compiler.
665 if In_Open_Scopes (Scope (A_Type)) then
666 Loc := Sloc (A_Type);
667 else
668 Loc := Sloc (Nod);
669 end if;
671 -- Nothing to generate in the following cases:
673 -- 1. Initialization is suppressed for the type
674 -- 2. The type is a value type, in the CIL sense.
675 -- 3. The type has CIL/JVM convention.
676 -- 4. An initialization already exists for the base type
678 if Initialization_Suppressed (A_Type)
679 or else Is_Value_Type (Comp_Type)
680 or else Convention (A_Type) = Convention_CIL
681 or else Convention (A_Type) = Convention_Java
682 or else Present (Base_Init_Proc (A_Type))
683 then
684 return;
685 end if;
687 Index_List := New_List;
689 -- We need an initialization procedure if any of the following is true:
691 -- 1. The component type has an initialization procedure
692 -- 2. The component type needs simple initialization
693 -- 3. Tasks are present
694 -- 4. The type is marked as a public entity
695 -- 5. The array type has a Default_Component_Value aspect
697 -- The reason for the public entity test is to deal properly with the
698 -- Initialize_Scalars pragma. This pragma can be set in the client and
699 -- not in the declaring package, this means the client will make a call
700 -- to the initialization procedure (because one of conditions 1-3 must
701 -- apply in this case), and we must generate a procedure (even if it is
702 -- null) to satisfy the call in this case.
704 -- Exception: do not build an array init_proc for a type whose root
705 -- type is Standard.String or Standard.Wide_[Wide_]String, since there
706 -- is no place to put the code, and in any case we handle initialization
707 -- of such types (in the Initialize_Scalars case, that's the only time
708 -- the issue arises) in a special manner anyway which does not need an
709 -- init_proc.
711 Has_Default_Init := Has_Non_Null_Base_Init_Proc (Comp_Type)
712 or else Needs_Simple_Initialization (Comp_Type)
713 or else Has_Task (Comp_Type)
714 or else Has_Default_Aspect (A_Type);
716 if Has_Default_Init
717 or else (not Restriction_Active (No_Initialize_Scalars)
718 and then Is_Public (A_Type)
719 and then not Is_Standard_String_Type (A_Type))
720 then
721 Proc_Id :=
722 Make_Defining_Identifier (Loc,
723 Chars => Make_Init_Proc_Name (A_Type));
725 -- If No_Default_Initialization restriction is active, then we don't
726 -- want to build an init_proc, but we need to mark that an init_proc
727 -- would be needed if this restriction was not active (so that we can
728 -- detect attempts to call it), so set a dummy init_proc in place.
729 -- This is only done though when actual default initialization is
730 -- needed (and not done when only Is_Public is True), since otherwise
731 -- objects such as arrays of scalars could be wrongly flagged as
732 -- violating the restriction.
734 if Restriction_Active (No_Default_Initialization) then
735 if Has_Default_Init then
736 Set_Init_Proc (A_Type, Proc_Id);
737 end if;
739 return;
740 end if;
742 Body_Stmts := Init_One_Dimension (1);
744 Discard_Node (
745 Make_Subprogram_Body (Loc,
746 Specification =>
747 Make_Procedure_Specification (Loc,
748 Defining_Unit_Name => Proc_Id,
749 Parameter_Specifications => Init_Formals (A_Type)),
750 Declarations => New_List,
751 Handled_Statement_Sequence =>
752 Make_Handled_Sequence_Of_Statements (Loc,
753 Statements => Body_Stmts)));
755 Set_Ekind (Proc_Id, E_Procedure);
756 Set_Is_Public (Proc_Id, Is_Public (A_Type));
757 Set_Is_Internal (Proc_Id);
758 Set_Has_Completion (Proc_Id);
760 if not Debug_Generated_Code then
761 Set_Debug_Info_Off (Proc_Id);
762 end if;
764 -- Set inlined unless tasks are around, in which case we do not
765 -- want to inline, because nested stuff may cause difficulties in
766 -- inter-unit inlining, and furthermore there is in any case no
767 -- point in inlining such complex init procs.
769 if not Has_Task (Proc_Id) then
770 Set_Is_Inlined (Proc_Id);
771 end if;
773 -- Associate Init_Proc with type, and determine if the procedure
774 -- is null (happens because of the Initialize_Scalars pragma case,
775 -- where we have to generate a null procedure in case it is called
776 -- by a client with Initialize_Scalars set). Such procedures have
777 -- to be generated, but do not have to be called, so we mark them
778 -- as null to suppress the call.
780 Set_Init_Proc (A_Type, Proc_Id);
782 if List_Length (Body_Stmts) = 1
784 -- We must skip SCIL nodes because they may have been added to this
785 -- list by Insert_Actions.
787 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
788 then
789 Set_Is_Null_Init_Proc (Proc_Id);
791 else
792 -- Try to build a static aggregate to statically initialize
793 -- objects of the type. This can only be done for constrained
794 -- one-dimensional arrays with static bounds.
796 Set_Static_Initialization
797 (Proc_Id,
798 Build_Equivalent_Array_Aggregate (First_Subtype (A_Type)));
799 end if;
800 end if;
801 end Build_Array_Init_Proc;
803 --------------------------------
804 -- Build_Array_Invariant_Proc --
805 --------------------------------
807 function Build_Array_Invariant_Proc
808 (A_Type : Entity_Id;
809 Nod : Node_Id) return Node_Id
811 Loc : constant Source_Ptr := Sloc (Nod);
813 Object_Name : constant Name_Id := New_Internal_Name ('I');
814 -- Name for argument of invariant procedure
816 Object_Entity : constant Node_Id :=
817 Make_Defining_Identifier (Loc, Object_Name);
818 -- The procedure declaration entity for the argument
820 Body_Stmts : List_Id;
821 Index_List : List_Id;
822 Proc_Id : Entity_Id;
823 Proc_Body : Node_Id;
825 function Build_Component_Invariant_Call return Node_Id;
826 -- Create one statement to verify invariant on one array component,
827 -- designated by a full set of indexes.
829 function Check_One_Dimension (N : Int) return List_Id;
830 -- Create loop to check on one dimension of the array. The single
831 -- statement in the loop body checks the inner dimensions if any, or
832 -- else a single component. This procedure is called recursively, with
833 -- N being the dimension to be initialized. A call with N greater than
834 -- the number of dimensions generates the component initialization
835 -- and terminates the recursion.
837 ------------------------------------
838 -- Build_Component_Invariant_Call --
839 ------------------------------------
841 function Build_Component_Invariant_Call return Node_Id is
842 Comp : Node_Id;
843 begin
844 Comp :=
845 Make_Indexed_Component (Loc,
846 Prefix => New_Occurrence_Of (Object_Entity, Loc),
847 Expressions => Index_List);
848 return
849 Make_Procedure_Call_Statement (Loc,
850 Name =>
851 New_Occurrence_Of
852 (Invariant_Procedure (Component_Type (A_Type)), Loc),
853 Parameter_Associations => New_List (Comp));
854 end Build_Component_Invariant_Call;
856 -------------------------
857 -- Check_One_Dimension --
858 -------------------------
860 function Check_One_Dimension (N : Int) return List_Id is
861 Index : Entity_Id;
863 begin
864 -- If all dimensions dealt with, we simply check invariant of the
865 -- component.
867 if N > Number_Dimensions (A_Type) then
868 return New_List (Build_Component_Invariant_Call);
870 -- Else generate one loop and recurse
872 else
873 Index :=
874 Make_Defining_Identifier (Loc, New_External_Name ('J', N));
876 Append (New_Occurrence_Of (Index, Loc), Index_List);
878 return New_List (
879 Make_Implicit_Loop_Statement (Nod,
880 Identifier => Empty,
881 Iteration_Scheme =>
882 Make_Iteration_Scheme (Loc,
883 Loop_Parameter_Specification =>
884 Make_Loop_Parameter_Specification (Loc,
885 Defining_Identifier => Index,
886 Discrete_Subtype_Definition =>
887 Make_Attribute_Reference (Loc,
888 Prefix =>
889 New_Occurrence_Of (Object_Entity, Loc),
890 Attribute_Name => Name_Range,
891 Expressions => New_List (
892 Make_Integer_Literal (Loc, N))))),
893 Statements => Check_One_Dimension (N + 1)));
894 end if;
895 end Check_One_Dimension;
897 -- Start of processing for Build_Array_Invariant_Proc
899 begin
900 Index_List := New_List;
902 Proc_Id :=
903 Make_Defining_Identifier (Loc,
904 Chars => New_External_Name (Chars (A_Type), "CInvariant"));
906 Body_Stmts := Check_One_Dimension (1);
908 Proc_Body :=
909 Make_Subprogram_Body (Loc,
910 Specification =>
911 Make_Procedure_Specification (Loc,
912 Defining_Unit_Name => Proc_Id,
913 Parameter_Specifications => New_List (
914 Make_Parameter_Specification (Loc,
915 Defining_Identifier => Object_Entity,
916 Parameter_Type => New_Occurrence_Of (A_Type, Loc)))),
918 Declarations => Empty_List,
919 Handled_Statement_Sequence =>
920 Make_Handled_Sequence_Of_Statements (Loc,
921 Statements => Body_Stmts));
923 Set_Ekind (Proc_Id, E_Procedure);
924 Set_Is_Public (Proc_Id, Is_Public (A_Type));
925 Set_Is_Internal (Proc_Id);
926 Set_Has_Completion (Proc_Id);
928 if not Debug_Generated_Code then
929 Set_Debug_Info_Off (Proc_Id);
930 end if;
932 return Proc_Body;
933 end Build_Array_Invariant_Proc;
935 --------------------------------
936 -- Build_Discr_Checking_Funcs --
937 --------------------------------
939 procedure Build_Discr_Checking_Funcs (N : Node_Id) is
940 Rec_Id : Entity_Id;
941 Loc : Source_Ptr;
942 Enclosing_Func_Id : Entity_Id;
943 Sequence : Nat := 1;
944 Type_Def : Node_Id;
945 V : Node_Id;
947 function Build_Case_Statement
948 (Case_Id : Entity_Id;
949 Variant : Node_Id) return Node_Id;
950 -- Build a case statement containing only two alternatives. The first
951 -- alternative corresponds exactly to the discrete choices given on the
952 -- variant with contains the components that we are generating the
953 -- checks for. If the discriminant is one of these return False. The
954 -- second alternative is an OTHERS choice that will return True
955 -- indicating the discriminant did not match.
957 function Build_Dcheck_Function
958 (Case_Id : Entity_Id;
959 Variant : Node_Id) return Entity_Id;
960 -- Build the discriminant checking function for a given variant
962 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id);
963 -- Builds the discriminant checking function for each variant of the
964 -- given variant part of the record type.
966 --------------------------
967 -- Build_Case_Statement --
968 --------------------------
970 function Build_Case_Statement
971 (Case_Id : Entity_Id;
972 Variant : Node_Id) return Node_Id
974 Alt_List : constant List_Id := New_List;
975 Actuals_List : List_Id;
976 Case_Node : Node_Id;
977 Case_Alt_Node : Node_Id;
978 Choice : Node_Id;
979 Choice_List : List_Id;
980 D : Entity_Id;
981 Return_Node : Node_Id;
983 begin
984 Case_Node := New_Node (N_Case_Statement, Loc);
986 -- Replace the discriminant which controls the variant with the name
987 -- of the formal of the checking function.
989 Set_Expression (Case_Node, Make_Identifier (Loc, Chars (Case_Id)));
991 Choice := First (Discrete_Choices (Variant));
993 if Nkind (Choice) = N_Others_Choice then
994 Choice_List := New_Copy_List (Others_Discrete_Choices (Choice));
995 else
996 Choice_List := New_Copy_List (Discrete_Choices (Variant));
997 end if;
999 if not Is_Empty_List (Choice_List) then
1000 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1001 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1003 -- In case this is a nested variant, we need to return the result
1004 -- of the discriminant checking function for the immediately
1005 -- enclosing variant.
1007 if Present (Enclosing_Func_Id) then
1008 Actuals_List := New_List;
1010 D := First_Discriminant (Rec_Id);
1011 while Present (D) loop
1012 Append (Make_Identifier (Loc, Chars (D)), Actuals_List);
1013 Next_Discriminant (D);
1014 end loop;
1016 Return_Node :=
1017 Make_Simple_Return_Statement (Loc,
1018 Expression =>
1019 Make_Function_Call (Loc,
1020 Name =>
1021 New_Occurrence_Of (Enclosing_Func_Id, Loc),
1022 Parameter_Associations =>
1023 Actuals_List));
1025 else
1026 Return_Node :=
1027 Make_Simple_Return_Statement (Loc,
1028 Expression =>
1029 New_Occurrence_Of (Standard_False, Loc));
1030 end if;
1032 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1033 Append (Case_Alt_Node, Alt_List);
1034 end if;
1036 Case_Alt_Node := New_Node (N_Case_Statement_Alternative, Loc);
1037 Choice_List := New_List (New_Node (N_Others_Choice, Loc));
1038 Set_Discrete_Choices (Case_Alt_Node, Choice_List);
1040 Return_Node :=
1041 Make_Simple_Return_Statement (Loc,
1042 Expression =>
1043 New_Occurrence_Of (Standard_True, Loc));
1045 Set_Statements (Case_Alt_Node, New_List (Return_Node));
1046 Append (Case_Alt_Node, Alt_List);
1048 Set_Alternatives (Case_Node, Alt_List);
1049 return Case_Node;
1050 end Build_Case_Statement;
1052 ---------------------------
1053 -- Build_Dcheck_Function --
1054 ---------------------------
1056 function Build_Dcheck_Function
1057 (Case_Id : Entity_Id;
1058 Variant : Node_Id) return Entity_Id
1060 Body_Node : Node_Id;
1061 Func_Id : Entity_Id;
1062 Parameter_List : List_Id;
1063 Spec_Node : Node_Id;
1065 begin
1066 Body_Node := New_Node (N_Subprogram_Body, Loc);
1067 Sequence := Sequence + 1;
1069 Func_Id :=
1070 Make_Defining_Identifier (Loc,
1071 Chars => New_External_Name (Chars (Rec_Id), 'D', Sequence));
1072 Set_Is_Discriminant_Check_Function (Func_Id);
1074 Spec_Node := New_Node (N_Function_Specification, Loc);
1075 Set_Defining_Unit_Name (Spec_Node, Func_Id);
1077 Parameter_List := Build_Discriminant_Formals (Rec_Id, False);
1079 Set_Parameter_Specifications (Spec_Node, Parameter_List);
1080 Set_Result_Definition (Spec_Node,
1081 New_Occurrence_Of (Standard_Boolean, Loc));
1082 Set_Specification (Body_Node, Spec_Node);
1083 Set_Declarations (Body_Node, New_List);
1085 Set_Handled_Statement_Sequence (Body_Node,
1086 Make_Handled_Sequence_Of_Statements (Loc,
1087 Statements => New_List (
1088 Build_Case_Statement (Case_Id, Variant))));
1090 Set_Ekind (Func_Id, E_Function);
1091 Set_Mechanism (Func_Id, Default_Mechanism);
1092 Set_Is_Inlined (Func_Id, True);
1093 Set_Is_Pure (Func_Id, True);
1094 Set_Is_Public (Func_Id, Is_Public (Rec_Id));
1095 Set_Is_Internal (Func_Id, True);
1097 if not Debug_Generated_Code then
1098 Set_Debug_Info_Off (Func_Id);
1099 end if;
1101 Analyze (Body_Node);
1103 Append_Freeze_Action (Rec_Id, Body_Node);
1104 Set_Dcheck_Function (Variant, Func_Id);
1105 return Func_Id;
1106 end Build_Dcheck_Function;
1108 ----------------------------
1109 -- Build_Dcheck_Functions --
1110 ----------------------------
1112 procedure Build_Dcheck_Functions (Variant_Part_Node : Node_Id) is
1113 Component_List_Node : Node_Id;
1114 Decl : Entity_Id;
1115 Discr_Name : Entity_Id;
1116 Func_Id : Entity_Id;
1117 Variant : Node_Id;
1118 Saved_Enclosing_Func_Id : Entity_Id;
1120 begin
1121 -- Build the discriminant-checking function for each variant, and
1122 -- label all components of that variant with the function's name.
1123 -- We only Generate a discriminant-checking function when the
1124 -- variant is not empty, to prevent the creation of dead code.
1125 -- The exception to that is when Frontend_Layout_On_Target is set,
1126 -- because the variant record size function generated in package
1127 -- Layout needs to generate calls to all discriminant-checking
1128 -- functions, including those for empty variants.
1130 Discr_Name := Entity (Name (Variant_Part_Node));
1131 Variant := First_Non_Pragma (Variants (Variant_Part_Node));
1133 while Present (Variant) loop
1134 Component_List_Node := Component_List (Variant);
1136 if not Null_Present (Component_List_Node)
1137 or else Frontend_Layout_On_Target
1138 then
1139 Func_Id := Build_Dcheck_Function (Discr_Name, Variant);
1141 Decl :=
1142 First_Non_Pragma (Component_Items (Component_List_Node));
1143 while Present (Decl) loop
1144 Set_Discriminant_Checking_Func
1145 (Defining_Identifier (Decl), Func_Id);
1146 Next_Non_Pragma (Decl);
1147 end loop;
1149 if Present (Variant_Part (Component_List_Node)) then
1150 Saved_Enclosing_Func_Id := Enclosing_Func_Id;
1151 Enclosing_Func_Id := Func_Id;
1152 Build_Dcheck_Functions (Variant_Part (Component_List_Node));
1153 Enclosing_Func_Id := Saved_Enclosing_Func_Id;
1154 end if;
1155 end if;
1157 Next_Non_Pragma (Variant);
1158 end loop;
1159 end Build_Dcheck_Functions;
1161 -- Start of processing for Build_Discr_Checking_Funcs
1163 begin
1164 -- Only build if not done already
1166 if not Discr_Check_Funcs_Built (N) then
1167 Type_Def := Type_Definition (N);
1169 if Nkind (Type_Def) = N_Record_Definition then
1170 if No (Component_List (Type_Def)) then -- null record.
1171 return;
1172 else
1173 V := Variant_Part (Component_List (Type_Def));
1174 end if;
1176 else pragma Assert (Nkind (Type_Def) = N_Derived_Type_Definition);
1177 if No (Component_List (Record_Extension_Part (Type_Def))) then
1178 return;
1179 else
1180 V := Variant_Part
1181 (Component_List (Record_Extension_Part (Type_Def)));
1182 end if;
1183 end if;
1185 Rec_Id := Defining_Identifier (N);
1187 if Present (V) and then not Is_Unchecked_Union (Rec_Id) then
1188 Loc := Sloc (N);
1189 Enclosing_Func_Id := Empty;
1190 Build_Dcheck_Functions (V);
1191 end if;
1193 Set_Discr_Check_Funcs_Built (N);
1194 end if;
1195 end Build_Discr_Checking_Funcs;
1197 --------------------------------
1198 -- Build_Discriminant_Formals --
1199 --------------------------------
1201 function Build_Discriminant_Formals
1202 (Rec_Id : Entity_Id;
1203 Use_Dl : Boolean) return List_Id
1205 Loc : Source_Ptr := Sloc (Rec_Id);
1206 Parameter_List : constant List_Id := New_List;
1207 D : Entity_Id;
1208 Formal : Entity_Id;
1209 Formal_Type : Entity_Id;
1210 Param_Spec_Node : Node_Id;
1212 begin
1213 if Has_Discriminants (Rec_Id) then
1214 D := First_Discriminant (Rec_Id);
1215 while Present (D) loop
1216 Loc := Sloc (D);
1218 if Use_Dl then
1219 Formal := Discriminal (D);
1220 Formal_Type := Etype (Formal);
1221 else
1222 Formal := Make_Defining_Identifier (Loc, Chars (D));
1223 Formal_Type := Etype (D);
1224 end if;
1226 Param_Spec_Node :=
1227 Make_Parameter_Specification (Loc,
1228 Defining_Identifier => Formal,
1229 Parameter_Type =>
1230 New_Occurrence_Of (Formal_Type, Loc));
1231 Append (Param_Spec_Node, Parameter_List);
1232 Next_Discriminant (D);
1233 end loop;
1234 end if;
1236 return Parameter_List;
1237 end Build_Discriminant_Formals;
1239 --------------------------------------
1240 -- Build_Equivalent_Array_Aggregate --
1241 --------------------------------------
1243 function Build_Equivalent_Array_Aggregate (T : Entity_Id) return Node_Id is
1244 Loc : constant Source_Ptr := Sloc (T);
1245 Comp_Type : constant Entity_Id := Component_Type (T);
1246 Index_Type : constant Entity_Id := Etype (First_Index (T));
1247 Proc : constant Entity_Id := Base_Init_Proc (T);
1248 Lo, Hi : Node_Id;
1249 Aggr : Node_Id;
1250 Expr : Node_Id;
1252 begin
1253 if not Is_Constrained (T)
1254 or else Number_Dimensions (T) > 1
1255 or else No (Proc)
1256 then
1257 Initialization_Warning (T);
1258 return Empty;
1259 end if;
1261 Lo := Type_Low_Bound (Index_Type);
1262 Hi := Type_High_Bound (Index_Type);
1264 if not Compile_Time_Known_Value (Lo)
1265 or else not Compile_Time_Known_Value (Hi)
1266 then
1267 Initialization_Warning (T);
1268 return Empty;
1269 end if;
1271 if Is_Record_Type (Comp_Type)
1272 and then Present (Base_Init_Proc (Comp_Type))
1273 then
1274 Expr := Static_Initialization (Base_Init_Proc (Comp_Type));
1276 if No (Expr) then
1277 Initialization_Warning (T);
1278 return Empty;
1279 end if;
1281 else
1282 Initialization_Warning (T);
1283 return Empty;
1284 end if;
1286 Aggr := Make_Aggregate (Loc, No_List, New_List);
1287 Set_Etype (Aggr, T);
1288 Set_Aggregate_Bounds (Aggr,
1289 Make_Range (Loc,
1290 Low_Bound => New_Copy (Lo),
1291 High_Bound => New_Copy (Hi)));
1292 Set_Parent (Aggr, Parent (Proc));
1294 Append_To (Component_Associations (Aggr),
1295 Make_Component_Association (Loc,
1296 Choices =>
1297 New_List (
1298 Make_Range (Loc,
1299 Low_Bound => New_Copy (Lo),
1300 High_Bound => New_Copy (Hi))),
1301 Expression => Expr));
1303 if Static_Array_Aggregate (Aggr) then
1304 return Aggr;
1305 else
1306 Initialization_Warning (T);
1307 return Empty;
1308 end if;
1309 end Build_Equivalent_Array_Aggregate;
1311 ---------------------------------------
1312 -- Build_Equivalent_Record_Aggregate --
1313 ---------------------------------------
1315 function Build_Equivalent_Record_Aggregate (T : Entity_Id) return Node_Id is
1316 Agg : Node_Id;
1317 Comp : Entity_Id;
1318 Comp_Type : Entity_Id;
1320 -- Start of processing for Build_Equivalent_Record_Aggregate
1322 begin
1323 if not Is_Record_Type (T)
1324 or else Has_Discriminants (T)
1325 or else Is_Limited_Type (T)
1326 or else Has_Non_Standard_Rep (T)
1327 then
1328 Initialization_Warning (T);
1329 return Empty;
1330 end if;
1332 Comp := First_Component (T);
1334 -- A null record needs no warning
1336 if No (Comp) then
1337 return Empty;
1338 end if;
1340 while Present (Comp) loop
1342 -- Array components are acceptable if initialized by a positional
1343 -- aggregate with static components.
1345 if Is_Array_Type (Etype (Comp)) then
1346 Comp_Type := Component_Type (Etype (Comp));
1348 if Nkind (Parent (Comp)) /= N_Component_Declaration
1349 or else No (Expression (Parent (Comp)))
1350 or else Nkind (Expression (Parent (Comp))) /= N_Aggregate
1351 then
1352 Initialization_Warning (T);
1353 return Empty;
1355 elsif Is_Scalar_Type (Component_Type (Etype (Comp)))
1356 and then
1357 (not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1358 or else
1359 not Compile_Time_Known_Value (Type_High_Bound (Comp_Type)))
1360 then
1361 Initialization_Warning (T);
1362 return Empty;
1364 elsif
1365 not Static_Array_Aggregate (Expression (Parent (Comp)))
1366 then
1367 Initialization_Warning (T);
1368 return Empty;
1369 end if;
1371 elsif Is_Scalar_Type (Etype (Comp)) then
1372 Comp_Type := Etype (Comp);
1374 if Nkind (Parent (Comp)) /= N_Component_Declaration
1375 or else No (Expression (Parent (Comp)))
1376 or else not Compile_Time_Known_Value (Expression (Parent (Comp)))
1377 or else not Compile_Time_Known_Value (Type_Low_Bound (Comp_Type))
1378 or else not
1379 Compile_Time_Known_Value (Type_High_Bound (Comp_Type))
1380 then
1381 Initialization_Warning (T);
1382 return Empty;
1383 end if;
1385 -- For now, other types are excluded
1387 else
1388 Initialization_Warning (T);
1389 return Empty;
1390 end if;
1392 Next_Component (Comp);
1393 end loop;
1395 -- All components have static initialization. Build positional aggregate
1396 -- from the given expressions or defaults.
1398 Agg := Make_Aggregate (Sloc (T), New_List, New_List);
1399 Set_Parent (Agg, Parent (T));
1401 Comp := First_Component (T);
1402 while Present (Comp) loop
1403 Append
1404 (New_Copy_Tree (Expression (Parent (Comp))), Expressions (Agg));
1405 Next_Component (Comp);
1406 end loop;
1408 Analyze_And_Resolve (Agg, T);
1409 return Agg;
1410 end Build_Equivalent_Record_Aggregate;
1412 -------------------------------
1413 -- Build_Initialization_Call --
1414 -------------------------------
1416 -- References to a discriminant inside the record type declaration can
1417 -- appear either in the subtype_indication to constrain a record or an
1418 -- array, or as part of a larger expression given for the initial value
1419 -- of a component. In both of these cases N appears in the record
1420 -- initialization procedure and needs to be replaced by the formal
1421 -- parameter of the initialization procedure which corresponds to that
1422 -- discriminant.
1424 -- In the example below, references to discriminants D1 and D2 in proc_1
1425 -- are replaced by references to formals with the same name
1426 -- (discriminals)
1428 -- A similar replacement is done for calls to any record initialization
1429 -- procedure for any components that are themselves of a record type.
1431 -- type R (D1, D2 : Integer) is record
1432 -- X : Integer := F * D1;
1433 -- Y : Integer := F * D2;
1434 -- end record;
1436 -- procedure proc_1 (Out_2 : out R; D1 : Integer; D2 : Integer) is
1437 -- begin
1438 -- Out_2.D1 := D1;
1439 -- Out_2.D2 := D2;
1440 -- Out_2.X := F * D1;
1441 -- Out_2.Y := F * D2;
1442 -- end;
1444 function Build_Initialization_Call
1445 (Loc : Source_Ptr;
1446 Id_Ref : Node_Id;
1447 Typ : Entity_Id;
1448 In_Init_Proc : Boolean := False;
1449 Enclos_Type : Entity_Id := Empty;
1450 Discr_Map : Elist_Id := New_Elmt_List;
1451 With_Default_Init : Boolean := False;
1452 Constructor_Ref : Node_Id := Empty) return List_Id
1454 Res : constant List_Id := New_List;
1455 Arg : Node_Id;
1456 Args : List_Id;
1457 Decls : List_Id;
1458 Decl : Node_Id;
1459 Discr : Entity_Id;
1460 First_Arg : Node_Id;
1461 Full_Init_Type : Entity_Id;
1462 Full_Type : Entity_Id;
1463 Init_Type : Entity_Id;
1464 Proc : Entity_Id;
1466 begin
1467 pragma Assert (Constructor_Ref = Empty
1468 or else Is_CPP_Constructor_Call (Constructor_Ref));
1470 if No (Constructor_Ref) then
1471 Proc := Base_Init_Proc (Typ);
1472 else
1473 Proc := Base_Init_Proc (Typ, Entity (Name (Constructor_Ref)));
1474 end if;
1476 pragma Assert (Present (Proc));
1477 Init_Type := Etype (First_Formal (Proc));
1478 Full_Init_Type := Underlying_Type (Init_Type);
1480 -- Nothing to do if the Init_Proc is null, unless Initialize_Scalars
1481 -- is active (in which case we make the call anyway, since in the
1482 -- actual compiled client it may be non null).
1483 -- Also nothing to do for value types.
1485 if (Is_Null_Init_Proc (Proc) and then not Init_Or_Norm_Scalars)
1486 or else Is_Value_Type (Typ)
1487 or else
1488 (Is_Array_Type (Typ) and then Is_Value_Type (Component_Type (Typ)))
1489 then
1490 return Empty_List;
1491 end if;
1493 -- Use the [underlying] full view when dealing with a private type. This
1494 -- may require several steps depending on derivations.
1496 Full_Type := Typ;
1497 loop
1498 if Is_Private_Type (Full_Type) then
1499 if Present (Full_View (Full_Type)) then
1500 Full_Type := Full_View (Full_Type);
1502 elsif Present (Underlying_Full_View (Full_Type)) then
1503 Full_Type := Underlying_Full_View (Full_Type);
1505 -- When a private type acts as a generic actual and lacks a full
1506 -- view, use the base type.
1508 elsif Is_Generic_Actual_Type (Full_Type) then
1509 Full_Type := Base_Type (Full_Type);
1511 -- The loop has recovered the [underlying] full view, stop the
1512 -- traversal.
1514 else
1515 exit;
1516 end if;
1518 -- The type is not private, nothing to do
1520 else
1521 exit;
1522 end if;
1523 end loop;
1525 -- If Typ is derived, the procedure is the initialization procedure for
1526 -- the root type. Wrap the argument in an conversion to make it type
1527 -- honest. Actually it isn't quite type honest, because there can be
1528 -- conflicts of views in the private type case. That is why we set
1529 -- Conversion_OK in the conversion node.
1531 if (Is_Record_Type (Typ)
1532 or else Is_Array_Type (Typ)
1533 or else Is_Private_Type (Typ))
1534 and then Init_Type /= Base_Type (Typ)
1535 then
1536 First_Arg := OK_Convert_To (Etype (Init_Type), Id_Ref);
1537 Set_Etype (First_Arg, Init_Type);
1539 else
1540 First_Arg := Id_Ref;
1541 end if;
1543 Args := New_List (Convert_Concurrent (First_Arg, Typ));
1545 -- In the tasks case, add _Master as the value of the _Master parameter
1546 -- and _Chain as the value of the _Chain parameter. At the outer level,
1547 -- these will be variables holding the corresponding values obtained
1548 -- from GNARL. At inner levels, they will be the parameters passed down
1549 -- through the outer routines.
1551 if Has_Task (Full_Type) then
1552 if Restriction_Active (No_Task_Hierarchy) then
1553 Append_To (Args,
1554 New_Occurrence_Of (RTE (RE_Library_Task_Level), Loc));
1555 else
1556 Append_To (Args, Make_Identifier (Loc, Name_uMaster));
1557 end if;
1559 -- Add _Chain (not done for sequential elaboration policy, see
1560 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
1562 if Partition_Elaboration_Policy /= 'S' then
1563 Append_To (Args, Make_Identifier (Loc, Name_uChain));
1564 end if;
1566 -- Ada 2005 (AI-287): In case of default initialized components
1567 -- with tasks, we generate a null string actual parameter.
1568 -- This is just a workaround that must be improved later???
1570 if With_Default_Init then
1571 Append_To (Args,
1572 Make_String_Literal (Loc,
1573 Strval => ""));
1575 else
1576 Decls :=
1577 Build_Task_Image_Decls (Loc, Id_Ref, Enclos_Type, In_Init_Proc);
1578 Decl := Last (Decls);
1580 Append_To (Args,
1581 New_Occurrence_Of (Defining_Identifier (Decl), Loc));
1582 Append_List (Decls, Res);
1583 end if;
1585 else
1586 Decls := No_List;
1587 Decl := Empty;
1588 end if;
1590 -- Add discriminant values if discriminants are present
1592 if Has_Discriminants (Full_Init_Type) then
1593 Discr := First_Discriminant (Full_Init_Type);
1594 while Present (Discr) loop
1596 -- If this is a discriminated concurrent type, the init_proc
1597 -- for the corresponding record is being called. Use that type
1598 -- directly to find the discriminant value, to handle properly
1599 -- intervening renamed discriminants.
1601 declare
1602 T : Entity_Id := Full_Type;
1604 begin
1605 if Is_Protected_Type (T) then
1606 T := Corresponding_Record_Type (T);
1607 end if;
1609 Arg :=
1610 Get_Discriminant_Value (
1611 Discr,
1613 Discriminant_Constraint (Full_Type));
1614 end;
1616 -- If the target has access discriminants, and is constrained by
1617 -- an access to the enclosing construct, i.e. a current instance,
1618 -- replace the reference to the type by a reference to the object.
1620 if Nkind (Arg) = N_Attribute_Reference
1621 and then Is_Access_Type (Etype (Arg))
1622 and then Is_Entity_Name (Prefix (Arg))
1623 and then Is_Type (Entity (Prefix (Arg)))
1624 then
1625 Arg :=
1626 Make_Attribute_Reference (Loc,
1627 Prefix => New_Copy (Prefix (Id_Ref)),
1628 Attribute_Name => Name_Unrestricted_Access);
1630 elsif In_Init_Proc then
1632 -- Replace any possible references to the discriminant in the
1633 -- call to the record initialization procedure with references
1634 -- to the appropriate formal parameter.
1636 if Nkind (Arg) = N_Identifier
1637 and then Ekind (Entity (Arg)) = E_Discriminant
1638 then
1639 Arg := New_Occurrence_Of (Discriminal (Entity (Arg)), Loc);
1641 -- Otherwise make a copy of the default expression. Note that
1642 -- we use the current Sloc for this, because we do not want the
1643 -- call to appear to be at the declaration point. Within the
1644 -- expression, replace discriminants with their discriminals.
1646 else
1647 Arg :=
1648 New_Copy_Tree (Arg, Map => Discr_Map, New_Sloc => Loc);
1649 end if;
1651 else
1652 if Is_Constrained (Full_Type) then
1653 Arg := Duplicate_Subexpr_No_Checks (Arg);
1654 else
1655 -- The constraints come from the discriminant default exps,
1656 -- they must be reevaluated, so we use New_Copy_Tree but we
1657 -- ensure the proper Sloc (for any embedded calls).
1659 Arg := New_Copy_Tree (Arg, New_Sloc => Loc);
1660 end if;
1661 end if;
1663 -- Ada 2005 (AI-287): In case of default initialized components,
1664 -- if the component is constrained with a discriminant of the
1665 -- enclosing type, we need to generate the corresponding selected
1666 -- component node to access the discriminant value. In other cases
1667 -- this is not required, either because we are inside the init
1668 -- proc and we use the corresponding formal, or else because the
1669 -- component is constrained by an expression.
1671 if With_Default_Init
1672 and then Nkind (Id_Ref) = N_Selected_Component
1673 and then Nkind (Arg) = N_Identifier
1674 and then Ekind (Entity (Arg)) = E_Discriminant
1675 then
1676 Append_To (Args,
1677 Make_Selected_Component (Loc,
1678 Prefix => New_Copy_Tree (Prefix (Id_Ref)),
1679 Selector_Name => Arg));
1680 else
1681 Append_To (Args, Arg);
1682 end if;
1684 Next_Discriminant (Discr);
1685 end loop;
1686 end if;
1688 -- If this is a call to initialize the parent component of a derived
1689 -- tagged type, indicate that the tag should not be set in the parent.
1691 if Is_Tagged_Type (Full_Init_Type)
1692 and then not Is_CPP_Class (Full_Init_Type)
1693 and then Nkind (Id_Ref) = N_Selected_Component
1694 and then Chars (Selector_Name (Id_Ref)) = Name_uParent
1695 then
1696 Append_To (Args, New_Occurrence_Of (Standard_False, Loc));
1698 elsif Present (Constructor_Ref) then
1699 Append_List_To (Args,
1700 New_Copy_List (Parameter_Associations (Constructor_Ref)));
1701 end if;
1703 Append_To (Res,
1704 Make_Procedure_Call_Statement (Loc,
1705 Name => New_Occurrence_Of (Proc, Loc),
1706 Parameter_Associations => Args));
1708 if Needs_Finalization (Typ)
1709 and then Nkind (Id_Ref) = N_Selected_Component
1710 then
1711 if Chars (Selector_Name (Id_Ref)) /= Name_uParent then
1712 Append_To (Res,
1713 Make_Init_Call
1714 (Obj_Ref => New_Copy_Tree (First_Arg),
1715 Typ => Typ));
1716 end if;
1717 end if;
1719 return Res;
1721 exception
1722 when RE_Not_Available =>
1723 return Empty_List;
1724 end Build_Initialization_Call;
1726 ----------------------------
1727 -- Build_Record_Init_Proc --
1728 ----------------------------
1730 procedure Build_Record_Init_Proc (N : Node_Id; Rec_Ent : Entity_Id) is
1731 Decls : constant List_Id := New_List;
1732 Discr_Map : constant Elist_Id := New_Elmt_List;
1733 Loc : constant Source_Ptr := Sloc (Rec_Ent);
1734 Counter : Int := 0;
1735 Proc_Id : Entity_Id;
1736 Rec_Type : Entity_Id;
1737 Set_Tag : Entity_Id := Empty;
1739 function Build_Assignment (Id : Entity_Id; N : Node_Id) return List_Id;
1740 -- Build an assignment statement which assigns the default expression
1741 -- to its corresponding record component if defined. The left hand side
1742 -- of the assignment is marked Assignment_OK so that initialization of
1743 -- limited private records works correctly. This routine may also build
1744 -- an adjustment call if the component is controlled.
1746 procedure Build_Discriminant_Assignments (Statement_List : List_Id);
1747 -- If the record has discriminants, add assignment statements to
1748 -- Statement_List to initialize the discriminant values from the
1749 -- arguments of the initialization procedure.
1751 function Build_Init_Statements (Comp_List : Node_Id) return List_Id;
1752 -- Build a list representing a sequence of statements which initialize
1753 -- components of the given component list. This may involve building
1754 -- case statements for the variant parts. Append any locally declared
1755 -- objects on list Decls.
1757 function Build_Init_Call_Thru (Parameters : List_Id) return List_Id;
1758 -- Given an untagged type-derivation that declares discriminants, e.g.
1760 -- type R (R1, R2 : Integer) is record ... end record;
1761 -- type D (D1 : Integer) is new R (1, D1);
1763 -- we make the _init_proc of D be
1765 -- procedure _init_proc (X : D; D1 : Integer) is
1766 -- begin
1767 -- _init_proc (R (X), 1, D1);
1768 -- end _init_proc;
1770 -- This function builds the call statement in this _init_proc.
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.
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.
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.
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.
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.
1800 function Parent_Subtype_Renaming_Discrims return Boolean;
1801 -- Returns True for base types N that rename discriminants, else False
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.
1807 ----------------------
1808 -- Build_Assignment --
1809 ----------------------
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;
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);
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. ???
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;
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.
1854 Exp := New_Copy_Tree (Exp, New_Scope => Proc_Id);
1856 Res := New_List (
1857 Make_Assignment_Statement (Loc,
1858 Name => Lhs,
1859 Expression => Exp));
1861 Set_No_Ctrl_Actions (First (Res));
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.
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)),
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;
1886 -- Adjust the component if controlled except if it is an aggregate
1887 -- that will be expanded inline.
1889 if Kind = N_Qualified_Expression then
1890 Kind := Nkind (Expression (N));
1891 end if;
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;
1903 return Res;
1905 exception
1906 when RE_Not_Available =>
1907 return Empty_List;
1908 end Build_Assignment;
1910 ------------------------------------
1911 -- Build_Discriminant_Assignments --
1912 ------------------------------------
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;
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
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.
1931 if Is_Tagged
1932 and then Present (Corresponding_Discriminant (D))
1933 then
1934 null;
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;
1943 Next_Discriminant (D);
1944 end loop;
1945 end if;
1946 end Build_Discriminant_Assignments;
1948 --------------------------
1949 -- Build_Init_Call_Thru --
1950 --------------------------
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));
1956 Parent_Type : constant Entity_Id :=
1957 Etype (First_Formal (Parent_Proc));
1959 Uparent_Type : constant Entity_Id :=
1960 Underlying_Type (Parent_Type);
1962 First_Discr_Param : Node_Id;
1964 Arg : Node_Id;
1965 Args : List_Id;
1966 First_Arg : Node_Id;
1967 Parent_Discr : Entity_Id;
1968 Res : List_Id;
1970 begin
1971 -- First argument (_Init) is the object to be initialized.
1972 -- ??? not sure where to get a reasonable Loc for First_Arg
1974 First_Arg :=
1975 OK_Convert_To (Parent_Type,
1976 New_Occurrence_Of
1977 (Defining_Identifier (First (Parameters)), Loc));
1979 Set_Etype (First_Arg, Parent_Type);
1981 Args := New_List (Convert_Concurrent (First_Arg, Rec_Type));
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.
1990 -- At inner levels, they will be the parameters passed down through
1991 -- the outer routines.
1993 First_Discr_Param := Next (First (Parameters));
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;
2003 -- Add _Chain (not done for sequential elaboration policy, see
2004 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
2006 if Partition_Elaboration_Policy /= 'S' then
2007 Append_To (Args, Make_Identifier (Loc, Name_uChain));
2008 end if;
2010 Append_To (Args, Make_Identifier (Loc, Name_uTask_Name));
2011 First_Discr_Param := Next (Next (Next (First_Discr_Param)));
2012 end if;
2014 -- Append discriminant values
2016 if Has_Discriminants (Uparent_Type) then
2017 pragma Assert (not Is_Tagged_Type (Uparent_Type));
2019 Parent_Discr := First_Discriminant (Uparent_Type);
2020 while Present (Parent_Discr) loop
2022 -- Get the initial value for this discriminant
2023 -- ??? needs to be cleaned up to use parent_Discr_Constr
2024 -- directly.
2026 declare
2027 Discr : Entity_Id :=
2028 First_Stored_Discriminant (Uparent_Type);
2030 Discr_Value : Elmt_Id :=
2031 First_Elmt (Stored_Constraint (Rec_Type));
2033 begin
2034 while Original_Record_Component (Parent_Discr) /= Discr loop
2035 Next_Stored_Discriminant (Discr);
2036 Next_Elmt (Discr_Value);
2037 end loop;
2039 Arg := Node (Discr_Value);
2040 end;
2042 -- Append it to the list
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));
2050 -- Case of access discriminants. We replace the reference
2051 -- to the type by a reference to the actual object.
2053 -- Is above comment right??? Use of New_Copy below seems mighty
2054 -- suspicious ???
2056 else
2057 Append_To (Args, New_Copy (Arg));
2058 end if;
2060 Next_Discriminant (Parent_Discr);
2061 end loop;
2062 end if;
2064 Res :=
2065 New_List (
2066 Make_Procedure_Call_Statement (Loc,
2067 Name =>
2068 New_Occurrence_Of (Parent_Proc, Loc),
2069 Parameter_Associations => Args));
2071 return Res;
2072 end Build_Init_Call_Thru;
2074 -----------------------------------
2075 -- Build_Offset_To_Top_Functions --
2076 -----------------------------------
2078 procedure Build_Offset_To_Top_Functions is
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;
2088 ----------------------------------
2089 -- Build_Offset_To_Top_Function --
2090 ----------------------------------
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;
2098 begin
2099 Func_Id := Make_Temporary (Loc, 'F');
2100 Set_DT_Offset_To_Top_Func (Iface_Comp, Func_Id);
2102 -- Generate
2103 -- function Fxx (O : in Rec_Typ) return Storage_Offset;
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));
2117 -- Generate
2118 -- function Fxx (O : in Rec_Typ) return Storage_Offset is
2119 -- begin
2120 -- return O.Iface_Comp'Position;
2121 -- end Fxx;
2123 Body_Node := New_Node (N_Subprogram_Body, Loc);
2124 Set_Specification (Body_Node, Spec_Node);
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)))));
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)))));
2153 Set_Ekind (Func_Id, E_Function);
2154 Set_Mechanism (Func_Id, Default_Mechanism);
2155 Set_Is_Internal (Func_Id, True);
2157 if not Debug_Generated_Code then
2158 Set_Debug_Info_Off (Func_Id);
2159 end if;
2161 Analyze (Body_Node);
2163 Append_Freeze_Action (Rec_Type, Body_Node);
2164 end Build_Offset_To_Top_Function;
2166 -- Local variables
2168 Iface_Comp : Node_Id;
2169 Iface_Comp_Elmt : Elmt_Id;
2170 Ifaces_Comp_List : Elist_Id;
2172 -- Start of processing for Build_Offset_To_Top_Functions
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.
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;
2188 Collect_Interface_Components (Rec_Type, Ifaces_Comp_List);
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)
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)));
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
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;
2208 Next_Elmt (Iface_Comp_Elmt);
2209 end loop;
2210 end Build_Offset_To_Top_Functions;
2212 ------------------------------
2213 -- Build_CPP_Init_Procedure --
2214 ------------------------------
2216 procedure Build_CPP_Init_Procedure is
2217 Body_Node : Node_Id;
2218 Body_Stmts : List_Id;
2219 Flag_Id : Entity_Id;
2220 Handled_Stmt_Node : Node_Id;
2221 Init_Tags_List : List_Id;
2222 Proc_Id : Entity_Id;
2223 Proc_Spec_Node : Node_Id;
2225 begin
2226 -- Check cases requiring no IC routine
2228 if not Is_CPP_Class (Root_Type (Rec_Type))
2229 or else Is_CPP_Class (Rec_Type)
2230 or else CPP_Num_Prims (Rec_Type) = 0
2231 or else not Tagged_Type_Expansion
2232 or else No_Run_Time_Mode
2233 then
2234 return;
2235 end if;
2237 -- Generate:
2239 -- Flag : Boolean := False;
2241 -- procedure Typ_IC is
2242 -- begin
2243 -- if not Flag then
2244 -- Copy C++ dispatch table slots from parent
2245 -- Update C++ slots of overridden primitives
2246 -- end if;
2247 -- end;
2249 Flag_Id := Make_Temporary (Loc, 'F');
2251 Append_Freeze_Action (Rec_Type,
2252 Make_Object_Declaration (Loc,
2253 Defining_Identifier => Flag_Id,
2254 Object_Definition =>
2255 New_Occurrence_Of (Standard_Boolean, Loc),
2256 Expression =>
2257 New_Occurrence_Of (Standard_True, Loc)));
2259 Body_Stmts := New_List;
2260 Body_Node := New_Node (N_Subprogram_Body, Loc);
2262 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2264 Proc_Id :=
2265 Make_Defining_Identifier (Loc,
2266 Chars => Make_TSS_Name (Rec_Type, TSS_CPP_Init_Proc));
2268 Set_Ekind (Proc_Id, E_Procedure);
2269 Set_Is_Internal (Proc_Id);
2271 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2273 Set_Parameter_Specifications (Proc_Spec_Node, New_List);
2274 Set_Specification (Body_Node, Proc_Spec_Node);
2275 Set_Declarations (Body_Node, New_List);
2277 Init_Tags_List := Build_Inherit_CPP_Prims (Rec_Type);
2279 Append_To (Init_Tags_List,
2280 Make_Assignment_Statement (Loc,
2281 Name =>
2282 New_Occurrence_Of (Flag_Id, Loc),
2283 Expression =>
2284 New_Occurrence_Of (Standard_False, Loc)));
2286 Append_To (Body_Stmts,
2287 Make_If_Statement (Loc,
2288 Condition => New_Occurrence_Of (Flag_Id, Loc),
2289 Then_Statements => Init_Tags_List));
2291 Handled_Stmt_Node :=
2292 New_Node (N_Handled_Sequence_Of_Statements, Loc);
2293 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2294 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2295 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2297 if not Debug_Generated_Code then
2298 Set_Debug_Info_Off (Proc_Id);
2299 end if;
2301 -- Associate CPP_Init_Proc with type
2303 Set_Init_Proc (Rec_Type, Proc_Id);
2304 end Build_CPP_Init_Procedure;
2306 --------------------------
2307 -- Build_Init_Procedure --
2308 --------------------------
2310 procedure Build_Init_Procedure is
2311 Body_Stmts : List_Id;
2312 Body_Node : Node_Id;
2313 Handled_Stmt_Node : Node_Id;
2314 Init_Tags_List : List_Id;
2315 Parameters : List_Id;
2316 Proc_Spec_Node : Node_Id;
2317 Record_Extension_Node : Node_Id;
2319 begin
2320 Body_Stmts := New_List;
2321 Body_Node := New_Node (N_Subprogram_Body, Loc);
2322 Set_Ekind (Proc_Id, E_Procedure);
2324 Proc_Spec_Node := New_Node (N_Procedure_Specification, Loc);
2325 Set_Defining_Unit_Name (Proc_Spec_Node, Proc_Id);
2327 Parameters := Init_Formals (Rec_Type);
2328 Append_List_To (Parameters,
2329 Build_Discriminant_Formals (Rec_Type, True));
2331 -- For tagged types, we add a flag to indicate whether the routine
2332 -- is called to initialize a parent component in the init_proc of
2333 -- a type extension. If the flag is false, we do not set the tag
2334 -- because it has been set already in the extension.
2336 if Is_Tagged_Type (Rec_Type) then
2337 Set_Tag := Make_Temporary (Loc, 'P');
2339 Append_To (Parameters,
2340 Make_Parameter_Specification (Loc,
2341 Defining_Identifier => Set_Tag,
2342 Parameter_Type =>
2343 New_Occurrence_Of (Standard_Boolean, Loc),
2344 Expression =>
2345 New_Occurrence_Of (Standard_True, Loc)));
2346 end if;
2348 Set_Parameter_Specifications (Proc_Spec_Node, Parameters);
2349 Set_Specification (Body_Node, Proc_Spec_Node);
2350 Set_Declarations (Body_Node, Decls);
2352 -- N is a Derived_Type_Definition that renames the parameters of the
2353 -- ancestor type. We initialize it by expanding our discriminants and
2354 -- call the ancestor _init_proc with a type-converted object.
2356 if Parent_Subtype_Renaming_Discrims then
2357 Append_List_To (Body_Stmts, Build_Init_Call_Thru (Parameters));
2359 elsif Nkind (Type_Definition (N)) = N_Record_Definition then
2360 Build_Discriminant_Assignments (Body_Stmts);
2362 if not Null_Present (Type_Definition (N)) then
2363 Append_List_To (Body_Stmts,
2364 Build_Init_Statements (Component_List (Type_Definition (N))));
2365 end if;
2367 -- N is a Derived_Type_Definition with a possible non-empty
2368 -- extension. The initialization of a type extension consists in the
2369 -- initialization of the components in the extension.
2371 else
2372 Build_Discriminant_Assignments (Body_Stmts);
2374 Record_Extension_Node :=
2375 Record_Extension_Part (Type_Definition (N));
2377 if not Null_Present (Record_Extension_Node) then
2378 declare
2379 Stmts : constant List_Id :=
2380 Build_Init_Statements (
2381 Component_List (Record_Extension_Node));
2383 begin
2384 -- The parent field must be initialized first because the
2385 -- offset of the new discriminants may depend on it. This is
2386 -- not needed if the parent is an interface type because in
2387 -- such case the initialization of the _parent field was not
2388 -- generated.
2390 if not Is_Interface (Etype (Rec_Ent)) then
2391 declare
2392 Parent_IP : constant Name_Id :=
2393 Make_Init_Proc_Name (Etype (Rec_Ent));
2394 Stmt : Node_Id;
2395 IP_Call : Node_Id;
2396 IP_Stmts : List_Id;
2398 begin
2399 -- Look for a call to the parent IP at the beginning
2400 -- of Stmts associated with the record extension
2402 Stmt := First (Stmts);
2403 IP_Call := Empty;
2404 while Present (Stmt) loop
2405 if Nkind (Stmt) = N_Procedure_Call_Statement
2406 and then Chars (Name (Stmt)) = Parent_IP
2407 then
2408 IP_Call := Stmt;
2409 exit;
2410 end if;
2412 Next (Stmt);
2413 end loop;
2415 -- If found then move it to the beginning of the
2416 -- statements of this IP routine
2418 if Present (IP_Call) then
2419 IP_Stmts := New_List;
2420 loop
2421 Stmt := Remove_Head (Stmts);
2422 Append_To (IP_Stmts, Stmt);
2423 exit when Stmt = IP_Call;
2424 end loop;
2426 Prepend_List_To (Body_Stmts, IP_Stmts);
2427 end if;
2428 end;
2429 end if;
2431 Append_List_To (Body_Stmts, Stmts);
2432 end;
2433 end if;
2434 end if;
2436 -- Add here the assignment to instantiate the Tag
2438 -- The assignment corresponds to the code:
2440 -- _Init._Tag := Typ'Tag;
2442 -- Suppress the tag assignment when VM_Target because VM tags are
2443 -- represented implicitly in objects. It is also suppressed in case
2444 -- of CPP_Class types because in this case the tag is initialized in
2445 -- the C++ side.
2447 if Is_Tagged_Type (Rec_Type)
2448 and then Tagged_Type_Expansion
2449 and then not No_Run_Time_Mode
2450 then
2451 -- Case 1: Ada tagged types with no CPP ancestor. Set the tags of
2452 -- the actual object and invoke the IP of the parent (in this
2453 -- order). The tag must be initialized before the call to the IP
2454 -- of the parent and the assignments to other components because
2455 -- the initial value of the components may depend on the tag (eg.
2456 -- through a dispatching operation on an access to the current
2457 -- type). The tag assignment is not done when initializing the
2458 -- parent component of a type extension, because in that case the
2459 -- tag is set in the extension.
2461 if not Is_CPP_Class (Root_Type (Rec_Type)) then
2463 -- Initialize the primary tag component
2465 Init_Tags_List := New_List (
2466 Make_Assignment_Statement (Loc,
2467 Name =>
2468 Make_Selected_Component (Loc,
2469 Prefix => Make_Identifier (Loc, Name_uInit),
2470 Selector_Name =>
2471 New_Occurrence_Of
2472 (First_Tag_Component (Rec_Type), Loc)),
2473 Expression =>
2474 New_Occurrence_Of
2475 (Node
2476 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2478 -- Ada 2005 (AI-251): Initialize the secondary tags components
2479 -- located at fixed positions (tags whose position depends on
2480 -- variable size components are initialized later ---see below)
2482 if Ada_Version >= Ada_2005
2483 and then not Is_Interface (Rec_Type)
2484 and then Has_Interfaces (Rec_Type)
2485 then
2486 Init_Secondary_Tags
2487 (Typ => Rec_Type,
2488 Target => Make_Identifier (Loc, Name_uInit),
2489 Stmts_List => Init_Tags_List,
2490 Fixed_Comps => True,
2491 Variable_Comps => False);
2492 end if;
2494 Prepend_To (Body_Stmts,
2495 Make_If_Statement (Loc,
2496 Condition => New_Occurrence_Of (Set_Tag, Loc),
2497 Then_Statements => Init_Tags_List));
2499 -- Case 2: CPP type. The imported C++ constructor takes care of
2500 -- tags initialization. No action needed here because the IP
2501 -- is built by Set_CPP_Constructors; in this case the IP is a
2502 -- wrapper that invokes the C++ constructor and copies the C++
2503 -- tags locally. Done to inherit the C++ slots in Ada derivations
2504 -- (see case 3).
2506 elsif Is_CPP_Class (Rec_Type) then
2507 pragma Assert (False);
2508 null;
2510 -- Case 3: Combined hierarchy containing C++ types and Ada tagged
2511 -- type derivations. Derivations of imported C++ classes add a
2512 -- complication, because we cannot inhibit tag setting in the
2513 -- constructor for the parent. Hence we initialize the tag after
2514 -- the call to the parent IP (that is, in reverse order compared
2515 -- with pure Ada hierarchies ---see comment on case 1).
2517 else
2518 -- Initialize the primary tag
2520 Init_Tags_List := New_List (
2521 Make_Assignment_Statement (Loc,
2522 Name =>
2523 Make_Selected_Component (Loc,
2524 Prefix => Make_Identifier (Loc, Name_uInit),
2525 Selector_Name =>
2526 New_Occurrence_Of
2527 (First_Tag_Component (Rec_Type), Loc)),
2528 Expression =>
2529 New_Occurrence_Of
2530 (Node
2531 (First_Elmt (Access_Disp_Table (Rec_Type))), Loc)));
2533 -- Ada 2005 (AI-251): Initialize the secondary tags components
2534 -- located at fixed positions (tags whose position depends on
2535 -- variable size components are initialized later ---see below)
2537 if Ada_Version >= Ada_2005
2538 and then not Is_Interface (Rec_Type)
2539 and then Has_Interfaces (Rec_Type)
2540 then
2541 Init_Secondary_Tags
2542 (Typ => Rec_Type,
2543 Target => Make_Identifier (Loc, Name_uInit),
2544 Stmts_List => Init_Tags_List,
2545 Fixed_Comps => True,
2546 Variable_Comps => False);
2547 end if;
2549 -- Initialize the tag component after invocation of parent IP.
2551 -- Generate:
2552 -- parent_IP(_init.parent); // Invokes the C++ constructor
2553 -- [ typIC; ] // Inherit C++ slots from parent
2554 -- init_tags
2556 declare
2557 Ins_Nod : Node_Id;
2559 begin
2560 -- Search for the call to the IP of the parent. We assume
2561 -- that the first init_proc call is for the parent.
2563 Ins_Nod := First (Body_Stmts);
2564 while Present (Next (Ins_Nod))
2565 and then (Nkind (Ins_Nod) /= N_Procedure_Call_Statement
2566 or else not Is_Init_Proc (Name (Ins_Nod)))
2567 loop
2568 Next (Ins_Nod);
2569 end loop;
2571 -- The IC routine copies the inherited slots of the C+ part
2572 -- of the dispatch table from the parent and updates the
2573 -- overridden C++ slots.
2575 if CPP_Num_Prims (Rec_Type) > 0 then
2576 declare
2577 Init_DT : Entity_Id;
2578 New_Nod : Node_Id;
2580 begin
2581 Init_DT := CPP_Init_Proc (Rec_Type);
2582 pragma Assert (Present (Init_DT));
2584 New_Nod :=
2585 Make_Procedure_Call_Statement (Loc,
2586 New_Occurrence_Of (Init_DT, Loc));
2587 Insert_After (Ins_Nod, New_Nod);
2589 -- Update location of init tag statements
2591 Ins_Nod := New_Nod;
2592 end;
2593 end if;
2595 Insert_List_After (Ins_Nod, Init_Tags_List);
2596 end;
2597 end if;
2599 -- Ada 2005 (AI-251): Initialize the secondary tag components
2600 -- located at variable positions. We delay the generation of this
2601 -- code until here because the value of the attribute 'Position
2602 -- applied to variable size components of the parent type that
2603 -- depend on discriminants is only safely read at runtime after
2604 -- the parent components have been initialized.
2606 if Ada_Version >= Ada_2005
2607 and then not Is_Interface (Rec_Type)
2608 and then Has_Interfaces (Rec_Type)
2609 and then Has_Discriminants (Etype (Rec_Type))
2610 and then Is_Variable_Size_Record (Etype (Rec_Type))
2611 then
2612 Init_Tags_List := New_List;
2614 Init_Secondary_Tags
2615 (Typ => Rec_Type,
2616 Target => Make_Identifier (Loc, Name_uInit),
2617 Stmts_List => Init_Tags_List,
2618 Fixed_Comps => False,
2619 Variable_Comps => True);
2621 if Is_Non_Empty_List (Init_Tags_List) then
2622 Append_List_To (Body_Stmts, Init_Tags_List);
2623 end if;
2624 end if;
2625 end if;
2627 Handled_Stmt_Node := New_Node (N_Handled_Sequence_Of_Statements, Loc);
2628 Set_Statements (Handled_Stmt_Node, Body_Stmts);
2630 -- Generate:
2631 -- Deep_Finalize (_init, C1, ..., CN);
2632 -- raise;
2634 if Counter > 0
2635 and then Needs_Finalization (Rec_Type)
2636 and then not Is_Abstract_Type (Rec_Type)
2637 and then not Restriction_Active (No_Exception_Propagation)
2638 then
2639 declare
2640 DF_Call : Node_Id;
2641 DF_Id : Entity_Id;
2643 begin
2644 -- Create a local version of Deep_Finalize which has indication
2645 -- of partial initialization state.
2647 DF_Id := Make_Temporary (Loc, 'F');
2649 Append_To (Decls, Make_Local_Deep_Finalize (Rec_Type, DF_Id));
2651 DF_Call :=
2652 Make_Procedure_Call_Statement (Loc,
2653 Name => New_Occurrence_Of (DF_Id, Loc),
2654 Parameter_Associations => New_List (
2655 Make_Identifier (Loc, Name_uInit),
2656 New_Occurrence_Of (Standard_False, Loc)));
2658 -- Do not emit warnings related to the elaboration order when a
2659 -- controlled object is declared before the body of Finalize is
2660 -- seen.
2662 Set_No_Elaboration_Check (DF_Call);
2664 Set_Exception_Handlers (Handled_Stmt_Node, New_List (
2665 Make_Exception_Handler (Loc,
2666 Exception_Choices => New_List (
2667 Make_Others_Choice (Loc)),
2668 Statements => New_List (
2669 DF_Call,
2670 Make_Raise_Statement (Loc)))));
2671 end;
2672 else
2673 Set_Exception_Handlers (Handled_Stmt_Node, No_List);
2674 end if;
2676 Set_Handled_Statement_Sequence (Body_Node, Handled_Stmt_Node);
2678 if not Debug_Generated_Code then
2679 Set_Debug_Info_Off (Proc_Id);
2680 end if;
2682 -- Associate Init_Proc with type, and determine if the procedure
2683 -- is null (happens because of the Initialize_Scalars pragma case,
2684 -- where we have to generate a null procedure in case it is called
2685 -- by a client with Initialize_Scalars set). Such procedures have
2686 -- to be generated, but do not have to be called, so we mark them
2687 -- as null to suppress the call.
2689 Set_Init_Proc (Rec_Type, Proc_Id);
2691 if List_Length (Body_Stmts) = 1
2693 -- We must skip SCIL nodes because they may have been added to this
2694 -- list by Insert_Actions.
2696 and then Nkind (First_Non_SCIL_Node (Body_Stmts)) = N_Null_Statement
2697 and then VM_Target = No_VM
2698 then
2699 -- Even though the init proc may be null at this time it might get
2700 -- some stuff added to it later by the VM backend.
2702 Set_Is_Null_Init_Proc (Proc_Id);
2703 end if;
2704 end Build_Init_Procedure;
2706 ---------------------------
2707 -- Build_Init_Statements --
2708 ---------------------------
2710 function Build_Init_Statements (Comp_List : Node_Id) return List_Id is
2711 Checks : constant List_Id := New_List;
2712 Actions : List_Id := No_List;
2713 Counter_Id : Entity_Id := Empty;
2714 Comp_Loc : Source_Ptr;
2715 Decl : Node_Id;
2716 Has_POC : Boolean;
2717 Id : Entity_Id;
2718 Parent_Stmts : List_Id;
2719 Stmts : List_Id;
2720 Typ : Entity_Id;
2722 procedure Increment_Counter (Loc : Source_Ptr);
2723 -- Generate an "increment by one" statement for the current counter
2724 -- and append it to the list Stmts.
2726 procedure Make_Counter (Loc : Source_Ptr);
2727 -- Create a new counter for the current component list. The routine
2728 -- creates a new defining Id, adds an object declaration and sets
2729 -- the Id generator for the next variant.
2731 -----------------------
2732 -- Increment_Counter --
2733 -----------------------
2735 procedure Increment_Counter (Loc : Source_Ptr) is
2736 begin
2737 -- Generate:
2738 -- Counter := Counter + 1;
2740 Append_To (Stmts,
2741 Make_Assignment_Statement (Loc,
2742 Name => New_Occurrence_Of (Counter_Id, Loc),
2743 Expression =>
2744 Make_Op_Add (Loc,
2745 Left_Opnd => New_Occurrence_Of (Counter_Id, Loc),
2746 Right_Opnd => Make_Integer_Literal (Loc, 1))));
2747 end Increment_Counter;
2749 ------------------
2750 -- Make_Counter --
2751 ------------------
2753 procedure Make_Counter (Loc : Source_Ptr) is
2754 begin
2755 -- Increment the Id generator
2757 Counter := Counter + 1;
2759 -- Create the entity and declaration
2761 Counter_Id :=
2762 Make_Defining_Identifier (Loc,
2763 Chars => New_External_Name ('C', Counter));
2765 -- Generate:
2766 -- Cnn : Integer := 0;
2768 Append_To (Decls,
2769 Make_Object_Declaration (Loc,
2770 Defining_Identifier => Counter_Id,
2771 Object_Definition =>
2772 New_Occurrence_Of (Standard_Integer, Loc),
2773 Expression =>
2774 Make_Integer_Literal (Loc, 0)));
2775 end Make_Counter;
2777 -- Start of processing for Build_Init_Statements
2779 begin
2780 if Null_Present (Comp_List) then
2781 return New_List (Make_Null_Statement (Loc));
2782 end if;
2784 Parent_Stmts := New_List;
2785 Stmts := New_List;
2787 -- Loop through visible declarations of task types and protected
2788 -- types moving any expanded code from the spec to the body of the
2789 -- init procedure.
2791 if Is_Task_Record_Type (Rec_Type)
2792 or else Is_Protected_Record_Type (Rec_Type)
2793 then
2794 declare
2795 Decl : constant Node_Id :=
2796 Parent (Corresponding_Concurrent_Type (Rec_Type));
2797 Def : Node_Id;
2798 N1 : Node_Id;
2799 N2 : Node_Id;
2801 begin
2802 if Is_Task_Record_Type (Rec_Type) then
2803 Def := Task_Definition (Decl);
2804 else
2805 Def := Protected_Definition (Decl);
2806 end if;
2808 if Present (Def) then
2809 N1 := First (Visible_Declarations (Def));
2810 while Present (N1) loop
2811 N2 := N1;
2812 N1 := Next (N1);
2814 if Nkind (N2) in N_Statement_Other_Than_Procedure_Call
2815 or else Nkind (N2) in N_Raise_xxx_Error
2816 or else Nkind (N2) = N_Procedure_Call_Statement
2817 then
2818 Append_To (Stmts,
2819 New_Copy_Tree (N2, New_Scope => Proc_Id));
2820 Rewrite (N2, Make_Null_Statement (Sloc (N2)));
2821 Analyze (N2);
2822 end if;
2823 end loop;
2824 end if;
2825 end;
2826 end if;
2828 -- Loop through components, skipping pragmas, in 2 steps. The first
2829 -- step deals with regular components. The second step deals with
2830 -- components that have per object constraints and no explicit
2831 -- initialization.
2833 Has_POC := False;
2835 -- First pass : regular components
2837 Decl := First_Non_Pragma (Component_Items (Comp_List));
2838 while Present (Decl) loop
2839 Comp_Loc := Sloc (Decl);
2840 Build_Record_Checks
2841 (Subtype_Indication (Component_Definition (Decl)), Checks);
2843 Id := Defining_Identifier (Decl);
2844 Typ := Etype (Id);
2846 -- Leave any processing of per-object constrained component for
2847 -- the second pass.
2849 if Has_Access_Constraint (Id) and then No (Expression (Decl)) then
2850 Has_POC := True;
2852 -- Regular component cases
2854 else
2855 -- In the context of the init proc, references to discriminants
2856 -- resolve to denote the discriminals: this is where we can
2857 -- freeze discriminant dependent component subtypes.
2859 if not Is_Frozen (Typ) then
2860 Append_List_To (Stmts, Freeze_Entity (Typ, N));
2861 end if;
2863 -- Explicit initialization
2865 if Present (Expression (Decl)) then
2866 if Is_CPP_Constructor_Call (Expression (Decl)) then
2867 Actions :=
2868 Build_Initialization_Call
2869 (Comp_Loc,
2870 Id_Ref =>
2871 Make_Selected_Component (Comp_Loc,
2872 Prefix =>
2873 Make_Identifier (Comp_Loc, Name_uInit),
2874 Selector_Name =>
2875 New_Occurrence_Of (Id, Comp_Loc)),
2876 Typ => Typ,
2877 In_Init_Proc => True,
2878 Enclos_Type => Rec_Type,
2879 Discr_Map => Discr_Map,
2880 Constructor_Ref => Expression (Decl));
2881 else
2882 Actions := Build_Assignment (Id, Expression (Decl));
2883 end if;
2885 -- CPU, Dispatching_Domain, Priority and Size components are
2886 -- filled with the corresponding rep item expression of the
2887 -- concurrent type (if any).
2889 elsif Ekind (Scope (Id)) = E_Record_Type
2890 and then Present (Corresponding_Concurrent_Type (Scope (Id)))
2891 and then Nam_In (Chars (Id), Name_uCPU,
2892 Name_uDispatching_Domain,
2893 Name_uPriority)
2894 then
2895 declare
2896 Exp : Node_Id;
2897 Nam : Name_Id;
2898 Ritem : Node_Id;
2900 begin
2901 if Chars (Id) = Name_uCPU then
2902 Nam := Name_CPU;
2904 elsif Chars (Id) = Name_uDispatching_Domain then
2905 Nam := Name_Dispatching_Domain;
2907 elsif Chars (Id) = Name_uPriority then
2908 Nam := Name_Priority;
2909 end if;
2911 -- Get the Rep Item (aspect specification, attribute
2912 -- definition clause or pragma) of the corresponding
2913 -- concurrent type.
2915 Ritem :=
2916 Get_Rep_Item
2917 (Corresponding_Concurrent_Type (Scope (Id)),
2918 Nam,
2919 Check_Parents => False);
2921 if Present (Ritem) then
2923 -- Pragma case
2925 if Nkind (Ritem) = N_Pragma then
2926 Exp := First (Pragma_Argument_Associations (Ritem));
2928 if Nkind (Exp) = N_Pragma_Argument_Association then
2929 Exp := Expression (Exp);
2930 end if;
2932 -- Conversion for Priority expression
2934 if Nam = Name_Priority then
2935 if Pragma_Name (Ritem) = Name_Priority
2936 and then not GNAT_Mode
2937 then
2938 Exp := Convert_To (RTE (RE_Priority), Exp);
2939 else
2940 Exp :=
2941 Convert_To (RTE (RE_Any_Priority), Exp);
2942 end if;
2943 end if;
2945 -- Aspect/Attribute definition clause case
2947 else
2948 Exp := Expression (Ritem);
2950 -- Conversion for Priority expression
2952 if Nam = Name_Priority then
2953 if Chars (Ritem) = Name_Priority
2954 and then not GNAT_Mode
2955 then
2956 Exp := Convert_To (RTE (RE_Priority), Exp);
2957 else
2958 Exp :=
2959 Convert_To (RTE (RE_Any_Priority), Exp);
2960 end if;
2961 end if;
2962 end if;
2964 -- Conversion for Dispatching_Domain value
2966 if Nam = Name_Dispatching_Domain then
2967 Exp :=
2968 Unchecked_Convert_To
2969 (RTE (RE_Dispatching_Domain_Access), Exp);
2970 end if;
2972 Actions := Build_Assignment (Id, Exp);
2974 -- Nothing needed if no Rep Item
2976 else
2977 Actions := No_List;
2978 end if;
2979 end;
2981 -- Composite component with its own Init_Proc
2983 elsif not Is_Interface (Typ)
2984 and then Has_Non_Null_Base_Init_Proc (Typ)
2985 then
2986 Actions :=
2987 Build_Initialization_Call
2988 (Comp_Loc,
2989 Make_Selected_Component (Comp_Loc,
2990 Prefix =>
2991 Make_Identifier (Comp_Loc, Name_uInit),
2992 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
2993 Typ,
2994 In_Init_Proc => True,
2995 Enclos_Type => Rec_Type,
2996 Discr_Map => Discr_Map);
2998 Clean_Task_Names (Typ, Proc_Id);
3000 -- Simple initialization
3002 elsif Component_Needs_Simple_Initialization (Typ) then
3003 Actions :=
3004 Build_Assignment
3005 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id)));
3007 -- Nothing needed for this case
3009 else
3010 Actions := No_List;
3011 end if;
3013 if Present (Checks) then
3014 if Chars (Id) = Name_uParent then
3015 Append_List_To (Parent_Stmts, Checks);
3016 else
3017 Append_List_To (Stmts, Checks);
3018 end if;
3019 end if;
3021 if Present (Actions) then
3022 if Chars (Id) = Name_uParent then
3023 Append_List_To (Parent_Stmts, Actions);
3025 else
3026 Append_List_To (Stmts, Actions);
3028 -- Preserve initialization state in the current counter
3030 if Needs_Finalization (Typ) then
3031 if No (Counter_Id) then
3032 Make_Counter (Comp_Loc);
3033 end if;
3035 Increment_Counter (Comp_Loc);
3036 end if;
3037 end if;
3038 end if;
3039 end if;
3041 Next_Non_Pragma (Decl);
3042 end loop;
3044 -- The parent field must be initialized first because variable
3045 -- size components of the parent affect the location of all the
3046 -- new components.
3048 Prepend_List_To (Stmts, Parent_Stmts);
3050 -- Set up tasks and protected object support. This needs to be done
3051 -- before any component with a per-object access discriminant
3052 -- constraint, or any variant part (which may contain such
3053 -- components) is initialized, because the initialization of these
3054 -- components may reference the enclosing concurrent object.
3056 -- For a task record type, add the task create call and calls to bind
3057 -- any interrupt (signal) entries.
3059 if Is_Task_Record_Type (Rec_Type) then
3061 -- In the case of the restricted run time the ATCB has already
3062 -- been preallocated.
3064 if Restricted_Profile then
3065 Append_To (Stmts,
3066 Make_Assignment_Statement (Loc,
3067 Name =>
3068 Make_Selected_Component (Loc,
3069 Prefix => Make_Identifier (Loc, Name_uInit),
3070 Selector_Name => Make_Identifier (Loc, Name_uTask_Id)),
3071 Expression =>
3072 Make_Attribute_Reference (Loc,
3073 Prefix =>
3074 Make_Selected_Component (Loc,
3075 Prefix => Make_Identifier (Loc, Name_uInit),
3076 Selector_Name => Make_Identifier (Loc, Name_uATCB)),
3077 Attribute_Name => Name_Unchecked_Access)));
3078 end if;
3080 Append_To (Stmts, Make_Task_Create_Call (Rec_Type));
3082 declare
3083 Task_Type : constant Entity_Id :=
3084 Corresponding_Concurrent_Type (Rec_Type);
3085 Task_Decl : constant Node_Id := Parent (Task_Type);
3086 Task_Def : constant Node_Id := Task_Definition (Task_Decl);
3087 Decl_Loc : Source_Ptr;
3088 Ent : Entity_Id;
3089 Vis_Decl : Node_Id;
3091 begin
3092 if Present (Task_Def) then
3093 Vis_Decl := First (Visible_Declarations (Task_Def));
3094 while Present (Vis_Decl) loop
3095 Decl_Loc := Sloc (Vis_Decl);
3097 if Nkind (Vis_Decl) = N_Attribute_Definition_Clause then
3098 if Get_Attribute_Id (Chars (Vis_Decl)) =
3099 Attribute_Address
3100 then
3101 Ent := Entity (Name (Vis_Decl));
3103 if Ekind (Ent) = E_Entry then
3104 Append_To (Stmts,
3105 Make_Procedure_Call_Statement (Decl_Loc,
3106 Name =>
3107 New_Occurrence_Of (RTE (
3108 RE_Bind_Interrupt_To_Entry), Decl_Loc),
3109 Parameter_Associations => New_List (
3110 Make_Selected_Component (Decl_Loc,
3111 Prefix =>
3112 Make_Identifier (Decl_Loc, Name_uInit),
3113 Selector_Name =>
3114 Make_Identifier
3115 (Decl_Loc, Name_uTask_Id)),
3116 Entry_Index_Expression
3117 (Decl_Loc, Ent, Empty, Task_Type),
3118 Expression (Vis_Decl))));
3119 end if;
3120 end if;
3121 end if;
3123 Next (Vis_Decl);
3124 end loop;
3125 end if;
3126 end;
3127 end if;
3129 -- For a protected type, add statements generated by
3130 -- Make_Initialize_Protection.
3132 if Is_Protected_Record_Type (Rec_Type) then
3133 Append_List_To (Stmts,
3134 Make_Initialize_Protection (Rec_Type));
3135 end if;
3137 -- Second pass: components with per-object constraints
3139 if Has_POC then
3140 Decl := First_Non_Pragma (Component_Items (Comp_List));
3141 while Present (Decl) loop
3142 Comp_Loc := Sloc (Decl);
3143 Id := Defining_Identifier (Decl);
3144 Typ := Etype (Id);
3146 if Has_Access_Constraint (Id)
3147 and then No (Expression (Decl))
3148 then
3149 if Has_Non_Null_Base_Init_Proc (Typ) then
3150 Append_List_To (Stmts,
3151 Build_Initialization_Call (Comp_Loc,
3152 Make_Selected_Component (Comp_Loc,
3153 Prefix =>
3154 Make_Identifier (Comp_Loc, Name_uInit),
3155 Selector_Name => New_Occurrence_Of (Id, Comp_Loc)),
3156 Typ,
3157 In_Init_Proc => True,
3158 Enclos_Type => Rec_Type,
3159 Discr_Map => Discr_Map));
3161 Clean_Task_Names (Typ, Proc_Id);
3163 -- Preserve initialization state in the current counter
3165 if Needs_Finalization (Typ) then
3166 if No (Counter_Id) then
3167 Make_Counter (Comp_Loc);
3168 end if;
3170 Increment_Counter (Comp_Loc);
3171 end if;
3173 elsif Component_Needs_Simple_Initialization (Typ) then
3174 Append_List_To (Stmts,
3175 Build_Assignment
3176 (Id, Get_Simple_Init_Val (Typ, N, Esize (Id))));
3177 end if;
3178 end if;
3180 Next_Non_Pragma (Decl);
3181 end loop;
3182 end if;
3184 -- Process the variant part
3186 if Present (Variant_Part (Comp_List)) then
3187 declare
3188 Variant_Alts : constant List_Id := New_List;
3189 Var_Loc : Source_Ptr;
3190 Variant : Node_Id;
3192 begin
3193 Variant :=
3194 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3195 while Present (Variant) loop
3196 Var_Loc := Sloc (Variant);
3197 Append_To (Variant_Alts,
3198 Make_Case_Statement_Alternative (Var_Loc,
3199 Discrete_Choices =>
3200 New_Copy_List (Discrete_Choices (Variant)),
3201 Statements =>
3202 Build_Init_Statements (Component_List (Variant))));
3203 Next_Non_Pragma (Variant);
3204 end loop;
3206 -- The expression of the case statement which is a reference
3207 -- to one of the discriminants is replaced by the appropriate
3208 -- formal parameter of the initialization procedure.
3210 Append_To (Stmts,
3211 Make_Case_Statement (Var_Loc,
3212 Expression =>
3213 New_Occurrence_Of (Discriminal (
3214 Entity (Name (Variant_Part (Comp_List)))), Var_Loc),
3215 Alternatives => Variant_Alts));
3216 end;
3217 end if;
3219 -- If no initializations when generated for component declarations
3220 -- corresponding to this Stmts, append a null statement to Stmts to
3221 -- to make it a valid Ada tree.
3223 if Is_Empty_List (Stmts) then
3224 Append (Make_Null_Statement (Loc), Stmts);
3225 end if;
3227 return Stmts;
3229 exception
3230 when RE_Not_Available =>
3231 return Empty_List;
3232 end Build_Init_Statements;
3234 -------------------------
3235 -- Build_Record_Checks --
3236 -------------------------
3238 procedure Build_Record_Checks (S : Node_Id; Check_List : List_Id) is
3239 Subtype_Mark_Id : Entity_Id;
3241 procedure Constrain_Array
3242 (SI : Node_Id;
3243 Check_List : List_Id);
3244 -- Apply a list of index constraints to an unconstrained array type.
3245 -- The first parameter is the entity for the resulting subtype.
3246 -- Check_List is a list to which the check actions are appended.
3248 ---------------------
3249 -- Constrain_Array --
3250 ---------------------
3252 procedure Constrain_Array
3253 (SI : Node_Id;
3254 Check_List : List_Id)
3256 C : constant Node_Id := Constraint (SI);
3257 Number_Of_Constraints : Nat := 0;
3258 Index : Node_Id;
3259 S, T : Entity_Id;
3261 procedure Constrain_Index
3262 (Index : Node_Id;
3263 S : Node_Id;
3264 Check_List : List_Id);
3265 -- Process an index constraint in a constrained array declaration.
3266 -- The constraint can be either a subtype name or a range with or
3267 -- without an explicit subtype mark. Index is the corresponding
3268 -- index of the unconstrained array. S is the range expression.
3269 -- Check_List is a list to which the check actions are appended.
3271 ---------------------
3272 -- Constrain_Index --
3273 ---------------------
3275 procedure Constrain_Index
3276 (Index : Node_Id;
3277 S : Node_Id;
3278 Check_List : List_Id)
3280 T : constant Entity_Id := Etype (Index);
3282 begin
3283 if Nkind (S) = N_Range then
3284 Process_Range_Expr_In_Decl (S, T, Check_List => Check_List);
3285 end if;
3286 end Constrain_Index;
3288 -- Start of processing for Constrain_Array
3290 begin
3291 T := Entity (Subtype_Mark (SI));
3293 if Is_Access_Type (T) then
3294 T := Designated_Type (T);
3295 end if;
3297 S := First (Constraints (C));
3298 while Present (S) loop
3299 Number_Of_Constraints := Number_Of_Constraints + 1;
3300 Next (S);
3301 end loop;
3303 -- In either case, the index constraint must provide a discrete
3304 -- range for each index of the array type and the type of each
3305 -- discrete range must be the same as that of the corresponding
3306 -- index. (RM 3.6.1)
3308 S := First (Constraints (C));
3309 Index := First_Index (T);
3310 Analyze (Index);
3312 -- Apply constraints to each index type
3314 for J in 1 .. Number_Of_Constraints loop
3315 Constrain_Index (Index, S, Check_List);
3316 Next (Index);
3317 Next (S);
3318 end loop;
3319 end Constrain_Array;
3321 -- Start of processing for Build_Record_Checks
3323 begin
3324 if Nkind (S) = N_Subtype_Indication then
3325 Find_Type (Subtype_Mark (S));
3326 Subtype_Mark_Id := Entity (Subtype_Mark (S));
3328 -- Remaining processing depends on type
3330 case Ekind (Subtype_Mark_Id) is
3332 when Array_Kind =>
3333 Constrain_Array (S, Check_List);
3335 when others =>
3336 null;
3337 end case;
3338 end if;
3339 end Build_Record_Checks;
3341 -------------------------------------------
3342 -- Component_Needs_Simple_Initialization --
3343 -------------------------------------------
3345 function Component_Needs_Simple_Initialization
3346 (T : Entity_Id) return Boolean
3348 begin
3349 return
3350 Needs_Simple_Initialization (T)
3351 and then not Is_RTE (T, RE_Tag)
3353 -- Ada 2005 (AI-251): Check also the tag of abstract interfaces
3355 and then not Is_RTE (T, RE_Interface_Tag);
3356 end Component_Needs_Simple_Initialization;
3358 --------------------------------------
3359 -- Parent_Subtype_Renaming_Discrims --
3360 --------------------------------------
3362 function Parent_Subtype_Renaming_Discrims return Boolean is
3363 De : Entity_Id;
3364 Dp : Entity_Id;
3366 begin
3367 if Base_Type (Rec_Ent) /= Rec_Ent then
3368 return False;
3369 end if;
3371 if Etype (Rec_Ent) = Rec_Ent
3372 or else not Has_Discriminants (Rec_Ent)
3373 or else Is_Constrained (Rec_Ent)
3374 or else Is_Tagged_Type (Rec_Ent)
3375 then
3376 return False;
3377 end if;
3379 -- If there are no explicit stored discriminants we have inherited
3380 -- the root type discriminants so far, so no renamings occurred.
3382 if First_Discriminant (Rec_Ent) =
3383 First_Stored_Discriminant (Rec_Ent)
3384 then
3385 return False;
3386 end if;
3388 -- Check if we have done some trivial renaming of the parent
3389 -- discriminants, i.e. something like
3391 -- type DT (X1, X2: int) is new PT (X1, X2);
3393 De := First_Discriminant (Rec_Ent);
3394 Dp := First_Discriminant (Etype (Rec_Ent));
3395 while Present (De) loop
3396 pragma Assert (Present (Dp));
3398 if Corresponding_Discriminant (De) /= Dp then
3399 return True;
3400 end if;
3402 Next_Discriminant (De);
3403 Next_Discriminant (Dp);
3404 end loop;
3406 return Present (Dp);
3407 end Parent_Subtype_Renaming_Discrims;
3409 ------------------------
3410 -- Requires_Init_Proc --
3411 ------------------------
3413 function Requires_Init_Proc (Rec_Id : Entity_Id) return Boolean is
3414 Comp_Decl : Node_Id;
3415 Id : Entity_Id;
3416 Typ : Entity_Id;
3418 begin
3419 -- Definitely do not need one if specifically suppressed
3421 if Initialization_Suppressed (Rec_Id) then
3422 return False;
3423 end if;
3425 -- If it is a type derived from a type with unknown discriminants,
3426 -- we cannot build an initialization procedure for it.
3428 if Has_Unknown_Discriminants (Rec_Id)
3429 or else Has_Unknown_Discriminants (Etype (Rec_Id))
3430 then
3431 return False;
3432 end if;
3434 -- Otherwise we need to generate an initialization procedure if
3435 -- Is_CPP_Class is False and at least one of the following applies:
3437 -- 1. Discriminants are present, since they need to be initialized
3438 -- with the appropriate discriminant constraint expressions.
3439 -- However, the discriminant of an unchecked union does not
3440 -- count, since the discriminant is not present.
3442 -- 2. The type is a tagged type, since the implicit Tag component
3443 -- needs to be initialized with a pointer to the dispatch table.
3445 -- 3. The type contains tasks
3447 -- 4. One or more components has an initial value
3449 -- 5. One or more components is for a type which itself requires
3450 -- an initialization procedure.
3452 -- 6. One or more components is a type that requires simple
3453 -- initialization (see Needs_Simple_Initialization), except
3454 -- that types Tag and Interface_Tag are excluded, since fields
3455 -- of these types are initialized by other means.
3457 -- 7. The type is the record type built for a task type (since at
3458 -- the very least, Create_Task must be called)
3460 -- 8. The type is the record type built for a protected type (since
3461 -- at least Initialize_Protection must be called)
3463 -- 9. The type is marked as a public entity. The reason we add this
3464 -- case (even if none of the above apply) is to properly handle
3465 -- Initialize_Scalars. If a package is compiled without an IS
3466 -- pragma, and the client is compiled with an IS pragma, then
3467 -- the client will think an initialization procedure is present
3468 -- and call it, when in fact no such procedure is required, but
3469 -- since the call is generated, there had better be a routine
3470 -- at the other end of the call, even if it does nothing).
3472 -- Note: the reason we exclude the CPP_Class case is because in this
3473 -- case the initialization is performed by the C++ constructors, and
3474 -- the IP is built by Set_CPP_Constructors.
3476 if Is_CPP_Class (Rec_Id) then
3477 return False;
3479 elsif Is_Interface (Rec_Id) then
3480 return False;
3482 elsif (Has_Discriminants (Rec_Id)
3483 and then not Is_Unchecked_Union (Rec_Id))
3484 or else Is_Tagged_Type (Rec_Id)
3485 or else Is_Concurrent_Record_Type (Rec_Id)
3486 or else Has_Task (Rec_Id)
3487 then
3488 return True;
3489 end if;
3491 Id := First_Component (Rec_Id);
3492 while Present (Id) loop
3493 Comp_Decl := Parent (Id);
3494 Typ := Etype (Id);
3496 if Present (Expression (Comp_Decl))
3497 or else Has_Non_Null_Base_Init_Proc (Typ)
3498 or else Component_Needs_Simple_Initialization (Typ)
3499 then
3500 return True;
3501 end if;
3503 Next_Component (Id);
3504 end loop;
3506 -- As explained above, a record initialization procedure is needed
3507 -- for public types in case Initialize_Scalars applies to a client.
3508 -- However, such a procedure is not needed in the case where either
3509 -- of restrictions No_Initialize_Scalars or No_Default_Initialization
3510 -- applies. No_Initialize_Scalars excludes the possibility of using
3511 -- Initialize_Scalars in any partition, and No_Default_Initialization
3512 -- implies that no initialization should ever be done for objects of
3513 -- the type, so is incompatible with Initialize_Scalars.
3515 if not Restriction_Active (No_Initialize_Scalars)
3516 and then not Restriction_Active (No_Default_Initialization)
3517 and then Is_Public (Rec_Id)
3518 then
3519 return True;
3520 end if;
3522 return False;
3523 end Requires_Init_Proc;
3525 -- Start of processing for Build_Record_Init_Proc
3527 begin
3528 -- Check for value type, which means no initialization required
3530 Rec_Type := Defining_Identifier (N);
3532 if Is_Value_Type (Rec_Type) then
3533 return;
3534 end if;
3536 -- This may be full declaration of a private type, in which case
3537 -- the visible entity is a record, and the private entity has been
3538 -- exchanged with it in the private part of the current package.
3539 -- The initialization procedure is built for the record type, which
3540 -- is retrievable from the private entity.
3542 if Is_Incomplete_Or_Private_Type (Rec_Type) then
3543 Rec_Type := Underlying_Type (Rec_Type);
3544 end if;
3546 -- If we have a variant record with restriction No_Implicit_Conditionals
3547 -- in effect, then we skip building the procedure. This is safe because
3548 -- if we can see the restriction, so can any caller, calls to initialize
3549 -- such records are not allowed for variant records if this restriction
3550 -- is active.
3552 if Has_Variant_Part (Rec_Type)
3553 and then Restriction_Active (No_Implicit_Conditionals)
3554 then
3555 return;
3556 end if;
3558 -- If there are discriminants, build the discriminant map to replace
3559 -- discriminants by their discriminals in complex bound expressions.
3560 -- These only arise for the corresponding records of synchronized types.
3562 if Is_Concurrent_Record_Type (Rec_Type)
3563 and then Has_Discriminants (Rec_Type)
3564 then
3565 declare
3566 Disc : Entity_Id;
3567 begin
3568 Disc := First_Discriminant (Rec_Type);
3569 while Present (Disc) loop
3570 Append_Elmt (Disc, Discr_Map);
3571 Append_Elmt (Discriminal (Disc), Discr_Map);
3572 Next_Discriminant (Disc);
3573 end loop;
3574 end;
3575 end if;
3577 -- Derived types that have no type extension can use the initialization
3578 -- procedure of their parent and do not need a procedure of their own.
3579 -- This is only correct if there are no representation clauses for the
3580 -- type or its parent, and if the parent has in fact been frozen so
3581 -- that its initialization procedure exists.
3583 if Is_Derived_Type (Rec_Type)
3584 and then not Is_Tagged_Type (Rec_Type)
3585 and then not Is_Unchecked_Union (Rec_Type)
3586 and then not Has_New_Non_Standard_Rep (Rec_Type)
3587 and then not Parent_Subtype_Renaming_Discrims
3588 and then Has_Non_Null_Base_Init_Proc (Etype (Rec_Type))
3589 then
3590 Copy_TSS (Base_Init_Proc (Etype (Rec_Type)), Rec_Type);
3592 -- Otherwise if we need an initialization procedure, then build one,
3593 -- mark it as public and inlinable and as having a completion.
3595 elsif Requires_Init_Proc (Rec_Type)
3596 or else Is_Unchecked_Union (Rec_Type)
3597 then
3598 Proc_Id :=
3599 Make_Defining_Identifier (Loc,
3600 Chars => Make_Init_Proc_Name (Rec_Type));
3602 -- If No_Default_Initialization restriction is active, then we don't
3603 -- want to build an init_proc, but we need to mark that an init_proc
3604 -- would be needed if this restriction was not active (so that we can
3605 -- detect attempts to call it), so set a dummy init_proc in place.
3607 if Restriction_Active (No_Default_Initialization) then
3608 Set_Init_Proc (Rec_Type, Proc_Id);
3609 return;
3610 end if;
3612 Build_Offset_To_Top_Functions;
3613 Build_CPP_Init_Procedure;
3614 Build_Init_Procedure;
3615 Set_Is_Public (Proc_Id, Is_Public (Rec_Ent));
3617 -- The initialization of protected records is not worth inlining.
3618 -- In addition, when compiled for another unit for inlining purposes,
3619 -- it may make reference to entities that have not been elaborated
3620 -- yet. Similar considerations apply to task types.
3622 if not Is_Concurrent_Type (Rec_Type)
3623 and then not Has_Task (Rec_Type)
3624 then
3625 Set_Is_Inlined (Proc_Id);
3626 end if;
3628 Set_Is_Internal (Proc_Id);
3629 Set_Has_Completion (Proc_Id);
3631 if not Debug_Generated_Code then
3632 Set_Debug_Info_Off (Proc_Id);
3633 end if;
3635 declare
3636 Agg : constant Node_Id :=
3637 Build_Equivalent_Record_Aggregate (Rec_Type);
3639 procedure Collect_Itypes (Comp : Node_Id);
3640 -- Generate references to itypes in the aggregate, because
3641 -- the first use of the aggregate may be in a nested scope.
3643 --------------------
3644 -- Collect_Itypes --
3645 --------------------
3647 procedure Collect_Itypes (Comp : Node_Id) is
3648 Ref : Node_Id;
3649 Sub_Aggr : Node_Id;
3650 Typ : constant Entity_Id := Etype (Comp);
3652 begin
3653 if Is_Array_Type (Typ) and then Is_Itype (Typ) then
3654 Ref := Make_Itype_Reference (Loc);
3655 Set_Itype (Ref, Typ);
3656 Append_Freeze_Action (Rec_Type, Ref);
3658 Ref := Make_Itype_Reference (Loc);
3659 Set_Itype (Ref, Etype (First_Index (Typ)));
3660 Append_Freeze_Action (Rec_Type, Ref);
3662 -- Recurse on nested arrays
3664 Sub_Aggr := First (Expressions (Comp));
3665 while Present (Sub_Aggr) loop
3666 Collect_Itypes (Sub_Aggr);
3667 Next (Sub_Aggr);
3668 end loop;
3669 end if;
3670 end Collect_Itypes;
3672 begin
3673 -- If there is a static initialization aggregate for the type,
3674 -- generate itype references for the types of its (sub)components,
3675 -- to prevent out-of-scope errors in the resulting tree.
3676 -- The aggregate may have been rewritten as a Raise node, in which
3677 -- case there are no relevant itypes.
3679 if Present (Agg) and then Nkind (Agg) = N_Aggregate then
3680 Set_Static_Initialization (Proc_Id, Agg);
3682 declare
3683 Comp : Node_Id;
3684 begin
3685 Comp := First (Component_Associations (Agg));
3686 while Present (Comp) loop
3687 Collect_Itypes (Expression (Comp));
3688 Next (Comp);
3689 end loop;
3690 end;
3691 end if;
3692 end;
3693 end if;
3694 end Build_Record_Init_Proc;
3696 --------------------------------
3697 -- Build_Record_Invariant_Proc --
3698 --------------------------------
3700 function Build_Record_Invariant_Proc
3701 (R_Type : Entity_Id;
3702 Nod : Node_Id) return Node_Id
3704 Loc : constant Source_Ptr := Sloc (Nod);
3706 Object_Name : constant Name_Id := New_Internal_Name ('I');
3707 -- Name for argument of invariant procedure
3709 Object_Entity : constant Node_Id :=
3710 Make_Defining_Identifier (Loc, Object_Name);
3711 -- The procedure declaration entity for the argument
3713 Invariant_Found : Boolean;
3714 -- Set if any component needs an invariant check.
3716 Proc_Id : Entity_Id;
3717 Proc_Body : Node_Id;
3718 Stmts : List_Id;
3719 Type_Def : Node_Id;
3721 function Build_Invariant_Checks (Comp_List : Node_Id) return List_Id;
3722 -- Recursive procedure that generates a list of checks for components
3723 -- that need it, and recurses through variant parts when present.
3725 function Build_Component_Invariant_Call (Comp : Entity_Id)
3726 return Node_Id;
3727 -- Build call to invariant procedure for a record component.
3729 ------------------------------------
3730 -- Build_Component_Invariant_Call --
3731 ------------------------------------
3733 function Build_Component_Invariant_Call (Comp : Entity_Id)
3734 return Node_Id
3736 Sel_Comp : Node_Id;
3737 Typ : Entity_Id;
3738 Call : Node_Id;
3740 begin
3741 Invariant_Found := True;
3742 Typ := Etype (Comp);
3744 Sel_Comp :=
3745 Make_Selected_Component (Loc,
3746 Prefix => New_Occurrence_Of (Object_Entity, Loc),
3747 Selector_Name => New_Occurrence_Of (Comp, Loc));
3749 if Is_Access_Type (Typ) then
3751 -- If the access component designates a type with an invariant,
3752 -- the check applies to the designated object. The access type
3753 -- itself may have an invariant, in which case it applies to the
3754 -- access value directly.
3756 -- Note: we are assuming that invariants will not occur on both
3757 -- the access type and the type that it designates. This is not
3758 -- really justified but it is hard to imagine that this case will
3759 -- ever cause trouble ???
3761 if not (Has_Invariants (Typ)) then
3762 Sel_Comp := Make_Explicit_Dereference (Loc, Sel_Comp);
3763 Typ := Designated_Type (Typ);
3764 end if;
3765 end if;
3767 -- The aspect is type-specific, so retrieve it from the base type
3769 Call :=
3770 Make_Procedure_Call_Statement (Loc,
3771 Name =>
3772 New_Occurrence_Of (Invariant_Procedure (Base_Type (Typ)), Loc),
3773 Parameter_Associations => New_List (Sel_Comp));
3775 if Is_Access_Type (Etype (Comp)) then
3776 Call :=
3777 Make_If_Statement (Loc,
3778 Condition =>
3779 Make_Op_Ne (Loc,
3780 Left_Opnd => Make_Null (Loc),
3781 Right_Opnd =>
3782 Make_Selected_Component (Loc,
3783 Prefix => New_Occurrence_Of (Object_Entity, Loc),
3784 Selector_Name => New_Occurrence_Of (Comp, Loc))),
3785 Then_Statements => New_List (Call));
3786 end if;
3788 return Call;
3789 end Build_Component_Invariant_Call;
3791 ----------------------------
3792 -- Build_Invariant_Checks --
3793 ----------------------------
3795 function Build_Invariant_Checks (Comp_List : Node_Id) return List_Id is
3796 Decl : Node_Id;
3797 Id : Entity_Id;
3798 Stmts : List_Id;
3800 begin
3801 Stmts := New_List;
3802 Decl := First_Non_Pragma (Component_Items (Comp_List));
3803 while Present (Decl) loop
3804 if Nkind (Decl) = N_Component_Declaration then
3805 Id := Defining_Identifier (Decl);
3807 if Has_Invariants (Etype (Id))
3808 and then In_Open_Scopes (Scope (R_Type))
3809 then
3810 if Has_Unchecked_Union (R_Type) then
3811 Error_Msg_NE
3812 ("invariants cannot be checked on components of "
3813 & "unchecked_union type&?", Decl, R_Type);
3814 return Empty_List;
3816 else
3817 Append_To (Stmts, Build_Component_Invariant_Call (Id));
3818 end if;
3820 elsif Is_Access_Type (Etype (Id))
3821 and then not Is_Access_Constant (Etype (Id))
3822 and then Has_Invariants (Designated_Type (Etype (Id)))
3823 and then In_Open_Scopes (Scope (Designated_Type (Etype (Id))))
3824 then
3825 Append_To (Stmts, Build_Component_Invariant_Call (Id));
3826 end if;
3827 end if;
3829 Next (Decl);
3830 end loop;
3832 if Present (Variant_Part (Comp_List)) then
3833 declare
3834 Variant_Alts : constant List_Id := New_List;
3835 Var_Loc : Source_Ptr;
3836 Variant : Node_Id;
3837 Variant_Stmts : List_Id;
3839 begin
3840 Variant :=
3841 First_Non_Pragma (Variants (Variant_Part (Comp_List)));
3842 while Present (Variant) loop
3843 Variant_Stmts :=
3844 Build_Invariant_Checks (Component_List (Variant));
3845 Var_Loc := Sloc (Variant);
3846 Append_To (Variant_Alts,
3847 Make_Case_Statement_Alternative (Var_Loc,
3848 Discrete_Choices =>
3849 New_Copy_List (Discrete_Choices (Variant)),
3850 Statements => Variant_Stmts));
3852 Next_Non_Pragma (Variant);
3853 end loop;
3855 -- The expression in the case statement is the reference to
3856 -- the discriminant of the target object.
3858 Append_To (Stmts,
3859 Make_Case_Statement (Var_Loc,
3860 Expression =>
3861 Make_Selected_Component (Var_Loc,
3862 Prefix => New_Occurrence_Of (Object_Entity, Var_Loc),
3863 Selector_Name => New_Occurrence_Of
3864 (Entity
3865 (Name (Variant_Part (Comp_List))), Var_Loc)),
3866 Alternatives => Variant_Alts));
3867 end;
3868 end if;
3870 return Stmts;
3871 end Build_Invariant_Checks;
3873 -- Start of processing for Build_Record_Invariant_Proc
3875 begin
3876 Invariant_Found := False;
3877 Type_Def := Type_Definition (Parent (R_Type));
3879 if Nkind (Type_Def) = N_Record_Definition
3880 and then not Null_Present (Type_Def)
3881 then
3882 Stmts := Build_Invariant_Checks (Component_List (Type_Def));
3883 else
3884 return Empty;
3885 end if;
3887 if not Invariant_Found then
3888 return Empty;
3889 end if;
3891 -- The name of the invariant procedure reflects the fact that the
3892 -- checks correspond to invariants on the component types. The
3893 -- record type itself may have invariants that will create a separate
3894 -- procedure whose name carries the Invariant suffix.
3896 Proc_Id :=
3897 Make_Defining_Identifier (Loc,
3898 Chars => New_External_Name (Chars (R_Type), "CInvariant"));
3900 Proc_Body :=
3901 Make_Subprogram_Body (Loc,
3902 Specification =>
3903 Make_Procedure_Specification (Loc,
3904 Defining_Unit_Name => Proc_Id,
3905 Parameter_Specifications => New_List (
3906 Make_Parameter_Specification (Loc,
3907 Defining_Identifier => Object_Entity,
3908 Parameter_Type => New_Occurrence_Of (R_Type, Loc)))),
3910 Declarations => Empty_List,
3911 Handled_Statement_Sequence =>
3912 Make_Handled_Sequence_Of_Statements (Loc,
3913 Statements => Stmts));
3915 Set_Ekind (Proc_Id, E_Procedure);
3916 Set_Is_Public (Proc_Id, Is_Public (R_Type));
3917 Set_Is_Internal (Proc_Id);
3918 Set_Has_Completion (Proc_Id);
3920 return Proc_Body;
3921 -- Insert_After (Nod, Proc_Body);
3922 -- Analyze (Proc_Body);
3923 end Build_Record_Invariant_Proc;
3925 ----------------------------
3926 -- Build_Slice_Assignment --
3927 ----------------------------
3929 -- Generates the following subprogram:
3931 -- procedure Assign
3932 -- (Source, Target : Array_Type,
3933 -- Left_Lo, Left_Hi : Index;
3934 -- Right_Lo, Right_Hi : Index;
3935 -- Rev : Boolean)
3936 -- is
3937 -- Li1 : Index;
3938 -- Ri1 : Index;
3940 -- begin
3942 -- if Left_Hi < Left_Lo then
3943 -- return;
3944 -- end if;
3946 -- if Rev then
3947 -- Li1 := Left_Hi;
3948 -- Ri1 := Right_Hi;
3949 -- else
3950 -- Li1 := Left_Lo;
3951 -- Ri1 := Right_Lo;
3952 -- end if;
3954 -- loop
3955 -- Target (Li1) := Source (Ri1);
3957 -- if Rev then
3958 -- exit when Li1 = Left_Lo;
3959 -- Li1 := Index'pred (Li1);
3960 -- Ri1 := Index'pred (Ri1);
3961 -- else
3962 -- exit when Li1 = Left_Hi;
3963 -- Li1 := Index'succ (Li1);
3964 -- Ri1 := Index'succ (Ri1);
3965 -- end if;
3966 -- end loop;
3967 -- end Assign;
3969 procedure Build_Slice_Assignment (Typ : Entity_Id) is
3970 Loc : constant Source_Ptr := Sloc (Typ);
3971 Index : constant Entity_Id := Base_Type (Etype (First_Index (Typ)));
3973 Larray : constant Entity_Id := Make_Temporary (Loc, 'A');
3974 Rarray : constant Entity_Id := Make_Temporary (Loc, 'R');
3975 Left_Lo : constant Entity_Id := Make_Temporary (Loc, 'L');
3976 Left_Hi : constant Entity_Id := Make_Temporary (Loc, 'L');
3977 Right_Lo : constant Entity_Id := Make_Temporary (Loc, 'R');
3978 Right_Hi : constant Entity_Id := Make_Temporary (Loc, 'R');
3979 Rev : constant Entity_Id := Make_Temporary (Loc, 'D');
3980 -- Formal parameters of procedure
3982 Proc_Name : constant Entity_Id :=
3983 Make_Defining_Identifier (Loc,
3984 Chars => Make_TSS_Name (Typ, TSS_Slice_Assign));
3986 Lnn : constant Entity_Id := Make_Temporary (Loc, 'L');
3987 Rnn : constant Entity_Id := Make_Temporary (Loc, 'R');
3988 -- Subscripts for left and right sides
3990 Decls : List_Id;
3991 Loops : Node_Id;
3992 Stats : List_Id;
3994 begin
3995 -- Build declarations for indexes
3997 Decls := New_List;
3999 Append_To (Decls,
4000 Make_Object_Declaration (Loc,
4001 Defining_Identifier => Lnn,
4002 Object_Definition =>
4003 New_Occurrence_Of (Index, Loc)));
4005 Append_To (Decls,
4006 Make_Object_Declaration (Loc,
4007 Defining_Identifier => Rnn,
4008 Object_Definition =>
4009 New_Occurrence_Of (Index, Loc)));
4011 Stats := New_List;
4013 -- Build test for empty slice case
4015 Append_To (Stats,
4016 Make_If_Statement (Loc,
4017 Condition =>
4018 Make_Op_Lt (Loc,
4019 Left_Opnd => New_Occurrence_Of (Left_Hi, Loc),
4020 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc)),
4021 Then_Statements => New_List (Make_Simple_Return_Statement (Loc))));
4023 -- Build initializations for indexes
4025 declare
4026 F_Init : constant List_Id := New_List;
4027 B_Init : constant List_Id := New_List;
4029 begin
4030 Append_To (F_Init,
4031 Make_Assignment_Statement (Loc,
4032 Name => New_Occurrence_Of (Lnn, Loc),
4033 Expression => New_Occurrence_Of (Left_Lo, Loc)));
4035 Append_To (F_Init,
4036 Make_Assignment_Statement (Loc,
4037 Name => New_Occurrence_Of (Rnn, Loc),
4038 Expression => New_Occurrence_Of (Right_Lo, Loc)));
4040 Append_To (B_Init,
4041 Make_Assignment_Statement (Loc,
4042 Name => New_Occurrence_Of (Lnn, Loc),
4043 Expression => New_Occurrence_Of (Left_Hi, Loc)));
4045 Append_To (B_Init,
4046 Make_Assignment_Statement (Loc,
4047 Name => New_Occurrence_Of (Rnn, Loc),
4048 Expression => New_Occurrence_Of (Right_Hi, Loc)));
4050 Append_To (Stats,
4051 Make_If_Statement (Loc,
4052 Condition => New_Occurrence_Of (Rev, Loc),
4053 Then_Statements => B_Init,
4054 Else_Statements => F_Init));
4055 end;
4057 -- Now construct the assignment statement
4059 Loops :=
4060 Make_Loop_Statement (Loc,
4061 Statements => New_List (
4062 Make_Assignment_Statement (Loc,
4063 Name =>
4064 Make_Indexed_Component (Loc,
4065 Prefix => New_Occurrence_Of (Larray, Loc),
4066 Expressions => New_List (New_Occurrence_Of (Lnn, Loc))),
4067 Expression =>
4068 Make_Indexed_Component (Loc,
4069 Prefix => New_Occurrence_Of (Rarray, Loc),
4070 Expressions => New_List (New_Occurrence_Of (Rnn, Loc))))),
4071 End_Label => Empty);
4073 -- Build the exit condition and increment/decrement statements
4075 declare
4076 F_Ass : constant List_Id := New_List;
4077 B_Ass : constant List_Id := New_List;
4079 begin
4080 Append_To (F_Ass,
4081 Make_Exit_Statement (Loc,
4082 Condition =>
4083 Make_Op_Eq (Loc,
4084 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4085 Right_Opnd => New_Occurrence_Of (Left_Hi, Loc))));
4087 Append_To (F_Ass,
4088 Make_Assignment_Statement (Loc,
4089 Name => New_Occurrence_Of (Lnn, Loc),
4090 Expression =>
4091 Make_Attribute_Reference (Loc,
4092 Prefix =>
4093 New_Occurrence_Of (Index, Loc),
4094 Attribute_Name => Name_Succ,
4095 Expressions => New_List (
4096 New_Occurrence_Of (Lnn, Loc)))));
4098 Append_To (F_Ass,
4099 Make_Assignment_Statement (Loc,
4100 Name => New_Occurrence_Of (Rnn, Loc),
4101 Expression =>
4102 Make_Attribute_Reference (Loc,
4103 Prefix =>
4104 New_Occurrence_Of (Index, Loc),
4105 Attribute_Name => Name_Succ,
4106 Expressions => New_List (
4107 New_Occurrence_Of (Rnn, Loc)))));
4109 Append_To (B_Ass,
4110 Make_Exit_Statement (Loc,
4111 Condition =>
4112 Make_Op_Eq (Loc,
4113 Left_Opnd => New_Occurrence_Of (Lnn, Loc),
4114 Right_Opnd => New_Occurrence_Of (Left_Lo, Loc))));
4116 Append_To (B_Ass,
4117 Make_Assignment_Statement (Loc,
4118 Name => New_Occurrence_Of (Lnn, Loc),
4119 Expression =>
4120 Make_Attribute_Reference (Loc,
4121 Prefix =>
4122 New_Occurrence_Of (Index, Loc),
4123 Attribute_Name => Name_Pred,
4124 Expressions => New_List (
4125 New_Occurrence_Of (Lnn, Loc)))));
4127 Append_To (B_Ass,
4128 Make_Assignment_Statement (Loc,
4129 Name => New_Occurrence_Of (Rnn, Loc),
4130 Expression =>
4131 Make_Attribute_Reference (Loc,
4132 Prefix =>
4133 New_Occurrence_Of (Index, Loc),
4134 Attribute_Name => Name_Pred,
4135 Expressions => New_List (
4136 New_Occurrence_Of (Rnn, Loc)))));
4138 Append_To (Statements (Loops),
4139 Make_If_Statement (Loc,
4140 Condition => New_Occurrence_Of (Rev, Loc),
4141 Then_Statements => B_Ass,
4142 Else_Statements => F_Ass));
4143 end;
4145 Append_To (Stats, Loops);
4147 declare
4148 Spec : Node_Id;
4149 Formals : List_Id := New_List;
4151 begin
4152 Formals := New_List (
4153 Make_Parameter_Specification (Loc,
4154 Defining_Identifier => Larray,
4155 Out_Present => True,
4156 Parameter_Type =>
4157 New_Occurrence_Of (Base_Type (Typ), Loc)),
4159 Make_Parameter_Specification (Loc,
4160 Defining_Identifier => Rarray,
4161 Parameter_Type =>
4162 New_Occurrence_Of (Base_Type (Typ), Loc)),
4164 Make_Parameter_Specification (Loc,
4165 Defining_Identifier => Left_Lo,
4166 Parameter_Type =>
4167 New_Occurrence_Of (Index, Loc)),
4169 Make_Parameter_Specification (Loc,
4170 Defining_Identifier => Left_Hi,
4171 Parameter_Type =>
4172 New_Occurrence_Of (Index, Loc)),
4174 Make_Parameter_Specification (Loc,
4175 Defining_Identifier => Right_Lo,
4176 Parameter_Type =>
4177 New_Occurrence_Of (Index, Loc)),
4179 Make_Parameter_Specification (Loc,
4180 Defining_Identifier => Right_Hi,
4181 Parameter_Type =>
4182 New_Occurrence_Of (Index, Loc)));
4184 Append_To (Formals,
4185 Make_Parameter_Specification (Loc,
4186 Defining_Identifier => Rev,
4187 Parameter_Type =>
4188 New_Occurrence_Of (Standard_Boolean, Loc)));
4190 Spec :=
4191 Make_Procedure_Specification (Loc,
4192 Defining_Unit_Name => Proc_Name,
4193 Parameter_Specifications => Formals);
4195 Discard_Node (
4196 Make_Subprogram_Body (Loc,
4197 Specification => Spec,
4198 Declarations => Decls,
4199 Handled_Statement_Sequence =>
4200 Make_Handled_Sequence_Of_Statements (Loc,
4201 Statements => Stats)));
4202 end;
4204 Set_TSS (Typ, Proc_Name);
4205 Set_Is_Pure (Proc_Name);
4206 end Build_Slice_Assignment;
4208 -----------------------------
4209 -- Build_Untagged_Equality --
4210 -----------------------------
4212 procedure Build_Untagged_Equality (Typ : Entity_Id) is
4213 Build_Eq : Boolean;
4214 Comp : Entity_Id;
4215 Decl : Node_Id;
4216 Op : Entity_Id;
4217 Prim : Elmt_Id;
4218 Eq_Op : Entity_Id;
4220 function User_Defined_Eq (T : Entity_Id) return Entity_Id;
4221 -- Check whether the type T has a user-defined primitive equality. If so
4222 -- return it, else return Empty. If true for a component of Typ, we have
4223 -- to build the primitive equality for it.
4225 ---------------------
4226 -- User_Defined_Eq --
4227 ---------------------
4229 function User_Defined_Eq (T : Entity_Id) return Entity_Id is
4230 Prim : Elmt_Id;
4231 Op : Entity_Id;
4233 begin
4234 Op := TSS (T, TSS_Composite_Equality);
4236 if Present (Op) then
4237 return Op;
4238 end if;
4240 Prim := First_Elmt (Collect_Primitive_Operations (T));
4241 while Present (Prim) loop
4242 Op := Node (Prim);
4244 if Chars (Op) = Name_Op_Eq
4245 and then Etype (Op) = Standard_Boolean
4246 and then Etype (First_Formal (Op)) = T
4247 and then Etype (Next_Formal (First_Formal (Op))) = T
4248 then
4249 return Op;
4250 end if;
4252 Next_Elmt (Prim);
4253 end loop;
4255 return Empty;
4256 end User_Defined_Eq;
4258 -- Start of processing for Build_Untagged_Equality
4260 begin
4261 -- If a record component has a primitive equality operation, we must
4262 -- build the corresponding one for the current type.
4264 Build_Eq := False;
4265 Comp := First_Component (Typ);
4266 while Present (Comp) loop
4267 if Is_Record_Type (Etype (Comp))
4268 and then Present (User_Defined_Eq (Etype (Comp)))
4269 then
4270 Build_Eq := True;
4271 end if;
4273 Next_Component (Comp);
4274 end loop;
4276 -- If there is a user-defined equality for the type, we do not create
4277 -- the implicit one.
4279 Prim := First_Elmt (Collect_Primitive_Operations (Typ));
4280 Eq_Op := Empty;
4281 while Present (Prim) loop
4282 if Chars (Node (Prim)) = Name_Op_Eq
4283 and then Comes_From_Source (Node (Prim))
4285 -- Don't we also need to check formal types and return type as in
4286 -- User_Defined_Eq above???
4288 then
4289 Eq_Op := Node (Prim);
4290 Build_Eq := False;
4291 exit;
4292 end if;
4294 Next_Elmt (Prim);
4295 end loop;
4297 -- If the type is derived, inherit the operation, if present, from the
4298 -- parent type. It may have been declared after the type derivation. If
4299 -- the parent type itself is derived, it may have inherited an operation
4300 -- that has itself been overridden, so update its alias and related
4301 -- flags. Ditto for inequality.
4303 if No (Eq_Op) and then Is_Derived_Type (Typ) then
4304 Prim := First_Elmt (Collect_Primitive_Operations (Etype (Typ)));
4305 while Present (Prim) loop
4306 if Chars (Node (Prim)) = Name_Op_Eq then
4307 Copy_TSS (Node (Prim), Typ);
4308 Build_Eq := False;
4310 declare
4311 Op : constant Entity_Id := User_Defined_Eq (Typ);
4312 Eq_Op : constant Entity_Id := Node (Prim);
4313 NE_Op : constant Entity_Id := Next_Entity (Eq_Op);
4315 begin
4316 if Present (Op) then
4317 Set_Alias (Op, Eq_Op);
4318 Set_Is_Abstract_Subprogram
4319 (Op, Is_Abstract_Subprogram (Eq_Op));
4321 if Chars (Next_Entity (Op)) = Name_Op_Ne then
4322 Set_Is_Abstract_Subprogram
4323 (Next_Entity (Op), Is_Abstract_Subprogram (NE_Op));
4324 end if;
4325 end if;
4326 end;
4328 exit;
4329 end if;
4331 Next_Elmt (Prim);
4332 end loop;
4333 end if;
4335 -- If not inherited and not user-defined, build body as for a type with
4336 -- tagged components.
4338 if Build_Eq then
4339 Decl :=
4340 Make_Eq_Body (Typ, Make_TSS_Name (Typ, TSS_Composite_Equality));
4341 Op := Defining_Entity (Decl);
4342 Set_TSS (Typ, Op);
4343 Set_Is_Pure (Op);
4345 if Is_Library_Level_Entity (Typ) then
4346 Set_Is_Public (Op);
4347 end if;
4348 end if;
4349 end Build_Untagged_Equality;
4351 -----------------------------------
4352 -- Build_Variant_Record_Equality --
4353 -----------------------------------
4355 -- Generates:
4357 -- function _Equality (X, Y : T) return Boolean is
4358 -- begin
4359 -- -- Compare discriminants
4361 -- if X.D1 /= Y.D1 or else X.D2 /= Y.D2 or else ... then
4362 -- return False;
4363 -- end if;
4365 -- -- Compare components
4367 -- if X.C1 /= Y.C1 or else X.C2 /= Y.C2 or else ... then
4368 -- return False;
4369 -- end if;
4371 -- -- Compare variant part
4373 -- case X.D1 is
4374 -- when V1 =>
4375 -- if X.C2 /= Y.C2 or else X.C3 /= Y.C3 or else ... then
4376 -- return False;
4377 -- end if;
4378 -- ...
4379 -- when Vn =>
4380 -- if X.Cn /= Y.Cn or else ... then
4381 -- return False;
4382 -- end if;
4383 -- end case;
4385 -- return True;
4386 -- end _Equality;
4388 procedure Build_Variant_Record_Equality (Typ : Entity_Id) is
4389 Loc : constant Source_Ptr := Sloc (Typ);
4391 F : constant Entity_Id :=
4392 Make_Defining_Identifier (Loc,
4393 Chars => Make_TSS_Name (Typ, TSS_Composite_Equality));
4395 X : constant Entity_Id := Make_Defining_Identifier (Loc, Name_X);
4396 Y : constant Entity_Id := Make_Defining_Identifier (Loc, Name_Y);
4398 Def : constant Node_Id := Parent (Typ);
4399 Comps : constant Node_Id := Component_List (Type_Definition (Def));
4400 Stmts : constant List_Id := New_List;
4401 Pspecs : constant List_Id := New_List;
4403 begin
4404 -- If we have a variant record with restriction No_Implicit_Conditionals
4405 -- in effect, then we skip building the procedure. This is safe because
4406 -- if we can see the restriction, so can any caller, calls to equality
4407 -- test routines are not allowed for variant records if this restriction
4408 -- is active.
4410 if Restriction_Active (No_Implicit_Conditionals) then
4411 return;
4412 end if;
4414 -- Derived Unchecked_Union types no longer inherit the equality function
4415 -- of their parent.
4417 if Is_Derived_Type (Typ)
4418 and then not Is_Unchecked_Union (Typ)
4419 and then not Has_New_Non_Standard_Rep (Typ)
4420 then
4421 declare
4422 Parent_Eq : constant Entity_Id :=
4423 TSS (Root_Type (Typ), TSS_Composite_Equality);
4424 begin
4425 if Present (Parent_Eq) then
4426 Copy_TSS (Parent_Eq, Typ);
4427 return;
4428 end if;
4429 end;
4430 end if;
4432 Discard_Node (
4433 Make_Subprogram_Body (Loc,
4434 Specification =>
4435 Make_Function_Specification (Loc,
4436 Defining_Unit_Name => F,
4437 Parameter_Specifications => Pspecs,
4438 Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)),
4439 Declarations => New_List,
4440 Handled_Statement_Sequence =>
4441 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts)));
4443 Append_To (Pspecs,
4444 Make_Parameter_Specification (Loc,
4445 Defining_Identifier => X,
4446 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4448 Append_To (Pspecs,
4449 Make_Parameter_Specification (Loc,
4450 Defining_Identifier => Y,
4451 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
4453 -- Unchecked_Unions require additional machinery to support equality.
4454 -- Two extra parameters (A and B) are added to the equality function
4455 -- parameter list for each discriminant of the type, in order to
4456 -- capture the inferred values of the discriminants in equality calls.
4457 -- The names of the parameters match the names of the corresponding
4458 -- discriminant, with an added suffix.
4460 if Is_Unchecked_Union (Typ) then
4461 declare
4462 Discr : Entity_Id;
4463 Discr_Type : Entity_Id;
4464 A, B : Entity_Id;
4465 New_Discrs : Elist_Id;
4467 begin
4468 New_Discrs := New_Elmt_List;
4470 Discr := First_Discriminant (Typ);
4471 while Present (Discr) loop
4472 Discr_Type := Etype (Discr);
4473 A := Make_Defining_Identifier (Loc,
4474 Chars => New_External_Name (Chars (Discr), 'A'));
4476 B := Make_Defining_Identifier (Loc,
4477 Chars => New_External_Name (Chars (Discr), 'B'));
4479 -- Add new parameters to the parameter list
4481 Append_To (Pspecs,
4482 Make_Parameter_Specification (Loc,
4483 Defining_Identifier => A,
4484 Parameter_Type =>
4485 New_Occurrence_Of (Discr_Type, Loc)));
4487 Append_To (Pspecs,
4488 Make_Parameter_Specification (Loc,
4489 Defining_Identifier => B,
4490 Parameter_Type =>
4491 New_Occurrence_Of (Discr_Type, Loc)));
4493 Append_Elmt (A, New_Discrs);
4495 -- Generate the following code to compare each of the inferred
4496 -- discriminants:
4498 -- if a /= b then
4499 -- return False;
4500 -- end if;
4502 Append_To (Stmts,
4503 Make_If_Statement (Loc,
4504 Condition =>
4505 Make_Op_Ne (Loc,
4506 Left_Opnd => New_Occurrence_Of (A, Loc),
4507 Right_Opnd => New_Occurrence_Of (B, Loc)),
4508 Then_Statements => New_List (
4509 Make_Simple_Return_Statement (Loc,
4510 Expression =>
4511 New_Occurrence_Of (Standard_False, Loc)))));
4512 Next_Discriminant (Discr);
4513 end loop;
4515 -- Generate component-by-component comparison. Note that we must
4516 -- propagate the inferred discriminants formals to act as
4517 -- the case statement switch. Their value is added when an
4518 -- equality call on unchecked unions is expanded.
4520 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps, New_Discrs));
4521 end;
4523 -- Normal case (not unchecked union)
4525 else
4526 Append_To (Stmts,
4527 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
4528 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
4529 end if;
4531 Append_To (Stmts,
4532 Make_Simple_Return_Statement (Loc,
4533 Expression => New_Occurrence_Of (Standard_True, Loc)));
4535 Set_TSS (Typ, F);
4536 Set_Is_Pure (F);
4538 if not Debug_Generated_Code then
4539 Set_Debug_Info_Off (F);
4540 end if;
4541 end Build_Variant_Record_Equality;
4543 -----------------------------
4544 -- Check_Stream_Attributes --
4545 -----------------------------
4547 procedure Check_Stream_Attributes (Typ : Entity_Id) is
4548 Comp : Entity_Id;
4549 Par_Read : constant Boolean :=
4550 Stream_Attribute_Available (Typ, TSS_Stream_Read)
4551 and then not Has_Specified_Stream_Read (Typ);
4552 Par_Write : constant Boolean :=
4553 Stream_Attribute_Available (Typ, TSS_Stream_Write)
4554 and then not Has_Specified_Stream_Write (Typ);
4556 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type);
4557 -- Check that Comp has a user-specified Nam stream attribute
4559 ----------------
4560 -- Check_Attr --
4561 ----------------
4563 procedure Check_Attr (Nam : Name_Id; TSS_Nam : TSS_Name_Type) is
4564 begin
4565 if not Stream_Attribute_Available (Etype (Comp), TSS_Nam) then
4566 Error_Msg_Name_1 := Nam;
4567 Error_Msg_N
4568 ("|component& in limited extension must have% attribute", Comp);
4569 end if;
4570 end Check_Attr;
4572 -- Start of processing for Check_Stream_Attributes
4574 begin
4575 if Par_Read or else Par_Write then
4576 Comp := First_Component (Typ);
4577 while Present (Comp) loop
4578 if Comes_From_Source (Comp)
4579 and then Original_Record_Component (Comp) = Comp
4580 and then Is_Limited_Type (Etype (Comp))
4581 then
4582 if Par_Read then
4583 Check_Attr (Name_Read, TSS_Stream_Read);
4584 end if;
4586 if Par_Write then
4587 Check_Attr (Name_Write, TSS_Stream_Write);
4588 end if;
4589 end if;
4591 Next_Component (Comp);
4592 end loop;
4593 end if;
4594 end Check_Stream_Attributes;
4596 -----------------------------
4597 -- Expand_Record_Extension --
4598 -----------------------------
4600 -- Add a field _parent at the beginning of the record extension. This is
4601 -- used to implement inheritance. Here are some examples of expansion:
4603 -- 1. no discriminants
4604 -- type T2 is new T1 with null record;
4605 -- gives
4606 -- type T2 is new T1 with record
4607 -- _Parent : T1;
4608 -- end record;
4610 -- 2. renamed discriminants
4611 -- type T2 (B, C : Int) is new T1 (A => B) with record
4612 -- _Parent : T1 (A => B);
4613 -- D : Int;
4614 -- end;
4616 -- 3. inherited discriminants
4617 -- type T2 is new T1 with record -- discriminant A inherited
4618 -- _Parent : T1 (A);
4619 -- D : Int;
4620 -- end;
4622 procedure Expand_Record_Extension (T : Entity_Id; Def : Node_Id) is
4623 Indic : constant Node_Id := Subtype_Indication (Def);
4624 Loc : constant Source_Ptr := Sloc (Def);
4625 Rec_Ext_Part : Node_Id := Record_Extension_Part (Def);
4626 Par_Subtype : Entity_Id;
4627 Comp_List : Node_Id;
4628 Comp_Decl : Node_Id;
4629 Parent_N : Node_Id;
4630 D : Entity_Id;
4631 List_Constr : constant List_Id := New_List;
4633 begin
4634 -- Expand_Record_Extension is called directly from the semantics, so
4635 -- we must check to see whether expansion is active before proceeding,
4636 -- because this affects the visibility of selected components in bodies
4637 -- of instances.
4639 if not Expander_Active then
4640 return;
4641 end if;
4643 -- This may be a derivation of an untagged private type whose full
4644 -- view is tagged, in which case the Derived_Type_Definition has no
4645 -- extension part. Build an empty one now.
4647 if No (Rec_Ext_Part) then
4648 Rec_Ext_Part :=
4649 Make_Record_Definition (Loc,
4650 End_Label => Empty,
4651 Component_List => Empty,
4652 Null_Present => True);
4654 Set_Record_Extension_Part (Def, Rec_Ext_Part);
4655 Mark_Rewrite_Insertion (Rec_Ext_Part);
4656 end if;
4658 Comp_List := Component_List (Rec_Ext_Part);
4660 Parent_N := Make_Defining_Identifier (Loc, Name_uParent);
4662 -- If the derived type inherits its discriminants the type of the
4663 -- _parent field must be constrained by the inherited discriminants
4665 if Has_Discriminants (T)
4666 and then Nkind (Indic) /= N_Subtype_Indication
4667 and then not Is_Constrained (Entity (Indic))
4668 then
4669 D := First_Discriminant (T);
4670 while Present (D) loop
4671 Append_To (List_Constr, New_Occurrence_Of (D, Loc));
4672 Next_Discriminant (D);
4673 end loop;
4675 Par_Subtype :=
4676 Process_Subtype (
4677 Make_Subtype_Indication (Loc,
4678 Subtype_Mark => New_Occurrence_Of (Entity (Indic), Loc),
4679 Constraint =>
4680 Make_Index_Or_Discriminant_Constraint (Loc,
4681 Constraints => List_Constr)),
4682 Def);
4684 -- Otherwise the original subtype_indication is just what is needed
4686 else
4687 Par_Subtype := Process_Subtype (New_Copy_Tree (Indic), Def);
4688 end if;
4690 Set_Parent_Subtype (T, Par_Subtype);
4692 Comp_Decl :=
4693 Make_Component_Declaration (Loc,
4694 Defining_Identifier => Parent_N,
4695 Component_Definition =>
4696 Make_Component_Definition (Loc,
4697 Aliased_Present => False,
4698 Subtype_Indication => New_Occurrence_Of (Par_Subtype, Loc)));
4700 if Null_Present (Rec_Ext_Part) then
4701 Set_Component_List (Rec_Ext_Part,
4702 Make_Component_List (Loc,
4703 Component_Items => New_List (Comp_Decl),
4704 Variant_Part => Empty,
4705 Null_Present => False));
4706 Set_Null_Present (Rec_Ext_Part, False);
4708 elsif Null_Present (Comp_List)
4709 or else Is_Empty_List (Component_Items (Comp_List))
4710 then
4711 Set_Component_Items (Comp_List, New_List (Comp_Decl));
4712 Set_Null_Present (Comp_List, False);
4714 else
4715 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
4716 end if;
4718 Analyze (Comp_Decl);
4719 end Expand_Record_Extension;
4721 ------------------------------------
4722 -- Expand_N_Full_Type_Declaration --
4723 ------------------------------------
4725 procedure Expand_N_Full_Type_Declaration (N : Node_Id) is
4726 procedure Build_Master (Ptr_Typ : Entity_Id);
4727 -- Create the master associated with Ptr_Typ
4729 ------------------
4730 -- Build_Master --
4731 ------------------
4733 procedure Build_Master (Ptr_Typ : Entity_Id) is
4734 Desig_Typ : Entity_Id := Designated_Type (Ptr_Typ);
4736 begin
4737 -- If the designated type is an incomplete view coming from a
4738 -- limited-with'ed package, we need to use the nonlimited view in
4739 -- case it has tasks.
4741 if Ekind (Desig_Typ) in Incomplete_Kind
4742 and then Present (Non_Limited_View (Desig_Typ))
4743 then
4744 Desig_Typ := Non_Limited_View (Desig_Typ);
4745 end if;
4747 -- Anonymous access types are created for the components of the
4748 -- record parameter for an entry declaration. No master is created
4749 -- for such a type.
4751 if Comes_From_Source (N) and then Has_Task (Desig_Typ) then
4752 Build_Master_Entity (Ptr_Typ);
4753 Build_Master_Renaming (Ptr_Typ);
4755 -- Create a class-wide master because a Master_Id must be generated
4756 -- for access-to-limited-class-wide types whose root may be extended
4757 -- with task components.
4759 -- Note: This code covers access-to-limited-interfaces because they
4760 -- can be used to reference tasks implementing them.
4762 elsif Is_Limited_Class_Wide_Type (Desig_Typ)
4763 and then Tasking_Allowed
4765 -- Do not create a class-wide master for types whose convention is
4766 -- Java since these types cannot embed Ada tasks anyway. Note that
4767 -- the following test cannot catch the following case:
4769 -- package java.lang.Object is
4770 -- type Typ is tagged limited private;
4771 -- type Ref is access all Typ'Class;
4772 -- private
4773 -- type Typ is tagged limited ...;
4774 -- pragma Convention (Typ, Java)
4775 -- end;
4777 -- Because the convention appears after we have done the
4778 -- processing for type Ref.
4780 and then Convention (Desig_Typ) /= Convention_Java
4781 and then Convention (Desig_Typ) /= Convention_CIL
4782 then
4783 Build_Class_Wide_Master (Ptr_Typ);
4784 end if;
4785 end Build_Master;
4787 -- Local declarations
4789 Def_Id : constant Entity_Id := Defining_Identifier (N);
4790 B_Id : constant Entity_Id := Base_Type (Def_Id);
4791 GM : constant Ghost_Mode_Type := Ghost_Mode;
4792 FN : Node_Id;
4793 Par_Id : Entity_Id;
4795 -- Start of processing for Expand_N_Full_Type_Declaration
4797 begin
4798 -- The type declaration may be subject to pragma Ghost with policy
4799 -- Ignore. Set the mode now to ensure that any nodes generated during
4800 -- expansion are properly flagged as ignored Ghost.
4802 Set_Ghost_Mode (N);
4804 if Is_Access_Type (Def_Id) then
4805 Build_Master (Def_Id);
4807 if Ekind (Def_Id) = E_Access_Protected_Subprogram_Type then
4808 Expand_Access_Protected_Subprogram_Type (N);
4809 end if;
4811 -- Array of anonymous access-to-task pointers
4813 elsif Ada_Version >= Ada_2005
4814 and then Is_Array_Type (Def_Id)
4815 and then Is_Access_Type (Component_Type (Def_Id))
4816 and then Ekind (Component_Type (Def_Id)) = E_Anonymous_Access_Type
4817 then
4818 Build_Master (Component_Type (Def_Id));
4820 elsif Has_Task (Def_Id) then
4821 Expand_Previous_Access_Type (Def_Id);
4823 -- Check the components of a record type or array of records for
4824 -- anonymous access-to-task pointers.
4826 elsif Ada_Version >= Ada_2005
4827 and then (Is_Record_Type (Def_Id)
4828 or else
4829 (Is_Array_Type (Def_Id)
4830 and then Is_Record_Type (Component_Type (Def_Id))))
4831 then
4832 declare
4833 Comp : Entity_Id;
4834 First : Boolean;
4835 M_Id : Entity_Id;
4836 Typ : Entity_Id;
4838 begin
4839 if Is_Array_Type (Def_Id) then
4840 Comp := First_Entity (Component_Type (Def_Id));
4841 else
4842 Comp := First_Entity (Def_Id);
4843 end if;
4845 -- Examine all components looking for anonymous access-to-task
4846 -- types.
4848 First := True;
4849 while Present (Comp) loop
4850 Typ := Etype (Comp);
4852 if Ekind (Typ) = E_Anonymous_Access_Type
4853 and then Has_Task (Available_View (Designated_Type (Typ)))
4854 and then No (Master_Id (Typ))
4855 then
4856 -- Ensure that the record or array type have a _master
4858 if First then
4859 Build_Master_Entity (Def_Id);
4860 Build_Master_Renaming (Typ);
4861 M_Id := Master_Id (Typ);
4863 First := False;
4865 -- Reuse the same master to service any additional types
4867 else
4868 Set_Master_Id (Typ, M_Id);
4869 end if;
4870 end if;
4872 Next_Entity (Comp);
4873 end loop;
4874 end;
4875 end if;
4877 Par_Id := Etype (B_Id);
4879 -- The parent type is private then we need to inherit any TSS operations
4880 -- from the full view.
4882 if Ekind (Par_Id) in Private_Kind
4883 and then Present (Full_View (Par_Id))
4884 then
4885 Par_Id := Base_Type (Full_View (Par_Id));
4886 end if;
4888 if Nkind (Type_Definition (Original_Node (N))) =
4889 N_Derived_Type_Definition
4890 and then not Is_Tagged_Type (Def_Id)
4891 and then Present (Freeze_Node (Par_Id))
4892 and then Present (TSS_Elist (Freeze_Node (Par_Id)))
4893 then
4894 Ensure_Freeze_Node (B_Id);
4895 FN := Freeze_Node (B_Id);
4897 if No (TSS_Elist (FN)) then
4898 Set_TSS_Elist (FN, New_Elmt_List);
4899 end if;
4901 declare
4902 T_E : constant Elist_Id := TSS_Elist (FN);
4903 Elmt : Elmt_Id;
4905 begin
4906 Elmt := First_Elmt (TSS_Elist (Freeze_Node (Par_Id)));
4907 while Present (Elmt) loop
4908 if Chars (Node (Elmt)) /= Name_uInit then
4909 Append_Elmt (Node (Elmt), T_E);
4910 end if;
4912 Next_Elmt (Elmt);
4913 end loop;
4915 -- If the derived type itself is private with a full view, then
4916 -- associate the full view with the inherited TSS_Elist as well.
4918 if Ekind (B_Id) in Private_Kind
4919 and then Present (Full_View (B_Id))
4920 then
4921 Ensure_Freeze_Node (Base_Type (Full_View (B_Id)));
4922 Set_TSS_Elist
4923 (Freeze_Node (Base_Type (Full_View (B_Id))), TSS_Elist (FN));
4924 end if;
4925 end;
4926 end if;
4928 -- Restore the original Ghost mode once analysis and expansion have
4929 -- taken place.
4931 Ghost_Mode := GM;
4932 end Expand_N_Full_Type_Declaration;
4934 ---------------------------------
4935 -- Expand_N_Object_Declaration --
4936 ---------------------------------
4938 procedure Expand_N_Object_Declaration (N : Node_Id) is
4939 Loc : constant Source_Ptr := Sloc (N);
4940 Def_Id : constant Entity_Id := Defining_Identifier (N);
4941 Expr : constant Node_Id := Expression (N);
4942 GM : constant Ghost_Mode_Type := Ghost_Mode;
4943 Obj_Def : constant Node_Id := Object_Definition (N);
4944 Typ : constant Entity_Id := Etype (Def_Id);
4945 Base_Typ : constant Entity_Id := Base_Type (Typ);
4946 Expr_Q : Node_Id;
4948 function Build_Equivalent_Aggregate return Boolean;
4949 -- If the object has a constrained discriminated type and no initial
4950 -- value, it may be possible to build an equivalent aggregate instead,
4951 -- and prevent an actual call to the initialization procedure.
4953 procedure Default_Initialize_Object (After : Node_Id);
4954 -- Generate all default initialization actions for object Def_Id. Any
4955 -- new code is inserted after node After.
4957 procedure Restore_Globals;
4958 -- Restore the values of all saved global variables
4960 function Rewrite_As_Renaming return Boolean;
4961 -- Indicate whether to rewrite a declaration with initialization into an
4962 -- object renaming declaration (see below).
4964 --------------------------------
4965 -- Build_Equivalent_Aggregate --
4966 --------------------------------
4968 function Build_Equivalent_Aggregate return Boolean is
4969 Aggr : Node_Id;
4970 Comp : Entity_Id;
4971 Discr : Elmt_Id;
4972 Full_Type : Entity_Id;
4974 begin
4975 Full_Type := Typ;
4977 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
4978 Full_Type := Full_View (Typ);
4979 end if;
4981 -- Only perform this transformation if Elaboration_Code is forbidden
4982 -- or undesirable, and if this is a global entity of a constrained
4983 -- record type.
4985 -- If Initialize_Scalars might be active this transformation cannot
4986 -- be performed either, because it will lead to different semantics
4987 -- or because elaboration code will in fact be created.
4989 if Ekind (Full_Type) /= E_Record_Subtype
4990 or else not Has_Discriminants (Full_Type)
4991 or else not Is_Constrained (Full_Type)
4992 or else Is_Controlled (Full_Type)
4993 or else Is_Limited_Type (Full_Type)
4994 or else not Restriction_Active (No_Initialize_Scalars)
4995 then
4996 return False;
4997 end if;
4999 if Ekind (Current_Scope) = E_Package
5000 and then
5001 (Restriction_Active (No_Elaboration_Code)
5002 or else Is_Preelaborated (Current_Scope))
5003 then
5004 -- Building a static aggregate is possible if the discriminants
5005 -- have static values and the other components have static
5006 -- defaults or none.
5008 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5009 while Present (Discr) loop
5010 if not Is_OK_Static_Expression (Node (Discr)) then
5011 return False;
5012 end if;
5014 Next_Elmt (Discr);
5015 end loop;
5017 -- Check that initialized components are OK, and that non-
5018 -- initialized components do not require a call to their own
5019 -- initialization procedure.
5021 Comp := First_Component (Full_Type);
5022 while Present (Comp) loop
5023 if Ekind (Comp) = E_Component
5024 and then Present (Expression (Parent (Comp)))
5025 and then
5026 not Is_OK_Static_Expression (Expression (Parent (Comp)))
5027 then
5028 return False;
5030 elsif Has_Non_Null_Base_Init_Proc (Etype (Comp)) then
5031 return False;
5033 end if;
5035 Next_Component (Comp);
5036 end loop;
5038 -- Everything is static, assemble the aggregate, discriminant
5039 -- values first.
5041 Aggr :=
5042 Make_Aggregate (Loc,
5043 Expressions => New_List,
5044 Component_Associations => New_List);
5046 Discr := First_Elmt (Discriminant_Constraint (Full_Type));
5047 while Present (Discr) loop
5048 Append_To (Expressions (Aggr), New_Copy (Node (Discr)));
5049 Next_Elmt (Discr);
5050 end loop;
5052 -- Now collect values of initialized components
5054 Comp := First_Component (Full_Type);
5055 while Present (Comp) loop
5056 if Ekind (Comp) = E_Component
5057 and then Present (Expression (Parent (Comp)))
5058 then
5059 Append_To (Component_Associations (Aggr),
5060 Make_Component_Association (Loc,
5061 Choices => New_List (New_Occurrence_Of (Comp, Loc)),
5062 Expression => New_Copy_Tree
5063 (Expression (Parent (Comp)))));
5064 end if;
5066 Next_Component (Comp);
5067 end loop;
5069 -- Finally, box-initialize remaining components
5071 Append_To (Component_Associations (Aggr),
5072 Make_Component_Association (Loc,
5073 Choices => New_List (Make_Others_Choice (Loc)),
5074 Expression => Empty));
5075 Set_Box_Present (Last (Component_Associations (Aggr)));
5076 Set_Expression (N, Aggr);
5078 if Typ /= Full_Type then
5079 Analyze_And_Resolve (Aggr, Full_View (Base_Type (Full_Type)));
5080 Rewrite (Aggr, Unchecked_Convert_To (Typ, Aggr));
5081 Analyze_And_Resolve (Aggr, Typ);
5082 else
5083 Analyze_And_Resolve (Aggr, Full_Type);
5084 end if;
5086 return True;
5088 else
5089 return False;
5090 end if;
5091 end Build_Equivalent_Aggregate;
5093 -------------------------------
5094 -- Default_Initialize_Object --
5095 -------------------------------
5097 procedure Default_Initialize_Object (After : Node_Id) is
5098 function New_Object_Reference return Node_Id;
5099 -- Return a new reference to Def_Id with attributes Assignment_OK and
5100 -- Must_Not_Freeze already set.
5102 --------------------------
5103 -- New_Object_Reference --
5104 --------------------------
5106 function New_Object_Reference return Node_Id is
5107 Obj_Ref : constant Node_Id := New_Occurrence_Of (Def_Id, Loc);
5109 begin
5110 -- The call to the type init proc or [Deep_]Finalize must not
5111 -- freeze the related object as the call is internally generated.
5112 -- This way legal rep clauses that apply to the object will not be
5113 -- flagged. Note that the initialization call may be removed if
5114 -- pragma Import is encountered or moved to the freeze actions of
5115 -- the object because of an address clause.
5117 Set_Assignment_OK (Obj_Ref);
5118 Set_Must_Not_Freeze (Obj_Ref);
5120 return Obj_Ref;
5121 end New_Object_Reference;
5123 -- Local variables
5125 Abrt_Blk : Node_Id;
5126 Abrt_HSS : Node_Id;
5127 Abrt_Id : Entity_Id;
5128 Abrt_Stmts : List_Id;
5129 Aggr_Init : Node_Id;
5130 Comp_Init : List_Id := No_List;
5131 Fin_Call : Node_Id;
5132 Fin_Stmts : List_Id := No_List;
5133 Obj_Init : Node_Id := Empty;
5134 Obj_Ref : Node_Id;
5136 Dummy : Entity_Id;
5137 -- This variable captures a dummy internal entity, see the comment
5138 -- associated with its use.
5140 -- Start of processing for Default_Initialize_Object
5142 begin
5143 -- Default initialization is suppressed for objects that are already
5144 -- known to be imported (i.e. whose declaration specifies the Import
5145 -- aspect). Note that for objects with a pragma Import, we generate
5146 -- initialization here, and then remove it downstream when processing
5147 -- the pragma. It is also suppressed for variables for which a pragma
5148 -- Suppress_Initialization has been explicitly given
5150 if Is_Imported (Def_Id) or else Suppress_Initialization (Def_Id) then
5151 return;
5152 end if;
5154 -- Step 1: Initialize the object
5156 if Needs_Finalization (Typ) and then not No_Initialization (N) then
5157 Obj_Init :=
5158 Make_Init_Call
5159 (Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5160 Typ => Typ);
5161 end if;
5163 -- Step 2: Initialize the components of the object
5165 -- Do not initialize the components if their initialization is
5166 -- prohibited or the type represents a value type in a .NET VM.
5168 if Has_Non_Null_Base_Init_Proc (Typ)
5169 and then not No_Initialization (N)
5170 and then not Initialization_Suppressed (Typ)
5171 and then not Is_Value_Type (Typ)
5172 then
5173 -- Do not initialize the components if No_Default_Initialization
5174 -- applies as the actual restriction check will occur later
5175 -- when the object is frozen as it is not known yet whether the
5176 -- object is imported or not.
5178 if not Restriction_Active (No_Default_Initialization) then
5180 -- If the values of the components are compile-time known, use
5181 -- their prebuilt aggregate form directly.
5183 Aggr_Init := Static_Initialization (Base_Init_Proc (Typ));
5185 if Present (Aggr_Init) then
5186 Set_Expression
5187 (N, New_Copy_Tree (Aggr_Init, New_Scope => Current_Scope));
5189 -- If type has discriminants, try to build an equivalent
5190 -- aggregate using discriminant values from the declaration.
5191 -- This is a useful optimization, in particular if restriction
5192 -- No_Elaboration_Code is active.
5194 elsif Build_Equivalent_Aggregate then
5195 null;
5197 -- Otherwise invoke the type init proc
5199 else
5200 Obj_Ref := New_Object_Reference;
5202 if Comes_From_Source (Def_Id) then
5203 Initialization_Warning (Obj_Ref);
5204 end if;
5206 Comp_Init := Build_Initialization_Call (Loc, Obj_Ref, Typ);
5207 end if;
5208 end if;
5210 -- Provide a default value if the object needs simple initialization
5211 -- and does not already have an initial value. A generated temporary
5212 -- do not require initialization because it will be assigned later.
5214 elsif Needs_Simple_Initialization
5215 (Typ, Initialize_Scalars
5216 and then No (Following_Address_Clause (N)))
5217 and then not Is_Internal (Def_Id)
5218 and then not Has_Init_Expression (N)
5219 then
5220 Set_No_Initialization (N, False);
5221 Set_Expression (N, Get_Simple_Init_Val (Typ, N, Esize (Def_Id)));
5222 Analyze_And_Resolve (Expression (N), Typ);
5223 end if;
5225 -- Step 3: Add partial finalization and abort actions, generate:
5227 -- Type_Init_Proc (Obj);
5228 -- begin
5229 -- Deep_Initialize (Obj);
5230 -- exception
5231 -- when others =>
5232 -- Deep_Finalize (Obj, Self => False);
5233 -- raise;
5234 -- end;
5236 -- Step 3a: Build the finalization block (if applicable)
5238 -- The finalization block is required when both the object and its
5239 -- controlled components are to be initialized. The block finalizes
5240 -- the components if the object initialization fails.
5242 if Has_Controlled_Component (Typ)
5243 and then Present (Comp_Init)
5244 and then Present (Obj_Init)
5245 and then not Restriction_Active (No_Exception_Propagation)
5246 then
5247 -- Generate:
5248 -- Type_Init_Proc (Obj);
5250 Fin_Stmts := Comp_Init;
5252 -- Generate:
5253 -- begin
5254 -- Deep_Initialize (Obj);
5255 -- exception
5256 -- when others =>
5257 -- Deep_Finalize (Obj, Self => False);
5258 -- raise;
5259 -- end;
5261 Fin_Call :=
5262 Make_Final_Call
5263 (Obj_Ref => New_Object_Reference,
5264 Typ => Typ,
5265 Skip_Self => True);
5267 if Present (Fin_Call) then
5269 -- Do not emit warnings related to the elaboration order when a
5270 -- controlled object is declared before the body of Finalize is
5271 -- seen.
5273 Set_No_Elaboration_Check (Fin_Call);
5275 Append_To (Fin_Stmts,
5276 Make_Block_Statement (Loc,
5277 Declarations => No_List,
5279 Handled_Statement_Sequence =>
5280 Make_Handled_Sequence_Of_Statements (Loc,
5281 Statements => New_List (Obj_Init),
5283 Exception_Handlers => New_List (
5284 Make_Exception_Handler (Loc,
5285 Exception_Choices => New_List (
5286 Make_Others_Choice (Loc)),
5288 Statements => New_List (
5289 Fin_Call,
5290 Make_Raise_Statement (Loc)))))));
5291 end if;
5293 -- Finalization is not required, the initialization calls are passed
5294 -- to the abort block building circuitry, generate:
5296 -- Type_Init_Proc (Obj);
5297 -- Deep_Initialize (Obj);
5299 else
5300 if Present (Comp_Init) then
5301 Fin_Stmts := Comp_Init;
5302 end if;
5304 if Present (Obj_Init) then
5305 if No (Fin_Stmts) then
5306 Fin_Stmts := New_List;
5307 end if;
5309 Append_To (Fin_Stmts, Obj_Init);
5310 end if;
5311 end if;
5313 -- Step 3b: Build the abort block (if applicable)
5315 -- The abort block is required when aborts are allowed in order to
5316 -- protect both initialization calls.
5318 if Present (Comp_Init) and then Present (Obj_Init) then
5319 if Abort_Allowed then
5321 -- Generate:
5322 -- Abort_Defer;
5324 Prepend_To
5325 (Fin_Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
5327 -- Generate:
5328 -- begin
5329 -- Abort_Defer;
5330 -- <finalization statements>
5331 -- at end
5332 -- Abort_Undefer_Direct;
5333 -- end;
5335 declare
5336 AUD : constant Entity_Id := RTE (RE_Abort_Undefer_Direct);
5338 begin
5339 Abrt_HSS :=
5340 Make_Handled_Sequence_Of_Statements (Loc,
5341 Statements => Fin_Stmts,
5342 At_End_Proc => New_Occurrence_Of (AUD, Loc));
5344 -- Present the Abort_Undefer_Direct function to the backend
5345 -- so that it can inline the call to the function.
5347 Add_Inlined_Body (AUD, N);
5348 end;
5350 Abrt_Blk :=
5351 Make_Block_Statement (Loc,
5352 Declarations => No_List,
5353 Handled_Statement_Sequence => Abrt_HSS);
5355 Add_Block_Identifier (Abrt_Blk, Abrt_Id);
5356 Expand_At_End_Handler (Abrt_HSS, Abrt_Id);
5358 Abrt_Stmts := New_List (Abrt_Blk);
5360 -- Abort is not required
5362 else
5363 -- Generate a dummy entity to ensure that the internal symbols
5364 -- are in sync when a unit is compiled with and without aborts.
5365 -- The entity is a block with proper scope and type.
5367 Dummy := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
5368 Set_Etype (Dummy, Standard_Void_Type);
5369 Abrt_Stmts := Fin_Stmts;
5370 end if;
5372 -- No initialization calls present
5374 else
5375 Abrt_Stmts := Fin_Stmts;
5376 end if;
5378 -- Step 4: Insert the whole initialization sequence into the tree
5379 -- If the object has a delayed freeze, as will be the case when
5380 -- it has aspect specifications, the initialization sequence is
5381 -- part of the freeze actions.
5383 if Has_Delayed_Freeze (Def_Id) then
5384 Append_Freeze_Actions (Def_Id, Abrt_Stmts);
5385 else
5386 Insert_Actions_After (After, Abrt_Stmts);
5387 end if;
5388 end Default_Initialize_Object;
5390 ---------------------
5391 -- Restore_Globals --
5392 ---------------------
5394 procedure Restore_Globals is
5395 begin
5396 Ghost_Mode := GM;
5397 end Restore_Globals;
5399 -------------------------
5400 -- Rewrite_As_Renaming --
5401 -------------------------
5403 function Rewrite_As_Renaming return Boolean is
5404 begin
5405 return not Aliased_Present (N)
5406 and then Is_Entity_Name (Expr_Q)
5407 and then Ekind (Entity (Expr_Q)) = E_Variable
5408 and then OK_To_Rename (Entity (Expr_Q))
5409 and then Is_Entity_Name (Obj_Def);
5410 end Rewrite_As_Renaming;
5412 -- Local variables
5414 Next_N : constant Node_Id := Next (N);
5415 Id_Ref : Node_Id;
5416 Tag_Assign : Node_Id;
5418 Init_After : Node_Id := N;
5419 -- Node after which the initialization actions are to be inserted. This
5420 -- is normally N, except for the case of a shared passive variable, in
5421 -- which case the init proc call must be inserted only after the bodies
5422 -- of the shared variable procedures have been seen.
5424 -- Start of processing for Expand_N_Object_Declaration
5426 begin
5427 -- Don't do anything for deferred constants. All proper actions will be
5428 -- expanded during the full declaration.
5430 if No (Expr) and Constant_Present (N) then
5431 return;
5432 end if;
5434 -- The type of the object cannot be abstract. This is diagnosed at the
5435 -- point the object is frozen, which happens after the declaration is
5436 -- fully expanded, so simply return now.
5438 if Is_Abstract_Type (Typ) then
5439 return;
5440 end if;
5442 -- The object declaration may be subject to pragma Ghost with policy
5443 -- Ignore. Set the mode now to ensure that any nodes generated during
5444 -- expansion are properly flagged as ignored Ghost.
5446 Set_Ghost_Mode (N);
5448 -- First we do special processing for objects of a tagged type where
5449 -- this is the point at which the type is frozen. The creation of the
5450 -- dispatch table and the initialization procedure have to be deferred
5451 -- to this point, since we reference previously declared primitive
5452 -- subprograms.
5454 -- Force construction of dispatch tables of library level tagged types
5456 if Tagged_Type_Expansion
5457 and then Static_Dispatch_Tables
5458 and then Is_Library_Level_Entity (Def_Id)
5459 and then Is_Library_Level_Tagged_Type (Base_Typ)
5460 and then Ekind_In (Base_Typ, E_Record_Type,
5461 E_Protected_Type,
5462 E_Task_Type)
5463 and then not Has_Dispatch_Table (Base_Typ)
5464 then
5465 declare
5466 New_Nodes : List_Id := No_List;
5468 begin
5469 if Is_Concurrent_Type (Base_Typ) then
5470 New_Nodes := Make_DT (Corresponding_Record_Type (Base_Typ), N);
5471 else
5472 New_Nodes := Make_DT (Base_Typ, N);
5473 end if;
5475 if not Is_Empty_List (New_Nodes) then
5476 Insert_List_Before (N, New_Nodes);
5477 end if;
5478 end;
5479 end if;
5481 -- Make shared memory routines for shared passive variable
5483 if Is_Shared_Passive (Def_Id) then
5484 Init_After := Make_Shared_Var_Procs (N);
5485 end if;
5487 -- If tasks being declared, make sure we have an activation chain
5488 -- defined for the tasks (has no effect if we already have one), and
5489 -- also that a Master variable is established and that the appropriate
5490 -- enclosing construct is established as a task master.
5492 if Has_Task (Typ) then
5493 Build_Activation_Chain_Entity (N);
5494 Build_Master_Entity (Def_Id);
5495 end if;
5497 -- Default initialization required, and no expression present
5499 if No (Expr) then
5501 -- If we have a type with a variant part, the initialization proc
5502 -- will contain implicit tests of the discriminant values, which
5503 -- counts as a violation of the restriction No_Implicit_Conditionals.
5505 if Has_Variant_Part (Typ) then
5506 declare
5507 Msg : Boolean;
5509 begin
5510 Check_Restriction (Msg, No_Implicit_Conditionals, Obj_Def);
5512 if Msg then
5513 Error_Msg_N
5514 ("\initialization of variant record tests discriminants",
5515 Obj_Def);
5516 return;
5517 end if;
5518 end;
5519 end if;
5521 -- For the default initialization case, if we have a private type
5522 -- with invariants, and invariant checks are enabled, then insert an
5523 -- invariant check after the object declaration. Note that it is OK
5524 -- to clobber the object with an invalid value since if the exception
5525 -- is raised, then the object will go out of scope. In the case where
5526 -- an array object is initialized with an aggregate, the expression
5527 -- is removed. Check flag Has_Init_Expression to avoid generating a
5528 -- junk invariant check and flag No_Initialization to avoid checking
5529 -- an uninitialized object such as a compiler temporary used for an
5530 -- aggregate.
5532 if Has_Invariants (Base_Typ)
5533 and then Present (Invariant_Procedure (Base_Typ))
5534 and then not Has_Init_Expression (N)
5535 and then not No_Initialization (N)
5536 then
5537 -- If entity has an address clause or aspect, make invariant
5538 -- call into a freeze action for the explicit freeze node for
5539 -- object. Otherwise insert invariant check after declaration.
5541 if Present (Following_Address_Clause (N))
5542 or else Has_Aspect (Def_Id, Aspect_Address)
5543 then
5544 Ensure_Freeze_Node (Def_Id);
5545 Set_Has_Delayed_Freeze (Def_Id);
5546 Set_Is_Frozen (Def_Id, False);
5548 if not Partial_View_Has_Unknown_Discr (Typ) then
5549 Append_Freeze_Action (Def_Id,
5550 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
5551 end if;
5553 elsif not Partial_View_Has_Unknown_Discr (Typ) then
5554 Insert_After (N,
5555 Make_Invariant_Call (New_Occurrence_Of (Def_Id, Loc)));
5556 end if;
5557 end if;
5559 Default_Initialize_Object (Init_After);
5561 -- Generate attribute for Persistent_BSS if needed
5563 if Persistent_BSS_Mode
5564 and then Comes_From_Source (N)
5565 and then Is_Potentially_Persistent_Type (Typ)
5566 and then not Has_Init_Expression (N)
5567 and then Is_Library_Level_Entity (Def_Id)
5568 then
5569 declare
5570 Prag : Node_Id;
5571 begin
5572 Prag :=
5573 Make_Linker_Section_Pragma
5574 (Def_Id, Sloc (N), ".persistent.bss");
5575 Insert_After (N, Prag);
5576 Analyze (Prag);
5577 end;
5578 end if;
5580 -- If access type, then we know it is null if not initialized
5582 if Is_Access_Type (Typ) then
5583 Set_Is_Known_Null (Def_Id);
5584 end if;
5586 -- Explicit initialization present
5588 else
5589 -- Obtain actual expression from qualified expression
5591 if Nkind (Expr) = N_Qualified_Expression then
5592 Expr_Q := Expression (Expr);
5593 else
5594 Expr_Q := Expr;
5595 end if;
5597 -- When we have the appropriate type of aggregate in the expression
5598 -- (it has been determined during analysis of the aggregate by
5599 -- setting the delay flag), let's perform in place assignment and
5600 -- thus avoid creating a temporary.
5602 if Is_Delayed_Aggregate (Expr_Q) then
5603 Convert_Aggr_In_Object_Decl (N);
5605 -- Ada 2005 (AI-318-02): If the initialization expression is a call
5606 -- to a build-in-place function, then access to the declared object
5607 -- must be passed to the function. Currently we limit such functions
5608 -- to those with constrained limited result subtypes, but eventually
5609 -- plan to expand the allowed forms of functions that are treated as
5610 -- build-in-place.
5612 elsif Ada_Version >= Ada_2005
5613 and then Is_Build_In_Place_Function_Call (Expr_Q)
5614 then
5615 Make_Build_In_Place_Call_In_Object_Declaration (N, Expr_Q);
5616 Restore_Globals;
5618 -- The previous call expands the expression initializing the
5619 -- built-in-place object into further code that will be analyzed
5620 -- later. No further expansion needed here.
5622 return;
5624 -- Ada 2005 (AI-251): Rewrite the expression that initializes a
5625 -- class-wide interface object to ensure that we copy the full
5626 -- object, unless we are targetting a VM where interfaces are handled
5627 -- by VM itself. Note that if the root type of Typ is an ancestor of
5628 -- Expr's type, both types share the same dispatch table and there is
5629 -- no need to displace the pointer.
5631 elsif Is_Interface (Typ)
5633 -- Avoid never-ending recursion because if Equivalent_Type is set
5634 -- then we've done it already and must not do it again.
5636 and then not
5637 (Nkind (Obj_Def) = N_Identifier
5638 and then Present (Equivalent_Type (Entity (Obj_Def))))
5639 then
5640 pragma Assert (Is_Class_Wide_Type (Typ));
5642 -- If the object is a return object of an inherently limited type,
5643 -- which implies build-in-place treatment, bypass the special
5644 -- treatment of class-wide interface initialization below. In this
5645 -- case, the expansion of the return statement will take care of
5646 -- creating the object (via allocator) and initializing it.
5648 if Is_Return_Object (Def_Id) and then Is_Limited_View (Typ) then
5649 null;
5651 elsif Tagged_Type_Expansion then
5652 declare
5653 Iface : constant Entity_Id := Root_Type (Typ);
5654 Expr_N : Node_Id := Expr;
5655 Expr_Typ : Entity_Id;
5656 New_Expr : Node_Id;
5657 Obj_Id : Entity_Id;
5658 Tag_Comp : Node_Id;
5660 begin
5661 -- If the original node of the expression was a conversion
5662 -- to this specific class-wide interface type then restore
5663 -- the original node because we must copy the object before
5664 -- displacing the pointer to reference the secondary tag
5665 -- component. This code must be kept synchronized with the
5666 -- expansion done by routine Expand_Interface_Conversion
5668 if not Comes_From_Source (Expr_N)
5669 and then Nkind (Expr_N) = N_Explicit_Dereference
5670 and then Nkind (Original_Node (Expr_N)) = N_Type_Conversion
5671 and then Etype (Original_Node (Expr_N)) = Typ
5672 then
5673 Rewrite (Expr_N, Original_Node (Expression (N)));
5674 end if;
5676 -- Avoid expansion of redundant interface conversion
5678 if Is_Interface (Etype (Expr_N))
5679 and then Nkind (Expr_N) = N_Type_Conversion
5680 and then Etype (Expr_N) = Typ
5681 then
5682 Expr_N := Expression (Expr_N);
5683 Set_Expression (N, Expr_N);
5684 end if;
5686 Obj_Id := Make_Temporary (Loc, 'D', Expr_N);
5687 Expr_Typ := Base_Type (Etype (Expr_N));
5689 if Is_Class_Wide_Type (Expr_Typ) then
5690 Expr_Typ := Root_Type (Expr_Typ);
5691 end if;
5693 -- Replace
5694 -- CW : I'Class := Obj;
5695 -- by
5696 -- Tmp : T := Obj;
5697 -- type Ityp is not null access I'Class;
5698 -- CW : I'Class renames Ityp (Tmp.I_Tag'Address).all;
5700 if Comes_From_Source (Expr_N)
5701 and then Nkind (Expr_N) = N_Identifier
5702 and then not Is_Interface (Expr_Typ)
5703 and then Interface_Present_In_Ancestor (Expr_Typ, Typ)
5704 and then (Expr_Typ = Etype (Expr_Typ)
5705 or else not
5706 Is_Variable_Size_Record (Etype (Expr_Typ)))
5707 then
5708 -- Copy the object
5710 Insert_Action (N,
5711 Make_Object_Declaration (Loc,
5712 Defining_Identifier => Obj_Id,
5713 Object_Definition =>
5714 New_Occurrence_Of (Expr_Typ, Loc),
5715 Expression => Relocate_Node (Expr_N)));
5717 -- Statically reference the tag associated with the
5718 -- interface
5720 Tag_Comp :=
5721 Make_Selected_Component (Loc,
5722 Prefix => New_Occurrence_Of (Obj_Id, Loc),
5723 Selector_Name =>
5724 New_Occurrence_Of
5725 (Find_Interface_Tag (Expr_Typ, Iface), Loc));
5727 -- Replace
5728 -- IW : I'Class := Obj;
5729 -- by
5730 -- type Equiv_Record is record ... end record;
5731 -- implicit subtype CW is <Class_Wide_Subtype>;
5732 -- Tmp : CW := CW!(Obj);
5733 -- type Ityp is not null access I'Class;
5734 -- IW : I'Class renames
5735 -- Ityp!(Displace (Temp'Address, I'Tag)).all;
5737 else
5738 -- Generate the equivalent record type and update the
5739 -- subtype indication to reference it.
5741 Expand_Subtype_From_Expr
5742 (N => N,
5743 Unc_Type => Typ,
5744 Subtype_Indic => Obj_Def,
5745 Exp => Expr_N);
5747 if not Is_Interface (Etype (Expr_N)) then
5748 New_Expr := Relocate_Node (Expr_N);
5750 -- For interface types we use 'Address which displaces
5751 -- the pointer to the base of the object (if required)
5753 else
5754 New_Expr :=
5755 Unchecked_Convert_To (Etype (Obj_Def),
5756 Make_Explicit_Dereference (Loc,
5757 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
5758 Make_Attribute_Reference (Loc,
5759 Prefix => Relocate_Node (Expr_N),
5760 Attribute_Name => Name_Address))));
5761 end if;
5763 -- Copy the object
5765 if not Is_Limited_Record (Expr_Typ) then
5766 Insert_Action (N,
5767 Make_Object_Declaration (Loc,
5768 Defining_Identifier => Obj_Id,
5769 Object_Definition =>
5770 New_Occurrence_Of (Etype (Obj_Def), Loc),
5771 Expression => New_Expr));
5773 -- Rename limited type object since they cannot be copied
5774 -- This case occurs when the initialization expression
5775 -- has been previously expanded into a temporary object.
5777 else pragma Assert (not Comes_From_Source (Expr_Q));
5778 Insert_Action (N,
5779 Make_Object_Renaming_Declaration (Loc,
5780 Defining_Identifier => Obj_Id,
5781 Subtype_Mark =>
5782 New_Occurrence_Of (Etype (Obj_Def), Loc),
5783 Name =>
5784 Unchecked_Convert_To
5785 (Etype (Obj_Def), New_Expr)));
5786 end if;
5788 -- Dynamically reference the tag associated with the
5789 -- interface.
5791 Tag_Comp :=
5792 Make_Function_Call (Loc,
5793 Name => New_Occurrence_Of (RTE (RE_Displace), Loc),
5794 Parameter_Associations => New_List (
5795 Make_Attribute_Reference (Loc,
5796 Prefix => New_Occurrence_Of (Obj_Id, Loc),
5797 Attribute_Name => Name_Address),
5798 New_Occurrence_Of
5799 (Node (First_Elmt (Access_Disp_Table (Iface))),
5800 Loc)));
5801 end if;
5803 Rewrite (N,
5804 Make_Object_Renaming_Declaration (Loc,
5805 Defining_Identifier => Make_Temporary (Loc, 'D'),
5806 Subtype_Mark => New_Occurrence_Of (Typ, Loc),
5807 Name =>
5808 Convert_Tag_To_Interface (Typ, Tag_Comp)));
5810 -- If the original entity comes from source, then mark the
5811 -- new entity as needing debug information, even though it's
5812 -- defined by a generated renaming that does not come from
5813 -- source, so that Materialize_Entity will be set on the
5814 -- entity when Debug_Renaming_Declaration is called during
5815 -- analysis.
5817 if Comes_From_Source (Def_Id) then
5818 Set_Debug_Info_Needed (Defining_Identifier (N));
5819 end if;
5821 Analyze (N, Suppress => All_Checks);
5823 -- Replace internal identifier of rewritten node by the
5824 -- identifier found in the sources. We also have to exchange
5825 -- entities containing their defining identifiers to ensure
5826 -- the correct replacement of the object declaration by this
5827 -- object renaming declaration because these identifiers
5828 -- were previously added by Enter_Name to the current scope.
5829 -- We must preserve the homonym chain of the source entity
5830 -- as well. We must also preserve the kind of the entity,
5831 -- which may be a constant. Preserve entity chain because
5832 -- itypes may have been generated already, and the full
5833 -- chain must be preserved for final freezing. Finally,
5834 -- preserve Comes_From_Source setting, so that debugging
5835 -- and cross-referencing information is properly kept, and
5836 -- preserve source location, to prevent spurious errors when
5837 -- entities are declared (they must have their own Sloc).
5839 declare
5840 New_Id : constant Entity_Id := Defining_Identifier (N);
5841 Next_Temp : constant Entity_Id := Next_Entity (New_Id);
5842 S_Flag : constant Boolean :=
5843 Comes_From_Source (Def_Id);
5845 begin
5846 Set_Next_Entity (New_Id, Next_Entity (Def_Id));
5847 Set_Next_Entity (Def_Id, Next_Temp);
5849 Set_Chars (Defining_Identifier (N), Chars (Def_Id));
5850 Set_Homonym (Defining_Identifier (N), Homonym (Def_Id));
5851 Set_Ekind (Defining_Identifier (N), Ekind (Def_Id));
5852 Set_Sloc (Defining_Identifier (N), Sloc (Def_Id));
5854 Set_Comes_From_Source (Def_Id, False);
5855 Exchange_Entities (Defining_Identifier (N), Def_Id);
5856 Set_Comes_From_Source (Def_Id, S_Flag);
5857 end;
5858 end;
5859 end if;
5861 Restore_Globals;
5862 return;
5864 -- Common case of explicit object initialization
5866 else
5867 -- In most cases, we must check that the initial value meets any
5868 -- constraint imposed by the declared type. However, there is one
5869 -- very important exception to this rule. If the entity has an
5870 -- unconstrained nominal subtype, then it acquired its constraints
5871 -- from the expression in the first place, and not only does this
5872 -- mean that the constraint check is not needed, but an attempt to
5873 -- perform the constraint check can cause order of elaboration
5874 -- problems.
5876 if not Is_Constr_Subt_For_U_Nominal (Typ) then
5878 -- If this is an allocator for an aggregate that has been
5879 -- allocated in place, delay checks until assignments are
5880 -- made, because the discriminants are not initialized.
5882 if Nkind (Expr) = N_Allocator and then No_Initialization (Expr)
5883 then
5884 null;
5886 -- Otherwise apply a constraint check now if no prev error
5888 elsif Nkind (Expr) /= N_Error then
5889 Apply_Constraint_Check (Expr, Typ);
5891 -- Deal with possible range check
5893 if Do_Range_Check (Expr) then
5895 -- If assignment checks are suppressed, turn off flag
5897 if Suppress_Assignment_Checks (N) then
5898 Set_Do_Range_Check (Expr, False);
5900 -- Otherwise generate the range check
5902 else
5903 Generate_Range_Check
5904 (Expr, Typ, CE_Range_Check_Failed);
5905 end if;
5906 end if;
5907 end if;
5908 end if;
5910 -- If the type is controlled and not inherently limited, then
5911 -- the target is adjusted after the copy and attached to the
5912 -- finalization list. However, no adjustment is done in the case
5913 -- where the object was initialized by a call to a function whose
5914 -- result is built in place, since no copy occurred. (Eventually
5915 -- we plan to support in-place function results for some cases
5916 -- of nonlimited types. ???) Similarly, no adjustment is required
5917 -- if we are going to rewrite the object declaration into a
5918 -- renaming declaration.
5920 if Needs_Finalization (Typ)
5921 and then not Is_Limited_View (Typ)
5922 and then not Rewrite_As_Renaming
5923 then
5924 Insert_Action_After (Init_After,
5925 Make_Adjust_Call (
5926 Obj_Ref => New_Occurrence_Of (Def_Id, Loc),
5927 Typ => Base_Typ));
5928 end if;
5930 -- For tagged types, when an init value is given, the tag has to
5931 -- be re-initialized separately in order to avoid the propagation
5932 -- of a wrong tag coming from a view conversion unless the type
5933 -- is class wide (in this case the tag comes from the init value).
5934 -- Suppress the tag assignment when VM_Target because VM tags are
5935 -- represented implicitly in objects. Ditto for types that are
5936 -- CPP_CLASS, and for initializations that are aggregates, because
5937 -- they have to have the right tag.
5939 -- The re-assignment of the tag has to be done even if the object
5940 -- is a constant. The assignment must be analyzed after the
5941 -- declaration. If an address clause follows, this is handled as
5942 -- part of the freeze actions for the object, otherwise insert
5943 -- tag assignment here.
5945 Tag_Assign := Make_Tag_Assignment (N);
5947 if Present (Tag_Assign) then
5948 if Present (Following_Address_Clause (N)) then
5949 Ensure_Freeze_Node (Def_Id);
5951 else
5952 Insert_Action_After (Init_After, Tag_Assign);
5953 end if;
5955 -- Handle C++ constructor calls. Note that we do not check that
5956 -- Typ is a tagged type since the equivalent Ada type of a C++
5957 -- class that has no virtual methods is an untagged limited
5958 -- record type.
5960 elsif Is_CPP_Constructor_Call (Expr) then
5962 -- The call to the initialization procedure does NOT freeze the
5963 -- object being initialized.
5965 Id_Ref := New_Occurrence_Of (Def_Id, Loc);
5966 Set_Must_Not_Freeze (Id_Ref);
5967 Set_Assignment_OK (Id_Ref);
5969 Insert_Actions_After (Init_After,
5970 Build_Initialization_Call (Loc, Id_Ref, Typ,
5971 Constructor_Ref => Expr));
5973 -- We remove here the original call to the constructor
5974 -- to avoid its management in the backend
5976 Set_Expression (N, Empty);
5977 Restore_Globals;
5978 return;
5980 -- Handle initialization of limited tagged types
5982 elsif Is_Tagged_Type (Typ)
5983 and then Is_Class_Wide_Type (Typ)
5984 and then Is_Limited_Record (Typ)
5985 then
5986 -- Given that the type is limited we cannot perform a copy. If
5987 -- Expr_Q is the reference to a variable we mark the variable
5988 -- as OK_To_Rename to expand this declaration into a renaming
5989 -- declaration (see bellow).
5991 if Is_Entity_Name (Expr_Q) then
5992 Set_OK_To_Rename (Entity (Expr_Q));
5994 -- If we cannot convert the expression into a renaming we must
5995 -- consider it an internal error because the backend does not
5996 -- have support to handle it.
5998 else
5999 pragma Assert (False);
6000 raise Program_Error;
6001 end if;
6003 -- For discrete types, set the Is_Known_Valid flag if the
6004 -- initializing value is known to be valid. Only do this for
6005 -- source assignments, since otherwise we can end up turning
6006 -- on the known valid flag prematurely from inserted code.
6008 elsif Comes_From_Source (N)
6009 and then Is_Discrete_Type (Typ)
6010 and then Expr_Known_Valid (Expr)
6011 then
6012 Set_Is_Known_Valid (Def_Id);
6014 elsif Is_Access_Type (Typ) then
6016 -- For access types set the Is_Known_Non_Null flag if the
6017 -- initializing value is known to be non-null. We can also set
6018 -- Can_Never_Be_Null if this is a constant.
6020 if Known_Non_Null (Expr) then
6021 Set_Is_Known_Non_Null (Def_Id, True);
6023 if Constant_Present (N) then
6024 Set_Can_Never_Be_Null (Def_Id);
6025 end if;
6026 end if;
6027 end if;
6029 -- If validity checking on copies, validate initial expression.
6030 -- But skip this if declaration is for a generic type, since it
6031 -- makes no sense to validate generic types. Not clear if this
6032 -- can happen for legal programs, but it definitely can arise
6033 -- from previous instantiation errors.
6035 if Validity_Checks_On
6036 and then Validity_Check_Copies
6037 and then not Is_Generic_Type (Etype (Def_Id))
6038 then
6039 Ensure_Valid (Expr);
6040 Set_Is_Known_Valid (Def_Id);
6041 end if;
6042 end if;
6044 -- Cases where the back end cannot handle the initialization directly
6045 -- In such cases, we expand an assignment that will be appropriately
6046 -- handled by Expand_N_Assignment_Statement.
6048 -- The exclusion of the unconstrained case is wrong, but for now it
6049 -- is too much trouble ???
6051 if (Is_Possibly_Unaligned_Slice (Expr)
6052 or else (Is_Possibly_Unaligned_Object (Expr)
6053 and then not Represented_As_Scalar (Etype (Expr))))
6054 and then not (Is_Array_Type (Etype (Expr))
6055 and then not Is_Constrained (Etype (Expr)))
6056 then
6057 declare
6058 Stat : constant Node_Id :=
6059 Make_Assignment_Statement (Loc,
6060 Name => New_Occurrence_Of (Def_Id, Loc),
6061 Expression => Relocate_Node (Expr));
6062 begin
6063 Set_Expression (N, Empty);
6064 Set_No_Initialization (N);
6065 Set_Assignment_OK (Name (Stat));
6066 Set_No_Ctrl_Actions (Stat);
6067 Insert_After_And_Analyze (Init_After, Stat);
6068 end;
6069 end if;
6071 -- Final transformation, if the initializing expression is an entity
6072 -- for a variable with OK_To_Rename set, then we transform:
6074 -- X : typ := expr;
6076 -- into
6078 -- X : typ renames expr
6080 -- provided that X is not aliased. The aliased case has to be
6081 -- excluded in general because Expr will not be aliased in general.
6083 if Rewrite_As_Renaming then
6084 Rewrite (N,
6085 Make_Object_Renaming_Declaration (Loc,
6086 Defining_Identifier => Defining_Identifier (N),
6087 Subtype_Mark => Obj_Def,
6088 Name => Expr_Q));
6090 -- We do not analyze this renaming declaration, because all its
6091 -- components have already been analyzed, and if we were to go
6092 -- ahead and analyze it, we would in effect be trying to generate
6093 -- another declaration of X, which won't do.
6095 Set_Renamed_Object (Defining_Identifier (N), Expr_Q);
6096 Set_Analyzed (N);
6098 -- We do need to deal with debug issues for this renaming
6100 -- First, if entity comes from source, then mark it as needing
6101 -- debug information, even though it is defined by a generated
6102 -- renaming that does not come from source.
6104 if Comes_From_Source (Defining_Identifier (N)) then
6105 Set_Debug_Info_Needed (Defining_Identifier (N));
6106 end if;
6108 -- Now call the routine to generate debug info for the renaming
6110 declare
6111 Decl : constant Node_Id := Debug_Renaming_Declaration (N);
6112 begin
6113 if Present (Decl) then
6114 Insert_Action (N, Decl);
6115 end if;
6116 end;
6117 end if;
6118 end if;
6120 if Nkind (N) = N_Object_Declaration
6121 and then Nkind (Obj_Def) = N_Access_Definition
6122 and then not Is_Local_Anonymous_Access (Etype (Def_Id))
6123 then
6124 -- An Ada 2012 stand-alone object of an anonymous access type
6126 declare
6127 Loc : constant Source_Ptr := Sloc (N);
6129 Level : constant Entity_Id :=
6130 Make_Defining_Identifier (Sloc (N),
6131 Chars =>
6132 New_External_Name (Chars (Def_Id), Suffix => "L"));
6134 Level_Expr : Node_Id;
6135 Level_Decl : Node_Id;
6137 begin
6138 Set_Ekind (Level, Ekind (Def_Id));
6139 Set_Etype (Level, Standard_Natural);
6140 Set_Scope (Level, Scope (Def_Id));
6142 if No (Expr) then
6144 -- Set accessibility level of null
6146 Level_Expr :=
6147 Make_Integer_Literal (Loc, Scope_Depth (Standard_Standard));
6149 else
6150 Level_Expr := Dynamic_Accessibility_Level (Expr);
6151 end if;
6153 Level_Decl :=
6154 Make_Object_Declaration (Loc,
6155 Defining_Identifier => Level,
6156 Object_Definition =>
6157 New_Occurrence_Of (Standard_Natural, Loc),
6158 Expression => Level_Expr,
6159 Constant_Present => Constant_Present (N),
6160 Has_Init_Expression => True);
6162 Insert_Action_After (Init_After, Level_Decl);
6164 Set_Extra_Accessibility (Def_Id, Level);
6165 end;
6166 end if;
6168 -- If the object is default initialized and its type is subject to
6169 -- pragma Default_Initial_Condition, add a runtime check to verify
6170 -- the assumption of the pragma (SPARK RM 7.3.3). Generate:
6172 -- <Base_Typ>Default_Init_Cond (<Base_Typ> (Def_Id));
6174 -- Note that the check is generated for source objects only
6176 if Comes_From_Source (Def_Id)
6177 and then (Has_Default_Init_Cond (Typ)
6178 or else
6179 Has_Inherited_Default_Init_Cond (Typ))
6180 and then not Has_Init_Expression (N)
6181 then
6182 declare
6183 DIC_Call : constant Node_Id :=
6184 Build_Default_Init_Cond_Call (Loc, Def_Id, Typ);
6185 begin
6186 if Present (Next_N) then
6187 Insert_Before_And_Analyze (Next_N, DIC_Call);
6189 -- The object declaration is the last node in a declarative or a
6190 -- statement list.
6192 else
6193 Append_To (List_Containing (N), DIC_Call);
6194 Analyze (DIC_Call);
6195 end if;
6196 end;
6197 end if;
6199 Restore_Globals;
6201 -- Exception on library entity not available
6203 exception
6204 when RE_Not_Available =>
6205 Restore_Globals;
6206 return;
6207 end Expand_N_Object_Declaration;
6209 ---------------------------------
6210 -- Expand_N_Subtype_Indication --
6211 ---------------------------------
6213 -- Add a check on the range of the subtype. The static case is partially
6214 -- duplicated by Process_Range_Expr_In_Decl in Sem_Ch3, but we still need
6215 -- to check here for the static case in order to avoid generating
6216 -- extraneous expanded code. Also deal with validity checking.
6218 procedure Expand_N_Subtype_Indication (N : Node_Id) is
6219 Ran : constant Node_Id := Range_Expression (Constraint (N));
6220 Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6222 begin
6223 if Nkind (Constraint (N)) = N_Range_Constraint then
6224 Validity_Check_Range (Range_Expression (Constraint (N)));
6225 end if;
6227 if Nkind_In (Parent (N), N_Constrained_Array_Definition, N_Slice) then
6228 Apply_Range_Check (Ran, Typ);
6229 end if;
6230 end Expand_N_Subtype_Indication;
6232 ---------------------------
6233 -- Expand_N_Variant_Part --
6234 ---------------------------
6236 -- Note: this procedure no longer has any effect. It used to be that we
6237 -- would replace the choices in the last variant by a when others, and
6238 -- also expanded static predicates in variant choices here, but both of
6239 -- those activities were being done too early, since we can't check the
6240 -- choices until the statically predicated subtypes are frozen, which can
6241 -- happen as late as the free point of the record, and we can't change the
6242 -- last choice to an others before checking the choices, which is now done
6243 -- at the freeze point of the record.
6245 procedure Expand_N_Variant_Part (N : Node_Id) is
6246 begin
6247 null;
6248 end Expand_N_Variant_Part;
6250 ---------------------------------
6251 -- Expand_Previous_Access_Type --
6252 ---------------------------------
6254 procedure Expand_Previous_Access_Type (Def_Id : Entity_Id) is
6255 Ptr_Typ : Entity_Id;
6257 begin
6258 -- Find all access types in the current scope whose designated type is
6259 -- Def_Id and build master renamings for them.
6261 Ptr_Typ := First_Entity (Current_Scope);
6262 while Present (Ptr_Typ) loop
6263 if Is_Access_Type (Ptr_Typ)
6264 and then Designated_Type (Ptr_Typ) = Def_Id
6265 and then No (Master_Id (Ptr_Typ))
6266 then
6267 -- Ensure that the designated type has a master
6269 Build_Master_Entity (Def_Id);
6271 -- Private and incomplete types complicate the insertion of master
6272 -- renamings because the access type may precede the full view of
6273 -- the designated type. For this reason, the master renamings are
6274 -- inserted relative to the designated type.
6276 Build_Master_Renaming (Ptr_Typ, Ins_Nod => Parent (Def_Id));
6277 end if;
6279 Next_Entity (Ptr_Typ);
6280 end loop;
6281 end Expand_Previous_Access_Type;
6283 ------------------------
6284 -- Expand_Tagged_Root --
6285 ------------------------
6287 procedure Expand_Tagged_Root (T : Entity_Id) is
6288 Def : constant Node_Id := Type_Definition (Parent (T));
6289 Comp_List : Node_Id;
6290 Comp_Decl : Node_Id;
6291 Sloc_N : Source_Ptr;
6293 begin
6294 if Null_Present (Def) then
6295 Set_Component_List (Def,
6296 Make_Component_List (Sloc (Def),
6297 Component_Items => Empty_List,
6298 Variant_Part => Empty,
6299 Null_Present => True));
6300 end if;
6302 Comp_List := Component_List (Def);
6304 if Null_Present (Comp_List)
6305 or else Is_Empty_List (Component_Items (Comp_List))
6306 then
6307 Sloc_N := Sloc (Comp_List);
6308 else
6309 Sloc_N := Sloc (First (Component_Items (Comp_List)));
6310 end if;
6312 Comp_Decl :=
6313 Make_Component_Declaration (Sloc_N,
6314 Defining_Identifier => First_Tag_Component (T),
6315 Component_Definition =>
6316 Make_Component_Definition (Sloc_N,
6317 Aliased_Present => False,
6318 Subtype_Indication => New_Occurrence_Of (RTE (RE_Tag), Sloc_N)));
6320 if Null_Present (Comp_List)
6321 or else Is_Empty_List (Component_Items (Comp_List))
6322 then
6323 Set_Component_Items (Comp_List, New_List (Comp_Decl));
6324 Set_Null_Present (Comp_List, False);
6326 else
6327 Insert_Before (First (Component_Items (Comp_List)), Comp_Decl);
6328 end if;
6330 -- We don't Analyze the whole expansion because the tag component has
6331 -- already been analyzed previously. Here we just insure that the tree
6332 -- is coherent with the semantic decoration
6334 Find_Type (Subtype_Indication (Component_Definition (Comp_Decl)));
6336 exception
6337 when RE_Not_Available =>
6338 return;
6339 end Expand_Tagged_Root;
6341 ----------------------
6342 -- Clean_Task_Names --
6343 ----------------------
6345 procedure Clean_Task_Names
6346 (Typ : Entity_Id;
6347 Proc_Id : Entity_Id)
6349 begin
6350 if Has_Task (Typ)
6351 and then not Restriction_Active (No_Implicit_Heap_Allocations)
6352 and then not Global_Discard_Names
6353 and then Tagged_Type_Expansion
6354 then
6355 Set_Uses_Sec_Stack (Proc_Id);
6356 end if;
6357 end Clean_Task_Names;
6359 ------------------------------
6360 -- Expand_Freeze_Array_Type --
6361 ------------------------------
6363 procedure Expand_Freeze_Array_Type (N : Node_Id) is
6364 Typ : constant Entity_Id := Entity (N);
6365 Base : constant Entity_Id := Base_Type (Typ);
6366 Comp_Typ : constant Entity_Id := Component_Type (Typ);
6367 Ins_Node : Node_Id;
6369 begin
6370 if not Is_Bit_Packed_Array (Typ) then
6372 -- If the component contains tasks, so does the array type. This may
6373 -- not be indicated in the array type because the component may have
6374 -- been a private type at the point of definition. Same if component
6375 -- type is controlled or contains protected objects.
6377 Set_Has_Task (Base, Has_Task (Comp_Typ));
6378 Set_Has_Protected (Base, Has_Protected (Comp_Typ));
6379 Set_Has_Controlled_Component
6380 (Base, Has_Controlled_Component
6381 (Comp_Typ)
6382 or else
6383 Is_Controlled (Comp_Typ));
6385 if No (Init_Proc (Base)) then
6387 -- If this is an anonymous array created for a declaration with
6388 -- an initial value, its init_proc will never be called. The
6389 -- initial value itself may have been expanded into assignments,
6390 -- in which case the object declaration is carries the
6391 -- No_Initialization flag.
6393 if Is_Itype (Base)
6394 and then Nkind (Associated_Node_For_Itype (Base)) =
6395 N_Object_Declaration
6396 and then
6397 (Present (Expression (Associated_Node_For_Itype (Base)))
6398 or else No_Initialization (Associated_Node_For_Itype (Base)))
6399 then
6400 null;
6402 -- We do not need an init proc for string or wide [wide] string,
6403 -- since the only time these need initialization in normalize or
6404 -- initialize scalars mode, and these types are treated specially
6405 -- and do not need initialization procedures.
6407 elsif Is_Standard_String_Type (Base) then
6408 null;
6410 -- Otherwise we have to build an init proc for the subtype
6412 else
6413 Build_Array_Init_Proc (Base, N);
6414 end if;
6415 end if;
6417 if Typ = Base then
6418 if Has_Controlled_Component (Base) then
6419 Build_Controlling_Procs (Base);
6421 if not Is_Limited_Type (Comp_Typ)
6422 and then Number_Dimensions (Typ) = 1
6423 then
6424 Build_Slice_Assignment (Typ);
6425 end if;
6426 end if;
6428 -- Create a finalization master to service the anonymous access
6429 -- components of the array.
6431 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
6432 and then Needs_Finalization (Designated_Type (Comp_Typ))
6433 then
6434 -- The finalization master is inserted before the declaration
6435 -- of the array type. The only exception to this is when the
6436 -- array type is an itype, in which case the master appears
6437 -- before the related context.
6439 if Is_Itype (Typ) then
6440 Ins_Node := Associated_Node_For_Itype (Typ);
6441 else
6442 Ins_Node := Parent (Typ);
6443 end if;
6445 Build_Finalization_Master
6446 (Typ => Comp_Typ,
6447 For_Anonymous => True,
6448 Context_Scope => Scope (Typ),
6449 Insertion_Node => Ins_Node);
6450 end if;
6451 end if;
6453 -- For packed case, default initialization, except if the component type
6454 -- is itself a packed structure with an initialization procedure, or
6455 -- initialize/normalize scalars active, and we have a base type, or the
6456 -- type is public, because in that case a client might specify
6457 -- Normalize_Scalars and there better be a public Init_Proc for it.
6459 elsif (Present (Init_Proc (Component_Type (Base)))
6460 and then No (Base_Init_Proc (Base)))
6461 or else (Init_Or_Norm_Scalars and then Base = Typ)
6462 or else Is_Public (Typ)
6463 then
6464 Build_Array_Init_Proc (Base, N);
6465 end if;
6467 if Has_Invariants (Component_Type (Base))
6468 and then Typ = Base
6469 and then In_Open_Scopes (Scope (Component_Type (Base)))
6470 then
6471 -- Generate component invariant checking procedure. This is only
6472 -- relevant if the array type is within the scope of the component
6473 -- type. Otherwise an array object can only be built using the public
6474 -- subprograms for the component type, and calls to those will have
6475 -- invariant checks. The invariant procedure is only generated for
6476 -- a base type, not a subtype.
6478 Insert_Component_Invariant_Checks
6479 (N, Base, Build_Array_Invariant_Proc (Base, N));
6480 end if;
6481 end Expand_Freeze_Array_Type;
6483 -----------------------------------
6484 -- Expand_Freeze_Class_Wide_Type --
6485 -----------------------------------
6487 procedure Expand_Freeze_Class_Wide_Type (N : Node_Id) is
6488 Typ : constant Entity_Id := Entity (N);
6489 Root : constant Entity_Id := Root_Type (Typ);
6491 function Is_C_Derivation (Typ : Entity_Id) return Boolean;
6492 -- Given a type, determine whether it is derived from a C or C++ root
6494 ---------------------
6495 -- Is_C_Derivation --
6496 ---------------------
6498 function Is_C_Derivation (Typ : Entity_Id) return Boolean is
6499 T : Entity_Id;
6501 begin
6502 T := Typ;
6503 loop
6504 if Is_CPP_Class (T)
6505 or else Convention (T) = Convention_C
6506 or else Convention (T) = Convention_CPP
6507 then
6508 return True;
6509 end if;
6511 exit when T = Etype (T);
6513 T := Etype (T);
6514 end loop;
6516 return False;
6517 end Is_C_Derivation;
6519 -- Start of processing for Expand_Freeze_Class_Wide_Type
6521 begin
6522 -- Certain run-time configurations and targets do not provide support
6523 -- for controlled types.
6525 if Restriction_Active (No_Finalization) then
6526 return;
6528 -- Do not create TSS routine Finalize_Address when dispatching calls are
6529 -- disabled since the core of the routine is a dispatching call.
6531 elsif Restriction_Active (No_Dispatching_Calls) then
6532 return;
6534 -- Do not create TSS routine Finalize_Address for concurrent class-wide
6535 -- types. Ignore C, C++, CIL and Java types since it is assumed that the
6536 -- non-Ada side will handle their destruction.
6538 elsif Is_Concurrent_Type (Root)
6539 or else Is_C_Derivation (Root)
6540 or else Convention (Typ) = Convention_CIL
6541 or else Convention (Typ) = Convention_CPP
6542 or else Convention (Typ) = Convention_Java
6543 then
6544 return;
6546 -- Do not create TSS routine Finalize_Address for .NET/JVM because these
6547 -- targets do not support address arithmetic and unchecked conversions.
6549 elsif VM_Target /= No_VM then
6550 return;
6552 -- Do not create TSS routine Finalize_Address when compiling in CodePeer
6553 -- mode since the routine contains an Unchecked_Conversion.
6555 elsif CodePeer_Mode then
6556 return;
6557 end if;
6559 -- Create the body of TSS primitive Finalize_Address. This automatically
6560 -- sets the TSS entry for the class-wide type.
6562 Make_Finalize_Address_Body (Typ);
6563 end Expand_Freeze_Class_Wide_Type;
6565 ------------------------------------
6566 -- Expand_Freeze_Enumeration_Type --
6567 ------------------------------------
6569 procedure Expand_Freeze_Enumeration_Type (N : Node_Id) is
6570 Typ : constant Entity_Id := Entity (N);
6571 Loc : constant Source_Ptr := Sloc (Typ);
6572 Ent : Entity_Id;
6573 Lst : List_Id;
6574 Num : Nat;
6575 Arr : Entity_Id;
6576 Fent : Entity_Id;
6577 Ityp : Entity_Id;
6578 Is_Contiguous : Boolean;
6579 Pos_Expr : Node_Id;
6580 Last_Repval : Uint;
6582 Func : Entity_Id;
6583 pragma Warnings (Off, Func);
6585 begin
6586 -- Various optimizations possible if given representation is contiguous
6588 Is_Contiguous := True;
6590 Ent := First_Literal (Typ);
6591 Last_Repval := Enumeration_Rep (Ent);
6593 Next_Literal (Ent);
6594 while Present (Ent) loop
6595 if Enumeration_Rep (Ent) - Last_Repval /= 1 then
6596 Is_Contiguous := False;
6597 exit;
6598 else
6599 Last_Repval := Enumeration_Rep (Ent);
6600 end if;
6602 Next_Literal (Ent);
6603 end loop;
6605 if Is_Contiguous then
6606 Set_Has_Contiguous_Rep (Typ);
6607 Ent := First_Literal (Typ);
6608 Num := 1;
6609 Lst := New_List (New_Occurrence_Of (Ent, Sloc (Ent)));
6611 else
6612 -- Build list of literal references
6614 Lst := New_List;
6615 Num := 0;
6617 Ent := First_Literal (Typ);
6618 while Present (Ent) loop
6619 Append_To (Lst, New_Occurrence_Of (Ent, Sloc (Ent)));
6620 Num := Num + 1;
6621 Next_Literal (Ent);
6622 end loop;
6623 end if;
6625 -- Now build an array declaration
6627 -- typA : array (Natural range 0 .. num - 1) of ctype :=
6628 -- (v, v, v, v, v, ....)
6630 -- where ctype is the corresponding integer type. If the representation
6631 -- is contiguous, we only keep the first literal, which provides the
6632 -- offset for Pos_To_Rep computations.
6634 Arr :=
6635 Make_Defining_Identifier (Loc,
6636 Chars => New_External_Name (Chars (Typ), 'A'));
6638 Append_Freeze_Action (Typ,
6639 Make_Object_Declaration (Loc,
6640 Defining_Identifier => Arr,
6641 Constant_Present => True,
6643 Object_Definition =>
6644 Make_Constrained_Array_Definition (Loc,
6645 Discrete_Subtype_Definitions => New_List (
6646 Make_Subtype_Indication (Loc,
6647 Subtype_Mark => New_Occurrence_Of (Standard_Natural, Loc),
6648 Constraint =>
6649 Make_Range_Constraint (Loc,
6650 Range_Expression =>
6651 Make_Range (Loc,
6652 Low_Bound =>
6653 Make_Integer_Literal (Loc, 0),
6654 High_Bound =>
6655 Make_Integer_Literal (Loc, Num - 1))))),
6657 Component_Definition =>
6658 Make_Component_Definition (Loc,
6659 Aliased_Present => False,
6660 Subtype_Indication => New_Occurrence_Of (Typ, Loc))),
6662 Expression =>
6663 Make_Aggregate (Loc,
6664 Expressions => Lst)));
6666 Set_Enum_Pos_To_Rep (Typ, Arr);
6668 -- Now we build the function that converts representation values to
6669 -- position values. This function has the form:
6671 -- function _Rep_To_Pos (A : etype; F : Boolean) return Integer is
6672 -- begin
6673 -- case ityp!(A) is
6674 -- when enum-lit'Enum_Rep => return posval;
6675 -- when enum-lit'Enum_Rep => return posval;
6676 -- ...
6677 -- when others =>
6678 -- [raise Constraint_Error when F "invalid data"]
6679 -- return -1;
6680 -- end case;
6681 -- end;
6683 -- Note: the F parameter determines whether the others case (no valid
6684 -- representation) raises Constraint_Error or returns a unique value
6685 -- of minus one. The latter case is used, e.g. in 'Valid code.
6687 -- Note: the reason we use Enum_Rep values in the case here is to avoid
6688 -- the code generator making inappropriate assumptions about the range
6689 -- of the values in the case where the value is invalid. ityp is a
6690 -- signed or unsigned integer type of appropriate width.
6692 -- Note: if exceptions are not supported, then we suppress the raise
6693 -- and return -1 unconditionally (this is an erroneous program in any
6694 -- case and there is no obligation to raise Constraint_Error here). We
6695 -- also do this if pragma Restrictions (No_Exceptions) is active.
6697 -- Is this right??? What about No_Exception_Propagation???
6699 -- Representations are signed
6701 if Enumeration_Rep (First_Literal (Typ)) < 0 then
6703 -- The underlying type is signed. Reset the Is_Unsigned_Type
6704 -- explicitly, because it might have been inherited from
6705 -- parent type.
6707 Set_Is_Unsigned_Type (Typ, False);
6709 if Esize (Typ) <= Standard_Integer_Size then
6710 Ityp := Standard_Integer;
6711 else
6712 Ityp := Universal_Integer;
6713 end if;
6715 -- Representations are unsigned
6717 else
6718 if Esize (Typ) <= Standard_Integer_Size then
6719 Ityp := RTE (RE_Unsigned);
6720 else
6721 Ityp := RTE (RE_Long_Long_Unsigned);
6722 end if;
6723 end if;
6725 -- The body of the function is a case statement. First collect case
6726 -- alternatives, or optimize the contiguous case.
6728 Lst := New_List;
6730 -- If representation is contiguous, Pos is computed by subtracting
6731 -- the representation of the first literal.
6733 if Is_Contiguous then
6734 Ent := First_Literal (Typ);
6736 if Enumeration_Rep (Ent) = Last_Repval then
6738 -- Another special case: for a single literal, Pos is zero
6740 Pos_Expr := Make_Integer_Literal (Loc, Uint_0);
6742 else
6743 Pos_Expr :=
6744 Convert_To (Standard_Integer,
6745 Make_Op_Subtract (Loc,
6746 Left_Opnd =>
6747 Unchecked_Convert_To
6748 (Ityp, Make_Identifier (Loc, Name_uA)),
6749 Right_Opnd =>
6750 Make_Integer_Literal (Loc,
6751 Intval => Enumeration_Rep (First_Literal (Typ)))));
6752 end if;
6754 Append_To (Lst,
6755 Make_Case_Statement_Alternative (Loc,
6756 Discrete_Choices => New_List (
6757 Make_Range (Sloc (Enumeration_Rep_Expr (Ent)),
6758 Low_Bound =>
6759 Make_Integer_Literal (Loc,
6760 Intval => Enumeration_Rep (Ent)),
6761 High_Bound =>
6762 Make_Integer_Literal (Loc, Intval => Last_Repval))),
6764 Statements => New_List (
6765 Make_Simple_Return_Statement (Loc,
6766 Expression => Pos_Expr))));
6768 else
6769 Ent := First_Literal (Typ);
6770 while Present (Ent) loop
6771 Append_To (Lst,
6772 Make_Case_Statement_Alternative (Loc,
6773 Discrete_Choices => New_List (
6774 Make_Integer_Literal (Sloc (Enumeration_Rep_Expr (Ent)),
6775 Intval => Enumeration_Rep (Ent))),
6777 Statements => New_List (
6778 Make_Simple_Return_Statement (Loc,
6779 Expression =>
6780 Make_Integer_Literal (Loc,
6781 Intval => Enumeration_Pos (Ent))))));
6783 Next_Literal (Ent);
6784 end loop;
6785 end if;
6787 -- In normal mode, add the others clause with the test
6789 if not No_Exception_Handlers_Set then
6790 Append_To (Lst,
6791 Make_Case_Statement_Alternative (Loc,
6792 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
6793 Statements => New_List (
6794 Make_Raise_Constraint_Error (Loc,
6795 Condition => Make_Identifier (Loc, Name_uF),
6796 Reason => CE_Invalid_Data),
6797 Make_Simple_Return_Statement (Loc,
6798 Expression =>
6799 Make_Integer_Literal (Loc, -1)))));
6801 -- If either of the restrictions No_Exceptions_Handlers/Propagation is
6802 -- active then return -1 (we cannot usefully raise Constraint_Error in
6803 -- this case). See description above for further details.
6805 else
6806 Append_To (Lst,
6807 Make_Case_Statement_Alternative (Loc,
6808 Discrete_Choices => New_List (Make_Others_Choice (Loc)),
6809 Statements => New_List (
6810 Make_Simple_Return_Statement (Loc,
6811 Expression =>
6812 Make_Integer_Literal (Loc, -1)))));
6813 end if;
6815 -- Now we can build the function body
6817 Fent :=
6818 Make_Defining_Identifier (Loc, Make_TSS_Name (Typ, TSS_Rep_To_Pos));
6820 Func :=
6821 Make_Subprogram_Body (Loc,
6822 Specification =>
6823 Make_Function_Specification (Loc,
6824 Defining_Unit_Name => Fent,
6825 Parameter_Specifications => New_List (
6826 Make_Parameter_Specification (Loc,
6827 Defining_Identifier =>
6828 Make_Defining_Identifier (Loc, Name_uA),
6829 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
6830 Make_Parameter_Specification (Loc,
6831 Defining_Identifier =>
6832 Make_Defining_Identifier (Loc, Name_uF),
6833 Parameter_Type =>
6834 New_Occurrence_Of (Standard_Boolean, Loc))),
6836 Result_Definition => New_Occurrence_Of (Standard_Integer, Loc)),
6838 Declarations => Empty_List,
6840 Handled_Statement_Sequence =>
6841 Make_Handled_Sequence_Of_Statements (Loc,
6842 Statements => New_List (
6843 Make_Case_Statement (Loc,
6844 Expression =>
6845 Unchecked_Convert_To
6846 (Ityp, Make_Identifier (Loc, Name_uA)),
6847 Alternatives => Lst))));
6849 Set_TSS (Typ, Fent);
6851 -- Set Pure flag (it will be reset if the current context is not Pure).
6852 -- We also pretend there was a pragma Pure_Function so that for purposes
6853 -- of optimization and constant-folding, we will consider the function
6854 -- Pure even if we are not in a Pure context).
6856 Set_Is_Pure (Fent);
6857 Set_Has_Pragma_Pure_Function (Fent);
6859 -- Unless we are in -gnatD mode, where we are debugging generated code,
6860 -- this is an internal entity for which we don't need debug info.
6862 if not Debug_Generated_Code then
6863 Set_Debug_Info_Off (Fent);
6864 end if;
6866 exception
6867 when RE_Not_Available =>
6868 return;
6869 end Expand_Freeze_Enumeration_Type;
6871 -------------------------------
6872 -- Expand_Freeze_Record_Type --
6873 -------------------------------
6875 procedure Expand_Freeze_Record_Type (N : Node_Id) is
6876 Def_Id : constant Node_Id := Entity (N);
6877 Type_Decl : constant Node_Id := Parent (Def_Id);
6878 Comp : Entity_Id;
6879 Comp_Typ : Entity_Id;
6880 Has_AACC : Boolean;
6881 Predef_List : List_Id;
6883 Renamed_Eq : Node_Id := Empty;
6884 -- Defining unit name for the predefined equality function in the case
6885 -- where the type has a primitive operation that is a renaming of
6886 -- predefined equality (but only if there is also an overriding
6887 -- user-defined equality function). Used to pass this entity from
6888 -- Make_Predefined_Primitive_Specs to Predefined_Primitive_Bodies.
6890 Wrapper_Decl_List : List_Id := No_List;
6891 Wrapper_Body_List : List_Id := No_List;
6893 -- Start of processing for Expand_Freeze_Record_Type
6895 begin
6896 -- Build discriminant checking functions if not a derived type (for
6897 -- derived types that are not tagged types, always use the discriminant
6898 -- checking functions of the parent type). However, for untagged types
6899 -- the derivation may have taken place before the parent was frozen, so
6900 -- we copy explicitly the discriminant checking functions from the
6901 -- parent into the components of the derived type.
6903 if not Is_Derived_Type (Def_Id)
6904 or else Has_New_Non_Standard_Rep (Def_Id)
6905 or else Is_Tagged_Type (Def_Id)
6906 then
6907 Build_Discr_Checking_Funcs (Type_Decl);
6909 elsif Is_Derived_Type (Def_Id)
6910 and then not Is_Tagged_Type (Def_Id)
6912 -- If we have a derived Unchecked_Union, we do not inherit the
6913 -- discriminant checking functions from the parent type since the
6914 -- discriminants are non existent.
6916 and then not Is_Unchecked_Union (Def_Id)
6917 and then Has_Discriminants (Def_Id)
6918 then
6919 declare
6920 Old_Comp : Entity_Id;
6922 begin
6923 Old_Comp :=
6924 First_Component (Base_Type (Underlying_Type (Etype (Def_Id))));
6925 Comp := First_Component (Def_Id);
6926 while Present (Comp) loop
6927 if Ekind (Comp) = E_Component
6928 and then Chars (Comp) = Chars (Old_Comp)
6929 then
6930 Set_Discriminant_Checking_Func (Comp,
6931 Discriminant_Checking_Func (Old_Comp));
6932 end if;
6934 Next_Component (Old_Comp);
6935 Next_Component (Comp);
6936 end loop;
6937 end;
6938 end if;
6940 if Is_Derived_Type (Def_Id)
6941 and then Is_Limited_Type (Def_Id)
6942 and then Is_Tagged_Type (Def_Id)
6943 then
6944 Check_Stream_Attributes (Def_Id);
6945 end if;
6947 -- Update task, protected, and controlled component flags, because some
6948 -- of the component types may have been private at the point of the
6949 -- record declaration. Detect anonymous access-to-controlled components.
6951 Has_AACC := False;
6953 Comp := First_Component (Def_Id);
6954 while Present (Comp) loop
6955 Comp_Typ := Etype (Comp);
6957 if Has_Task (Comp_Typ) then
6958 Set_Has_Task (Def_Id);
6959 end if;
6961 if Has_Protected (Comp_Typ) then
6962 Set_Has_Protected (Def_Id);
6963 end if;
6965 -- Do not set Has_Controlled_Component on a class-wide equivalent
6966 -- type. See Make_CW_Equivalent_Type.
6968 if not Is_Class_Wide_Equivalent_Type (Def_Id)
6969 and then
6970 (Has_Controlled_Component (Comp_Typ)
6971 or else (Chars (Comp) /= Name_uParent
6972 and then (Is_Controlled_Active (Comp_Typ))))
6973 then
6974 Set_Has_Controlled_Component (Def_Id);
6975 end if;
6977 -- Non-self-referential anonymous access-to-controlled component
6979 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
6980 and then Needs_Finalization (Designated_Type (Comp_Typ))
6981 and then Designated_Type (Comp_Typ) /= Def_Id
6982 then
6983 Has_AACC := True;
6984 end if;
6986 Next_Component (Comp);
6987 end loop;
6989 -- Handle constructors of untagged CPP_Class types
6991 if not Is_Tagged_Type (Def_Id) and then Is_CPP_Class (Def_Id) then
6992 Set_CPP_Constructors (Def_Id);
6993 end if;
6995 -- Creation of the Dispatch Table. Note that a Dispatch Table is built
6996 -- for regular tagged types as well as for Ada types deriving from a C++
6997 -- Class, but not for tagged types directly corresponding to C++ classes
6998 -- In the later case we assume that it is created in the C++ side and we
6999 -- just use it.
7001 if Is_Tagged_Type (Def_Id) then
7003 -- Add the _Tag component
7005 if Underlying_Type (Etype (Def_Id)) = Def_Id then
7006 Expand_Tagged_Root (Def_Id);
7007 end if;
7009 if Is_CPP_Class (Def_Id) then
7010 Set_All_DT_Position (Def_Id);
7012 -- Create the tag entities with a minimum decoration
7014 if Tagged_Type_Expansion then
7015 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
7016 end if;
7018 Set_CPP_Constructors (Def_Id);
7020 else
7021 if not Building_Static_DT (Def_Id) then
7023 -- Usually inherited primitives are not delayed but the first
7024 -- Ada extension of a CPP_Class is an exception since the
7025 -- address of the inherited subprogram has to be inserted in
7026 -- the new Ada Dispatch Table and this is a freezing action.
7028 -- Similarly, if this is an inherited operation whose parent is
7029 -- not frozen yet, it is not in the DT of the parent, and we
7030 -- generate an explicit freeze node for the inherited operation
7031 -- so it is properly inserted in the DT of the current type.
7033 declare
7034 Elmt : Elmt_Id;
7035 Subp : Entity_Id;
7037 begin
7038 Elmt := First_Elmt (Primitive_Operations (Def_Id));
7039 while Present (Elmt) loop
7040 Subp := Node (Elmt);
7042 if Present (Alias (Subp)) then
7043 if Is_CPP_Class (Etype (Def_Id)) then
7044 Set_Has_Delayed_Freeze (Subp);
7046 elsif Has_Delayed_Freeze (Alias (Subp))
7047 and then not Is_Frozen (Alias (Subp))
7048 then
7049 Set_Is_Frozen (Subp, False);
7050 Set_Has_Delayed_Freeze (Subp);
7051 end if;
7052 end if;
7054 Next_Elmt (Elmt);
7055 end loop;
7056 end;
7057 end if;
7059 -- Unfreeze momentarily the type to add the predefined primitives
7060 -- operations. The reason we unfreeze is so that these predefined
7061 -- operations will indeed end up as primitive operations (which
7062 -- must be before the freeze point).
7064 Set_Is_Frozen (Def_Id, False);
7066 -- Do not add the spec of predefined primitives in case of
7067 -- CPP tagged type derivations that have convention CPP.
7069 if Is_CPP_Class (Root_Type (Def_Id))
7070 and then Convention (Def_Id) = Convention_CPP
7071 then
7072 null;
7074 -- Do not add the spec of predefined primitives in case of
7075 -- CIL and Java tagged types
7077 elsif Convention (Def_Id) = Convention_CIL
7078 or else Convention (Def_Id) = Convention_Java
7079 then
7080 null;
7082 -- Do not add the spec of the predefined primitives if we are
7083 -- compiling under restriction No_Dispatching_Calls.
7085 elsif not Restriction_Active (No_Dispatching_Calls) then
7086 Make_Predefined_Primitive_Specs
7087 (Def_Id, Predef_List, Renamed_Eq);
7088 Insert_List_Before_And_Analyze (N, Predef_List);
7089 end if;
7091 -- Ada 2005 (AI-391): For a nonabstract null extension, create
7092 -- wrapper functions for each nonoverridden inherited function
7093 -- with a controlling result of the type. The wrapper for such
7094 -- a function returns an extension aggregate that invokes the
7095 -- parent function.
7097 if Ada_Version >= Ada_2005
7098 and then not Is_Abstract_Type (Def_Id)
7099 and then Is_Null_Extension (Def_Id)
7100 then
7101 Make_Controlling_Function_Wrappers
7102 (Def_Id, Wrapper_Decl_List, Wrapper_Body_List);
7103 Insert_List_Before_And_Analyze (N, Wrapper_Decl_List);
7104 end if;
7106 -- Ada 2005 (AI-251): For a nonabstract type extension, build
7107 -- null procedure declarations for each set of homographic null
7108 -- procedures that are inherited from interface types but not
7109 -- overridden. This is done to ensure that the dispatch table
7110 -- entry associated with such null primitives are properly filled.
7112 if Ada_Version >= Ada_2005
7113 and then Etype (Def_Id) /= Def_Id
7114 and then not Is_Abstract_Type (Def_Id)
7115 and then Has_Interfaces (Def_Id)
7116 then
7117 Insert_Actions (N, Make_Null_Procedure_Specs (Def_Id));
7118 end if;
7120 Set_Is_Frozen (Def_Id);
7121 if not Is_Derived_Type (Def_Id)
7122 or else Is_Tagged_Type (Etype (Def_Id))
7123 then
7124 Set_All_DT_Position (Def_Id);
7126 -- If this is a type derived from an untagged private type whose
7127 -- full view is tagged, the type is marked tagged for layout
7128 -- reasons, but it has no dispatch table.
7130 elsif Is_Derived_Type (Def_Id)
7131 and then Is_Private_Type (Etype (Def_Id))
7132 and then not Is_Tagged_Type (Etype (Def_Id))
7133 then
7134 return;
7135 end if;
7137 -- Create and decorate the tags. Suppress their creation when
7138 -- VM_Target because the dispatching mechanism is handled
7139 -- internally by the VMs.
7141 if Tagged_Type_Expansion then
7142 Append_Freeze_Actions (Def_Id, Make_Tags (Def_Id));
7144 -- Generate dispatch table of locally defined tagged type.
7145 -- Dispatch tables of library level tagged types are built
7146 -- later (see Analyze_Declarations).
7148 if not Building_Static_DT (Def_Id) then
7149 Append_Freeze_Actions (Def_Id, Make_DT (Def_Id));
7150 end if;
7152 elsif VM_Target /= No_VM then
7153 Append_Freeze_Actions (Def_Id, Make_VM_TSD (Def_Id));
7154 end if;
7156 -- If the type has unknown discriminants, propagate dispatching
7157 -- information to its underlying record view, which does not get
7158 -- its own dispatch table.
7160 if Is_Derived_Type (Def_Id)
7161 and then Has_Unknown_Discriminants (Def_Id)
7162 and then Present (Underlying_Record_View (Def_Id))
7163 then
7164 declare
7165 Rep : constant Entity_Id := Underlying_Record_View (Def_Id);
7166 begin
7167 Set_Access_Disp_Table
7168 (Rep, Access_Disp_Table (Def_Id));
7169 Set_Dispatch_Table_Wrappers
7170 (Rep, Dispatch_Table_Wrappers (Def_Id));
7171 Set_Direct_Primitive_Operations
7172 (Rep, Direct_Primitive_Operations (Def_Id));
7173 end;
7174 end if;
7176 -- Make sure that the primitives Initialize, Adjust and Finalize
7177 -- are Frozen before other TSS subprograms. We don't want them
7178 -- Frozen inside.
7180 if Is_Controlled (Def_Id) then
7181 if not Is_Limited_Type (Def_Id) then
7182 Append_Freeze_Actions (Def_Id,
7183 Freeze_Entity
7184 (Find_Prim_Op (Def_Id, Name_Adjust), Def_Id));
7185 end if;
7187 Append_Freeze_Actions (Def_Id,
7188 Freeze_Entity
7189 (Find_Prim_Op (Def_Id, Name_Initialize), Def_Id));
7191 Append_Freeze_Actions (Def_Id,
7192 Freeze_Entity
7193 (Find_Prim_Op (Def_Id, Name_Finalize), Def_Id));
7194 end if;
7196 -- Freeze rest of primitive operations. There is no need to handle
7197 -- the predefined primitives if we are compiling under restriction
7198 -- No_Dispatching_Calls.
7200 if not Restriction_Active (No_Dispatching_Calls) then
7201 Append_Freeze_Actions
7202 (Def_Id, Predefined_Primitive_Freeze (Def_Id));
7203 end if;
7204 end if;
7206 -- In the untagged case, ever since Ada 83 an equality function must
7207 -- be provided for variant records that are not unchecked unions.
7208 -- In Ada 2012 the equality function composes, and thus must be built
7209 -- explicitly just as for tagged records.
7211 elsif Has_Discriminants (Def_Id)
7212 and then not Is_Limited_Type (Def_Id)
7213 then
7214 declare
7215 Comps : constant Node_Id :=
7216 Component_List (Type_Definition (Type_Decl));
7217 begin
7218 if Present (Comps)
7219 and then Present (Variant_Part (Comps))
7220 then
7221 Build_Variant_Record_Equality (Def_Id);
7222 end if;
7223 end;
7225 -- Otherwise create primitive equality operation (AI05-0123)
7227 -- This is done unconditionally to ensure that tools can be linked
7228 -- properly with user programs compiled with older language versions.
7229 -- In addition, this is needed because "=" composes for bounded strings
7230 -- in all language versions (see Exp_Ch4.Expand_Composite_Equality).
7232 elsif Comes_From_Source (Def_Id)
7233 and then Convention (Def_Id) = Convention_Ada
7234 and then not Is_Limited_Type (Def_Id)
7235 then
7236 Build_Untagged_Equality (Def_Id);
7237 end if;
7239 -- Before building the record initialization procedure, if we are
7240 -- dealing with a concurrent record value type, then we must go through
7241 -- the discriminants, exchanging discriminals between the concurrent
7242 -- type and the concurrent record value type. See the section "Handling
7243 -- of Discriminants" in the Einfo spec for details.
7245 if Is_Concurrent_Record_Type (Def_Id)
7246 and then Has_Discriminants (Def_Id)
7247 then
7248 declare
7249 Ctyp : constant Entity_Id :=
7250 Corresponding_Concurrent_Type (Def_Id);
7251 Conc_Discr : Entity_Id;
7252 Rec_Discr : Entity_Id;
7253 Temp : Entity_Id;
7255 begin
7256 Conc_Discr := First_Discriminant (Ctyp);
7257 Rec_Discr := First_Discriminant (Def_Id);
7258 while Present (Conc_Discr) loop
7259 Temp := Discriminal (Conc_Discr);
7260 Set_Discriminal (Conc_Discr, Discriminal (Rec_Discr));
7261 Set_Discriminal (Rec_Discr, Temp);
7263 Set_Discriminal_Link (Discriminal (Conc_Discr), Conc_Discr);
7264 Set_Discriminal_Link (Discriminal (Rec_Discr), Rec_Discr);
7266 Next_Discriminant (Conc_Discr);
7267 Next_Discriminant (Rec_Discr);
7268 end loop;
7269 end;
7270 end if;
7272 if Has_Controlled_Component (Def_Id) then
7273 Build_Controlling_Procs (Def_Id);
7274 end if;
7276 Adjust_Discriminants (Def_Id);
7278 if Tagged_Type_Expansion or else not Is_Interface (Def_Id) then
7280 -- Do not need init for interfaces on e.g. CIL since they're
7281 -- abstract. Helps operation of peverify (the PE Verify tool).
7283 Build_Record_Init_Proc (Type_Decl, Def_Id);
7284 end if;
7286 -- For tagged type that are not interfaces, build bodies of primitive
7287 -- operations. Note: do this after building the record initialization
7288 -- procedure, since the primitive operations may need the initialization
7289 -- routine. There is no need to add predefined primitives of interfaces
7290 -- because all their predefined primitives are abstract.
7292 if Is_Tagged_Type (Def_Id) and then not Is_Interface (Def_Id) then
7294 -- Do not add the body of predefined primitives in case of CPP tagged
7295 -- type derivations that have convention CPP.
7297 if Is_CPP_Class (Root_Type (Def_Id))
7298 and then Convention (Def_Id) = Convention_CPP
7299 then
7300 null;
7302 -- Do not add the body of predefined primitives in case of CIL and
7303 -- Java tagged types.
7305 elsif Convention (Def_Id) = Convention_CIL
7306 or else Convention (Def_Id) = Convention_Java
7307 then
7308 null;
7310 -- Do not add the body of the predefined primitives if we are
7311 -- compiling under restriction No_Dispatching_Calls or if we are
7312 -- compiling a CPP tagged type.
7314 elsif not Restriction_Active (No_Dispatching_Calls) then
7316 -- Create the body of TSS primitive Finalize_Address. This must
7317 -- be done before the bodies of all predefined primitives are
7318 -- created. If Def_Id is limited, Stream_Input and Stream_Read
7319 -- may produce build-in-place allocations and for those the
7320 -- expander needs Finalize_Address.
7322 Make_Finalize_Address_Body (Def_Id);
7323 Predef_List := Predefined_Primitive_Bodies (Def_Id, Renamed_Eq);
7324 Append_Freeze_Actions (Def_Id, Predef_List);
7325 end if;
7327 -- Ada 2005 (AI-391): If any wrappers were created for nonoverridden
7328 -- inherited functions, then add their bodies to the freeze actions.
7330 if Present (Wrapper_Body_List) then
7331 Append_Freeze_Actions (Def_Id, Wrapper_Body_List);
7332 end if;
7334 -- Create extra formals for the primitive operations of the type.
7335 -- This must be done before analyzing the body of the initialization
7336 -- procedure, because a self-referential type might call one of these
7337 -- primitives in the body of the init_proc itself.
7339 declare
7340 Elmt : Elmt_Id;
7341 Subp : Entity_Id;
7343 begin
7344 Elmt := First_Elmt (Primitive_Operations (Def_Id));
7345 while Present (Elmt) loop
7346 Subp := Node (Elmt);
7347 if not Has_Foreign_Convention (Subp)
7348 and then not Is_Predefined_Dispatching_Operation (Subp)
7349 then
7350 Create_Extra_Formals (Subp);
7351 end if;
7353 Next_Elmt (Elmt);
7354 end loop;
7355 end;
7356 end if;
7358 -- Create a heterogeneous finalization master to service the anonymous
7359 -- access-to-controlled components of the record type.
7361 if Has_AACC then
7362 declare
7363 Encl_Scope : constant Entity_Id := Scope (Def_Id);
7364 Ins_Node : constant Node_Id := Parent (Def_Id);
7365 Loc : constant Source_Ptr := Sloc (Def_Id);
7366 Fin_Mas_Id : Entity_Id;
7368 Attributes_Set : Boolean := False;
7369 Master_Built : Boolean := False;
7370 -- Two flags which control the creation and initialization of a
7371 -- common heterogeneous master.
7373 begin
7374 Comp := First_Component (Def_Id);
7375 while Present (Comp) loop
7376 Comp_Typ := Etype (Comp);
7378 -- A non-self-referential anonymous access-to-controlled
7379 -- component.
7381 if Ekind (Comp_Typ) = E_Anonymous_Access_Type
7382 and then Needs_Finalization (Designated_Type (Comp_Typ))
7383 and then Designated_Type (Comp_Typ) /= Def_Id
7384 then
7385 if VM_Target = No_VM then
7387 -- Build a homogeneous master for the first anonymous
7388 -- access-to-controlled component. This master may be
7389 -- converted into a heterogeneous collection if more
7390 -- components are to follow.
7392 if not Master_Built then
7393 Master_Built := True;
7395 -- All anonymous access-to-controlled types allocate
7396 -- on the global pool. Note that the finalization
7397 -- master and the associated storage pool must be set
7398 -- on the root type (both are "root type only").
7400 Set_Associated_Storage_Pool
7401 (Root_Type (Comp_Typ), RTE (RE_Global_Pool_Object));
7403 Build_Finalization_Master
7404 (Typ => Root_Type (Comp_Typ),
7405 For_Anonymous => True,
7406 Context_Scope => Encl_Scope,
7407 Insertion_Node => Ins_Node);
7409 Fin_Mas_Id := Finalization_Master (Comp_Typ);
7411 -- Subsequent anonymous access-to-controlled components
7412 -- reuse the available master.
7414 else
7415 -- All anonymous access-to-controlled types allocate
7416 -- on the global pool. Note that both the finalization
7417 -- master and the associated storage pool must be set
7418 -- on the root type (both are "root type only").
7420 Set_Associated_Storage_Pool
7421 (Root_Type (Comp_Typ), RTE (RE_Global_Pool_Object));
7423 -- Shared the master among multiple components
7425 Set_Finalization_Master
7426 (Root_Type (Comp_Typ), Fin_Mas_Id);
7428 -- Convert the master into a heterogeneous collection.
7429 -- Generate:
7430 -- Set_Is_Heterogeneous (<Fin_Mas_Id>);
7432 if not Attributes_Set then
7433 Attributes_Set := True;
7435 Insert_Action (Ins_Node,
7436 Make_Procedure_Call_Statement (Loc,
7437 Name =>
7438 New_Occurrence_Of
7439 (RTE (RE_Set_Is_Heterogeneous), Loc),
7440 Parameter_Associations => New_List (
7441 New_Occurrence_Of (Fin_Mas_Id, Loc))));
7442 end if;
7443 end if;
7445 -- Since .NET/JVM targets do not support heterogeneous
7446 -- masters, each component must have its own master.
7448 else
7449 Build_Finalization_Master
7450 (Typ => Comp_Typ,
7451 For_Anonymous => True,
7452 Context_Scope => Encl_Scope,
7453 Insertion_Node => Ins_Node);
7454 end if;
7455 end if;
7457 Next_Component (Comp);
7458 end loop;
7459 end;
7460 end if;
7462 -- Check whether individual components have a defined invariant, and add
7463 -- the corresponding component invariant checks.
7465 -- Do not create an invariant procedure for some internally generated
7466 -- subtypes, in particular those created for objects of a class-wide
7467 -- type. Such types may have components to which invariant apply, but
7468 -- the corresponding checks will be applied when an object of the parent
7469 -- type is constructed.
7471 -- Such objects will show up in a class-wide postcondition, and the
7472 -- invariant will be checked, if necessary, upon return from the
7473 -- enclosing subprogram.
7475 if not Is_Class_Wide_Equivalent_Type (Def_Id) then
7476 Insert_Component_Invariant_Checks
7477 (N, Def_Id, Build_Record_Invariant_Proc (Def_Id, N));
7478 end if;
7479 end Expand_Freeze_Record_Type;
7481 ------------------------------
7482 -- Freeze_Stream_Operations --
7483 ------------------------------
7485 procedure Freeze_Stream_Operations (N : Node_Id; Typ : Entity_Id) is
7486 Names : constant array (1 .. 4) of TSS_Name_Type :=
7487 (TSS_Stream_Input,
7488 TSS_Stream_Output,
7489 TSS_Stream_Read,
7490 TSS_Stream_Write);
7491 Stream_Op : Entity_Id;
7493 begin
7494 -- Primitive operations of tagged types are frozen when the dispatch
7495 -- table is constructed.
7497 if not Comes_From_Source (Typ) or else Is_Tagged_Type (Typ) then
7498 return;
7499 end if;
7501 for J in Names'Range loop
7502 Stream_Op := TSS (Typ, Names (J));
7504 if Present (Stream_Op)
7505 and then Is_Subprogram (Stream_Op)
7506 and then Nkind (Unit_Declaration_Node (Stream_Op)) =
7507 N_Subprogram_Declaration
7508 and then not Is_Frozen (Stream_Op)
7509 then
7510 Append_Freeze_Actions (Typ, Freeze_Entity (Stream_Op, N));
7511 end if;
7512 end loop;
7513 end Freeze_Stream_Operations;
7515 -----------------
7516 -- Freeze_Type --
7517 -----------------
7519 -- Full type declarations are expanded at the point at which the type is
7520 -- frozen. The formal N is the Freeze_Node for the type. Any statements or
7521 -- declarations generated by the freezing (e.g. the procedure generated
7522 -- for initialization) are chained in the Actions field list of the freeze
7523 -- node using Append_Freeze_Actions.
7525 function Freeze_Type (N : Node_Id) return Boolean is
7526 GM : constant Ghost_Mode_Type := Ghost_Mode;
7527 -- Save the current Ghost mode in effect in case the type being frozen
7528 -- sets a different mode.
7530 procedure Process_RACW_Types (Typ : Entity_Id);
7531 -- Validate and generate stubs for all RACW types associated with type
7532 -- Typ.
7534 procedure Process_Pending_Access_Types (Typ : Entity_Id);
7535 -- Associate type Typ's Finalize_Address primitive with the finalization
7536 -- masters of pending access-to-Typ types.
7538 procedure Restore_Globals;
7539 -- Restore the values of all saved global variables
7541 ------------------------
7542 -- Process_RACW_Types --
7543 ------------------------
7545 procedure Process_RACW_Types (Typ : Entity_Id) is
7546 List : constant Elist_Id := Access_Types_To_Process (N);
7547 E : Elmt_Id;
7548 Seen : Boolean := False;
7550 begin
7551 if Present (List) then
7552 E := First_Elmt (List);
7553 while Present (E) loop
7554 if Is_Remote_Access_To_Class_Wide_Type (Node (E)) then
7555 Validate_RACW_Primitives (Node (E));
7556 Seen := True;
7557 end if;
7559 Next_Elmt (E);
7560 end loop;
7561 end if;
7563 -- If there are RACWs designating this type, make stubs now
7565 if Seen then
7566 Remote_Types_Tagged_Full_View_Encountered (Typ);
7567 end if;
7568 end Process_RACW_Types;
7570 ----------------------------------
7571 -- Process_Pending_Access_Types --
7572 ----------------------------------
7574 procedure Process_Pending_Access_Types (Typ : Entity_Id) is
7575 E : Elmt_Id;
7577 begin
7578 -- Finalize_Address is not generated in CodePeer mode because the
7579 -- body contains address arithmetic. This processing is disabled.
7581 if CodePeer_Mode then
7582 null;
7584 -- Certain itypes are generated for contexts that cannot allocate
7585 -- objects and should not set primitive Finalize_Address.
7587 elsif Is_Itype (Typ)
7588 and then Nkind (Associated_Node_For_Itype (Typ)) =
7589 N_Explicit_Dereference
7590 then
7591 null;
7593 -- When an access type is declared after the incomplete view of a
7594 -- Taft-amendment type, the access type is considered pending in
7595 -- case the full view of the Taft-amendment type is controlled. If
7596 -- this is indeed the case, associate the Finalize_Address routine
7597 -- of the full view with the finalization masters of all pending
7598 -- access types. This scenario applies to anonymous access types as
7599 -- well.
7601 elsif Needs_Finalization (Typ)
7602 and then Present (Pending_Access_Types (Typ))
7603 then
7604 E := First_Elmt (Pending_Access_Types (Typ));
7605 while Present (E) loop
7607 -- Generate:
7608 -- Set_Finalize_Address
7609 -- (Ptr_Typ, <Typ>FD'Unrestricted_Access);
7611 Append_Freeze_Action (Typ,
7612 Make_Set_Finalize_Address_Call
7613 (Loc => Sloc (N),
7614 Ptr_Typ => Node (E)));
7616 Next_Elmt (E);
7617 end loop;
7618 end if;
7619 end Process_Pending_Access_Types;
7621 ---------------------
7622 -- Restore_Globals --
7623 ---------------------
7625 procedure Restore_Globals is
7626 begin
7627 Ghost_Mode := GM;
7628 end Restore_Globals;
7630 -- Local variables
7632 Def_Id : constant Entity_Id := Entity (N);
7633 Result : Boolean := False;
7635 -- Start of processing for Freeze_Type
7637 begin
7638 -- The type being frozen may be subject to pragma Ghost with policy
7639 -- Ignore. Set the mode now to ensure that any nodes generated during
7640 -- freezing are properly flagged as ignored Ghost.
7642 Set_Ghost_Mode (N, Def_Id);
7644 -- Process any remote access-to-class-wide types designating the type
7645 -- being frozen.
7647 Process_RACW_Types (Def_Id);
7649 -- Freeze processing for record types
7651 if Is_Record_Type (Def_Id) then
7652 if Ekind (Def_Id) = E_Record_Type then
7653 Expand_Freeze_Record_Type (N);
7654 elsif Is_Class_Wide_Type (Def_Id) then
7655 Expand_Freeze_Class_Wide_Type (N);
7656 end if;
7658 -- Freeze processing for array types
7660 elsif Is_Array_Type (Def_Id) then
7661 Expand_Freeze_Array_Type (N);
7663 -- Freeze processing for access types
7665 -- For pool-specific access types, find out the pool object used for
7666 -- this type, needs actual expansion of it in some cases. Here are the
7667 -- different cases :
7669 -- 1. Rep Clause "for Def_Id'Storage_Size use 0;"
7670 -- ---> don't use any storage pool
7672 -- 2. Rep Clause : for Def_Id'Storage_Size use Expr.
7673 -- Expand:
7674 -- Def_Id__Pool : Stack_Bounded_Pool (Expr, DT'Size, DT'Alignment);
7676 -- 3. Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7677 -- ---> Storage Pool is the specified one
7679 -- See GNAT Pool packages in the Run-Time for more details
7681 elsif Ekind_In (Def_Id, E_Access_Type, E_General_Access_Type) then
7682 declare
7683 Loc : constant Source_Ptr := Sloc (N);
7684 Desig_Type : constant Entity_Id := Designated_Type (Def_Id);
7685 Pool_Object : Entity_Id;
7687 Freeze_Action_Typ : Entity_Id;
7689 begin
7690 -- Case 1
7692 -- Rep Clause "for Def_Id'Storage_Size use 0;"
7693 -- ---> don't use any storage pool
7695 if No_Pool_Assigned (Def_Id) then
7696 null;
7698 -- Case 2
7700 -- Rep Clause : for Def_Id'Storage_Size use Expr.
7701 -- ---> Expand:
7702 -- Def_Id__Pool : Stack_Bounded_Pool
7703 -- (Expr, DT'Size, DT'Alignment);
7705 elsif Has_Storage_Size_Clause (Def_Id) then
7706 declare
7707 DT_Size : Node_Id;
7708 DT_Align : Node_Id;
7710 begin
7711 -- For unconstrained composite types we give a size of zero
7712 -- so that the pool knows that it needs a special algorithm
7713 -- for variable size object allocation.
7715 if Is_Composite_Type (Desig_Type)
7716 and then not Is_Constrained (Desig_Type)
7717 then
7718 DT_Size := Make_Integer_Literal (Loc, 0);
7719 DT_Align := Make_Integer_Literal (Loc, Maximum_Alignment);
7721 else
7722 DT_Size :=
7723 Make_Attribute_Reference (Loc,
7724 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7725 Attribute_Name => Name_Max_Size_In_Storage_Elements);
7727 DT_Align :=
7728 Make_Attribute_Reference (Loc,
7729 Prefix => New_Occurrence_Of (Desig_Type, Loc),
7730 Attribute_Name => Name_Alignment);
7731 end if;
7733 Pool_Object :=
7734 Make_Defining_Identifier (Loc,
7735 Chars => New_External_Name (Chars (Def_Id), 'P'));
7737 -- We put the code associated with the pools in the entity
7738 -- that has the later freeze node, usually the access type
7739 -- but it can also be the designated_type; because the pool
7740 -- code requires both those types to be frozen
7742 if Is_Frozen (Desig_Type)
7743 and then (No (Freeze_Node (Desig_Type))
7744 or else Analyzed (Freeze_Node (Desig_Type)))
7745 then
7746 Freeze_Action_Typ := Def_Id;
7748 -- A Taft amendment type cannot get the freeze actions
7749 -- since the full view is not there.
7751 elsif Is_Incomplete_Or_Private_Type (Desig_Type)
7752 and then No (Full_View (Desig_Type))
7753 then
7754 Freeze_Action_Typ := Def_Id;
7756 else
7757 Freeze_Action_Typ := Desig_Type;
7758 end if;
7760 Append_Freeze_Action (Freeze_Action_Typ,
7761 Make_Object_Declaration (Loc,
7762 Defining_Identifier => Pool_Object,
7763 Object_Definition =>
7764 Make_Subtype_Indication (Loc,
7765 Subtype_Mark =>
7766 New_Occurrence_Of
7767 (RTE (RE_Stack_Bounded_Pool), Loc),
7769 Constraint =>
7770 Make_Index_Or_Discriminant_Constraint (Loc,
7771 Constraints => New_List (
7773 -- First discriminant is the Pool Size
7775 New_Occurrence_Of (
7776 Storage_Size_Variable (Def_Id), Loc),
7778 -- Second discriminant is the element size
7780 DT_Size,
7782 -- Third discriminant is the alignment
7784 DT_Align)))));
7785 end;
7787 Set_Associated_Storage_Pool (Def_Id, Pool_Object);
7789 -- Case 3
7791 -- Rep Clause "for Def_Id'Storage_Pool use a_Pool_Object"
7792 -- ---> Storage Pool is the specified one
7794 -- When compiling in Ada 2012 mode, ensure that the accessibility
7795 -- level of the subpool access type is not deeper than that of the
7796 -- pool_with_subpools.
7798 elsif Ada_Version >= Ada_2012
7799 and then Present (Associated_Storage_Pool (Def_Id))
7801 -- Omit this check on .NET/JVM where pools are not supported
7803 and then VM_Target = No_VM
7805 -- Omit this check for the case of a configurable run-time that
7806 -- does not provide package System.Storage_Pools.Subpools.
7808 and then RTE_Available (RE_Root_Storage_Pool_With_Subpools)
7809 then
7810 declare
7811 Loc : constant Source_Ptr := Sloc (Def_Id);
7812 Pool : constant Entity_Id :=
7813 Associated_Storage_Pool (Def_Id);
7814 RSPWS : constant Entity_Id :=
7815 RTE (RE_Root_Storage_Pool_With_Subpools);
7817 begin
7818 -- It is known that the accessibility level of the access
7819 -- type is deeper than that of the pool.
7821 if Type_Access_Level (Def_Id) > Object_Access_Level (Pool)
7822 and then not Accessibility_Checks_Suppressed (Def_Id)
7823 and then not Accessibility_Checks_Suppressed (Pool)
7824 then
7825 -- Static case: the pool is known to be a descendant of
7826 -- Root_Storage_Pool_With_Subpools.
7828 if Is_Ancestor (RSPWS, Etype (Pool)) then
7829 Error_Msg_N
7830 ("??subpool access type has deeper accessibility "
7831 & "level than pool", Def_Id);
7833 Append_Freeze_Action (Def_Id,
7834 Make_Raise_Program_Error (Loc,
7835 Reason => PE_Accessibility_Check_Failed));
7837 -- Dynamic case: when the pool is of a class-wide type,
7838 -- it may or may not support subpools depending on the
7839 -- path of derivation. Generate:
7841 -- if Def_Id in RSPWS'Class then
7842 -- raise Program_Error;
7843 -- end if;
7845 elsif Is_Class_Wide_Type (Etype (Pool)) then
7846 Append_Freeze_Action (Def_Id,
7847 Make_If_Statement (Loc,
7848 Condition =>
7849 Make_In (Loc,
7850 Left_Opnd => New_Occurrence_Of (Pool, Loc),
7851 Right_Opnd =>
7852 New_Occurrence_Of
7853 (Class_Wide_Type (RSPWS), Loc)),
7855 Then_Statements => New_List (
7856 Make_Raise_Program_Error (Loc,
7857 Reason => PE_Accessibility_Check_Failed))));
7858 end if;
7859 end if;
7860 end;
7861 end if;
7863 -- For access-to-controlled types (including class-wide types and
7864 -- Taft-amendment types, which potentially have controlled
7865 -- components), expand the list controller object that will store
7866 -- the dynamically allocated objects. Don't do this transformation
7867 -- for expander-generated access types, but do it for types that
7868 -- are the full view of types derived from other private types.
7869 -- Also suppress the list controller in the case of a designated
7870 -- type with convention Java, since this is used when binding to
7871 -- Java API specs, where there's no equivalent of a finalization
7872 -- list and we don't want to pull in the finalization support if
7873 -- not needed.
7875 if not Comes_From_Source (Def_Id)
7876 and then not Has_Private_Declaration (Def_Id)
7877 then
7878 null;
7880 -- An exception is made for types defined in the run-time because
7881 -- Ada.Tags.Tag itself is such a type and cannot afford this
7882 -- unnecessary overhead that would generates a loop in the
7883 -- expansion scheme. Another exception is if Restrictions
7884 -- (No_Finalization) is active, since then we know nothing is
7885 -- controlled.
7887 elsif Restriction_Active (No_Finalization)
7888 or else In_Runtime (Def_Id)
7889 then
7890 null;
7892 -- Create a finalization master for an access-to-controlled type
7893 -- or an access-to-incomplete type. It is assumed that the full
7894 -- view will be controlled.
7896 elsif Needs_Finalization (Desig_Type)
7897 or else (Is_Incomplete_Type (Desig_Type)
7898 and then No (Full_View (Desig_Type)))
7899 then
7900 Build_Finalization_Master (Def_Id);
7902 -- Create a finalization master when the designated type contains
7903 -- a private component. It is assumed that the full view will be
7904 -- controlled.
7906 elsif Has_Private_Component (Desig_Type) then
7907 Build_Finalization_Master
7908 (Typ => Def_Id,
7909 For_Private => True,
7910 Context_Scope => Scope (Def_Id),
7911 Insertion_Node => Declaration_Node (Desig_Type));
7912 end if;
7913 end;
7915 -- Freeze processing for enumeration types
7917 elsif Ekind (Def_Id) = E_Enumeration_Type then
7919 -- We only have something to do if we have a non-standard
7920 -- representation (i.e. at least one literal whose pos value
7921 -- is not the same as its representation)
7923 if Has_Non_Standard_Rep (Def_Id) then
7924 Expand_Freeze_Enumeration_Type (N);
7925 end if;
7927 -- Private types that are completed by a derivation from a private
7928 -- type have an internally generated full view, that needs to be
7929 -- frozen. This must be done explicitly because the two views share
7930 -- the freeze node, and the underlying full view is not visible when
7931 -- the freeze node is analyzed.
7933 elsif Is_Private_Type (Def_Id)
7934 and then Is_Derived_Type (Def_Id)
7935 and then Present (Full_View (Def_Id))
7936 and then Is_Itype (Full_View (Def_Id))
7937 and then Has_Private_Declaration (Full_View (Def_Id))
7938 and then Freeze_Node (Full_View (Def_Id)) = N
7939 then
7940 Set_Entity (N, Full_View (Def_Id));
7941 Result := Freeze_Type (N);
7942 Set_Entity (N, Def_Id);
7944 -- All other types require no expander action. There are such cases
7945 -- (e.g. task types and protected types). In such cases, the freeze
7946 -- nodes are there for use by Gigi.
7948 end if;
7950 -- Complete the initialization of all pending access types' finalization
7951 -- masters now that the designated type has been is frozen and primitive
7952 -- Finalize_Address generated.
7954 Process_Pending_Access_Types (Def_Id);
7955 Freeze_Stream_Operations (N, Def_Id);
7957 Restore_Globals;
7958 return Result;
7960 exception
7961 when RE_Not_Available =>
7962 Restore_Globals;
7963 return False;
7964 end Freeze_Type;
7966 -------------------------
7967 -- Get_Simple_Init_Val --
7968 -------------------------
7970 function Get_Simple_Init_Val
7971 (T : Entity_Id;
7972 N : Node_Id;
7973 Size : Uint := No_Uint) return Node_Id
7975 Loc : constant Source_Ptr := Sloc (N);
7976 Val : Node_Id;
7977 Result : Node_Id;
7978 Val_RE : RE_Id;
7980 Size_To_Use : Uint;
7981 -- This is the size to be used for computation of the appropriate
7982 -- initial value for the Normalize_Scalars and Initialize_Scalars case.
7984 IV_Attribute : constant Boolean :=
7985 Nkind (N) = N_Attribute_Reference
7986 and then Attribute_Name (N) = Name_Invalid_Value;
7988 Lo_Bound : Uint;
7989 Hi_Bound : Uint;
7990 -- These are the values computed by the procedure Check_Subtype_Bounds
7992 procedure Check_Subtype_Bounds;
7993 -- This procedure examines the subtype T, and its ancestor subtypes and
7994 -- derived types to determine the best known information about the
7995 -- bounds of the subtype. After the call Lo_Bound is set either to
7996 -- No_Uint if no information can be determined, or to a value which
7997 -- represents a known low bound, i.e. a valid value of the subtype can
7998 -- not be less than this value. Hi_Bound is similarly set to a known
7999 -- high bound (valid value cannot be greater than this).
8001 --------------------------
8002 -- Check_Subtype_Bounds --
8003 --------------------------
8005 procedure Check_Subtype_Bounds is
8006 ST1 : Entity_Id;
8007 ST2 : Entity_Id;
8008 Lo : Node_Id;
8009 Hi : Node_Id;
8010 Loval : Uint;
8011 Hival : Uint;
8013 begin
8014 Lo_Bound := No_Uint;
8015 Hi_Bound := No_Uint;
8017 -- Loop to climb ancestor subtypes and derived types
8019 ST1 := T;
8020 loop
8021 if not Is_Discrete_Type (ST1) then
8022 return;
8023 end if;
8025 Lo := Type_Low_Bound (ST1);
8026 Hi := Type_High_Bound (ST1);
8028 if Compile_Time_Known_Value (Lo) then
8029 Loval := Expr_Value (Lo);
8031 if Lo_Bound = No_Uint or else Lo_Bound < Loval then
8032 Lo_Bound := Loval;
8033 end if;
8034 end if;
8036 if Compile_Time_Known_Value (Hi) then
8037 Hival := Expr_Value (Hi);
8039 if Hi_Bound = No_Uint or else Hi_Bound > Hival then
8040 Hi_Bound := Hival;
8041 end if;
8042 end if;
8044 ST2 := Ancestor_Subtype (ST1);
8046 if No (ST2) then
8047 ST2 := Etype (ST1);
8048 end if;
8050 exit when ST1 = ST2;
8051 ST1 := ST2;
8052 end loop;
8053 end Check_Subtype_Bounds;
8055 -- Start of processing for Get_Simple_Init_Val
8057 begin
8058 -- For a private type, we should always have an underlying type (because
8059 -- this was already checked in Needs_Simple_Initialization). What we do
8060 -- is to get the value for the underlying type and then do an unchecked
8061 -- conversion to the private type.
8063 if Is_Private_Type (T) then
8064 Val := Get_Simple_Init_Val (Underlying_Type (T), N, Size);
8066 -- A special case, if the underlying value is null, then qualify it
8067 -- with the underlying type, so that the null is properly typed.
8068 -- Similarly, if it is an aggregate it must be qualified, because an
8069 -- unchecked conversion does not provide a context for it.
8071 if Nkind_In (Val, N_Null, N_Aggregate) then
8072 Val :=
8073 Make_Qualified_Expression (Loc,
8074 Subtype_Mark =>
8075 New_Occurrence_Of (Underlying_Type (T), Loc),
8076 Expression => Val);
8077 end if;
8079 Result := Unchecked_Convert_To (T, Val);
8081 -- Don't truncate result (important for Initialize/Normalize_Scalars)
8083 if Nkind (Result) = N_Unchecked_Type_Conversion
8084 and then Is_Scalar_Type (Underlying_Type (T))
8085 then
8086 Set_No_Truncation (Result);
8087 end if;
8089 return Result;
8091 -- Scalars with Default_Value aspect. The first subtype may now be
8092 -- private, so retrieve value from underlying type.
8094 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
8095 if Is_Private_Type (First_Subtype (T)) then
8096 return Unchecked_Convert_To (T,
8097 Default_Aspect_Value (Full_View (First_Subtype (T))));
8098 else
8099 return
8100 Convert_To (T, Default_Aspect_Value (First_Subtype (T)));
8101 end if;
8103 -- Otherwise, for scalars, we must have normalize/initialize scalars
8104 -- case, or if the node N is an 'Invalid_Value attribute node.
8106 elsif Is_Scalar_Type (T) then
8107 pragma Assert (Init_Or_Norm_Scalars or IV_Attribute);
8109 -- Compute size of object. If it is given by the caller, we can use
8110 -- it directly, otherwise we use Esize (T) as an estimate. As far as
8111 -- we know this covers all cases correctly.
8113 if Size = No_Uint or else Size <= Uint_0 then
8114 Size_To_Use := UI_Max (Uint_1, Esize (T));
8115 else
8116 Size_To_Use := Size;
8117 end if;
8119 -- Maximum size to use is 64 bits, since we will create values of
8120 -- type Unsigned_64 and the range must fit this type.
8122 if Size_To_Use /= No_Uint and then Size_To_Use > Uint_64 then
8123 Size_To_Use := Uint_64;
8124 end if;
8126 -- Check known bounds of subtype
8128 Check_Subtype_Bounds;
8130 -- Processing for Normalize_Scalars case
8132 if Normalize_Scalars and then not IV_Attribute then
8134 -- If zero is invalid, it is a convenient value to use that is
8135 -- for sure an appropriate invalid value in all situations.
8137 if Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
8138 Val := Make_Integer_Literal (Loc, 0);
8140 -- Cases where all one bits is the appropriate invalid value
8142 -- For modular types, all 1 bits is either invalid or valid. If
8143 -- it is valid, then there is nothing that can be done since there
8144 -- are no invalid values (we ruled out zero already).
8146 -- For signed integer types that have no negative values, either
8147 -- there is room for negative values, or there is not. If there
8148 -- is, then all 1-bits may be interpreted as minus one, which is
8149 -- certainly invalid. Alternatively it is treated as the largest
8150 -- positive value, in which case the observation for modular types
8151 -- still applies.
8153 -- For float types, all 1-bits is a NaN (not a number), which is
8154 -- certainly an appropriately invalid value.
8156 elsif Is_Unsigned_Type (T)
8157 or else Is_Floating_Point_Type (T)
8158 or else Is_Enumeration_Type (T)
8159 then
8160 Val := Make_Integer_Literal (Loc, 2 ** Size_To_Use - 1);
8162 -- Resolve as Unsigned_64, because the largest number we can
8163 -- generate is out of range of universal integer.
8165 Analyze_And_Resolve (Val, RTE (RE_Unsigned_64));
8167 -- Case of signed types
8169 else
8170 declare
8171 Signed_Size : constant Uint :=
8172 UI_Min (Uint_63, Size_To_Use - 1);
8174 begin
8175 -- Normally we like to use the most negative number. The one
8176 -- exception is when this number is in the known subtype
8177 -- range and the largest positive number is not in the known
8178 -- subtype range.
8180 -- For this exceptional case, use largest positive value
8182 if Lo_Bound /= No_Uint and then Hi_Bound /= No_Uint
8183 and then Lo_Bound <= (-(2 ** Signed_Size))
8184 and then Hi_Bound < 2 ** Signed_Size
8185 then
8186 Val := Make_Integer_Literal (Loc, 2 ** Signed_Size - 1);
8188 -- Normal case of largest negative value
8190 else
8191 Val := Make_Integer_Literal (Loc, -(2 ** Signed_Size));
8192 end if;
8193 end;
8194 end if;
8196 -- Here for Initialize_Scalars case (or Invalid_Value attribute used)
8198 else
8199 -- For float types, use float values from System.Scalar_Values
8201 if Is_Floating_Point_Type (T) then
8202 if Root_Type (T) = Standard_Short_Float then
8203 Val_RE := RE_IS_Isf;
8204 elsif Root_Type (T) = Standard_Float then
8205 Val_RE := RE_IS_Ifl;
8206 elsif Root_Type (T) = Standard_Long_Float then
8207 Val_RE := RE_IS_Ilf;
8208 else pragma Assert (Root_Type (T) = Standard_Long_Long_Float);
8209 Val_RE := RE_IS_Ill;
8210 end if;
8212 -- If zero is invalid, use zero values from System.Scalar_Values
8214 elsif Lo_Bound /= No_Uint and then Lo_Bound > Uint_0 then
8215 if Size_To_Use <= 8 then
8216 Val_RE := RE_IS_Iz1;
8217 elsif Size_To_Use <= 16 then
8218 Val_RE := RE_IS_Iz2;
8219 elsif Size_To_Use <= 32 then
8220 Val_RE := RE_IS_Iz4;
8221 else
8222 Val_RE := RE_IS_Iz8;
8223 end if;
8225 -- For unsigned, use unsigned values from System.Scalar_Values
8227 elsif Is_Unsigned_Type (T) then
8228 if Size_To_Use <= 8 then
8229 Val_RE := RE_IS_Iu1;
8230 elsif Size_To_Use <= 16 then
8231 Val_RE := RE_IS_Iu2;
8232 elsif Size_To_Use <= 32 then
8233 Val_RE := RE_IS_Iu4;
8234 else
8235 Val_RE := RE_IS_Iu8;
8236 end if;
8238 -- For signed, use signed values from System.Scalar_Values
8240 else
8241 if Size_To_Use <= 8 then
8242 Val_RE := RE_IS_Is1;
8243 elsif Size_To_Use <= 16 then
8244 Val_RE := RE_IS_Is2;
8245 elsif Size_To_Use <= 32 then
8246 Val_RE := RE_IS_Is4;
8247 else
8248 Val_RE := RE_IS_Is8;
8249 end if;
8250 end if;
8252 Val := New_Occurrence_Of (RTE (Val_RE), Loc);
8253 end if;
8255 -- The final expression is obtained by doing an unchecked conversion
8256 -- of this result to the base type of the required subtype. Use the
8257 -- base type to prevent the unchecked conversion from chopping bits,
8258 -- and then we set Kill_Range_Check to preserve the "bad" value.
8260 Result := Unchecked_Convert_To (Base_Type (T), Val);
8262 -- Ensure result is not truncated, since we want the "bad" bits, and
8263 -- also kill range check on result.
8265 if Nkind (Result) = N_Unchecked_Type_Conversion then
8266 Set_No_Truncation (Result);
8267 Set_Kill_Range_Check (Result, True);
8268 end if;
8270 return Result;
8272 -- String or Wide_[Wide]_String (must have Initialize_Scalars set)
8274 elsif Is_Standard_String_Type (T) then
8275 pragma Assert (Init_Or_Norm_Scalars);
8277 return
8278 Make_Aggregate (Loc,
8279 Component_Associations => New_List (
8280 Make_Component_Association (Loc,
8281 Choices => New_List (
8282 Make_Others_Choice (Loc)),
8283 Expression =>
8284 Get_Simple_Init_Val
8285 (Component_Type (T), N, Esize (Root_Type (T))))));
8287 -- Access type is initialized to null
8289 elsif Is_Access_Type (T) then
8290 return Make_Null (Loc);
8292 -- No other possibilities should arise, since we should only be calling
8293 -- Get_Simple_Init_Val if Needs_Simple_Initialization returned True,
8294 -- indicating one of the above cases held.
8296 else
8297 raise Program_Error;
8298 end if;
8300 exception
8301 when RE_Not_Available =>
8302 return Empty;
8303 end Get_Simple_Init_Val;
8305 ------------------------------
8306 -- Has_New_Non_Standard_Rep --
8307 ------------------------------
8309 function Has_New_Non_Standard_Rep (T : Entity_Id) return Boolean is
8310 begin
8311 if not Is_Derived_Type (T) then
8312 return Has_Non_Standard_Rep (T)
8313 or else Has_Non_Standard_Rep (Root_Type (T));
8315 -- If Has_Non_Standard_Rep is not set on the derived type, the
8316 -- representation is fully inherited.
8318 elsif not Has_Non_Standard_Rep (T) then
8319 return False;
8321 else
8322 return First_Rep_Item (T) /= First_Rep_Item (Root_Type (T));
8324 -- May need a more precise check here: the First_Rep_Item may be a
8325 -- stream attribute, which does not affect the representation of the
8326 -- type ???
8328 end if;
8329 end Has_New_Non_Standard_Rep;
8331 ----------------
8332 -- In_Runtime --
8333 ----------------
8335 function In_Runtime (E : Entity_Id) return Boolean is
8336 S1 : Entity_Id;
8338 begin
8339 S1 := Scope (E);
8340 while Scope (S1) /= Standard_Standard loop
8341 S1 := Scope (S1);
8342 end loop;
8344 return Is_RTU (S1, System) or else Is_RTU (S1, Ada);
8345 end In_Runtime;
8347 ---------------------------------------
8348 -- Insert_Component_Invariant_Checks --
8349 ---------------------------------------
8351 procedure Insert_Component_Invariant_Checks
8352 (N : Node_Id;
8353 Typ : Entity_Id;
8354 Proc : Node_Id)
8356 Loc : constant Source_Ptr := Sloc (Typ);
8357 Proc_Id : Entity_Id;
8359 begin
8360 if Present (Proc) then
8361 Proc_Id := Defining_Entity (Proc);
8363 if not Has_Invariants (Typ) then
8364 Set_Has_Invariants (Typ);
8365 Set_Is_Invariant_Procedure (Proc_Id);
8366 Set_Invariant_Procedure (Typ, Proc_Id);
8367 Insert_After (N, Proc);
8368 Analyze (Proc);
8370 else
8372 -- Find already created invariant subprogram, insert body of
8373 -- component invariant proc in its body, and add call after
8374 -- other checks.
8376 declare
8377 Bod : Node_Id;
8378 Inv_Id : constant Entity_Id := Invariant_Procedure (Typ);
8379 Call : constant Node_Id :=
8380 Make_Procedure_Call_Statement (Sloc (N),
8381 Name => New_Occurrence_Of (Proc_Id, Loc),
8382 Parameter_Associations =>
8383 New_List
8384 (New_Occurrence_Of (First_Formal (Inv_Id), Loc)));
8386 begin
8387 -- The invariant body has not been analyzed yet, so we do a
8388 -- sequential search forward, and retrieve it by name.
8390 Bod := Next (N);
8391 while Present (Bod) loop
8392 exit when Nkind (Bod) = N_Subprogram_Body
8393 and then Chars (Defining_Entity (Bod)) = Chars (Inv_Id);
8394 Next (Bod);
8395 end loop;
8397 -- If the body is not found, it is the case of an invariant
8398 -- appearing on a full declaration in a private part, in
8399 -- which case the type has been frozen but the invariant
8400 -- procedure for the composite type not created yet. Create
8401 -- body now.
8403 if No (Bod) then
8404 Build_Invariant_Procedure (Typ, Parent (Current_Scope));
8405 Bod := Unit_Declaration_Node
8406 (Corresponding_Body (Unit_Declaration_Node (Inv_Id)));
8407 end if;
8409 Append_To (Declarations (Bod), Proc);
8410 Append_To (Statements (Handled_Statement_Sequence (Bod)), Call);
8411 Analyze (Proc);
8412 Analyze (Call);
8413 end;
8414 end if;
8415 end if;
8416 end Insert_Component_Invariant_Checks;
8418 ----------------------------
8419 -- Initialization_Warning --
8420 ----------------------------
8422 procedure Initialization_Warning (E : Entity_Id) is
8423 Warning_Needed : Boolean;
8425 begin
8426 Warning_Needed := False;
8428 if Ekind (Current_Scope) = E_Package
8429 and then Static_Elaboration_Desired (Current_Scope)
8430 then
8431 if Is_Type (E) then
8432 if Is_Record_Type (E) then
8433 if Has_Discriminants (E)
8434 or else Is_Limited_Type (E)
8435 or else Has_Non_Standard_Rep (E)
8436 then
8437 Warning_Needed := True;
8439 else
8440 -- Verify that at least one component has an initialization
8441 -- expression. No need for a warning on a type if all its
8442 -- components have no initialization.
8444 declare
8445 Comp : Entity_Id;
8447 begin
8448 Comp := First_Component (E);
8449 while Present (Comp) loop
8450 if Ekind (Comp) = E_Discriminant
8451 or else
8452 (Nkind (Parent (Comp)) = N_Component_Declaration
8453 and then Present (Expression (Parent (Comp))))
8454 then
8455 Warning_Needed := True;
8456 exit;
8457 end if;
8459 Next_Component (Comp);
8460 end loop;
8461 end;
8462 end if;
8464 if Warning_Needed then
8465 Error_Msg_N
8466 ("Objects of the type cannot be initialized statically "
8467 & "by default??", Parent (E));
8468 end if;
8469 end if;
8471 else
8472 Error_Msg_N ("Object cannot be initialized statically??", E);
8473 end if;
8474 end if;
8475 end Initialization_Warning;
8477 ------------------
8478 -- Init_Formals --
8479 ------------------
8481 function Init_Formals (Typ : Entity_Id) return List_Id is
8482 Loc : constant Source_Ptr := Sloc (Typ);
8483 Formals : List_Id;
8485 begin
8486 -- First parameter is always _Init : in out typ. Note that we need this
8487 -- to be in/out because in the case of the task record value, there
8488 -- are default record fields (_Priority, _Size, -Task_Info) that may
8489 -- be referenced in the generated initialization routine.
8491 Formals := New_List (
8492 Make_Parameter_Specification (Loc,
8493 Defining_Identifier => Make_Defining_Identifier (Loc, Name_uInit),
8494 In_Present => True,
8495 Out_Present => True,
8496 Parameter_Type => New_Occurrence_Of (Typ, Loc)));
8498 -- For task record value, or type that contains tasks, add two more
8499 -- formals, _Master : Master_Id and _Chain : in out Activation_Chain
8500 -- We also add these parameters for the task record type case.
8502 if Has_Task (Typ)
8503 or else (Is_Record_Type (Typ) and then Is_Task_Record_Type (Typ))
8504 then
8505 Append_To (Formals,
8506 Make_Parameter_Specification (Loc,
8507 Defining_Identifier =>
8508 Make_Defining_Identifier (Loc, Name_uMaster),
8509 Parameter_Type =>
8510 New_Occurrence_Of (RTE (RE_Master_Id), Loc)));
8512 -- Add _Chain (not done for sequential elaboration policy, see
8513 -- comment for Create_Restricted_Task_Sequential in s-tarest.ads).
8515 if Partition_Elaboration_Policy /= 'S' then
8516 Append_To (Formals,
8517 Make_Parameter_Specification (Loc,
8518 Defining_Identifier =>
8519 Make_Defining_Identifier (Loc, Name_uChain),
8520 In_Present => True,
8521 Out_Present => True,
8522 Parameter_Type =>
8523 New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)));
8524 end if;
8526 Append_To (Formals,
8527 Make_Parameter_Specification (Loc,
8528 Defining_Identifier =>
8529 Make_Defining_Identifier (Loc, Name_uTask_Name),
8530 In_Present => True,
8531 Parameter_Type => New_Occurrence_Of (Standard_String, Loc)));
8532 end if;
8534 return Formals;
8536 exception
8537 when RE_Not_Available =>
8538 return Empty_List;
8539 end Init_Formals;
8541 -------------------------
8542 -- Init_Secondary_Tags --
8543 -------------------------
8545 procedure Init_Secondary_Tags
8546 (Typ : Entity_Id;
8547 Target : Node_Id;
8548 Stmts_List : List_Id;
8549 Fixed_Comps : Boolean := True;
8550 Variable_Comps : Boolean := True)
8552 Loc : constant Source_Ptr := Sloc (Target);
8554 -- Inherit the C++ tag of the secondary dispatch table of Typ associated
8555 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8557 procedure Initialize_Tag
8558 (Typ : Entity_Id;
8559 Iface : Entity_Id;
8560 Tag_Comp : Entity_Id;
8561 Iface_Tag : Node_Id);
8562 -- Initialize the tag of the secondary dispatch table of Typ associated
8563 -- with Iface. Tag_Comp is the component of Typ that stores Iface_Tag.
8564 -- Compiling under the CPP full ABI compatibility mode, if the ancestor
8565 -- of Typ CPP tagged type we generate code to inherit the contents of
8566 -- the dispatch table directly from the ancestor.
8568 --------------------
8569 -- Initialize_Tag --
8570 --------------------
8572 procedure Initialize_Tag
8573 (Typ : Entity_Id;
8574 Iface : Entity_Id;
8575 Tag_Comp : Entity_Id;
8576 Iface_Tag : Node_Id)
8578 Comp_Typ : Entity_Id;
8579 Offset_To_Top_Comp : Entity_Id := Empty;
8581 begin
8582 -- Initialize pointer to secondary DT associated with the interface
8584 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8585 Append_To (Stmts_List,
8586 Make_Assignment_Statement (Loc,
8587 Name =>
8588 Make_Selected_Component (Loc,
8589 Prefix => New_Copy_Tree (Target),
8590 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8591 Expression =>
8592 New_Occurrence_Of (Iface_Tag, Loc)));
8593 end if;
8595 Comp_Typ := Scope (Tag_Comp);
8597 -- Initialize the entries of the table of interfaces. We generate a
8598 -- different call when the parent of the type has variable size
8599 -- components.
8601 if Comp_Typ /= Etype (Comp_Typ)
8602 and then Is_Variable_Size_Record (Etype (Comp_Typ))
8603 and then Chars (Tag_Comp) /= Name_uTag
8604 then
8605 pragma Assert (Present (DT_Offset_To_Top_Func (Tag_Comp)));
8607 -- Issue error if Set_Dynamic_Offset_To_Top is not available in a
8608 -- configurable run-time environment.
8610 if not RTE_Available (RE_Set_Dynamic_Offset_To_Top) then
8611 Error_Msg_CRT
8612 ("variable size record with interface types", Typ);
8613 return;
8614 end if;
8616 -- Generate:
8617 -- Set_Dynamic_Offset_To_Top
8618 -- (This => Init,
8619 -- Interface_T => Iface'Tag,
8620 -- Offset_Value => n,
8621 -- Offset_Func => Fn'Address)
8623 Append_To (Stmts_List,
8624 Make_Procedure_Call_Statement (Loc,
8625 Name =>
8626 New_Occurrence_Of (RTE (RE_Set_Dynamic_Offset_To_Top), Loc),
8627 Parameter_Associations => New_List (
8628 Make_Attribute_Reference (Loc,
8629 Prefix => New_Copy_Tree (Target),
8630 Attribute_Name => Name_Address),
8632 Unchecked_Convert_To (RTE (RE_Tag),
8633 New_Occurrence_Of
8634 (Node (First_Elmt (Access_Disp_Table (Iface))),
8635 Loc)),
8637 Unchecked_Convert_To
8638 (RTE (RE_Storage_Offset),
8639 Make_Attribute_Reference (Loc,
8640 Prefix =>
8641 Make_Selected_Component (Loc,
8642 Prefix => New_Copy_Tree (Target),
8643 Selector_Name =>
8644 New_Occurrence_Of (Tag_Comp, Loc)),
8645 Attribute_Name => Name_Position)),
8647 Unchecked_Convert_To (RTE (RE_Offset_To_Top_Function_Ptr),
8648 Make_Attribute_Reference (Loc,
8649 Prefix => New_Occurrence_Of
8650 (DT_Offset_To_Top_Func (Tag_Comp), Loc),
8651 Attribute_Name => Name_Address)))));
8653 -- In this case the next component stores the value of the offset
8654 -- to the top.
8656 Offset_To_Top_Comp := Next_Entity (Tag_Comp);
8657 pragma Assert (Present (Offset_To_Top_Comp));
8659 Append_To (Stmts_List,
8660 Make_Assignment_Statement (Loc,
8661 Name =>
8662 Make_Selected_Component (Loc,
8663 Prefix => New_Copy_Tree (Target),
8664 Selector_Name =>
8665 New_Occurrence_Of (Offset_To_Top_Comp, Loc)),
8667 Expression =>
8668 Make_Attribute_Reference (Loc,
8669 Prefix =>
8670 Make_Selected_Component (Loc,
8671 Prefix => New_Copy_Tree (Target),
8672 Selector_Name => New_Occurrence_Of (Tag_Comp, Loc)),
8673 Attribute_Name => Name_Position)));
8675 -- Normal case: No discriminants in the parent type
8677 else
8678 -- Don't need to set any value if this interface shares the
8679 -- primary dispatch table.
8681 if not Is_Ancestor (Iface, Typ, Use_Full_View => True) then
8682 Append_To (Stmts_List,
8683 Build_Set_Static_Offset_To_Top (Loc,
8684 Iface_Tag => New_Occurrence_Of (Iface_Tag, Loc),
8685 Offset_Value =>
8686 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8687 Make_Attribute_Reference (Loc,
8688 Prefix =>
8689 Make_Selected_Component (Loc,
8690 Prefix => New_Copy_Tree (Target),
8691 Selector_Name =>
8692 New_Occurrence_Of (Tag_Comp, Loc)),
8693 Attribute_Name => Name_Position))));
8694 end if;
8696 -- Generate:
8697 -- Register_Interface_Offset
8698 -- (This => Init,
8699 -- Interface_T => Iface'Tag,
8700 -- Is_Constant => True,
8701 -- Offset_Value => n,
8702 -- Offset_Func => null);
8704 if RTE_Available (RE_Register_Interface_Offset) then
8705 Append_To (Stmts_List,
8706 Make_Procedure_Call_Statement (Loc,
8707 Name =>
8708 New_Occurrence_Of
8709 (RTE (RE_Register_Interface_Offset), Loc),
8710 Parameter_Associations => New_List (
8711 Make_Attribute_Reference (Loc,
8712 Prefix => New_Copy_Tree (Target),
8713 Attribute_Name => Name_Address),
8715 Unchecked_Convert_To (RTE (RE_Tag),
8716 New_Occurrence_Of
8717 (Node (First_Elmt (Access_Disp_Table (Iface))), Loc)),
8719 New_Occurrence_Of (Standard_True, Loc),
8721 Unchecked_Convert_To (RTE (RE_Storage_Offset),
8722 Make_Attribute_Reference (Loc,
8723 Prefix =>
8724 Make_Selected_Component (Loc,
8725 Prefix => New_Copy_Tree (Target),
8726 Selector_Name =>
8727 New_Occurrence_Of (Tag_Comp, Loc)),
8728 Attribute_Name => Name_Position)),
8730 Make_Null (Loc))));
8731 end if;
8732 end if;
8733 end Initialize_Tag;
8735 -- Local variables
8737 Full_Typ : Entity_Id;
8738 Ifaces_List : Elist_Id;
8739 Ifaces_Comp_List : Elist_Id;
8740 Ifaces_Tag_List : Elist_Id;
8741 Iface_Elmt : Elmt_Id;
8742 Iface_Comp_Elmt : Elmt_Id;
8743 Iface_Tag_Elmt : Elmt_Id;
8744 Tag_Comp : Node_Id;
8745 In_Variable_Pos : Boolean;
8747 -- Start of processing for Init_Secondary_Tags
8749 begin
8750 -- Handle private types
8752 if Present (Full_View (Typ)) then
8753 Full_Typ := Full_View (Typ);
8754 else
8755 Full_Typ := Typ;
8756 end if;
8758 Collect_Interfaces_Info
8759 (Full_Typ, Ifaces_List, Ifaces_Comp_List, Ifaces_Tag_List);
8761 Iface_Elmt := First_Elmt (Ifaces_List);
8762 Iface_Comp_Elmt := First_Elmt (Ifaces_Comp_List);
8763 Iface_Tag_Elmt := First_Elmt (Ifaces_Tag_List);
8764 while Present (Iface_Elmt) loop
8765 Tag_Comp := Node (Iface_Comp_Elmt);
8767 -- Check if parent of record type has variable size components
8769 In_Variable_Pos := Scope (Tag_Comp) /= Etype (Scope (Tag_Comp))
8770 and then Is_Variable_Size_Record (Etype (Scope (Tag_Comp)));
8772 -- If we are compiling under the CPP full ABI compatibility mode and
8773 -- the ancestor is a CPP_Pragma tagged type then we generate code to
8774 -- initialize the secondary tag components from tags that reference
8775 -- secondary tables filled with copy of parent slots.
8777 if Is_CPP_Class (Root_Type (Full_Typ)) then
8779 -- Reject interface components located at variable offset in
8780 -- C++ derivations. This is currently unsupported.
8782 if not Fixed_Comps and then In_Variable_Pos then
8784 -- Locate the first dynamic component of the record. Done to
8785 -- improve the text of the warning.
8787 declare
8788 Comp : Entity_Id;
8789 Comp_Typ : Entity_Id;
8791 begin
8792 Comp := First_Entity (Typ);
8793 while Present (Comp) loop
8794 Comp_Typ := Etype (Comp);
8796 if Ekind (Comp) /= E_Discriminant
8797 and then not Is_Tag (Comp)
8798 then
8799 exit when
8800 (Is_Record_Type (Comp_Typ)
8801 and then
8802 Is_Variable_Size_Record (Base_Type (Comp_Typ)))
8803 or else
8804 (Is_Array_Type (Comp_Typ)
8805 and then Is_Variable_Size_Array (Comp_Typ));
8806 end if;
8808 Next_Entity (Comp);
8809 end loop;
8811 pragma Assert (Present (Comp));
8812 Error_Msg_Node_2 := Comp;
8813 Error_Msg_NE
8814 ("parent type & with dynamic component & cannot be parent"
8815 & " of 'C'P'P derivation if new interfaces are present",
8816 Typ, Scope (Original_Record_Component (Comp)));
8818 Error_Msg_Sloc :=
8819 Sloc (Scope (Original_Record_Component (Comp)));
8820 Error_Msg_NE
8821 ("type derived from 'C'P'P type & defined #",
8822 Typ, Scope (Original_Record_Component (Comp)));
8824 -- Avoid duplicated warnings
8826 exit;
8827 end;
8829 -- Initialize secondary tags
8831 else
8832 Append_To (Stmts_List,
8833 Make_Assignment_Statement (Loc,
8834 Name =>
8835 Make_Selected_Component (Loc,
8836 Prefix => New_Copy_Tree (Target),
8837 Selector_Name =>
8838 New_Occurrence_Of (Node (Iface_Comp_Elmt), Loc)),
8839 Expression =>
8840 New_Occurrence_Of (Node (Iface_Tag_Elmt), Loc)));
8841 end if;
8843 -- Otherwise generate code to initialize the tag
8845 else
8846 if (In_Variable_Pos and then Variable_Comps)
8847 or else (not In_Variable_Pos and then Fixed_Comps)
8848 then
8849 Initialize_Tag (Full_Typ,
8850 Iface => Node (Iface_Elmt),
8851 Tag_Comp => Tag_Comp,
8852 Iface_Tag => Node (Iface_Tag_Elmt));
8853 end if;
8854 end if;
8856 Next_Elmt (Iface_Elmt);
8857 Next_Elmt (Iface_Comp_Elmt);
8858 Next_Elmt (Iface_Tag_Elmt);
8859 end loop;
8860 end Init_Secondary_Tags;
8862 ------------------------
8863 -- Is_User_Defined_Eq --
8864 ------------------------
8866 function Is_User_Defined_Equality (Prim : Node_Id) return Boolean is
8867 begin
8868 return Chars (Prim) = Name_Op_Eq
8869 and then Etype (First_Formal (Prim)) =
8870 Etype (Next_Formal (First_Formal (Prim)))
8871 and then Base_Type (Etype (Prim)) = Standard_Boolean;
8872 end Is_User_Defined_Equality;
8874 ----------------------------------------
8875 -- Make_Controlling_Function_Wrappers --
8876 ----------------------------------------
8878 procedure Make_Controlling_Function_Wrappers
8879 (Tag_Typ : Entity_Id;
8880 Decl_List : out List_Id;
8881 Body_List : out List_Id)
8883 Loc : constant Source_Ptr := Sloc (Tag_Typ);
8884 Prim_Elmt : Elmt_Id;
8885 Subp : Entity_Id;
8886 Actual_List : List_Id;
8887 Formal_List : List_Id;
8888 Formal : Entity_Id;
8889 Par_Formal : Entity_Id;
8890 Formal_Node : Node_Id;
8891 Func_Body : Node_Id;
8892 Func_Decl : Node_Id;
8893 Func_Spec : Node_Id;
8894 Return_Stmt : Node_Id;
8896 begin
8897 Decl_List := New_List;
8898 Body_List := New_List;
8900 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
8901 while Present (Prim_Elmt) loop
8902 Subp := Node (Prim_Elmt);
8904 -- If a primitive function with a controlling result of the type has
8905 -- not been overridden by the user, then we must create a wrapper
8906 -- function here that effectively overrides it and invokes the
8907 -- (non-abstract) parent function. This can only occur for a null
8908 -- extension. Note that functions with anonymous controlling access
8909 -- results don't qualify and must be overridden. We also exclude
8910 -- Input attributes, since each type will have its own version of
8911 -- Input constructed by the expander. The test for Comes_From_Source
8912 -- is needed to distinguish inherited operations from renamings
8913 -- (which also have Alias set). We exclude internal entities with
8914 -- Interface_Alias to avoid generating duplicated wrappers since
8915 -- the primitive which covers the interface is also available in
8916 -- the list of primitive operations.
8918 -- The function may be abstract, or require_Overriding may be set
8919 -- for it, because tests for null extensions may already have reset
8920 -- the Is_Abstract_Subprogram_Flag. If Requires_Overriding is not
8921 -- set, functions that need wrappers are recognized by having an
8922 -- alias that returns the parent type.
8924 if Comes_From_Source (Subp)
8925 or else No (Alias (Subp))
8926 or else Present (Interface_Alias (Subp))
8927 or else Ekind (Subp) /= E_Function
8928 or else not Has_Controlling_Result (Subp)
8929 or else Is_Access_Type (Etype (Subp))
8930 or else Is_Abstract_Subprogram (Alias (Subp))
8931 or else Is_TSS (Subp, TSS_Stream_Input)
8932 then
8933 goto Next_Prim;
8935 elsif Is_Abstract_Subprogram (Subp)
8936 or else Requires_Overriding (Subp)
8937 or else
8938 (Is_Null_Extension (Etype (Subp))
8939 and then Etype (Alias (Subp)) /= Etype (Subp))
8940 then
8941 Formal_List := No_List;
8942 Formal := First_Formal (Subp);
8944 if Present (Formal) then
8945 Formal_List := New_List;
8947 while Present (Formal) loop
8948 Append
8949 (Make_Parameter_Specification
8950 (Loc,
8951 Defining_Identifier =>
8952 Make_Defining_Identifier (Sloc (Formal),
8953 Chars => Chars (Formal)),
8954 In_Present => In_Present (Parent (Formal)),
8955 Out_Present => Out_Present (Parent (Formal)),
8956 Null_Exclusion_Present =>
8957 Null_Exclusion_Present (Parent (Formal)),
8958 Parameter_Type =>
8959 New_Occurrence_Of (Etype (Formal), Loc),
8960 Expression =>
8961 New_Copy_Tree (Expression (Parent (Formal)))),
8962 Formal_List);
8964 Next_Formal (Formal);
8965 end loop;
8966 end if;
8968 Func_Spec :=
8969 Make_Function_Specification (Loc,
8970 Defining_Unit_Name =>
8971 Make_Defining_Identifier (Loc,
8972 Chars => Chars (Subp)),
8973 Parameter_Specifications => Formal_List,
8974 Result_Definition =>
8975 New_Occurrence_Of (Etype (Subp), Loc));
8977 Func_Decl := Make_Subprogram_Declaration (Loc, Func_Spec);
8978 Append_To (Decl_List, Func_Decl);
8980 -- Build a wrapper body that calls the parent function. The body
8981 -- contains a single return statement that returns an extension
8982 -- aggregate whose ancestor part is a call to the parent function,
8983 -- passing the formals as actuals (with any controlling arguments
8984 -- converted to the types of the corresponding formals of the
8985 -- parent function, which might be anonymous access types), and
8986 -- having a null extension.
8988 Formal := First_Formal (Subp);
8989 Par_Formal := First_Formal (Alias (Subp));
8990 Formal_Node := First (Formal_List);
8992 if Present (Formal) then
8993 Actual_List := New_List;
8994 else
8995 Actual_List := No_List;
8996 end if;
8998 while Present (Formal) loop
8999 if Is_Controlling_Formal (Formal) then
9000 Append_To (Actual_List,
9001 Make_Type_Conversion (Loc,
9002 Subtype_Mark =>
9003 New_Occurrence_Of (Etype (Par_Formal), Loc),
9004 Expression =>
9005 New_Occurrence_Of
9006 (Defining_Identifier (Formal_Node), Loc)));
9007 else
9008 Append_To
9009 (Actual_List,
9010 New_Occurrence_Of
9011 (Defining_Identifier (Formal_Node), Loc));
9012 end if;
9014 Next_Formal (Formal);
9015 Next_Formal (Par_Formal);
9016 Next (Formal_Node);
9017 end loop;
9019 Return_Stmt :=
9020 Make_Simple_Return_Statement (Loc,
9021 Expression =>
9022 Make_Extension_Aggregate (Loc,
9023 Ancestor_Part =>
9024 Make_Function_Call (Loc,
9025 Name =>
9026 New_Occurrence_Of (Alias (Subp), Loc),
9027 Parameter_Associations => Actual_List),
9028 Null_Record_Present => True));
9030 Func_Body :=
9031 Make_Subprogram_Body (Loc,
9032 Specification => New_Copy_Tree (Func_Spec),
9033 Declarations => Empty_List,
9034 Handled_Statement_Sequence =>
9035 Make_Handled_Sequence_Of_Statements (Loc,
9036 Statements => New_List (Return_Stmt)));
9038 Set_Defining_Unit_Name
9039 (Specification (Func_Body),
9040 Make_Defining_Identifier (Loc, Chars (Subp)));
9042 Append_To (Body_List, Func_Body);
9044 -- Replace the inherited function with the wrapper function in the
9045 -- primitive operations list. We add the minimum decoration needed
9046 -- to override interface primitives.
9048 Set_Ekind (Defining_Unit_Name (Func_Spec), E_Function);
9050 Override_Dispatching_Operation
9051 (Tag_Typ, Subp, New_Op => Defining_Unit_Name (Func_Spec),
9052 Is_Wrapper => True);
9053 end if;
9055 <<Next_Prim>>
9056 Next_Elmt (Prim_Elmt);
9057 end loop;
9058 end Make_Controlling_Function_Wrappers;
9060 -------------------
9061 -- Make_Eq_Body --
9062 -------------------
9064 function Make_Eq_Body
9065 (Typ : Entity_Id;
9066 Eq_Name : Name_Id) return Node_Id
9068 Loc : constant Source_Ptr := Sloc (Parent (Typ));
9069 Decl : Node_Id;
9070 Def : constant Node_Id := Parent (Typ);
9071 Stmts : constant List_Id := New_List;
9072 Variant_Case : Boolean := Has_Discriminants (Typ);
9073 Comps : Node_Id := Empty;
9074 Typ_Def : Node_Id := Type_Definition (Def);
9076 begin
9077 Decl :=
9078 Predef_Spec_Or_Body (Loc,
9079 Tag_Typ => Typ,
9080 Name => Eq_Name,
9081 Profile => New_List (
9082 Make_Parameter_Specification (Loc,
9083 Defining_Identifier =>
9084 Make_Defining_Identifier (Loc, Name_X),
9085 Parameter_Type => New_Occurrence_Of (Typ, Loc)),
9087 Make_Parameter_Specification (Loc,
9088 Defining_Identifier =>
9089 Make_Defining_Identifier (Loc, Name_Y),
9090 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
9092 Ret_Type => Standard_Boolean,
9093 For_Body => True);
9095 if Variant_Case then
9096 if Nkind (Typ_Def) = N_Derived_Type_Definition then
9097 Typ_Def := Record_Extension_Part (Typ_Def);
9098 end if;
9100 if Present (Typ_Def) then
9101 Comps := Component_List (Typ_Def);
9102 end if;
9104 Variant_Case :=
9105 Present (Comps) and then Present (Variant_Part (Comps));
9106 end if;
9108 if Variant_Case then
9109 Append_To (Stmts,
9110 Make_Eq_If (Typ, Discriminant_Specifications (Def)));
9111 Append_List_To (Stmts, Make_Eq_Case (Typ, Comps));
9112 Append_To (Stmts,
9113 Make_Simple_Return_Statement (Loc,
9114 Expression => New_Occurrence_Of (Standard_True, Loc)));
9116 else
9117 Append_To (Stmts,
9118 Make_Simple_Return_Statement (Loc,
9119 Expression =>
9120 Expand_Record_Equality
9121 (Typ,
9122 Typ => Typ,
9123 Lhs => Make_Identifier (Loc, Name_X),
9124 Rhs => Make_Identifier (Loc, Name_Y),
9125 Bodies => Declarations (Decl))));
9126 end if;
9128 Set_Handled_Statement_Sequence
9129 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
9130 return Decl;
9131 end Make_Eq_Body;
9133 ------------------
9134 -- Make_Eq_Case --
9135 ------------------
9137 -- <Make_Eq_If shared components>
9139 -- case X.D1 is
9140 -- when V1 => <Make_Eq_Case> on subcomponents
9141 -- ...
9142 -- when Vn => <Make_Eq_Case> on subcomponents
9143 -- end case;
9145 function Make_Eq_Case
9146 (E : Entity_Id;
9147 CL : Node_Id;
9148 Discrs : Elist_Id := New_Elmt_List) return List_Id
9150 Loc : constant Source_Ptr := Sloc (E);
9151 Result : constant List_Id := New_List;
9152 Variant : Node_Id;
9153 Alt_List : List_Id;
9155 function Corresponding_Formal (C : Node_Id) return Entity_Id;
9156 -- Given the discriminant that controls a given variant of an unchecked
9157 -- union, find the formal of the equality function that carries the
9158 -- inferred value of the discriminant.
9160 function External_Name (E : Entity_Id) return Name_Id;
9161 -- The value of a given discriminant is conveyed in the corresponding
9162 -- formal parameter of the equality routine. The name of this formal
9163 -- parameter carries a one-character suffix which is removed here.
9165 --------------------------
9166 -- Corresponding_Formal --
9167 --------------------------
9169 function Corresponding_Formal (C : Node_Id) return Entity_Id is
9170 Discr : constant Entity_Id := Entity (Name (Variant_Part (C)));
9171 Elm : Elmt_Id;
9173 begin
9174 Elm := First_Elmt (Discrs);
9175 while Present (Elm) loop
9176 if Chars (Discr) = External_Name (Node (Elm)) then
9177 return Node (Elm);
9178 end if;
9180 Next_Elmt (Elm);
9181 end loop;
9183 -- A formal of the proper name must be found
9185 raise Program_Error;
9186 end Corresponding_Formal;
9188 -------------------
9189 -- External_Name --
9190 -------------------
9192 function External_Name (E : Entity_Id) return Name_Id is
9193 begin
9194 Get_Name_String (Chars (E));
9195 Name_Len := Name_Len - 1;
9196 return Name_Find;
9197 end External_Name;
9199 -- Start of processing for Make_Eq_Case
9201 begin
9202 Append_To (Result, Make_Eq_If (E, Component_Items (CL)));
9204 if No (Variant_Part (CL)) then
9205 return Result;
9206 end if;
9208 Variant := First_Non_Pragma (Variants (Variant_Part (CL)));
9210 if No (Variant) then
9211 return Result;
9212 end if;
9214 Alt_List := New_List;
9215 while Present (Variant) loop
9216 Append_To (Alt_List,
9217 Make_Case_Statement_Alternative (Loc,
9218 Discrete_Choices => New_Copy_List (Discrete_Choices (Variant)),
9219 Statements =>
9220 Make_Eq_Case (E, Component_List (Variant), Discrs)));
9221 Next_Non_Pragma (Variant);
9222 end loop;
9224 -- If we have an Unchecked_Union, use one of the parameters of the
9225 -- enclosing equality routine that captures the discriminant, to use
9226 -- as the expression in the generated case statement.
9228 if Is_Unchecked_Union (E) then
9229 Append_To (Result,
9230 Make_Case_Statement (Loc,
9231 Expression =>
9232 New_Occurrence_Of (Corresponding_Formal (CL), Loc),
9233 Alternatives => Alt_List));
9235 else
9236 Append_To (Result,
9237 Make_Case_Statement (Loc,
9238 Expression =>
9239 Make_Selected_Component (Loc,
9240 Prefix => Make_Identifier (Loc, Name_X),
9241 Selector_Name => New_Copy (Name (Variant_Part (CL)))),
9242 Alternatives => Alt_List));
9243 end if;
9245 return Result;
9246 end Make_Eq_Case;
9248 ----------------
9249 -- Make_Eq_If --
9250 ----------------
9252 -- Generates:
9254 -- if
9255 -- X.C1 /= Y.C1
9256 -- or else
9257 -- X.C2 /= Y.C2
9258 -- ...
9259 -- then
9260 -- return False;
9261 -- end if;
9263 -- or a null statement if the list L is empty
9265 function Make_Eq_If
9266 (E : Entity_Id;
9267 L : List_Id) return Node_Id
9269 Loc : constant Source_Ptr := Sloc (E);
9270 C : Node_Id;
9271 Field_Name : Name_Id;
9272 Cond : Node_Id;
9274 begin
9275 if No (L) then
9276 return Make_Null_Statement (Loc);
9278 else
9279 Cond := Empty;
9281 C := First_Non_Pragma (L);
9282 while Present (C) loop
9283 Field_Name := Chars (Defining_Identifier (C));
9285 -- The tags must not be compared: they are not part of the value.
9286 -- Ditto for parent interfaces because their equality operator is
9287 -- abstract.
9289 -- Note also that in the following, we use Make_Identifier for
9290 -- the component names. Use of New_Occurrence_Of to identify the
9291 -- components would be incorrect because the wrong entities for
9292 -- discriminants could be picked up in the private type case.
9294 if Field_Name = Name_uParent
9295 and then Is_Interface (Etype (Defining_Identifier (C)))
9296 then
9297 null;
9299 elsif Field_Name /= Name_uTag then
9300 Evolve_Or_Else (Cond,
9301 Make_Op_Ne (Loc,
9302 Left_Opnd =>
9303 Make_Selected_Component (Loc,
9304 Prefix => Make_Identifier (Loc, Name_X),
9305 Selector_Name => Make_Identifier (Loc, Field_Name)),
9307 Right_Opnd =>
9308 Make_Selected_Component (Loc,
9309 Prefix => Make_Identifier (Loc, Name_Y),
9310 Selector_Name => Make_Identifier (Loc, Field_Name))));
9311 end if;
9313 Next_Non_Pragma (C);
9314 end loop;
9316 if No (Cond) then
9317 return Make_Null_Statement (Loc);
9319 else
9320 return
9321 Make_Implicit_If_Statement (E,
9322 Condition => Cond,
9323 Then_Statements => New_List (
9324 Make_Simple_Return_Statement (Loc,
9325 Expression => New_Occurrence_Of (Standard_False, Loc))));
9326 end if;
9327 end if;
9328 end Make_Eq_If;
9330 -------------------
9331 -- Make_Neq_Body --
9332 -------------------
9334 function Make_Neq_Body (Tag_Typ : Entity_Id) return Node_Id is
9336 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean;
9337 -- Returns true if Prim is a renaming of an unresolved predefined
9338 -- inequality operation.
9340 --------------------------------
9341 -- Is_Predefined_Neq_Renaming --
9342 --------------------------------
9344 function Is_Predefined_Neq_Renaming (Prim : Node_Id) return Boolean is
9345 begin
9346 return Chars (Prim) /= Name_Op_Ne
9347 and then Present (Alias (Prim))
9348 and then Comes_From_Source (Prim)
9349 and then Is_Intrinsic_Subprogram (Alias (Prim))
9350 and then Chars (Alias (Prim)) = Name_Op_Ne;
9351 end Is_Predefined_Neq_Renaming;
9353 -- Local variables
9355 Loc : constant Source_Ptr := Sloc (Parent (Tag_Typ));
9356 Stmts : constant List_Id := New_List;
9357 Decl : Node_Id;
9358 Eq_Prim : Entity_Id;
9359 Left_Op : Entity_Id;
9360 Renaming_Prim : Entity_Id;
9361 Right_Op : Entity_Id;
9362 Target : Entity_Id;
9364 -- Start of processing for Make_Neq_Body
9366 begin
9367 -- For a call on a renaming of a dispatching subprogram that is
9368 -- overridden, if the overriding occurred before the renaming, then
9369 -- the body executed is that of the overriding declaration, even if the
9370 -- overriding declaration is not visible at the place of the renaming;
9371 -- otherwise, the inherited or predefined subprogram is called, see
9372 -- (RM 8.5.4(8))
9374 -- Stage 1: Search for a renaming of the inequality primitive and also
9375 -- search for an overriding of the equality primitive located before the
9376 -- renaming declaration.
9378 declare
9379 Elmt : Elmt_Id;
9380 Prim : Node_Id;
9382 begin
9383 Eq_Prim := Empty;
9384 Renaming_Prim := Empty;
9386 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9387 while Present (Elmt) loop
9388 Prim := Node (Elmt);
9390 if Is_User_Defined_Equality (Prim) and then No (Alias (Prim)) then
9391 if No (Renaming_Prim) then
9392 pragma Assert (No (Eq_Prim));
9393 Eq_Prim := Prim;
9394 end if;
9396 elsif Is_Predefined_Neq_Renaming (Prim) then
9397 Renaming_Prim := Prim;
9398 end if;
9400 Next_Elmt (Elmt);
9401 end loop;
9402 end;
9404 -- No further action needed if no renaming was found
9406 if No (Renaming_Prim) then
9407 return Empty;
9408 end if;
9410 -- Stage 2: Replace the renaming declaration by a subprogram declaration
9411 -- (required to add its body)
9413 Decl := Parent (Parent (Renaming_Prim));
9414 Rewrite (Decl,
9415 Make_Subprogram_Declaration (Loc,
9416 Specification => Specification (Decl)));
9417 Set_Analyzed (Decl);
9419 -- Remove the decoration of intrinsic renaming subprogram
9421 Set_Is_Intrinsic_Subprogram (Renaming_Prim, False);
9422 Set_Convention (Renaming_Prim, Convention_Ada);
9423 Set_Alias (Renaming_Prim, Empty);
9424 Set_Has_Completion (Renaming_Prim, False);
9426 -- Stage 3: Build the corresponding body
9428 Left_Op := First_Formal (Renaming_Prim);
9429 Right_Op := Next_Formal (Left_Op);
9431 Decl :=
9432 Predef_Spec_Or_Body (Loc,
9433 Tag_Typ => Tag_Typ,
9434 Name => Chars (Renaming_Prim),
9435 Profile => New_List (
9436 Make_Parameter_Specification (Loc,
9437 Defining_Identifier =>
9438 Make_Defining_Identifier (Loc, Chars (Left_Op)),
9439 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9441 Make_Parameter_Specification (Loc,
9442 Defining_Identifier =>
9443 Make_Defining_Identifier (Loc, Chars (Right_Op)),
9444 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9446 Ret_Type => Standard_Boolean,
9447 For_Body => True);
9449 -- If the overriding of the equality primitive occurred before the
9450 -- renaming, then generate:
9452 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9453 -- begin
9454 -- return not Oeq (X, Y);
9455 -- end;
9457 if Present (Eq_Prim) then
9458 Target := Eq_Prim;
9460 -- Otherwise build a nested subprogram which performs the predefined
9461 -- evaluation of the equality operator. That is, generate:
9463 -- function <Neq_Name> (X : Y : Typ) return Boolean is
9464 -- function Oeq (X : Y) return Boolean is
9465 -- begin
9466 -- <<body of default implementation>>
9467 -- end;
9468 -- begin
9469 -- return not Oeq (X, Y);
9470 -- end;
9472 else
9473 declare
9474 Local_Subp : Node_Id;
9475 begin
9476 Local_Subp := Make_Eq_Body (Tag_Typ, Name_Op_Eq);
9477 Set_Declarations (Decl, New_List (Local_Subp));
9478 Target := Defining_Entity (Local_Subp);
9479 end;
9480 end if;
9482 Append_To (Stmts,
9483 Make_Simple_Return_Statement (Loc,
9484 Expression =>
9485 Make_Op_Not (Loc,
9486 Make_Function_Call (Loc,
9487 Name => New_Occurrence_Of (Target, Loc),
9488 Parameter_Associations => New_List (
9489 Make_Identifier (Loc, Chars (Left_Op)),
9490 Make_Identifier (Loc, Chars (Right_Op)))))));
9492 Set_Handled_Statement_Sequence
9493 (Decl, Make_Handled_Sequence_Of_Statements (Loc, Stmts));
9494 return Decl;
9495 end Make_Neq_Body;
9497 -------------------------------
9498 -- Make_Null_Procedure_Specs --
9499 -------------------------------
9501 function Make_Null_Procedure_Specs (Tag_Typ : Entity_Id) return List_Id is
9502 Decl_List : constant List_Id := New_List;
9503 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9504 Formal : Entity_Id;
9505 Formal_List : List_Id;
9506 New_Param_Spec : Node_Id;
9507 Parent_Subp : Entity_Id;
9508 Prim_Elmt : Elmt_Id;
9509 Subp : Entity_Id;
9511 begin
9512 Prim_Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
9513 while Present (Prim_Elmt) loop
9514 Subp := Node (Prim_Elmt);
9516 -- If a null procedure inherited from an interface has not been
9517 -- overridden, then we build a null procedure declaration to
9518 -- override the inherited procedure.
9520 Parent_Subp := Alias (Subp);
9522 if Present (Parent_Subp)
9523 and then Is_Null_Interface_Primitive (Parent_Subp)
9524 then
9525 Formal_List := No_List;
9526 Formal := First_Formal (Subp);
9528 if Present (Formal) then
9529 Formal_List := New_List;
9531 while Present (Formal) loop
9533 -- Copy the parameter spec including default expressions
9535 New_Param_Spec :=
9536 New_Copy_Tree (Parent (Formal), New_Sloc => Loc);
9538 -- Generate a new defining identifier for the new formal.
9539 -- required because New_Copy_Tree does not duplicate
9540 -- semantic fields (except itypes).
9542 Set_Defining_Identifier (New_Param_Spec,
9543 Make_Defining_Identifier (Sloc (Formal),
9544 Chars => Chars (Formal)));
9546 -- For controlling arguments we must change their
9547 -- parameter type to reference the tagged type (instead
9548 -- of the interface type)
9550 if Is_Controlling_Formal (Formal) then
9551 if Nkind (Parameter_Type (Parent (Formal))) = N_Identifier
9552 then
9553 Set_Parameter_Type (New_Param_Spec,
9554 New_Occurrence_Of (Tag_Typ, Loc));
9556 else pragma Assert
9557 (Nkind (Parameter_Type (Parent (Formal))) =
9558 N_Access_Definition);
9559 Set_Subtype_Mark (Parameter_Type (New_Param_Spec),
9560 New_Occurrence_Of (Tag_Typ, Loc));
9561 end if;
9562 end if;
9564 Append (New_Param_Spec, Formal_List);
9566 Next_Formal (Formal);
9567 end loop;
9568 end if;
9570 Append_To (Decl_List,
9571 Make_Subprogram_Declaration (Loc,
9572 Make_Procedure_Specification (Loc,
9573 Defining_Unit_Name =>
9574 Make_Defining_Identifier (Loc, Chars (Subp)),
9575 Parameter_Specifications => Formal_List,
9576 Null_Present => True)));
9577 end if;
9579 Next_Elmt (Prim_Elmt);
9580 end loop;
9582 return Decl_List;
9583 end Make_Null_Procedure_Specs;
9585 -------------------------------------
9586 -- Make_Predefined_Primitive_Specs --
9587 -------------------------------------
9589 procedure Make_Predefined_Primitive_Specs
9590 (Tag_Typ : Entity_Id;
9591 Predef_List : out List_Id;
9592 Renamed_Eq : out Entity_Id)
9594 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean;
9595 -- Returns true if Prim is a renaming of an unresolved predefined
9596 -- equality operation.
9598 -------------------------------
9599 -- Is_Predefined_Eq_Renaming --
9600 -------------------------------
9602 function Is_Predefined_Eq_Renaming (Prim : Node_Id) return Boolean is
9603 begin
9604 return Chars (Prim) /= Name_Op_Eq
9605 and then Present (Alias (Prim))
9606 and then Comes_From_Source (Prim)
9607 and then Is_Intrinsic_Subprogram (Alias (Prim))
9608 and then Chars (Alias (Prim)) = Name_Op_Eq;
9609 end Is_Predefined_Eq_Renaming;
9611 -- Local variables
9613 Loc : constant Source_Ptr := Sloc (Tag_Typ);
9614 Res : constant List_Id := New_List;
9615 Eq_Name : Name_Id := Name_Op_Eq;
9616 Eq_Needed : Boolean;
9617 Eq_Spec : Node_Id;
9618 Prim : Elmt_Id;
9620 Has_Predef_Eq_Renaming : Boolean := False;
9621 -- Set to True if Tag_Typ has a primitive that renames the predefined
9622 -- equality operator. Used to implement (RM 8-5-4(8)).
9624 -- Start of processing for Make_Predefined_Primitive_Specs
9626 begin
9627 Renamed_Eq := Empty;
9629 -- Spec of _Size
9631 Append_To (Res, Predef_Spec_Or_Body (Loc,
9632 Tag_Typ => Tag_Typ,
9633 Name => Name_uSize,
9634 Profile => New_List (
9635 Make_Parameter_Specification (Loc,
9636 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9637 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9639 Ret_Type => Standard_Long_Long_Integer));
9641 -- Specs for dispatching stream attributes
9643 declare
9644 Stream_Op_TSS_Names :
9645 constant array (Integer range <>) of TSS_Name_Type :=
9646 (TSS_Stream_Read,
9647 TSS_Stream_Write,
9648 TSS_Stream_Input,
9649 TSS_Stream_Output);
9651 begin
9652 for Op in Stream_Op_TSS_Names'Range loop
9653 if Stream_Operation_OK (Tag_Typ, Stream_Op_TSS_Names (Op)) then
9654 Append_To (Res,
9655 Predef_Stream_Attr_Spec (Loc, Tag_Typ,
9656 Stream_Op_TSS_Names (Op)));
9657 end if;
9658 end loop;
9659 end;
9661 -- Spec of "=" is expanded if the type is not limited and if a user
9662 -- defined "=" was not already declared for the non-full view of a
9663 -- private extension
9665 if not Is_Limited_Type (Tag_Typ) then
9666 Eq_Needed := True;
9667 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9668 while Present (Prim) loop
9670 -- If a primitive is encountered that renames the predefined
9671 -- equality operator before reaching any explicit equality
9672 -- primitive, then we still need to create a predefined equality
9673 -- function, because calls to it can occur via the renaming. A
9674 -- new name is created for the equality to avoid conflicting with
9675 -- any user-defined equality. (Note that this doesn't account for
9676 -- renamings of equality nested within subpackages???)
9678 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9679 Has_Predef_Eq_Renaming := True;
9680 Eq_Name := New_External_Name (Chars (Node (Prim)), 'E');
9682 -- User-defined equality
9684 elsif Is_User_Defined_Equality (Node (Prim)) then
9685 if No (Alias (Node (Prim)))
9686 or else Nkind (Unit_Declaration_Node (Node (Prim))) =
9687 N_Subprogram_Renaming_Declaration
9688 then
9689 Eq_Needed := False;
9690 exit;
9692 -- If the parent is not an interface type and has an abstract
9693 -- equality function, the inherited equality is abstract as
9694 -- well, and no body can be created for it.
9696 elsif not Is_Interface (Etype (Tag_Typ))
9697 and then Present (Alias (Node (Prim)))
9698 and then Is_Abstract_Subprogram (Alias (Node (Prim)))
9699 then
9700 Eq_Needed := False;
9701 exit;
9703 -- If the type has an equality function corresponding with
9704 -- a primitive defined in an interface type, the inherited
9705 -- equality is abstract as well, and no body can be created
9706 -- for it.
9708 elsif Present (Alias (Node (Prim)))
9709 and then Comes_From_Source (Ultimate_Alias (Node (Prim)))
9710 and then
9711 Is_Interface
9712 (Find_Dispatching_Type (Ultimate_Alias (Node (Prim))))
9713 then
9714 Eq_Needed := False;
9715 exit;
9716 end if;
9717 end if;
9719 Next_Elmt (Prim);
9720 end loop;
9722 -- If a renaming of predefined equality was found but there was no
9723 -- user-defined equality (so Eq_Needed is still true), then set the
9724 -- name back to Name_Op_Eq. But in the case where a user-defined
9725 -- equality was located after such a renaming, then the predefined
9726 -- equality function is still needed, so Eq_Needed must be set back
9727 -- to True.
9729 if Eq_Name /= Name_Op_Eq then
9730 if Eq_Needed then
9731 Eq_Name := Name_Op_Eq;
9732 else
9733 Eq_Needed := True;
9734 end if;
9735 end if;
9737 if Eq_Needed then
9738 Eq_Spec := Predef_Spec_Or_Body (Loc,
9739 Tag_Typ => Tag_Typ,
9740 Name => Eq_Name,
9741 Profile => New_List (
9742 Make_Parameter_Specification (Loc,
9743 Defining_Identifier =>
9744 Make_Defining_Identifier (Loc, Name_X),
9745 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9747 Make_Parameter_Specification (Loc,
9748 Defining_Identifier =>
9749 Make_Defining_Identifier (Loc, Name_Y),
9750 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
9751 Ret_Type => Standard_Boolean);
9752 Append_To (Res, Eq_Spec);
9754 if Has_Predef_Eq_Renaming then
9755 Renamed_Eq := Defining_Unit_Name (Specification (Eq_Spec));
9757 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
9758 while Present (Prim) loop
9760 -- Any renamings of equality that appeared before an
9761 -- overriding equality must be updated to refer to the
9762 -- entity for the predefined equality, otherwise calls via
9763 -- the renaming would get incorrectly resolved to call the
9764 -- user-defined equality function.
9766 if Is_Predefined_Eq_Renaming (Node (Prim)) then
9767 Set_Alias (Node (Prim), Renamed_Eq);
9769 -- Exit upon encountering a user-defined equality
9771 elsif Chars (Node (Prim)) = Name_Op_Eq
9772 and then No (Alias (Node (Prim)))
9773 then
9774 exit;
9775 end if;
9777 Next_Elmt (Prim);
9778 end loop;
9779 end if;
9780 end if;
9782 -- Spec for dispatching assignment
9784 Append_To (Res, Predef_Spec_Or_Body (Loc,
9785 Tag_Typ => Tag_Typ,
9786 Name => Name_uAssign,
9787 Profile => New_List (
9788 Make_Parameter_Specification (Loc,
9789 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
9790 Out_Present => True,
9791 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
9793 Make_Parameter_Specification (Loc,
9794 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
9795 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)))));
9796 end if;
9798 -- Ada 2005: Generate declarations for the following primitive
9799 -- operations for limited interfaces and synchronized types that
9800 -- implement a limited interface.
9802 -- Disp_Asynchronous_Select
9803 -- Disp_Conditional_Select
9804 -- Disp_Get_Prim_Op_Kind
9805 -- Disp_Get_Task_Id
9806 -- Disp_Requeue
9807 -- Disp_Timed_Select
9809 -- Disable the generation of these bodies if No_Dispatching_Calls,
9810 -- Ravenscar or ZFP is active.
9812 if Ada_Version >= Ada_2005
9813 and then not Restriction_Active (No_Dispatching_Calls)
9814 and then not Restriction_Active (No_Select_Statements)
9815 and then RTE_Available (RE_Select_Specific_Data)
9816 then
9817 -- These primitives are defined abstract in interface types
9819 if Is_Interface (Tag_Typ)
9820 and then Is_Limited_Record (Tag_Typ)
9821 then
9822 Append_To (Res,
9823 Make_Abstract_Subprogram_Declaration (Loc,
9824 Specification =>
9825 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9827 Append_To (Res,
9828 Make_Abstract_Subprogram_Declaration (Loc,
9829 Specification =>
9830 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9832 Append_To (Res,
9833 Make_Abstract_Subprogram_Declaration (Loc,
9834 Specification =>
9835 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9837 Append_To (Res,
9838 Make_Abstract_Subprogram_Declaration (Loc,
9839 Specification =>
9840 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9842 Append_To (Res,
9843 Make_Abstract_Subprogram_Declaration (Loc,
9844 Specification =>
9845 Make_Disp_Requeue_Spec (Tag_Typ)));
9847 Append_To (Res,
9848 Make_Abstract_Subprogram_Declaration (Loc,
9849 Specification =>
9850 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9852 -- If ancestor is an interface type, declare non-abstract primitives
9853 -- to override the abstract primitives of the interface type.
9855 -- In VM targets we define these primitives in all root tagged types
9856 -- that are not interface types. Done because in VM targets we don't
9857 -- have secondary dispatch tables and any derivation of Tag_Typ may
9858 -- cover limited interfaces (which always have these primitives since
9859 -- they may be ancestors of synchronized interface types).
9861 elsif (not Is_Interface (Tag_Typ)
9862 and then Is_Interface (Etype (Tag_Typ))
9863 and then Is_Limited_Record (Etype (Tag_Typ)))
9864 or else
9865 (Is_Concurrent_Record_Type (Tag_Typ)
9866 and then Has_Interfaces (Tag_Typ))
9867 or else
9868 (not Tagged_Type_Expansion
9869 and then not Is_Interface (Tag_Typ)
9870 and then Tag_Typ = Root_Type (Tag_Typ))
9871 then
9872 Append_To (Res,
9873 Make_Subprogram_Declaration (Loc,
9874 Specification =>
9875 Make_Disp_Asynchronous_Select_Spec (Tag_Typ)));
9877 Append_To (Res,
9878 Make_Subprogram_Declaration (Loc,
9879 Specification =>
9880 Make_Disp_Conditional_Select_Spec (Tag_Typ)));
9882 Append_To (Res,
9883 Make_Subprogram_Declaration (Loc,
9884 Specification =>
9885 Make_Disp_Get_Prim_Op_Kind_Spec (Tag_Typ)));
9887 Append_To (Res,
9888 Make_Subprogram_Declaration (Loc,
9889 Specification =>
9890 Make_Disp_Get_Task_Id_Spec (Tag_Typ)));
9892 Append_To (Res,
9893 Make_Subprogram_Declaration (Loc,
9894 Specification =>
9895 Make_Disp_Requeue_Spec (Tag_Typ)));
9897 Append_To (Res,
9898 Make_Subprogram_Declaration (Loc,
9899 Specification =>
9900 Make_Disp_Timed_Select_Spec (Tag_Typ)));
9901 end if;
9902 end if;
9904 -- All tagged types receive their own Deep_Adjust and Deep_Finalize
9905 -- regardless of whether they are controlled or may contain controlled
9906 -- components.
9908 -- Do not generate the routines if finalization is disabled
9910 if Restriction_Active (No_Finalization) then
9911 null;
9913 -- Finalization is not available for CIL value types
9915 elsif Is_Value_Type (Tag_Typ) then
9916 null;
9918 else
9919 if not Is_Limited_Type (Tag_Typ) then
9920 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust));
9921 end if;
9923 Append_To (Res, Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize));
9924 end if;
9926 Predef_List := Res;
9927 end Make_Predefined_Primitive_Specs;
9929 -------------------------
9930 -- Make_Tag_Assignment --
9931 -------------------------
9933 function Make_Tag_Assignment (N : Node_Id) return Node_Id is
9934 Loc : constant Source_Ptr := Sloc (N);
9935 Def_If : constant Entity_Id := Defining_Identifier (N);
9936 Expr : constant Node_Id := Expression (N);
9937 Typ : constant Entity_Id := Etype (Def_If);
9938 Full_Typ : constant Entity_Id := Underlying_Type (Typ);
9939 New_Ref : Node_Id;
9941 begin
9942 -- This expansion activity is called during analysis, but cannot
9943 -- be applied in ASIS mode when other expansion is disabled.
9945 if Is_Tagged_Type (Typ)
9946 and then not Is_Class_Wide_Type (Typ)
9947 and then not Is_CPP_Class (Typ)
9948 and then Tagged_Type_Expansion
9949 and then Nkind (Expr) /= N_Aggregate
9950 and then not ASIS_Mode
9951 and then (Nkind (Expr) /= N_Qualified_Expression
9952 or else Nkind (Expression (Expr)) /= N_Aggregate)
9953 then
9954 New_Ref :=
9955 Make_Selected_Component (Loc,
9956 Prefix => New_Occurrence_Of (Def_If, Loc),
9957 Selector_Name =>
9958 New_Occurrence_Of (First_Tag_Component (Full_Typ), Loc));
9959 Set_Assignment_OK (New_Ref);
9961 return
9962 Make_Assignment_Statement (Loc,
9963 Name => New_Ref,
9964 Expression =>
9965 Unchecked_Convert_To (RTE (RE_Tag),
9966 New_Occurrence_Of (Node
9967 (First_Elmt (Access_Disp_Table (Full_Typ))), Loc)));
9968 else
9969 return Empty;
9970 end if;
9971 end Make_Tag_Assignment;
9973 ---------------------------------
9974 -- Needs_Simple_Initialization --
9975 ---------------------------------
9977 function Needs_Simple_Initialization
9978 (T : Entity_Id;
9979 Consider_IS : Boolean := True) return Boolean
9981 Consider_IS_NS : constant Boolean :=
9982 Normalize_Scalars or (Initialize_Scalars and Consider_IS);
9984 begin
9985 -- Never need initialization if it is suppressed
9987 if Initialization_Suppressed (T) then
9988 return False;
9989 end if;
9991 -- Check for private type, in which case test applies to the underlying
9992 -- type of the private type.
9994 if Is_Private_Type (T) then
9995 declare
9996 RT : constant Entity_Id := Underlying_Type (T);
9997 begin
9998 if Present (RT) then
9999 return Needs_Simple_Initialization (RT);
10000 else
10001 return False;
10002 end if;
10003 end;
10005 -- Scalar type with Default_Value aspect requires initialization
10007 elsif Is_Scalar_Type (T) and then Has_Default_Aspect (T) then
10008 return True;
10010 -- Cases needing simple initialization are access types, and, if pragma
10011 -- Normalize_Scalars or Initialize_Scalars is in effect, then all scalar
10012 -- types.
10014 elsif Is_Access_Type (T)
10015 or else (Consider_IS_NS and then (Is_Scalar_Type (T)))
10016 then
10017 return True;
10019 -- If Initialize/Normalize_Scalars is in effect, string objects also
10020 -- need initialization, unless they are created in the course of
10021 -- expanding an aggregate (since in the latter case they will be
10022 -- filled with appropriate initializing values before they are used).
10024 elsif Consider_IS_NS
10025 and then Is_Standard_String_Type (T)
10026 and then
10027 (not Is_Itype (T)
10028 or else Nkind (Associated_Node_For_Itype (T)) /= N_Aggregate)
10029 then
10030 return True;
10032 else
10033 return False;
10034 end if;
10035 end Needs_Simple_Initialization;
10037 ----------------------
10038 -- Predef_Deep_Spec --
10039 ----------------------
10041 function Predef_Deep_Spec
10042 (Loc : Source_Ptr;
10043 Tag_Typ : Entity_Id;
10044 Name : TSS_Name_Type;
10045 For_Body : Boolean := False) return Node_Id
10047 Formals : List_Id;
10049 begin
10050 -- V : in out Tag_Typ
10052 Formals := New_List (
10053 Make_Parameter_Specification (Loc,
10054 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
10055 In_Present => True,
10056 Out_Present => True,
10057 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)));
10059 -- F : Boolean := True
10061 if Name = TSS_Deep_Adjust
10062 or else Name = TSS_Deep_Finalize
10063 then
10064 Append_To (Formals,
10065 Make_Parameter_Specification (Loc,
10066 Defining_Identifier => Make_Defining_Identifier (Loc, Name_F),
10067 Parameter_Type => New_Occurrence_Of (Standard_Boolean, Loc),
10068 Expression => New_Occurrence_Of (Standard_True, Loc)));
10069 end if;
10071 return
10072 Predef_Spec_Or_Body (Loc,
10073 Name => Make_TSS_Name (Tag_Typ, Name),
10074 Tag_Typ => Tag_Typ,
10075 Profile => Formals,
10076 For_Body => For_Body);
10078 exception
10079 when RE_Not_Available =>
10080 return Empty;
10081 end Predef_Deep_Spec;
10083 -------------------------
10084 -- Predef_Spec_Or_Body --
10085 -------------------------
10087 function Predef_Spec_Or_Body
10088 (Loc : Source_Ptr;
10089 Tag_Typ : Entity_Id;
10090 Name : Name_Id;
10091 Profile : List_Id;
10092 Ret_Type : Entity_Id := Empty;
10093 For_Body : Boolean := False) return Node_Id
10095 Id : constant Entity_Id := Make_Defining_Identifier (Loc, Name);
10096 Spec : Node_Id;
10098 begin
10099 Set_Is_Public (Id, Is_Public (Tag_Typ));
10101 -- The internal flag is set to mark these declarations because they have
10102 -- specific properties. First, they are primitives even if they are not
10103 -- defined in the type scope (the freezing point is not necessarily in
10104 -- the same scope). Second, the predefined equality can be overridden by
10105 -- a user-defined equality, no body will be generated in this case.
10107 Set_Is_Internal (Id);
10109 if not Debug_Generated_Code then
10110 Set_Debug_Info_Off (Id);
10111 end if;
10113 if No (Ret_Type) then
10114 Spec :=
10115 Make_Procedure_Specification (Loc,
10116 Defining_Unit_Name => Id,
10117 Parameter_Specifications => Profile);
10118 else
10119 Spec :=
10120 Make_Function_Specification (Loc,
10121 Defining_Unit_Name => Id,
10122 Parameter_Specifications => Profile,
10123 Result_Definition => New_Occurrence_Of (Ret_Type, Loc));
10124 end if;
10126 if Is_Interface (Tag_Typ) then
10127 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
10129 -- If body case, return empty subprogram body. Note that this is ill-
10130 -- formed, because there is not even a null statement, and certainly not
10131 -- a return in the function case. The caller is expected to do surgery
10132 -- on the body to add the appropriate stuff.
10134 elsif For_Body then
10135 return Make_Subprogram_Body (Loc, Spec, Empty_List, Empty);
10137 -- For the case of an Input attribute predefined for an abstract type,
10138 -- generate an abstract specification. This will never be called, but we
10139 -- need the slot allocated in the dispatching table so that attributes
10140 -- typ'Class'Input and typ'Class'Output will work properly.
10142 elsif Is_TSS (Name, TSS_Stream_Input)
10143 and then Is_Abstract_Type (Tag_Typ)
10144 then
10145 return Make_Abstract_Subprogram_Declaration (Loc, Spec);
10147 -- Normal spec case, where we return a subprogram declaration
10149 else
10150 return Make_Subprogram_Declaration (Loc, Spec);
10151 end if;
10152 end Predef_Spec_Or_Body;
10154 -----------------------------
10155 -- Predef_Stream_Attr_Spec --
10156 -----------------------------
10158 function Predef_Stream_Attr_Spec
10159 (Loc : Source_Ptr;
10160 Tag_Typ : Entity_Id;
10161 Name : TSS_Name_Type;
10162 For_Body : Boolean := False) return Node_Id
10164 Ret_Type : Entity_Id;
10166 begin
10167 if Name = TSS_Stream_Input then
10168 Ret_Type := Tag_Typ;
10169 else
10170 Ret_Type := Empty;
10171 end if;
10173 return
10174 Predef_Spec_Or_Body
10175 (Loc,
10176 Name => Make_TSS_Name (Tag_Typ, Name),
10177 Tag_Typ => Tag_Typ,
10178 Profile => Build_Stream_Attr_Profile (Loc, Tag_Typ, Name),
10179 Ret_Type => Ret_Type,
10180 For_Body => For_Body);
10181 end Predef_Stream_Attr_Spec;
10183 ---------------------------------
10184 -- Predefined_Primitive_Bodies --
10185 ---------------------------------
10187 function Predefined_Primitive_Bodies
10188 (Tag_Typ : Entity_Id;
10189 Renamed_Eq : Entity_Id) return List_Id
10191 Loc : constant Source_Ptr := Sloc (Tag_Typ);
10192 Res : constant List_Id := New_List;
10193 Decl : Node_Id;
10194 Prim : Elmt_Id;
10195 Eq_Needed : Boolean;
10196 Eq_Name : Name_Id;
10197 Ent : Entity_Id;
10199 pragma Warnings (Off, Ent);
10201 begin
10202 pragma Assert (not Is_Interface (Tag_Typ));
10204 -- See if we have a predefined "=" operator
10206 if Present (Renamed_Eq) then
10207 Eq_Needed := True;
10208 Eq_Name := Chars (Renamed_Eq);
10210 -- If the parent is an interface type then it has defined all the
10211 -- predefined primitives abstract and we need to check if the type
10212 -- has some user defined "=" function which matches the profile of
10213 -- the Ada predefined equality operator to avoid generating it.
10215 elsif Is_Interface (Etype (Tag_Typ)) then
10216 Eq_Needed := True;
10217 Eq_Name := Name_Op_Eq;
10219 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10220 while Present (Prim) loop
10221 if Chars (Node (Prim)) = Name_Op_Eq
10222 and then not Is_Internal (Node (Prim))
10223 and then Present (First_Entity (Node (Prim)))
10225 -- The predefined equality primitive must have exactly two
10226 -- formals whose type is this tagged type
10228 and then Present (Last_Entity (Node (Prim)))
10229 and then Next_Entity (First_Entity (Node (Prim)))
10230 = Last_Entity (Node (Prim))
10231 and then Etype (First_Entity (Node (Prim))) = Tag_Typ
10232 and then Etype (Last_Entity (Node (Prim))) = Tag_Typ
10233 then
10234 Eq_Needed := False;
10235 Eq_Name := No_Name;
10236 exit;
10237 end if;
10239 Next_Elmt (Prim);
10240 end loop;
10242 else
10243 Eq_Needed := False;
10244 Eq_Name := No_Name;
10246 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10247 while Present (Prim) loop
10248 if Chars (Node (Prim)) = Name_Op_Eq
10249 and then Is_Internal (Node (Prim))
10250 then
10251 Eq_Needed := True;
10252 Eq_Name := Name_Op_Eq;
10253 exit;
10254 end if;
10256 Next_Elmt (Prim);
10257 end loop;
10258 end if;
10260 -- Body of _Size
10262 Decl := Predef_Spec_Or_Body (Loc,
10263 Tag_Typ => Tag_Typ,
10264 Name => Name_uSize,
10265 Profile => New_List (
10266 Make_Parameter_Specification (Loc,
10267 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10268 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10270 Ret_Type => Standard_Long_Long_Integer,
10271 For_Body => True);
10273 Set_Handled_Statement_Sequence (Decl,
10274 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10275 Make_Simple_Return_Statement (Loc,
10276 Expression =>
10277 Make_Attribute_Reference (Loc,
10278 Prefix => Make_Identifier (Loc, Name_X),
10279 Attribute_Name => Name_Size)))));
10281 Append_To (Res, Decl);
10283 -- Bodies for Dispatching stream IO routines. We need these only for
10284 -- non-limited types (in the limited case there is no dispatching).
10285 -- We also skip them if dispatching or finalization are not available
10286 -- or if stream operations are prohibited by restriction No_Streams or
10287 -- from use of pragma/aspect No_Tagged_Streams.
10289 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Read)
10290 and then No (TSS (Tag_Typ, TSS_Stream_Read))
10291 then
10292 Build_Record_Read_Procedure (Loc, Tag_Typ, Decl, Ent);
10293 Append_To (Res, Decl);
10294 end if;
10296 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Write)
10297 and then No (TSS (Tag_Typ, TSS_Stream_Write))
10298 then
10299 Build_Record_Write_Procedure (Loc, Tag_Typ, Decl, Ent);
10300 Append_To (Res, Decl);
10301 end if;
10303 -- Skip body of _Input for the abstract case, since the corresponding
10304 -- spec is abstract (see Predef_Spec_Or_Body).
10306 if not Is_Abstract_Type (Tag_Typ)
10307 and then Stream_Operation_OK (Tag_Typ, TSS_Stream_Input)
10308 and then No (TSS (Tag_Typ, TSS_Stream_Input))
10309 then
10310 Build_Record_Or_Elementary_Input_Function
10311 (Loc, Tag_Typ, Decl, Ent);
10312 Append_To (Res, Decl);
10313 end if;
10315 if Stream_Operation_OK (Tag_Typ, TSS_Stream_Output)
10316 and then No (TSS (Tag_Typ, TSS_Stream_Output))
10317 then
10318 Build_Record_Or_Elementary_Output_Procedure (Loc, Tag_Typ, Decl, Ent);
10319 Append_To (Res, Decl);
10320 end if;
10322 -- Ada 2005: Generate bodies for the following primitive operations for
10323 -- limited interfaces and synchronized types that implement a limited
10324 -- interface.
10326 -- disp_asynchronous_select
10327 -- disp_conditional_select
10328 -- disp_get_prim_op_kind
10329 -- disp_get_task_id
10330 -- disp_timed_select
10332 -- The interface versions will have null bodies
10334 -- Disable the generation of these bodies if No_Dispatching_Calls,
10335 -- Ravenscar or ZFP is active.
10337 -- In VM targets we define these primitives in all root tagged types
10338 -- that are not interface types. Done because in VM targets we don't
10339 -- have secondary dispatch tables and any derivation of Tag_Typ may
10340 -- cover limited interfaces (which always have these primitives since
10341 -- they may be ancestors of synchronized interface types).
10343 if Ada_Version >= Ada_2005
10344 and then not Is_Interface (Tag_Typ)
10345 and then
10346 ((Is_Interface (Etype (Tag_Typ))
10347 and then Is_Limited_Record (Etype (Tag_Typ)))
10348 or else
10349 (Is_Concurrent_Record_Type (Tag_Typ)
10350 and then Has_Interfaces (Tag_Typ))
10351 or else
10352 (not Tagged_Type_Expansion
10353 and then Tag_Typ = Root_Type (Tag_Typ)))
10354 and then not Restriction_Active (No_Dispatching_Calls)
10355 and then not Restriction_Active (No_Select_Statements)
10356 and then RTE_Available (RE_Select_Specific_Data)
10357 then
10358 Append_To (Res, Make_Disp_Asynchronous_Select_Body (Tag_Typ));
10359 Append_To (Res, Make_Disp_Conditional_Select_Body (Tag_Typ));
10360 Append_To (Res, Make_Disp_Get_Prim_Op_Kind_Body (Tag_Typ));
10361 Append_To (Res, Make_Disp_Get_Task_Id_Body (Tag_Typ));
10362 Append_To (Res, Make_Disp_Requeue_Body (Tag_Typ));
10363 Append_To (Res, Make_Disp_Timed_Select_Body (Tag_Typ));
10364 end if;
10366 if not Is_Limited_Type (Tag_Typ) and then not Is_Interface (Tag_Typ) then
10368 -- Body for equality
10370 if Eq_Needed then
10371 Decl := Make_Eq_Body (Tag_Typ, Eq_Name);
10372 Append_To (Res, Decl);
10373 end if;
10375 -- Body for inequality (if required)
10377 Decl := Make_Neq_Body (Tag_Typ);
10379 if Present (Decl) then
10380 Append_To (Res, Decl);
10381 end if;
10383 -- Body for dispatching assignment
10385 Decl :=
10386 Predef_Spec_Or_Body (Loc,
10387 Tag_Typ => Tag_Typ,
10388 Name => Name_uAssign,
10389 Profile => New_List (
10390 Make_Parameter_Specification (Loc,
10391 Defining_Identifier => Make_Defining_Identifier (Loc, Name_X),
10392 Out_Present => True,
10393 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc)),
10395 Make_Parameter_Specification (Loc,
10396 Defining_Identifier => Make_Defining_Identifier (Loc, Name_Y),
10397 Parameter_Type => New_Occurrence_Of (Tag_Typ, Loc))),
10398 For_Body => True);
10400 Set_Handled_Statement_Sequence (Decl,
10401 Make_Handled_Sequence_Of_Statements (Loc, New_List (
10402 Make_Assignment_Statement (Loc,
10403 Name => Make_Identifier (Loc, Name_X),
10404 Expression => Make_Identifier (Loc, Name_Y)))));
10406 Append_To (Res, Decl);
10407 end if;
10409 -- Generate empty bodies of routines Deep_Adjust and Deep_Finalize for
10410 -- tagged types which do not contain controlled components.
10412 -- Do not generate the routines if finalization is disabled
10414 if Restriction_Active (No_Finalization) then
10415 null;
10417 elsif not Has_Controlled_Component (Tag_Typ) then
10418 if not Is_Limited_Type (Tag_Typ) then
10419 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Adjust, True);
10421 if Is_Controlled (Tag_Typ) then
10422 Set_Handled_Statement_Sequence (Decl,
10423 Make_Handled_Sequence_Of_Statements (Loc,
10424 Statements => New_List (
10425 Make_Adjust_Call (
10426 Obj_Ref => Make_Identifier (Loc, Name_V),
10427 Typ => Tag_Typ))));
10429 else
10430 Set_Handled_Statement_Sequence (Decl,
10431 Make_Handled_Sequence_Of_Statements (Loc,
10432 Statements => New_List (
10433 Make_Null_Statement (Loc))));
10434 end if;
10436 Append_To (Res, Decl);
10437 end if;
10439 Decl := Predef_Deep_Spec (Loc, Tag_Typ, TSS_Deep_Finalize, True);
10441 if Is_Controlled (Tag_Typ) then
10442 Set_Handled_Statement_Sequence (Decl,
10443 Make_Handled_Sequence_Of_Statements (Loc,
10444 Statements => New_List (
10445 Make_Final_Call
10446 (Obj_Ref => Make_Identifier (Loc, Name_V),
10447 Typ => Tag_Typ))));
10449 else
10450 Set_Handled_Statement_Sequence (Decl,
10451 Make_Handled_Sequence_Of_Statements (Loc,
10452 Statements => New_List (Make_Null_Statement (Loc))));
10453 end if;
10455 Append_To (Res, Decl);
10456 end if;
10458 return Res;
10459 end Predefined_Primitive_Bodies;
10461 ---------------------------------
10462 -- Predefined_Primitive_Freeze --
10463 ---------------------------------
10465 function Predefined_Primitive_Freeze
10466 (Tag_Typ : Entity_Id) return List_Id
10468 Res : constant List_Id := New_List;
10469 Prim : Elmt_Id;
10470 Frnodes : List_Id;
10472 begin
10473 Prim := First_Elmt (Primitive_Operations (Tag_Typ));
10474 while Present (Prim) loop
10475 if Is_Predefined_Dispatching_Operation (Node (Prim)) then
10476 Frnodes := Freeze_Entity (Node (Prim), Tag_Typ);
10478 if Present (Frnodes) then
10479 Append_List_To (Res, Frnodes);
10480 end if;
10481 end if;
10483 Next_Elmt (Prim);
10484 end loop;
10486 return Res;
10487 end Predefined_Primitive_Freeze;
10489 -------------------------
10490 -- Stream_Operation_OK --
10491 -------------------------
10493 function Stream_Operation_OK
10494 (Typ : Entity_Id;
10495 Operation : TSS_Name_Type) return Boolean
10497 Has_Predefined_Or_Specified_Stream_Attribute : Boolean := False;
10499 begin
10500 -- Special case of a limited type extension: a default implementation
10501 -- of the stream attributes Read or Write exists if that attribute
10502 -- has been specified or is available for an ancestor type; a default
10503 -- implementation of the attribute Output (resp. Input) exists if the
10504 -- attribute has been specified or Write (resp. Read) is available for
10505 -- an ancestor type. The last condition only applies under Ada 2005.
10507 if Is_Limited_Type (Typ) and then Is_Tagged_Type (Typ) then
10508 if Operation = TSS_Stream_Read then
10509 Has_Predefined_Or_Specified_Stream_Attribute :=
10510 Has_Specified_Stream_Read (Typ);
10512 elsif Operation = TSS_Stream_Write then
10513 Has_Predefined_Or_Specified_Stream_Attribute :=
10514 Has_Specified_Stream_Write (Typ);
10516 elsif Operation = TSS_Stream_Input then
10517 Has_Predefined_Or_Specified_Stream_Attribute :=
10518 Has_Specified_Stream_Input (Typ)
10519 or else
10520 (Ada_Version >= Ada_2005
10521 and then Stream_Operation_OK (Typ, TSS_Stream_Read));
10523 elsif Operation = TSS_Stream_Output then
10524 Has_Predefined_Or_Specified_Stream_Attribute :=
10525 Has_Specified_Stream_Output (Typ)
10526 or else
10527 (Ada_Version >= Ada_2005
10528 and then Stream_Operation_OK (Typ, TSS_Stream_Write));
10529 end if;
10531 -- Case of inherited TSS_Stream_Read or TSS_Stream_Write
10533 if not Has_Predefined_Or_Specified_Stream_Attribute
10534 and then Is_Derived_Type (Typ)
10535 and then (Operation = TSS_Stream_Read
10536 or else Operation = TSS_Stream_Write)
10537 then
10538 Has_Predefined_Or_Specified_Stream_Attribute :=
10539 Present
10540 (Find_Inherited_TSS (Base_Type (Etype (Typ)), Operation));
10541 end if;
10542 end if;
10544 -- If the type is not limited, or else is limited but the attribute is
10545 -- explicitly specified or is predefined for the type, then return True,
10546 -- unless other conditions prevail, such as restrictions prohibiting
10547 -- streams or dispatching operations. We also return True for limited
10548 -- interfaces, because they may be extended by nonlimited types and
10549 -- permit inheritance in this case (addresses cases where an abstract
10550 -- extension doesn't get 'Input declared, as per comments below, but
10551 -- 'Class'Input must still be allowed). Note that attempts to apply
10552 -- stream attributes to a limited interface or its class-wide type
10553 -- (or limited extensions thereof) will still get properly rejected
10554 -- by Check_Stream_Attribute.
10556 -- We exclude the Input operation from being a predefined subprogram in
10557 -- the case where the associated type is an abstract extension, because
10558 -- the attribute is not callable in that case, per 13.13.2(49/2). Also,
10559 -- we don't want an abstract version created because types derived from
10560 -- the abstract type may not even have Input available (for example if
10561 -- derived from a private view of the abstract type that doesn't have
10562 -- a visible Input), but a VM such as .NET or the Java VM can treat the
10563 -- operation as inherited anyway, and we don't want an abstract function
10564 -- to be (implicitly) inherited in that case because it can lead to a VM
10565 -- exception.
10567 -- Do not generate stream routines for type Finalization_Master because
10568 -- a master may never appear in types and therefore cannot be read or
10569 -- written.
10571 return
10572 (not Is_Limited_Type (Typ)
10573 or else Is_Interface (Typ)
10574 or else Has_Predefined_Or_Specified_Stream_Attribute)
10575 and then
10576 (Operation /= TSS_Stream_Input
10577 or else not Is_Abstract_Type (Typ)
10578 or else not Is_Derived_Type (Typ))
10579 and then not Has_Unknown_Discriminants (Typ)
10580 and then not
10581 (Is_Interface (Typ)
10582 and then
10583 (Is_Task_Interface (Typ)
10584 or else Is_Protected_Interface (Typ)
10585 or else Is_Synchronized_Interface (Typ)))
10586 and then not Restriction_Active (No_Streams)
10587 and then not Restriction_Active (No_Dispatch)
10588 and then No (No_Tagged_Streams_Pragma (Typ))
10589 and then not No_Run_Time_Mode
10590 and then RTE_Available (RE_Tag)
10591 and then No (Type_Without_Stream_Operation (Typ))
10592 and then RTE_Available (RE_Root_Stream_Type)
10593 and then not Is_RTE (Typ, RE_Finalization_Master);
10594 end Stream_Operation_OK;
10596 end Exp_Ch3;